source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_stomate/stomate_turnover.f90 @ 8367

Last change on this file since 8367 was 6863, checked in by nicolas.vuichard, 4 years ago

correction of r6862

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 49.3 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_turnover.f90
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.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_cov_max, &
173       gdd_from_growthinit, leaf_age, leaf_frac, age, lai, biomass, &
174       turnover, senescence,turnover_time,when_growthinit)
175
176    !! 0. Variable and parameter declaration
177
178    !! 0.1 Input variables
179
180    INTEGER(i_std), INTENT(in)                                 :: npts                 !! Domain size - number of grid cells
181                                                                                       !! (unitless)
182    REAL(r_std), INTENT(in)                                    :: dt                   !! time step (dt_days)
183    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                   :: PFTpresent           !! PFT exists (true/false)
184    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: herbivores           !! time constant of probability of a leaf to
185                                                                                       !! be eaten by a herbivore (days)
186    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: maxmoiavail_lastyear !! last year's maximum moisture availability
187                                                                                       !! (0-1, unitless)
188    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: minmoiavail_lastyear !! last year's minimum moisture availability
189                                                                                       !! (0-1, unitless)
190    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_week        !! "weekly" moisture availability
191                                                                                       !! (0-1, unitless)
192    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_month       !! "monthly" moisture availability
193                                                                                       !! (0-1, unitless)
194    REAL(r_std), DIMENSION(npts), INTENT(in)                   :: t2m_longterm         !! "long term" 2 meter reference
195                                                                                       !! temperatures (K)
196    REAL(r_std), DIMENSION(npts), INTENT(in)                   :: t2m_month            !! "monthly" 2-meter temperatures (K)
197    REAL(r_std), DIMENSION(npts), INTENT(in)                   :: t2m_week             !! "weekly" 2 meter temperatures (K)
198    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_cov_max        !! "maximal" coverage fraction of a PFT (LAI
199                                                                                       !! -> infinity) on ground (unitless)
200    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: gdd_from_growthinit  !! gdd senescence for crop
201
202    !! 0.2 Output variables
203
204    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(out) :: turnover         !! Turnover @tex ($gC m^{-2}$) @endtex
205    LOGICAL, DIMENSION(npts,nvm), INTENT(out)                  :: senescence           !! is the plant senescent? (true/false)
206                                                                                       !! (interesting only for deciduous trees:
207                                                                                       !! carbohydrate reserve)
208    !! 0.3 Modified variables
209
210    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age             !! age of the leaves (days)
211    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac            !! fraction of leaves in leaf age class
212                                                                                       !! (0-1, unitless)
213    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: age                  !! age (years)
214    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: lai                  !! leaf area index @tex ($m^2 m^{-2}$)
215                                                                                       !! @endtex
216    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: biomass        !! biomass @tex ($gC m^{-2}$) @endtex
217    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: turnover_time        !! turnover_time of grasses (days)
218    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: when_growthinit      !! how many days since the
219                                                                                       !! beginning of the growing season
220                                                                                       !! (days)
221
222    !! 0.4 Local  variables
223
224    REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_meanage         !! mean age of the leaves (days)
225    REAL(r_std), DIMENSION(npts)                               :: dturnover            !! Intermediate variable for turnover ??
226                                                                                       !! @tex ($gC m^{-2}$) @endtex
227    REAL(r_std), DIMENSION(npts)                               :: moiavail_crit        !! critical moisture availability, function
228                                                                                       !! of last year's moisture availability
229                                                                                       !! (0-1, unitless)
230    REAL(r_std), DIMENSION(npts)                               :: tl                   !! long term annual mean temperature, (C)
231    REAL(r_std), DIMENSION(npts)                               :: t_crit               !! critical senescence temperature, function
232                                                                                       !! of long term annual temperature (K)
233    LOGICAL, DIMENSION(npts)                                   :: shed_rest            !! shed the remaining leaves? (true/false)
234    REAL(r_std), DIMENSION(npts)                               :: sapconv              !! Sapwood conversion @tex ($gC m^{-2}$)
235                                                                                       !! @endtex
236    REAL(r_std), DIMENSION(npts)                               :: hw_old               !! old heartwood mass @tex ($gC m^{-2}$)
237                                                                                       !! @endtex
238    REAL(r_std), DIMENSION(npts)                               :: hw_new               !! new heartwood mass @tex ($gC m^{-2}$)
239                                                                                       !! @endtex
240    REAL(r_std), DIMENSION(npts)                               :: lm_old               !! old leaf mass @tex ($gC m^{-2}$) @endtex
241    REAL(r_std), DIMENSION(npts,nleafages)                     :: delta_lm             !! leaf mass change for each age class @tex
242                                                                                       !! ($gC m^{-2}$) @endtex
243    REAL(r_std), DIMENSION(npts)                               :: turnover_rate        !! turnover rate (unitless)
244    REAL(r_std), DIMENSION(npts,nvm)                           :: leaf_age_crit        !! critical leaf age (days)
245    REAL(r_std), DIMENSION(npts,nvm)                           :: new_turnover_time    !! instantaneous turnover time (days)
246    INTEGER(i_std)                                             :: j,m,k                !! Index (unitless)
247
248!_ ================================================================================================================================
249
250    IF (printlev>=3) WRITE(numout,*) 'Entering turnover'
251
252    !! 1. first call - output messages
253
254    IF ( firstcall_turnover ) THEN
255
256       IF (printlev >=2 ) THEN
257          WRITE(numout,*) 'turnover:'
258          WRITE(numout,*) ' > minimum mean leaf age for senescence (days) (::min_leaf_age_for_senescence) : '&
259               ,min_leaf_age_for_senescence
260       END IF
261       firstcall_turnover = .FALSE.
262
263
264    ENDIF
265
266    !! 2. Initializations
267
268    !! 2.1 set output to zero
269    turnover(:,:,:,:) = zero
270    new_turnover_time(:,:) = zero
271    senescence(:,:) = .FALSE.
272
273    !! 2.2 Recalculate mean leaf age
274    !      Mean leaf age is recalculated from leaf ages of separate leaf age classes. Should actually be recalculated at the
275    !      end of this routine, but it does not change too fast.
276    !      The mean leaf age is calculated using the following equation:
277    !      \latexonly
278    !      \input{turnover_lma_update_eqn1.tex}
279    !      \endlatexonly
280    !      \n
281    leaf_meanage(:,:) = zero
282
283    DO m = 1, nleafages
284       leaf_meanage(:,:) = leaf_meanage(:,:) + leaf_age(:,:,m) * leaf_frac(:,:,m)
285    ENDDO
286
287    !! 3. Climatic senescence
288
289    !     Three different types of "climatic" leaf senescence,
290    !     that do not change the age structure.
291    DO j = 2,nvm ! Loop over # PFTs
292
293       !! 3.1 Determine if there is climatic senescence.
294       !      The climatic senescence can be of three types:
295       !      sensitivity to cold temperatures, to lack of water, or both. If meteorological conditions are
296       !      fulfilled, a flag senescence is set to TRUE.
297       !      Evergreen species do not experience climatic senescence.
298
299       SELECT CASE ( senescence_type(j) )
300
301
302       CASE ('crop' )!for crop senescence is based on a GDD criterium as in crop models
303          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
304               ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
305               ( gdd_from_growthinit(:,j) .GT.  gdd_senescence(j)))
306             senescence(:,j) = .TRUE.
307          ENDWHERE
308
309       CASE ( 'cold' )
310
311          !! 3.1.1 Summergreen species: Climatic senescence is triggered by sensitivity to cold temperatures
312          !        Climatic senescence is triggered by sensitivity to cold temperatures as follows:
313          !        If biomass is large enough (i.e. when it is greater than zero),
314          !        AND (i.e. when leaf mean age is above a certain PFT-dependent treshold ::min_leaf_age_for_senescence,
315          !        which is given in ::stomate_constants),     
316          !        AND the monthly temperature is low enough (i.e. when monthly temperature ::t2m_month(:) is below a critical
317          !        temperature ::t_crit(:), which is calculated in this module),
318          !        AND the temperature tendency is negative (i.e. when weekly temperatures ::t2m_week(:) are lower than monthly
319          !        temperatures ::t2m_month(:))
320          !        If these conditions are met, senescence is set to TRUE.
321          !
322          !        The critical temperature for senescence is calculated using the following equation:
323          !        \latexonly
324          !        \input{turnover_temp_crit_eqn2.tex}
325          !        \endlatexonly
326          !        \n
327          !
328          ! Critical temperature for senescence may depend on long term annual mean temperature
329          tl(:) = t2m_longterm(:) - ZeroCelsius
330          t_crit(:) = ZeroCelsius + senescence_temp(j,1) + &
331               tl(:) * senescence_temp(j,2) + &
332               tl(:)*tl(:) * senescence_temp(j,3)
333
334          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
335               ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
336               ( t2m_month(:) .LT. t_crit(:) ) .AND. ( t2m_week(:) .LT. t2m_month(:) ) )
337
338             senescence(:,j) = .TRUE.
339
340          ENDWHERE
341
342       CASE ( 'dry' )
343
344          !! 3.1.2 Raingreen species: Climatic senescence is triggered by sensitivity to lack of water availability
345          !        Climatic senescence is triggered by sensitivity to lack of water availability as follows: 
346          !        If biomass is large enough (i.e. when it is greater than zero),
347          !        AND (i.e. when leaf mean age is above a certain PFT-dependent treshold ::min_leaf_age_for_senescence,
348          !        which is given in ::stomate_constants),     
349          !        AND the moisture availability drops below a critical level (i.e. when weekly moisture availability
350          !        ::moiavail_week(:,j) is below a critical moisture availability ::moiavail_crit(:),
351          !        which is calculated in this module),
352          !        If these conditions are met, senescence is set to TRUE.
353          !
354          !        The moisture availability critical level is calculated using the following equation:
355          !        \latexonly
356          !        \input{turnover_moist_crit_eqn3.tex}
357          !        \endlatexonly
358          !        \n
359          moiavail_crit(:) = &
360               MIN( MAX( minmoiavail_lastyear(:,j) + hum_frac(j) * &
361               ( maxmoiavail_lastyear(:,j) - minmoiavail_lastyear(:,j) ), &
362               senescence_hum(j) ), &
363               nosenescence_hum(j) )
364
365          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
366               ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
367               ( moiavail_week(:,j) .LT. moiavail_crit(:) ) )
368
369             senescence(:,j) = .TRUE.
370
371          ENDWHERE
372
373       CASE ( 'mixed' )
374
375          !! 3.1.3 Mixed criterion: Climatic senescence is triggered by sensitivity to temperature or to lack of water 
376          !        Climatic senescence is triggered by sensitivity to temperature or to lack of water availability as follows:
377          !        If biomass is large enough (i.e. when it is greater than zero),
378          !        AND (i.e. when leaf mean age is above a certain PFT-dependent treshold ::min_leaf_age_for_senescence,
379          !        which is given in ::stomate_constants),     
380          !        AND the moisture availability drops below a critical level (i.e. when weekly moisture availability
381          !        ::moiavail_week(:,j) is below a critical moisture availability ::moiavail_crit(:), calculated in this module),
382          !        OR
383          !        the monthly temperature is low enough (i.e. when monthly temperature ::t2m_month(:) is below a critical
384          !        temperature ::t_crit(:), calculated in this module),
385          !        AND the temperature tendency is negative (i.e. when weekly temperatures ::t2m_week(:) are lower than
386          !        monthly temperatures ::t2m_month(:)).
387          !        If these conditions are met, senescence is set to TRUE.
388          moiavail_crit(:) = &
389               MIN( MAX( minmoiavail_lastyear(:,j) + hum_frac(j) * &
390               (maxmoiavail_lastyear(:,j) - minmoiavail_lastyear(:,j) ), &
391               senescence_hum(j) ), &
392               nosenescence_hum(j) )
393
394          tl(:) = t2m_longterm(:) - ZeroCelsius
395          t_crit(:) = ZeroCelsius + senescence_temp(j,1) + &
396               tl(:) * senescence_temp(j,2) + &
397               tl(:)*tl(:) * senescence_temp(j,3)
398
399          IF ( is_tree(j) ) THEN
400             ! critical temperature for senescence may depend on long term annual mean temperature
401             WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
402                  ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
403                  ( ( moiavail_week(:,j) .LT. moiavail_crit(:) ) .OR. &
404                  ( ( t2m_month(:) .LT. t_crit(:) ) .AND. ( t2m_week(:) .LT. t2m_month(:) ) ) ) )
405                senescence(:,j) = .TRUE.
406             ENDWHERE
407          ELSE
408
409            turnover_time(:,j) = max_turnover_time(j)
410
411!!            WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
412!!                 ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
413!!                 ( ( moiavail_week(:,j) .LT. moiavail_crit(:) )))
414!!                turnover_time(:,j) = max_turnover_time(j) * &
415!!                     (1.-   (1.- (moiavail_week(:,j)/  moiavail_crit(:)))**2)         
416!!            ENDWHERE
417!!
418!!            WHERE ( turnover_time(:,j) .LT. min_turnover_time(j) )             
419!!             turnover_time(:,j) = min_turnover_time(j)                         
420!!            ENDWHERE                                                                   
421!!
422!!            WHERE ((( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. &
423!!                ( leaf_meanage(:,j) .GT. min_leaf_age_for_senescence(j) ) .AND. &
424!!                ((t2m_month(:) .LT. t_crit(:)) .AND. (lai(:,j) .GT. lai_max(j)/4.) .OR. &
425!!                (t2m_month(:) .LT. ZeroCelsius)) .AND. ( t2m_week(:) .LT. t2m_month(:) )))
426!!               turnover_time(:,j)= leaffall(j)
427!!            ENDWHERE
428            WHERE (( leaf_frac(:,j,nleafages) .GT. 0.6) .AND. (when_growthinit(:,j).GT. 100.))   
429                senescence(:,j) = .TRUE.                     
430             ENDWHERE               
431         ENDIF
432
433
434       !! Evergreen species do not experience climatic senescence
435       CASE ( 'none' )
436
437         
438       !! In case no climatic senescence type is recognized.
439       CASE default
440
441          WRITE(numout,*) '  turnover: don''t know how to treat this PFT.'
442          WRITE(numout,*) '  number (::j) : ',j
443          WRITE(numout,*) '  senescence type (::senescence_type(j)) : ',senescence_type(j)
444
445          CALL ipslerr_p(3,"turn","Dont know how to treat this PFT.","","")
446
447       END SELECT
448
449       !! 3.2 Drop leaves and roots, plus stems and fruits for grasses
450
451       IF ( is_tree(j) ) THEN
452
453          !! 3.2.1 Trees in climatic senescence lose their fine roots at the same rate as they lose their leaves.
454          !        The rate of biomass loss of both fine roots and leaves is presribed through the equation:
455          !        \latexonly
456          !        \input{turnover_clim_senes_biomass_eqn4.tex}
457          !        \endlatexonly
458          !        \n
459          !         with ::leaffall(j) a PFT-dependent time constant which is given in ::stomate_constants),
460          WHERE ( senescence(:,j) )
461
462             turnover(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) * dt / leaffall(j)
463             turnover(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) * dt / leaffall(j)
464             turnover(:,j,ileaf,initrogen) = biomass(:,j,ileaf,initrogen) * dt / leaffall(j)
465             turnover(:,j,iroot,initrogen) = biomass(:,j,iroot,initrogen) * dt / leaffall(j)
466
467
468          ENDWHERE
469
470       ELSE
471
472          !! 3.2.2 In grasses, leaf senescence is extended to the whole plant
473          !        In grasses, leaf senescence is extended to the whole plant (all carbon pools) except to its
474          !        carbohydrate reserve.     
475
476          IF (senescence_type(j) .EQ. 'crop') THEN
477             ! 3.2.2.1 crops with 'crop' phenological model
478             WHERE ( senescence(:,j) )
479                turnover(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) * dt / leaffall(j)
480                turnover(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) * dt / leaffall(j)
481                turnover(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) * dt / leaffall(j)
482                turnover(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) * dt /leaffall(j)
483
484                turnover(:,j,ileaf,initrogen) = biomass(:,j,ileaf,initrogen) * dt / leaffall(j)
485                turnover(:,j,iroot,initrogen) = biomass(:,j,iroot,initrogen) * dt / leaffall(j)
486                turnover(:,j,isapabove,initrogen) = biomass(:,j,isapabove,initrogen) * dt / leaffall(j)
487                turnover(:,j,ifruit,initrogen) = biomass(:,j,ifruit,initrogen) * 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
497                turnover(:,j,ileaf,initrogen) = biomass(:,j,ileaf,initrogen) * dt / turnover_time(:,j)
498                turnover(:,j,isapabove,initrogen) = biomass(:,j,isapabove,initrogen) * dt / turnover_time(:,j)
499                turnover(:,j,iroot,initrogen) = biomass(:,j,iroot,initrogen) * dt / turnover_time(:,j) 
500                turnover(:,j,ifruit,initrogen) = biomass(:,j,ifruit,initrogen) * dt / turnover_time(:,j)
501             ENDWHERE
502          ENDIF
503       ENDIF      ! tree/grass
504
505       biomass(:,j,ileaf,:) = biomass(:,j,ileaf,:) - turnover(:,j,ileaf,:)
506       biomass(:,j,isapabove,:) = biomass(:,j,isapabove,:) - turnover(:,j,isapabove,:)
507       biomass(:,j,iroot,:) = biomass(:,j,iroot,:) - turnover(:,j,iroot,:)
508       biomass(:,j,ifruit,:) = biomass(:,j,ifruit,:) - turnover(:,j,ifruit,:)
509
510       biomass(:,j,ilabile,initrogen) = biomass(:,j,ilabile,initrogen) &
511            + recycle_leaf(j) * turnover(:,j,ileaf,initrogen) &
512            + recycle_root(j) * turnover(:,j,iroot,initrogen) 
513
514       turnover(:,j,ileaf,initrogen) = turnover(:,j,ileaf,initrogen) * ( 1.0 - recycle_leaf(j) )
515       turnover(:,j,iroot,initrogen) = turnover(:,j,iroot,initrogen) * ( 1.0 - recycle_root(j) )
516
517    ENDDO        ! loop over PFTs
518
519    !! 4. Leaf fall
520    !     At a certain age, leaves fall off, even if the climate would allow a green plant
521    !     all year round. Even if the meteorological conditions are favorable for leaf maintenance,
522    !     plants, and in particular, evergreen trees, have to renew their leaves simply because the
523    !     old leaves become inefficient.   
524    !     Roots, fruits (and stems) follow leaves. The decay rate varies with leaf age.
525    !     Note that plant is not declared senescent in this case (wchich is important for allocation:
526    !     if the plant loses leaves because of their age, it can renew them).
527    !
528    !     The leaf turnover rate due to aging of leaves is calculated using the following equation:
529    !     \latexonly
530    !     \input{turnover_age_senes_biomass_eqn5.tex}
531    !     \endlatexonly
532    !     \n
533    DO j = 2,nvm ! Loop over # PFTs
534
535       !! save old leaf mass
536       lm_old(:) = biomass(:,j,ileaf,icarbon)
537
538       !! initialize leaf mass change in age class
539       delta_lm(:,:) = zero
540
541       IF ( is_tree(j) .OR. (.NOT. natural(j)) ) THEN
542
543          !! 4.1 Trees: leaves, roots, fruits roots and fruits follow leaves.
544
545          !! 4.1.1 Critical age: prescribed for trees
546          leaf_age_crit(:,j) = leafagecrit(j)
547
548       ELSE
549
550          !! 4.2 Grasses: leaves, roots, fruits, sap follow leaves.
551
552          !! 4.2.1 Critical leaf age depends on long-term temperature
553          !        Critical leaf age depends on long-term temperature
554          !        generally, lower turnover in cooler climates.
555          leaf_age_crit(:,j) = &
556               MIN( leafagecrit(j) * leaf_age_crit_coeff(1) , &
557               MAX( leafagecrit(j) * leaf_age_crit_coeff(2) , &
558               leafagecrit(j) - leaf_age_crit_coeff(3) * &
559               ( t2m_longterm(:)-ZeroCelsius - leaf_age_crit_tref ) ) )
560
561       END IF
562         
563       ! 4.2.2 Loop over leaf age classes
564       DO m = 1, nleafages
565
566          turnover_rate(:) = zero
567
568          WHERE ( leaf_age(:,j,m) .GT. leaf_age_crit(:,j)/2. )
569
570             turnover_rate(:) =  &
571                  MIN( 0.99_r_std, dt / ( leaf_age_crit(:,j) * &
572                  ( leaf_age_crit(:,j) / leaf_age(:,j,m) )**quatre ) )
573
574          ENDWHERE
575         
576          dturnover(:) = biomass(:,j,ileaf,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
577          turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + dturnover(:)
578          biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - dturnover(:)
579
580          ! save leaf mass change
581          delta_lm(:,m) = - dturnover(:)
582         
583          dturnover(:) = biomass(:,j,iroot,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
584          turnover(:,j,iroot,icarbon) = turnover(:,j,iroot,icarbon) + dturnover(:)
585          biomass(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) - dturnover(:)
586         
587          dturnover(:) = biomass(:,j,ifruit,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
588          turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + dturnover(:)
589          biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - dturnover(:)
590
591
592          !! for N pools
593          dturnover(:) = biomass(:,j,ileaf,initrogen) * leaf_frac(:,j,m) * turnover_rate(:)
594          turnover(:,j,ileaf,initrogen) = turnover(:,j,ileaf,initrogen) + ( 1.0 - recycle_leaf(j) ) * dturnover(:)
595          biomass(:,j,ilabile,initrogen) = biomass(:,j,ilabile,initrogen) + recycle_leaf(j) * dturnover(:)
596          biomass(:,j,ileaf,initrogen) = biomass(:,j,ileaf,initrogen) - dturnover(:) 
597
598          dturnover(:) = biomass(:,j,iroot,initrogen) * leaf_frac(:,j,m) * turnover_rate(:)
599          turnover(:,j,iroot,initrogen) = turnover(:,j,iroot,initrogen) + ( 1.0 - recycle_root(j) ) * dturnover(:)
600          biomass(:,j,ilabile,initrogen) = biomass(:,j,ilabile,initrogen) + recycle_root(j) * dturnover(:)
601          biomass(:,j,iroot,initrogen) = biomass(:,j,iroot,initrogen) - dturnover(:)
602
603          dturnover(:) = biomass(:,j,ifruit,initrogen) * leaf_frac(:,j,m) * turnover_rate(:)
604          turnover(:,j,ifruit,initrogen) = turnover(:,j,ifruit,initrogen) + dturnover(:) 
605          biomass(:,j,ifruit,initrogen) = biomass(:,j,ifruit,initrogen) - dturnover(:) 
606         
607          IF (.NOT. is_tree(j)) THEN
608             dturnover(:) = biomass(:,j,isapabove,icarbon) * leaf_frac(:,j,m) * turnover_rate(:)
609             turnover(:,j,isapabove,icarbon) = turnover(:,j,isapabove,icarbon) + dturnover(:)
610             biomass(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) - dturnover(:)
611
612             dturnover(:) = biomass(:,j,isapabove,initrogen) * leaf_frac(:,j,m) * turnover_rate(:)
613             turnover(:,j,isapabove,initrogen) = turnover(:,j,isapabove,initrogen) + dturnover(:) 
614             biomass(:,j,isapabove,initrogen) = biomass(:,j,isapabove,initrogen) - dturnover(:) 
615          ENDIF
616         
617       ENDDO
618
619       !! 4.3 Recalculate the fraction of leaf biomass in each leaf age class.
620       !      Older leaves will fall more fast than younger leaves and therefore
621       !      the leaf age distribution needs to be recalculated after turnover.
622       !      The fraction of biomass in each leaf class is updated using the following equation:
623       !      \latexonly
624       !      \input{turnover_update_LeafAgeDistribution_eqn6.tex}
625       !      \endlatexonly
626       !      \n
627       !
628       !      new fraction = new leaf mass of that fraction / new total leaf mass
629       !                   = (old fraction*old total leaf mass ::lm_old(:) + biomass change of that fraction ::delta_lm(:,m)  ) /
630       !                     new total leaf mass ::biomass(:,j,ileaf
631       DO m = 1, nleafages
632         
633          WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_sechiba )
634             leaf_frac(:,j,m) = ( leaf_frac(:,j,m)*lm_old(:) + delta_lm(:,m) ) / biomass(:,j,ileaf,icarbon)
635          ELSEWHERE
636             leaf_frac(:,j,m) = zero
637          ENDWHERE
638       
639       ENDDO
640       
641    ENDDO         ! loop over PFTs
642
643    !! 5. New (provisional) LAI
644    !     ::lai(:,j) is determined from the leaf biomass ::biomass(:,j,ileaf,icarbon) and the
645    !     specific leaf surface :: sla(j) (m^2 gC^{-1})
646    !     The leaf area index is updated using the following equation:
647    !     \latexonly
648    !     \input{turnover_update_LAI_eqn7.tex}
649    !     \endlatexonly
650    !     \n
651
652    !    lai(:,ibare_sechiba) = zero
653    !    DO j = 2, nvm ! Loop over # PFTs
654    !        lai(:,j) = biomass(:,j,ileaf,icarbon) * sla(j)
655    !    ENDDO
656
657    !! 6. Definitely drop all leaves if there is a very low leaf mass during senescence.
658
659    !     Both for deciduous trees and grasses same conditions are checked:
660    !     If biomass is large enough (i.e. when it is greater than zero),
661    !     AND when senescence is set to true
662    !     AND the leaf biomass drops below a critical minimum biomass level (i.e. when it is lower than half
663    !     the minimum initial LAI ::lai_initmin(j) divided by the specific leaf area ::sla(j),
664    !     ::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),
665    !     If these conditions are met, the flag ::shed_rest(:) is set to TRUE.
666    !
667    !     After this, the biomass of different carbon pools both for trees and grasses is set to zero
668    !     and the mean leaf age is reset to zero.
669    !     Finally, the leaf fraction and leaf age of the different leaf age classes is set to zero.
670    DO j = 2,nvm ! Loop over # PFTs
671
672       shed_rest(:) = .FALSE.
673
674       !! 6.1 For deciduous trees: next to leaves, also fruits and fine roots are dropped
675       !      For deciduous trees: next to leaves, also fruits and fine roots are dropped: fruit ::biomass(:,j,ifruit)
676       !      and fine root ::biomass(:,j,iroot) carbon pools are set to zero.
677       IF ( is_tree(j) .AND. ( senescence_type(j) .NE. 'none' ) ) THEN
678
679          ! check whether we shed the remaining leaves
680          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. senescence(:,j) .AND. &
681               ( biomass(:,j,ileaf,icarbon) .LT. (lai_initmin(j) / 2.)/slainit(j) )             )
682
683             shed_rest(:) = .TRUE.
684
685             turnover(:,j,ileaf,icarbon)  = turnover(:,j,ileaf,icarbon) + biomass(:,j,ileaf,icarbon)
686             turnover(:,j,iroot,icarbon)  = turnover(:,j,iroot,icarbon) + biomass(:,j,iroot,icarbon)
687             turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + biomass(:,j,ifruit,icarbon)
688
689             biomass(:,j,ileaf,icarbon)  = zero
690             biomass(:,j,iroot,icarbon)  = zero
691             biomass(:,j,ifruit,icarbon) = zero
692
693             ! for N pools
694             turnover(:,j,ileaf,initrogen) = turnover(:,j,ileaf,initrogen) &
695                  + (1.0-recycle_leaf(j)) * biomass(:,j,ileaf,initrogen)
696             turnover(:,j,iroot,initrogen) = turnover(:,j,iroot,initrogen) &
697                  + (1.0-recycle_root(j)) * biomass(:,j,iroot,initrogen)
698             turnover(:,j,ifruit,initrogen) = turnover(:,j,ifruit,initrogen) &
699                  + biomass(:,j,ifruit,initrogen)
700
701             biomass(:,j,ilabile,initrogen) = biomass(:,j,ilabile,initrogen) &
702                  + recycle_leaf(j) * biomass(:,j,ileaf,initrogen) &
703                  + recycle_root(j) * biomass(:,j,iroot,initrogen)             
704             biomass(:,j,ileaf,initrogen) = zero
705             biomass(:,j,iroot,initrogen) = zero
706             biomass(:,j,ifruit,initrogen) = zero
707
708             ! reset leaf age and lai
709             leaf_meanage(:,j) = zero
710             lai(:,j) = zero
711          ENDWHERE
712
713       ENDIF
714
715       !! 6.2 For grasses: all aboveground carbon pools, except the carbohydrate reserves are affected:
716       !      For grasses: all aboveground carbon pools, except the carbohydrate reserves are affected:
717       !      fruit ::biomass(:,j,ifruit,icarbon), fine root ::biomass(:,j,iroot,icarbon) and sapwood above
718       !      ::biomass(:,j,isapabove,icarbon) carbon pools are set to zero.
719       IF ( .NOT. is_tree(j) ) THEN
720
721          ! Shed the remaining leaves if LAI very low.
722          WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. senescence(:,j) .AND. &
723               (  biomass(:,j,ileaf,icarbon) .LT. (lai_initmin(j) / 2.)/slainit(j) ))
724
725             shed_rest(:) = .TRUE.
726
727             turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + biomass(:,j,ileaf,icarbon)
728             turnover(:,j,isapabove,icarbon) = turnover(:,j,isapabove,icarbon) + biomass(:,j,isapabove,icarbon)
729             turnover(:,j,iroot,icarbon) = turnover(:,j,iroot,icarbon) + biomass(:,j,iroot,icarbon)
730             turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + biomass(:,j,ifruit,icarbon)
731
732             biomass(:,j,ileaf,icarbon) = zero
733             biomass(:,j,isapabove,icarbon) = zero
734             biomass(:,j,iroot,icarbon) = zero
735             biomass(:,j,ifruit,icarbon) = zero
736
737             turnover(:,j,ileaf,initrogen) = turnover(:,j,ileaf,initrogen) &
738                  + (1.0-recycle_leaf(j)) * biomass(:,j,ileaf,initrogen)
739             turnover(:,j,iroot,initrogen) = turnover(:,j,iroot,initrogen) &
740                  + (1.0-recycle_root(j)) * biomass(:,j,iroot,initrogen)
741             turnover(:,j,ifruit,initrogen) = turnover(:,j,ifruit,initrogen) &
742                  + biomass(:,j,ifruit,initrogen)
743
744             biomass(:,j,ilabile,initrogen) = biomass(:,j,ilabile,initrogen) &
745                  + recycle_leaf(j) * biomass(:,j,ileaf,initrogen) &
746                  + recycle_root(j) * biomass(:,j,iroot,initrogen)             
747             biomass(:,j,ileaf,initrogen) = zero
748             biomass(:,j,iroot,initrogen) = zero
749             biomass(:,j,ifruit,initrogen) = zero
750
751             ! reset leaf age and lai
752             leaf_meanage(:,j) = zero
753             lai(:,j) = zero
754          ENDWHERE
755
756       ENDIF
757
758       !! 6.3 Reset the leaf age structure: the leaf fraction and leaf age of the different leaf age classes is set to zero.
759     
760       DO m = 1, nleafages
761
762          WHERE ( shed_rest(:) )
763
764             leaf_age(:,j,m) = zero
765             leaf_frac(:,j,m) = zero
766
767          ENDWHERE
768
769       ENDDO
770
771    ENDDO          ! loop over PFTs
772   
773    !! 7. Herbivore activity: elephants, cows, gazelles but no lions.
774 
775    !     Herbivore activity affects the biomass of leaves and fruits as well
776    !     as stalks (only for grasses). Herbivore activity does not modify leaf
777    !     age structure. Herbivores ::herbivores(:,j) is the time constant of
778    !     probability of a leaf to be eaten by a herbivore, and is calculated in
779    !     ::stomate_season. following Mc Naughton et al. [1989].
780
781    IF ( ok_herbivores ) THEN
782
783       ! If the herbivore activity is allowed (if ::ok_herbivores is true, which is set in run.def),
784       ! remove the amount of biomass consumed by herbivory from the leaf biomass ::biomass(:,j,ileaf,icarbon) and
785       ! the fruit biomass ::biomass(:,j,ifruit,icarbon).
786       ! The daily amount consumed equals the biomass multiplied by 1 day divided by the time constant ::herbivores(:,j).
787       DO j = 2,nvm ! Loop over # PFTs
788
789          IF ( is_tree(j) ) THEN
790
791             !! For trees: only the leaves and fruit carbon pools are affected
792
793             WHERE (biomass(:,j,ileaf,icarbon) .GT. zero)
794                ! added by shilong
795                WHERE (herbivores(:,j).GT. min_sechiba)
796                   dturnover(:) = biomass(:,j,ileaf,icarbon) * dt / herbivores(:,j)
797                   turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + dturnover(:)
798                   biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - dturnover(:)
799
800                   dturnover(:) = biomass(:,j,ileaf,initrogen) * dt / herbivores(:,j) 
801                   turnover(:,j,ileaf,initrogen) = turnover(:,j,ileaf,initrogen) + dturnover(:)
802                   biomass(:,j,ileaf,initrogen) = biomass(:,j,ileaf,initrogen) - dturnover(:) 
803
804
805                   dturnover(:) = biomass(:,j,ifruit,icarbon) * dt / herbivores(:,j)
806                   turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + dturnover(:)
807                   biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - dturnover(:)
808
809                   dturnover(:) = biomass(:,j,ifruit,initrogen) * dt / herbivores(:,j)
810                   turnover(:,j,ifruit,initrogen) = turnover(:,j,ifruit,initrogen) + dturnover(:) 
811                   biomass(:,j,ifruit,initrogen) = biomass(:,j,ifruit,initrogen) - dturnover(:) 
812                ENDWHERE
813             ENDWHERE
814
815          ELSE
816
817             ! For grasses: all aboveground carbon pools are affected: leaves, fruits and sapwood above
818             WHERE ( biomass(:,j,ileaf,icarbon) .GT. zero )
819                ! added by shilong
820                WHERE (herbivores(:,j) .GT. min_sechiba)
821                   dturnover(:) = biomass(:,j,ileaf,icarbon) * dt / herbivores(:,j)
822                   turnover(:,j,ileaf,icarbon) = turnover(:,j,ileaf,icarbon) + dturnover(:)
823                   biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - dturnover(:)
824
825                  dturnover(:) = biomass(:,j,ileaf,initrogen) * dt / herbivores(:,j) 
826                   turnover(:,j,ileaf,initrogen) = turnover(:,j,ileaf,initrogen) + dturnover(:)
827                   biomass(:,j,ileaf,initrogen) = biomass(:,j,ileaf,initrogen) - dturnover(:) 
828
829                   dturnover(:) = biomass(:,j,isapabove,icarbon) * dt / herbivores(:,j)
830                   turnover(:,j,isapabove,icarbon) = turnover(:,j,isapabove,icarbon) + dturnover(:)
831                   biomass(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) - dturnover(:)
832
833                   dturnover(:) = biomass(:,j,isapabove,initrogen)  * dt / herbivores(:,j)
834                   turnover(:,j,isapabove,initrogen) = turnover(:,j,isapabove,initrogen) + dturnover(:) 
835                   biomass(:,j,isapabove,initrogen) = biomass(:,j,isapabove,initrogen) - dturnover(:) 
836
837
838                   dturnover(:) = biomass(:,j,ifruit,icarbon) * dt / herbivores(:,j)
839                   turnover(:,j,ifruit,icarbon) = turnover(:,j,ifruit,icarbon) + dturnover(:)
840                   biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - dturnover(:)
841
842                   dturnover(:) = biomass(:,j,ifruit,initrogen) * dt / herbivores(:,j)
843                   turnover(:,j,ifruit,initrogen) = turnover(:,j,ifruit,initrogen) + dturnover(:) 
844                   biomass(:,j,ifruit,initrogen) = biomass(:,j,ifruit,initrogen) - dturnover(:) 
845                ENDWHERE
846
847             ENDWHERE
848
849          ENDIF  ! tree/grass?
850
851       ENDDO    ! loop over PFTs
852
853    ENDIF ! end herbivores
854
855    !! 8. Fruit turnover for trees
856
857    !     Fruit turnover for trees: trees simply lose their fruits with a time constant ::tau_fruit(j),
858    !     that is set to 90 days for all PFTs in ::stomate_constants
859
860    DO k = 1,nelements 
861       DO j = 2,nvm ! Loop over # PFTs
862          IF ( is_tree(j) ) THEN
863
864             dturnover(:) = biomass(:,j,ifruit,k) * dt / tau_fruit(j)
865             turnover(:,j,ifruit,k) = turnover(:,j,ifruit,k) + dturnover(:)
866             biomass(:,j,ifruit,k) = biomass(:,j,ifruit,k) - dturnover(:)
867             
868          ENDIF
869       ENDDO       ! loop over PFTs
870    END DO
871
872    !! 9 Conversion of sapwood to heartwood both for aboveground and belowground sapwood and heartwood.
873
874    !   Following LPJ (Sitch et al., 2003), sapwood biomass is converted into heartwood biomass
875    !   with a time constant tau ::tau_sap(j) of 1 year.
876    !   Note that this biomass conversion is not added to "turnover" as the biomass is not lost!
877    DO j = 2,nvm ! Loop over # PFTs
878
879       IF ( is_tree(j) ) THEN
880
881          !! For the recalculation of age in 9.2 (in case the vegetation is not dynamic ie. ::ok_dgvm is FALSE),
882          !! the heartwood above and below is stored in ::hw_old(:).
883          IF ( .NOT. ok_dgvm ) THEN
884             hw_old(:) = biomass(:,j,iheartabove,icarbon) + biomass(:,j,iheartbelow,icarbon)
885          ENDIF
886
887          !! 9.1 Calculate the rate of sapwood to heartwood conversion
888          !      Calculate the rate of sapwood to heartwood conversion with the time constant ::tau_sap(j)
889          !      and update aboveground and belowground sapwood ::biomass(:,j,isapabove) and ::biomass(:,j,isapbelow)
890          !      and heartwood ::biomass(:,j,iheartabove) and ::biomass(:,j,iheartbelow).
891
892          DO k = 1,nelements
893
894             ! Above the ground
895             sapconv(:) = biomass(:,j,isapabove,k) * dt / tau_sap(j)
896             biomass(:,j,isapabove,k) = biomass(:,j,isapabove,k) - sapconv(:)
897             biomass(:,j,iheartabove,k) =  biomass(:,j,iheartabove,k) + sapconv(:)
898             
899             ! Below the ground
900             sapconv(:) = biomass(:,j,isapbelow,k) * dt / tau_sap(j)
901             biomass(:,j,isapbelow,k) = biomass(:,j,isapbelow,k) - sapconv(:)
902             biomass(:,j,iheartbelow,k) =  biomass(:,j,iheartbelow,k) + sapconv(:)
903
904          END DO
905
906          !! 9.2 If the vegetation is not dynamic, the age of the plant is decreased.
907          !      The updated heartwood, the sum of new heartwood above and new heartwood below after
908          !      converting sapwood to heartwood, is saved as ::hw_new(:) .
909          !      Creation of new heartwood decreases the age of the plant with a factor that is determined by:
910          !      old heartwood ::hw_old(:) divided by the new heartwood ::hw_new(:)
911          IF ( .NOT. ok_dgvm ) THEN
912
913             hw_new(:) = biomass(:,j,iheartabove,icarbon) + biomass(:,j,iheartbelow,icarbon)
914
915             WHERE ( hw_new(:) .GT. min_sechiba )
916
917                age(:,j) = age(:,j) * hw_old(:)/hw_new(:)
918
919             ENDWHERE
920
921          ENDIF
922
923       ENDIF
924
925    ENDDO       ! loop over PFTs
926
927
928!    WRITE(numout,*) '***** turnover_time:',turnover_time(:,:)
929
930    CALL xios_orchidee_send_field("HERBIVORES",herbivores)
931    CALL xios_orchidee_send_field("LEAF_AGE",leaf_meanage)
932   
933
934    ! Write mean leaf age and time constant of probability of a leaf to be eaten by a herbivore
935    ! to the stomate output file.
936    CALL histwrite_p (hist_id_stomate, 'LEAF_AGE', itime, &
937         leaf_meanage, npts*nvm, horipft_index)
938    CALL histwrite_p (hist_id_stomate, 'HERBIVORES', itime, &
939         herbivores, npts*nvm, horipft_index)
940
941    IF (printlev>=4) WRITE(numout,*) 'Leaving turnover'
942
943  END SUBROUTINE turn
944
945END MODULE stomate_turnover
Note: See TracBrowser for help on using the repository browser.