source: tags/ORCHIDEE_1_9_5_2/ORCHIDEE/src_stomate/lpj_fire.f90 @ 404

Last change on this file since 404 was 186, checked in by martial.mancip, 13 years ago

First steps to DGVM for Merge version. This won't compile. I lock the trunk. Martial.

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