source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/lpj_fire.f90 @ 64

Last change on this file since 64 was 64, checked in by didier.solyga, 14 years ago

Import first version of ORCHIDEE_EXT

File size: 18.3 KB
RevLine 
[64]1! calculate fire extent and impact on plants.
2! This is treated on a pseudo-daily basis (fireindex has a long-term memory).
3! We only take into account the natural litter.
4! Grasses are totally burned.
5! When the vegetation is dynamic, it also decreases the density of individuals.
6! Fire burns litter on the ground.
7!
8! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/lpj_fire.f90,v 1.12 2010/04/06 15:44:01 ssipsl Exp $
9! IPSL (2006)
10!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
11!
12MODULE lpj_fire
13
14  ! modules used:
15
16  USE ioipsl
17  USE stomate_data
18  USE parallel
19  USE pft_parameters
20  USE constantes
21
22  IMPLICIT NONE
23
24  ! private & public routines
25
26  PRIVATE
27  PUBLIC fire,fire_clear
28
29  ! first call
30  LOGICAL, SAVE                                                   :: firstcall = .TRUE.
31  ! flag that disable fire
32  LOGICAL, SAVE                                                   :: disable_fire
33
34CONTAINS
35
36
37  SUBROUTINE fire_clear
38    firstcall = .TRUE.
39  END SUBROUTINE fire_clear
40
41  SUBROUTINE fire (npts, dt, litterpart, &
42       litterhum_daily, t2m_daily, lignin_struc, &
43       fireindex, firelitter, biomass, ind, &
44       litter, dead_leaves, bm_to_litter, black_carbon, &
45       co2_fire)
46
47    !
48    ! 0 declarations
49    !
50
51    ! 0.1 input
52
53    ! Domain size
54    INTEGER(i_std), INTENT(in)                                             :: npts
55    ! Time step in days
56    REAL(r_std), INTENT(in)                                          :: dt
57    ! fraction of litter above the ground belonging to different PFTs
58    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(in)              :: litterpart
59    ! Daily litter moisture (between 0 and 1)
60    REAL(r_std), DIMENSION(npts), INTENT(in)                         :: litterhum_daily
61    ! Daily 2 meter temperature (K)
62    REAL(r_std), DIMENSION(npts), INTENT(in)                         :: t2m_daily
63    ! ratio Lignine/Carbon in structural litter, above and below ground,
64    ! (gC/(m**2 of ground))
65    REAL(r_std), DIMENSION(npts,nvm,nlevs), INTENT(in)         :: lignin_struc
66
67    ! 0.2 modified fields
68
69    ! Probability of fire
70    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: fireindex
71    ! Longer term total natural litter above the ground, gC/m**2 of natural ground
72    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: firelitter
73    ! biomass (gC/m**2)
74    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: biomass
75    ! density of individuals (1/m**2)
76    REAl(r_std), DIMENSION(npts,nvm), INTENT(inout)                 :: ind
77    ! metabolic and structural litter, above and below ground (gC/m**2)
78    REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs), INTENT(inout):: litter
79    ! dead leaves on ground, per PFT, metabolic and structural,
80    !   in gC/(m**2 of ground)
81    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)           :: dead_leaves
82    ! conversion of biomass to litter (gC/(m**2 of average ground)) / day
83    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(inout)          :: bm_to_litter
84    ! black carbon on the ground (gC/(m**2 of total ground))
85    REAL(r_std), DIMENSION(npts), INTENT(inout)                      :: black_carbon
86
87    ! 0.3 output
88
89    ! carbon emitted into the atmosphere by fire (living and dead biomass)
90    ! (in gC/m**2/day)
91    !NV devient 2D
92    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                        :: co2_fire
93
94    ! 0.4 local
95
96    ! Time scale for memory of the fire index (days). Validated for one year in the DGVM.
97    !MM Shilong ??
98!!$    REAL(r_std), PARAMETER                                           :: tau_fire = 365.  ! GKtest
99
100    ! fire perturbation
101    REAL(r_std), DIMENSION(npts)                                     :: fire_disturb
102    ! what fraction of the plants is burned each day?
103    REAL(r_std), DIMENSION(npts,nvm)                                :: firedeath 
104    ! Moisture limit (critical moisture limit)
105    REAL(r_std), DIMENSION(npts)                                     :: moistlimit
106    ! total litter above the ground for a vegetation type (gC/m**2)
107    REAL(r_std), DIMENSION(npts)                                     :: litter_above
108    ! daily fire index
109    REAL(r_std), DIMENSION(npts,nvm)                           :: fireindex_daily
110    ! fire extent, on ground
111    REAL(r_std), DIMENSION(npts, nvm)                          :: firefrac
112    ! residual fraction of exposed structural litter, depending on lignin fraction
113    REAL(r_std), DIMENSION(npts)                                     :: struc_residual
114    ! residue, i.e. exposed carbon - volatilized carbon ( gC/(m**2 of ground))
115    REAL(r_std), DIMENSION(npts)                                     :: residue
116    ! fraction of residue transformed into black carbon
117    REAL(r_std), DIMENSION(npts)                                     :: bcfrac
118    ! intermediate variable
119    REAL(r_std), DIMENSION(npts)                                     :: x
120    ! annual fire fraction
121    REAL(r_std), DIMENSION(npts)                                     :: aff
122    ! index
123    INTEGER(i_std)                                                  :: j,k,m
124
125    ! =========================================================================
126
127    IF (bavard.GE.3) WRITE(numout,*) 'Entering fire'
128
129    !
130    ! 1 Initializations
131    !
132
133    IF ( firstcall ) THEN
134
135       !
136       ! 1.1  messages
137       !
138
139       WRITE(numout,*) 'fire:'
140
141       WRITE(numout,*) '   > temporal inertia of fire probability (d): ',tau_fire
142
143       WRITE(numout,*) '   > fraction of burned biomass that becomes CO2:'
144       WRITE(numout,*) '     leaves: ', co2frac(ileaf)
145       WRITE(numout,*) '     sap above ground: ', co2frac(isapabove)
146       WRITE(numout,*) '     sap below ground: ', co2frac(isapbelow)
147       WRITE(numout,*) '     heartwood above ground: ', co2frac(iheartabove)
148       WRITE(numout,*) '     heartwood below ground: ', co2frac(iheartbelow)
149       WRITE(numout,*) '     roots: ', co2frac(iroot)
150       WRITE(numout,*) '     fruits: ', co2frac(ifruit)
151       WRITE(numout,*) '     carbohydrate reserve: ', co2frac(icarbres)
152
153       WRITE(numout,*) '   > critical litter quantity (gC/m**2): ',litter_crit
154       WRITE(numout,*) '   > We calculate a fire probability on agricultural ground, but'
155       WRITE(numout,*) '       the effective fire fraction is zero.'
156
157       firstcall = .FALSE.
158       !
159       ! 1.3 read the flag that disable fire
160       !
161       !Config  Key  = FIRE_DISABLE
162       !Config  Desc = no fire allowed
163       !Config  Def  = n
164       !Config  Help = With this variable, you can allow or not
165       !Config         the estimation of CO2 lost by fire
166       !
167       disable_fire=.FALSE.
168       CALL getin_p('FIRE_DISABLE', disable_fire)
169    ENDIF
170
171    !
172    ! 1.4 Initialize output
173    !
174
175    co2_fire(:,:) = zero
176    firedeath(:,:) = zero
177    fireindex_daily(:,:) = zero
178    firefrac(:,:) = zero
179
180    !
181    ! 2 Determine fire probability. We calculate this probability (and long-term litter)
182    !   also for agricultural ground, but the fire fraction on agricultural ground is set
183    !   to 0 for the moment.
184    !
185
186
187    DO j = 2,nvm
188
189       ! total litter above the ground, for the vegetation type we are talking about
190
191       litter_above(:) = litter(:,imetabolic,j,iabove) + &
192            litter(:,istructural,j,iabove)
193
194       !
195       ! 2.1 calculate moisture limit. If it stays 0, this means that there is no litter
196       !     on the ground, and this means that there can be no fore.
197       !     Sum over different litter parts from the various PFTs, taking into account the
198       !       litter flamability which is a function of the PFT.
199       !     Difference to Stephen Sitch's approach: Daily litter, not annual mean.
200       !     Reason: 1. seems more reasonable.
201       !             2. easier to implement (otherwise, would need moisture limit
202       !                from previous year)
203       !
204
205       moistlimit(:) = zero
206
207       WHERE ( (t2m_daily(:) .GT. ZeroCelsius) .AND. (litter_above(:) .GT. min_stomate) )
208
209          moistlimit(:) = &
210               ( litterpart(:,j,imetabolic)*litter(:,imetabolic,j,iabove) + &
211               litterpart(:,j,istructural)*litter(:,istructural,j,iabove)  ) / &
212               litter_above(:) * flam(j)
213
214       ENDWHERE
215
216       !
217       ! 2.2 daily fire index.
218       !
219       WHERE ( moistlimit(:) .GT. min_stomate )
220
221          ! is a function of litter humidity. Very sensible to STOMATE's time step as
222          ! with larger dt, one misses dry days with very high fireindex ( strongly
223          ! nonlinear: exp(-x^2)! )
224
225          x(:) = litterhum_daily(:)/moistlimit(:)
226          fireindex_daily(:,j) = EXP( - pi * x(:) * x(:) )
227
228       ELSEWHERE
229
230          fireindex_daily(:,j) = zero
231
232       ENDWHERE
233
234       !
235       ! 2.3 increase long-term fire index (mean probability)
236       !
237
238       fireindex(:,j) = ((tau_fire - dt) * fireindex(:,j) + (dt) * fireindex_daily(:,j)) / tau_fire
239
240       !
241       ! 2.4 litter influences fire intensity.
242       !     We use longer-term litter to be consistent with the fire index.
243       !
244
245       firelitter(:,j) = &
246            ( ( tau_fire-dt ) * firelitter(:,j) + dt * litter_above(:) ) / tau_fire
247
248
249       !
250       ! 3 Calculate fire fraction from litter and fireindex (i.e. basically drought)
251
252       !
253       ! 3.1 natural ground
254       !
255
256       !     This formulation has been developped for annual fire indices!
257       !     original form: firefrac(i) = fireindex(i) * EXP( f(fireindex(i)) )
258       !     Transform into daily fire fraction.
259
260       ! annual fire fraction
261
262       aff(:) = firefrac_func (npts, fireindex(:,j))
263
264       ! transform from annual fraction to daily fraction.
265       ! annual fire fraction = 1. - (fraction of tree that survives each day) ** 365 =
266       !                      = 1. - ( 1. - daily fire fraction )**365
267       ! Thus, daily fire fraction = 1. - ( 1. - annual fire fraction )**(1/365)
268       ! If annual firefrac<<1, then firefrac_daily = firefrac * dt/one_year
269       ! This approximation avoids numerical problems.
270
271       IF(.NOT.disable_fire.AND.natural(j))THEN
272          WHERE ( aff(:) .GT. 0.1 )
273             firefrac(:,j) = 1. - ( 1. - aff(:) ) ** (dt/one_year)
274          ELSEWHERE
275             firefrac(:,j) = aff(:) * dt/one_year
276          ENDWHERE
277       ELSE
278          firefrac(:,j) = zero
279       ENDIF
280
281       ! No fire if litter is below critical value
282
283       WHERE ( firelitter(:,j) .LT. litter_crit )
284          firefrac(:,j) = zero
285       ENDWHERE
286
287       ! However, there is a minimum fire extent
288
289       firefrac(:,j) = MAX( 0.001_r_std * dt/one_year, firefrac(:,j) )
290
291       ! if FIRE_DISABLE flag is set no fire
292       IF (disable_fire) firefrac=0
293       !
294       ! 3.2 agricultural ground: no fire for the moment
295       !
296
297       IF ( .NOT. natural(j)) firefrac(:,j) = zero
298
299       !
300       ! 4 Determine fire impact: calculate fire disturbance for each PFT
301       !
302
303       !
304       ! 4.1 are we talking about a natural or an agricultural PFT?
305       !
306
307       !
308       ! 4.2 fire disturbance
309       !
310
311       IF ( tree(j) ) THEN
312
313          ! 4.2.1 Trees: always disturbed
314
315          fire_disturb(:) = ( 1. - resist(j) ) * firefrac(:,j)
316
317       ELSE
318
319          ! 4.2.2 Grasses are not disturbed if they are not in their growing season
320
321          WHERE ( biomass(:,j,ileaf) .GT. min_stomate )
322
323             fire_disturb(:) = ( 1. - resist(j) ) * firefrac(:,j)
324
325          ELSEWHERE
326
327             fire_disturb(:) = zero
328
329          ENDWHERE
330
331       ENDIF
332
333       !
334       ! 4.3 litter and co2 created through fire on living biomass
335       !
336
337       ! biomass can go into litter or atmosphere, depending on what plant compartment
338       ! we are talking about.
339
340       DO k = 1, nparts
341
342          ! grass roots and reserve survive.
343
344          IF ( .NOT. ( ( .NOT. tree(j) ) .AND. ( ( k.EQ.iroot ) .OR. ( k.EQ.icarbres ) ) ) ) THEN
345
346             ! 4.3.1 A fraction goes directly into the atmosphere.
347             !       CO2 flux in gC/m**2 of total ground/day.
348             !NV passe en 2D           
349             co2_fire(:,j) =  co2_fire(:,j)+ biomass(:,j,k) * fire_disturb(:) * co2frac(k) / dt
350
351             ! 4.3.2 Determine the residue, in gC/m**2 of ground.
352
353             residue(:) = biomass(:,j,k) * fire_disturb(:) * ( 1. - co2frac(k) )
354             !MM in SZ ???        residue(:) = fire_disturb(:) * ( 1. - co2frac(k) )
355
356             ! 4.3.2.1 determine fraction of black carbon. Only for plant parts above the
357             !         ground, i.e. when co2_frac > 0.
358             !         A small part of the residue, which can be expressed as a function of
359             !         the fraction of volatilized carbon (assimilated to co2frac here),
360             !         becomes black carbon, and thus withdrawn from the soil carbon cycle (added
361             !         to the "geologic carbon cycle we don't care about here).
362             !         [Kuhlbusch et al. JGR 101, 23651-23665, 1996; Kuhlbusch & Crutzen, GBC 9,
363             !          491-501, 1995].
364
365             !             IF ( co2frac(k) .GT. min_stomate ) THEN
366             IF ( co2frac(k) .GT. zero ) THEN
367                bcfrac(:) = bcfrac_coeff(1) / ( bcfrac_coeff(2) ** ( bcfrac_coeff(3) - 100.*co2frac(k) ) + 1. )
368             ELSE
369                bcfrac(:) = zero
370             ENDIF
371
372             ! 4.3.2.2 Add this fraction of the residue to the black carbon "reservoir", in
373             !         gC/(m**2 of total ground).
374
375             black_carbon(:) = &
376                  black_carbon(:) + bcfrac(:) * residue(:)
377             !MM in SZ                  black_carbon(:) + bcfrac(:) * residue(:) * biomass(:,j,k)
378
379             ! 4.3.2.3 The rest (largest part) of the residue becomes litter.
380             bm_to_litter(:,j,k) = bm_to_litter(:,j,k) + residue(:) * ( 1 - bcfrac(:) )
381             !MM in SZ   bm_to_litter(:,j,k) = bm_to_litter(:,j,k) + residue(:) * ( 1 - bcfrac(:) ) * biomass(:,j,k)
382          ENDIF  ! not for grass roots
383
384       ENDDO
385
386       !
387       ! 4.4 new vegetation characteristics
388       !
389
390       ! 4.4.1 decrease biomass per m**2 of ground
391       !       except for grass roots.
392
393       DO k = 1, nparts
394
395          IF ( .NOT. ( ( .NOT. tree(j) ) .AND. ( ( k.EQ.iroot ) .OR. ( k.EQ.icarbres) ) ) ) THEN
396
397             biomass(:,j,k) = ( 1. - fire_disturb(:) ) * biomass(:,j,k)
398
399          ENDIF
400
401       ENDDO
402
403       ! 4.4.2 If vegetation is dynamic, then decrease the density of tree
404       !       individuals.
405
406       IF ( control%ok_dgvm .AND. tree(j) ) THEN
407
408          ! fraction of plants that dies each day.
409          ! exact formulation: 1. - (1.-fire_disturb(:)) ** (1./dt)
410          firedeath(:,j) = fire_disturb(:) / dt
411
412          ind(:,j) = ( 1. - fire_disturb(:) ) * ind(:,j)
413
414       ENDIF
415
416    ENDDO      ! loop over PFTs
417
418    !
419    ! 5 A fraction of the litter is burned by the fire
420    !
421
422    DO j = 2,nvm
423
424       !
425       ! 5.1 exposed metabolic litter burns totally and goes directly into the atmosphere as
426       !     CO2.
427       !
428
429       ! 5.1.1 CO2 flux, in gC/(m**2 of total ground)/day.
430
431       co2_fire(:,j) = co2_fire(:,j) + litter(:,imetabolic,j,iabove) * &
432            firefrac(:,j) / dt
433
434       ! 5.1.2 decrease metabolic litter
435
436       litter(:,imetabolic,j,iabove) = litter(:,imetabolic,j,iabove) * &
437            ( 1. - firefrac(:,j) )
438
439       !
440       ! 5.2 exposed structural litter is not totally transformed into CO2.
441       !
442
443       ! 5.2.1 Fraction of exposed structural litter that does not
444       !       burn totally should depend on lignin content (lignin_struc). VERY TENTATIVE!
445
446       struc_residual(:) = 0.5 * lignin_struc(:,j,iabove)
447
448       ! 5.2.2 CO2 flux, in gC/(m**2 of total ground)/day.
449
450       co2_fire(:,j) = co2_fire(:,j) + &
451            litter(:,istructural,j,iabove) * firefrac(:,j) * &
452            ( 1. - struc_residual(:) )/ dt
453
454       ! 5.2.3 determine residue (litter that undergoes fire, but is not transformed
455       !       into CO2)
456
457       residue(:) = litter(:,istructural,j,iabove) * firefrac(:,j) * &
458            struc_residual(:)
459       !MM in SZ        residue(:) = firefrac(:,j) * struc_residual(:)
460
461       ! 5.2.4 determine fraction of black carbon in the residue.
462       !       depends on volatilized fraction of carbon (see 4.3.2.1)
463
464       bcfrac(:) = bcfrac_coeff(1)/ ( bcfrac_coeff(2) ** ( bcfrac_coeff(3) - 100.*(1.-struc_residual(:)) ) + 1. )
465
466       ! 5.2.5 Add this fraction of the residue to the black carbon "reservoir", in
467       !       gC/(m**2 of total ground).
468
469       black_carbon(:) = &
470            black_carbon(:) + bcfrac(:) * residue(:)
471       !MM in SZ             black_carbon(:) + bcfrac(:) * residue(:) * litter(:,iwoody,j,iabove)
472
473       ! 5.2.6 The rest (largest part) of the residue remains litter. Remaining litter
474       !       is the sum of this and of the litter which has not undergone a fire.
475
476       litter(:,istructural,j,iabove) = &
477            litter(:,istructural,j,iabove) * ( 1. - firefrac(:,j) ) + &
478            residue(:) * ( 1. - bcfrac(:) )
479       !MM in SZ            residue(:) * ( 1. - bcfrac(:) ) * litter(:,iwoody,j,iabove)
480
481    ENDDO  !  ground
482
483    !
484    ! 5.3 diagnose fraction of leaves burned.
485    !     exposed leaves are burned entirely, even their structural part
486    !
487
488    DO j = 2,nvm
489
490       DO k = 1, nlitt
491          dead_leaves(:,j,k) = dead_leaves(:,j,k) * ( 1. - firefrac(:,j) )
492       ENDDO
493
494    ENDDO
495
496    !
497    ! 6 history
498    !
499
500    ! output in 1/day
501    firefrac(:,:) = firefrac(:,:) / dt
502
503    CALL histwrite (hist_id_stomate, 'FIREFRAC', itime, &
504         firefrac(:,:), npts*nvm, horipft_index)
505    CALL histwrite (hist_id_stomate, 'FIREDEATH', itime, &
506         firedeath(:,:), npts*nvm, horipft_index)
507
508    IF (bavard.GE.4) WRITE(numout,*) 'Leaving fire'
509
510  END SUBROUTINE fire
511
512  FUNCTION firefrac_func (npts, x) RESULT (firefrac_result)
513
514    !
515    ! 0 declarations
516    !
517
518    ! 0.1 input
519
520    ! Domain size
521    INTEGER(i_std), INTENT(in)                                             :: npts
522    ! fire index
523    REAL(r_std), DIMENSION(npts), INTENT(in)                         :: x
524
525    ! 0.2 result
526
527    ! fire fraction
528    REAL(r_std), DIMENSION(npts)                                     :: firefrac_result
529
530    ! 0.3 local
531
532    ! intermediate variable
533    REAL(r_std), DIMENSION(npts)                                     :: xm1
534
535    xm1(:) = x(:) - 1.
536
537    firefrac_result(:) = &
538!         x(:) * EXP( xm1(:) / ( -.13*xm1(:)*xm1(:)*xm1(:) + .6*xm1(:)*xm1(:) + .8*xm1(:) + .45 ) )
539         x(:) * EXP( xm1(:) / ( -firefrac_coeff(4)*xm1(:)*xm1(:)*xm1(:) + firefrac_coeff(3)*xm1(:)*xm1(:) + firefrac_coeff(2)*xm1(:) + firefrac_coeff(1) ) )
540
541
542  END FUNCTION firefrac_func
543
544END MODULE lpj_fire
Note: See TracBrowser for help on using the repository browser.