source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_stomate/stomate_turnover.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 43.3 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_turnover.f90
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module manages the end of the growing season and calculates herbivory and turnover of leaves, fruits, fine roots.
10!!
11!!\n DESCRIPTION: This subroutine calculates leaf senescence due to climatic conditions or as a
12!! function of leaf age and new LAI, and subsequent turnover of the different plant biomass compartments (sections 1 to 6),
13!! herbivory (section 7), fruit turnover for trees (section 8) and sapwood conversion (section 9).
14!!
15!! RECENT CHANGE(S): None
16!!
17!! SVN          :
18!! $HeadURL$
19!! $Date$
20!! $Revision$
21!! \n
22!_ ================================================================================================================================
23
24MODULE stomate_turnover
25
26  ! modules used:
27  USE xios_orchidee
28  USE ioipsl_para
29  USE stomate_data
30  USE constantes
31  USE pft_parameters
32
33  IMPLICIT NONE
34
35  ! private & public routines
36
37  PRIVATE
38  PUBLIC turn, turn_clear
39
40  LOGICAL, SAVE                          :: firstcall_turnover = .TRUE.           !! first call (true/false)
41!$OMP THREADPRIVATE(firstcall_turnover)
42
43CONTAINS
44
45
46!! ================================================================================================================================
47!! SUBROUTINE   : turn_clear
48!!
49!>\BRIEF        Set flag ::firstcall_turnover to .TRUE., and therefore activate section 1
50!!              of subroutine turn which writes a message to the output.
51!!               
52!_ ================================================================================================================================
53
54  SUBROUTINE turn_clear
55    firstcall_turnover=.TRUE.
56  END SUBROUTINE turn_clear
57
58
59!! ================================================================================================================================
60!! SUBROUTINE    : turn
61!!
62!>\BRIEF         Calculate turnover of leaves, roots, fruits and sapwood due to aging or climatic
63!!               induced senescence. Calculate herbivory.
64!!
65!! DESCRIPTION : This subroutine determines the turnover of leaves and fine roots (and stems for grasses)
66!! and simulates following processes:
67!! 1. Mean leaf age is calculated from leaf ages of separate leaf age classes. Should actually
68!!    be recalculated at the end of the routine, but it does not change too fast. The mean leaf
69!!    age is calculated using the following equation:
70!!    \latexonly
71!!    \input{turnover_lma_update_eqn1.tex}
72!!    \endlatexonly
73!!    \n
74!! 2. Meteorological senescence: the detection of the end of the growing season and shedding
75!!    of leaves, fruits and fine roots due to unfavourable meteorological conditions.
76!!    The model distinguishes three different types of "climatic" leaf senescence, that do not
77!!    change the age structure: sensitivity to cold temperatures, to lack of water, or both.
78!!    If meteorological conditions are fulfilled, a flag ::senescence is set to TRUE. Note
79!!    that evergreen species do not experience climatic senescence.
80!!    Climatic senescence is triggered by sensitivity to cold temperatures where the critical
81!!    temperature for senescence is calculated using the following equation:
82!!    \latexonly
83!!    \input{turnover_temp_crit_eqn2.tex}
84!!    \endlatexonly
85!!    \n
86!!    Climatic senescence is triggered by sensitivity to lack of water availability where the
87!!    moisture availability critical level is calculated using the following equation:
88!!    \latexonly
89!!    \input{turnover_moist_crit_eqn3.tex}
90!!    \endlatexonly
91!!    \n
92!!    Climatic senescence is triggered by sensitivity to temperature or to lack of water where
93!!    critical temperature and moisture availability are calculated as above.\n
94!!    Trees in climatic senescence lose their fine roots at the same rate as they lose their leaves.
95!!    The rate of biomass loss of both fine roots and leaves is presribed through the equation:
96!!    \latexonly
97!!    \input{turnover_clim_senes_biomass_eqn4.tex}
98!!    \endlatexonly
99!!    \n
100!!    with ::leaffall(j) a PFT-dependent time constant which is given in
101!!    ::stomate_constants. In grasses, leaf senescence is extended to the whole plant
102!!    (all carbon pools) except to its carbohydrate reserve.   
103!! 3. Senescence due to aging: the loss of leaves, fruits and  biomass due to aging
104!!    At a certain age, leaves fall off, even if the climate would allow a green plant
105!!    all year round. Even if the meteorological conditions are favorable for leaf maintenance,
106!!    plants, and in particular, evergreen trees, have to renew their leaves simply because the
107!!    old leaves become inefficient. Roots, fruits (and stems for grasses) follow leaves.
108!!    The ??senescence?? rate varies with leaf age. Note that plant is not declared senescent
109!!    in this case (wchich is important for allocation: if the plant loses leaves because of
110!!    their age, it can renew them). The leaf turnover rate due to aging of leaves is calculated
111!!    using the following equation:
112!!    \latexonly
113!!    \input{turnover_age_senes_biomass_eqn5.tex}
114!!    \endlatexonly
115!!    \n
116!!    Drop all leaves if there is a very low leaf mass during senescence. After this, the biomass
117!!    of different carbon pools both for trees and grasses is set to zero and the mean leaf age
118!!    is reset to zero. Finally, the leaf fraction and leaf age of the different leaf age classes
119!!    is set to zero. For deciduous trees: next to leaves, also fruits and fine roots are dropped.
120!!    For grasses: all aboveground carbon pools, except the carbohydrate reserves are affected:
121!! 4. Update the leaf biomass, leaf age class fraction and the LAI
122!!    Older leaves will fall more frequently than younger leaves and therefore the leaf age
123!!    distribution needs to be recalculated after turnover. The fraction of biomass in each
124!!    leaf class is updated using the following equation:
125!!    \latexonly
126!!    \input{turnover_update_LeafAgeDistribution_eqn6.tex}
127!!    \endlatexonly
128!!    \n
129!! 5. Simulate herbivory activity and update leaf and fruits biomass. Herbivore activity
130!!    affects the biomass of leaves and fruits as well as stalks (only for grasses).
131!!    However, herbivores do not modify leaf age structure.
132!! 6. Calculates fruit turnover for trees. Trees simply lose their fruits with a time
133!!    constant ::tau_fruit(j), that is set to 90 days for all PFTs in ::stomate_constants
134!! 7. Convert sapwood to heartwood for trees and update heart and softwood above and
135!!    belowground biomass. Sapwood biomass is converted into heartwood biomass
136!!    with a time constant tau ::tau_sap(j) of 1 year. Note that this biomass conversion
137!!    is not added to "turnover" as the biomass is not lost. For the updated heartwood,
138!!    the sum of new heartwood above and new heartwood below after converting sapwood to
139!!    heartwood, is saved as ::hw_new(:). Creation of new heartwood decreases the age of
140!!    the plant ??carbon?? with a factor that is determined by: old heartwood ::hw_old(:)
141!!    divided by the new heartwood ::hw_new(:)
142!!
143!! RECENT CHANGE(S) : None
144!!
145!! MAIN OUTPUT VARIABLES: ::Biomass of leaves, fruits, fine roots and sapwood above (latter for grasses only),
146!!                        ::Update LAI, ::Update leaf age distribution with new leaf age class fraction
147!!
148!! REFERENCE(S) :
149!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
150!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
151!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
152!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
153!! - McNaughton, S. J., M. Oesterheld, D. A. Frank and K. J. Williams (1989),
154!! Ecosystem-level patterns of primary productivity and herbivory in terrestrial habitats,
155!! Nature, 341, 142-144, 1989.
156!! - Sitch, S., C. Huntingford, N. Gedney, P. E. Levy, M. Lomas, S. L. Piao, , Betts, R., Ciais, P., Cox, P.,
157!! Friedlingstein, P., Jones, C. D., Prentice, I. C. and F. I. Woodward : Evaluation of the terrestrial carbon 
158!! cycle, future plant geography and climate-carbon cycle feedbacks using 5 dynamic global vegetation
159!! models (dgvms), Global Change Biology, 14(9), 2015–2039, 2008.
160!!
161!! FLOWCHART    :
162!! \latexonly
163!! \includegraphics[scale=0.5]{turnover_flowchart_1.png}
164!! \includegraphics[scale=0.5]{turnover_flowchart_2.png}
165!! \endlatexonly
166!! \n
167!_ ================================================================================================================================
168
169  SUBROUTINE turn (npts, dt, PFTpresent, &
170       herbivores, &
171       maxmoiavail_lastyear, minmoiavail_lastyear, &
172       moiavail_week, moiavail_month, t2m_longterm, t2m_month, t2m_week, veget_max, &
173       gdd_from_growthinit, leaf_age, leaf_frac, age, lai, biomass, &
174       turnover, senescence,turnover_time, &
175!gmjc
176       sla_calc)
177!end gmjc
178    !! 0. Variable and parameter declaration
179
180    !! 0.1 Input variables
181
182    INTEGER(i_std), INTENT(in)                                 :: npts                 !! Domain size - number of grid cells
183                                                                                       !! (unitless)
184    REAL(r_std), INTENT(in)                                    :: dt                   !! time step (dt_days)
185    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                   :: PFTpresent           !! PFT exists (true/false)
186    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: herbivores           !! time constant of probability of a leaf to
187                                                                                       !! be eaten by a herbivore (days)
188    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: maxmoiavail_lastyear !! last year's maximum moisture availability
189                                                                                       !! (0-1, unitless)
190    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: minmoiavail_lastyear !! last year's minimum moisture availability
191                                                                                       !! (0-1, unitless)
192    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_week        !! "weekly" moisture availability
193                                                                                       !! (0-1, unitless)
194    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_month       !! "monthly" moisture availability
195                                                                                       !! (0-1, unitless)
196    REAL(r_std), DIMENSION(npts), INTENT(in)                   :: t2m_longterm         !! "long term" 2 meter reference
197                                                                                       !! temperatures (K)
198    REAL(r_std), DIMENSION(npts), INTENT(in)                   :: t2m_month            !! "monthly" 2-meter temperatures (K)
199    REAL(r_std), DIMENSION(npts), INTENT(in)                   :: t2m_week             !! "weekly" 2 meter temperatures (K)
200    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_max            !! "maximal" coverage fraction of a PFT (LAI
201                                                                                       !! -> infinity) on ground (unitless)
202    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: gdd_from_growthinit  !! gdd senescence for crop
203
204    !! 0.2 Output variables
205
206    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(out) :: turnover         !! Turnover @tex ($gC m^{-2}$) @endtex
207    LOGICAL, DIMENSION(npts,nvm), INTENT(out)                  :: senescence           !! is the plant senescent? (true/false)
208                                                                                       !! (interesting only for deciduous trees:
209                                                                                       !! carbohydrate reserve)
210    !! 0.3 Modified variables
211
212    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age             !! age of the leaves (days)
213    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac            !! fraction of leaves in leaf age class
214                                                                                       !! (0-1, unitless)
215    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: age                  !! age (years)
216    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: lai                  !! leaf area index @tex ($m^2 m^{-2}$)
217                                                                                       !! @endtex
218    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: biomass        !! biomass @tex ($gC m^{-2}$) @endtex
219    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: turnover_time        !! turnover_time of grasses (days)
220!gmjc
221    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: sla_calc
222!end gmjc
223    !! 0.4 Local  variables
224
225    REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_meanage         !! mean age of the leaves (days)
226    REAL(r_std), DIMENSION(npts)                               :: dturnover            !! Intermediate variable for turnover ??
227                                                                                       !! @tex ($gC m^{-2}$) @endtex
228    REAL(r_std), DIMENSION(npts)                               :: moiavail_crit        !! critical moisture availability, function
229                                                                                       !! of last year's moisture availability
230                                                                                       !! (0-1, unitless)
231    REAL(r_std), DIMENSION(npts)                               :: tl                   !! long term annual mean temperature, (C)
232    REAL(r_std), DIMENSION(npts)                               :: t_crit               !! critical senescence temperature, function
233                                                                                       !! of long term annual temperature (K)
234    LOGICAL, DIMENSION(npts)                                   :: shed_rest            !! shed the remaining leaves? (true/false)
235    REAL(r_std), DIMENSION(npts)                               :: sapconv              !! Sapwood conversion @tex ($gC m^{-2}$)
236                                                                                       !! @endtex
237    REAL(r_std), DIMENSION(npts)                               :: hw_old               !! old heartwood mass @tex ($gC m^{-2}$)
238                                                                                       !! @endtex
239    REAL(r_std), DIMENSION(npts)                               :: hw_new               !! new heartwood mass @tex ($gC m^{-2}$)
240                                                                                       !! @endtex
241    REAL(r_std), DIMENSION(npts)                               :: lm_old               !! old leaf mass @tex ($gC m^{-2}$) @endtex
242    REAL(r_std), DIMENSION(npts,nleafages)                     :: delta_lm             !! leaf mass change for each age class @tex
243                                                                                       !! ($gC m^{-2}$) @endtex
244    REAL(r_std), DIMENSION(npts)                               :: turnover_rate        !! turnover rate (unitless)
245    REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_age_crit        !! critical leaf age (days)
246    REAL(r_std), DIMENSION(npts,nvm)                           :: new_turnover_time    !! instantaneous turnover time (days)
247    INTEGER(i_std)                                             :: j,m,k                !! Index (unitless)
248
249!_ ================================================================================================================================
250
251    IF (printlev>=3) WRITE(numout,*) 'Entering turnover'
252
253    !! 1. first call - output messages
254
255    IF ( firstcall_turnover ) THEN
256
257       WRITE(numout,*) 'turnover:'
258
259       WRITE(numout,*) ' > minimum mean leaf age for senescence (days) (::min_leaf_age_for_senescence) : '&
260            ,min_leaf_age_for_senescence
261
262       firstcall_turnover = .FALSE.
263
264
265    ENDIF
266
267    !! 2. Initializations
268
269    !! 2.1 set output to zero
270    turnover(:,:,:,:) = zero
271    new_turnover_time(:,:) = zero
272    senescence(:,:) = .FALSE.
273
274    !! 2.2 Recalculate mean leaf age
275    !      Mean leaf age is recalculated from leaf ages of separate leaf age classes. Should actually be recalculated at the
276    !      end of this routine, but it does not change too fast.
277    !      The mean leaf age is calculated using the following equation:
278    !      \latexonly
279    !      \input{turnover_lma_update_eqn1.tex}
280    !      \endlatexonly
281    !      \n
282    leaf_meanage(:,:) = zero
283
284    DO m = 1, nleafages
285       leaf_meanage(:,:) = leaf_meanage(:,:) + leaf_age(:,:,m) * leaf_frac(:,:,m)
286    ENDDO
287
288    !! 3. Climatic senescence
289
290    !     Three different types of "climatic" leaf senescence,
291    !     that do not change the age structure.
292    DO j = 2,nvm ! Loop over # PFTs
293
294       !! 3.1 Determine if there is climatic senescence.
295       !      The climatic senescence can be of three types:
296       !      sensitivity to cold temperatures, to lack of water, or both. If meteorological conditions are
297       !      fulfilled, a flag senescence is set to TRUE.
298       !      Evergreen species do not experience climatic senescence.
299
300       SELECT CASE ( senescence_type(j) )
301
302
303       CASE ('crop' )!for crop senescence is based on a GDD criterium as in crop models
304          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
305               ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
306               ( gdd_from_growthinit(:,j) .GT.  gdd_senescence(j)))
307             senescence(:,j) = .TRUE.
308          ENDWHERE
309
310       CASE ( 'cold' )
311
312          !! 3.1.1 Summergreen species: Climatic senescence is triggered by sensitivity to cold temperatures
313          !        Climatic senescence is triggered by sensitivity to cold temperatures as follows:
314          !        If biomass is large enough (i.e. when it is greater than zero),
315          !        AND (i.e. when leaf mean age is above a certain PFT-dependent treshold ::min_leaf_age_for_senescence,
316          !        which is given in ::stomate_constants),     
317          !        AND the monthly temperature is low enough (i.e. when monthly temperature ::t2m_month(:) is below a critical
318          !        temperature ::t_crit(:), which is calculated in this module),
319          !        AND the temperature tendency is negative (i.e. when weekly temperatures ::t2m_week(:) are lower than monthly
320          !        temperatures ::t2m_month(:))
321          !        If these conditions are met, senescence is set to TRUE.
322          !
323          !        The critical temperature for senescence is calculated using the following equation:
324          !        \latexonly
325          !        \input{turnover_temp_crit_eqn2.tex}
326          !        \endlatexonly
327          !        \n
328          !
329          ! Critical temperature for senescence may depend on long term annual mean temperature
330          tl(:) = t2m_longterm(:) - ZeroCelsius
331          t_crit(:) = ZeroCelsius + senescence_temp(j,1) + &
332               tl(:) * senescence_temp(j,2) + &
333               tl(:)*tl(:) * senescence_temp(j,3)
334
335          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
336               ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
337               ( t2m_month(:) .LT. t_crit(:) ) .AND. ( t2m_week(:) .LT. t2m_month(:) ) )
338
339             senescence(:,j) = .TRUE.
340
341          ENDWHERE
342
343       CASE ( 'dry' )
344
345          !! 3.1.2 Raingreen species: Climatic senescence is triggered by sensitivity to lack of water availability
346          !        Climatic senescence is triggered by sensitivity to lack of water availability as follows: 
347          !        If biomass is large enough (i.e. when it is greater than zero),
348          !        AND (i.e. when leaf mean age is above a certain PFT-dependent treshold ::min_leaf_age_for_senescence,
349          !        which is given in ::stomate_constants),     
350          !        AND the moisture availability drops below a critical level (i.e. when weekly moisture availability
351          !        ::moiavail_week(:,j) is below a critical moisture availability ::moiavail_crit(:),
352          !        which is calculated in this module),
353          !        If these conditions are met, senescence is set to TRUE.
354          !
355          !        The moisture availability critical level is calculated using the following equation:
356          !        \latexonly
357          !        \input{turnover_moist_crit_eqn3.tex}
358          !        \endlatexonly
359          !        \n
360          moiavail_crit(:) = &
361               MIN( MAX( minmoiavail_lastyear(:,j) + hum_frac(j) * &
362               ( maxmoiavail_lastyear(:,j) - minmoiavail_lastyear(:,j) ), &
363               senescence_hum(j) ), &
364               nosenescence_hum(j) )
365
366          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
367               ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
368               ( moiavail_week(:,j) .LT. moiavail_crit(:) ) )
369
370             senescence(:,j) = .TRUE.
371
372          ENDWHERE
373
374       CASE ( 'mixed' )
375
376          !! 3.1.3 Mixed criterion: Climatic senescence is triggered by sensitivity to temperature or to lack of water 
377          !        Climatic senescence is triggered by sensitivity to temperature or to lack of water availability as follows:
378          !        If biomass is large enough (i.e. when it is greater than zero),
379          !        AND (i.e. when leaf mean age is above a certain PFT-dependent treshold ::min_leaf_age_for_senescence,
380          !        which is given in ::stomate_constants),     
381          !        AND the moisture availability drops below a critical level (i.e. when weekly moisture availability
382          !        ::moiavail_week(:,j) is below a critical moisture availability ::moiavail_crit(:), calculated in this module),
383          !        OR
384          !        the monthly temperature is low enough (i.e. when monthly temperature ::t2m_month(:) is below a critical
385          !        temperature ::t_crit(:), calculated in this module),
386          !        AND the temperature tendency is negative (i.e. when weekly temperatures ::t2m_week(:) are lower than
387          !        monthly temperatures ::t2m_month(:)).
388          !        If these conditions are met, senescence is set to TRUE.
389          moiavail_crit(:) = &
390               MIN( MAX( minmoiavail_lastyear(:,j) + hum_frac(j) * &
391               (maxmoiavail_lastyear(:,j) - minmoiavail_lastyear(:,j) ), &
392               senescence_hum(j) ), &
393               nosenescence_hum(j) )
394
395          tl(:) = t2m_longterm(:) - ZeroCelsius
396          t_crit(:) = ZeroCelsius + senescence_temp(j,1) + &
397               tl(:) * senescence_temp(j,2) + &
398               tl(:)*tl(:) * senescence_temp(j,3)
399
400          IF ( is_tree(j) ) THEN
401             ! critical temperature for senescence may depend on long term annual mean temperature
402             WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
403                  ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
404                  ( ( moiavail_week(:,j) .LT. moiavail_crit(:) ) .OR. &
405                  ( ( t2m_month(:) .LT. t_crit(:) ) .AND. ( t2m_week(:) .LT. t2m_month(:) ) ) ) )
406                senescence(:,j) = .TRUE.
407             ENDWHERE
408          ELSE
409
410            turnover_time(:,j) = max_turnover_time(j)
411
412            WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
413                 ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
414                 ( ( moiavail_week(:,j) .LT. moiavail_crit(:) )))
415                turnover_time(:,j) = max_turnover_time(j) * &
416                     (1.-   (1.- (moiavail_week(:,j)/  moiavail_crit(:)))**2)           
417            ENDWHERE
418
419            WHERE ( turnover_time(:,j) .LT. min_turnover_time(j) )               
420               turnover_time(:,j) = min_turnover_time(j)                         
421            ENDWHERE                                                                     
422
423            WHERE ((( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
424                ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
425                ((t2m_month(:) .LT. t_crit(:)) .AND. (lai(:,j) .GT. lai_max(j)/4.) .OR. &
426                (t2m_month(:) .LT. ZeroCelsius)) .AND. ( t2m_week(:) .LT. t2m_month(:) )))
427               turnover_time(:,j)= leaffall(j)
428            ENDWHERE
429!gmjc
430          IF (is_grassland_manag(j)) THEN
431            WHERE (lai(:,j) .LT. 0.5)
432               turnover_time(:,j)= max_turnover_time(j)
433            ENDWHERE
434            WHERE (lai(:,j) .GT. 2.55)
435               turnover_time(:,j)= MAX(45.0,(85.0-lai(:,j)*10.0))
436            ENDWHERE
437          ENDIF
438!end gmjc
439         ENDIF
440
441
442       !! Evergreen species do not experience climatic senescence
443       CASE ( 'none' )
444
445         
446       !! In case no climatic senescence type is recognized.
447       CASE default
448
449          WRITE(numout,*) '  turnover: don''t know how to treat this PFT.'
450          WRITE(numout,*) '  number (::j) : ',j
451          WRITE(numout,*) '  senescence type (::senescence_type(j)) : ',senescence_type(j)
452
453          CALL ipslerr_p(3,"turn","Dont know how to treat this PFT.","","")
454
455       END SELECT
456
457       !! 3.2 Drop leaves and roots, plus stems and fruits for grasses
458
459       IF ( is_tree(j) ) THEN
460
461          !! 3.2.1 Trees in climatic senescence lose their fine roots at the same rate as they lose their leaves.
462          !        The rate of biomass loss of both fine roots and leaves is presribed through the equation:
463          !        \latexonly
464          !        \input{turnover_clim_senes_biomass_eqn4.tex}
465          !        \endlatexonly
466          !        \n
467          !         with ::leaffall(j) a PFT-dependent time constant which is given in ::stomate_constants),
468          WHERE ( senescence(:,j) )
469
470             turnover(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) * dt / leaffall(j)
471             turnover(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) * dt / leaffall(j)
472
473          ENDWHERE
474
475       ELSE
476
477          !! 3.2.2 In grasses, leaf senescence is extended to the whole plant
478          !        In grasses, leaf senescence is extended to the whole plant (all carbon pools) except to its
479          !        carbohydrate reserve.     
480
481          IF (senescence_type(j) .EQ. 'crop') THEN
482             ! 3.2.2.1 crops with 'crop' phenological model
483             WHERE ( senescence(:,j) )
484                turnover(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) * dt / leaffall(j)
485                turnover(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) * dt / leaffall(j)
486                turnover(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) * dt / leaffall(j)
487                turnover(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) * dt /leaffall(j)
488             ENDWHERE
489          ELSE
490          ! 3.2.2.2 grass or crops based on 'mixed' phenological model
491             WHERE (turnover_time(:,j) .LT. max_turnover_time(j)) 
492                turnover(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) * dt / turnover_time(:,j)
493                turnover(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) * dt / turnover_time(:,j)
494                turnover(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) * dt / turnover_time(:,j) 
495                turnover(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) * dt / turnover_time(:,j)
496             ENDWHERE
497          ENDIF
498       ENDIF      ! tree/grass
499       biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - turnover(:,j,ileaf,icarbon)
500       biomass(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) - turnover(:,j,isapabove,icarbon)
501       biomass(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) - turnover(:,j,iroot,icarbon)
502       biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - turnover(:,j,ifruit,icarbon)
503    ENDDO        ! loop over PFTs
504
505    !! 4. Leaf fall
506    !     At a certain age, leaves fall off, even if the climate would allow a green plant
507    !     all year round. Even if the meteorological conditions are favorable for leaf maintenance,
508    !     plants, and in particular, evergreen trees, have to renew their leaves simply because the
509    !     old leaves become inefficient.   
510    !     Roots, fruits (and stems) follow leaves. The decay rate varies with leaf age.
511    !     Note that plant is not declared senescent in this case (wchich is important for allocation:
512    !     if the plant loses leaves because of their age, it can renew them).
513    !
514    !     The leaf turnover rate due to aging of leaves is calculated using the following equation:
515    !     \latexonly
516    !     \input{turnover_age_senes_biomass_eqn5.tex}
517    !     \endlatexonly
518    !     \n
519    DO j = 2,nvm ! Loop over # PFTs
520
521       !! save old leaf mass
522       lm_old(:) = biomass(:,j,ileaf,icarbon)
523
524       !! initialize leaf mass change in age class
525       delta_lm(:,:) = zero
526
527       IF ( is_tree(j) .OR. (.NOT. natural(j)) ) THEN
528
529          !! 4.1 Trees: leaves, roots, fruits roots and fruits follow leaves.
530
531          !! 4.1.1 Critical age: prescribed for trees
532          leaf_age_crit(:,j) = leafagecrit(j)
533
534       ELSE
535
536          !! 4.2 Grasses: leaves, roots, fruits, sap follow leaves.
537
538          !! 4.2.1 Critical leaf age depends on long-term temperature
539          !        Critical leaf age depends on long-term temperature
540          !        generally, lower turnover in cooler climates.
541          leaf_age_crit(:,j) = &
542               MIN( leafagecrit(j) * leaf_age_crit_coeff(1) , &
543               MAX( leafagecrit(j) * leaf_age_crit_coeff(2) , &
544               leafagecrit(j) - leaf_age_crit_coeff(3) * &
545               ( t2m_longterm(:)-ZeroCelsius - leaf_age_crit_tref ) ) )
546
547       END IF
548         
549       ! 4.2.2 Loop over leaf age classes
550       DO m = 1, nleafages
551
552          turnover_rate(:) = zero
553
554          WHERE ( leaf_age(:,j,m) .GT. leaf_age_crit(:,j)/2. )
555
556             turnover_rate(:) =  &
557                  MIN( 0.99_r_std, dt / ( leaf_age_crit(:,j) * &
558                  ( leaf_age_crit(:,j) / leaf_age(:,j,m) )**quatre ) )
559
560          ENDWHERE
561         
562          dturnover(:) = biomass(:,j,ileaf,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
563          turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + dturnover(:)
564          biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - dturnover(:)
565
566          ! save leaf mass change
567          delta_lm(:,m) = - dturnover(:)
568         
569          dturnover(:) = biomass(:,j,iroot,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
570          turnover(:,j,iroot,icarbon) = turnover(:,j,iroot,icarbon) + dturnover(:)
571          biomass(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) - dturnover(:)
572         
573          dturnover(:) = biomass(:,j,ifruit,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
574          turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + dturnover(:)
575          biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - dturnover(:)
576         
577          IF (.NOT. is_tree(j)) THEN
578             dturnover(:) = biomass(:,j,isapabove,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
579             turnover(:,j,isapabove,icarbon) = turnover(:,j,isapabove,icarbon) + dturnover(:)
580             biomass(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) - dturnover(:)
581          ENDIF
582         
583       ENDDO
584
585       !! 4.3 Recalculate the fraction of leaf biomass in each leaf age class.
586       !      Older leaves will fall more fast than younger leaves and therefore
587       !      the leaf age distribution needs to be recalculated after turnover.
588       !      The fraction of biomass in each leaf class is updated using the following equation:
589       !      \latexonly
590       !      \input{turnover_update_LeafAgeDistribution_eqn6.tex}
591       !      \endlatexonly
592       !      \n
593       !
594       !      new fraction = new leaf mass of that fraction / new total leaf mass
595       !                   = (old fraction*old total leaf mass ::lm_old(:) + biomass change of that fraction ::delta_lm(:,m)  ) /
596       !                     new total leaf mass ::biomass(:,j,ileaf
597       DO m = 1, nleafages
598         
599          WHERE ( biomass(:,j,ileaf,icarbon) .GT. zero )
600             leaf_frac(:,j,m) = ( leaf_frac(:,j,m)*lm_old(:) + delta_lm(:,m) ) / biomass(:,j,ileaf,icarbon)
601          ELSEWHERE
602             leaf_frac(:,j,m) = zero
603          ENDWHERE
604       
605       ENDDO
606       
607    ENDDO         ! loop over PFTs
608
609    !! 5. New (provisional) LAI
610    !     ::lai(:,j) is determined from the leaf biomass ::biomass(:,j,ileaf,icarbon) and the
611    !     specific leaf surface :: sla(j) (m^2 gC^{-1})
612    !     The leaf area index is updated using the following equation:
613    !     \latexonly
614    !     \input{turnover_update_LAI_eqn7.tex}
615    !     \endlatexonly
616    !     \n
617
618    !    lai(:,ibare_sechiba) = zero
619    !    DO j = 2, nvm ! Loop over # PFTs
620    !        lai(:,j) = biomass(:,j,ileaf,icarbon) * sla(j)
621    !    ENDDO
622
623    !! 6. Definitely drop all leaves if there is a very low leaf mass during senescence.
624
625    !     Both for deciduous trees and grasses same conditions are checked:
626    !     If biomass is large enough (i.e. when it is greater than zero),
627    !     AND when senescence is set to true
628    !     AND the leaf biomass drops below a critical minimum biomass level (i.e. when it is lower than half
629    !     the minimum initial LAI ::lai_initmin(j) divided by the specific leaf area ::sla(j),
630    !     ::lai_initmin(j) is set to 0.3 in stomate_data.f90 and sla is a constant that is set to 0.015366 m2/gC),
631    !     If these conditions are met, the flag ::shed_rest(:) is set to TRUE.
632    !
633    !     After this, the biomass of different carbon pools both for trees and grasses is set to zero
634    !     and the mean leaf age is reset to zero.
635    !     Finally, the leaf fraction and leaf age of the different leaf age classes is set to zero.
636    DO j = 2,nvm ! Loop over # PFTs
637
638       shed_rest(:) = .FALSE.
639
640       !! 6.1 For deciduous trees: next to leaves, also fruits and fine roots are dropped
641       !      For deciduous trees: next to leaves, also fruits and fine roots are dropped: fruit ::biomass(:,j,ifruit)
642       !      and fine root ::biomass(:,j,iroot) carbon pools are set to zero.
643       IF ( is_tree(j) .AND. ( senescence_type(j) .NE. 'none' ) ) THEN
644
645          ! check whether we shed the remaining leaves
646          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. senescence(:,j) .AND. &
647               ( biomass(:,j,ileaf,icarbon) .LT. (lai_initmin(j) / 2.)/sla_calc(:,j) )             )
648
649             shed_rest(:) = .TRUE.
650
651             turnover(:,j,ileaf,icarbon)  = turnover(:,j,ileaf,icarbon) + biomass(:,j,ileaf,icarbon)
652             turnover(:,j,iroot,icarbon)  = turnover(:,j,iroot,icarbon) + biomass(:,j,iroot,icarbon)
653             turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + biomass(:,j,ifruit,icarbon)
654
655             biomass(:,j,ileaf,icarbon)  = zero
656             biomass(:,j,iroot,icarbon)  = zero
657             biomass(:,j,ifruit,icarbon) = zero
658
659             ! reset leaf age
660             leaf_meanage(:,j) = zero
661
662          ENDWHERE
663
664       ENDIF
665
666       !! 6.2 For grasses: all aboveground carbon pools, except the carbohydrate reserves are affected:
667       !      For grasses: all aboveground carbon pools, except the carbohydrate reserves are affected:
668       !      fruit ::biomass(:,j,ifruit,icarbon), fine root ::biomass(:,j,iroot,icarbon) and sapwood above
669       !      ::biomass(:,j,isapabove,icarbon) carbon pools are set to zero.
670       IF ( .NOT. is_tree(j) ) THEN
671
672          ! Shed the remaining leaves if LAI very low.
673          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. senescence(:,j) .AND. &
674               (  biomass(:,j,ileaf,icarbon) .LT. (lai_initmin(j) / 2.)/sla_calc(:,j) ))
675
676             shed_rest(:) = .TRUE.
677
678             turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + biomass(:,j,ileaf,icarbon)
679             turnover(:,j,isapabove,icarbon) = turnover(:,j,isapabove,icarbon) + biomass(:,j,isapabove,icarbon)
680             turnover(:,j,iroot,icarbon) = turnover(:,j,iroot,icarbon) + biomass(:,j,iroot,icarbon)
681             turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + biomass(:,j,ifruit,icarbon)
682
683             biomass(:,j,ileaf,icarbon) = zero
684             biomass(:,j,isapabove,icarbon) = zero
685             biomass(:,j,iroot,icarbon) = zero
686             biomass(:,j,ifruit,icarbon) = zero
687
688             ! reset leaf age
689             leaf_meanage(:,j) = zero
690
691          ENDWHERE
692
693       ENDIF
694
695       !! 6.3 Reset the leaf age structure: the leaf fraction and leaf age of the different leaf age classes is set to zero.
696     
697       DO m = 1, nleafages
698
699          WHERE ( shed_rest(:) )
700
701             leaf_age(:,j,m) = zero
702             leaf_frac(:,j,m) = zero
703
704          ENDWHERE
705
706       ENDDO
707
708    ENDDO          ! loop over PFTs
709   
710    !! 7. Herbivore activity: elephants, cows, gazelles but no lions.
711 
712    !     Herbivore activity affects the biomass of leaves and fruits as well
713    !     as stalks (only for grasses). Herbivore activity does not modify leaf
714    !     age structure. Herbivores ::herbivores(:,j) is the time constant of
715    !     probability of a leaf to be eaten by a herbivore, and is calculated in
716    !     ::stomate_season. following Mc Naughton et al. [1989].
717
718    IF ( ok_herbivores ) THEN
719
720       ! If the herbivore activity is allowed (if ::ok_herbivores is true, which is set in run.def),
721       ! remove the amount of biomass consumed by herbivory from the leaf biomass ::biomass(:,j,ileaf,icarbon) and
722       ! the fruit biomass ::biomass(:,j,ifruit,icarbon).
723       ! The daily amount consumed equals the biomass multiplied by 1 day divided by the time constant ::herbivores(:,j).
724       DO j = 2,nvm ! Loop over # PFTs
725
726          IF ( is_tree(j) ) THEN
727
728             !! For trees: only the leaves and fruit carbon pools are affected
729
730             WHERE (biomass(:,j,ileaf,icarbon) .GT. zero)
731                ! added by shilong
732                WHERE (herbivores(:,j).GT. zero)
733                   dturnover(:) = biomass(:,j,ileaf,icarbon) * dt / herbivores(:,j)
734                   turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + dturnover(:)
735                   biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - dturnover(:)
736
737                   dturnover(:) = biomass(:,j,ifruit,icarbon) * dt / herbivores(:,j)
738                   turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + dturnover(:)
739                   biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - dturnover(:)
740                ENDWHERE
741             ENDWHERE
742
743          ELSE
744
745             ! For grasses: all aboveground carbon pools are affected: leaves, fruits and sapwood above
746             WHERE ( biomass(:,j,ileaf,icarbon) .GT. zero )
747                ! added by shilong
748                WHERE (herbivores(:,j) .GT. zero)
749                   dturnover(:) = biomass(:,j,ileaf,icarbon) * dt / herbivores(:,j)
750                   turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + dturnover(:)
751                   biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - dturnover(:)
752
753                   dturnover(:) = biomass(:,j,isapabove,icarbon) * dt / herbivores(:,j)
754                   turnover(:,j,isapabove,icarbon) = turnover(:,j,isapabove,icarbon) + dturnover(:)
755                   biomass(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) - dturnover(:)
756
757                   dturnover(:) = biomass(:,j,ifruit,icarbon) * dt / herbivores(:,j)
758                   turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + dturnover(:)
759                   biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - dturnover(:)
760                ENDWHERE
761
762             ENDWHERE
763
764          ENDIF  ! tree/grass?
765
766       ENDDO    ! loop over PFTs
767
768    ENDIF ! end herbivores
769
770    !! 8. Fruit turnover for trees
771
772    !     Fruit turnover for trees: trees simply lose their fruits with a time constant ::tau_fruit(j),
773    !     that is set to 90 days for all PFTs in ::stomate_constants
774
775    DO k = 1,nelements 
776       DO j = 2,nvm ! Loop over # PFTs
777          IF ( is_tree(j) ) THEN
778
779             dturnover(:) = biomass(:,j,ifruit,k) * dt / tau_fruit(j)
780             turnover(:,j,ifruit,k) = turnover(:,j,ifruit,k) + dturnover(:)
781             biomass(:,j,ifruit,k) = biomass(:,j,ifruit,k) - dturnover(:)
782             
783          ENDIF
784       ENDDO       ! loop over PFTs
785    END DO
786
787    !! 9 Conversion of sapwood to heartwood both for aboveground and belowground sapwood and heartwood.
788
789    !   Following LPJ (Sitch et al., 2003), sapwood biomass is converted into heartwood biomass
790    !   with a time constant tau ::tau_sap(j) of 1 year.
791    !   Note that this biomass conversion is not added to "turnover" as the biomass is not lost!
792    DO j = 2,nvm ! Loop over # PFTs
793
794       IF ( is_tree(j) ) THEN
795
796          !! For the recalculation of age in 9.2 (in case the vegetation is not dynamic ie. ::ok_dgvm is FALSE),
797          !! the heartwood above and below is stored in ::hw_old(:).
798          IF ( .NOT. ok_dgvm ) THEN
799             hw_old(:) = biomass(:,j,iheartabove,icarbon) + biomass(:,j,iheartbelow,icarbon)
800          ENDIF
801
802          !! 9.1 Calculate the rate of sapwood to heartwood conversion
803          !      Calculate the rate of sapwood to heartwood conversion with the time constant ::tau_sap(j)
804          !      and update aboveground and belowground sapwood ::biomass(:,j,isapabove) and ::biomass(:,j,isapbelow)
805          !      and heartwood ::biomass(:,j,iheartabove) and ::biomass(:,j,iheartbelow).
806
807          DO k = 1,nelements
808
809             ! Above the ground
810             sapconv(:) = biomass(:,j,isapabove,k) * dt / tau_sap(j)
811             biomass(:,j,isapabove,k) = biomass(:,j,isapabove,k) - sapconv(:)
812             biomass(:,j,iheartabove,k) =  biomass(:,j,iheartabove,k) + sapconv(:)
813             
814             ! Below the ground
815             sapconv(:) = biomass(:,j,isapbelow,k) * dt / tau_sap(j)
816             biomass(:,j,isapbelow,k) = biomass(:,j,isapbelow,k) - sapconv(:)
817             biomass(:,j,iheartbelow,k) =  biomass(:,j,iheartbelow,k) + sapconv(:)
818
819          END DO
820
821          !! 9.2 If the vegetation is not dynamic, the age of the plant is decreased.
822          !      The updated heartwood, the sum of new heartwood above and new heartwood below after
823          !      converting sapwood to heartwood, is saved as ::hw_new(:) .
824          !      Creation of new heartwood decreases the age of the plant with a factor that is determined by:
825          !      old heartwood ::hw_old(:) divided by the new heartwood ::hw_new(:)
826          IF ( .NOT. ok_dgvm ) THEN
827
828             hw_new(:) = biomass(:,j,iheartabove,icarbon) + biomass(:,j,iheartbelow,icarbon)
829
830             WHERE ( hw_new(:) .GT. zero )
831
832                age(:,j) = age(:,j) * hw_old(:)/hw_new(:)
833
834             ENDWHERE
835
836          ENDIF
837
838       ENDIF
839
840    ENDDO       ! loop over PFTs
841
842
843    CALL xios_orchidee_send_field("HERBIVORES",herbivores)
844    CALL xios_orchidee_send_field("LEAF_AGE",leaf_meanage)
845   
846
847    ! Write mean leaf age and time constant of probability of a leaf to be eaten by a herbivore
848    ! to the stomate output file.
849    CALL histwrite_p (hist_id_stomate, 'LEAF_AGE', itime, &
850         leaf_meanage, npts*nvm, horipft_index)
851    CALL histwrite_p (hist_id_stomate, 'HERBIVORES', itime, &
852         herbivores, npts*nvm, horipft_index)
853
854    IF (printlev>=4) WRITE(numout,*) 'Leaving turnover'
855
856  END SUBROUTINE turn
857
858END MODULE stomate_turnover
Note: See TracBrowser for help on using the repository browser.