source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_stomate/stomate_season.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 68.0 KB
Line 
1! =================================================================================================================================
2! MODULE        : stomate_season
3!
4! CONTACT       : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE       : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>\BRIEF       This module calculates long-term meteorological parameters from daily temperatures
9!! and precipitations (essentially for phenology).
10!!     
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S): None
14!!
15!! SVN          :
16!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_season.f90 $
17!! $Date: 2017-10-18 11:15:06 +0200 (Wed, 18 Oct 2017) $
18!! $Revision: 4693 $
19!! \n
20!_ =================================================================================================================================
21
22MODULE stomate_season
23
24  ! modules used:
25  USE xios_orchidee
26  USE ioipsl_para
27  USE stomate_data
28  USE constantes
29  USE constantes_soil
30  USE pft_parameters 
31  USE solar
32  USE grid
33  USE time, ONLY : one_year, julian_diff, LastTsYear
34
35  IMPLICIT NONE
36
37  ! private & public routines
38
39  PRIVATE
40  PUBLIC season,season_clear
41
42  LOGICAL, SAVE              :: firstcall_season = .TRUE.  !! first call (true/false)
43!$OMP THREADPRIVATE(firstcall_season)
44
45CONTAINS
46
47!! ================================================================================================================================
48!! SUBROUTINE   : season_clear
49!!
50!>\BRIEF          Flag setting
51!!
52!! DESCRIPTION  : This subroutine sets flags ::firstcall_season, to .TRUE., and therefore activates   
53!!                section 1.1 of the ::season subroutine which writes messages to the output. \n
54!!                This subroutine is called at the end of the subroutine ::stomate_clear, in the
55!!                module ::stomate.
56!!
57!! RECENT CHANGE(S):None
58!!
59!! MAIN OUTPUT VARIABLE(S): ::firstcall_season
60!!
61!! REFERENCE(S)  : None
62!!
63!! FLOWCHART     : None
64!! \n             
65!_ =================================================================================================================================
66
67  SUBROUTINE season_clear
68    firstcall_season=.TRUE.
69  END SUBROUTINE season_clear
70
71
72
73!! ================================================================================================================================
74!! SUBROUTINE   : season
75!!
76!>\BRIEF          This subroutine calculates many of the long-term biometeorological variables
77!!                needed in the phenology subroutines and in the calculation of long-term vegetation
78!!                dynamics in the LPJ DGVM.
79!!
80!! DESCRIPTION    This subroutine is called by the module ::stomate before LPJ, and mainly deals 
81!!                with the calculation of long-term meteorological variables, carbon fluxes and
82!!                vegetation-related variables that are used to calculate vegetation dynamics
83!!                in the stomate modules relating to the phenology and to the longer-term
84!!                changes in vegetation type and fractional cover in the LPJ DGVM modules. \n
85!!                In sections 2 to 5, longer-term meteorological variables are calculated. The
86!!                long-term moisture availabilities are used in the leaf onset and senescence
87!!                phenological models ::stomate_phenology and ::stomate_turnover that require
88!!                a moisture condition. The long term temperatures are also required for phenology
89!!                but in addition they are used in calculations of C flux and the presence and
90!!                establishment of vegetation patterns on a longer timescale in the LPJ DGVM modules.
91!!                Finally the monthly soil humidity/relative soil moisture is used in the C
92!!                allocation module ::stomate_alloc. \n
93!!                Sections 12 to 14 also calculate long-term variables of C fluxes, including NPP,
94!!                turnover and GPP. The first two are used to calculate long-term vegetation
95!!                dynamics and land cover change in the LPJ DVGM modules. The weekly GPP is used
96!!                to determine the dormancy onset and time-length, as described below. \n
97!!                The long-term variables described above are are used in certain vegetation
98!!                dynamics processes in order to maintain consistency with the basic hypotheses of the
99!!                parameterisations of LPJ, which operates on a one year time step (Krinner et al., 2005).
100!!                In order to reduce the computer memory requirements, short-term variables (e.g. daily
101!!                temperatures) are not stored for averaging over a longer period. Instead
102!!                the long-term variables (e.g. monthly temperature) are calculated at each time step
103!!                using a linear relaxation method, following the equation:
104!!                \latexonly
105!!                \input{season_lin_relax_eqn1.tex}
106!!                \endlatexonly
107!!                \n
108!!                The long-term variables are therefore updated on a daily basis. This method allows for
109!!                smooth temporal variation of the long-term variables which are used to calculate
110!!                vegetation dynamics (Krinner et al., 2005). \n
111!!                Sections 6 to 11 calculate the variables required for to determine leaf onset in
112!!                the module ::stomate_phenology.
113!!                These include :
114!!                - the dormance onset and time-length, when GPP is below a certain threshold \n
115!!                - the growing degree days (GDD), which is the sum of daily temperatures greater than
116!!                -5 degrees C, either since the onset of the dormancy period, or since midwinter \n
117!!                - the number of chilling days, which is the number of days with a daily temperature
118!!                lower than a PFT-dependent threshold since the beginning of the dormancy period \n
119!!                - the number of growing days, which is the the number of days with a temperature
120!!                greater than -5 degrees C since the onset of the dormancy period \n
121!!                - the time since the minimum moisture availability in the dormancy period. \n
122!!                These variables are used to determine the conditions needed for the start of the
123!!                leaf growing season. The specific models to which they correspond are given below. \n
124!!                Sections 15 to 20 are used to update the maximum/minimum or the sum of various
125!!                meteorological and biological variables during the year that are required for
126!!                calculating either leaf onset or longer-term vegetation dynamics the following year. \n
127!!                At the end of the year, these variables are updated from "thisyear" to "lastyear",
128!!                in Section 21 of this subroutine, for use the following year. \n
129!!                Finally the probably amount of herbivore consumption is calculated in Section 22,
130!!                following McNaughton et al. (1989).
131!!
132!! RECENT CHANGE(S): None
133!!               
134!! MAIN OUTPUT VARIABLE(S): :: herbivores,
135!!                        :: maxmoiavail_lastyear, :: maxmoiavail_thisyear,
136!!                        :: minmoiavail_lastyear, :: minmoiavail_thisyear,
137!!                        :: maxgppweek_lastyear, :: maxgppweek_thisyear,
138!!                        :: gdd0_lastyear, :: gdd0_thisyear,
139!!                        :: precip_lastyear, :: precip_thisyear,
140!!                        :: lm_lastyearmax, :: lm_thisyearmax,
141!!                        :: maxfpc_lastyear, :: maxfpc_thisyear,
142!!                        :: moiavail_month, :: moiavail_week,
143!!                        :: t2m_longterm, :: t2m_month, :: t2m_week,
144!!                        :: tsoil_month, :: soilhum_month,
145!!                        :: npp_longterm, :: turnover_longterm, :: gpp_week,
146!!                        :: gdd_m5_dormance, :: gdd_midwinter,
147!!                        :: ncd_dormance, :: ngd_minus5, :: time_lowgpp,
148!!                        :: time_hum_min, :: hum_min_dormance
149!!     
150!! REFERENCES   :
151!! - Krinner, G., N. Viovy, N. de Noblet-Ducoudre, J. Ogee, J. Polcher, P.
152!! Friedlingstein, P. Ciais, S. Sitch and I.C. Prentice (2005), A dynamic global
153!! vegetation model for studies of the coupled atmosphere-biosphere system, Global
154!! Biogeochemical Cycles, 19, doi:10.1029/2003GB002199.
155!! - McNaughton, S.J., M. Oesterheld, D.A. Frank and K.J. Williams (1989),
156!! Ecosystem-level patterns of primary productivity and herbivory in terrestrial
157!! habitats, Nature, 341, 142-144.
158!!                       
159!! FLOWCHART    :
160!! \latexonly
161!! \includegraphics[scale = 1]{season_flowchart_part1.png}
162!! \includegraphics[scale = 1]{season_flowchart_part2.png}
163!! \includegraphics[scale = 1]{season_flowchart_part3.png}
164!! \endlatexonly
165!! \n   
166!_ =================================================================================================================================
167
168  SUBROUTINE season (npts, dt, veget_cov, veget_cov_max, &
169       moiavail_daily, t2m_daily, tsoil_daily, soilhum_daily, lalo,  &
170       precip_daily, npp_daily, biomass, turnover_daily, gpp_daily, when_growthinit, &
171       maxmoiavail_lastyear, maxmoiavail_thisyear, &
172       minmoiavail_lastyear, minmoiavail_thisyear, &
173       maxgppweek_lastyear, maxgppweek_thisyear, &
174       gdd0_lastyear, gdd0_thisyear, &
175       precip_lastyear, precip_thisyear, &
176       lm_lastyearmax, lm_thisyearmax, &
177       maxfpc_lastyear, maxfpc_thisyear, &
178       moiavail_month, moiavail_week, t2m_longterm, tau_longterm, t2m_month, t2m_week, &
179       tsoil_month, soilhum_month, &
180       npp_longterm, turnover_longterm, gpp_week, &
181       gdd_m5_dormance, gdd_midwinter, ncd_dormance, ngd_minus5, &
182       time_hum_min, hum_min_dormance, gdd_init_date , & 
183       gdd_from_growthinit, herbivores, &
184       Tseason, Tseason_length, Tseason_tmp, &
185       Tmin_spring_time, t2m_min_daily, begin_leaves, onset_date)
186
187    !
188    !! 0. Variable and parameter declaration
189    !
190
191    !
192    !! 0.1 Input variables
193    !
194    INTEGER(i_std), INTENT(in)                             :: npts              !! Domain size - number of grid cells (unitless)
195    REAL(r_std), INTENT(in)                                :: dt                !! time step in days (dt_days)
196    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: veget_cov         !! coverage fraction of a PFT. Here: fraction of
197                                                                                !! total ground. (0-1, unitless)
198    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: veget_cov_max     !! "maximal" coverage fraction of a PFT (for LAI ->
199                                                                                !! infinity) (0-1, unitless)Here: fraction of
200                                                                                !! total ground.
201    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: moiavail_daily    !! Daily moisture availability (0-1, unitless)
202    REAL(r_std), DIMENSION(npts), INTENT(in)               :: t2m_daily         !! Daily 2 meter temperature (K)
203    REAL(r_std), DIMENSION(npts,nslm), INTENT(in)          :: tsoil_daily       !! Daily soil temperature (K)
204    REAL(r_std), DIMENSION(npts,nslm), INTENT(in)          :: soilhum_daily     !! Daily soil humidity (0-1, unitless)
205    REAL(r_std), DIMENSION(npts,2), INTENT(in)             :: lalo              !!  array of lat/lon
206    REAL(r_std), DIMENSION(npts), INTENT(in)               :: precip_daily      !! Daily mean precipitation @tex ($mm day^{-1}$)
207                                                                                !! @endtex
208    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: npp_daily         !! daily net primary productivity @tex ($gC m^{-2}
209                                                                                !! day^{-1}$) @endtex
210    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: biomass     !! biomass @tex ($gC m^{-2} of ground$) @endtex
211    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: turnover_daily  !! Turnover rates @tex ($gC m^{-2} day^{-1}$)
212                                                                                !! @endtex
213    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: gpp_daily         !! daily gross primary productivity 
214                                                                                !! (Here: @tex $gC m^{-2} of total ground
215                                                                                !! day^{-1}$) @endtex
216    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)           :: when_growthinit   !! how many days ago was the beginning of the
217                                                                                !! growing season (days)
218    LOGICAL, DIMENSION(npts,nvm), INTENT(in)               :: begin_leaves      !! signal to start putting leaves on (true/false)
219    REAL(r_std), DIMENSION(npts), INTENT(in)               :: t2m_min_daily     !! Daily minimum 2-meter temperature (K)
220
221    !
222    !! 0.2 Output variables
223    ! (diagnostic)
224    !
225    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)          :: herbivores        !! time constant of probability of a leaf to be
226                                                                                !! eaten by a herbivore (days)
227
228    !
229    !! 0.3 Modified variables
230    !
231    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxmoiavail_lastyear      !! last year's maximum moisture
232                                                                                        !! availability (0-1, unitless)
233    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxmoiavail_thisyear      !! this year's maximum moisture
234                                                                                        !! availability (0-1, unitless)
235    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: minmoiavail_lastyear      !! last year's minimum moisture
236                                                                                        !! availability (0-1, unitless)
237    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: minmoiavail_thisyear      !! this year's minimum moisture
238                                                                                        !! availability (0-1, unitless)
239    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxgppweek_lastyear       !! last year's maximum weekly GPP
240                                                                                        !! @tex ($gC m^{-2} week^{-1}$) @endtex
241    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxgppweek_thisyear       !! this year's maximum weekly GPP
242                                                                                        !! @tex ($gC m^{-2} week^{-1}$) @endtex
243    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: gdd0_lastyear             !! last year's annual GDD0 (C)
244    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: gdd0_thisyear             !! this year's annual GDD0 (C)
245    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: precip_lastyear           !! last year's annual precipitation
246                                                                                        !! @tex ($mm year^{-1}$) @endtex
247    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: precip_thisyear           !! this year's annual precipitation
248                                                                                        !! @tex ($mm year^{-1}$) @endtex
249    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: lm_lastyearmax            !! last year's maximum leaf mass, for each
250                                                                                        !! PFT @tex ($gC m^{-2}$) @endtex
251    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: lm_thisyearmax            !! this year's maximum leaf mass, for each
252                                                                                        !! PFT @tex ($gC m^{-2}$) @endtex
253    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxfpc_lastyear           !! last year's maximum fpc for each PFT, on
254                                                                                        !! ground (0-1, unitless)
255    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: maxfpc_thisyear           !! this year's maximum fpc for each PFT, on
256                                                                                        !! ground (0-1, unitless)
257    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: moiavail_month            !! "monthly" moisture availability
258                                                                                        !! (0-1, unitless)
259    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: moiavail_week             !! "weekly" moisture availability
260                                                                                        !! (0-1, unitless)
261    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: t2m_longterm              !! "long term" 2-meter temperatures (K)
262    REAL(r_std), INTENT(inout)                             :: tau_longterm     
263    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: t2m_month                 !! "monthly" 2-meter temperatures (K)
264    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: t2m_week                  !! "weekly" 2-meter temperatures (K)
265    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: Tseason                   !! "seasonal" 2-meter temperatures (K),
266                                                                                        !! used to constrain boreal treeline
267    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: Tseason_tmp               !! temporary variable to calculate Tseason
268    REAL(r_std), DIMENSION(npts), INTENT(inout)            :: Tseason_length            !! temporary variable to calculate Tseason:
269                                                                                        !! number of days when t2m_week is higher than 0 degree
270    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: Tmin_spring_time          !! Number of days after begin_leaves (leaf onset)
271    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: onset_date                !! Date in the year at when the leaves started to grow(begin_leaves)
272    REAL(r_std), DIMENSION(npts,nslm), INTENT(inout)       :: tsoil_month               !! "monthly" soil temperatures (K)
273    REAL(r_std), DIMENSION(npts,nslm), INTENT(inout)       :: soilhum_month             !! "monthly" soil humidity (0-1, unitless)
274    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: npp_longterm              !! "long term" net primary productivity
275                                                                                        !! @tex ($gC m^{-2} year^{-1}$) @endtex
276    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: turnover_longterm !! "long term" turnover rate
277                                                                                        !! @tex ($gC m^{-2} year^{-1}$) @endtex
278    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gpp_week                  !! "weekly" GPP @tex ($gC m^{-2} day^{-1}$)
279                                                                                        !! @endtex
280    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gdd_m5_dormance           !! growing degree days above threshold -5
281                                                                                        !! deg. C (C)
282    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gdd_midwinter             !! growing degree days since midwinter (C)
283    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: ncd_dormance              !! number of chilling days since leaves
284                                                                                        !! were lost (days)
285    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: ngd_minus5                !! number of growing days (days)
286    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: time_hum_min              !! time elapsed since strongest moisture
287                                                                                        !! availability (days)
288    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: hum_min_dormance          !! minimum moisture during dormance
289                                                                                        !! (0-1, unitless)
290    REAL(r_std), DIMENSION(npts,2), INTENT(inout)          :: gdd_init_date             !! inital date for gdd count
291    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)        :: gdd_from_growthinit       !! growing degree days, threshold 0 deg. C
292                                                                                        !! since beginning of season
293
294    !
295    !! 0.4 Local variables
296    !
297    INTEGER(i_std)                                          :: j                        !! indices (unitless)
298    REAL(r_std)                                             :: ncd_max                  !! maximum ncd (to avoid floating point
299                                                                                        !! underflows) (days)
300    REAL(r_std), DIMENSION(npts)                            :: sumfpc_nat               !! sum of natural fpcs (0-1, unitless)
301                                                                                        !! [DISPENSABLE]
302    REAL(r_std), DIMENSION(npts,nvm)                        :: weighttot                !! weight of biomass @tex ($gC m^{-2}$)
303                                                                                        !! @endtex
304    REAL(r_std), DIMENSION(npts,nvm)                        :: nlflong_nat              !! natural long-term leaf NPP
305                                                                                        !! @tex ($gC m^{-2} year^{-1}$) @endtex
306    REAL(r_std), DIMENSION(npts,nvm)                        :: green_age                !! residence time of green tissue (years)
307    REAL(r_std), DIMENSION(npts)                            :: consumption              !! herbivore consumption
308                                                                                        !! @tex ($gC m^{-2} day^{-1}$) @endtex
309    REAL(r_std), DIMENSION(npts)                            :: fracnat                  !! fraction of each gridcell occupied by
310                                                                                        !! natural vegetation (0-1, unitless)
311    REAL(r_std), DIMENSION(npts)                            :: solad                    !! maximal radation during current day
312                                                                                        !! (clear sky condition)
313    REAL(r_std), DIMENSION(npts)                            :: solai                    !! maximal radation during current day
314                                                                                        !! (clear sky condition)
315    REAL(r_std), DIMENSION(npts)                            :: cloud                    !! cloud fraction
316
317!_ =================================================================================================================================
318
319    IF (printlev>=3) WRITE(numout,*) 'Entering season'
320
321    !
322    !! 1. Initializations
323    !! 1.1 Calculate ::ncd_max - the maximum possible NCD (number of chilling days) as:
324    !!     \latexonly
325    !!     \input{season_ncdmax_eqn2.tex}
326    !!     \endlatexonly
327    !!     \n
328    !!     where one_year is 1 year in seconds (defined in ::constantes).
329    !
330    ncd_max = ncd_max_year * one_year
331
332    IF ( firstcall_season ) THEN
333
334       !
335       !! 1.2 first call - output message giving the setting of the ::gppfrac_dormance,
336       !!     ::hvc1, ::hvc2 and ::leaf_frac (as a percentage) parameters which are
337       !!     defined at the beginning of this subroutine. Also outputs the value of
338       !!     ::ncd_max.
339       !
340
341       IF ( printlev>=2 ) THEN
342
343          WRITE(numout,*) 'season: '
344
345          WRITE(numout,*) '   > maximum GPP/GGP_max ratio for dormance (::gppfrac_dormance) :',gppfrac_dormance !*
346
347          WRITE(numout,*) '   > maximum possible ncd(days) (::ncd_max) : ',ncd_max !*
348
349          WRITE(numout,*) '   > herbivore consumption C (gC/m2/d) as a function of NPP (gC/m2/d): (::hvc1) (::hvc2)' !*
350          WRITE(numout,*) '     C=',hvc1,' * NPP^',hvc2
351          WRITE(numout,*) '   > for herbivores, suppose that (::leaf_frac_hvc)',leaf_frac_hvc*100., &
352               '% of NPP is allocated to leaves'
353
354       ENDIF
355
356       !
357       !! 1.3 Check whether longer-term meteorological and phenology-related variables are not initialized
358       !!     to less than zero. If the following meteorological variables are less than ::min_stomate which is set
359       !!     to 1.E-8 in ::grid, then they are set to the current daily value. If the phenology-
360       !!     related variables are less than ::min_stomate, they are set to "undef".
361       !!     Warning messages are output in each case, and are also output if "long-term" C fluxes GPP,
362       !!     NPP and turnover are less than ::min_stomate.
363       !
364
365       !! 1.3.1 moisture availabilities (i.e. relative soil moisture, including the root soil profile):
366
367       !! 1.3.1.1 "monthly" (::moiavail_month)
368       IF ( ABS( SUM( moiavail_month(:,2:nvm) ) ) .LT. min_stomate ) THEN
369
370          ! in this case, set them it today's moisture availability
371          WRITE(numout,*) 'Warning! We have to initialize the ''monthly'' moisture availabilities. '
372          moiavail_month(:,:) = moiavail_daily(:,:)
373
374       ENDIF
375
376       !! 1.3.1.2 "weekly" (::moiavail_week)
377
378       IF ( ABS( SUM( moiavail_week(:,2:nvm) ) ) .LT. min_stomate ) THEN
379
380          ! in this case, set them it today's moisture availability
381          WRITE(numout,*) 'Warning! We have to initialize the ''weekly'' moisture availabilities. '
382          moiavail_week(:,:) = moiavail_daily(:,:)
383
384       ENDIF
385
386       !! 1.3.2 2-meter temperatures:
387
388       !!  "monthly" (::t2m_month)
389       IF ( ABS( SUM( t2m_month(:) ) ) .LT. min_stomate ) THEN
390
391          ! in this case, set them to today's temperature
392          WRITE(numout,*) 'Warning! We have to initialize the ''monthly'' 2m temperatures.'
393          t2m_month(:) = t2m_daily(:)
394
395       ENDIF
396
397       !!  "weekly" (::2m_week)
398       IF ( ABS( SUM( t2m_week(:) ) ) .LT. min_stomate ) THEN
399
400          ! in this case, set them to today's temperature
401          WRITE(numout,*) 'Warning! We have to initialize the ''weekly'' 2m temperatures.'
402          t2m_week(:) = t2m_daily(:)
403
404       ENDIF
405
406       !! 1.3.3 "monthly" soil temperatures (::tsoil_month):
407       !MM PAS PARALLELISE!!
408       IF ( ABS( SUM( tsoil_month(:,:) ) ) .LT. min_stomate ) THEN
409
410          ! in this case, set them to today's temperature
411          WRITE(numout,*) 'Warning!'// &
412               ' We have to initialize the ''monthly'' soil temperatures.'
413          tsoil_month(:,:) = tsoil_daily(:,:)
414
415       ENDIF
416
417       !! 1.3.4 "monthly" soil humidity (::soilhum_month):
418       IF ( ABS( SUM( soilhum_month(:,:) ) ) .LT. min_stomate ) THEN
419
420          ! in this case, set them to today's humidity
421          WRITE(numout,*) 'Warning!'// &
422               ' We have to initialize the ''monthly'' soil humidity.'
423          soilhum_month(:,:) = soilhum_daily(:,:)
424
425       ENDIF
426
427       !! 1.3.5 growing degree days, threshold -5 deg C (::gdd_m5_dormance):
428       IF ( ABS( SUM( gdd_m5_dormance(:,2:nvm) ) ) .LT. min_stomate ) THEN
429          WRITE(numout,*) 'Warning! Growing degree days (-5 deg) are initialized to ''undef''.'
430          gdd_m5_dormance(:,:) = undef
431       ENDIF
432
433       !! 1.3.6 growing degree days since midwinter (::gdd_midwinter):
434       IF ( ABS( SUM( gdd_midwinter(:,2:nvm) ) ) .LT. min_stomate ) THEN
435          WRITE(numout,*) 'Warning! Growing degree days since midwinter' // &
436               ' are initialized to ''undef''.'
437          gdd_midwinter(:,:) = undef
438       ENDIF
439
440       !! 1.3.7 number of chilling days since leaves were lost (::ncd_dormance):
441       IF ( ABS( SUM( ncd_dormance(:,2:nvm) ) ) .LT. min_stomate ) THEN
442          WRITE(numout,*) 'Warning! Number of chilling days is initialized to ''undef''.'
443          ncd_dormance(:,:) = undef
444       ENDIF
445
446       !! 1.3.8 number of growing days, threshold -5 deg C (::ngd_minus5):
447       IF ( ABS( SUM( ngd_minus5(:,2:nvm) ) ) .LT. min_stomate ) THEN
448          WRITE(numout,*) 'Warning! Number of growing days (-5 deg) is initialized to 0.'
449       ENDIF
450
451       !! 1.3.9 "long term" npp (::npp_longterm):
452       IF ( ABS( SUM( npp_longterm(:,2:nvm) ) ) .LT. min_stomate ) THEN
453          WRITE(numout,*) 'Warning! Long term NPP is initialized to 0.'
454       ENDIF
455
456       !! 1.3.10 "long term" turnover (::turnover_longterm):
457       IF ( ABS( SUM( turnover_longterm(:,2:nvm,:,:) ) ) .LT. min_stomate ) THEN
458          WRITE(numout,*) 'Warning! Long term turnover is initialized to 0.'
459       ENDIF
460
461       !! 1.3.11 "weekly" GPP (::gpp_week):
462       IF ( ABS( SUM( gpp_week(:,2:nvm) ) ) .LT. min_stomate ) THEN
463          WRITE(numout,*) 'Warning! Weekly GPP is initialized to 0.'
464       ENDIF
465
466       !! 1.3.12 minimum moisture availabilities (::minmoiavail_thisyear)
467       !!        In this case, if the minimum moisture
468       !!        is less than ::min_stomate, the variable is set to ::large_value,
469       !!        which is defined in ::stomate_constants as 1.E33_r_std:
470       IF ( ABS( SUM( minmoiavail_thisyear(:,2:nvm) ) ) .LT. min_stomate ) THEN
471
472          ! in this case, set them to a very high value
473          WRITE(numout,*) 'Warning! We have to initialize this year''s minimum '// &
474               'moisture availabilities.'
475          minmoiavail_thisyear(:,:) = large_value
476
477       ENDIF
478
479       !
480       !! 1.4 reset firstcall_season flag
481       !
482
483       firstcall_season = .FALSE.
484
485    ENDIF
486
487    ! determine min yearly clear sky radiation (solstice) as beginning for gdd count
488    cloud(:) = zero
489    CALL downward_solar_flux (npts, lalo(:,1),julian_diff,12.,cloud,1,solad,solai)
490
491    WHERE (solad(:) .LT. gdd_init_date(:,2))
492       gdd_init_date(:,1)= julian_diff
493       gdd_init_date(:,2)= solad(:)
494    ENDWHERE
495
496
497    !
498    !! NOTE: Sections 2. to 5. compute slowly-varying, "long-term" (i.e. weekly/monthly)
499    !! input variables using a linear relaxation method, following the equation:
500    !! \latexonly
501    !! \input{season_lin_relax_eqn1.tex}
502    !! \endlatexonly
503    !! \n
504    !! as described in the introduction to this subroutine (see Krinner et al., 2005). 
505    !! The time constant in the above equation is given for each of the variables
506    !! described.
507    !
508
509    !
510    !! 2. Moisture availability (relative soil moisture, including the root profile) :
511    !!    The time constants (as in the above equation) for these calculations are
512    !!    given by the parameters ::tau_hum_month (for the monthly
513    !!    calculation) or ::tau_hum_week (for the weekly),
514    !!    which are set in ::stomate_data to be 20 and 7 days respectively.
515    !!    If the moisture availability is less than zero, it is set to zero.
516    !!    These variables are mostly used in the phenological leaf onset and senescence
517    !!    models in the modules ::stomate_phenology and ::stomate_turnover,
518    !!    respectively. They are used in models which require a moisture limitation
519    !!    condition. These are the 'hum', 'moi', 'humgdd' and 'moigdd' onset models,
520    !!    and the 'mixed' and 'dry' (weekly only) senescence models. In addition,
521    !!    the weekly moisture availability is used to calculate the limitation
522    !!    on the fraction of NPP allocated to different compartments in the module
523    !!    ::stomate_alloc.
524    !
525
526    !
527    !! 2.1 "monthly" (::moiavail_month)
528    !
529
530    moiavail_month = ( moiavail_month * ( tau_hum_month - dt ) + &
531         moiavail_daily * dt ) / tau_hum_month
532
533    DO j = 2,nvm  ! Loop over # PFTs
534       WHERE ( ABS(moiavail_month(:,j)) .LT. EPSILON(zero) )
535          moiavail_month(:,j) = zero
536       ENDWHERE
537    ENDDO
538
539    !
540    !! 2.2 "weekly" (::moiavail_week)
541    !
542
543    moiavail_week = ( moiavail_week * ( tau_hum_week - dt ) + &
544         moiavail_daily * dt ) / tau_hum_week
545
546    DO j = 2,nvm ! Loop over # PFTs
547       WHERE ( ABS(moiavail_week(:,j)) .LT. EPSILON(zero) ) 
548          moiavail_week(:,j) = zero
549       ENDWHERE
550    ENDDO
551
552    !
553    !! 3. 2-meter temperatures
554    !!    The time constants for the "long-term", "monthly" and "weekly" 2-meter
555    !!    temperatures are given by the parameters ::tau_longterm_max,
556    !!    ::tau_t2m_month, and ::tau_t2m_week,
557    !!    which are set in ::stomate_data to be 3 * one year (in seconds, as
558    !!    described above) and 20 and 7 days respectively.
559    !!    If the temperature is less than zero, it is set to zero.
560    !!    In addition the "long term" temperature is written to the history file. \n
561    !!    These variables are used in many different modules of STOMATE.
562    !!    The longterm t2m is limied to the intervall [tlong_ref_min, tlong_ref_max]
563    !!    using the equation:
564    !!      \latexonly
565    !!      \input{season_t2m_long_ref_eqn3.tex}
566    !!      \endlatexonly
567    !!      \n
568    !!    The "monthly" and "weekly" temperature is used in the modules
569    !!    ::stomate_phenology and ::stomate_turnover for the onset and senescence
570    !!    phenological models which require a temperature condition. In addition
571    !!    the "monthly" temperature is used in ::lpj_constraints to determine
572    !!    the presence and regeneration of the vegetation and in the module
573    !!    ::stomate_assimtemp to calculate photosynthesis temperatures.
574       
575    ! Update tau_longterm
576    tau_longterm = MIN(tau_longterm+dt,tau_longterm_max)
577   
578    ! Recalculate the reference temperature using the old reference temperature and the current temperature
579    t2m_longterm(:) = ( t2m_longterm(:) * ( tau_longterm - dt ) + &
580         t2m_daily(:) * dt ) / tau_longterm
581
582    ! The longterm reference is not allowed to go outside the interval [tlong_ref_min, tlong_ref_max]
583    t2m_longterm(:) = MAX( tlong_ref_min, MIN( tlong_ref_max, t2m_longterm(:) ) )
584
585    CALL xios_orchidee_send_field("t2m_longterm",t2m_longterm)
586
587    CALL histwrite_p (hist_id_stomate, 'T2M_LONGTERM', itime, &
588         t2m_longterm, npts, hori_index)
589
590    !
591    !! 3.3 "monthly" (::t2m_month)
592    !
593
594    t2m_month = ( t2m_month * ( tau_t2m_month - dt ) + &
595         t2m_daily * dt ) / tau_t2m_month
596
597    WHERE ( ABS(t2m_month(:)) .LT. EPSILON(zero) )
598       t2m_month(:) = zero
599    ENDWHERE
600
601    ! Store the day in onset_date when the leaves started grow. julian_diff is the day in the year [1-366].
602    WHERE ( begin_leaves(:,:) )
603       onset_date(:,:)=julian_diff
604    ELSEWHERE
605       onset_date(:,:)=0
606    ENDWHERE
607   
608    ! Calculate "seasonal" temperature
609    WHERE ( t2m_week (:) .GT. ZeroCelsius )
610       Tseason_tmp(:) = Tseason_tmp(:) + t2m_week(:)
611       Tseason_length(:)=Tseason_length(:) + dt
612    ENDWHERE
613
614    ! calculate Tmin in spring (after onset)
615    DO j=1, nvm
616       IF (leaf_tab(j)==1 .AND. pheno_type(j)==2) THEN
617          ! leaf_tab=broadleaf and pheno_typ=summergreen
618          ! Only treat broadleag and summergreen pfts
619         
620          WHERE ( Tmin_spring_time(:,j)>0 .AND. (Tmin_spring_time(:,j)<spring_days_max) )
621             Tmin_spring_time(:,j)=Tmin_spring_time(:,j)+1
622          ELSEWHERE
623             Tmin_spring_time(:,j)=0
624          ENDWHERE
625         
626          WHERE ( begin_leaves(:,j) )
627             Tmin_spring_time(:,j)=1
628          ENDWHERE
629       END IF
630    END DO
631
632    !
633    !! 3.4 "weekly" (::t2m_week)
634    !
635
636    t2m_week = ( t2m_week * ( tau_t2m_week - dt ) + &
637         t2m_daily * dt ) / tau_t2m_week
638
639    WHERE ( ABS(t2m_week(:)) .LT. EPSILON(zero) )
640       t2m_week(:) = zero
641    ENDWHERE
642
643    !
644    !! 4. "monthly" soil temperatures (::tsoil_month)
645    !!    The time constant is given by the parameter ::tau_tsoil_month,
646    !!    which is set in ::stomate_data to be 20 days.
647    !!    If the monthly soil temperature is less than zero, it is set to zero. \n
648    !!    This variable is used in the ::stomate_allocation module.
649    !
650
651    tsoil_month = ( tsoil_month * ( tau_tsoil_month - dt ) + &
652         tsoil_daily(:,:) * dt ) / tau_tsoil_month
653
654    WHERE ( ABS(tsoil_month(:,:)) .LT. EPSILON(zero) )
655       tsoil_month(:,:) = zero
656    ENDWHERE
657
658    !
659    !! 5. ''monthly'' soil humidity (or relative soil moisture - ::soilhum_month)
660    !!    The time constant is given by the parameter ::tau_soilhum_month,
661    !!    which is set in ::stomate_data to be 20 days.
662    !!    If the monthly soil humidity is less than zero, it is set to zero.
663    !
664
665    soilhum_month = ( soilhum_month * ( tau_soilhum_month - dt ) + &
666         soilhum_daily * dt ) / tau_soilhum_month
667
668    WHERE ( ABS(soilhum_month(:,:)) .LT. EPSILON(zero) )
669       soilhum_month(:,:) = zero
670    ENDWHERE
671
672    !
673    !! 6. Calculate the dormance time-length (::time_lowgpp).
674    !!    The dormancy time-length is increased by the stomate time step when   
675    !!    the weekly GPP is below one of two thresholds,
676    !!    OR if the growing season started more than 2 years ago AND the amount of biomass
677    !!    in the carbohydrate reserve is 4 times as much as the leaf biomass.
678    !!    i.e. the plant is declared dormant if it is accumulating carbohydrates but not
679    !!    using them, so that the beginning of the growing season can be detected .
680    !     This last condition was added by Nicolas Viovy.
681    !!    - NV: special case (3rd condition)
682    !!    Otherwise, set ::time_lowgpp to zero. \n
683    !!    The weekly GPP must be below either the parameter ::min_gpp_allowed, which is set at
684    !!    the beginning of this subroutine to be 0.3gC/m^2/year,
685    !!    OR it must be less than last year's maximum weekly GPP multiplied by the
686    !!    maximal ratio of GPP to maximum GPP (::gppfrac_dormance), which is set to 0.2 at the
687    !!    beginning of this subroutine. \n
688    !!    This variable is used in the ::stomate_phenology module to allow the detection of the
689    !!    beginning of the vegetation growing season for different onset models.
690    !!    Each PFT is looped over.
691    !
692    !NVMODIF
693!!$    DO j = 2,nvm ! Loop over # PFTs
694!!$       WHERE ( ( gpp_week(:,j) .LT. min_gpp_allowed ) .OR. &
695!!$            ( gpp_week(:,j) .LT. gppfrac_dormance * maxgppweek_lastyear(:,j) ) .OR. &
696!!$            ( ( when_growthinit(:,j) .GT. 2.*one_year ) .AND. &
697!!$            ( biomass(:,j,icarbres,icarbon) .GT. biomass(:,j,ileaf,icarbon)*4. ) ) )
698!!$          !       WHERE ( ( gpp_week(:,j) .EQ. zero ) .OR. &
699!!$          !            ( gpp_week(:,j) .LT. gppfrac_dormance * maxgppweek_lastyear(:,j) ) .OR. &
700!!$          !            ( ( when_growthinit(:,j) .GT. 2.*one_year ) .AND. &
701!!$          !            ( biomass(:,j,icarbres,icarbon) .GT. biomass(:,j,ileaf,icarbon)*4. ) ) )
702!!$       
703!!$          time_lowgpp(:,j) = time_lowgpp(:,j) + dt
704!!$         
705!!$       ELSEWHERE
706!!$         
707!!$          time_lowgpp(:,j) = zero
708!!$
709!!$       ENDWHERE
710!!$    ENDDO
711
712    !
713    !! 7. Calculate the growing degree days (GDD - ::gdd_m5_dormance).
714    !!    This variable is the GDD sum of the temperatures higher than -5 degrees C.
715    !!    It is inititalised to 0 at the beginning of the dormancy period (i.e.
716    !!    when ::time_lowgpp>0), and is set to "undef" when there is GPP
717    !!    (::time_lowgpp=0), as it is not used during the growing season. \n
718    !!    ::gdd_m5_dormance is further scaled by (::tau_gdd -dt / ::tau_gdd),
719    !!    - ::tau_gdd is set to 40. in the module ::stomate_constants. \n
720    !     Nicolas Viovy - not sure why this is...
721    !!    This variable is used in the ::stomate_phenology module for the
722    !!    'humgdd' and 'moigdd' leaf onset models. \n
723    !!    Each PFT is looped over but ::gdd_m5_dormance is only calculated for
724    !!    those PFTs for which a critical GDD is defined, i.e. those which are
725    !!    assigned to the 'humgdd' or 'moigdd' models. \n
726    !!    Finally if GDD sum is less than zero, then it is set to zero.
727    !
728
729    DO j = 2,nvm ! Loop over # PFTs
730
731       IF (.NOT. natural(j)) THEN
732          ! reset counter: start of the growing season
733          WHERE ((when_growthinit(:,j) .EQ. zero))
734             gdd_from_growthinit(:,j) = zero
735          ENDWHERE
736          ! increase gdd counter
737          WHERE ( t2m_daily(:) .GT. (ZeroCelsius)  )
738             gdd_from_growthinit(:,j) = gdd_from_growthinit(:,j) + &
739                                 dt * ( t2m_daily(:) - (ZeroCelsius) )
740          ENDWHERE
741       ELSE
742          gdd_from_growthinit(:,j) = undef
743       ENDIF
744
745       ! only for PFTs for which critical gdd is defined
746       ! gdd_m5_dormance is set to 0 at the end of the growing season. It is set to undef
747       ! at the beginning of the growing season.
748
749       IF ( ALL(pheno_gdd_crit(j,:) .NE. undef) ) THEN
750
751          !
752          !! 7.1 set to zero if undefined and there is no GPP
753          !
754
755          WHERE (gdd_init_date(:,1) .EQ. julian_diff)
756
757             gdd_m5_dormance(:,j) = zero
758
759          ENDWHERE
760
761          !
762          !! 7.2 set to undef if there is GPP
763          !
764
765          WHERE ( when_growthinit(:,j) .EQ. zero )
766
767             gdd_m5_dormance(:,j) = undef
768
769          ENDWHERE
770
771          !
772          !! 7.3 normal update as described above where ::gdd_m5_dormance is defined (not set to "undef").
773          !
774
775          WHERE ( ( t2m_daily(:) .GT. ( ZeroCelsius - gdd_threshold ) ) .AND. &
776               ( gdd_m5_dormance(:,j) .NE. undef )           )
777             gdd_m5_dormance(:,j) = gdd_m5_dormance(:,j) + &
778                  dt * ( t2m_daily(:) - ( ZeroCelsius - gdd_threshold ) )
779          ENDWHERE
780
781          WHERE ( gdd_m5_dormance(:,j) .NE. undef ) 
782             gdd_m5_dormance(:,j) = gdd_m5_dormance(:,j) * &
783                  ( tau_gdd - dt ) / tau_gdd
784          ENDWHERE
785
786       ENDIF
787
788    ENDDO
789
790    !
791    !! 7.4 Set to zero if GDD is less than zero.
792
793    DO j = 2,nvm ! Loop over # PFTs
794       WHERE ( ABS(gdd_m5_dormance(:,j)) .LT. EPSILON(zero) )
795          gdd_m5_dormance(:,j) = zero
796       ENDWHERE
797    ENDDO
798
799    !
800    !! 8. Calculate the growing degree days (GDD) since midwinter (::gdd_midwinter)
801    !!    This variable represents the GDD sum of temperatures higher than a PFT-dependent
802    !!    threshold (::ncdgdd_temp), since midwinter.
803    !!    Midwinter is detected if the monthly temperature (::t2m_month) is lower than the weekly
804    !!    temperature (::t2m_week) AND if the monthly temperature is lower than the long-term
805    !!    temperature (t2m_longterm). These variables were calculated earlier in this subroutine. \n
806    !!    ::gdd_midwinter is initialised to 0.0 when midwinter is detected, and from then on
807    !!    increased with each temperature greater than ::ncdgdd_temp, which is defined
808    !!    in the module ::stomate_constants. \n
809    !!    ::gdd_midwinter is set to "undef" when midsummer is detected, following the opposite
810    !!    conditions to those used to define midwinter. \n
811    !!    The variable is used in the ::stomate_phenology module for the leaf onset model 'ncdgdd'.
812    !!    Each PFT is looped over but the ::gdd_midwinter is only calculated for those
813    !!    PFTs for which a critical 'ncdgdd' temperature is defined, i.e. those which are
814    !!    assigned to the 'ncdgdd' model. \n
815    !
816
817    DO j = 2,nvm ! Loop over # PFTs
818
819       ! only for PFTs for which ncdgdd_crittemp is defined
820
821       IF ( ncdgdd_temp(j) .NE. undef ) THEN
822
823          !
824          !! 8.1 set to 0 if undef and if we detect "midwinter"
825          !
826
827!!$          WHERE ( ( gdd_midwinter(:,j) .EQ. undef ) .AND. &
828!!$               ( t2m_month(:) .LT. t2m_week(:) ) .AND. &
829!!$               ( t2m_month(:) .LT. t2m_longterm(:) )    )
830          WHERE (gdd_init_date(:,1) .EQ. julian_diff)
831
832             gdd_midwinter(:,j) = zero
833
834          ENDWHERE
835
836          !
837          !! 8.2 set to undef if we detect "midsummer"
838          !
839
840          WHERE ( ( t2m_month(:) .GT. t2m_week(:) ) .AND. &
841               ( t2m_month(:) .GT. t2m_longterm(:) )    )
842
843             gdd_midwinter(:,j) = undef
844
845          ENDWHERE
846
847          !
848          !! 8.3 normal update as described above
849          !
850
851          WHERE ( ( gdd_midwinter(:,j) .NE. undef ) .AND. &
852               ( t2m_daily(:) .GT. ncdgdd_temp(j)+ZeroCelsius ) )
853
854             gdd_midwinter(:,j) = &
855                  gdd_midwinter(:,j) + &
856                  dt * ( t2m_daily(:) - ( ncdgdd_temp(j)+ZeroCelsius ) )
857
858          ENDWHERE
859
860       ENDIF
861
862    ENDDO
863
864    !
865    !! 9. Calculate the number of chilling days (NCD) since leaves were lost (::ncd_dormance).
866    !!    This variable is initialised to 0 at the beginning of the dormancy period (::time_lowgpp>0)
867    !!    and increased by the stomate time step when the daily temperature is lower than the
868    !!    PFT-dependent threshold ::ncdgdd_temp, which is defined for each PFT
869    !!    in a table (::ncdgdd_temp_tab) in the module ::stomate_data. \n
870    !!    It is set to "undef" when there is GPP (::time_lowgpp=0) as it is not needed during
871    !!    the growing season. \n
872    !!    The variable is used in the ::stomate_phenology module for the leaf onset model 'ncdgdd'.
873    !!    Each PFT is looped over but the ::ncd_dormance is only calculated for those
874    !!    PFTs for which a critical 'ncdgdd' temperature is defined, i.e. those which are
875    !!    assigned to the 'ncdgdd' model.
876    !
877
878    DO j = 2,nvm ! Loop over # PFTs
879
880       IF ( ncdgdd_temp(j) .NE. undef ) THEN
881
882          !
883          !! 9.1 set to zero if undefined and there is no GPP
884          !
885
886          WHERE (gdd_init_date(:,1) .EQ. julian_diff)
887
888             ncd_dormance(:,j) = zero
889
890          ENDWHERE
891
892          !
893          !! 9.2 set to undef if there is GPP
894          !
895
896          WHERE ( when_growthinit(:,j) .EQ. zero )
897
898             ncd_dormance(:,j) = undef
899
900          ENDWHERE
901
902          !
903          !! 9.3 normal update, as described above, where ::ncd_dormance is defined
904          !
905
906          WHERE ( ( ncd_dormance(:,j) .NE. undef ) .AND. &
907               ( t2m_daily(:) .LE. ncdgdd_temp(j)+ZeroCelsius ) )
908
909             ncd_dormance(:,j) = MIN( ncd_dormance(:,j) + dt, ncd_max )
910
911          ENDWHERE
912
913       ENDIF
914
915    ENDDO
916
917    !
918    !! 10. Calculate the number of growing days (NGD) since leaves were lost (::ngd_minus5).
919    !!     This variable is initialised to 0 at the beginning of the dormancy period (::time_lowgpp>0)
920    !!     and increased by the stomate time step when the daily temperature is higher than the threshold
921    !!     -5 degrees C. \n   
922    !!     ::ngd_minus5 is further scaled by (::tau_ngd -dt / ::tau_ngd),
923    !!     - ::tau_ngd is set to 50. in the module ::stomate_constants. \n
924    !      Nicolas Viovy - not sure why this is...
925    !!     The variable is used in the ::stomate_phenology module for the leaf onset model 'ngd'.
926    !!     Each PFT is looped over.
927    !!     If the NGD is less than zero, it is set to zero.
928    !
929
930    DO j = 2,nvm ! Loop over # PFTs
931
932       !
933       !! 10.1 Where there is GPP (i.e. ::time_lowgpp=0), set NGD to 0.
934       !!      This means that we only take into account NGDs when the leaves are off
935       !
936
937       WHERE (gdd_init_date(:,1) .EQ. julian_diff)
938          ngd_minus5(:,j) = zero
939       ENDWHERE
940
941       !
942       !! 10.2 normal update, as described above.
943       !
944
945       WHERE ( t2m_daily(:) .GT. (ZeroCelsius - gdd_threshold) )
946          ngd_minus5(:,j) = ngd_minus5(:,j) + dt
947       ENDWHERE
948
949       ngd_minus5(:,j) = ngd_minus5(:,j) * ( tau_ngd - dt ) / tau_ngd
950
951    ENDDO
952
953    DO j = 2,nvm ! Loop over # PFTs
954       WHERE ( ABS(ngd_minus5(:,j)) .LT. EPSILON(zero) )
955          ngd_minus5(:,j) = zero
956       ENDWHERE
957    ENDDO
958
959    !
960    !! 11. Calculate the minimum humidity/relative soil moisture since dormance began (::hum_min_dormance)
961    !!     and the time elapsed since this minimum (::time_hum_min). \n
962    !!     The minimum moisture availability occurs when the monthly moisture availability, which is updated
963    !!     daily earlier in this subroutine as previously described, is at a minimum during the dormancy period.
964    !!     Therefore the ::hum_min_dormance is initialised to the monthly moisture availability
965    !!     at the beginning of the dormancy period (i.e. if it was previously set to undefined and the
966    !!     ::time_lowgpp>0) AND then whenever the monthly moisture availability is less than it has previously
967    !!     been. \n
968    !!     Consequently, the time counter (::time_hum_min) is initialised to 0 at the beginning of the dormancy 
969    !!     period (i.e. if it was previously set to undefined and the ::time_lowgpp>0) AND when the minimum
970    !!     moisture availability is reached, and is increased by the stomate time step every day throughout
971    !!     the dormancy period. \n
972    !!     ::time_hum_min is used in the ::stomate_phenology module for the leaf onset models 'moi' and 'moigdd'.
973    !!     Each PFT is looped over but the two variables are only calculated for those
974    !!     PFTs for which the critical parameter ::hum_min_time is defined, i.e.   
975    !!     those which are assigned to the 'moi' or 'moigdd' models.
976    !
977
978    DO j = 2,nvm ! Loop over # PFTs
979
980       IF ( hum_min_time(j) .NE. undef ) THEN
981
982          !
983          !! 11.1 initialize if undefined and there is no GPP
984          !
985
986          WHERE (when_growthinit(:,j) .EQ. zero)
987
988             time_hum_min(:,j) = zero
989             hum_min_dormance(:,j) = moiavail_month(:,j)
990
991          ENDWHERE
992
993          !
994          !! 11.3 normal update, as described above, where ::time_hum_min and ::hum_min_dormance are defined
995          !
996
997          !! 11.3.1 increase time counter by the stomate time step
998
999          WHERE ( hum_min_dormance(:,j) .NE. undef )
1000
1001             time_hum_min(:,j) = time_hum_min(:,j) + dt
1002
1003          ENDWHERE
1004
1005          !! 11.3.2 set time counter to zero if minimum is reached
1006
1007          WHERE (( hum_min_dormance(:,j) .NE. undef ) .AND. &
1008               ( moiavail_month(:,j) .LE. hum_min_dormance(:,j) ) )
1009
1010             hum_min_dormance(:,j) = moiavail_month(:,j)
1011             time_hum_min(:,j) = zero
1012
1013          ENDWHERE
1014
1015       ENDIF
1016
1017    ENDDO
1018
1019    !
1020    !! NOTE: Sections 12. to 14. compute slowly-varying, "long-term" (i.e. weekly/monthly)
1021    !! C fluxes (NPP, turnover, GPP) using the same linear relaxation method as in
1022    !! Sections 2. and 5. and described in the introduction to this section, as given
1023    !! by the following equation:
1024    !! \latexonly
1025    !! \input{season_lin_relax_eqn1.tex}
1026    !! \endlatexonly
1027    !! \n
1028    !! The following variables are calculated using the above equation, and the time constant
1029    !! is given for each.
1030    !
1031
1032    !
1033    !! 12. Update the "long term" NPP. (::npp_daily in gC/m^2/day, ::npp_longterm in gC/m^2/year.)
1034    !!     The time constant is given by the parameter ::tau_longterm,
1035    !!     which is set in ::stomate_data to be 3 * one year (in seconds, as
1036    !!     described above). If the ::npp_longterm is less than zero then set it to zero. \n
1037    !!     ::npp_longterm is used in ::stomate_lpj in the calculation of long-term
1038    !!     vegetation dynamics and in ::stomate_lcchange in the calculation of
1039    !!     land cover change. It is also used to calculate diagnose the hebivory activity in
1040    !!     Section 22 of this subroutine.
1041    !
1042
1043    npp_longterm = ( npp_longterm * ( tau_longterm - dt ) + &
1044         (npp_daily*one_year) * dt                          ) / &
1045         tau_longterm
1046
1047    DO j = 2,nvm ! Loop over # PFTs
1048       WHERE ( ABS(npp_longterm(:,j)) .LT. EPSILON(zero) )
1049          npp_longterm(:,j) = zero
1050       ENDWHERE
1051    ENDDO
1052
1053    !
1054    !! 13. Update the "long term" turnover rates (in gC/m^2/year).
1055    !!     The time constant is given by the parameter ::tau_longterm,
1056    !!     which is set in ::stomate_data to be 3 * one year (in seconds, as
1057    !!     described above). If the ::turnover_longterm is less than zero then set it to zero.\n
1058    !!     ::turnover_longterm is used in ::stomate_lpj and :: lpg_gap in the calculation
1059    !!     of long-term vegetation dynamics.
1060    !
1061
1062    turnover_longterm(:,:,:,:) = ( turnover_longterm(:,:,:,:) * ( tau_longterm - dt ) + &
1063         (turnover_daily(:,:,:,:)*one_year) * dt                          ) / &
1064         tau_longterm
1065
1066    DO j = 2,nvm ! Loop over # PFTs
1067       WHERE ( ABS(turnover_longterm(:,j,:,:)) .LT. EPSILON(zero) )
1068          turnover_longterm(:,j,:,:) = zero
1069       ENDWHERE
1070    ENDDO
1071
1072    !
1073    !! 14. Update the "weekly" GPP (where there is vegetation), otherwise set to zero.
1074    !!     The time constant is given by the parameter ::tau_gpp_week,
1075    !!     which is set in ::stomate_data to be 7 days. If the ::gpp_week is
1076    !!     less than zero then set it to zero. \n
1077    !!     ::gpp_week is used to update the annual maximum weekly GPP (::maxgppweek_thisyear)
1078    !!     in Section 16 of this subroutine, which is then used to update the variable
1079    !!     ::maxgppweek_lastyear in Section 21 of this subroutine. Both ::gpp_week and
1080    !!     ::maxgppweek_lastyear are used in Section 6 of this subroutine to calculate
1081    !!     the onset and time-length of the dormancy period.
1082    !      Note: Used to be weekly GPP divided by veget_cov_max, i.e. per ground covered, but not anymore.
1083    !
1084
1085    WHERE ( veget_cov_max .GT. zero )
1086
1087       gpp_week = ( gpp_week * ( tau_gpp_week - dt ) + &
1088            gpp_daily * dt ) / tau_gpp_week
1089
1090    ELSEWHERE
1091
1092       gpp_week = zero
1093
1094    ENDWHERE
1095
1096    DO j = 2,nvm ! Loop over # PFTs
1097       WHERE ( ABS(gpp_week(:,j)) .LT. EPSILON(zero) )
1098          gpp_week(:,j) = zero
1099       ENDWHERE
1100    ENDDO
1101
1102    !
1103    !! 15. Update the maximum and minimum moisture availabilities (::maxmoiavail_thisyear
1104    !!     and ::minmoiavail_thisyear). If the daily moisture availability, ::moiavail_daily,
1105    !!     which was calculated earlier in this subroutine, is greater or less than the current
1106    !!     value of the maximum or minimum moisture availability, then set the value for the maximum
1107    !!     or minimum to the current daily value respectively. \n
1108    !!     ::maxmoiavail_thisyear and ::minmoiavail_thisyear are used to update the variables
1109    !!     ::maxmoiavail_lastyear and ::minmoiavail_lastyear in Section 21 of this subroutine,
1110    !!     which are used in the module ::stomate_phenology for the leaf onset models 'hum' and
1111    !!     'humgdd', and in the module ::stomate_turnover for the leaf senescence models 'dry'
1112    !!     and 'mixed'.
1113    !
1114
1115    WHERE ( moiavail_daily .GT. maxmoiavail_thisyear )
1116       maxmoiavail_thisyear = moiavail_daily
1117    ENDWHERE
1118
1119    WHERE ( moiavail_daily .LT. minmoiavail_thisyear )
1120       minmoiavail_thisyear = moiavail_daily
1121    ENDWHERE
1122
1123    !
1124    !! 16. Update the annual maximum weekly GPP (::maxgppweek_thisyear), if the weekly GPP
1125    !!     is greater than the current value of the annual maximum weekly GPP.
1126    !!     The use of this variable is described in Section 14.
1127    !
1128
1129    WHERE ( gpp_week .GT. maxgppweek_thisyear )
1130       maxgppweek_thisyear = gpp_week
1131    ENDWHERE
1132
1133    !
1134    !! 17. Update the annual GDD0 by adding the current daily 2-meter temperature
1135    !!     (multiplied by the stomate time step, which is one day), if it is greater
1136    !!     than zero degrees C. \n
1137    !!     This variable is mostly used in the module ::lpj_establish.
1138    !
1139
1140    WHERE ( t2m_daily .GT. ZeroCelsius )
1141       gdd0_thisyear = gdd0_thisyear + dt * ( t2m_daily - ZeroCelsius )
1142    ENDWHERE
1143
1144    !
1145    !! 18. Update the annual precipitation by adding the current daily precipitation
1146    !!     amount (multiplied by the stomate time step, which is usually one day). \n
1147    !
1148
1149    precip_thisyear = precip_thisyear + dt * precip_daily
1150
1151   
1152!
1153    !! 19. Update the annual maximum leaf mass for each PFT (::lm_thisyearmax) and the maximum fractional
1154    !!     plant cover if the LPJ DGVM is activated.       
1155    !
1156   
1157    !
1158    !! 19.1 If the LPJ DGVM is activated first the fraction of natural vegetation (::fracnat), i.e. non-
1159    !!      agricultural vegetation (PFTs 2-11) is calculated for each PFT. Each PFT is looped over.
1160    !
1161    IF(ok_dgvm ) THEN
1162
1163       fracnat(:) = un
1164       DO j = 2,nvm ! Loop over # PFTs
1165          IF ( .NOT. natural(j) ) THEN
1166             fracnat(:) = fracnat(:) - veget_cov_max(:,j)
1167          ENDIF
1168       ENDDO
1169
1170    ENDIF
1171
1172    !
1173    !! 19.2 If LPJ and STOMATE are activated, first the maximum fractional plant cover needs to be updated,
1174    !!      and then this year's leaf biomass. Each PFT is looped over.
1175    !!      Both are updated according to the linear relaxation method described above.
1176    !!      \latexonly
1177    !!      \input{season_lin_relax_eqn1.tex}
1178    !!      \endlatexonly
1179    !!      \n
1180    !!      The time constant for this process is set as one year (in seconds) divided by the parameter
1181    !!      ::leaflife_tab, which gives the leaf lifetime in years and is set for each PFT in the module
1182    !!      ::stomate_constants. Each PFT is looped over. \n
1183    !
1184
1185    IF ( ok_stomate ) THEN
1186       IF(ok_dgvm ) THEN
1187          DO j=2,nvm ! Loop over # PFTs
1188
1189             !
1190             !! 19.2.1 Calculate maximum fractional plant cover (::maxfpc_lastyear).
1191             !!        If natural vegetation is present in the grid cell, and the leaf
1192             !!        biomass is greater than three-quarters of last year's leaf biomass, the maximum fractional plant
1193             !!        cover for last year is updated. \n
1194             !!        The short-term variable (Xs in the above equation) that is being used to update the long-term
1195             !!        maximum fractional plant cover is the fractional cover of natural vegetation, specified as
1196             !!        ::veget_cov/::fracnat. Last year's value is then set to be this year's value.
1197             !
1198
1199             IF ( natural(j) .AND. ok_dgvm ) THEN
1200
1201                WHERE ( fracnat(:) .GT. min_stomate .AND. biomass(:,j,ileaf,icarbon).GT. lm_lastyearmax(:,j)*0.75 )
1202                   maxfpc_lastyear(:,j) = ( maxfpc_lastyear(:,j) * ( one_year/leaflife_tab(j)- dt ) + &
1203                        veget_cov(:,j) / fracnat(:) * dt ) / (one_year/leaflife_tab(j))
1204                ENDWHERE
1205                maxfpc_thisyear(:,j) = maxfpc_lastyear(:,j) ! just to initialise value
1206
1207             ENDIF
1208
1209!NV : correct initialization
1210!!$             WHERE(biomass(:,j,ileaf,icarbon).GT. lm_lastyearmax(:,j)*0.75)
1211!!$                lm_lastyearmax(:,j) = ( lm_lastyearmax(:,j) * ( one_year/leaflife_tab(j)- dt ) + &
1212!!$                     biomass(:,j,ileaf,icarbon) * dt ) / (one_year/leaflife_tab(j))
1213!!$             ENDWHERE
1214!!$             lm_thisyearmax(:,j)=lm_lastyearmax(:,j) ! just to initialise value
1215
1216             
1217             !
1218             !! 19.2.2 Update this year's leaf biomass (::lm_thisyearmax).
1219             !!        The short-term variable (Xs in the above equation) that is being used to update the long-term
1220             !!        this year's leaf biomass is the leaf biomass pool (::biomass(i,j,ileaf).
1221             !
1222             WHERE (lm_thisyearmax(:,j) .GT. min_stomate)
1223                WHERE(biomass(:,j,ileaf,icarbon).GT. lm_thisyearmax(:,j)*0.75)
1224                   lm_thisyearmax(:,j) = ( lm_thisyearmax(:,j) * ( one_year/leaflife_tab(j)- dt ) + &
1225                        biomass(:,j,ileaf,icarbon) * dt ) / (one_year/leaflife_tab(j))
1226                ENDWHERE
1227             ELSEWHERE
1228                lm_thisyearmax(:,j) =biomass(:,j,ileaf,icarbon)
1229             ENDWHERE
1230
1231          ENDDO
1232
1233       ELSE
1234         
1235          !
1236          !! 19.3 If LPJ DGVM is not activated but STOMATE is, the maximum leaf mass is set to be the same 
1237          !!      as the leaf biomass (::biomass(i,j,ileaf), without a change in the maximum fractional plant cover.
1238          !
1239          DO j = 2,nvm ! Loop over # PFTs
1240             WHERE ( biomass(:,j,ileaf,icarbon) .GT. lm_thisyearmax(:,j) )
1241                lm_thisyearmax(:,j) = biomass(:,j,ileaf,icarbon)
1242             ENDWHERE
1243          ENDDO
1244
1245       ENDIF !(ok_dgvm)
1246    ELSE
1247
1248          !
1249          !! 19.4 If STOMATE is not activated, the maximum leaf biomass is set to be the maximum possible
1250          !!      LAI of the PFT.
1251          !
1252
1253       DO j = 2,nvm ! Loop over # PFTs
1254          lm_thisyearmax(:,j) = lai_max(j)  / sla(j)
1255       ENDDO
1256
1257    ENDIF  !(ok_stomate)
1258
1259    !
1260    !! 20. Update the annual maximum fractional plant cover for each PFT if the current fractional cover
1261    !!     (::veget_cov), is larger than the current maximum value.
1262    !!     ::veget_cov is defined as fraction of total ground. Therefore, maxfpc_thisyear has the same unit.
1263    !
1264
1265    WHERE ( veget_cov(:,:) .GT. maxfpc_thisyear(:,:) )
1266       maxfpc_thisyear(:,:) = veget_cov(:,:)
1267    ENDWHERE
1268
1269    !
1270    !! 21. At the end of the every year, last year's maximum and minimum moisture availability,
1271    !!     annual GDD0, annual precipitation, annual max weekly GPP, and maximum leaf mass are
1272    !!     updated with the value calculated for the current year, and then their value reset.
1273    !!     Either to zero for the maximum variables, or to ::large_value (set to be 1.E33 in ::
1274    !!     the module ::stomate_constants) for the minimum variable ::minmoiavail_thisyear.
1275    !
1276
1277    IF ( LastTsYear ) THEN
1278
1279       !
1280       !! 21.1 Update last year's values. \n
1281       !!      The variables ::maxmoiavail_lastyear, ::minmoiavail_lastyear and ::maxgppweek_lastyear 
1282       !!      are updated using the relaxation method:
1283       !!      \latexonly
1284       !!      \input{season_lin_relax_eqn1.tex}
1285       !!      \endlatexonly
1286       !!      \n
1287       !!      where Xs is this year's value, dt (Delta-t) is set to 1 (year), and the time constant (tau) !??
1288       !!      is set by the parameter ::tau_climatology, which is set to 20 years at the beginning
1289       !!      of this subroutine. \n
1290       !!      The other variables (::gdd0_lastyear, ::precip_lastyear, ::lm_lastyearmax and
1291       !!      ::maxfpc_lastyear) are just replaced with this year's value.
1292       !
1293       !NVMODIF
1294       maxmoiavail_lastyear(:,:) = (maxmoiavail_lastyear(:,:)*(tau_climatology-1)+ maxmoiavail_thisyear(:,:))/tau_climatology
1295       minmoiavail_lastyear(:,:) = (minmoiavail_lastyear(:,:)*(tau_climatology-1)+ minmoiavail_thisyear(:,:))/tau_climatology
1296       maxgppweek_lastyear(:,:) =( maxgppweek_lastyear(:,:)*(tau_climatology-1)+ maxgppweek_thisyear(:,:))/tau_climatology
1297       !       maxmoiavail_lastyear(:,:) = maxmoiavail_thisyear(:,:)
1298       !       minmoiavail_lastyear(:,:) = minmoiavail_thisyear(:,:)
1299       !       maxgppweek_lastyear(:,:) = maxgppweek_thisyear(:,:)
1300       
1301       gdd0_lastyear(:) = gdd0_thisyear(:)
1302
1303       precip_lastyear(:) = precip_thisyear(:)
1304
1305       lm_lastyearmax(:,:) = lm_thisyearmax(:,:)
1306
1307       maxfpc_lastyear(:,:) = maxfpc_thisyear(:,:)
1308
1309       ! Calculate Tseason
1310       Tseason(:) = zero
1311       WHERE ( Tseason_length(:) .GT. min_sechiba )
1312          Tseason(:) = Tseason_tmp(:) / Tseason_length(:)
1313       ENDWHERE
1314
1315       !
1316       !! 21.2 Reset new values for the "this year" variables. \n
1317       !!      The maximum variables are set to zero and the minimum variable ::minmoiavail_thisyear
1318       !!      is set to ::large_value (set to be 1.E33 in the module ::stomate_constants).
1319       !
1320
1321       maxmoiavail_thisyear(:,:) = zero
1322       minmoiavail_thisyear(:,:) = large_value
1323
1324       maxgppweek_thisyear(:,:) = zero
1325
1326       gdd0_thisyear(:) = zero
1327
1328       precip_thisyear(:) = zero
1329
1330       lm_thisyearmax(:,:) = zero
1331
1332       maxfpc_thisyear(:,:) = zero
1333
1334       Tseason_tmp(:) = zero
1335       Tseason_length(:) =zero
1336       Tmin_spring_time(:,:)=zero
1337       onset_date(:,:)=zero
1338
1339       !
1340       ! 21.3 Special treatment for maxfpc. !??
1341       !! 21.3 Set the maximum fractional plant cover for non-natural vegetation
1342       !!      (i.e. agricultural C3 and C4 - PFT 12 and 13) vegetation for last year to be zero.
1343       !
1344
1345       !
1346       ! 21.3.1 Only take into account natural PFTs
1347       !
1348
1349       DO j = 2,nvm ! Loop over # PFTs
1350          IF ( .NOT. natural(j) ) THEN
1351             maxfpc_lastyear(:,j) = zero
1352          ENDIF
1353       ENDDO
1354
1355       ! 21.3.2 In Stomate, veget_cov is defined as a fraction of ground, not as a fraction
1356       !        of total ground. maxfpc_lastyear will be compared to veget_cov in lpj_light.
1357       !        Therefore, we have to transform maxfpc_lastyear.
1358
1359
1360       ! 21.3.3 The sum of the maxfpc_lastyear for natural PFT must not exceed fpc_crit (=.95).
1361       !        However, it can slightly exceed this value as not all PFTs reach their maximum
1362       !        fpc at the same time. Therefore, if sum(maxfpc_lastyear) for the natural PFTs
1363       !        exceeds fpc_crit, we scale the values of maxfpc_lastyear so that the sum is
1364       !        fpc_crit.
1365
1366!!$       ! calculate the sum of maxfpc_lastyear
1367!!$       sumfpc_nat(:) = zero
1368!!$       DO j = 2,nvm ! Loop over # PFTs
1369!!$          sumfpc_nat(:) = sumfpc_nat(:) + maxfpc_lastyear(:,j)
1370!!$       ENDDO
1371!!$
1372!!$       ! scale so that the new sum is fpc_crit
1373!!$       DO j = 2,nvm ! Loop over # PFTs
1374!!$          WHERE ( sumfpc_nat(:) .GT. fpc_crit )
1375!!$             maxfpc_lastyear(:,j) = maxfpc_lastyear(:,j) * (fpc_crit/sumfpc_nat(:))
1376!!$          ENDWHERE
1377!!$       ENDDO
1378
1379    ENDIF  ! LastTsYear
1380
1381    !
1382    !! 22. Diagnose herbivore activity (::herbivores), determined as probability for a leaf to be
1383    !!     eaten in a day (follows McNaughton et al., 1989). \n
1384    !!     The amount of herbivore activity is used in the modules ::lpj_establish 
1385    !!     and ::stomate_turnover.
1386    !
1387
1388    !
1389    !! 22.1 First calculate the mean long-term leaf NPP in grid box, mean residence
1390    !!      time (years) of green tissue to give the biomass available for herbivore consumption.
1391    !!      Each PFT is looped over, though the calculation is only made for
1392    !!      natural vegetation (PFTs 2-11).
1393    !
1394
1395    nlflong_nat(:,:) = zero
1396    weighttot(:,:) = zero
1397    green_age(:,:) = zero
1398    !
1399    DO j = 2,nvm ! Loop over # PFTs
1400       !
1401       IF ( natural(j) ) THEN
1402          !
1403          !! 22.1.1 Calculate the total weight of the leaves (::weighttot) as last year's leaf biomass
1404          !
1405          weighttot(:,j) = lm_lastyearmax(:,j)
1406         
1407          !
1408          !! 22.1.2 Calculate the mean long-term leaf NPP as the long-term NPP calculated in Section 12 of
1409          !!        this subroutine weighted by the leaf fraction (::leaf_frac), which is defined to be 0.33
1410          !!        at the beginning of this subroutine.
1411          !
1412          nlflong_nat(:,j) = npp_longterm(:,j) * leaf_frac_hvc
1413         
1414          !
1415          !! 22.1.3 Calculate the mean residence time of the green tissue (::green_age)
1416          !!        This is calculated as the sum of 6 months
1417          !!        for natural seasonal vegetation (i.e. PFTs 3, 6, 8-11), and 2 years for evergreen
1418          !!        (PFTs 2, 4, 5, 8), multiplied by last year's leaf biomass for each PFT, divided by the
1419          !!        total weight of the leaves for all PFTs.
1420          !         This is a crude approximation.  !!?? By whom?
1421          !!        The difference between seasonal and evergreen vegetation is determined by the parameter
1422          !!        ::pheno_model, which specifies the onset model of the PFT.
1423 
1424          !
1425          IF ( pheno_model(j) .EQ. 'none' ) THEN
1426             green_age(:,j) = green_age_ever * lm_lastyearmax(:,j)
1427          ELSE
1428             green_age(:,j) = green_age_dec * lm_lastyearmax(:,j)
1429          ENDIF
1430          !
1431       ENDIF
1432       !
1433    ENDDO
1434    !
1435    WHERE ( weighttot(:,:) .GT. min_sechiba )
1436       green_age(:,:) = green_age(:,:) / weighttot(:,:)
1437    ELSEWHERE
1438       green_age(:,:) = un
1439    ENDWHERE
1440
1441    !
1442    !! 22.2 McNaughton et al. (1989) give herbivore consumption as a function of mean, long-term leaf NPP.
1443    !!      as it gives an estimate of the edible biomass. The consumption of biomass by herbivores and the
1444    !!      resultant herbivore activity are calculated following the equations:
1445    !!      \latexonly
1446    !!      \input{season_consumption_eqn4.tex}
1447    !!      \endlatexonly
1448    !!      \n
1449    !!      and
1450    !!      \latexonly
1451    !!      \input{season_herbivore_eqn5.tex}
1452    !!      \endlatexonly
1453    !!      \n
1454    !       
1455
1456    DO j = 2,nvm ! Loop over # PFTs
1457       !
1458       IF ( natural(j) ) THEN
1459          !
1460          WHERE ( nlflong_nat(:,j) .GT. zero )
1461             consumption(:) = hvc1 * nlflong_nat(:,j) ** hvc2
1462             herbivores(:,j) = one_year * green_age(:,j) * nlflong_nat(:,j) / consumption(:)
1463          ELSEWHERE
1464             herbivores(:,j) = 100000.
1465          ENDWHERE
1466          !
1467       ELSE
1468          !
1469          herbivores(:,j) = 100000.
1470          !
1471       ENDIF
1472       !
1473    ENDDO
1474    herbivores(:,ibare_sechiba) = zero
1475
1476    IF (printlev>=4) WRITE(numout,*) 'Leaving season'
1477
1478  END SUBROUTINE season
1479
1480END MODULE stomate_season
Note: See TracBrowser for help on using the repository browser.