source: branches/publications/ORCHIDEE-Hillslope-r6515/src_stomate/stomate_phenology.f90 @ 7442

Last change on this file since 7442 was 5745, checked in by thomas.verbeke, 5 years ago

Update GW version of ORCHIDEE-GW branche:
1) Addition of these trunk changesets:
https://forge.ipsl.jussieu.fr/orchidee/changeset/5433/trunk/ORCHIDEE
https://forge.ipsl.jussieu.fr/orchidee/changeset/5536/trunk/ORCHIDEE
https://forge.ipsl.jussieu.fr/orchidee/changeset/5573/trunk/ORCHIDEE
https://forge.ipsl.jussieu.fr/orchidee/changeset/5614/trunk/ORCHIDEE

2) Modification of wtd calculation in hydrol.f90
3) Modification of .xml files

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 83.4 KB
Line 
1! =================================================================================================================================
2! MODULE        : stomate_phenology
3!
4! CONTACT       : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE       : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>\BRIEF        This module manages the beginning of the growing season (leaf onset).
9!!     
10!!\n DESCRIPTION: None
11!!
12!! RECENT CHANGE(S): None
13!!
14!! SVN          :
15!! $HeadURL$
16!! $Date$
17!! $Revision$
18!! \n
19!_ =================================================================================================================================
20
21MODULE stomate_phenology
22
23  ! modules used:
24  USE xios_orchidee
25  USE ioipsl_para
26  USE stomate_data
27  USE constantes
28  USE pft_parameters
29  USE time, ONLY : LastTsYear
30
31  IMPLICIT NONE
32
33  ! private & public routines
34
35  PRIVATE
36  PUBLIC phenology,phenology_clear
37
38  ! first call
39  LOGICAL, SAVE                                              :: firstcall_all_phenology = .TRUE.
40!$OMP THREADPRIVATE(firstcall_all_phenology)
41  LOGICAL, SAVE                                              :: firstcall_hum = .TRUE.
42!$OMP THREADPRIVATE(firstcall_hum)
43  LOGICAL, SAVE                                              :: firstcall_moi = .TRUE.
44!$OMP THREADPRIVATE(firstcall_moi)
45  LOGICAL, SAVE                                              :: firstcall_humgdd = .TRUE.
46!$OMP THREADPRIVATE(firstcall_humgdd)
47  LOGICAL, SAVE                                              :: firstcall_moigdd = .TRUE.
48!$OMP THREADPRIVATE(firstcall_moigdd)
49
50CONTAINS
51
52
53!! ================================================================================================================================
54!! SUBROUTINE   : phenology_clear
55!!
56!>\BRIEF          Flags setting   
57!!
58!! DESCRIPTION  : This subroutine sets flags
59!!                ::firstcall_all_phenology, ::firstcall_hum, ::firstcall_moi, ::firstcall_humgdd,
60!!                ::firstcall_moigdd to .TRUE., and therefore activates section 1.1 of each
61!!                subroutine which writes messages to the output. \n
62!!                This subroutine is called at the beginning of ::stomateLpj_clear in the
63!!                ::stomate_lpj module.
64!!
65!! RECENT CHANGE(S): None
66!!
67!! MAIN OUTPUT VARIABLE(S): ::firstcall_all_phenology, ::firstcall_hum, ::firstcall_moi, ::firstcall_humgdd,
68!!                ::firstcall_moigdd
69!!
70!! REFERENCE(S)  : None
71!!
72!! FLOWCHART     : None
73!! \n
74!_ ================================================================================================================================
75
76  SUBROUTINE phenology_clear
77    firstcall_all_phenology=.TRUE.
78    firstcall_hum=.TRUE.
79    firstcall_moi = .TRUE.
80    firstcall_humgdd = .TRUE.
81    firstcall_moigdd = .TRUE.
82  END SUBROUTINE phenology_clear
83
84
85!! ================================================================================================================================
86!! SUBROUTINE   : phenology
87!!
88!>\BRIEF          This subroutine controls the detection of the beginning of the growing season
89!!                (if dormancy has been long enough), leaf onset, given favourable biometeorological
90!!                conditions, and leaf growth and biomass allocation when leaf biomass is low (i.e.
91!!                at the start of the growing season.
92!!
93!! DESCRIPTION  : This subroutine is called by the module ::stomate_lpj and deals with the beginning of the 
94!!                growing season. First it is established whether the beginning of the growing season is
95!!                allowed. This occurs if the dormance period has been long enough (i.e. greater
96!!                than a minimum PFT-dependent threshold, specified by ::lowgpp_time),
97!!                AND if the last beginning of the growing season was a sufficiently long time ago
98!!                (i.e. when the growing season length is greater than a minimum threshold, specified
99!!                by ::min_growthinit_time, which is defined in this module to be 300 days. \n
100!!                The dormancy time-length is represented by the variable
101!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
102!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
103!!                it is set to zero. \n
104!!                ::lowgpp_time is set for each PFT in ::stomate_data from a table of all
105!!                PFT values (::lowgpp_time_tab), which is defined in ::stomate_constants. \n
106!!                The growing season length is given by ::when_growthinit, which increases
107!!                by the stomate time-step at each call to this phenology module, except for when
108!!                leaf onset is detected, when it is set to 0. \n
109!!                If these two conditions are met, leaf onset occurs if the biometeorological
110!!                conditions are also met. This is determined by the leaf onset models, which are
111!!                biome-specific. Each PFT is looped over (ignoring bare soil).
112!!                The onset phenology model is selected, (according to the parameter
113!!                ::pheno_model, which is initialised in stomate_data), and called. \n
114!!                There are six leaf onset phenology models currently being used by ORCHIDEE.
115!!                These are: 'hum' and 'moi', which are based exclusively on moisture conditions,
116!!                'humgdd' and 'moigdd', which are based on both temperature and moisture conditions,
117!!                'ncdgdd', which is based on a "chilling" requirement for leaf onset, and
118!!                'ngd', which is based on the number of growing days since the temperature was
119!!                above a certain threshold, to account for the end of soil frost.
120!!                Those models which are based mostly on temperature conditions are used for
121!!                temperate and boreal biomes, and those which include a moisture condition are used
122!!                for tropical biomes. More detail on the biometeorological conditions is provided
123!!                in the sections on the individual onset models. \n
124!!                The moisture conditions are based on the concept of plant "moisture availability".
125!!                This is based on the soil humidity (relative soil moisture), but is moderated by
126!!                the root density profile, as per the equation:
127!!                \latexonly
128!!                \input{phenology_moiavail_eqn1.tex}
129!!                \endlatexonly
130!!                \n
131!!                Although some studies have shown that the length of the photoperiod is important
132!!                in determining onset (and senescence) dates, this is not considered in the current
133!!                versions of the onset models (Krinner et al., 2005). \n
134!!                If conditions are favourable, leaf onset occurs (::begin_leaves is set to TRUE),
135!!                ::when_growthinit is set to 0.0, and the growing season has begun. \n
136!!                Following the detection of leaf onset, biomass is allocated from the carbohydrate
137!!                reserves equally to the leaves and roots IF the leaf biomass is lower than a minimum
138!!                threshold, which is calculated in this subroutine from the parameter
139!!                ::lai_initmin, divided by the specific leaf area (both of which are
140!!                PFT-dependent and set in ::stomate_constants). \n
141!!                Finally, if biomass is required to be allocated from the carbohydrate reserve
142!!                because the leaf biomass is too low, the leaf age and leaf age distribution is
143!!                re-set. In this case the youngest age class fraction is set to 1 and all other   
144!!                leaf age class fractions are set to 0. All leaf ages are set to 0. If there is
145!!                no biomass in the carbohydrate reserve, leaf onset will not occur and the PFT
146!!                will disappear from the grid cell (Krinner et al., 2005). \n
147!!                This subrouting is called in ::stomate_lpj.
148!!
149!! RECENT CHANGE(S): None
150!!
151!! MAIN OUTPUT VARIABLE(S): ::biomass,
152!!                        ::when_growthinit,
153!!                        ::leaf age distribution
154!!                        ::leaf fraction
155!!
156!! REFERENCE(S) :
157!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
158!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
159!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
160!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
161!!
162!! FLOWCHART    :
163!! \latexonly
164!! \includegraphics[scale = 1]{phenology_flowchart.png}
165!! \endlatexonly
166!! \n
167!_ ================================================================================================================================
168
169  SUBROUTINE phenology (npts, dt, PFTpresent, &
170       veget_cov_max, &
171       t2m_longterm, t2m_month, t2m_week, gpp, &
172       maxmoiavail_lastyear, minmoiavail_lastyear, &
173       moiavail_month, moiavail_week, &
174       gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
175       senescence, time_hum_min, &
176       biomass, leaf_frac, leaf_age, &
177       when_growthinit, co2_to_bm, &
178       begin_leaves)
179
180    !
181    !! 0. Variable and parameter declaration
182    !
183
184    !
185    !! 0.1 Input variables
186    !
187    INTEGER(i_std), INTENT(in)                                          :: npts                 !! Domain size - number of grid
188                                                                                                !! cells (unitless)
189    REAL(r_std), INTENT(in)                                             :: dt                   !! time step (dt_days)
190    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                            :: PFTpresent           !! PFT exists (true/false)
191    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: veget_cov_max        !! "maximal" coverage fraction of a
192                                                                                                !! PFT (LAI -> infinity) on ground
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
197                                                                                                !! (K)
198    REAL(r_std), DIMENSION(npts), INTENT(in)                            :: t2m_week             !! "weekly" 2-meter temperatures (K)
199    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: gpp                  !! daily gross primary productivity
200                                                                                                !! @tex ($gC m^{-2} of
201                                                                                                !! ground/day$) @endtex
202    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: maxmoiavail_lastyear !! last year's maximum moisture
203                                                                                                !! availability (0-1, unitless)
204    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: minmoiavail_lastyear !! last year's minimum moisture
205                                                                                                !! availability (0-1, unitless)
206    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: moiavail_month       !! "monthly" moisture availability
207                                                                                                !! (0-1, unitless)
208    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: moiavail_week        !! "weekly" moisture availability
209                                                                                                !! (0-1, unitless)
210    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: gdd_m5_dormance      !! growing degree days above a
211                                                                                                !! threshold of -5 deg C (C)
212    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                     :: gdd_midwinter        !! growing degree days, since
213                                                                                                !! midwinter (C)
214    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: ncd_dormance         !! number of chilling days since
215                                                                                                !! leaves were lost (days)
216    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: ngd_minus5           !! number of growing days above a
217                                                                                                !! threshold of -5 deg C (days)
218    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                            :: senescence           !! is the plant senescent? (only
219                                                                                                !! for deciduous trees -
220                                                                                                !! carbohydrate reserve)
221                                                                                                !! (true/false)
222    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                        :: time_hum_min         !! time elapsed since strongest
223                                                                                                !! moisture availability (days)
224
225    !
226    !! 0.2 Ouput variables
227    !
228
229    !
230    !! 0.3 Modified variables
231    !
232    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout)    :: biomass              !! biomass @tex ($gC m^{-2} of
233                                                                                                !! ground$) @endtex
234    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)           :: leaf_frac            !! fraction of leaves in leaf age
235                                                                                                !! class (0-1, unitless)
236    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)           :: leaf_age             !! leaf age (days)
237    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                     :: when_growthinit      !! how many days since the
238                                                                                                !! beginning of the growing season
239                                                                                                !! (days)
240    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)                     :: co2_to_bm            !! co2 taken up by carbohydrate
241                                                                                                !! reserve at the beginning of the
242                                                                                                !! growing season @tex ($gC m^{-2}
243                                                                                                !! of total ground/day$) @endtex
244                                                                                                ! NV passge 2D
245    LOGICAL, DIMENSION(npts,nvm), INTENT(out)                           :: begin_leaves         !! signal to start putting leaves on (true/false)
246
247    !
248    !! 0.4 Local variables
249    !
250    LOGICAL, DIMENSION(npts,nvm)                                        :: allow_initpheno      !! are we allowed to decalre the
251                                                                                                !! beginning of the growing
252                                                                                                !! season? (true/false)
253    REAL(r_std), DIMENSION(npts)                                        :: bm_wanted            !! biomass we would like to have
254                                                                                                !! @tex ($gC m^{-2} of ground$)
255                                                                                                !! @endtex
256    REAL(r_std), DIMENSION(npts)                                        :: bm_use               !! biomass we use (from
257                                                                                                !! carbohydrate reserve or from
258                                                                                                !! atmosphere) @tex ($gC m^{-2} of
259                                                                                                !! ground$) @endtex
260    REAL(r_std), DIMENSION(npts)                                        :: lm_min               !! minimum leaf mass @tex ($gC
261                                                                                                !! m^{-2} of ground$) @endtex
262    LOGICAL(r_std), DIMENSION(npts)                                     :: age_reset            !! does the leaf age distribution
263                                                                                                !! have to be reset? (true/false)
264    INTEGER(i_std)                                                      :: i,j,m                !! indices (unitless)
265    REAL(r_std), DIMENSION(npts,nvm)                                    :: histvar              !! controls the history output
266                                                                                                !! level - 0: nothing is written;
267                                                                                                !! 10: everything is written
268                                                                                                !! (0-10, unitless)
269
270!_ ================================================================================================================================
271
272    IF (printlev>=3) WRITE(numout,*) 'Entering phenology'
273
274    !
275    !! 1. first call - output message giving the setting of the ::always_init
276    !!    and ::min_growthinit_time parameters.
277    !
278
279    IF ( firstcall_all_phenology ) THEN
280
281       IF (printlev >= 2) THEN
282          WRITE(numout,*) 'phenology:'
283
284          WRITE(numout,*) '   > take carbon from atmosphere if carbohydrate' // &
285               ' reserve too small (::always_init): ', always_init
286         
287          WRITE(numout,*) '   > minimum time since last beginning of a growing' // &
288               ' season (d) (::min_growthinit_time): ', min_growthinit_time
289       END IF
290       firstcall_all_phenology = .FALSE.
291
292    ENDIF
293
294    !
295    !! 2. Detection of the beginning of the growing season.
296    !
297
298    !
299    !! 2.1 allow detection of the beginning of the growing season if dormance was
300    !!     long enough (i.e. when ::time_lowgpp, which is calculated in ::stomate_season,
301    !!     is above a certain PFT-dependent threshold, ::lowgpp_time,
302    !!     which is given in ::stomate_constants),
303    !!     AND the last beginning of growing season was a sufficiently long time ago
304    !!     (i.e. when ::when_growthinit, which is calculated in this module,
305    !!     is greater than ::min_growthinit_time, which is declared at the beginning of this module).
306    !!     If these conditions are met, allow_initpheno is set to TRUE. Each PFT is looped over.
307    !
308
309    allow_initpheno(:,1) = .FALSE.
310    DO j = 2,nvm
311
312       WHERE ( when_growthinit(:,j) .GT. min_growthinit_time )
313          allow_initpheno(:,j) = .TRUE.
314       ELSEWHERE
315          allow_initpheno(:,j) = .FALSE.
316       ENDWHERE
317
318    ENDDO
319
320    WHERE(allow_initpheno)
321       histvar=un
322    ELSEWHERE
323       histvar=zero
324    ENDWHERE
325
326    CALL xios_orchidee_send_field("ALLOW_INITPHENO",histvar)
327
328    CALL histwrite_p (hist_id_stomate, 'ALLOW_INITPHENO', itime, histvar, npts*nvm, horipft_index)
329
330    !
331    !! 2.2 increase the ::when_growthinit counter, which gives the number of days since the beginning of the growing season.
332    !!     Needed for allocation and for the detection of the beginning of the growing season.
333    !
334
335    when_growthinit(:,:) = when_growthinit(:,:) + dt
336
337    !
338    !! 3. Leaf onset.
339    !!    Check biometeorological conditions using the onset phenological models,
340    !!    which are different for each PFT group (i.e. grass versus tropical etc.
341    !!    See below for more detail on the different models and which PFTs use each model).
342    !
343
344    !! - By default: phenology does not start (::begin_leaves set to FALSE).
345    begin_leaves(:,:) = .FALSE.
346
347    !! - The onset phenology model is selected, (according to the parameter ::pheno_model,
348    !! which is initialised in stomate_data), and called.
349    !! Each PFT is looped over (ignoring bare soil).
350    !! If conditions are favourable, begin_leaves is set to TRUE.
351   
352    ! parameter used in all the differents models of phenology
353    t_always = ZeroCelsius + t_always_add
354
355    DO j = 2,nvm ! Loop over # PFTs
356
357       SELECT CASE ( pheno_model(j) )
358
359       CASE ( 'hum' )
360
361          CALL pheno_hum (npts, j, PFTpresent, allow_initpheno, &
362               moiavail_month, moiavail_week, &
363               maxmoiavail_lastyear, minmoiavail_lastyear, &
364               begin_leaves)
365
366       CASE ( 'moi' )
367
368          CALL pheno_moi (npts, j, PFTpresent, allow_initpheno, &
369               time_hum_min, &
370               moiavail_month, moiavail_week, &
371               begin_leaves)
372
373
374       CASE ( 'ncdgdd' )
375
376          CALL pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
377               ncd_dormance, gdd_midwinter, &
378               t2m_month, t2m_week, begin_leaves)
379
380       CASE ( 'ngd' )
381
382          CALL pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd_minus5, &
383               t2m_month, t2m_week, begin_leaves)
384
385       CASE ( 'humgdd' )
386
387          CALL pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
388               maxmoiavail_lastyear, minmoiavail_lastyear, &
389               t2m_longterm, t2m_month, t2m_week, &
390               moiavail_week, moiavail_month, &
391               begin_leaves)
392
393       CASE ( 'moigdd' )
394
395          CALL pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd_m5_dormance, &
396               time_hum_min, &
397               t2m_longterm, t2m_month, t2m_week, &
398               moiavail_week, moiavail_month, &
399               begin_leaves)
400
401       CASE ( 'none' )
402
403          ! no action
404
405       CASE default
406
407          WRITE(numout,*) 'phenology: don''t know how to treat this PFT.'
408          WRITE(numout,*) '  number: (::j)',j
409          WRITE(numout,*) '  phenology model (::pheno_model(j)) : ',pheno_model(j)
410          CALL ipslerr_p(3,'stomate phenology','Cannot treat this PFT','','')
411
412       END SELECT
413
414    ENDDO
415
416    WHERE(begin_leaves)
417       histvar=un
418    ELSEWHERE
419       histvar=zero
420    ENDWHERE
421
422    CALL xios_orchidee_send_field("BEGIN_LEAVES",histvar)
423
424    CALL histwrite_p (hist_id_stomate, 'BEGIN_LEAVES', itime, histvar, npts*nvm, horipft_index)
425
426    !
427    !! 4. Leaf growth and biomass allocation when leaf biomass is low.
428    !!   Leaves start to grow if biometeorological conditions are favourable (::begin_leaves == TRUE) and if
429    !!   leaf growth is allowed (::allow_initpheno == TRUE).
430    !!   PFTs and then grid cells are looped over.
431    !
432
433    !! Added the case((pheno_model(j) == "none") .AND. (biomass(i,j,ileaf,icarbon).LT. min_sechiba)) condition
434    !! to deal with extreme cases when the evergreen leaf biomass reaches zero
435    IF ( LastTsYear ) THEN
436      DO j = 2, nvm
437        DO i = 1, npts
438          IF (((veget_cov_max(i,j) .GT. min_sechiba) .AND. always_init(j)) .AND. ((pheno_model(j) == "none") &
439                  .AND. (biomass(i,j,ileaf,icarbon) .LT. min_sechiba)))   THEN
440             lm_min(i) = lai_initmin(j) / sla(j)
441             biomass(i,j,ileaf,icarbon) = biomass(i,j,ileaf,icarbon) + lm_min(i)
442             biomass(i,j,iroot,icarbon) = biomass(i,j,iroot,icarbon) + lm_min(i)
443             co2_to_bm(i,j) = co2_to_bm(i,j) + ( lm_min(i) * 2 ) / dt
444             !! 4.0.1 fractions - set the youngest age class fraction to 1 and
445             !all other leaf age class fractions to 0.
446             leaf_frac(i,j,1) = un 
447             DO m = 2, nleafages 
448                leaf_frac(i,j,m) = zero 
449             ENDDO ! m = 2, nleafages
450             !! 4.0.2 ages - set all leaf ages to 0.
451             DO m = 1, nleafages 
452                leaf_age(i,j,m) = zero 
453             ENDDO ! m = 1, nleafages
454          ENDIF
455        END DO
456      END DO
457    END IF
458
459
460    DO j = 2,nvm ! Loop over # PFTs
461
462       age_reset(:) = .FALSE.
463
464       DO i = 1, npts
465
466          IF ( begin_leaves(i,j) ) THEN
467
468             !! 4.1 First minimum biomass is calculated using the following equation:
469             !!     \latexonly
470             !!     \input{phenology_lm_min_eqn2.tex}
471             !!     \endlatexonly
472             !!     \n
473
474             lm_min(i) = lai_initmin(j) / sla(j)
475
476             !! 4.2 If leaf biomass is lower than the minimum biomass then biomass must be allocated from the carbohydrate
477             !!     reserves to leaves and roots.
478
479             IF ( biomass(i,j,ileaf,icarbon) .LT. lm_min(i) ) THEN
480
481                !
482                !! 4.2.1 Determine how much biomass is available to use
483                !!       First calculate how much biomass is wanted/required
484                !!       (::bm_wanted = 2 x the minimum leaf biomass).
485                !
486
487                bm_wanted(i) = 2. * lm_min(i)
488
489                !! 4.2.2 If the biomass in the carbohydrate reserves is less than the required biomass
490                !!       take the required amount of carbon from the atmosphere and put it into the
491                !!       carbohydrate reserve. This only occurs if the parameter ::always_init
492                !!       (set at beginning of this ::subroutine) is TRUE. Default is FALSE.
493
494                IF ( always_init(j) .AND. ( biomass(i,j,icarbres,icarbon) .LT. bm_wanted(i) ) ) THEN
495                   !NV passage 2D
496                   co2_to_bm(i,j) = co2_to_bm(i,j) + ( bm_wanted(i) - biomass(i,j,icarbres,icarbon) ) / dt
497
498                   biomass(i,j,icarbres,icarbon) = bm_wanted(i)
499
500                ENDIF
501               
502                !! 4.2.3 The biomass available to use is set to be the minimum of the biomass of the carbohydrate reservoir (if
503                !! carbon not taken from the atmosphere), and the wanted biomass.
504                bm_use(i) = MIN( biomass(i,j,icarbres,icarbon), bm_wanted(i) )
505
506                !
507                !! 4.2.4 divide the biomass which is available to use equally between the leaves and roots.
508                !
509
510                biomass(i,j,ileaf,icarbon) = biomass(i,j,ileaf,icarbon) + bm_use(i) / 2.
511
512                biomass(i,j,iroot,icarbon) = biomass(i,j,iroot,icarbon) + bm_use(i) / 2.
513
514                !
515                !! 4.2.5 decrease carbohydrate reservoir biomass by the amount that's been allocated to the leaves and roots
516                !
517
518                biomass(i,j,icarbres,icarbon) = biomass(i,j,icarbres,icarbon) - bm_use(i)
519
520                !
521                !! 4.2.6 set reset leaf age distribution (::age_reset) flag. Default is TRUE.
522                !     (done later for better vectorization)
523                !
524
525                age_reset(i) = .TRUE.
526
527             ENDIF  ! leaf mass is very low
528
529             !
530             !! 4.3 reset when_growthinit counter: start of the growing season
531             !
532
533             when_growthinit(i,j) = zero
534
535          ENDIF    ! start of the growing season
536
537       ENDDO      ! loop over grid points
538
539       !
540       !! 4.4 reset leaf age distribution where necessary (i.e. when age_reset is TRUE)
541       !!     simply say that everything is in the youngest age class
542       !
543
544       !! 4.4.1 fractions - set the youngest age class fraction to 1 and all other leaf age class fractions to 0.
545
546       WHERE ( age_reset(:) )
547          leaf_frac(:,j,1) = un
548       ENDWHERE
549       DO m = 2, nleafages
550          WHERE ( age_reset(:) )
551             leaf_frac(:,j,m) = zero
552          ENDWHERE
553       ENDDO
554
555       !! 4.4.2 ages - set all leaf ages to 0.
556
557       DO m = 1, nleafages
558          WHERE ( age_reset(:) )
559             leaf_age(:,j,m) = zero
560          ENDWHERE
561       ENDDO
562
563    ENDDO        ! loop over # PFTs
564
565
566    IF (printlev>=3) WRITE(numout,*) 'Leaving phenology'
567
568  END SUBROUTINE phenology
569
570
571!! ================================================================================================================================
572!! SUBROUTINE   : pheno_hum
573!!
574!>\BRIEF          The 'hum' onset model initiate leaf onset based exclusively on moisture
575!!                availability criteria.
576!!                Currently no PFTs are assigned to this onset model.
577!!
578!! DESCRIPTION  : This model is for tropical biomes, where temperatures are high but moisture
579!!                might be a limiting factor on growth. It is based on leaf onset model 4a in
580!!                Botta et al. (2000), which adopts the approach of Le Roux (1995). \n
581!!                Leaf onset occurs if the monthly moisture availability is still quite
582!!                low (i.e. lower than the weekly availability), but the weekly availability is
583!!                higher than the critical threshold ::availability_crit (as it reacts faster),
584!!                which indicates the weekly moisture availability is increasing.
585!!                OR if the monthly moisture availability is high enough (i.e. above the
586!!                threshold value ::moiavail_always), leaf onset is initiated if this has not
587!!                already happened. This allows vegetation in arid areas to respond to rapidly
588!!                changing soil moisture conditions (Krinner et al., 2005). \n
589!!                The critical weekly moisture availability threshold (::availability_crit), is
590!!                calculated in this subroutine, and is a function of last year's maximum and
591!!                minimum moisture availability and the PFT-dependent parameter
592!!                ::hum_frac, which specifies how much of last year's available
593!!                moisture is required for leaf onset, as per the equation:
594!!                \latexonly
595!!                \input{phenology_moi_availcrit_eqn3.tex}
596!!                \endlatexonly
597!!                \n
598!!                ::hum_frac is set for each PFT in ::stomate_data from a table
599!!                which contains all the PFT values (::hum_frac_tab) in ::stomate_constants. \n
600!!                Last year's maximum and minimum moisture availability and the monthly and
601!!                weekly moisture availability are 
602!!                The ::pheno_hum subroutine is called in the subroutine ::phenology.
603!!
604!! RECENT CHANGE(S): None
605!!
606!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start.
607!!
608!! REFERENCE(S) :
609!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
610!! A global prognostic scheme of leaf onset using satellite data,
611!! Global Change Biology, 207, 337-347.
612!! - Le Roux, X. (1995), Etude et modelisation des echanges d'eau et d'energie
613!! sol-vegetation-atmosphere dans une savane humide, PhD Thesis, University
614!! Pierre et Marie Curie, Paris, France.
615!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
616!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
617!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
618!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
619!!
620!! FLOWCHART    :
621!! \latexonly
622!! \includegraphics[scale = 1]{pheno_hum.png}
623!! \endlatexonly
624!! \n             
625!_ ================================================================================================================================
626
627  SUBROUTINE pheno_hum (npts, j, PFTpresent, allow_initpheno, &
628       moiavail_month, moiavail_week, &
629       maxmoiavail_lastyear, minmoiavail_lastyear, &
630       begin_leaves)
631
632    !
633    !! 0. Variable and parameter declarations
634    !
635
636    !
637    !! 0.1 Input variables
638    !
639    INTEGER(i_std), INTENT(in)                                             :: npts                  !! Domain size - number of
640                                                                                                    !! grid cells (unitless)
641    INTEGER(i_std), INTENT(in)                                             :: j                     !! PFT index (unitless)
642    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                               :: PFTpresent            !! PFT exists (true/false)
643    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                               :: allow_initpheno       !! are we allowed to
644                                                                                                    !! declare the beginning of
645                                                                                                    !! the growing season?
646                                                                                                    !! (true/false)
647    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: moiavail_month        !! "monthly" moisture
648                                                                                                    !! availability (0-1, unitless)
649    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: moiavail_week         !! "weekly" moisture
650                                                                                                    !! availability (0-1, unitless)
651    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: maxmoiavail_lastyear  !! last year's maximum
652                                                                                                    !! moisture availability
653                                                                                                    !! (0-1, unitless)
654    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                           :: minmoiavail_lastyear  !! last year's minimum
655                                                                                                    !! moisture availability
656                                                                                                    !! (0-1, unitless)
657
658    !
659    !! 0.2 Output variables
660    !
661
662    !
663    !! 0.3 Modified variables
664    !
665    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)                            :: begin_leaves          !! signal to start putting
666                                                                                                    !! leaves on (true/false)
667
668    !
669    !! 0.4 Local variables
670    !
671    REAL(r_std)                                                            :: moiavail_always       !! critical monthly
672                                                                                                    !! moisture availability - set
673                                                                                                    !! for tree or grass
674                                                                                                    !! (0-1, unitless)
675    REAL(r_std), DIMENSION(npts)                                           :: availability_crit     !! critical weekly moisture
676                                                                                                    !! availability (0-1, unitless)
677    INTEGER(i_std)                                                         :: i                     !! index (unitless)
678
679!_ ================================================================================================================================
680
681    IF (printlev>=3) WRITE(numout,*) 'Entering hum'
682
683    !
684    !! 1. Initializations
685    !
686
687    !
688    !! 1.1 first call - outputs the name of onset model and the moisture availability
689    !!     parameters for tree and grass
690    !
691
692    IF ( firstcall_hum ) THEN
693
694       IF (printlev >= 2) THEN
695          WRITE(numout,*) 'pheno_hum:'
696          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
697          WRITE(numout,*) '         trees (::moiavail_always_tree): ', moiavail_always_tree
698          WRITE(numout,*) '         grasses (::moiavail_always_grass):', moiavail_always_grass
699       END IF
700       firstcall_hum = .FALSE.
701
702    ENDIF
703
704    !
705    !! 1.2 initialize output
706    !
707
708    begin_leaves(:,j) = .FALSE.
709
710    !
711    !! 1.3 check the critical value ::hum_frac is defined. If not, stop.
712    !
713
714    IF ( hum_frac(j) .EQ. undef ) THEN
715
716       WRITE(numout,*) 'hum: hum_frac is undefined for PFT (::j)',j
717       CALL ipslerr_p(3,'stomate phenology','hum_frac is undefined for this PFT','','')
718
719    ENDIF
720
721    !
722    !! 1.4 set the critical monthly moisture availability above which we always detect the beginning of the
723    !!     growing season - set as the moisture availability for trees or grass.
724    !
725
726    IF ( is_tree(j) ) THEN
727       moiavail_always = moiavail_always_tree
728    ELSE
729       moiavail_always = moiavail_always_grass
730    ENDIF
731
732    !
733    !! 2. Check if biometeorological conditions are favourable for leaf growth.
734    !! The PFT has to be there and start of growing season must be allowed
735    !
736
737    DO i = 1, npts
738
739       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
740
741          !! 2.1 Calculate the critical weekly moisture availability: depends linearly on the last year
742          !! minimum and maximum moisture availabilities, and on the parameter ::hum_frac.
743
744          availability_crit(i) = minmoiavail_lastyear(i,j) + hum_frac(j) * &
745               ( maxmoiavail_lastyear(i,j) - minmoiavail_lastyear(i,j) )
746
747          !! 2.2 Determine if growing season should start (if so, ::begin_leaves set to TRUE).
748          !!     Leaf onset occurs if the monthly moisture availability is still quite
749          !!     low (i.e. lower than the weekly availability), but the weekly availability is
750          !!     already higher than the critical threshold ::availability_crit (as it reacts faster),
751          !!     which indicates the weekly moisture availability is increasing.
752          !!     OR if the monthly moisture availability is high enough (i.e. above the threshold value
753          !!     ::moiavail_always), leaf onset is initiated if this has not already happened.
754
755          IF ( ( ( moiavail_week(i,j)  .GE. availability_crit(i) ) .AND. &
756               ( moiavail_month(i,j) .LT. moiavail_week(i,j) )   ) .OR. &
757               ( moiavail_month(i,j) .GE. moiavail_always )                ) THEN
758             begin_leaves(i,j) = .TRUE.
759          ENDIF
760
761       ENDIF        ! PFT there and start of growing season allowed
762
763    ENDDO ! end loop over grid points
764
765    IF (printlev>=4) WRITE(numout,*) 'Leaving hum'
766
767  END SUBROUTINE pheno_hum
768
769
770!! ================================================================================================================================
771!! SUBROUTINE   : pheno_moi
772!!
773!>\BRIEF          The 'moi' onset model (::pheno_moi) initiates leaf onset based exclusively
774!!                on moisture availability criteria.
775!!                It is very similar to the 'hum' onset model but instead of the weekly moisture
776!!                availability being higher than a constant threshold, the condition is that the
777!!                moisture minimum happened a sufficiently long time ago.
778!!                Currently PFT 3 (Tropical Broad-leaved Raingreen) is assigned to this model.
779!!
780!! DESCRIPTION  : This model is for tropical biomes, where temperatures are high but moisture
781!!                might be a limiting factor on growth. It is based on leaf onset model 4b in
782!!                Botta et al. (2000).
783!!                Leaf onset begins if the plant moisture availability minimum was a sufficiently 
784!!                time ago, as specified by the PFT-dependent parameter ::hum_min_time
785!!                AND if the "monthly" moisture availability is lower than the "weekly"
786!!                availability (indicating that soil moisture is increasing).
787!!                OR if the monthly moisture availability is high enough (i.e. above the threshold
788!!                value ::moiavail_always), leaf onset is initiated if this has not already
789!!                happened. \n
790!!                ::hum_min_time is set for each PFT in ::stomate_data, and is
791!!                defined in the table ::hum_min_time_tab in ::stomate_constants. \n
792!!                ::moiavail_always is defined for both tree and grass in this subroutine
793!!                (set to 1. and 0.6 respectively). \n
794!!                The ::pheno_moi subroutine is called in the subroutine ::phenology.
795!!
796!! RECENT CHANGE(S): None
797!!       
798!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start.
799!!
800!! REFERENCE(S) :
801!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
802!! A global prognostic scheme of leaf onset using satellite data,
803!! Global Change Biology, 207, 337-347.
804!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
805!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
806!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
807!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
808!!
809!! FLOWCHART    :
810!! \latexonly
811!! \includegraphics[scale = 1]{pheno_moi.png}
812!! \endlatexonly
813!! \n
814!_ ================================================================================================================================
815
816  SUBROUTINE pheno_moi (npts, j, PFTpresent, allow_initpheno, &
817       time_hum_min, &
818       moiavail_month, moiavail_week, &
819       begin_leaves)
820
821    !
822    !! 0. Variable and parameter declaration
823    !
824
825    !
826    !! 0.1 Input variables
827    !
828    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
829    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
830    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
831    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
832                                                                                !! growing season? (true/false)
833    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
834                                                                                !! availability (days)
835    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
836    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
837
838    !
839    !! 0.2 Output variables
840    !
841    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
842
843    !
844    !! 0.3 Modified variables
845    !
846
847    !
848    !! 0.4 Local variables
849    !
850    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
851                                                                                                !! set for tree or grass
852                                                                                                !! (0-1, unitless)
853    INTEGER(i_std)                                           :: i                               !! index (unitless)
854
855!_ ================================================================================================================================
856
857    IF (printlev>=3) WRITE(numout,*) 'Entering moi'
858
859    !
860    !! 1. Initializations
861    !
862
863    !
864    !! 1.1 first call - outputs the name of onset model and the moisture availability
865    !!     parameters for tree and grass
866    !
867
868    IF ( firstcall_moi ) THEN
869       IF (printlev >= 2) THEN
870          WRITE(numout,*) 'pheno_moi:'
871          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
872          WRITE(numout,*) '         trees (::moiavail_always_tree):', moiavail_always_tree
873          WRITE(numout,*) '         grasses (::moiavail_always_grass):', moiavail_always_grass
874       END IF
875       firstcall_moi = .FALSE.
876
877    ENDIF
878
879    !
880    !! 1.2 initialize output
881    !
882
883    begin_leaves(:,j) = .FALSE.
884
885    !
886    !! 1.3 check the critical value ::hum_min_time is definded. If not, stop
887    !
888
889    IF ( hum_min_time(j) .EQ. undef ) THEN
890
891       WRITE(numout,*) 'moi: hum_min_time is undefined for PFT (::j) ',j
892       CALL ipslerr_p(3,'stomate phenology','hum_min_time is undefined for this PFT','','')
893
894    ENDIF
895
896    !
897    !! 1.4 set the critical monthly moisture availability above which we always detect the beginning of the
898    !!     growing season - set as the moisture availability for trees or grass.
899    !
900
901    IF ( is_tree(j) ) THEN
902       moiavail_always = moiavail_always_tree
903    ELSE
904       moiavail_always = moiavail_always_grass
905    ENDIF
906
907    !
908    !! 2. Check if biometeorological conditions are favourable for leaf growth.
909    !! The PFT has to be there and start of growing season must be allowed.
910    !
911
912    DO i = 1, npts
913
914       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
915         
916          !! 2.1 Determine if growing season should start (if so, ::begin_leaves set to TRUE).
917          !!     The favorable season starts if the moisture minimum (::time_hum_min) was a sufficiently long
918          !!     time ago, i.e. greater than the threshold specified by the parameter ::hum_min_time
919          !!     and if the "monthly" moisture availability is lower than the "weekly"
920          !!     availability (indicating that soil moisture is increasing).
921          !!     OR if the monthly moisture availability is high enough (i.e. above the threshold value
922          !!     ::moiavail_always), initiate the growing season if this has not happened yet.
923
924          IF  ( ( ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) .AND. &
925               ( time_hum_min(i,j) .GT. hum_min_time(j) )    ) .OR. &
926               ( moiavail_month(i,j) .GE. moiavail_always )                     ) THEN
927             begin_leaves(i,j) = .TRUE.
928          ENDIF
929
930       ENDIF        ! PFT there and start of growing season allowed
931
932    ENDDO ! end loop over grid points
933
934    IF (printlev>=4) WRITE(numout,*) 'Leaving moi'
935
936  END SUBROUTINE pheno_moi
937
938
939!! ================================================================================================================================
940!! SUBROUTINE   : pheno_humgdd
941!!
942!>\BRIEF          The 'humgdd' onset model initiates leaf onset based on mixed conditions of
943!!                temperature and moisture availability criteria.
944!!                Currently no PFTs are assigned to this onset model.
945!!
946!! DESCRIPTION  : In this model the Growing Degree Day (GDD) model (Chuine, 2000) is combined
947!!                with the 'hum' onset model (::pheno_hum), which has previously been described,
948!!                in order to account for dependence on both temperature and moisture conditions
949!!                in warmer climates. \n.
950!!                The GDD model specifies that daily temperatures above a threshold of -5 
951!!                degrees C are summed, minus this threshold, giving the GDD, starting from
952!!                the beginning of the dormancy period (::time_lowgpp>0), i.e. since the leaves
953!!                were lost. \n.
954!!                The dormancy time-length is represented by the variable
955!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
956!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
957!!                it is set to zero. \n
958!!                Leaf onset begins when the a PFT-dependent GDD-threshold is reached.
959!!                In addition there are temperature and moisture conditions.
960!!                The temperature condition specifies that the monthly temperature has to be
961!!                higher than a constant threshold (::t_always) OR
962!!                the weekly temperature is higher than the monthly temperature.
963!!                There has to be at least some moisture. The moisture condition
964!!                is exactly the same as the 'hum' onset model (::pheno_hum), which has already
965!!                been described. \n
966!!                The GDD (::gdd_m5_dormance) is calculated in ::stomate_season. GDD is set to
967!!                undef if beginning of the growing season detected, i.e. when there is GPP
968!!                (::time_lowgpp>0).
969!!                The parameter ::t_always is defined as 10 degrees C in this subroutine,
970!!                as are the parameters ::moisture_avail_tree and ::moisture_avail_grass
971!!                (set to 1 and 0.6 respectively), which are used in the moisture condition
972!!                (see ::pheno_moi onset model description). \n
973!!                The PFT-dependent GDD threshold (::gdd_crit) is calculated as in the onset
974!!                model ::pheno_humgdd, using the equation:
975!!                \latexonly
976!!                \input{phenology_hummoigdd_gddcrit_eqn4.tex}
977!!                \endlatexonly
978!!                \n
979!!                The three GDDcrit parameters (::gdd(j,*)) are set for each PFT in
980!!                ::stomate_data, and three tables defining each of the three critical GDD
981!!                parameters for each PFT is given in ::gdd_crit1_tab, ::gdd_crit2_tab and
982!!                ::gdd_crit3_tab in ::stomate_constants. \n
983!!                The ::pheno_humgdd subroutine is called in the subroutine ::phenology.
984!!
985!! RECENT CHANGES: None
986!!               
987!! MAIN OUTPUT VARIABLES: ::begin_leaves - specifies whether leaf growth can start
988!!
989!! REFERENCE(S) :
990!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
991!! A global prognostic scheme of leaf onset using satellite data,
992!! Global Change Biology, 207, 337-347.
993!! - Chuine, I (2000), A unified model for the budburst of trees, Journal of
994!! Theoretical Biology, 207, 337-347.
995!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
996!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
997!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
998!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
999!!
1000!! FLOWCHART    :
1001!! \latexonly
1002!! \includegraphics[scale = 1]{pheno_humgdd.png}
1003!! \endlatexonly
1004!! \n             
1005!_ ================================================================================================================================
1006
1007  SUBROUTINE pheno_humgdd (npts, j, PFTpresent, allow_initpheno, gdd, &
1008       maxmoiavail_lastyear, minmoiavail_lastyear, &
1009       t2m_longterm, t2m_month, t2m_week, &
1010       moiavail_week, moiavail_month, &
1011       begin_leaves)
1012
1013    !
1014    !! 0. Variable and parameter declaration
1015    !
1016
1017    !
1018    !! 0.1 Input variables
1019    !
1020    INTEGER(i_std), INTENT(in)                               :: npts                    !! Domain size - number of grid cells
1021                                                                                        !! (unitless)
1022    INTEGER(i_std), INTENT(in)                               :: j                       !! PFT index (unitless)
1023    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent              !! PFT exists (true/false)
1024    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno         !! are we allowed to declare the beginning
1025                                                                                        !! of the growing season? (true/false)
1026    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd                     !! growing degree days, calculated since
1027                                                                                        !! leaves have fallen (C)
1028    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: maxmoiavail_lastyear    !! last year's maximum moisture
1029                                                                                        !! availability (0-1, unitless)
1030    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: minmoiavail_lastyear    !! last year's minimum moisture
1031                                                                                        !! availability (0-1, unitless)
1032    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm            !! "long term" 2 meter temperatures (K)
1033    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month               !! "monthly" 2-meter temperatures (K)
1034    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week                !! "weekly" 2-meter temperatures (K)
1035    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week           !! "weekly" moisture availability
1036                                                                                        !! (0-1, unitless)
1037    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month          !! "monthly" moisture availability
1038                                                                                        !! (0-1, unitless)
1039
1040    !
1041    !! 0.2 Output variables
1042    !
1043    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves            !! signal to start putting leaves on
1044                                                                                        !! (true/false)
1045
1046    !
1047    !! 0.3 Modified variables
1048    !
1049
1050    !
1051    !! 0.4 Local variables
1052    !
1053    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1054                                                                                                !! set for tree or grass
1055                                                                                                !! (0-1, unitless)
1056    REAL(r_std), DIMENSION(npts)                             :: moiavail_crit                   !! critical moisture availability
1057                                                                                                !! (0-1, unitless)
1058    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1059    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1060    INTEGER(i_std)                                           :: i                               !! index (unitless)
1061
1062!_ ================================================================================================================================
1063
1064    IF (printlev>=3) WRITE(numout,*) 'Entering humgdd'
1065
1066    !
1067    !! 1. Initializations
1068    !
1069
1070    !
1071    !! 1.1 first call - outputs the name of the onset model, the values of the 
1072    !!     moisture availability parameters for tree and grass, and the value of the
1073    !!     critical monthly temperature.
1074    !
1075
1076    IF ( firstcall_humgdd ) THEN
1077
1078       IF (printlev >= 2) THEN
1079          WRITE(numout,*) 'pheno_humgdd:'
1080          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1081          WRITE(numout,*) '         trees (::moiavail_always_tree): ', moiavail_always_tree
1082          WRITE(numout,*) '         grasses (::moiavail_always_grass): ', moiavail_always_grass
1083          WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter: ', &
1084               t_always
1085       END IF
1086
1087       firstcall_humgdd = .FALSE.
1088
1089    ENDIF
1090
1091    !
1092    !! 1.2 initialize output
1093    !
1094
1095    begin_leaves(:,j) = .FALSE.
1096
1097    !
1098    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_frac are defined.
1099    !!     If not, stop.
1100    !
1101
1102    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1103
1104       WRITE(numout,*) 'humgdd: pheno_gdd_crit is undefined for PFT (::j) ',j
1105       CALL ipslerr_p(3,'stomate phenology','pheno_gdd_crit is undefined for this PFT','','')
1106
1107    ENDIF
1108
1109    IF ( hum_frac(j) .EQ. undef ) THEN
1110
1111       WRITE(numout,*) 'humgdd: hum_frac is undefined for PFT (::j) ',j
1112       CALL ipslerr_p(3,'stomate phenology','hum_frac is undefined for this PFT','','')
1113
1114    ENDIF
1115
1116    !
1117    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
1118    !!     growing season - set as the moisture availability for trees or grass.
1119    !
1120
1121    IF ( is_tree(j) ) THEN
1122       moiavail_always = moiavail_always_tree
1123    ELSE
1124       moiavail_always = moiavail_always_grass
1125    ENDIF
1126
1127    !
1128    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1129    !!   The PFT has to be there, start of growing season must be allowed,
1130    !!   and GDD has to be defined.
1131    !
1132
1133    DO i = 1, npts
1134
1135       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1136            ( gdd(i,j) .NE. undef )                           ) THEN
1137
1138          !! 2.1 Calculate the critical weekly moisture availability: depends linearly on the last year
1139          !! minimum and maximum moisture availabilities, and on the parameter ::hum_frac.,
1140          !! (as in the ::pheno_hum model), as per the equation:
1141
1142          moiavail_crit(i) = minmoiavail_lastyear(i,j) + hum_frac(j) * &
1143               ( maxmoiavail_lastyear(i,j) - minmoiavail_lastyear(i,j) )
1144
1145          !! 2.2 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
1146          !!     critical GDD and the "long term" 2 meter air temperatures. 
1147
1148          tl(i) =  t2m_longterm(i) - ZeroCelsius
1149          gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1150               tl(i)*tl(i)*pheno_gdd_crit(j,3)
1151         
1152          !! 2.3 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1153          !!     - Has the critical gdd been reached and is the temperature increasing?
1154          !!     - Is there at least some humidity/moisture availability?
1155          !!     This occurs if the critical gdd (::gdd_crit) has been reached
1156          !!     AND that is temperature increasing, which is true either if the monthly
1157          !!     temperature being higher than the threshold ::t_always, OR if the weekly
1158          !!     temperature is higher than the monthly,
1159          !!     AND finally that there is sufficient moisture availability, which is
1160          !!     the same condition as for the ::pheno_hum onset model.
1161
1162          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1163               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1164               ( t2m_month(i) .GT. t_always )          ) .AND. &
1165               ( ( ( moiavail_week(i,j)  .GE. moiavail_crit(i) ) .AND. &
1166               ( moiavail_month(i,j) .LT. moiavail_crit(i) )        ) .OR. &
1167               ( moiavail_month(i,j) .GE. moiavail_always )                   ) )  THEN
1168             begin_leaves(i,j) = .TRUE.
1169          ENDIF
1170
1171       ENDIF        ! PFT there and start of growing season allowed
1172
1173    ENDDO ! End loop over grid points
1174
1175    IF (printlev>=4) WRITE(numout,*) 'Leaving humgdd'
1176
1177  END SUBROUTINE pheno_humgdd
1178
1179
1180!! ================================================================================================================================
1181!! SUBROUTINE   : pheno_moigdd
1182!!
1183!>\BRIEF          The 'moigdd' onset model initiates leaf onset based on mixed temperature
1184!!                and moisture availability criteria.
1185!!                Currently PFTs 10 - 13 (C3 and C4 grass, and C3 and C4 agriculture)
1186!!                are assigned to this model.
1187!!
1188!! DESCRIPTION  : This onset model combines the GDD model (Chuine, 2000), as described for
1189!!                the 'humgdd' onset model (::pheno_humgdd), and the 'moi' model, in order
1190!!                to account for dependence on both temperature and moisture conditions in
1191!!                warmer climates. \n
1192!!                Leaf onset begins when the a PFT-dependent GDD threshold is reached.
1193!!                In addition there are temperature and moisture conditions.
1194!!                The temperature condition specifies that the monthly temperature has to be
1195!!                higher than a constant threshold (::t_always) OR
1196!!                the weekly temperature is higher than the monthly temperature.
1197!!                There has to be at least some moisture. The moisture condition
1198!!                is exactly the same as the 'moi' onset model (::pheno_moi), which has
1199!!                already been described. \n
1200!!                GDD is set to undef if beginning of the growing season detected.
1201!!                As in the ::pheno_humgdd model, the parameter ::t_always is defined as
1202!!                10 degrees C in this subroutine, as are the parameters ::moisture_avail_tree
1203!!                and ::moisture_avail_grass (set to 1 and 0.6 respectively), which are used
1204!!                in the moisture condition (see ::pheno_moi onset model description). \n
1205!!                The PFT-dependent GDD threshold (::gdd_crit) is calculated as in the onset
1206!!                model ::pheno_humgdd, using the equation:
1207!!                \latexonly
1208!!                \input{phenology_hummoigdd_gddcrit_eqn4.tex}
1209!!                \endlatexonly
1210!!                \n
1211!!                where i and j are the grid cell and PFT respectively.
1212!!                The three GDDcrit parameters (::gdd(j,*)) are set for each PFT in
1213!!                ::stomate_data, and three tables defining each of the three critical GDD
1214!!                parameters for each PFT is given in ::gdd_crit1_tab, ::gdd_crit2_tab and
1215!!                ::gdd_crit3_tab in ::stomate_constants. \n
1216!!                The ::pheno_moigdd subroutine is called in the subroutine ::phenology.
1217!!
1218!! RECENT CHANGE(S): Added temperature threshold for C4 grass (pheno_moigdd_t_crit), Dan Zhu april 2015
1219!!               
1220!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1221!!
1222!! REFERENCE(S) :
1223!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1224!! A global prognostic scheme of leaf onset using satellite data,
1225!! Global Change Biology, 207, 337-347.
1226!! - Chuine, I (2000), A unified model for the budburst of trees, Journal of
1227!! Theoretical Biology, 207, 337-347.
1228!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1229!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1230!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1231!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1232!! - Still et al., Global distribution of C3 and C4 vegetation: Carbon cycle implications,
1233!! 2003, Global Biogeochemmical Cycles, DOI: 10.1029/2001GB001807.
1234!!
1235!! FLOWCHART    :
1236!! \latexonly
1237!! \includegraphics[scale = 1]{pheno_moigdd.png}
1238!! \endlatexonly
1239!! \n
1240!_ ================================================================================================================================
1241
1242  SUBROUTINE pheno_moigdd (npts, j, PFTpresent, allow_initpheno, gdd, &
1243       time_hum_min, &
1244       t2m_longterm, t2m_month, t2m_week, &
1245       moiavail_week, moiavail_month, &
1246       begin_leaves)
1247
1248    !
1249    !! 0. Variable and parameter declaration
1250    !
1251
1252    !
1253    !! 0.1 Input variables
1254    !
1255    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1256    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1257    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1258    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to decalre the beginning of the
1259                                                                                !! growing season? (true/false)
1260    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gdd             !! growing degree days, calculated since leaves
1261                                                                                !! have fallen (C)
1262    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: time_hum_min    !! time elapsed since strongest moisture
1263                                                                                !! availability (days)
1264    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_longterm    !! "long term" 2 meter temperatures (K)
1265    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1266    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1267    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week   !! "weekly" moisture availability (0-1, unitless)
1268    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_month  !! "monthly" moisture availability (0-1, unitless)
1269
1270    !
1271    !! 0.2 Output variables
1272    !
1273
1274    !
1275    !! 0.3 Modified variables
1276    !
1277    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1278
1279    !
1280    !! 0.4 Local variables
1281    !
1282    REAL(r_std)                                              :: moiavail_always                 !! critical moisture availability -
1283                                                                                                !! set for tree or grass
1284                                                                                                !! (0-1, unitless)
1285    REAL(r_std), DIMENSION(npts)                             :: tl                              !! long term temperature (C)
1286    REAL(r_std), DIMENSION(npts)                             :: gdd_crit                        !! critical GDD (C)
1287    INTEGER(i_std)                                           :: i                               !! index (unitless)
1288
1289!_ ================================================================================================================================
1290
1291    IF (printlev>=3) WRITE(numout,*) 'Entering moigdd'
1292
1293    !
1294    !! 1. Initializations
1295    !
1296
1297    !
1298    !! 1.1 first call - outputs the name of the onset model, the values of the 
1299    !!     moisture availability parameters for tree and grass, and the value of the
1300    !!     critical monthly temperature.
1301    !
1302
1303    IF ( firstcall_moigdd ) THEN
1304
1305       IF (printlev >= 2) THEN
1306          WRITE(numout,*) 'pheno_moigdd:'
1307          WRITE(numout,*) '   > moisture availability above which moisture tendency doesn''t matter: '
1308          WRITE(numout,*) '         trees (::moiavail_always_tree) :', moiavail_always_tree
1309          WRITE(numout,*) '         grasses (::moiavail_always_grass) :', moiavail_always_grass
1310          WRITE(numout,*) '   > monthly temp. above which temp. tendency doesn''t matter (::t_always): ', &
1311               t_always
1312       END IF
1313       firstcall_moigdd = .FALSE.
1314
1315    ENDIF
1316
1317    !
1318    !! 1.2 initialize output
1319    !
1320
1321    begin_leaves(:,j) = .FALSE.
1322
1323    !
1324    !! 1.3 check the critical values ::gdd and ::pheno_crit_hum_min_time are defined.
1325    !!     If not, stop.
1326    !
1327
1328    IF ( ANY(pheno_gdd_crit(j,:) .EQ. undef) ) THEN
1329
1330       WRITE(numout,*) 'moigdd: pheno_gdd_crit is undefined for PFT',j
1331       CALL ipslerr_p(3,'stomate phenology','pheno_gdd is undefined for this PFT','','')
1332
1333    ENDIF
1334
1335    IF ( hum_min_time(j) .EQ. undef ) THEN
1336
1337       WRITE(numout,*) 'moigdd: hum_min_time is undefined for PFT',j
1338       CALL ipslerr_p(3,'stomate phenology','hum_min is undefined for this PFT','','')
1339
1340    ENDIF
1341
1342    !
1343    !! 1.4 set the critical moisture availability above which we always detect the beginning of the
1344    !!     growing season - set as the moisture availability for trees or grass.
1345    !
1346
1347    IF ( is_tree(j) ) THEN
1348       moiavail_always = moiavail_always_tree
1349    ELSE
1350       moiavail_always = moiavail_always_grass
1351    ENDIF
1352
1353    !
1354    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1355    !!    The PFT has to be there, the start of growing season must be allowed,
1356    !!    and GDD has to be defined.
1357    !
1358
1359    DO i = 1, npts
1360
1361       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1362            ( gdd(i,j) .NE. undef )                           ) THEN
1363         
1364          !! 2.1 Calculate the critical GDD (::gdd_crit), which is a function of the PFT-dependent
1365          !!     critical GDD and the "long term" 2 meter air temperatures
1366         
1367          tl(i) = t2m_longterm(i) - ZeroCelsius
1368          gdd_crit(i) = pheno_gdd_crit(j,1) + tl(i)*pheno_gdd_crit(j,2) + &
1369               tl(i)*tl(i)*pheno_gdd_crit(j,3)
1370
1371          !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1372          !!     This occurs if the critical gdd (::gdd_crit) has been reached
1373          !!     AND that is temperature increasing, which is true either if the monthly
1374          !!     temperature being higher than the threshold ::t_always, OR if the weekly
1375          !!     temperature is higher than the monthly,
1376          !!     AND finally that there is sufficient moisture availability, which is
1377          !!     the same condition as for the ::pheno_moi onset model.
1378          !!     AND when pheno_moigdd_t_crit is set(for C4 grass), if the average temperature threshold is reached
1379
1380          IF ( ( gdd(i,j) .GE. gdd_crit(i) ) .AND. &
1381               ( ( t2m_week(i) .GT. t2m_month(i) ) .OR. &
1382                 ( t2m_month(i) .GT. t_always )  ) .AND. &
1383               ( ( ( time_hum_min(i,j) .GT. hum_min_time(j) ) .AND. &
1384                 ( moiavail_week(i,j) .GT. moiavail_month(i,j) ) ) .OR. &
1385                 ( moiavail_month(i,j) .GE. moiavail_always )  ) .AND. &
1386               ( ( pheno_moigdd_t_crit(j) == undef ) .OR. &
1387                 (t2m_month(i) .GT. (ZeroCelsius + pheno_moigdd_t_crit(j))) ) ) THEN
1388
1389             begin_leaves(i,j) = .TRUE.
1390             
1391          ENDIF
1392
1393       ENDIF        ! PFT there and start of growing season allowed
1394
1395    ENDDO
1396
1397    IF (printlev>=4) WRITE(numout,*) 'Leaving moigdd'
1398
1399  END SUBROUTINE pheno_moigdd
1400
1401
1402!! ================================================================================================================================
1403!! SUBROUTINE   : pheno_ncdgdd
1404!!
1405!>\BRIEF          The Number of Chilling Days - Growing Degree Day (NCD-GDD) model initiates
1406!!                leaf onset if a certain relationship between the number of chilling days (NCD)
1407!!                since leaves were lost, and the growing degree days (GDD) since midwinter, is
1408!!                fulfilled.
1409!!                Currently PFT 6 (Temperate Broad-leaved Summergreen) and PFT 8 (Boreal Broad-
1410!!                leaved Summergreen) are assigned to this model.
1411!!
1412!! DESCRIPTION  : Experiments have shown that some
1413!!                species have a "chilling" requirement, i.e. their physiology needs cold
1414!!                temperatures to trigger the mechanism that will allow the following budburst
1415!!                (e.g. Orlandi et al., 2004).
1416!!                An increase in chilling days, defined as a day with a daily mean air
1417!!                temperature below a PFT-dependent threshold, reduces a plant's GDD demand
1418!!                (Cannell and Smith, 1986; Murray et al., (1989); Botta et al., 2000).
1419!!                The GDD threshold therefore decreases as NCD
1420!!                increases, using the following empirical negative explonential law:
1421!!                \latexonly
1422!!                \input{phenology_ncdgdd_gddmin_eqn5.tex}
1423!!                \endlatexonly
1424!!                \n
1425!!                The constants used have been calibrated against data CHECK FOR REFERENCE OR PERSON WHO DID UPDATE.
1426!!                Leaf onset begins if the GDD is higher than the calculated minimum GDD
1427!!                (dependent upon NCD) AND if the weekly temperature is higher than the monthly
1428!!                temperature. This is to ensure the temperature is increasing. \n
1429!!                The dormancy time-length is represented by the variable
1430!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
1431!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
1432!!                it is set to zero. \n
1433!!                The NCD (::ncd_dormance) is calculated in ::stomate_season as 
1434!!                the number of days with a temperature below a PFT-dependent constant threshold
1435!!                (::ncdgdd_temp), starting from the beginning of the dormancy period
1436!!                (::time_lowgpp>0), i.e. since the leaves were lost. \n
1437!!                The growing degree day sum of the temperatures higher than
1438!!                ::ncdgdd_temp (GDD) since midwinter (::gdd_midwinter)
1439!!                is also calculated in ::stomate_season.
1440!!                Midwinter is detected if the monthly temperature is lower than the weekly
1441!!                temperature AND  the monthly temperature is lower than the long-term
1442!!                temperature. ::gdd_minter is therefore set to 0 at the beginning of midwinter
1443!!                and increased with each temperature greater than the PFT-dependent threshold.
1444!!                When midsummer is detected (the opposite of the above conditions),
1445!!                ::gdd_midwinter is set to undef.
1446!!                CHECK! WHEN TO START OF DORMANCY BEEN MODIFIED FROM BOTTA- ADD IN?
1447!!                The ::pheno_ncdgdd subroutine is called in the subroutine ::phenology.
1448!!
1449!! RECENT CHANGE(S): None
1450!!               
1451!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1452!!
1453!! REFERENCE(S) :
1454!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1455!! A global prognostic scheme of leaf onset using satellite data,
1456!! Global Change Biology, 207, 337-347.
1457!! - Cannell, M.J.R. and R.I. Smith (1986), Climatic warming, spring budburst and
1458!! frost damage on trees, Journal of Applied Ecology, 23, 177-191.
1459!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1460!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1461!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1462!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1463!! - Murray, M.B., G.R. Cannell and R.I. Smith (1989), Date of budburst of fifteen
1464!! tree species in Britain following climatic warming, Journal of Applied Ecology,
1465!! 26, 693-700.
1466!! - Orlandi, F., H. Garcia-Mozo, L.V. Ezquerra, B. Romano, E. Dominquez, C. Galan,
1467!! and M. Fornaciari (2004), Phenological olive chilling requirements in Umbria
1468!! (Italy) and Andalusia (Spain), Plant Biosystems, 138, 111-116.
1469!!
1470!! FLOWCHART    :
1471!! \latexonly
1472!! \includegraphics[scale = 1]{pheno_ncdgdd.png}
1473!! \endlatexonly
1474!! \n
1475!_ ================================================================================================================================
1476
1477  SUBROUTINE pheno_ncdgdd (npts, j, PFTpresent, allow_initpheno, &
1478       ncd_dormance, gdd_midwinter, &
1479       t2m_month, t2m_week, begin_leaves)
1480
1481    !
1482    !! 0. Variable and parameter declaration
1483    !
1484
1485    !
1486    !! 0.1 Input variables
1487    !
1488    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1489    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1490    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1491    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
1492                                                                                !! growing season? (true/false)
1493    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: ncd_dormance    !! number of chilling days since leaves were lost
1494                                                                                !! (days)
1495    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: gdd_midwinter   !! growing degree days since midwinter (C)
1496    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1497    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1498
1499    !
1500    !! 0.2 Output variables
1501    !
1502
1503    !
1504    !! 0.3 Modified variables
1505    !
1506    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1507
1508    !
1509    !! 0.4 Local variables
1510    !
1511    INTEGER(i_std)                                           :: i               !! index (unitless)
1512    REAL(r_std)                                              :: gdd_min         !! critical gdd (C)
1513
1514!_ ================================================================================================================================
1515
1516    IF (printlev>=3) WRITE(numout,*) 'Entering ncdgdd'
1517
1518    !
1519    !! 1. Initializations
1520    !
1521
1522    !
1523    !! 1.1 initialize output
1524    !
1525
1526    begin_leaves(:,j) = .FALSE.
1527
1528    !
1529    !! 1.2 check the critical value ::ncdgdd_temp is defined.
1530    !!     If not, stop.
1531    !
1532
1533    IF ( ncdgdd_temp(j) .EQ. undef ) THEN
1534
1535       WRITE(numout,*) 'ncdgdd: ncdgdd_temp is undefined for PFT (::j) ',j
1536       CALL ipslerr_p(3,'stomate phenology','ncdgdd_temp this PFT','','')
1537
1538    ENDIF
1539
1540    !
1541    !! 2. Check if biometeorological conditions are favourable for leaf growth.   
1542    !!    PFT has to be there and start of growing season must be allowed.
1543    !
1544
1545    DO i = 1, npts ! loop over grid points
1546
1547       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) .AND. &
1548            ( gdd_midwinter(i,j) .NE. undef ) .AND. &
1549            ( ncd_dormance(i,j) .NE. undef )                  ) THEN
1550
1551          !! 2.1 Calculate the critical gdd, which is related to ::ncd_dormance
1552          !!     using an empirical negative exponential law as described above.           
1553
1554          gdd_min = ( gddncd_ref / exp(gddncd_curve*ncd_dormance(i,j)) - gddncd_offset )
1555
1556          !! 2.2 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1557          !!     This occurs if the critical GDD been reached AND the temperatures are increasing.
1558          !!     If the growing season has started, ::gdd_midwinter is set to "undef".
1559
1560          IF ( ( gdd_midwinter(i,j) .GE. gdd_min ) .AND. &
1561               ( t2m_week(i) .GT. t2m_month(i) ) ) THEN
1562             begin_leaves(i,j) = .TRUE.
1563             gdd_midwinter(i,j)=undef
1564          ENDIF
1565
1566       ENDIF        ! PFT there and start of growing season allowed
1567
1568    ENDDO ! end loop over grid points
1569
1570    IF (printlev>=4) WRITE(numout,*) 'Leaving ncdgdd'
1571
1572  END SUBROUTINE pheno_ncdgdd
1573
1574
1575!! ================================================================================================================================
1576!! SUBROUTINE   : pheno_ngd
1577!!
1578!>\BRIEF          The Number of Growing Days (NGD) leaf onset model initiates leaf onset if the NGD,
1579!!                defined as the number of days with temperature above a constant threshold,
1580!!                exceeds a critical value.
1581!!                Currently PFT 9 (Boreal Leedleleaf Summergreen) is assigned to this model.
1582!!
1583!! DESCRIPTION    The NGD model is a variant of the GDD model. The model was proposed by Botta et
1584!!                al. (2000) for boreal and arctic biomes, and is designed to estimate
1585!!                leaf onset after the end of soil frost.
1586!!                The NDG (::ngd_minus5) is the number of days with a daily mean air
1587!!                temperature of greater than -5 degrees C,
1588!!                starting from the beginning of the dormancy period (i.e. time since the leaves
1589!!                were lost/GPP below a certain threshold).
1590!!                Leaf onset begins if the NGD is higher than the PFT-dependent constant threshold,
1591!!                ::ngd,  AND if the weekly temperature is higher than the monthly
1592!!                temperature. \n
1593!!                The dormancy time-length is represented by the variable
1594!!                ::time_lowgpp, which is calculated in ::stomate_season. It is increased by
1595!!                the stomate time step when the weekly GPP is lower than a threshold. Otherwise
1596!!                it is set to zero. \n
1597!!                ::ngd_minus5 is also calculated in ::stomate_season. It is initialised at the
1598!!                beginning of the dormancy period (::time_lowgpp>0), and increased by the
1599!!                stomate time step when the temperature > -5 degrees C. \n
1600!!                ::ngd is set for each PFT in ::stomate_data, and a
1601!!                table defining the minimum NGD for each PFT is given in ::ngd_crit_tab
1602!!                in ::stomate_constants. \n
1603!!                The ::pheno_ngd subroutine is called in the subroutine ::phenology.     
1604!!
1605!! RECENT CHANGE(S): None
1606!!               
1607!! MAIN OUTPUT VARIABLE(S): ::begin_leaves - specifies whether leaf growth can start
1608!!
1609!! REFERENCE(S) :
1610!! - Botta, A., N. Viovy, P. Ciais, P. Friedlingstein and P. Monfray (2000),
1611!! A global prognostic scheme of leaf onset using satellite data,
1612!! Global Change Biology, 207, 337-347.
1613!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
1614!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
1615!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
1616!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
1617!!
1618!! FLOWCHART    :
1619!! \latexonly
1620!! \includegraphics[scale = 1]{pheno_ngd.png}
1621!! \endlatexonly
1622!! \n
1623!_ ================================================================================================================================
1624
1625  SUBROUTINE pheno_ngd (npts, j, PFTpresent, allow_initpheno, ngd, &
1626       t2m_month, t2m_week, begin_leaves)
1627
1628    !
1629    !! 0. Variable and parameter declaration
1630    !
1631
1632    !
1633    !! 0.1 Input variables
1634    !
1635    INTEGER(i_std), INTENT(in)                               :: npts            !! Domain size - number of grid cells (unitless)
1636    INTEGER(i_std), INTENT(in)                               :: j               !! PFT index (unitless)
1637    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent      !! PFT exists (true/false)
1638    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: allow_initpheno !! are we allowed to declare the beginning of the
1639                                                                                !! growing season? (true/false)
1640    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: ngd             !! growing degree days (C)
1641    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_month       !! "monthly" 2-meter temperatures (K)
1642    REAL(r_std), DIMENSION(npts), INTENT(in)                 :: t2m_week        !! "weekly" 2-meter temperatures (K)
1643
1644    !
1645    !! 0.2 Output variables
1646    !
1647
1648    !
1649    !! 0.3 Modified variables
1650    !
1651    LOGICAL, DIMENSION(npts,nvm), INTENT(inout)              :: begin_leaves    !! signal to start putting leaves on (true/false)
1652
1653    !
1654    !! 0.4 Local variables
1655    !
1656    INTEGER(i_std)                                           :: i               !! index (unitless)
1657
1658    !! =========================================================================
1659
1660    IF (printlev>=3) WRITE(numout,*) 'Entering ngd'
1661
1662    !
1663    !! 1. Initializations
1664    !
1665
1666    !
1667    !! 1.1 initialize output
1668    !
1669
1670    begin_leaves(:,j) = .FALSE.
1671
1672    !
1673    !! 1.2 check the critical value ::ngd_crit is defined.
1674    !!     If not, stop.
1675    !
1676
1677    IF ( ngd_crit(j) .EQ. undef ) THEN
1678
1679       WRITE(numout,*) 'ngd: ngd_crit is undefined for PFT (::j) ',j
1680       CALL ipslerr_p(3,'stomate phenology','ngd_crit is undefined for this PFT','','')
1681
1682    ENDIF
1683
1684    !
1685    !! 2. Check if biometeorological conditions are favourable for leaf growth.
1686    !!    PFT has to be there and start of growing season must be allowed.
1687    !
1688
1689    DO i = 1, npts
1690
1691       IF ( PFTpresent(i,j) .AND. allow_initpheno(i,j) ) THEN
1692
1693          !! 2.1 Determine if the growing season should start (if so, ::begin_leaves set to TRUE).
1694          !!     This occurs if the critical NGD has been reached AND are temperatures increasing.
1695
1696          IF ( ( ngd(i,j) .GE. ngd_crit(j) ) .AND. &
1697               ( t2m_week(i) .GT. t2m_month(i) )        ) THEN
1698             begin_leaves(i,j) = .TRUE.
1699          ENDIF
1700
1701       ENDIF        ! PFT there and start of growing season allowed
1702
1703    ENDDO ! end loop over grid points
1704
1705    IF (printlev>=4) WRITE(numout,*) 'Leaving ngd'
1706
1707  END SUBROUTINE pheno_ngd
1708
1709END MODULE stomate_phenology
Note: See TracBrowser for help on using the repository browser.