source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/stomate_turnover.f90 @ 6737

Last change on this file since 6737 was 5149, checked in by chao.yue, 6 years ago

Add mass balance check for land use change

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