source: branches/publications/ORCHIDEE-LEAK-r5919/src_stomate/lpj_fire.f90 @ 5925

Last change on this file since 5925 was 3550, checked in by bertrand.guenet, 8 years ago

update between the trunk rev 3340 and SOM it's still not working

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 27.2 KB
Line 
1! =================================================================================================================================
2! MODULE        : lpj_fire
3!
4! CONTACT       : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE       : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>\BRIEF         Calculates the probability of fire and its effects on the carbon cycle
9!!
10!!\n DESCRIPTION: None
11!!
12!! RECENT CHANGE(S): None
13!!
14!! SVN           :
15!! $HeadURL$
16!! $Date$
17!! $Revision$
18!! \n
19!_ ================================================================================================================================
20
21MODULE lpj_fire
22
23  ! modules used:
24  USE xios_orchidee
25  USE stomate_data
26  USE ioipsl_para 
27  USE pft_parameters
28  USE constantes
29  USE constantes_soil
30
31  IMPLICIT NONE
32
33  ! private & public routines
34
35  PRIVATE
36  PUBLIC fire,fire_clear
37
38  LOGICAL, SAVE                   :: firstcall_fire = .TRUE.        !! first call
39!$OMP THREADPRIVATE(firstcall_fire)
40
41CONTAINS
42
43
44!! ================================================================================================================================
45!!  SUBROUTINE   : fire_clear
46!!
47!>\BRIEF        Set the firstcall_fire flag to .TRUE. and activate initialization
48!!
49!_ ================================================================================================================================
50
51  SUBROUTINE fire_clear
52    firstcall_fire = .TRUE.
53  END SUBROUTINE fire_clear
54
55
56!! ================================================================================================================================
57!! SUBROUTINE     : fire
58!!
59!>\BRIEF          Calculate fire index and fraction of area burned by comparing
60!! daily litter moisture with prescribed moisture of fire inhibition. If daily
61!! moisture is below the precribed threshold, allow fire disturbance and
62!! calculate CO_2 emissions from fire. The main algorithm follows Thonicke et al.
63!! (2001)
64!!
65!! DESCRIPTION  : Fire occurs when the three basic prerequisites are met:
66!! sufficient fuel on the ground, relatively dry fuel (fuel moisture lower than
67!! the moisture of extinction), and presence of ignition sources.  The flag
68!! ::disable_fire is used to use this fire module or not. While here in the module the
69!! ignition source is not explicitely represented. It's assumed
70!! that the ignition source is always available, i.e., if a sufficient amount
71!! of dead fuel exists with a moisture content below the moisture of fire
72!! inhibition, then both live and dead fuel will start to burn.\n
73!!
74!! The module completes the following tasks:
75!! 1. Calculates daily fire index, long term fire index and available ground
76!! litter for burning.\n
77!! \latexonly
78!! \input{lpj_fire_1.tex} 
79!! \endlatexonly
80!! Where, m is the daily litter moisture, m_e is the moisture of extinction, p(m)
81!! is probability of fire (i.e. the daily fire index).\n
82!!
83!! \latexonly
84!! \input{lpj_fire_2.tex} 
85!! \endlatexonly
86!! Where, s is the long term fire index and A(s) is the annual fire fraction.\n
87!! 2. Calculates annual fire fraction, then transform to daily fraction in the
88!! same time step of stomate.\n
89!! 3. Ground litter and grass live biomass (in growing season and except root and carbon
90!! reserve pool) are  burned at full fire fraction.\n
91!! 4. Fire fraction for tree PFT are compromised by prescribed fire resistence.
92!! Tree live biomass are consumed using this compromised fire fraction and consumption
93!! fraction for different biomass parts. In the case of activation of dynamic
94!! vegetation, tree individual density is updated after fire. \n
95!! 5. For all types of fuel (either ground litter or live biomass) that are
96!! burned, there is a certain fraction of “residue” that are not completely
97!! burned. The remaining part is transferred to (in case of biomass) or
98!! remains (in case of ground litter) as litter.\n
99!! 6. Update the biomass, litter or dead leaves pool after burning.
100!!
101!! RECENT CHANGE(S): April 2015: Black carbon calculations is removed. The black carbon was not conserved.
102!!
103!! MAIN OUTPUT VARIABLE(S): ::co2_fire or the carbon emitted into the atmosphere
104!! by fire, including both living and dead biomass (gC m^{-2} dtslow^{-1})$ @endtex
105!!
106!! REFERENCES    :
107!! - Thonicke K., Venevsky S., Sitch S., and Cramer W. (2001) The role of fire
108!! disturbance for global vegetation dynamics: coupling fire into a Dynamic
109!! Global Vegetation Model, Global Ecology & Biogeography, 10, 661-677.
110!! - Kuhlbusch et al. JGR 101, 23651-23665, 1996
111!! - Kuhlbusch & Crutzen, GBC 9, 491-501, 1995
112!! - Lardy, R, et al., A new method to determine soil organic carbon equilibrium,
113!! Environmental Modelling & Software (2011), doi:10.1016|j.envsoft.2011.05.016
114!!
115!! FLOWCHART     : None
116!! \n
117!_ ================================================================================================================================
118 
119  SUBROUTINE fire (npts, dt, litterpart, &
120       litterhum_daily, t2m_daily, lignin_struc_above,veget_max, &
121       fireindex, firelitter, biomass, ind, &
122       litter_above, dead_leaves, bm_to_litter, &
123       co2_fire)
124
125  !! 0. Variable and parameter declarations
126
127    !! 0.1 Input variables
128   
129    INTEGER(i_std), INTENT(in)                                   :: npts                !! Domain size - number of pixels
130                                                                                        !! (unitless)   
131    REAL(r_std), INTENT(in)                                      :: dt                  !! Time step of the simulations for stomate
132                                                                                        !! (days)   
133    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(in)           :: litterpart          !! [DISPENSABLE] Fraction of litter above
134                                                                                        !! the ground belonging to different PFTs
135                                                                                        !! ?? this variable is used but might be
136                                                                                        !! redundant (with value of always 1) ??
137                                                                                        !! To check but probably litterpart to be
138                                                                                        !! removed. Probably a residual from
139                                                                                        !! nat/agri before merge   
140    REAL(r_std), DIMENSION(npts), INTENT(in)                     :: litterhum_daily     !! Daily litter moisture (unitless, 0-1)   
141    REAL(r_std), DIMENSION(npts), INTENT(in)                     :: t2m_daily           !! Daily 2 meter temperature (K)   
142    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                 :: lignin_struc_above        !! Ratio Lignin/Carbon in structural above
143                                                                                        !! and below ground litter
144                                                                                        !! @tex $(gC gC^{-1})$ @endtex
145    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                 :: veget_max           !! Maximum fraction of vegetation type including
146                                                                                        !! non-biological fraction (0-1, unitless)
147
148    !! 0.2 Output variables
149   
150    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: co2_fire            !! Carbon emitted into the atmosphere by
151                                                                                        !! fire, including both living and dead
152                                                                                        !! biomass
153                                                                                        !! @tex $(gC m^{-2} dtslow^{-1})$ @endtex
154    !! 0.3 Modified variables
155   
156    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)              :: fireindex           !! Probability of fire; in the code means
157                                                                                        !! long term fire index (unitless, 0-1)   
158    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)              :: firelitter          !! Total natural litter
159                                                                                        !! available for burning above the ground
160                                                                                        !! @tex $(gC m^{-2})$ @endtex
161    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout)  :: biomass        !! Biomass @tex $(gC m^{-2})$ @endtex
162    REAl(r_std), DIMENSION(npts,nvm), INTENT(inout)                   :: ind            !! Density of individuals
163                                                                                        !! @tex $(m^{-2})$ @endtex
164    REAL(r_std), DIMENSION(npts,nlitt,nvm,nelements), INTENT(inout) :: litter_above     !! Metabolic and structural litter, above
165                                                                                        !! and below ground
166                                                                                        !! @tex $(gC m^{-2})$ @endtex
167    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)        :: dead_leaves         !! Dead leaves on ground, per PFT,
168                                                                                        !! metabolic and structural
169                                                                                        !! @tex $(gC m^{-2})$ @endtex
170    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout):: bm_to_litter     !! Biomass entering the litter pool
171                                                                                        !! @tex $(gC m^{-2} dtslow^{-1})$ @endtex
172   
173
174    !! 0.4 Local variables
175
176    REAL(r_std), DIMENSION(npts)                                  :: fire_disturb       !! Actual fire disturbance fraction
177                                                                                        !! after consideration of inherent fire
178                                                                                        !! resistance of different PFTs
179                                                                                        !! (unitless, 0-1) 
180    REAL(r_std), DIMENSION(npts,nvm)                              :: firedeath          !! In case of activation of dynamic
181                                                                                        !! vegetation, the daily fraction of
182                                                                                        !! burned individuals (unitless, 0-1) 
183    REAL(r_std), DIMENSION(npts)                                  :: moistlimit         !! Moisture for fire inhibition per PFT                                                                                         !!
184                                                                                        !! (unitless, 0-1) ; temporary variable
185                                                                                        !! for each PFT in the loop over #PFT ?
186                                                                                        !! it's not fire inhibition, it's
187                                                                                        !! "moisture of extinction" by the original
188                                                                                        !! reference paper, and a more "fire
189                                                                                        !! professional name" it's better to change
190                                                                                        !! the name of moistlimit
191    REAL(r_std), DIMENSION(npts)                                  :: litter             !! Total aboveground litter per PFT                                                                                         !!
192                                                                                        !! @tex $(gC m^{-2})$ @endtex
193    REAL(r_std), DIMENSION(npts,nvm)                              :: fireindex_daily    !! Daily fire index (unitless, 0-1)
194    REAL(r_std), DIMENSION(npts, nvm)                             :: firefrac           !! Daily fire burning fraction on ground
195                                                                                        !! (unitless, 0-1)
196    REAL(r_std), DIMENSION(npts)                                  :: struc_residual     !! Fraction of structural litter not burned
197                                                                                        !! (thus residual), depending on strutural
198                                                                                        !! litter lignin content  (unitless, 0-1)
199    REAL(r_std), DIMENSION(npts)                                  :: residue            !! Fuel (either biomass or litter) not
200                                                                                        !! burned  @tex $(gC m^{-2})$ @endtex
201    REAL(r_std), DIMENSION(npts)                                  :: x                  !! Intermediate variable
202    REAL(r_std), DIMENSION(npts)                                  :: aff                !! Annual fire fraction (unitless, 0-1)
203    INTEGER(i_std)                                                :: j,k,m,l            !! Indeces
204!_ ================================================================================================================================
205
206    IF (printlev>=3) WRITE(numout,*) 'Entering fire'
207
208 !! 1. Initialization
209
210    IF ( firstcall_fire ) THEN
211
212       !! 1.1 Fraction to CO_2
213       !      What fraction of the plant biomass compartment, if burned, is transformed
214       !      into CO_2 released to the atmosphere?
215       !??! the fraction for heartabove seems too big, it's not clear if this value is correct.
216
217       !! 1.2 print control messages
218       WRITE(numout,*) 'fire:'
219
220       WRITE(numout,*) '   > temporal inertia of fire probability (d): ',tau_fire
221
222       WRITE(numout,*) '   > fraction of burned biomass that becomes CO2:'
223       WRITE(numout,*) '     leaves: ', co2frac(ileaf)
224       WRITE(numout,*) '     sap above ground: ', co2frac(isapabove)
225       WRITE(numout,*) '     sap below ground: ', co2frac(isapbelow)
226       WRITE(numout,*) '     heartwood above ground: ', co2frac(iheartabove)
227       WRITE(numout,*) '     heartwood below ground: ', co2frac(iheartbelow)
228       WRITE(numout,*) '     roots: ', co2frac(iroot)
229       WRITE(numout,*) '     fruits: ', co2frac(ifruit)
230       WRITE(numout,*) '     carbohydrate reserve: ', co2frac(icarbres)
231
232       WRITE(numout,*) '   > critical litter quantity (gC/m**2): ',litter_crit
233       WRITE(numout,*) '   > We calculate a fire probability on agricultural ground, but'
234       WRITE(numout,*) '       the effective fire fraction is zero.'
235
236       firstcall_fire = .FALSE.
237
238    ENDIF
239
240    !! 1.4 Initialize output
241    co2_fire(:,:) = zero
242    firedeath(:,:) = zero
243    fireindex_daily(:,:) = zero
244    firefrac(:,:) = zero
245
246 !! 2. Determine fire probability
247 
248    ! Calculate probability that crops are not burned for the moment
249    ! Calculate long-term aboveground litter
250 
251    ! a long loop over PFT
252    DO j = 2,nvm !loop over #PFT
253
254       !! 2.1 Total above ground litter
255       !      Total litter above the ground for the PFT under consideration
256       litter(:) = litter_above(:,imetabolic,j,icarbon) + &
257            litter_above(:,istructural,j,icarbon)
258
259       !! 2.2 Calculate the PFT litter amount weighted by moisture
260       ! If litter moisture is higher than moisture of extinction, fire is not possible.
261       moistlimit(:) = zero
262       WHERE ( (t2m_daily(:) .GT. ZeroCelsius) .AND. (litter(:) .GT. min_stomate) )
263       !?? the calculation here is redundant? as the part before flam(j) is 1?
264       !?? see first comment.. litterpart to be removed ?
265          moistlimit(:) = moistlimit(:) + &
266               ( litterpart(:,j,imetabolic)*litter_above(:,imetabolic,j,icarbon) + &
267               litterpart(:,j,istructural)*litter_above(:,istructural,j,icarbon)  ) / &
268               litter(:) * flam(j)
269
270       ENDWHERE
271       !! 2.3 Calculate daily fire index
272       !      Calculate daily fire index
273       !      \latexonly
274       !        \input{lpj_fire_1.tex} 
275       !      \endlatexonly
276       !      Where, m is the daily litter moisture, m_e is the moisture of extinction, p(m)
277       !      is probability of fire (i.e. the daily fire index).\n
278       WHERE ( moistlimit(:) .GT. min_stomate )
279          x(:) = litterhum_daily(:)/moistlimit(:)
280          fireindex_daily(:,j) = EXP( - pi * x(:) * x(:) )
281       ELSEWHERE
282          fireindex_daily(:,j) = zero
283       ENDWHERE
284
285       !! 2.4 Calculate long-term fire index
286       !      Calculate long-term fire index which is the mean probability of fire
287       fireindex(:,j) = ((tau_fire - dt) * fireindex(:,j) + (dt) * fireindex_daily(:,j)) / tau_fire
288
289       !! 2.5 Calculate long term aboveground litter that are available for burning
290       firelitter(:,j) = &
291            ( ( tau_fire-dt ) * firelitter(:,j) + dt * litter(:) ) / tau_fire
292
293  !! 3. Calculate fire fraction from litter and fireindex
294
295       !! 3.1 Fire fraction from long term fire index for natural PFTs
296       !  Transform the annual fire fraction to daily fraction. This is done by assuming that
297       !  each day the fire fraction is the same.
298       aff(:) = firefrac_func (npts, fireindex(:,j))
299
300       ! annual_fire_fraction = 1. - ( 1. - daily_fire_fraction )**365
301       ! Thus, daily_fire_fraction = 1. - ( 1. - annual_fire_fraction )**(1/365)
302       ! If annual firefrac<<1, then firefrac_daily = firefrac * dt/one_year
303       ! This approximation avoids numerical problems.
304       ! the variable 'un' is 1
305       IF(.NOT.disable_fire.AND.natural(j))THEN
306          WHERE ( aff(:) .GT. 0.1 )
307             firefrac(:,j) = un - ( un - aff(:) ) ** (dt/one_year)
308          ELSEWHERE
309             firefrac(:,j) = aff(:) * dt/one_year
310          ENDWHERE
311       ELSE
312          firefrac(:,j) = zero
313       ENDIF
314
315       ! No fire if litter is below critical value
316       WHERE ( firelitter(:,j) .LT. litter_crit )
317          firefrac(:,j) = zero
318       ENDWHERE
319
320       ! However, there is a minimum fire extent
321       firefrac(:,j) = MAX( 0.001_r_std * dt/one_year, firefrac(:,j) )
322
323       ! if FIRE_DISABLE flag is set no fire
324       IF (disable_fire) firefrac = zero
325       
326       !! 3.2 For agricultural ground, no fire is burned for the moment
327       IF ( .NOT. natural(j)) firefrac(:,j) = zero
328       
329  !! 4. Determine fire impact
330
331       ! Calculate fire disturbance fraction for each PFT, and fire emissions due
332       ! to grasses.
333   
334       !! 4.1 Tree and grass live biomass
335       ! Tree live biomass is not burned in fire.
336       ! However, in the dynamic vegetation module, tree individual density
337       ! will be updated after fire. The fraction of tree individuals that are
338       ! supposed to die in fire is the fire fraction multiplied by the tree PFT fire
339       ! resistance which reflect survivorship of different tree PFTs during fire. 
340       IF ( is_tree(j) ) THEN
341
342          !! 4.1.1 Disturban,ce factor for trees
343          !        Trees are disturbed over the whole year. A resistance factor is 
344          !        used to reflect survivorship of different tree PFTs during fire.
345          fire_disturb(:) = ( un - resist(j) ) * firefrac(:,j)
346
347       ELSE
348
349          !! 4.1.2 Disturbance factor for grasses
350          !        Grass is not disturbed outside the growing season thus grass biomass
351          !        is only burned during the growing season.
352          WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
353
354             fire_disturb(:) = ( un - resist(j) ) * firefrac(:,j)
355
356          ELSEWHERE
357
358             fire_disturb(:) = zero
359
360          ENDWHERE
361
362       ENDIF
363
364       !! 4.2 Burn live biomass
365       !      The burned part goes to either the atmposhere or litter
366       DO k = 1, nparts
367
368          ! for tree PFT, all biomass compartments are burned.
369          ! for grass biomass compartments, all are burned except root and carbon reserve
370          ! IF concerning PFT is tree; OR (the PFT is grass, but not root or carbon reserve biomass); then it's burned.
371          IF ( .NOT. ( ( .NOT. is_tree(j) ) .AND. ( ( k.EQ.iroot ) .OR. ( k.EQ.icarbres ) ) ) ) THEN
372
373             !! 4.2.1 Fraction to the atmosphere.
374             co2_fire(:,j) =  co2_fire(:,j)+ biomass(:,j,k,icarbon) * fire_disturb(:) * co2frac(k) / dt
375
376             !! 4.2.2 Determine the residue
377             !        Residual is expressed in gC/m^2
378             residue(:) = biomass(:,j,k,icarbon) * fire_disturb(:) * ( un - co2frac(k) )
379
380             !! 4.2.2.3 The rest (largest part) of the residue becomes litter.
381             bm_to_litter(:,j,k,icarbon) = bm_to_litter(:,j,k,icarbon) + residue(:)
382          ENDIF
383
384       ENDDO
385
386     
387       !! 4.3 Update biomass pool after burning
388       
389       !! 4.3.1 Decrease biomass amount except for grass roots and carbon reserve.
390       DO m = 1, nelements ! Loop over # elements
391         
392          DO k = 1, nparts
393
394             ! **2
395             IF ( .NOT. ( ( .NOT. is_tree(j) ) .AND. ( ( k.EQ.iroot ) .OR. ( k.EQ.icarbres) ) ) ) THEN
396               
397                biomass(:,j,k,m) = ( un - fire_disturb(:) ) * biomass(:,j,k,m)
398               
399             ENDIF
400
401          ENDDO
402         
403       END DO ! End Loop over # elements
404
405
406       !! 4.3.2 If vegetation is dynamic, then decrease the density of tree individuals.
407       IF ( (ok_dgvm .OR. .NOT.lpj_gap_const_mort) .AND. is_tree(j) ) THEN
408
409          firedeath(:,j) = fire_disturb(:) / dt
410
411          ind(:,j) = ( un - fire_disturb(:) ) * ind(:,j)
412
413       ENDIF
414
415    ENDDO      ! loop over #PFT
416
417  !! 5. Burn litter
418
419    !   All litter (either forest or grass) is burned throughout the whole year
420    !   Metabolic litter is totally burned. Burning fraction of structural litter is related
421    !   with its lignin content. The burned part either goes to the atmosphere
422    !   or remains in litter as unburned residue.
423    DO j = 2,nvm  !loop over #PFT
424
425       !! 5.1 Burn exposed metabolic litter
426       !      Exposed metabolic litter burns completely and goes directly into the atmosphere as CO2.
427
428       !! 5.1.1 CO2 flux from litter burning
429       !        Flux expressed in gC m^{-2}dtslow^{-1}
430       co2_fire(:,j) = co2_fire(:,j) + litter_above(:,imetabolic,j,icarbon) * &
431            firefrac(:,j) / dt
432       !! 5.1.2 Decrease metabolic litter
433         DO m = 1,nelements
434            litter_above(:,imetabolic,j,m) = litter_above(:,imetabolic,j,m) * &
435                 ( un - firefrac(:,j) )
436         ENDDO
437       !! 5.2 Burning exposed structural litter
438       !      The fraction that goes to the atmosphere is related to its lignin content. The remaining unburned
439       !      residues remain as litter.
440
441       !! 5.2.1 Incomplete burning of exposed structural litter 
442       !        Fraction of structural litter that does not burn completly. This fraction depends on lignin
443       !        content (lignin_struc).
444       struc_residual(:) = fire_resist_struct * lignin_struc_above(:,j) 
445
446       !! 5.2.2 CO2 flux from litter burning
447       !  Flux expressed in gC m^{-2}dtslow^{-1}
448       co2_fire(:,j) = co2_fire(:,j) + &
449            litter_above(:,istructural,j,icarbon) * firefrac(:,j) * &
450            ( un - struc_residual(:) )/ dt
451       !! 5.2.3 Determine residue
452       !        The residue is litter that undergoes fire, but is not transformed into CO2
453       residue(:) = litter_above(:,istructural,j,icarbon) * firefrac(:,j) * &
454            struc_residual(:)
455
456       !! 5.2.6 TResidue remaining litter
457       !        The rest (largest part) of the residue remains litter. Remaining
458       !        litter is the sum of this and of the litter which has not undergone a fire.
459       WHERE (veget_max(:,j) .GT. min_stomate)
460       litter_above(:,istructural,j,icarbon) = &
461            litter_above(:,istructural,j,icarbon) * ( un - firefrac(:,j) ) + &
462            residue(:)
463       ENDWHERE
464
465    ENDDO  !  loop over #PFT
466!WRITE (numout,*) "litter_above_#2_fire_PFT6=",litter_above(:,:,6,:)
467!WRITE (numout,*) "litter_above_#2_fire_PFT10=",litter_above(:,:,10,:)
468   
469   !! 5.3 Update exposed dead leaves (leaf litter) on the ground
470   !      Dead leaves are supposed to burn completely in fire even their structural part.
471    DO j = 2,nvm
472
473       DO k = 1, nlitt
474          dead_leaves(:,j,k) = dead_leaves(:,j,k) * ( un - firefrac(:,j) )
475       ENDDO
476
477    ENDDO
478
479  !! 6. write out history variables
480
481    ! output in 1/dtslow
482    firefrac(:,:) = firefrac(:,:) / dt
483
484    CALL xios_orchidee_send_field("FIREFRAC",firefrac(:,:))
485    CALL xios_orchidee_send_field("FIREDEATH",firedeath(:,:))
486
487    CALL histwrite_p (hist_id_stomate, 'FIREFRAC', itime, &
488         firefrac(:,:), npts*nvm, horipft_index)
489    CALL histwrite_p (hist_id_stomate, 'FIREDEATH', itime, &
490         firedeath(:,:), npts*nvm, horipft_index)
491
492    IF (printlev>=4) WRITE(numout,*) 'Leaving fire'
493
494  END SUBROUTINE fire
495
496
497!! ================================================================================================================================
498!! FUNCTION     : firefrac_func
499!!
500!>\BRIEF        Calculate the annual fire fraction using long term fire index
501!!
502!! DESCRIPTION  : None
503!!
504!! RECENT CHANGE(S): None
505!!
506!! RETURN VALUE : annual fire fraction (::firefrac_result)
507!!
508!! REFERENCES   :
509!! - Thonicke K., Venevsky S., Sitch S., and Cramer W. (2001) The role of fire
510!! disturbance for global vegetation dynamics: coupling fire into a Dynamic
511!! Global Vegetation Model, Global Ecology & Biogeography, 10, 661-677.\n
512!!
513!! FLOWCHART    : None
514!! \n
515!_ ================================================================================================================================
516   
517  FUNCTION firefrac_func (npts, x) RESULT (firefrac_result)
518
519!! 0. Variable and parameter declaration
520
521    !! 0.1 Input variables
522
523    INTEGER(i_std), INTENT(in)                 :: npts             !! Domain size (unitless)
524    REAL(r_std), DIMENSION(npts), INTENT(in)   :: x                !! fire index (unitless, 0-1)
525
526    !! 0.2 Output variables
527
528    REAL(r_std), DIMENSION(npts)               :: firefrac_result  !! fire fraction (unitless, 0-1)
529
530    !! 0.3 Modified variables
531
532    !! 0.4 Local variables
533    REAL(r_std), DIMENSION(npts)               :: xm1              !! intermediate variable
534!_ ================================================================================================================================
535
536!! 1. Function
537
538    xm1(:) = x(:) - 1.
539
540    ! this equation is from Thonicke et al. (2001) equation (9), it use the fire index as input to calculate annual fire fraction.
541    ! but with different parameters with the source literature.
542    !! \latexonly
543    !! \input{lpj_fire_2.tex} 
544    !! \endlatexonly
545    !! Where, s is the long term fire index and A(s) is the annual fire fraction.\n
546    !??! here we use a different parameter with K. Thonicke et al. (2001)
547    !??! it's not clear if these parameters are correct.
548    firefrac_result(:) = &
549         &     x(:) * EXP( xm1(:) / ( -firefrac_coeff(4)*xm1(:)*xm1(:)*xm1(:) + &
550         &     firefrac_coeff(3)*xm1(:)*xm1(:) + &
551         &     firefrac_coeff(2)*xm1(:) +  &     
552         &     firefrac_coeff(1) ) )
553
554  END FUNCTION firefrac_func
555
556END MODULE lpj_fire
Note: See TracBrowser for help on using the repository browser.