source: branches/publications/ORCHIDEE-LEAK-r5919/src_stomate/stomate_phenology.f90 @ 5925

Last change on this file since 5925 was 2738, checked in by josefine.ghattas, 9 years ago

Small modifications for TAF :

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