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

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

copy ORCHIDEE-GMv3.2 for publication

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