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