1 | ! Version 0: 26/06/2010 |
---|
2 | ! This is the module where we define the number of pfts and the values of the |
---|
3 | ! parameters |
---|
4 | ! author : D.Solyga |
---|
5 | |
---|
6 | MODULE pft_parameters |
---|
7 | |
---|
8 | USE constantes_mtc |
---|
9 | USE constantes |
---|
10 | USE ioipsl |
---|
11 | USE parallel |
---|
12 | USE defprec |
---|
13 | |
---|
14 | IMPLICIT NONE |
---|
15 | |
---|
16 | |
---|
17 | !------------------------- |
---|
18 | ! PFT global |
---|
19 | !------------------------ |
---|
20 | ! Number of vegetation types (see constantes_veg) |
---|
21 | INTEGER(i_std) :: nvm = 13 |
---|
22 | !- |
---|
23 | !Table of conversion : we associate one pft to one mtc |
---|
24 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pft_to_mtc |
---|
25 | !- |
---|
26 | ! Description of the PFT |
---|
27 | CHARACTER(len=34), ALLOCATABLE, SAVE, DIMENSION (:) :: PFT_name |
---|
28 | ! |
---|
29 | ! Flag l_first_define_pft |
---|
30 | LOGICAL, SAVE :: l_first_define_pft = .TRUE. |
---|
31 | |
---|
32 | !---------------------- |
---|
33 | ! Vegetation structure |
---|
34 | !---------------------- |
---|
35 | !- |
---|
36 | ! 1 .Sechiba |
---|
37 | !- |
---|
38 | ! Value for veget_ori for tests in 0-dim simulations |
---|
39 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: veget_ori_fixed_test_1 |
---|
40 | ! laimax for maximum lai see also type of lai interpolation |
---|
41 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: llaimax |
---|
42 | ! laimin for minimum lai see also type of lai interpolation |
---|
43 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: llaimin |
---|
44 | ! prescribed height of vegetation. |
---|
45 | ! Value for height_presc : one for each vegetation type |
---|
46 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: height_presc |
---|
47 | ! Type of behaviour of the LAI evolution algorithm |
---|
48 | ! for each vegetation type. |
---|
49 | ! Value of type_of_lai, one for each vegetation type : mean or interp |
---|
50 | CHARACTER(len=5),ALLOCATABLE, SAVE, DIMENSION (:) :: type_of_lai |
---|
51 | ! Is the vegetation type a tree ? |
---|
52 | LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_tree |
---|
53 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
54 | ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' |
---|
55 | ! is PFT deciduous ? |
---|
56 | LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_deciduous |
---|
57 | LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_evergreen |
---|
58 | LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_c3 |
---|
59 | ! used in diffuco !! Nathalie le 28 mars 2006 - sur proposition de Fred Hourdin, ajout |
---|
60 | !! d'un potentiometre pour regler la resistance de la vegetation |
---|
61 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: rveg_pft |
---|
62 | |
---|
63 | !- |
---|
64 | ! 2 .Stomate |
---|
65 | !- |
---|
66 | ! leaf type |
---|
67 | ! 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bared ground |
---|
68 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaf_tab |
---|
69 | ! specif leaf area (m**2/gC) |
---|
70 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: sla |
---|
71 | ! natural? |
---|
72 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:) :: natural |
---|
73 | |
---|
74 | !------------------------------- |
---|
75 | ! Evapotranspiration - sechiba |
---|
76 | !------------------------------- |
---|
77 | !- |
---|
78 | ! Structural resistance. |
---|
79 | ! Value for rstruct_const : one for each vegetation type |
---|
80 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: rstruct_const |
---|
81 | ! |
---|
82 | ! A vegetation dependent constant used in the calculation |
---|
83 | ! of the surface resistance. |
---|
84 | ! Value for kzero one for each vegetation type |
---|
85 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: kzero |
---|
86 | |
---|
87 | |
---|
88 | !------------------- |
---|
89 | ! Water - sechiba |
---|
90 | !------------------- |
---|
91 | !- |
---|
92 | ! Maximum field capacity for each of the vegetations (Temporary). |
---|
93 | ! Value of wmax_veg : max quantity of water : |
---|
94 | ! one for each vegetation type en Kg/M3 |
---|
95 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: wmax_veg |
---|
96 | ! Root profile description for the different vegetation types. |
---|
97 | ! These are the factor in the exponential which gets |
---|
98 | ! the root density as a function of depth |
---|
99 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: humcste |
---|
100 | ! used in hydrolc |
---|
101 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: throughfall_by_pft |
---|
102 | |
---|
103 | |
---|
104 | !------------------ |
---|
105 | ! Albedo - sechiba |
---|
106 | !------------------ |
---|
107 | !- |
---|
108 | ! Initial snow albedo value for each vegetation type |
---|
109 | ! as it will be used in condveg_snow |
---|
110 | ! Values are from the Thesis of S. Chalita (1992) |
---|
111 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_ini |
---|
112 | ! |
---|
113 | ! Decay rate of snow albedo value for each vegetation type |
---|
114 | ! as it will be used in condveg_snow |
---|
115 | ! Values are from the Thesis of S. Chalita (1992) |
---|
116 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_dec |
---|
117 | ! |
---|
118 | ! leaf albedo of vegetation type, visible albedo |
---|
119 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_vis |
---|
120 | ! leaf albedo of vegetation type, near infrared albedo |
---|
121 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_nir |
---|
122 | ! leaf albedo of vegetation type, VIS+NIR |
---|
123 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf |
---|
124 | |
---|
125 | |
---|
126 | !------------------------ |
---|
127 | ! Soil - vegetation |
---|
128 | !------------------------ |
---|
129 | ! |
---|
130 | ! Table which contains the correlation between the soil types |
---|
131 | ! and vegetation type. Two modes exist : |
---|
132 | ! 1) pref_soil_veg = 0 then we have an equidistribution |
---|
133 | ! of vegetation on soil types |
---|
134 | ! 2) Else for each pft the prefered soil type is given : |
---|
135 | ! 1=sand, 2=loan, 3=clay |
---|
136 | ! The variable is initialized in slowproc. |
---|
137 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: pref_soil_veg |
---|
138 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_sand |
---|
139 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_loan |
---|
140 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_clay |
---|
141 | |
---|
142 | !---------------- |
---|
143 | ! Photosynthesis |
---|
144 | !---------------- |
---|
145 | !- |
---|
146 | ! 1 .CO2 |
---|
147 | !- |
---|
148 | ! flag for C4 vegetation types |
---|
149 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:) :: is_c4 |
---|
150 | ! Slope of the gs/A relation (Ball & al.) |
---|
151 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: gsslope |
---|
152 | ! intercept of the gs/A relation (Ball & al.) |
---|
153 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: gsoffset |
---|
154 | ! values used for vcmax when STOMATE is not activated |
---|
155 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: vcmax_fix |
---|
156 | ! values used for vjmax when STOMATE is not activated |
---|
157 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: vjmax_fix |
---|
158 | ! values used for photosynthesis tmin when STOMATE is not activated |
---|
159 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: co2_tmin_fix |
---|
160 | ! values used for photosynthesis topt when STOMATE is not activated |
---|
161 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: co2_topt_fix |
---|
162 | ! values used for photosynthesis tmax when STOMATE is not activated |
---|
163 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: co2_tmax_fix |
---|
164 | !- |
---|
165 | ! 2 .Stomate |
---|
166 | !- |
---|
167 | ! extinction coefficient of the Monsi&Seaki relationship (1953) |
---|
168 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ext_coeff ! = ext_coef in sechiba |
---|
169 | ! Maximum rate of carboxylation |
---|
170 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: vcmax_opt |
---|
171 | ! Maximum rate of RUbp regeneration |
---|
172 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: vjmax_opt |
---|
173 | ! minimum photosynthesis temperature, |
---|
174 | ! constant a of ax^2+bx+c (deg C),tabulated |
---|
175 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_min_a |
---|
176 | ! minimum photosynthesis temperature, |
---|
177 | ! constant b of ax^2+bx+c (deg C),tabulated |
---|
178 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_min_b |
---|
179 | ! minimum photosynthesis temperature, |
---|
180 | ! constant c of ax^2+bx+c (deg C),tabulated |
---|
181 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_min_c |
---|
182 | ! optimum photosynthesis temperature, |
---|
183 | ! constant a of ax^2+bx+c (deg C),tabulated |
---|
184 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_opt_a |
---|
185 | ! optimum photosynthesis temperature, |
---|
186 | ! constant b of ax^2+bx+c (deg C),tabulated |
---|
187 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_opt_b |
---|
188 | ! optimum photosynthesis temperature, |
---|
189 | ! constant c of ax^2+bx+c (deg C),tabulated |
---|
190 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_opt_c |
---|
191 | ! maximum photosynthesis temperature, |
---|
192 | ! constant a of ax^2+bx+c (deg C), tabulated |
---|
193 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_max_a |
---|
194 | ! maximum photosynthesis temperature, |
---|
195 | ! constant b of ax^2+bx+c (deg C), tabulated |
---|
196 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_max_b |
---|
197 | ! maximum photosynthesis temperature, |
---|
198 | ! constant c of ax^2+bx+c (deg C), tabulated |
---|
199 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_max_c |
---|
200 | |
---|
201 | |
---|
202 | !----------------------- |
---|
203 | ! Respiration - stomate |
---|
204 | !----------------------- |
---|
205 | ! |
---|
206 | !-! slope of maintenance respiration coefficient (1/K, 1/K^2, 1/K^3), used in the code |
---|
207 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: maint_resp_slope |
---|
208 | ! slope of maintenance respiration coefficient (1/K), |
---|
209 | ! constant c of aT^2+bT+c , tabulated |
---|
210 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: maint_resp_slope_c |
---|
211 | ! slope of maintenance respiration coefficient (1/K), |
---|
212 | ! constant b of aT^2+bT+c , tabulated |
---|
213 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: maint_resp_slope_b |
---|
214 | ! slope of maintenance respiration coefficient (1/K), |
---|
215 | ! constant a of aT^2+bT+c , tabulated |
---|
216 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: maint_resp_slope_a |
---|
217 | !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, used in the code |
---|
218 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: coeff_maint_zero |
---|
219 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
220 | ! for leaves, tabulated |
---|
221 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_leaf |
---|
222 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
223 | ! for sapwood above, tabulated |
---|
224 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_sapabove |
---|
225 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
226 | ! for sapwood below, tabulated |
---|
227 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_sapbelow |
---|
228 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
229 | ! for heartwood above, tabulated |
---|
230 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_heartabove |
---|
231 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
232 | ! for heartwood below, tabulated |
---|
233 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_heartbelow |
---|
234 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
235 | ! for roots, tabulated |
---|
236 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_root |
---|
237 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
238 | ! for fruits, tabulated |
---|
239 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_fruit |
---|
240 | ! maintenance respiration coefficient (g/g/day) at 0 deg C, |
---|
241 | ! for carbohydrate reserve, tabulated |
---|
242 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::cm_zero_carbres |
---|
243 | |
---|
244 | |
---|
245 | !---------------- |
---|
246 | ! Fire - stomate |
---|
247 | !---------------- |
---|
248 | ! |
---|
249 | ! flamability: critical fraction of water holding capacity |
---|
250 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: flam |
---|
251 | ! fire resistance |
---|
252 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: resist |
---|
253 | |
---|
254 | |
---|
255 | !--------------- |
---|
256 | ! Flux - LUC |
---|
257 | !--------------- |
---|
258 | ! |
---|
259 | ! Coeff of biomass export for the year |
---|
260 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: coeff_lcchange_1 |
---|
261 | ! Coeff of biomass export for the decade |
---|
262 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: coeff_lcchange_10 |
---|
263 | ! Coeff of biomass export for the century |
---|
264 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: coeff_lcchange_100 |
---|
265 | |
---|
266 | |
---|
267 | !----------- |
---|
268 | ! Phenology |
---|
269 | !----------- |
---|
270 | !- |
---|
271 | ! 1 .Stomate |
---|
272 | !- |
---|
273 | ! maximum LAI, PFT-specific |
---|
274 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: lai_max |
---|
275 | ! which phenology model is used? (tabulated) |
---|
276 | CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_model |
---|
277 | ! type of phenology |
---|
278 | ! 0=bared ground 1=evergreen, 2=summergreen, 3=raingreen, 4=perennial |
---|
279 | ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols |
---|
280 | INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_type |
---|
281 | !- |
---|
282 | ! 2. Leaf Onset |
---|
283 | !- |
---|
284 | !-! critical gdd,tabulated (C), used in the code |
---|
285 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: pheno_gdd_crit |
---|
286 | ! critical gdd,tabulated (C), constant c of aT^2+bT+c |
---|
287 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_gdd_crit_c |
---|
288 | ! critical gdd,tabulated (C), constant b of aT^2+bT+c |
---|
289 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_gdd_crit_b |
---|
290 | ! critical gdd,tabulated (C), constant a of aT^2+bT+c |
---|
291 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_gdd_crit_a |
---|
292 | ! critical ngd,tabulated. Threshold -5 degrees |
---|
293 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ngd_crit |
---|
294 | ! critical temperature for the ncd vs. gdd function in phenology |
---|
295 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ncdgdd_temp |
---|
296 | ! critical humidity (relative to min/max) for phenology |
---|
297 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: hum_frac |
---|
298 | ! minimum duration of dormance (d) for phenology |
---|
299 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: lowgpp_time |
---|
300 | ! minimum time elapsed since moisture minimum (d) |
---|
301 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: hum_min_time |
---|
302 | ! sapwood -> heartwood conversion time (d) |
---|
303 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tau_sap |
---|
304 | ! fruit lifetime (d) |
---|
305 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tau_fruit |
---|
306 | ! fraction of primary leaf and root allocation put into reserve |
---|
307 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ecureuil |
---|
308 | ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
309 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alloc_min |
---|
310 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alloc_max |
---|
311 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: demi_alloc |
---|
312 | !>> DS new for merge in the trunk |
---|
313 | ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla |
---|
314 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaflife_tab |
---|
315 | !- |
---|
316 | ! 3. Senescence |
---|
317 | !- |
---|
318 | ! length of death of leaves,tabulated (d) |
---|
319 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaffall |
---|
320 | ! critical leaf age,tabulated (d) |
---|
321 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leafagecrit |
---|
322 | ! type of senescence,tabulated |
---|
323 | ! List of avaible types of senescence : |
---|
324 | ! 'cold ', 'dry ', 'mixed ', 'none ' |
---|
325 | CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_type |
---|
326 | ! critical relative moisture availability for senescence |
---|
327 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_hum |
---|
328 | ! relative moisture availability above which |
---|
329 | ! there is no humidity-related senescence |
---|
330 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: nosenescence_hum |
---|
331 | ! maximum turnover time for grasse |
---|
332 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: max_turnover_time |
---|
333 | ! minimum turnover time for grasse |
---|
334 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: min_turnover_time |
---|
335 | ! minimum leaf age to allow senescence g |
---|
336 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: min_leaf_age_for_senescence |
---|
337 | !-! critical temperature for senescence (C), used in the code |
---|
338 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: senescence_temp |
---|
339 | ! critical temperature for senescence (C), |
---|
340 | ! constant c of aT^2+bT+c , tabulated |
---|
341 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_temp_c |
---|
342 | ! critical temperature for senescence (C), |
---|
343 | ! constant b of aT^2+bT+c , tabulated |
---|
344 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_temp_b |
---|
345 | ! critical temperature for senescence (C), |
---|
346 | ! constant a of aT^2+bT+c , tabulated |
---|
347 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_temp_a |
---|
348 | |
---|
349 | |
---|
350 | !----------- |
---|
351 | ! DGVM |
---|
352 | !----------- |
---|
353 | !- |
---|
354 | ! residence time (y) of trees |
---|
355 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: residence_time |
---|
356 | ! critical tmin, tabulated (C) |
---|
357 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tmin_crit |
---|
358 | ! critical tcm, tabulated (C) |
---|
359 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tcm_crit |
---|
360 | |
---|
361 | |
---|
362 | !-------------------------------------------- |
---|
363 | ! Internal parameters used in stomate_data |
---|
364 | !------------------------------------------- |
---|
365 | ! |
---|
366 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: lai_initmin |
---|
367 | ! is pft a tree |
---|
368 | LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:) :: tree |
---|
369 | ! sapling biomass (gC/ind) |
---|
370 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: bm_sapl |
---|
371 | ! migration speed (m/year) |
---|
372 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: migrate |
---|
373 | ! maximum stem diameter from which on crown area no longer increases (m)m |
---|
374 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: maxdia |
---|
375 | ! crown of tree when sapling (m**2) |
---|
376 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cn_sapl |
---|
377 | ! time constant for leaf age discretisation (d) |
---|
378 | REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaf_timecst |
---|
379 | |
---|
380 | |
---|
381 | |
---|
382 | CONTAINS |
---|
383 | ! |
---|
384 | SUBROUTINE pft_parameters_main |
---|
385 | |
---|
386 | IMPLICIT NONE |
---|
387 | |
---|
388 | ! Local |
---|
389 | INTEGER(i_std) :: i |
---|
390 | |
---|
391 | !---------------------- |
---|
392 | ! PFT global |
---|
393 | !---------------------- |
---|
394 | |
---|
395 | IF(l_first_define_pft) THEN |
---|
396 | |
---|
397 | ! 1. First time step |
---|
398 | IF(long_print) THEN |
---|
399 | WRITE(numout,*) 'l_first_define_pft :we read the parameters from the def files' |
---|
400 | ENDIF |
---|
401 | |
---|
402 | ! 2. Memory allocation |
---|
403 | ! Allocation of memory for the pfts-parameters |
---|
404 | CALL pft_parameters_alloc |
---|
405 | |
---|
406 | ! 3. Correspondance table |
---|
407 | |
---|
408 | ! 3.1 Initialisation of the correspondance table |
---|
409 | ! Initialisation of the correspondance table |
---|
410 | pft_to_mtc (:) = undef_int |
---|
411 | |
---|
412 | ! 3.2 Reading of the conrrespondance table in the .def file |
---|
413 | ! |
---|
414 | !Config Key = PFT_TO_MTC |
---|
415 | !Config Desc = correspondance array linking a PFT to MTC |
---|
416 | !Config if = ANYTIME |
---|
417 | !Config Def = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 |
---|
418 | !Config Help = |
---|
419 | !Config Units = NONE |
---|
420 | CALL getin_p('PFT_TO_MTC',pft_to_mtc) |
---|
421 | |
---|
422 | ! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array |
---|
423 | ! If the configuration is wrong, send a error message to the user. |
---|
424 | IF(nvm .EQ. 13 ) THEN |
---|
425 | IF(pft_to_mtc(1) .EQ. undef_int) THEN |
---|
426 | WRITE(numout,*) 'Note to the user : we will use ORCHIDEE to its standard configuration' |
---|
427 | pft_to_mtc(:) = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /) |
---|
428 | ENDIF |
---|
429 | ELSE |
---|
430 | IF(pft_to_mtc(1) .EQ. undef_int) THEN |
---|
431 | WRITE(numout,*)' The array PFT_TO_MTC is empty : we stop' |
---|
432 | ENDIF |
---|
433 | ENDIF |
---|
434 | |
---|
435 | ! 3.4 Some error messages |
---|
436 | |
---|
437 | ! 3.4.1 What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)? |
---|
438 | DO i = 1, nvm |
---|
439 | IF(pft_to_mtc(i) .GT. nvmc) THEN |
---|
440 | WRITE(numout,*) "the MTC you chose doesn't exist" |
---|
441 | STOP 'we stop reading pft_to_mtc' |
---|
442 | ENDIF |
---|
443 | ENDDO |
---|
444 | |
---|
445 | |
---|
446 | ! 3.4.2 Check if pft_to_mtc(1) = 1 |
---|
447 | IF(pft_to_mtc(1) .NE. 1) THEN |
---|
448 | WRITE(numout,*) 'the first pft has to be the bare soil' |
---|
449 | STOP 'we stop reading next values of pft_to_mtc' |
---|
450 | ELSE |
---|
451 | DO i = 2,nvm |
---|
452 | IF(pft_to_mtc(i) .EQ.1) THEN |
---|
453 | WRITE(numout,*) 'only pft_to_mtc(1) has to be the bare soil' |
---|
454 | STOP 'we stop reading pft_to_mtc' |
---|
455 | ENDIF |
---|
456 | ENDDO |
---|
457 | ENDIF |
---|
458 | |
---|
459 | |
---|
460 | ! 4.Initialisation of the pfts-parameters |
---|
461 | CALL pft_parameters_init |
---|
462 | |
---|
463 | ! 5. Useful data |
---|
464 | |
---|
465 | ! 5.1 Read the name of the PFTs given by the user |
---|
466 | ! |
---|
467 | !Config Key = PFT_NAME |
---|
468 | !Config Desc = Name of a PFT |
---|
469 | !Config if = ANYTIME |
---|
470 | !Config Def = bared ground, tropical broad-leaved evergreen, tropical broad-leaved raingreen, temperate needleleaf evergreen,temperate broad-leaved evergreen |
---|
471 | ! temperate broad-leaved summergreen, boreal needleleaf evergreen, boreal broad-leaved summergreen, boreal needleleaf summergreen, |
---|
472 | ! C3 grass, C4 grass, C3 agriculture, C4 agriculture |
---|
473 | !Config Help = the user can name the new PFTs he/she introducing for new species |
---|
474 | !Config Units = NONE |
---|
475 | CALL getin('PFT_NAME',pft_name) |
---|
476 | |
---|
477 | ! 5.2 A useful message to the user: correspondance between the number of the pft |
---|
478 | ! and the name of the associated mtc |
---|
479 | DO i = 1,nvm |
---|
480 | WRITE(numout,*) 'the PFT',i, 'called ', PFT_name(i),'corresponds to the MTC : ',MTC_name(pft_to_mtc(i)) |
---|
481 | ENDDO |
---|
482 | |
---|
483 | ! 6. Initialisation of 2D arrays used in the code |
---|
484 | |
---|
485 | !-alb_leaf |
---|
486 | alb_leaf(:) = zero |
---|
487 | |
---|
488 | !- pref_soil_veg |
---|
489 | pref_soil_veg(:,:) = zero_int |
---|
490 | |
---|
491 | !- pheno_gdd_crit |
---|
492 | pheno_gdd_crit(:,:) = zero |
---|
493 | ! |
---|
494 | !- senescence_temp |
---|
495 | senescence_temp(:,:) = zero |
---|
496 | ! |
---|
497 | !- maint_resp_slope |
---|
498 | maint_resp_slope(:,:) = zero |
---|
499 | ! |
---|
500 | !-coeff_maint_zero |
---|
501 | coeff_maint_zero(:,:) = zero |
---|
502 | |
---|
503 | ! 7. End message |
---|
504 | IF(long_print) THEN |
---|
505 | WRITE(numout,*) 'pft_parameters_done' |
---|
506 | ENDIF |
---|
507 | |
---|
508 | ELSE |
---|
509 | |
---|
510 | l_first_define_pft = .FALSE. |
---|
511 | |
---|
512 | RETURN |
---|
513 | |
---|
514 | ENDIF |
---|
515 | |
---|
516 | END SUBROUTINE pft_parameters_main |
---|
517 | ! |
---|
518 | != |
---|
519 | ! |
---|
520 | SUBROUTINE pft_parameters_init |
---|
521 | |
---|
522 | IMPLICIT NONE |
---|
523 | |
---|
524 | !------------ |
---|
525 | ! local |
---|
526 | INTEGER(i_std) :: j,k |
---|
527 | !------------ |
---|
528 | |
---|
529 | ! |
---|
530 | ! 1. Correspondance between the PFTs values and thes MTCs values |
---|
531 | ! |
---|
532 | |
---|
533 | DO j= 1, nvm |
---|
534 | |
---|
535 | PFT_name(j) = MTC_name(pft_to_mtc(j)) |
---|
536 | |
---|
537 | !- |
---|
538 | ! Vegetation structure |
---|
539 | !- |
---|
540 | ! |
---|
541 | ! 1 .Sechiba |
---|
542 | ! |
---|
543 | veget_ori_fixed_test_1(j) = veget_ori_fixed_mtc(pft_to_mtc(j)) |
---|
544 | llaimax(j) = llaimax_mtc(pft_to_mtc(j)) |
---|
545 | llaimin(j) = llaimin_mtc(pft_to_mtc(j)) |
---|
546 | height_presc(j) = height_presc_mtc(pft_to_mtc(j)) |
---|
547 | type_of_lai(j) = type_of_lai_mtc(pft_to_mtc(j)) |
---|
548 | is_tree(j) = is_tree_mtc(pft_to_mtc(j)) |
---|
549 | rveg_pft(j) = rveg_mtc(pft_to_mtc(j)) |
---|
550 | |
---|
551 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
552 | ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' |
---|
553 | is_deciduous(j) = is_deciduous_mtc(pft_to_mtc(j)) |
---|
554 | is_evergreen(j) = is_evergreen_mtc(pft_to_mtc(j)) |
---|
555 | is_c3(j) = is_c3(pft_to_mtc(j)) |
---|
556 | |
---|
557 | ! |
---|
558 | ! 2 .Stomate |
---|
559 | ! |
---|
560 | leaf_tab(j) = leaf_tab_mtc(pft_to_mtc(j)) |
---|
561 | sla(j) = sla_mtc(pft_to_mtc(j)) |
---|
562 | natural(j) = natural_mtc(pft_to_mtc(j)) |
---|
563 | |
---|
564 | !- |
---|
565 | ! Evapotranspiration - sechiba |
---|
566 | !- |
---|
567 | rstruct_const(j) = rstruct_const_mtc(pft_to_mtc(j)) |
---|
568 | kzero(j) = kzero_mtc(pft_to_mtc(j)) |
---|
569 | !- |
---|
570 | ! Water - sechiba |
---|
571 | !- |
---|
572 | wmax_veg(j) = wmax_veg_mtc(pft_to_mtc(j)) |
---|
573 | humcste(j) = humcste_mtc(pft_to_mtc(j)) |
---|
574 | throughfall_by_pft(j) = throughfall_by_mtc(pft_to_mtc(j)) |
---|
575 | !- |
---|
576 | ! Albedo - sechiba |
---|
577 | !- |
---|
578 | snowa_ini(j) = snowa_ini_mtc(pft_to_mtc(j)) |
---|
579 | snowa_dec(j) = snowa_dec_mtc(pft_to_mtc(j)) |
---|
580 | alb_leaf_vis(j) = alb_leaf_vis_mtc(pft_to_mtc(j)) |
---|
581 | alb_leaf_nir(j) = alb_leaf_nir_mtc(pft_to_mtc(j)) |
---|
582 | !- |
---|
583 | ! Soil - vegetation |
---|
584 | !- |
---|
585 | pref_soil_veg_sand(j) = pref_soil_veg_sand_mtc(pft_to_mtc(j)) |
---|
586 | pref_soil_veg_loan(j) = pref_soil_veg_loan_mtc(pft_to_mtc(j)) |
---|
587 | pref_soil_veg_clay(j) = pref_soil_veg_clay_mtc(pft_to_mtc(j)) |
---|
588 | |
---|
589 | !- |
---|
590 | ! Photosynthesis |
---|
591 | !- |
---|
592 | ! |
---|
593 | ! 1 .CO2 |
---|
594 | ! |
---|
595 | is_c4(j) = is_c4_mtc(pft_to_mtc(j)) |
---|
596 | gsslope(j) = gsslope_mtc(pft_to_mtc(j)) |
---|
597 | gsoffset(j) = gsoffset_mtc(pft_to_mtc(j)) |
---|
598 | vcmax_fix(j) = vcmax_fix_mtc(pft_to_mtc(j)) |
---|
599 | vjmax_fix(j) = vjmax_fix_mtc(pft_to_mtc(j)) |
---|
600 | co2_tmin_fix(j) = co2_tmin_fix_mtc(pft_to_mtc(j)) |
---|
601 | co2_topt_fix(j) = co2_topt_fix_mtc(pft_to_mtc(j)) |
---|
602 | co2_tmax_fix(j) = co2_tmax_fix_mtc(pft_to_mtc(j)) |
---|
603 | ! |
---|
604 | ! 2 .Stomate |
---|
605 | ! |
---|
606 | ext_coeff(j) = ext_coeff_mtc(pft_to_mtc(j)) |
---|
607 | vcmax_opt(j) = vcmax_opt_mtc(pft_to_mtc(j)) |
---|
608 | vjmax_opt(j) = vjmax_opt_mtc(pft_to_mtc(j)) |
---|
609 | tphoto_min_a(j) = tphoto_min_a_mtc(pft_to_mtc(j)) |
---|
610 | tphoto_min_b(j) = tphoto_min_b_mtc(pft_to_mtc(j)) |
---|
611 | tphoto_min_c(j) = tphoto_min_c_mtc(pft_to_mtc(j)) |
---|
612 | tphoto_opt_a(j) = tphoto_opt_a_mtc(pft_to_mtc(j)) |
---|
613 | tphoto_opt_b(j) = tphoto_opt_b_mtc(pft_to_mtc(j)) |
---|
614 | tphoto_opt_c(j) = tphoto_opt_c_mtc(pft_to_mtc(j)) |
---|
615 | tphoto_max_a(j) = tphoto_max_a_mtc(pft_to_mtc(j)) |
---|
616 | tphoto_max_b(j) = tphoto_max_b_mtc(pft_to_mtc(j)) |
---|
617 | tphoto_max_c(j) = tphoto_max_c_mtc(pft_to_mtc(j)) |
---|
618 | !- |
---|
619 | ! Respiration - stomate |
---|
620 | !- |
---|
621 | maint_resp_slope_c(j) = maint_resp_slope_c_mtc(pft_to_mtc(j)) |
---|
622 | maint_resp_slope_b(j) = maint_resp_slope_b_mtc(pft_to_mtc(j)) |
---|
623 | maint_resp_slope_a(j) = maint_resp_slope_a_mtc(pft_to_mtc(j)) |
---|
624 | cm_zero_leaf(j)= cm_zero_leaf_mtc(pft_to_mtc(j)) |
---|
625 | cm_zero_sapabove(j) = cm_zero_sapabove_mtc(pft_to_mtc(j)) |
---|
626 | cm_zero_sapbelow(j) = cm_zero_sapbelow_mtc(pft_to_mtc(j)) |
---|
627 | cm_zero_heartabove(j) = cm_zero_heartabove_mtc(pft_to_mtc(j)) |
---|
628 | cm_zero_heartbelow(j) = cm_zero_heartbelow_mtc(pft_to_mtc(j)) |
---|
629 | cm_zero_root(j) = cm_zero_root_mtc(pft_to_mtc(j)) |
---|
630 | cm_zero_fruit(j) = cm_zero_fruit_mtc(pft_to_mtc(j)) |
---|
631 | cm_zero_carbres(j) = cm_zero_carbres_mtc(pft_to_mtc(j)) |
---|
632 | !- |
---|
633 | ! Fire - stomate |
---|
634 | !- |
---|
635 | flam(j) = flam_mtc(pft_to_mtc(j)) |
---|
636 | resist(j) = resist_mtc(pft_to_mtc(j)) |
---|
637 | !- |
---|
638 | ! Flux - LUC |
---|
639 | !- |
---|
640 | coeff_lcchange_1(j) = coeff_lcchange_1_mtc(pft_to_mtc(j)) |
---|
641 | coeff_lcchange_10(j) = coeff_lcchange_10_mtc(pft_to_mtc(j)) |
---|
642 | coeff_lcchange_100(j) = coeff_lcchange_100_mtc(pft_to_mtc(j)) |
---|
643 | !- |
---|
644 | ! Phenology |
---|
645 | !- |
---|
646 | ! |
---|
647 | ! 1 .Stomate |
---|
648 | ! |
---|
649 | lai_max(j) = lai_max_mtc(pft_to_mtc(j)) |
---|
650 | pheno_model(j) = pheno_model_mtc(pft_to_mtc(j)) |
---|
651 | pheno_type(j) = pheno_type_mtc(pft_to_mtc(j)) |
---|
652 | ! |
---|
653 | ! 2. Leaf Onset |
---|
654 | ! |
---|
655 | pheno_gdd_crit_c(j) = pheno_gdd_crit_c_mtc(pft_to_mtc(j)) |
---|
656 | pheno_gdd_crit_b(j) = pheno_gdd_crit_b_mtc(pft_to_mtc(j)) |
---|
657 | pheno_gdd_crit_a(j) = pheno_gdd_crit_a_mtc(pft_to_mtc(j)) |
---|
658 | ngd_crit(j) = ngd_crit_mtc(pft_to_mtc(j)) |
---|
659 | ncdgdd_temp(j) = ncdgdd_temp_mtc(pft_to_mtc(j)) |
---|
660 | hum_frac(j) = hum_frac_mtc(pft_to_mtc(j)) |
---|
661 | lowgpp_time(j) = lowgpp_time_mtc(pft_to_mtc(j)) |
---|
662 | hum_min_time(j) = hum_min_time_mtc(pft_to_mtc(j)) |
---|
663 | tau_sap(j) = tau_sap_mtc(pft_to_mtc(j)) |
---|
664 | tau_fruit(j) = tau_fruit_mtc(pft_to_mtc(j)) |
---|
665 | ecureuil(j) = ecureuil_mtc(pft_to_mtc(j)) |
---|
666 | alloc_min(j) = alloc_min_mtc(pft_to_mtc(j)) |
---|
667 | alloc_max(j) = alloc_max_mtc(pft_to_mtc(j)) |
---|
668 | demi_alloc(j) = demi_alloc_mtc(pft_to_mtc(j)) |
---|
669 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
670 | leaflife_tab(j) = leaflife_mtc(pft_to_mtc(j)) |
---|
671 | ! |
---|
672 | ! 3. Senescence |
---|
673 | ! |
---|
674 | leaffall(j) = leaffall_mtc(pft_to_mtc(j)) |
---|
675 | leafagecrit(j) = leafagecrit_mtc(pft_to_mtc(j)) |
---|
676 | senescence_type(j) = senescence_type_mtc(pft_to_mtc(j)) |
---|
677 | senescence_hum(j) = senescence_hum_mtc(pft_to_mtc(j)) |
---|
678 | nosenescence_hum(j) = nosenescence_hum_mtc(pft_to_mtc(j)) |
---|
679 | max_turnover_time(j) = max_turnover_time_mtc(pft_to_mtc(j)) |
---|
680 | min_turnover_time(j) = min_turnover_time_mtc(pft_to_mtc(j)) |
---|
681 | min_leaf_age_for_senescence(j) = min_leaf_age_for_senescence_mtc(pft_to_mtc(j)) |
---|
682 | senescence_temp_c(j) = senescence_temp_c_mtc(pft_to_mtc(j)) |
---|
683 | senescence_temp_b(j) = senescence_temp_b_mtc(pft_to_mtc(j)) |
---|
684 | senescence_temp_a(j) = senescence_temp_a_mtc(pft_to_mtc(j)) |
---|
685 | !- |
---|
686 | ! DGVM |
---|
687 | residence_time(j) = residence_time_mtc(pft_to_mtc(j)) |
---|
688 | tmin_crit(j) = tmin_crit_mtc(pft_to_mtc(j)) |
---|
689 | tcm_crit(j) = tcm_crit_mtc(pft_to_mtc(j)) |
---|
690 | |
---|
691 | ENDDO ! end loop over nvm |
---|
692 | |
---|
693 | END SUBROUTINE pft_parameters_init |
---|
694 | ! |
---|
695 | != |
---|
696 | ! |
---|
697 | SUBROUTINE pft_parameters_alloc |
---|
698 | |
---|
699 | IMPLICIT NONE |
---|
700 | !------------------ |
---|
701 | ! local |
---|
702 | LOGICAL :: l_error |
---|
703 | INTEGER :: ier |
---|
704 | !----------------- |
---|
705 | |
---|
706 | l_error = .FALSE. |
---|
707 | ALLOCATE(pft_to_mtc(nvm),stat=ier) |
---|
708 | l_error = l_error .OR. (ier .NE. 0) |
---|
709 | ALLOCATE(PFT_name(nvm),stat=ier) |
---|
710 | l_error = l_error .OR. (ier .NE. 0) |
---|
711 | !- |
---|
712 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
713 | ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' |
---|
714 | ALLOCATE(is_deciduous(nvm),stat=ier) |
---|
715 | l_error = l_error .OR. (ier .NE. 0) |
---|
716 | ALLOCATE(is_evergreen(nvm),stat=ier) |
---|
717 | l_error = l_error .OR. (ier .NE. 0) |
---|
718 | ALLOCATE(is_c3(nvm),stat=ier) |
---|
719 | l_error = l_error .OR. (ier .NE. 0) |
---|
720 | ALLOCATE(leaflife_tab(nvm),stat=ier) |
---|
721 | l_error = l_error .OR. (ier .NE. 0) |
---|
722 | ! >> END |
---|
723 | |
---|
724 | ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier) |
---|
725 | l_error = l_error .OR. (ier .NE. 0) |
---|
726 | ALLOCATE(llaimax(nvm),stat=ier) |
---|
727 | l_error = l_error .OR. (ier .NE. 0) |
---|
728 | ALLOCATE(llaimin(nvm),stat=ier) |
---|
729 | l_error = l_error .OR. (ier .NE. 0) |
---|
730 | ALLOCATE(height_presc(nvm),stat=ier) |
---|
731 | l_error = l_error .OR. (ier .NE. 0) |
---|
732 | ALLOCATE(type_of_lai(nvm),stat=ier) |
---|
733 | l_error = l_error .OR. (ier .NE. 0) |
---|
734 | ALLOCATE(is_tree(nvm),stat=ier) |
---|
735 | l_error = l_error .OR. (ier .NE. 0) |
---|
736 | !- |
---|
737 | ALLOCATE(leaf_tab(nvm),stat=ier) |
---|
738 | l_error = l_error .OR. (ier .NE. 0) |
---|
739 | ALLOCATE(sla(nvm),stat=ier) |
---|
740 | l_error = l_error .OR. (ier .NE. 0) |
---|
741 | ALLOCATE(natural(nvm),stat=ier) |
---|
742 | l_error = l_error .OR. (ier .NE. 0) |
---|
743 | !- |
---|
744 | ALLOCATE(is_c4(nvm),stat=ier) |
---|
745 | l_error = l_error .OR. (ier .NE. 0) |
---|
746 | ALLOCATE(gsslope(nvm),stat=ier) |
---|
747 | l_error = l_error .OR. (ier .NE. 0) |
---|
748 | ALLOCATE(gsoffset(nvm),stat=ier) |
---|
749 | l_error = l_error .OR. (ier .NE. 0) |
---|
750 | ALLOCATE(vcmax_fix(nvm),stat=ier) |
---|
751 | l_error = l_error .OR. (ier .NE. 0) |
---|
752 | ALLOCATE(vjmax_fix(nvm),stat=ier) |
---|
753 | l_error = l_error .OR. (ier .NE. 0) |
---|
754 | ALLOCATE(co2_tmin_fix(nvm),stat=ier) |
---|
755 | l_error = l_error .OR. (ier .NE. 0) |
---|
756 | ALLOCATE(co2_topt_fix(nvm),stat=ier) |
---|
757 | l_error = l_error .OR. (ier .NE. 0) |
---|
758 | ALLOCATE(co2_tmax_fix(nvm),stat=ier) |
---|
759 | l_error = l_error .OR. (ier .NE. 0) |
---|
760 | !- |
---|
761 | ALLOCATE(ext_coeff(nvm),stat=ier) |
---|
762 | l_error = l_error .OR. (ier .NE. 0) |
---|
763 | ALLOCATE(vcmax_opt(nvm),stat=ier) |
---|
764 | l_error = l_error .OR. (ier .NE. 0) |
---|
765 | ALLOCATE(vjmax_opt(nvm),stat=ier) |
---|
766 | l_error = l_error .OR. (ier .NE. 0) |
---|
767 | ALLOCATE(tphoto_min_a(nvm),stat=ier) |
---|
768 | l_error = l_error .OR. (ier .NE. 0) |
---|
769 | ALLOCATE(tphoto_min_b(nvm),stat=ier) |
---|
770 | l_error = l_error .OR. (ier .NE. 0) |
---|
771 | ALLOCATE(tphoto_min_c(nvm),stat=ier) |
---|
772 | l_error = l_error .OR. (ier .NE. 0) |
---|
773 | ALLOCATE(tphoto_opt_a(nvm),stat=ier) |
---|
774 | l_error = l_error .OR. (ier .NE. 0) |
---|
775 | ALLOCATE(tphoto_opt_b(nvm),stat=ier) |
---|
776 | l_error = l_error .OR. (ier .NE. 0) |
---|
777 | ALLOCATE(tphoto_opt_c(nvm),stat=ier) |
---|
778 | l_error = l_error .OR. (ier .NE. 0) |
---|
779 | ALLOCATE(tphoto_max_a(nvm),stat=ier) |
---|
780 | l_error = l_error .OR. (ier .NE. 0) |
---|
781 | ALLOCATE(tphoto_max_b(nvm),stat=ier) |
---|
782 | l_error = l_error .OR. (ier .NE. 0) |
---|
783 | ALLOCATE(tphoto_max_c(nvm),stat=ier) |
---|
784 | l_error = l_error .OR. (ier .NE. 0) |
---|
785 | !- |
---|
786 | ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier) |
---|
787 | l_error = l_error .OR. (ier .NE. 0) |
---|
788 | ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier) |
---|
789 | l_error = l_error .OR. (ier .NE. 0) |
---|
790 | ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier) |
---|
791 | l_error = l_error .OR. (ier .NE. 0) |
---|
792 | ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier) |
---|
793 | l_error = l_error .OR. (ier .NE. 0) |
---|
794 | ALLOCATE(ngd_crit(nvm),stat=ier) |
---|
795 | l_error = l_error .OR. (ier .NE. 0) |
---|
796 | ALLOCATE(ncdgdd_temp(nvm),stat=ier) |
---|
797 | l_error = l_error .OR. (ier .NE. 0) |
---|
798 | ALLOCATE(hum_frac(nvm),stat=ier) |
---|
799 | l_error = l_error .OR. (ier .NE. 0) |
---|
800 | ALLOCATE(lowgpp_time(nvm),stat=ier) |
---|
801 | l_error = l_error .OR. (ier .NE. 0) |
---|
802 | ALLOCATE(hum_min_time(nvm),stat=ier) |
---|
803 | l_error = l_error .OR. (ier .NE. 0) |
---|
804 | ALLOCATE(tau_sap(nvm),stat=ier) |
---|
805 | l_error = l_error .OR. (ier .NE. 0) |
---|
806 | ALLOCATE(tau_fruit(nvm),stat=ier) |
---|
807 | l_error = l_error .OR. (ier .NE. 0) |
---|
808 | ALLOCATE(ecureuil(nvm),stat=ier) |
---|
809 | l_error = l_error .OR. (ier .NE. 0) |
---|
810 | ALLOCATE(alloc_min(nvm),stat=ier) |
---|
811 | l_error = l_error .OR. (ier .NE. 0) |
---|
812 | ALLOCATE(alloc_max(nvm),stat=ier) |
---|
813 | l_error = l_error .OR. (ier .NE. 0) |
---|
814 | ALLOCATE(demi_alloc(nvm),stat=ier) |
---|
815 | l_error = l_error .OR. (ier .NE. 0) |
---|
816 | !- |
---|
817 | ALLOCATE(maint_resp_slope(nvm,3),stat=ier) |
---|
818 | l_error = l_error .OR. (ier .NE. 0) |
---|
819 | ALLOCATE(maint_resp_slope_c(nvm),stat=ier) |
---|
820 | l_error = l_error .OR. (ier .NE. 0) |
---|
821 | ALLOCATE(maint_resp_slope_b(nvm),stat=ier) |
---|
822 | l_error = l_error .OR. (ier .NE. 0) |
---|
823 | ALLOCATE(maint_resp_slope_a(nvm),stat=ier) |
---|
824 | l_error = l_error .OR. (ier .NE. 0) |
---|
825 | ALLOCATE(coeff_maint_zero(nvm,nparts),stat=ier) |
---|
826 | l_error = l_error .OR. (ier .NE. 0) |
---|
827 | ALLOCATE(cm_zero_leaf(nvm),stat=ier) |
---|
828 | l_error = l_error .OR. (ier .NE. 0) |
---|
829 | ALLOCATE(cm_zero_sapabove(nvm),stat=ier) |
---|
830 | l_error = l_error .OR. (ier .NE. 0) |
---|
831 | ALLOCATE(cm_zero_sapbelow(nvm),stat=ier) |
---|
832 | l_error = l_error .OR. (ier .NE. 0) |
---|
833 | ALLOCATE(cm_zero_heartabove(nvm),stat=ier) |
---|
834 | l_error = l_error .OR. (ier .NE. 0) |
---|
835 | ALLOCATE(cm_zero_heartbelow(nvm),stat=ier) |
---|
836 | l_error = l_error .OR. (ier .NE. 0) |
---|
837 | ALLOCATE(cm_zero_root(nvm),stat=ier) |
---|
838 | l_error = l_error .OR. (ier .NE. 0) |
---|
839 | ALLOCATE(cm_zero_fruit(nvm),stat=ier) |
---|
840 | l_error = l_error .OR. (ier .NE. 0) |
---|
841 | ALLOCATE(cm_zero_carbres(nvm),stat=ier) |
---|
842 | l_error = l_error .OR. (ier .NE. 0) |
---|
843 | !- |
---|
844 | ALLOCATE(flam(nvm),stat=ier) |
---|
845 | l_error = l_error .OR. (ier .NE. 0) |
---|
846 | ALLOCATE(resist(nvm),stat=ier) |
---|
847 | l_error = l_error .OR. (ier .NE. 0) |
---|
848 | !- |
---|
849 | ALLOCATE(coeff_lcchange_1(nvm),stat=ier) |
---|
850 | l_error = l_error .OR. (ier .NE. 0) |
---|
851 | ALLOCATE(coeff_lcchange_10(nvm),stat=ier) |
---|
852 | l_error = l_error .OR. (ier .NE. 0) |
---|
853 | ALLOCATE(coeff_lcchange_100(nvm),stat=ier) |
---|
854 | l_error = l_error .OR. (ier .NE. 0) |
---|
855 | !- |
---|
856 | ALLOCATE(lai_max(nvm),stat=ier) |
---|
857 | l_error = l_error .OR. (ier .NE. 0) |
---|
858 | ALLOCATE(pheno_model(nvm),stat=ier) |
---|
859 | l_error = l_error .OR. (ier .NE. 0) |
---|
860 | ALLOCATE(pheno_type(nvm),stat=ier) |
---|
861 | l_error = l_error .OR. (ier .NE. 0) |
---|
862 | !- |
---|
863 | ALLOCATE(leaffall(nvm),stat=ier) |
---|
864 | l_error = l_error .OR. (ier .NE. 0) |
---|
865 | ALLOCATE(leafagecrit(nvm),stat=ier) |
---|
866 | l_error = l_error .OR. (ier .NE. 0) |
---|
867 | ALLOCATE(senescence_type(nvm),stat=ier) |
---|
868 | l_error = l_error .OR. (ier .NE. 0) |
---|
869 | ALLOCATE(senescence_hum(nvm),stat=ier) |
---|
870 | l_error = l_error .OR. (ier .NE. 0) |
---|
871 | ALLOCATE(nosenescence_hum(nvm),stat=ier) |
---|
872 | l_error = l_error .OR. (ier .NE. 0) |
---|
873 | ALLOCATE(max_turnover_time(nvm),stat=ier) |
---|
874 | l_error = l_error .OR. (ier .NE. 0) |
---|
875 | ALLOCATE(min_turnover_time(nvm),stat=ier) |
---|
876 | l_error = l_error .OR. (ier .NE. 0) |
---|
877 | ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier) |
---|
878 | l_error = l_error .OR. (ier .NE. 0) |
---|
879 | ALLOCATE(senescence_temp_c(nvm),stat=ier) |
---|
880 | l_error = l_error .OR. (ier .NE. 0) |
---|
881 | ALLOCATE(senescence_temp_b(nvm),stat=ier) |
---|
882 | l_error = l_error .OR. (ier .NE. 0) |
---|
883 | ALLOCATE(senescence_temp_a(nvm),stat=ier) |
---|
884 | l_error = l_error .OR. (ier .NE. 0) |
---|
885 | ALLOCATE(senescence_temp(nvm,3),stat=ier) |
---|
886 | l_error = l_error .OR. (ier .NE. 0) |
---|
887 | !- |
---|
888 | ALLOCATE(residence_time(nvm),stat=ier) |
---|
889 | l_error = l_error .OR. (ier .NE. 0) |
---|
890 | ALLOCATE(tmin_crit(nvm),stat=ier) |
---|
891 | l_error = l_error .OR. (ier .NE. 0) |
---|
892 | ALLOCATE(tcm_crit(nvm),stat=ier) |
---|
893 | l_error = l_error .OR. (ier .NE. 0) |
---|
894 | !- |
---|
895 | ALLOCATE(rstruct_const(nvm),stat=ier) |
---|
896 | l_error = l_error .OR. (ier .NE. 0) |
---|
897 | ALLOCATE(kzero(nvm),stat=ier) |
---|
898 | l_error = l_error .OR. (ier .NE. 0) |
---|
899 | !- |
---|
900 | ALLOCATE(wmax_veg(nvm),stat=ier) |
---|
901 | l_error = l_error .OR. (ier .NE. 0) |
---|
902 | ALLOCATE(humcste(nvm),stat=ier) |
---|
903 | l_error = l_error .OR. (ier .NE. 0) |
---|
904 | !- |
---|
905 | ALLOCATE(snowa_ini(nvm),stat=ier) |
---|
906 | l_error = l_error .OR. (ier .NE. 0) |
---|
907 | ALLOCATE(snowa_dec(nvm),stat=ier) |
---|
908 | l_error = l_error .OR. (ier .NE. 0) |
---|
909 | ALLOCATE(alb_leaf_vis(nvm),stat=ier) |
---|
910 | l_error = l_error .OR. (ier .NE. 0) |
---|
911 | ALLOCATE(alb_leaf_nir(nvm),stat=ier) |
---|
912 | l_error = l_error .OR. (ier .NE. 0) |
---|
913 | ALLOCATE(alb_leaf(2*nvm),stat=ier) |
---|
914 | l_error = l_error .OR. (ier .NE. 0) |
---|
915 | !- |
---|
916 | ALLOCATE(pref_soil_veg_sand(nvm),stat=ier) |
---|
917 | l_error = l_error .OR. (ier .NE. 0) |
---|
918 | ALLOCATE(pref_soil_veg_loan(nvm),stat=ier) |
---|
919 | l_error = l_error .OR. (ier .NE. 0) |
---|
920 | ALLOCATE(pref_soil_veg_clay(nvm),stat=ier) |
---|
921 | l_error = l_error .OR. (ier .NE. 0) |
---|
922 | ALLOCATE(pref_soil_veg(nvm,nstm),stat=ier) |
---|
923 | l_error = l_error .OR. (ier .NE. 0) |
---|
924 | !- |
---|
925 | ALLOCATE(lai_initmin(nvm),stat=ier) |
---|
926 | l_error = l_error .OR. (ier .NE. 0) |
---|
927 | ALLOCATE(tree(nvm),stat=ier) |
---|
928 | l_error = l_error .OR. (ier .NE. 0) |
---|
929 | ALLOCATE(bm_sapl(nvm,nparts),stat=ier) |
---|
930 | l_error = l_error .OR. (ier .NE. 0) |
---|
931 | ALLOCATE(migrate(nvm),stat=ier) |
---|
932 | l_error = l_error .OR. (ier .NE. 0) |
---|
933 | ALLOCATE(maxdia(nvm),stat=ier) |
---|
934 | l_error = l_error .OR. (ier .NE. 0) |
---|
935 | ALLOCATE(cn_sapl(nvm),stat=ier) |
---|
936 | l_error = l_error .OR. (ier .NE. 0) |
---|
937 | ALLOCATE(leaf_timecst(nvm),stat=ier) |
---|
938 | l_error = l_error .OR. (ier .NE. 0) |
---|
939 | !- |
---|
940 | ALLOCATE(throughfall_by_pft(nvm),stat=ier) |
---|
941 | l_error = l_error .OR. (ier .NE. 0) |
---|
942 | ALLOCATE (rveg_pft(nvm),stat=ier) |
---|
943 | l_error = l_error .OR. (ier .NE. 0) |
---|
944 | ! |
---|
945 | IF (l_error) THEN |
---|
946 | STOP 'pft _alloc : error in memory allocation' |
---|
947 | ENDIF |
---|
948 | |
---|
949 | END SUBROUTINE pft_parameters_alloc |
---|
950 | ! |
---|
951 | != |
---|
952 | ! |
---|
953 | SUBROUTINE getin_sechiba_pft_parameters |
---|
954 | |
---|
955 | IMPLICIT NONE |
---|
956 | |
---|
957 | LOGICAL, SAVE :: first_call = .TRUE. |
---|
958 | |
---|
959 | IF(first_call) THEN |
---|
960 | |
---|
961 | !- |
---|
962 | ! Vegetation structure |
---|
963 | !- |
---|
964 | ! |
---|
965 | !Config Key = SECHIBA_LAI |
---|
966 | !Config Desc = laimax for maximum lai see also type of lai interpolation |
---|
967 | !Config if = IMPOSE_VEG |
---|
968 | !Config Def = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2. |
---|
969 | !Config Help = Values of lai used for interpolation of the lai map |
---|
970 | !Config Units = |
---|
971 | CALL getin_p('SECHIBA_LAI',llaimax) |
---|
972 | ! |
---|
973 | !Config Key = LLAIMIN |
---|
974 | !Config Desc = laimin for minimum lai see also type of lai interpolation |
---|
975 | !Config if = OK_SECHIBA |
---|
976 | !Config Def = 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0. |
---|
977 | !Config Help = |
---|
978 | !Config Units = |
---|
979 | CALL getin_p('LLAIMIN',llaimin) |
---|
980 | ! |
---|
981 | !Config Key = SLOWPROC_HEIGHT |
---|
982 | !Config Desc = prescribed height of vegetation : one for each vegetation type |
---|
983 | !Config if = OK_SECHIBA |
---|
984 | !Config Def = 0.,30.,30.,20.,20.,20.,15.,15.,15.,.5,.6,1.,1. |
---|
985 | !Config Help = |
---|
986 | !Config Units = Meters (m) ? |
---|
987 | CALL getin_p('SLOWPROC_HEIGHT', height_presc) |
---|
988 | ! |
---|
989 | !Config Key = TYPE_OF_LAI |
---|
990 | !Config Desc = Type of behaviour of the LAI evolution algorithm for each vegetation type : mean or interp |
---|
991 | !Config if = OK_SECHIBA |
---|
992 | !Config Def = inter','inter','inter','inter','inter','inter','inter','inter','inter','inter','inter','inter','inter' |
---|
993 | !Config Help = |
---|
994 | !Config Units = NONE |
---|
995 | CALL getin('TYPE_OF_LAI',type_of_lai) |
---|
996 | ! |
---|
997 | !Config Key = IS_TREE |
---|
998 | !Config Desc = Is the vegetation type a tree ? |
---|
999 | !Config if = OK_SECHIBA |
---|
1000 | !Config Def = n, y, y, y, y, y, y, y, y, n, n, n, n |
---|
1001 | !Config Help = |
---|
1002 | !Config Units = NONE |
---|
1003 | CALL getin_p('IS_TREE',is_tree) |
---|
1004 | ! |
---|
1005 | !Config Key = NATURAL |
---|
1006 | !Config Desc = natural? |
---|
1007 | !Config if = OK_SECHIBA |
---|
1008 | !Config Def = y, y, y, y, y, y, y, y, y, y, y, n, n |
---|
1009 | !Config Help = |
---|
1010 | !Config Units = NONE |
---|
1011 | CALL getin_p('NATURAL',natural) |
---|
1012 | |
---|
1013 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
1014 | ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' |
---|
1015 | ! |
---|
1016 | !Config Key = IS_DECIDUOUS |
---|
1017 | !Config Desc = is PFT deciduous ? |
---|
1018 | !Config if = OK_SECHIBA |
---|
1019 | !Config Def = n, n, y, n, n, y, n, y, y, n, n, n, n |
---|
1020 | !Config Help = |
---|
1021 | !Config Units = NONE |
---|
1022 | CALL getin('IS_DECIDUOUS',is_deciduous) |
---|
1023 | ! |
---|
1024 | !Config Key = IS_EVERGREEN |
---|
1025 | !Config Desc = is PFT evergreen ? |
---|
1026 | !Config if = OK_SECHIBA |
---|
1027 | !Config Def = n, y, n, y, y, n, y, n, n, n, n, n, n |
---|
1028 | !Config Help = |
---|
1029 | !Config Units = NONE |
---|
1030 | CALL getin('IS_EVERGREEN',is_evergreen) |
---|
1031 | ! |
---|
1032 | !Config Key = IS_C3 |
---|
1033 | !Config Desc = is PFT C3 ? |
---|
1034 | !Config if = OK_SECHIBA |
---|
1035 | !Config Def = n, n, n, n, n, n, n, n, n, n, y, n, y, n |
---|
1036 | !Config Help = |
---|
1037 | !Config Units = NONE |
---|
1038 | CALL getin_p('IS_C3',is_c3) |
---|
1039 | |
---|
1040 | !- |
---|
1041 | ! Photosynthesis |
---|
1042 | !- |
---|
1043 | ! |
---|
1044 | !Config Key = IS_C4 |
---|
1045 | !Config Desc = flag for C4 vegetation types |
---|
1046 | !Config if = OK_SECHIBA |
---|
1047 | !Config Def = n, n, n, n, n, n, n, n, n, n, n, y, n, y |
---|
1048 | !Config Help = |
---|
1049 | !Config Units = NONE |
---|
1050 | CALL getin_p('IS_C4',is_c4) |
---|
1051 | ! |
---|
1052 | !Config Key = GSSLOPE |
---|
1053 | !Config Desc = Slope of the gs/A relation (Ball & al. |
---|
1054 | !Config if = OK_SECHIBA AND OK_CO2 |
---|
1055 | !Config Def = 0., 9., 9., 9., 9., 9., 9., 9., 9., 9., 3., 9., 3. |
---|
1056 | !Config Help = |
---|
1057 | !Config Units = |
---|
1058 | CALL getin_p('GSSLOPE',gsslope) |
---|
1059 | ! |
---|
1060 | !Config Key = GSOFFSET |
---|
1061 | !Config Desc = intercept of the gs/A relation (Ball & al.) |
---|
1062 | !Config if = OK_SECHIBA |
---|
1063 | !Config Def = 0.0, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.03, 0.01, 0.03 |
---|
1064 | !Config Help = |
---|
1065 | !Config Units = |
---|
1066 | CALL getin_p('GSOFFSET',gsoffset) |
---|
1067 | ! |
---|
1068 | !Config Key = VCMAX_FIX |
---|
1069 | !Config Desc = values used for vcmax when STOMATE is not activated |
---|
1070 | !Config if = OK_SECHIBA |
---|
1071 | !Config Def = 0., 40., 50., 30., 35., 40.,30., 40., 35., 60., 60., 70., 70. |
---|
1072 | !Config Help = |
---|
1073 | !Config Units = |
---|
1074 | CALL getin_p('VCMAX_FIX',vcmax_fix) |
---|
1075 | ! |
---|
1076 | !Config Key = VJMAX_FIX |
---|
1077 | !Config Desc = values used for vjmax when STOMATE is not activated |
---|
1078 | !Config if = OK_SECHIBA |
---|
1079 | !Config Def = 0., 80., 100., 60., 70., 80., 60., 80., 70., 120., 120., 140., 140. |
---|
1080 | !Config Help = |
---|
1081 | !Config Units = |
---|
1082 | CALL getin_p('VJMAX_FIX',vjmax_fix) |
---|
1083 | ! |
---|
1084 | !Config Key = CO2_TMIN_FIX |
---|
1085 | !Config Desc = values used for photosynthesis tmin when STOMATE is not activated |
---|
1086 | !Config if = OK_SECHIBA |
---|
1087 | !Config Def = 0., 2., 2., -4., -3., -2., -4., -4., -4., -5., 6., -5., 6. |
---|
1088 | !Config Help = |
---|
1089 | !Config Units = |
---|
1090 | CALL getin_p('CO2_TMIN_FIX',co2_tmin_fix) |
---|
1091 | ! |
---|
1092 | !Config Key = CO2_TOPT_FIX |
---|
1093 | !Config Desc = values used for photosynthesis topt when STOMATE is not activated |
---|
1094 | !Config if = OK_SECHIBA |
---|
1095 | !Config Def = 0., 27.5, 27.5, 17.5, 25., 20.,17.5, 17.5, 17.5, 20., 32.5, 20., 32.5 |
---|
1096 | !Config Help = |
---|
1097 | !Config Units = |
---|
1098 | CALL getin_p('CO2_TOPT_FIX',co2_topt_fix) |
---|
1099 | ! |
---|
1100 | !Config Key = CO2_TMAX_FIX |
---|
1101 | !Config Desc = values used for photosynthesis tmax when STOMATE is not activated |
---|
1102 | !Config if = OK_SECHIBA |
---|
1103 | !Config Def = 0., 55., 55., 38., 48., 38.,38., 38., 38., 45., 55., 45., 55. |
---|
1104 | !Config Help = |
---|
1105 | !Config Units = |
---|
1106 | CALL getin_p('CO2_TMAX_FIX',co2_tmax_fix) |
---|
1107 | ! |
---|
1108 | !Config Key = EXT_COEFF |
---|
1109 | !Config Desc = extinction coefficient of the Monsi&Seaki relationship (1953) |
---|
1110 | !Config if = OK_SECHIBA OR OK_STOMATE |
---|
1111 | !Config Def = .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5 |
---|
1112 | !Config Help = |
---|
1113 | !Config Units = |
---|
1114 | CALL getin_p('EXT_COEFF',ext_coeff) |
---|
1115 | !- |
---|
1116 | ! Evapotranspiration - sechiba |
---|
1117 | !- |
---|
1118 | ! |
---|
1119 | !Config Key = RSTRUCT_CONST |
---|
1120 | !Config Desc = Structural resistance : one for each vegetation type |
---|
1121 | !Config if = OK_SECHIBA |
---|
1122 | !Config Def = 0.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0, 25.0, 2.5, 2.0, 2.0, 2.0 |
---|
1123 | !Config Help = |
---|
1124 | !Config Units = |
---|
1125 | CALL getin_p('RSTRUCT_CONST',rstruct_const) |
---|
1126 | ! |
---|
1127 | !Config Key = KZERO |
---|
1128 | !Config Desc = A vegetation dependent constant used in the calculation of the surface resistance. |
---|
1129 | !Config if = OK_SECHIBA |
---|
1130 | !Config Def = 0.0, 12.E-5, 12.E-5, 12.e-5, 12.e-5, 25.e-5, 12.e-5,25.e-5, 25.e-5, 30.e-5, 30.e-5, 30.e-5, 30.e-5 |
---|
1131 | !Config Help = |
---|
1132 | !Config Units = |
---|
1133 | CALL getin_p('KZERO',kzero) |
---|
1134 | ! |
---|
1135 | ! Ajouts Nathalie - le 28 Mars 2006 - sur conseils Fred Hourdin |
---|
1136 | ! |
---|
1137 | !Config Key = RVEG_PFT |
---|
1138 | !Config Desc = Artificial parameter to increase or decrease canopy resistance. |
---|
1139 | !Config if = OK_SECHIBA |
---|
1140 | !Config Def = 1. |
---|
1141 | !Config Help = This parameter is set by PFT. |
---|
1142 | !Config Units = |
---|
1143 | CALL getin_p('RVEG_PFT', rveg_pft) |
---|
1144 | !- |
---|
1145 | ! Water-hydrology - sechiba |
---|
1146 | !- |
---|
1147 | ! |
---|
1148 | !Config Key = WMAX_VEG |
---|
1149 | !Config Desc = Maximum field capacity for each of the vegetations (Temporary): max quantity of water |
---|
1150 | !Config if = OK_SECHIBA |
---|
1151 | !Config Def = 150., 150., 150., 150., 150., 150., 150.,150., 150., 150., 150., 150., 150. |
---|
1152 | !Config Help = |
---|
1153 | !Config Units = Kg/M3 |
---|
1154 | CALL getin_p('WMAX_VEG',wmax_veg) |
---|
1155 | ! |
---|
1156 | !Config Key = HYDROL_HUMCSTE |
---|
1157 | !Config Desc = Root profile |
---|
1158 | !Config Def = 5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4. |
---|
1159 | !Config if = OK_SECHIBA |
---|
1160 | !Config Help = Default values were defined for 2 meters soil depth. |
---|
1161 | !Config For 4 meters soil depth, you may use those ones : |
---|
1162 | !Config 5., .4, .4, 1., .8, .8, 1., 1., .8, 4., 1., 4., 1. |
---|
1163 | !Config Units = |
---|
1164 | CALL getin_p('HYDROL_HUMCSTE', humcste) |
---|
1165 | ! |
---|
1166 | !Config Key = PERCENT_THROUGHFALL_PFT |
---|
1167 | !Config Desc = Percent by PFT of precip that is not intercepted by the canopy |
---|
1168 | !Config if = OK_SECHIBA OR OK_CWRR |
---|
1169 | !Config Def = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. |
---|
1170 | !Config Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall |
---|
1171 | !Config will get directly to the ground without being intercepted, for each PFT. |
---|
1172 | !Config Units = Kg/M3 |
---|
1173 | CALL getin_p('PERCENT_TROUGHFALL_PFT',throughfall_by_pft) |
---|
1174 | !- |
---|
1175 | ! Albedo - sechiba |
---|
1176 | !- |
---|
1177 | ! |
---|
1178 | !Config Key = SNOWA_INI |
---|
1179 | !Config Desc = Initial snow albedo value for each vegetation type as it will be used in condveg_snow |
---|
1180 | !Config if = OK_SECHIBA |
---|
1181 | !Config Def = 0.35, 0., 0., 0.14, 0.14,0.14, 0.14, 0.14, 0.14, 0.18,0.18, 0.18, 0.18 |
---|
1182 | !Config Help = Values are from the Thesis of S. Chalita (1992) |
---|
1183 | !Config Units = |
---|
1184 | CALL getin_p('SNOWA_INI',snowa_ini) |
---|
1185 | ! |
---|
1186 | !Config Key = SNOWA_DEC |
---|
1187 | !Config Desc = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow |
---|
1188 | !Config if = OK_SECHIBA |
---|
1189 | !Config Def = 0.45, 0., 0., 0.06, 0.06, 0.11, 0.06, 0.11, 0.11, 0.52,0.52, 0.52, 0.52 |
---|
1190 | !Config Help = Values are from the Thesis of S. Chalita (1992) |
---|
1191 | !Config Units = |
---|
1192 | CALL getin_p('SNOWA_DEC',snowa_dec) |
---|
1193 | ! |
---|
1194 | !Config Key = ALB_LEAF_VIS |
---|
1195 | !Config Desc = leaf albedo of vegetation type, visible albedo |
---|
1196 | !Config if = OK_SECHIBA |
---|
1197 | !Config Def = .00, .04, .06, .06, .06,.06, .06, .06, .06, .10, .10, .10, .10 |
---|
1198 | !Config Help = |
---|
1199 | !Config Units = |
---|
1200 | CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis) |
---|
1201 | ! |
---|
1202 | !Config Key = ALB_LEAF_NIR |
---|
1203 | !Config Desc = leaf albedo of vegetation type, near infrared albedo |
---|
1204 | !Config if = OK_SECHIBA |
---|
1205 | !Config Def =.00, .20, .22, .22, .22,.22, .22, .22, .22, .30,.30, .30, .30 |
---|
1206 | !Config Help = |
---|
1207 | !Config Units = |
---|
1208 | CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir) |
---|
1209 | !- |
---|
1210 | ! Soil - vegetation |
---|
1211 | !- |
---|
1212 | ! |
---|
1213 | !Config Key = PREF_SOIL_VEG_SAND |
---|
1214 | !Config Desc = Table which contains the correlation between the soil types and vegetation type |
---|
1215 | !Config if = OK_SECHIBA |
---|
1216 | !Config Def = 1, 3, 3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2 |
---|
1217 | !Config Help = first layer of the soil |
---|
1218 | !Config Units = |
---|
1219 | CALL getin_p('PREF_SOIL_VEG_SAND',pref_soil_veg_sand) |
---|
1220 | ! |
---|
1221 | !Config Key = PREF_SOIL_VEG_LOAN |
---|
1222 | !Config Desc = Table which contains the correlation between the soil types and vegetation type |
---|
1223 | !Config if = OK_SECHIBA |
---|
1224 | !Config Def = 2, 2, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3 |
---|
1225 | !Config Help = second layer of the soil |
---|
1226 | !Config Units = |
---|
1227 | CALL getin_p('PREF_SOIL_VEG_LOAN',pref_soil_veg_loan) |
---|
1228 | ! |
---|
1229 | !Config Key = PREF_SOIL_VEG_CLAY |
---|
1230 | !Config Desc = Table which contains the correlation between the soil types and vegetation type |
---|
1231 | !Config if = OK_SECHIBA |
---|
1232 | !Config Def = 3, 1, 1, 1, 1, 1 ,1 ,1 ,1 ,1 ,1 ,1, 1 |
---|
1233 | !Config Help = third layer of the soil |
---|
1234 | !Config Units = |
---|
1235 | CALL getin_p('PREF_SOIL_VEG_CLAY',pref_soil_veg_clay) |
---|
1236 | |
---|
1237 | first_call = .FALSE. |
---|
1238 | |
---|
1239 | ENDIF |
---|
1240 | |
---|
1241 | END SUBROUTINE getin_sechiba_pft_parameters |
---|
1242 | ! |
---|
1243 | != |
---|
1244 | ! |
---|
1245 | SUBROUTINE getin_stomate_pft_parameters |
---|
1246 | |
---|
1247 | IMPLICIT NONE |
---|
1248 | |
---|
1249 | LOGICAL, SAVE :: first_call = .TRUE. |
---|
1250 | |
---|
1251 | IF(first_call) THEN |
---|
1252 | |
---|
1253 | !- |
---|
1254 | ! Vegetation structure |
---|
1255 | !- |
---|
1256 | ! |
---|
1257 | !Config Key = LEAF_TAB |
---|
1258 | !Config Desc = leaf type : 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bare ground |
---|
1259 | !Config if = OK_STOMATE |
---|
1260 | !Config Def = 4, 1, 1, 2, 1, 1, 2, 1, 2, 3, 3, 3, 3 |
---|
1261 | !Config Help = |
---|
1262 | !Config Units = NONE |
---|
1263 | CALL getin_p('LEAF_TAB',leaf_tab) |
---|
1264 | ! |
---|
1265 | !Config Key = SLA |
---|
1266 | !Config Desc = specif leaf area |
---|
1267 | !Config if = OK_STOMATE |
---|
1268 | !Config Def = 1.5E-2, 1.53E-2, 2.6E-2, 9.26E-3, 2E-2, 2.6E-2, 9.26E-3, 2.6E-2, 1.9E-2, 2.6E-2, 2.6E-2, 2.6E-2, 2.6E-2 |
---|
1269 | !Config Help = |
---|
1270 | !Config Units = m**2/gC |
---|
1271 | CALL getin_p('SLA',sla) |
---|
1272 | !- |
---|
1273 | ! Photosynthesis |
---|
1274 | !- |
---|
1275 | ! |
---|
1276 | !Config Key = VCMAX_OPT |
---|
1277 | !Config Desc = Maximum rate of carboxylation |
---|
1278 | !Config if = OK_STOMATE |
---|
1279 | !Config Def = undef, 65., 65., 35., 45., 55., 35., 45., 35., 70., 70.,70., 70. |
---|
1280 | !Config Help = |
---|
1281 | !Config Units = % |
---|
1282 | CALL getin_p('VCMAX_OPT',vcmax_opt) |
---|
1283 | ! |
---|
1284 | !Config Key = VJMAX_OPT |
---|
1285 | !Config Desc = Maximum rate of RUbp regeneration |
---|
1286 | !Config if = OK_STOMATE |
---|
1287 | !Config Def = undef, 130., 130., 70., 80., 110., 70., 90., 70., 160.,160.,200., 200. |
---|
1288 | !Config Help = |
---|
1289 | !Config Units = % |
---|
1290 | CALL getin_p('VJMAX_OPT',vjmax_opt) |
---|
1291 | ! |
---|
1292 | !Config Key = TPHOTO_MIN_A |
---|
1293 | !Config Desc = minimum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated |
---|
1294 | !Config if = OK_STOMATE |
---|
1295 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.0025, 0., 0., 0. |
---|
1296 | !Config Help = |
---|
1297 | !Config Units = NONE |
---|
1298 | CALL getin_p('TPHOTO_MIN_A',tphoto_min_a) |
---|
1299 | ! |
---|
1300 | !Config Key = TPHOTO_MIN_B |
---|
1301 | !Config Desc = minimum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated |
---|
1302 | !Config if = OK_STOMATE |
---|
1303 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.1, 0.,0.,0. |
---|
1304 | !Config Help = |
---|
1305 | !Config Units = NONE |
---|
1306 | CALL getin_p('TPHOTO_MIN_B',tphoto_min_b) |
---|
1307 | ! |
---|
1308 | !Config Key = TPHOTO_MIN_C |
---|
1309 | !Config Desc = minimum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated |
---|
1310 | !Config if = OK_STOMATE |
---|
1311 | !Config Def = undef, 2., 2., -4., -3.,-2.,-4., -4.,-4.,-3.25, 13.,-5.,13. |
---|
1312 | !Config Help = |
---|
1313 | !Config Units = NONE |
---|
1314 | CALL getin_p('TPHOTO_MIN_C',tphoto_min_c) |
---|
1315 | ! |
---|
1316 | !Config Key = TPHOTO_OPT_A |
---|
1317 | !Config Desc = optimum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated |
---|
1318 | !Config if = OK_STOMATE |
---|
1319 | !Config Def = undef, 0., 0., 0., 0.,0.,0.,0.,0.,0.0025,0.,0.,0. |
---|
1320 | !Config Help = |
---|
1321 | !Config Units = NONE |
---|
1322 | CALL getin_p('TPHOTO_OPT_A',tphoto_opt_a) |
---|
1323 | ! |
---|
1324 | !Config Key = TPHOTO_OPT_B |
---|
1325 | !Config Desc = optimum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated |
---|
1326 | !Config if = OK_STOMATE |
---|
1327 | !Config Def = undef, 0.,0.,0.,0.,0.,0., 0.,0.,0.25,0.,0.,0. |
---|
1328 | !Config Help = |
---|
1329 | !Config Units = NONE |
---|
1330 | CALL getin_p('TPHOTO_OPT_B',tphoto_opt_b) |
---|
1331 | ! |
---|
1332 | !Config Key = TPHOTO_OPT_C |
---|
1333 | !Config Desc = optimum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated |
---|
1334 | !Config if = OK_STOMATE |
---|
1335 | !Config Def = undef, 37., 37., 25., 32., 26., 25., 25., 25., 27.25, 36., 30., 36. |
---|
1336 | !Config Help = |
---|
1337 | !Config Units = NONE |
---|
1338 | CALL getin_p('TPHOTO_OPT_C',tphoto_opt_c) |
---|
1339 | ! |
---|
1340 | !Config Key = TPHOTO_MAX_A |
---|
1341 | !Config Desc = maximum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated |
---|
1342 | !Config if = OK_STOMATE |
---|
1343 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.00375, 0., 0., 0. |
---|
1344 | !Config Help = |
---|
1345 | !Config Units = NONE |
---|
1346 | CALL getin_p('TPHOTO_MAX_A',tphoto_max_a) |
---|
1347 | ! |
---|
1348 | !Config Key = TPHOTO_MAX_B |
---|
1349 | !Config Desc = maximum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated |
---|
1350 | !Config if = OK_STOMATE |
---|
1351 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0.,0.35, 0., 0., 0. |
---|
1352 | !Config Help = |
---|
1353 | !Config Units = NONE |
---|
1354 | CALL getin_p('TPHOTO_MAX_B',tphoto_max_b) |
---|
1355 | ! |
---|
1356 | !Config Key = TPHOTO_MAX_C |
---|
1357 | !Config Desc = maximum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated |
---|
1358 | !Config if = OK_STOMATE |
---|
1359 | !Config Def = undef, 55., 55.,38., 48.,38.,38., 38., 38., 41.125, 55., 45., 55. |
---|
1360 | !Config Help = |
---|
1361 | !Config Units = NONE |
---|
1362 | CALL getin_p('TPHOTO_MAX_C',tphoto_max_c) |
---|
1363 | !- |
---|
1364 | ! Respiration - stomate |
---|
1365 | !- |
---|
1366 | ! |
---|
1367 | !Config Key = MAINT_RESP_SLOPE_C |
---|
1368 | !Config Desc = slope of maintenance respiration coefficient (1/K), constant c of aT^2+bT+c , tabulated |
---|
1369 | !Config if = OK_STOMATE |
---|
1370 | !Config Def = undef, .12, .12,.16,.16,.16,.16,.16,.16,.16,.12,.16,.12 |
---|
1371 | !Config Help = |
---|
1372 | !Config Units = NONE |
---|
1373 | CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) |
---|
1374 | ! |
---|
1375 | !Config Key = MAINT_RESP_SLOPE_B |
---|
1376 | !Config Desc = slope of maintenance respiration coefficient (1/K), constant b of aT^2+bT+c , tabulated |
---|
1377 | !Config if = OK_STOMATE |
---|
1378 | !Config Def = undef,.0,.0,.0,.0,.0,.0,.0,.0, -.00133,.0, -.00133,.0 |
---|
1379 | !Config Help = |
---|
1380 | !Config Units = NONE |
---|
1381 | CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b) |
---|
1382 | ! |
---|
1383 | !Config Key = MAINT_RESP_SLOPE_A |
---|
1384 | !Config Desc = slope of maintenance respiration coefficient (1/K), constant a of aT^2+bT+c , tabulated |
---|
1385 | !Config if = OK_STOMATE |
---|
1386 | !Config Def = undef,.0,.0, .0,.0,.0,.0,.0,.0,.0,.0,.0,.0 |
---|
1387 | !Config Help = |
---|
1388 | !Config Units = NONE |
---|
1389 | CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a) |
---|
1390 | ! |
---|
1391 | !Config Key = CM_ZERO_LEAF |
---|
1392 | !Config Desc = maintenance respiration coefficient at 0 deg C, for leaves, tabulated |
---|
1393 | !Config if = OK_STOMATE |
---|
1394 | !Config Def = undef, 2.35E-3, 2.62E-3, 1.01E-3, 2.35E-3, 2.62E-3, 1.01E-3,2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3 |
---|
1395 | !Config Help = |
---|
1396 | !Config Units = g/g/day |
---|
1397 | CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf) |
---|
1398 | ! |
---|
1399 | !Config Key = CM_ZERO_SAPABOVE |
---|
1400 | !Config Desc = maintenance respiration coefficient at 0 deg C,for sapwood above, tabulated |
---|
1401 | !Config if = OK_STOMATE |
---|
1402 | !Config Def = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 |
---|
1403 | !Config Help = |
---|
1404 | !Config Units = g/g/day |
---|
1405 | CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove) |
---|
1406 | ! |
---|
1407 | !Config Key = CM_ZERO_SAPBELOW |
---|
1408 | !Config Desc = maintenance respiration coefficient (g/g/day) at 0 deg C, for sapwood below, tabulated |
---|
1409 | !Config if = OK_STOMATE |
---|
1410 | !Config Def = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 |
---|
1411 | !Config Help = |
---|
1412 | !Config Units = g/g/day |
---|
1413 | CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow) |
---|
1414 | ! |
---|
1415 | !Config Key = CM_ZERO_HEARTABOVE |
---|
1416 | !Config Desc = maintenance respiration coefficient at 0 deg C, for heartwood above, tabulated |
---|
1417 | !Config if = OK_STOMATE |
---|
1418 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0. |
---|
1419 | !Config Help = |
---|
1420 | !Config Units = g/g/day |
---|
1421 | CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove) |
---|
1422 | ! |
---|
1423 | !Config Key = CM_ZERO_HEARTBELOW |
---|
1424 | !Config Desc = maintenance respiration coefficient at 0 deg C,for heartwood below, tabulated |
---|
1425 | !Config if = OK_STOMATE |
---|
1426 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0. |
---|
1427 | !Config Help = |
---|
1428 | !Config Units = g/g/day |
---|
1429 | CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow) |
---|
1430 | ! |
---|
1431 | !Config Key = CM_ZERO_ROOT |
---|
1432 | !Config Desc = maintenance respiration coefficient at 0 deg C, for roots, tabulated |
---|
1433 | !Config if = OK_STOMATE |
---|
1434 | !Config Def = undef,1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3,1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3 |
---|
1435 | !Config Help = |
---|
1436 | !Config Units = g/g/day |
---|
1437 | CALL getin_p('CM_ZERO_ROOT',cm_zero_root) |
---|
1438 | ! |
---|
1439 | !Config Key = CM_ZERO_FRUIT |
---|
1440 | !Config Desc = maintenance respiration coefficient at 0 deg C, for fruits, tabulated |
---|
1441 | !Config if = OK_STOMATE |
---|
1442 | !Config Def = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 |
---|
1443 | !Config Help = |
---|
1444 | !Config Units = g/g/day |
---|
1445 | CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit) |
---|
1446 | ! |
---|
1447 | !Config Key = CM_ZERO_CARBRES |
---|
1448 | !Config Desc = maintenance respiration coefficient at 0 deg C, for carbohydrate reserve, tabulated |
---|
1449 | !Config if = OK_STOMATE |
---|
1450 | !Config Def = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 |
---|
1451 | !Config Help = |
---|
1452 | !Config Units = g/g/day |
---|
1453 | CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres) |
---|
1454 | !- |
---|
1455 | ! Fire - stomate |
---|
1456 | !- |
---|
1457 | ! |
---|
1458 | !Config Key = FLAM |
---|
1459 | !Config Desc = flamability: critical fraction of water holding capacity |
---|
1460 | !Config if = OK_STOMATE |
---|
1461 | !Config Def = undef,.15,.25,.25,.25,.25,.25,.25,.25,.25,.25,.35,.35 |
---|
1462 | !Config Help = |
---|
1463 | !Config Units = |
---|
1464 | CALL getin_p('FLAM',flam) |
---|
1465 | ! |
---|
1466 | !Config Key = RESIST |
---|
1467 | !Config Desc = fire resistance |
---|
1468 | !Config if = OK_STOMATE |
---|
1469 | !Config Def = undef, .95,.90,.12,.50,.12,.12,.12,.12,.0,.0,.0,.0 |
---|
1470 | !Config Help = |
---|
1471 | !Config Units = |
---|
1472 | CALL getin_p('RESIST',resist) |
---|
1473 | !- |
---|
1474 | ! Flux - LUC |
---|
1475 | !- |
---|
1476 | ! |
---|
1477 | !Config Key = COEFF_LCCHANGE_1 |
---|
1478 | !Config Desc = Coeff of biomass export for the year |
---|
1479 | !Config if = OK_STOMATE |
---|
1480 | !Config Def = undef,0.597,0.597,0.597,0.597,0.597,0.597, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597 |
---|
1481 | !Config Help = |
---|
1482 | !Config Units = |
---|
1483 | CALL getin_p('COEFF_LCCHANGE_1',coeff_lcchange_1) |
---|
1484 | ! |
---|
1485 | !Config Key = COEFF_LCCHANGE_10 |
---|
1486 | !Config Desc = Coeff of biomass export for the decade |
---|
1487 | !Config if = OK_STOMATE |
---|
1488 | !Config Def = undef,0.403,0.403,0.299,0.299,0.299,0.299,0.299,0.299,0.299,0.403,0.299,0.403 |
---|
1489 | !Config Help = |
---|
1490 | !Config Units = |
---|
1491 | CALL getin_p('COEFF_LCCHANGE_10',coeff_lcchange_10) |
---|
1492 | ! |
---|
1493 | !Config Key = COEFF_LCCHANGE_100 |
---|
1494 | !Config Desc = Coeff of biomass export for the century |
---|
1495 | !Config if = OK_STOMATE |
---|
1496 | !Config Def = undef, 0.,0.,0.104,0.104,0.104,0.104,0.104,0.104,0.104, 0.,0.104,0. |
---|
1497 | !Config Help = |
---|
1498 | !Config Units = |
---|
1499 | CALL getin_p('COEFF_LCCHANGE_100',coeff_lcchange_100) |
---|
1500 | !- |
---|
1501 | ! Phenology |
---|
1502 | !- |
---|
1503 | ! |
---|
1504 | !Config Key = LAI_MAX |
---|
1505 | !Config Desc = maximum LAI, PFT-specific |
---|
1506 | !Config if = OK_STOMATE |
---|
1507 | !Config Def = undef, 7., 7., 5., 5., 5.,4.5, 4.5, 3.0, 2.5, 2.5, 5.,5. |
---|
1508 | !Config Help = |
---|
1509 | !Config Units = |
---|
1510 | CALL getin_p('LAI_MAX',lai_max) |
---|
1511 | ! |
---|
1512 | !Config Key = PHENO_MODEL |
---|
1513 | !Config Desc = which phenology model is used? (tabulated) |
---|
1514 | !Config if = OK_STOMATE |
---|
1515 | !Config Def = 'none ', 'none ', 'moi ', 'none ','none ','ncdgdd','none ','ncdgdd','ngd ','moigdd','moigdd','moigdd','moigdd' |
---|
1516 | !Config Help = |
---|
1517 | !Config Units = NONE |
---|
1518 | CALL getin('PHENO_MODEL',pheno_model) |
---|
1519 | ! |
---|
1520 | !Config Key = PHENO_TYPE |
---|
1521 | !Config Desc = type of phenology, 0=bare ground 1=evergreen, 2=summergreen, 3=raingreen, 4=perennial |
---|
1522 | !Config if = OK_STOMATE |
---|
1523 | !Config Def = 0, 1, 3, 1, 1, 2, 1, 2, 2, 4, 4, 2, 3 |
---|
1524 | !Config Help = |
---|
1525 | !Config Units = NONE |
---|
1526 | CALL getin_p('PHENO_TYPE',pheno_type) |
---|
1527 | !- |
---|
1528 | ! Phenology : Leaf Onset |
---|
1529 | !- |
---|
1530 | ! |
---|
1531 | !Config Key = PHENO_GDD_CRIT_C |
---|
1532 | !Config Desc = critical gdd, tabulated (C), constant c of aT^2+bT+c |
---|
1533 | !Config if = OK_STOMATE |
---|
1534 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 270., 400., 125., 400. |
---|
1535 | !Config Help = |
---|
1536 | !Config Units = NONE |
---|
1537 | CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c) |
---|
1538 | ! |
---|
1539 | !Config Key = PHENO_GDD_CRIT_B |
---|
1540 | !Config Desc = critical gdd, tabulated (C), constant b of aT^2+bT+c |
---|
1541 | !Config if = OK_STOMATE |
---|
1542 | !Config Def = undef, undef, undef, undef, undef, undef, undef,undef, undef, 6.25, 0., 0., 0. |
---|
1543 | !Config Help = |
---|
1544 | !Config Units = NONE |
---|
1545 | CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b) |
---|
1546 | ! |
---|
1547 | !Config Key = PHENO_GDD_CRIT_A |
---|
1548 | !Config Desc = critical gdd, tabulated (C), constant a of aT^2+bT+c |
---|
1549 | !Config if = OK_STOMATE |
---|
1550 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.03125, 0., 0., 0. |
---|
1551 | !Config Help = |
---|
1552 | !Config Units = NONE |
---|
1553 | CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a) |
---|
1554 | ! |
---|
1555 | !Config Key = NGD_CRIT |
---|
1556 | !Config Desc = critical ngd, tabulated. Threshold -5 degrees |
---|
1557 | !Config if = OK_STOMATE |
---|
1558 | !Config Def = undef, undef, undef, undef, undef, undef, undef, 0., undef, undef, undef, undef, undef |
---|
1559 | !Config Help = |
---|
1560 | !Config Units = |
---|
1561 | CALL getin_p('NGD_CRIT',ngd_crit) |
---|
1562 | ! |
---|
1563 | !Config Key = NCDGDD_TEMP |
---|
1564 | !Config Desc = critical temperature for the ncd vs. gdd function in phenology |
---|
1565 | !Config if = OK_STOMATE |
---|
1566 | !Config Def = undef, undef, undef, undef, undef, 5., undef, 0., undef, undef, undef, undef, undef |
---|
1567 | !Config Help = |
---|
1568 | !Config Units = celsius degrees (C) ? |
---|
1569 | CALL getin_p('NCDGDD_TEMP', ncdgdd_temp) |
---|
1570 | ! |
---|
1571 | !Config Key = HUM_FRAC |
---|
1572 | !Config Desc = critical humidity (relative to min/max) for phenology |
---|
1573 | !Config if = OK_STOMATE |
---|
1574 | !Config Def = undef, undef, .5, undef, undef, undef, undef, undef, undef, .5, .5, .5,.5 |
---|
1575 | !Config Help = |
---|
1576 | !Config Units = |
---|
1577 | CALL getin_p('HUM_FRAC', hum_frac) |
---|
1578 | ! |
---|
1579 | !Config Key = LOWGPP_TIME |
---|
1580 | !Config Desc = minimum duration of dormance (d) for phenology |
---|
1581 | !Config if = OK_STOMATE |
---|
1582 | !Config Def = undef, undef, 30., undef, undef, 30., undef, 30., 30., 30., 30., 30., 30. |
---|
1583 | !Config Help = |
---|
1584 | !Config Units = days |
---|
1585 | CALL getin_p('LOWGPP_TIME', lowgpp_time) |
---|
1586 | ! |
---|
1587 | !Config Key = HUM_MIN_TIME |
---|
1588 | !Config Desc = minimum time elapsed since moisture minimum |
---|
1589 | !Config if = OK_STOMATE |
---|
1590 | !Config Def = undef, undef, 50., undef, undef, undef, undef, undef, undef, 35., 35., 75., 75. |
---|
1591 | !Config Help = |
---|
1592 | !Config Units = days (d) |
---|
1593 | CALL getin_p('HUM_MIN_TIME', hum_min_time) |
---|
1594 | ! |
---|
1595 | !Config Key = TAU_SAP |
---|
1596 | !Config Desc = sapwood -> heartwood conversion time |
---|
1597 | !Config if = OK_STOMATE |
---|
1598 | !Config Def = undef, 730., 730., 730., 730., 730., 730., 730., 730., undef, undef, undef, undef |
---|
1599 | !Config Help = |
---|
1600 | !Config Units = days (d) |
---|
1601 | CALL getin_p('TAU_SAP',tau_sap) |
---|
1602 | ! |
---|
1603 | !Config Key = TAU_FRUIT |
---|
1604 | !Config Desc = fruit lifetime |
---|
1605 | !Config if = OK_STOMATE |
---|
1606 | !Config Def = undef, 90., 90., 90., 90., 90., 90., 90., 90., undef, undef, undef, undef |
---|
1607 | !Config Help = |
---|
1608 | !Config Units = days (d) |
---|
1609 | CALL getin_p('TAU_FRUIT',tau_fruit) |
---|
1610 | ! |
---|
1611 | !Config Key = ECUREUIL |
---|
1612 | !Config Desc = fraction of primary leaf and root allocation put into reserve |
---|
1613 | !Config if = OK_STOMATE |
---|
1614 | !Config Def = undef, .0, 1.,.0,.0, 1., .0,1., 1., 1., 1., 1., 1. |
---|
1615 | !Config Help = |
---|
1616 | !Config Units = NONE |
---|
1617 | CALL getin_p('ECUREUIL',ecureuil) |
---|
1618 | ! |
---|
1619 | !Config Key = ALLOC_MIN |
---|
1620 | !Config Desc = allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
1621 | !Config if = OK_STOMATE |
---|
1622 | !Config Def = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef |
---|
1623 | !Config Help = |
---|
1624 | !Config Units = |
---|
1625 | CALL getin_p('ALLOC_MIN',alloc_min) |
---|
1626 | ! |
---|
1627 | !Config Key = ALLOC_MAX |
---|
1628 | !Config Desc = |
---|
1629 | !Config if = OK_STOMATE |
---|
1630 | !Config Def = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef |
---|
1631 | !Config Help = |
---|
1632 | !Config Units = |
---|
1633 | CALL getin_p('ALLOC_MAX',alloc_max) |
---|
1634 | ! |
---|
1635 | !Config Key = DEMI_ALLOC |
---|
1636 | !Config Desc = |
---|
1637 | !Config if = OK_STOMATE |
---|
1638 | !Config Def = undef, 5., 5., 5., 5., 5., 5., 5., 5., undef, undef, undef, undef |
---|
1639 | !Config Help = |
---|
1640 | !Config Units = |
---|
1641 | CALL getin_p('DEMI_ALLOC',demi_alloc) |
---|
1642 | |
---|
1643 | !>> DS new for merge in the trunk |
---|
1644 | ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla |
---|
1645 | ! |
---|
1646 | !Config Key = LEAFLIFE_TAB |
---|
1647 | !Config Desc = |
---|
1648 | !Config if = OK_STOMATE |
---|
1649 | !Config Def = undef, .5, 2.,.33, 1., 2.,.33, 2., 2., 2., 2., 2., 2. |
---|
1650 | !Config Help = |
---|
1651 | !Config Units = |
---|
1652 | CALL getin_p('LEAFLIFE_TAB',leaflife_tab) |
---|
1653 | |
---|
1654 | !- |
---|
1655 | ! Phenology : Senescence |
---|
1656 | !- |
---|
1657 | ! |
---|
1658 | !Config Key = LEAFFALL |
---|
1659 | !Config Desc = length of death of leaves, tabulated |
---|
1660 | !Config if = OK_STOMATE |
---|
1661 | !Config Def = undef, undef, 10., undef, undef, 10., undef,10., 10., 10., 10., 10., 10. |
---|
1662 | !Config Help = |
---|
1663 | !Config Units = days (d) |
---|
1664 | CALL getin_p('LEAFFALL',leaffall) |
---|
1665 | ! |
---|
1666 | !Config Key = LEAFAGECRIT |
---|
1667 | !Config Desc = critical leaf age, tabulated (d) |
---|
1668 | !Config if = OK_STOMATE |
---|
1669 | !Config Def = undef, 730., 180., 910., 730., 180., 910.,180., 180., 120., 120., 90., 90. |
---|
1670 | !Config Help = |
---|
1671 | !Config Units = days (d) |
---|
1672 | CALL getin_p('LEAFAGECRIT',leafagecrit) |
---|
1673 | ! |
---|
1674 | !Config Key = SENESCENCE_TYPE |
---|
1675 | !Config Desc = type of senescence, tabulated |
---|
1676 | !Config if = OK_STOMATE |
---|
1677 | !Config Def = 'none ', 'none ', 'dry ', 'none ', 'none ', 'cold ', 'none ', 'cold ', 'cold ', 'mixed ','mixed ', 'mixed ', 'mixed ' |
---|
1678 | !Config Help = |
---|
1679 | !Config Units = NONE |
---|
1680 | CALL getin('SENESCENCE_TYPE', senescence_type) |
---|
1681 | ! |
---|
1682 | !Config Key = SENESCENCE_HUM |
---|
1683 | !Config Desc = critical relative moisture availability for senescence |
---|
1684 | !Config if = OK_STOMATE |
---|
1685 | !Config Def = undef, undef, .3, undef, undef, undef, undef, undef, undef, .2, .2, .3, .2 |
---|
1686 | !Config Help = |
---|
1687 | !Config Units = |
---|
1688 | CALL getin_p('SENESCENCE_HUM', senescence_hum) |
---|
1689 | ! |
---|
1690 | !Config Key = NOSENESCENCE_HUM |
---|
1691 | !Config Desc = relative moisture availability above which there is no humidity-related senescence |
---|
1692 | !Config if = OK_STOMATE |
---|
1693 | !Config Def = undef, undef, .8, undef, undef, undef, undef, undef, undef, .3, .3, .3, .3 |
---|
1694 | !Config Help = |
---|
1695 | !Config Units = |
---|
1696 | CALL getin_p('NOSENESCENCE_HUM', nosenescence_hum) |
---|
1697 | ! |
---|
1698 | !Config Key = MAX_TURNOVER_TIME |
---|
1699 | !Config Desc = maximum turnover time for grasse |
---|
1700 | !Config if = OK_STOMATE |
---|
1701 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 80., 80., 80., 80. |
---|
1702 | !Config Help = |
---|
1703 | !Config Units = days (d) |
---|
1704 | CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time) |
---|
1705 | ! |
---|
1706 | !Config Key = MIN_TURNOVER_TIME |
---|
1707 | !Config Desc = minimum turnover time for grasse |
---|
1708 | !Config if = OK_STOMATE |
---|
1709 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 10., 10., 10., 10. |
---|
1710 | !Config Help = |
---|
1711 | !Config Units = days (d) |
---|
1712 | CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time) |
---|
1713 | ! |
---|
1714 | !Config Key = MIN_LEAF_AGE_FOR_SENESCENCE |
---|
1715 | !Config Desc = minimum leaf age to allow senescence g |
---|
1716 | !Config if = OK_STOMATE |
---|
1717 | !Config Def = undef, undef, 90., undef, undef, 90., undef, 60., 60., 30., 30., 30., 30. |
---|
1718 | !Config Help = |
---|
1719 | !Config Units = days ? |
---|
1720 | CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE', min_leaf_age_for_senescence) |
---|
1721 | ! |
---|
1722 | !Config Key = SENESCENCE_TEMP_C |
---|
1723 | !Config Desc = critical temperature for senescence (C), constant c of aT^2+bT+c, tabulated |
---|
1724 | !Config if = OK_STOMATE |
---|
1725 | !Config Def = undef, undef, undef, undef, undef, 12., undef, 7., 2., -1.375, 5., 5., 10. |
---|
1726 | !Config Help = |
---|
1727 | !Config Units = NONE |
---|
1728 | CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c) |
---|
1729 | ! |
---|
1730 | !Config Key = SENESCENCE_TEMP_B |
---|
1731 | !Config Desc = critical temperature for senescence (C), constant b of aT^2+bT+c ,tabulated |
---|
1732 | !Config if = OK_STOMATE |
---|
1733 | !Config Def = undef, undef, undef, undef, undef, 0., undef, 0., 0., .1, 0., 0., 0. |
---|
1734 | !Config Help = |
---|
1735 | !Config Units = NONE |
---|
1736 | CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b) |
---|
1737 | ! |
---|
1738 | !Config Key = SENESCENCE_TEMP_A |
---|
1739 | !Config Desc = critical temperature for senescence (C), constant a of aT^2+bT+c , tabulated |
---|
1740 | !Config if = OK_STOMATE |
---|
1741 | !Config Def = undef, undef, undef, undef, undef, 0., undef, 0., 0.,.00375, 0., 0., 0. |
---|
1742 | !Config Help = |
---|
1743 | !Config Units = NONE |
---|
1744 | CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a) |
---|
1745 | !- |
---|
1746 | ! DGVM |
---|
1747 | !- |
---|
1748 | ! |
---|
1749 | !Config Key = RESIDENCE_TIME |
---|
1750 | !Config Desc = residence time of trees |
---|
1751 | !Config if = OK_DGVM AND .NOT. LPJ_GAP_CONST_MORT |
---|
1752 | !Config Def = undef, 30.0, 30.0, 40.0, 40.0, 40.0, 80.0, 80.0, 80.0, 0.0, 0.0, 0.0, 0.0 |
---|
1753 | !Config Help = |
---|
1754 | !Config Units = years (y) |
---|
1755 | CALL getin_p('RESIDENCE_TIME',residence_time) |
---|
1756 | ! |
---|
1757 | !Config Key = TMIN_CRIT |
---|
1758 | !Config Desc = critical tmin, tabulated (C) |
---|
1759 | !Config if = OK_STOMATE |
---|
1760 | !Config Def = undef, 0.0, 0.0, -30.0, -14.0, -30.0, -45.0, -45.0, undef, undef, undef, undef, undef |
---|
1761 | !Config Help = |
---|
1762 | !Config Units = Celsius degrees |
---|
1763 | CALL getin_p('TMIN_CRIT',tmin_crit) |
---|
1764 | ! |
---|
1765 | !Config Key = TCM_CRIT |
---|
1766 | !Config Desc = critical tcm, tabulated (C) |
---|
1767 | !Config if = OK_STOMATE |
---|
1768 | !Config Def = undef, undef, undef, 5.0, 15.5, 15.5, -8.0, -8.0, -8.0, undef, undef, undef, undef |
---|
1769 | !Config Help = |
---|
1770 | !Config Units = Celsius degrees |
---|
1771 | CALL getin_p('TCM_CRIT',tcm_crit) |
---|
1772 | |
---|
1773 | first_call = .FALSE. |
---|
1774 | |
---|
1775 | ENDIF |
---|
1776 | |
---|
1777 | END SUBROUTINE getin_stomate_pft_parameters |
---|
1778 | ! |
---|
1779 | != |
---|
1780 | ! |
---|
1781 | SUBROUTINE pft_parameters_clear |
---|
1782 | |
---|
1783 | l_first_define_pft = .TRUE. |
---|
1784 | |
---|
1785 | IF(ALLOCATED(pft_to_mtc))DEALLOCATE(pft_to_mtc) |
---|
1786 | IF(ALLOCATED(PFT_name))DEALLOCATE(PFT_name) |
---|
1787 | !- |
---|
1788 | !>> DS new for merge in the trunk ! 15/06/2011 |
---|
1789 | ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver' |
---|
1790 | IF(ALLOCATED(is_deciduous))DEALLOCATE(is_deciduous) |
---|
1791 | IF(ALLOCATED(is_evergreen))DEALLOCATE(is_evergreen) |
---|
1792 | IF(ALLOCATED(leaflife_tab))DEALLOCATE(leaflife_tab) |
---|
1793 | IF(ALLOCATED(is_c3))DEALLOCATE(is_c3) |
---|
1794 | !- |
---|
1795 | IF(ALLOCATED(veget_ori_fixed_test_1))DEALLOCATE(veget_ori_fixed_test_1) |
---|
1796 | IF(ALLOCATED(llaimax))DEALLOCATE(llaimax) |
---|
1797 | IF(ALLOCATED(llaimin))DEALLOCATE(llaimin) |
---|
1798 | IF(ALLOCATED(height_presc))DEALLOCATE(height_presc) |
---|
1799 | IF(ALLOCATED(type_of_lai))DEALLOCATE(type_of_lai) |
---|
1800 | IF(ALLOCATED(is_tree))DEALLOCATE(is_tree) |
---|
1801 | !- |
---|
1802 | IF(ALLOCATED(leaf_tab))DEALLOCATE(leaf_tab) |
---|
1803 | IF(ALLOCATED(sla))DEALLOCATE(sla) |
---|
1804 | IF(ALLOCATED(natural))DEALLOCATE(natural) |
---|
1805 | !- |
---|
1806 | IF(ALLOCATED(is_c4))DEALLOCATE(is_c4) |
---|
1807 | IF(ALLOCATED(gsslope))DEALLOCATE(gsslope) |
---|
1808 | IF(ALLOCATED(gsoffset))DEALLOCATE(gsoffset) |
---|
1809 | IF(ALLOCATED(vcmax_fix))DEALLOCATE(vcmax_fix) |
---|
1810 | IF(ALLOCATED(vjmax_fix))DEALLOCATE(vjmax_fix) |
---|
1811 | IF(ALLOCATED(co2_tmin_fix))DEALLOCATE(co2_tmin_fix) |
---|
1812 | IF(ALLOCATED(co2_topt_fix))DEALLOCATE(co2_topt_fix) |
---|
1813 | IF(ALLOCATED(co2_tmax_fix))DEALLOCATE(co2_tmax_fix) |
---|
1814 | !- |
---|
1815 | IF(ALLOCATED(ext_coeff))DEALLOCATE(ext_coeff) |
---|
1816 | IF(ALLOCATED(vcmax_opt))DEALLOCATE(vcmax_opt) |
---|
1817 | IF(ALLOCATED(vjmax_opt))DEALLOCATE(vjmax_opt) |
---|
1818 | IF(ALLOCATED(tphoto_min_a))DEALLOCATE(tphoto_min_a) |
---|
1819 | IF(ALLOCATED(tphoto_min_b))DEALLOCATE(tphoto_min_b) |
---|
1820 | IF(ALLOCATED(tphoto_min_c))DEALLOCATE(tphoto_min_c) |
---|
1821 | IF(ALLOCATED(tphoto_opt_a))DEALLOCATE(tphoto_opt_a) |
---|
1822 | IF(ALLOCATED(tphoto_opt_b))DEALLOCATE(tphoto_opt_b) |
---|
1823 | IF(ALLOCATED(tphoto_opt_c))DEALLOCATE(tphoto_opt_c) |
---|
1824 | IF(ALLOCATED(tphoto_max_a))DEALLOCATE(tphoto_max_a) |
---|
1825 | IF(ALLOCATED(tphoto_max_b))DEALLOCATE(tphoto_max_b) |
---|
1826 | IF(ALLOCATED(tphoto_max_c))DEALLOCATE(tphoto_max_c) |
---|
1827 | !- |
---|
1828 | IF(ALLOCATED(maint_resp_slope))DEALLOCATE(maint_resp_slope) |
---|
1829 | IF(ALLOCATED(maint_resp_slope_c))DEALLOCATE(maint_resp_slope_c) |
---|
1830 | IF(ALLOCATED(maint_resp_slope_b))DEALLOCATE(maint_resp_slope_b) |
---|
1831 | IF(ALLOCATED(maint_resp_slope_a))DEALLOCATE(maint_resp_slope_a) |
---|
1832 | IF(ALLOCATED(coeff_maint_zero))DEALLOCATE(coeff_maint_zero) |
---|
1833 | IF(ALLOCATED(cm_zero_leaf))DEALLOCATE(cm_zero_leaf) |
---|
1834 | IF(ALLOCATED(cm_zero_sapabove))DEALLOCATE(cm_zero_sapabove) |
---|
1835 | IF(ALLOCATED(cm_zero_sapbelow))DEALLOCATE(cm_zero_sapbelow) |
---|
1836 | IF(ALLOCATED(cm_zero_heartabove))DEALLOCATE(cm_zero_heartabove) |
---|
1837 | IF(ALLOCATED(cm_zero_heartbelow))DEALLOCATE(cm_zero_heartbelow) |
---|
1838 | IF(ALLOCATED(cm_zero_root))DEALLOCATE(cm_zero_root) |
---|
1839 | IF(ALLOCATED(cm_zero_fruit))DEALLOCATE(cm_zero_fruit) |
---|
1840 | IF(ALLOCATED(cm_zero_carbres))DEALLOCATE(cm_zero_carbres) |
---|
1841 | !- |
---|
1842 | IF(ALLOCATED(flam))DEALLOCATE(flam) |
---|
1843 | IF(ALLOCATED(resist))DEALLOCATE(resist) |
---|
1844 | !- |
---|
1845 | IF(ALLOCATED(coeff_lcchange_1))DEALLOCATE(coeff_lcchange_1) |
---|
1846 | IF(ALLOCATED(coeff_lcchange_10))DEALLOCATE(coeff_lcchange_10) |
---|
1847 | IF(ALLOCATED(coeff_lcchange_100))DEALLOCATE(coeff_lcchange_100) |
---|
1848 | !- |
---|
1849 | IF(ALLOCATED(lai_max)) DEALLOCATE(lai_max) |
---|
1850 | IF(ALLOCATED(pheno_model))DEALLOCATE(pheno_model) |
---|
1851 | IF(ALLOCATED(pheno_type))DEALLOCATE(pheno_type) |
---|
1852 | !- |
---|
1853 | IF(ALLOCATED(pheno_gdd_crit_c))DEALLOCATE(pheno_gdd_crit_c) |
---|
1854 | IF(ALLOCATED(pheno_gdd_crit_b))DEALLOCATE(pheno_gdd_crit_b) |
---|
1855 | IF(ALLOCATED(pheno_gdd_crit_a))DEALLOCATE(pheno_gdd_crit_a) |
---|
1856 | IF(ALLOCATED(pheno_gdd_crit))DEALLOCATE(pheno_gdd_crit) |
---|
1857 | IF(ALLOCATED(ngd_crit))DEALLOCATE(ngd_crit) |
---|
1858 | IF(ALLOCATED(ncdgdd_temp))DEALLOCATE(ncdgdd_temp) |
---|
1859 | IF(ALLOCATED(hum_frac))DEALLOCATE(hum_frac) |
---|
1860 | IF(ALLOCATED(lowgpp_time))DEALLOCATE(lowgpp_time) |
---|
1861 | IF(ALLOCATED(hum_min_time))DEALLOCATE(hum_min_time) |
---|
1862 | IF(ALLOCATED(tau_sap))DEALLOCATE(tau_sap) |
---|
1863 | IF(ALLOCATED(tau_fruit))DEALLOCATE(tau_fruit) |
---|
1864 | IF(ALLOCATED(ecureuil))DEALLOCATE(ecureuil) |
---|
1865 | IF(ALLOCATED(alloc_min))DEALLOCATE(alloc_min) |
---|
1866 | IF(ALLOCATED(alloc_max))DEALLOCATE(alloc_max) |
---|
1867 | IF(ALLOCATED(demi_alloc))DEALLOCATE(demi_alloc) |
---|
1868 | !- |
---|
1869 | IF(ALLOCATED(leaffall))DEALLOCATE(leaffall) |
---|
1870 | IF(ALLOCATED(leafagecrit))DEALLOCATE(leafagecrit) |
---|
1871 | IF(ALLOCATED(senescence_type))DEALLOCATE(senescence_type) |
---|
1872 | IF(ALLOCATED(senescence_hum))DEALLOCATE(senescence_hum) |
---|
1873 | IF(ALLOCATED(nosenescence_hum))DEALLOCATE(nosenescence_hum) |
---|
1874 | IF(ALLOCATED(max_turnover_time))DEALLOCATE(max_turnover_time) |
---|
1875 | IF(ALLOCATED(min_turnover_time))DEALLOCATE(min_turnover_time) |
---|
1876 | IF(ALLOCATED(min_leaf_age_for_senescence))DEALLOCATE(min_leaf_age_for_senescence) |
---|
1877 | !- |
---|
1878 | IF(ALLOCATED(senescence_temp_c))DEALLOCATE(senescence_temp_c) |
---|
1879 | IF(ALLOCATED(senescence_temp_b))DEALLOCATE(senescence_temp_b) |
---|
1880 | IF(ALLOCATED(senescence_temp_a))DEALLOCATE(senescence_temp_a) |
---|
1881 | IF(ALLOCATED(senescence_temp))DEALLOCATE(senescence_temp) |
---|
1882 | !- |
---|
1883 | IF(ALLOCATED(residence_time))DEALLOCATE(residence_time) |
---|
1884 | IF(ALLOCATED(tmin_crit))DEALLOCATE(tmin_crit) |
---|
1885 | IF(ALLOCATED(tcm_crit))DEALLOCATE(tcm_crit) |
---|
1886 | !- |
---|
1887 | IF(ALLOCATED(rstruct_const))DEALLOCATE(rstruct_const) |
---|
1888 | IF(ALLOCATED(kzero))DEALLOCATE(kzero) |
---|
1889 | !- |
---|
1890 | IF(ALLOCATED(wmax_veg))DEALLOCATE(wmax_veg) |
---|
1891 | IF(ALLOCATED(humcste))DEALLOCATE(humcste) |
---|
1892 | !- |
---|
1893 | IF(ALLOCATED(snowa_ini))DEALLOCATE(snowa_ini) |
---|
1894 | IF(ALLOCATED(snowa_dec))DEALLOCATE(snowa_dec) |
---|
1895 | IF(ALLOCATED(alb_leaf_vis))DEALLOCATE(alb_leaf_vis) |
---|
1896 | IF(ALLOCATED(alb_leaf_nir))DEALLOCATE(alb_leaf_nir) |
---|
1897 | IF(ALLOCATED(alb_leaf))DEALLOCATE(alb_leaf) |
---|
1898 | !- |
---|
1899 | IF(ALLOCATED(pref_soil_veg_sand))DEALLOCATE(pref_soil_veg_sand) |
---|
1900 | IF(ALLOCATED(pref_soil_veg_loan))DEALLOCATE(pref_soil_veg_loan) |
---|
1901 | IF(ALLOCATED(pref_soil_veg_clay))DEALLOCATE(pref_soil_veg_clay) |
---|
1902 | IF(ALLOCATED(pref_soil_veg))DEALLOCATE(pref_soil_veg) |
---|
1903 | !- |
---|
1904 | IF(ALLOCATED(lai_initmin))DEALLOCATE(lai_initmin) |
---|
1905 | IF(ALLOCATED(tree))DEALLOCATE(tree) |
---|
1906 | IF(ALLOCATED(bm_sapl))DEALLOCATE(bm_sapl) |
---|
1907 | IF(ALLOCATED(migrate))DEALLOCATE(migrate) |
---|
1908 | IF(ALLOCATED(maxdia))DEALLOCATE(maxdia) |
---|
1909 | IF(ALLOCATED(cn_sapl))DEALLOCATE(cn_sapl) |
---|
1910 | IF(ALLOCATED(leaf_timecst))DEALLOCATE(leaf_timecst) |
---|
1911 | !- |
---|
1912 | IF(ALLOCATED(throughfall_by_pft))DEALLOCATE(throughfall_by_pft) |
---|
1913 | IF(ALLOCATED(rveg_pft))DEALLOCATE(rveg_pft) |
---|
1914 | |
---|
1915 | END SUBROUTINE pft_parameters_clear |
---|
1916 | |
---|
1917 | END MODULE pft_parameters |
---|