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

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

multiplied black_carbon with veget_max; add veget_max as an argument of fire (with N.Vuichard)

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