1 | ! ================================================================================================================================= |
---|
2 | ! MODULE : pft_parameters |
---|
3 | ! |
---|
4 | ! CONTACT : orchidee-help _at_ ipsl.jussieu.fr |
---|
5 | ! |
---|
6 | ! LICENCE : IPSL (2011) |
---|
7 | ! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC |
---|
8 | ! |
---|
9 | !>\BRIEF This module initializes all the pft parameters in function of the |
---|
10 | !! number of vegetation types and of the values chosen by the user. |
---|
11 | !! |
---|
12 | !!\n DESCRIPTION: This module allocates and initializes the pft parameters in function of the number of pfts |
---|
13 | !! and the values of the parameters. \n |
---|
14 | !! The number of PFTs is read in intersurf.f90 (subroutine intsurf_config). \n |
---|
15 | !! Then we can initialize the parameters. \n |
---|
16 | !! This module is the result of the merge of constantes_co2, constantes_veg, stomate_constants.\n |
---|
17 | !! |
---|
18 | !! RECENT CHANGE(S): Josefine Ghattas 2013 : The declaration part has been extracted and moved to module pft_parameters_var |
---|
19 | !! |
---|
20 | !! REFERENCE(S) : None |
---|
21 | !! |
---|
22 | !! SVN : |
---|
23 | !! $HeadURL: $ |
---|
24 | !! $Date: 2015-02-22 16:18:16 +0100 (Sun, 22 Feb 2015) $ |
---|
25 | !! $Revision: 2555 $ |
---|
26 | !! \n |
---|
27 | !_ ================================================================================================================================ |
---|
28 | |
---|
29 | MODULE pft_parameters |
---|
30 | |
---|
31 | USE pft_parameters_var |
---|
32 | USE constantes_mtc |
---|
33 | USE constantes |
---|
34 | USE ioipsl |
---|
35 | USE ioipsl_para |
---|
36 | USE defprec |
---|
37 | ! tzjwb |
---|
38 | USE vertical_soil_var |
---|
39 | |
---|
40 | IMPLICIT NONE |
---|
41 | |
---|
42 | CONTAINS |
---|
43 | ! |
---|
44 | |
---|
45 | !! ================================================================================================================================ |
---|
46 | !! SUBROUTINE : pft_parameters_main |
---|
47 | !! |
---|
48 | !>\BRIEF This subroutine initializes all the pft parameters in function of the |
---|
49 | !! number of vegetation types chosen by the user. |
---|
50 | !! |
---|
51 | !! DESCRIPTION : This subroutine is called after the reading of the number of PFTS and the options |
---|
52 | !! activated by the user in the configuration files. (structure active_flags) \n |
---|
53 | !! The allocation is done just before reading the correspondence table between PFTs and MTCs |
---|
54 | !! defined by the user in the configuration file.\n |
---|
55 | !! With the correspondence table, the subroutine can initialize the pft parameters in function |
---|
56 | !! of the flags activated (ok_sechiba, ok_stomate, ok_co2, routing, new_hydrol...) in order to |
---|
57 | !! optimize the memory allocation. \n |
---|
58 | !! If the number of PFTs and pft_to_mtc are not found, the standard configuration will be used |
---|
59 | !! (13 PFTs, PFT = MTC). \n |
---|
60 | !! Some restrictions : the pft 1 can only be the bare soil and it is unique. \n |
---|
61 | !! Algorithm : Build new PFT from 13 generic-PFT or meta-classes. |
---|
62 | !! 1. Read the number of PFTs in "run.def". If nothing is found, it is assumed that the user intend to use |
---|
63 | !! the standard of PFTs (13). |
---|
64 | !! 2. Read the index vector in "run.def". The index vector associates one PFT to one meta-classe (or generic PFT). |
---|
65 | !! When the association is done, the PFT defined by the user inherited the default values from the meta classe. |
---|
66 | !! If nothing is found, it is assumed to use the standard index vector (PFT = MTC). |
---|
67 | !! 3. Check consistency |
---|
68 | !! 4. Memory allocation and initialization. |
---|
69 | !! 5. The parameters are read in the configuration file in intsurf_config (intersurf module). |
---|
70 | !! |
---|
71 | !! RECENT CHANGE(S): None |
---|
72 | !! |
---|
73 | !! MAIN OUTPUT VARIABLE(S): None |
---|
74 | !! |
---|
75 | !! REFERENCE(S) : None |
---|
76 | !! |
---|
77 | !! FLOWCHART : None |
---|
78 | !! \n |
---|
79 | !_ ================================================================================================================================ |
---|
80 | |
---|
81 | SUBROUTINE pft_parameters_main(active_flags) |
---|
82 | |
---|
83 | IMPLICIT NONE |
---|
84 | |
---|
85 | !! 0. Variables and parameters declaration |
---|
86 | |
---|
87 | !! 0.1 Input variables |
---|
88 | |
---|
89 | TYPE(control_type),INTENT(in) :: active_flags !! What parts of the code are activated ? (true/false) |
---|
90 | |
---|
91 | !! 0.4 Local variables |
---|
92 | |
---|
93 | INTEGER(i_std) :: j !! Index (unitless) |
---|
94 | |
---|
95 | !_ ================================================================================================================================ |
---|
96 | |
---|
97 | ! |
---|
98 | ! PFT global |
---|
99 | ! |
---|
100 | |
---|
101 | IF(l_first_pft_parameters) THEN |
---|
102 | |
---|
103 | !! 1. First time step |
---|
104 | IF(long_print) THEN |
---|
105 | WRITE(numout,*) 'l_first_pft_parameters :we read the parameters from the def files' |
---|
106 | ENDIF |
---|
107 | ! tzjwb active sinon plante |
---|
108 | ! IF ( active_flags%hydrol_cwrr ) THEN |
---|
109 | |
---|
110 | !! 2.1 Read the flag ok_throughfall_by_pft to know if |
---|
111 | !! we have to use the parameter throughfall_by_pft |
---|
112 | |
---|
113 | !Config Key = OK_THROUGHFALL_PFT |
---|
114 | !Config Desc = Activate use of PERCENT_THROUGHFALL_PFT |
---|
115 | !Config If = HYDROL_CWRR |
---|
116 | !Config Def = FALSE |
---|
117 | !Config Help = If NOT OFF_LINE_MODE it is always TRUE (coupled with a GCM) |
---|
118 | !Config Units = [FLAG] |
---|
119 | ! IF ( .NOT. OFF_LINE_MODE ) ok_throughfall_by_pft = .TRUE. |
---|
120 | ok_throughfall_by_pft = .TRUE. |
---|
121 | CALL getin_p('OK_THROUGHFALL_PFT',ok_throughfall_by_pft) |
---|
122 | |
---|
123 | ! END IF |
---|
124 | |
---|
125 | !! 2.2 Memory allocation for the pfts-parameters |
---|
126 | CALL pft_parameters_alloc(active_flags) |
---|
127 | |
---|
128 | !! 3. Correspondance table |
---|
129 | |
---|
130 | !! 3.1 Initialisation of the correspondance table |
---|
131 | !! Initialisation of the correspondance table |
---|
132 | IF (nvm == nvmc) THEN |
---|
133 | WRITE(numout,*) 'Message to the user : we will use ORCHIDEE to its standard configuration' |
---|
134 | pft_to_mtc = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /) |
---|
135 | ELSE |
---|
136 | pft_to_mtc(:) = undef_int |
---|
137 | ENDIF !(nvm == nvmc) |
---|
138 | |
---|
139 | !! 3.2 Reading of the conrrespondance table in the .def file |
---|
140 | ! |
---|
141 | !Config Key = PFT_TO_MTC |
---|
142 | !Config Desc = correspondance array linking a PFT to MTC |
---|
143 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
144 | !Config Def = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 |
---|
145 | !Config Help = |
---|
146 | !Config Units = [-] |
---|
147 | CALL getin_p('PFT_TO_MTC',pft_to_mtc) |
---|
148 | |
---|
149 | !! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array |
---|
150 | !! If the configuration is wrong, send a error message to the user. |
---|
151 | IF(nvm /= nvmc ) THEN |
---|
152 | ! |
---|
153 | IF(pft_to_mtc(1) == undef_int) THEN |
---|
154 | CALL ipslerr_p (3,'pft_parameters', & |
---|
155 | 'The array PFT_TO_MTC is empty','','') |
---|
156 | ENDIF !(pft_to_mtc(1) == undef_int) |
---|
157 | ! |
---|
158 | ENDIF !(nvm /= nvmc ) |
---|
159 | |
---|
160 | !! 3.4 Some error messages |
---|
161 | |
---|
162 | !! 3.4.1 What happened if pft_to_mtc(j) > nvmc or pft_to_mtc(j) <=0 (if the mtc doesn't exist)? |
---|
163 | DO j = 1, nvm ! Loop over # PFTs |
---|
164 | ! |
---|
165 | IF( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) ) THEN |
---|
166 | WRITE(numout,*) 'pft_to_mtc(j),j,nvmc: ',pft_to_mtc(j),j,nvmc,nvm |
---|
167 | CALL ipslerr_p (3,'pft_parameters', & |
---|
168 | 'the metaclass chosen does not exist','','') |
---|
169 | ENDIF !( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) ) |
---|
170 | ! |
---|
171 | ENDDO ! Loop over # PFTs |
---|
172 | |
---|
173 | |
---|
174 | !! 3.4.2 Check if pft_to_mtc(1) = 1 |
---|
175 | IF(pft_to_mtc(1) /= 1) THEN |
---|
176 | ! |
---|
177 | CALL ipslerr_p (3,'pft_parameters', & |
---|
178 | 'the first pft has to be the bare soil','','') |
---|
179 | ! |
---|
180 | ELSE |
---|
181 | ! |
---|
182 | DO j = 2,nvm ! Loop over # PFTs different from bare soil |
---|
183 | ! |
---|
184 | IF(pft_to_mtc(j) == 1) THEN |
---|
185 | CALL ipslerr_p (3,'pft_parameters', & |
---|
186 | 'only pft_to_mtc(1) has to be the bare soil','','') |
---|
187 | ENDIF ! (pft_to_mtc(j) == 1) |
---|
188 | ! |
---|
189 | ENDDO ! Loop over # PFTs different from bare soil |
---|
190 | ! |
---|
191 | ENDIF !(pft_to_mtc(1) /= 1) |
---|
192 | |
---|
193 | |
---|
194 | !! 4.Initialisation of the pfts-parameters |
---|
195 | CALL pft_parameters_init(active_flags) |
---|
196 | |
---|
197 | !! 5. Useful data |
---|
198 | |
---|
199 | !! 5.1 Read the name of the PFTs given by the user |
---|
200 | ! |
---|
201 | !Config Key = PFT_NAME |
---|
202 | !Config Desc = Name of a PFT |
---|
203 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
204 | !Config Def = bare ground, tropical broad-leaved evergreen, tropical broad-leaved raingreen, |
---|
205 | !Config temperate needleleaf evergreen, temperate broad-leaved evergreen temperate broad-leaved summergreen, |
---|
206 | !Config boreal needleleaf evergreen, boreal broad-leaved summergreen, boreal needleleaf summergreen, |
---|
207 | !Config C3 grass, C4 grass, C3 agriculture, C4 agriculture |
---|
208 | !Config Help = the user can name the new PFTs he/she introducing for new species |
---|
209 | !Config Units = [-] |
---|
210 | CALL getin_p('PFT_NAME',pft_name) |
---|
211 | |
---|
212 | !! 5.2 A useful message to the user: correspondance between the number of the pft |
---|
213 | !! and the name of the associated mtc |
---|
214 | DO j = 1,nvm ! Loop over # PFTs |
---|
215 | ! |
---|
216 | WRITE(numout,*) 'the PFT',j, 'called ', PFT_name(j),'corresponds to the MTC : ',MTC_name(pft_to_mtc(j)) |
---|
217 | ! |
---|
218 | ENDDO ! Loop over # PFTs |
---|
219 | |
---|
220 | |
---|
221 | !! 6. End message |
---|
222 | IF(long_print) THEN |
---|
223 | WRITE(numout,*) 'pft_parameters_done' |
---|
224 | ENDIF |
---|
225 | |
---|
226 | !! 8. Reset flag |
---|
227 | l_first_pft_parameters = .FALSE. |
---|
228 | |
---|
229 | ELSE |
---|
230 | |
---|
231 | RETURN |
---|
232 | |
---|
233 | ENDIF !(l_first_pft_parameters) |
---|
234 | |
---|
235 | END SUBROUTINE pft_parameters_main |
---|
236 | ! |
---|
237 | != |
---|
238 | ! |
---|
239 | |
---|
240 | !! ================================================================================================================================ |
---|
241 | !! SUBROUTINE : pft_parameters_init |
---|
242 | !! |
---|
243 | !>\BRIEF This subroutine initializes all the pft parameters by the default values |
---|
244 | !! of the corresponding metaclasse. |
---|
245 | !! |
---|
246 | !! DESCRIPTION : This subroutine is called after the reading of the number of PFTS and the correspondence |
---|
247 | !! table defined by the user in the configuration files. \n |
---|
248 | !! With the correspondence table, the subroutine can search the default values for the parameter |
---|
249 | !! even if the PFTs are classified in a random order (except bare soil). \n |
---|
250 | !! With the correspondence table, the subroutine can initialize the pft parameters in function |
---|
251 | !! of the flags activated (ok_sechiba, ok_stomate, ok_co2, routing, new_hydrol...).\n |
---|
252 | !! |
---|
253 | !! RECENT CHANGE(S): Didier Solyga : Simplified PFT loops : use vector notation. |
---|
254 | !! |
---|
255 | !! MAIN OUTPUT VARIABLE(S): None |
---|
256 | !! |
---|
257 | !! REFERENCE(S) : None |
---|
258 | !! |
---|
259 | !! FLOWCHART : None |
---|
260 | !! \n |
---|
261 | !_ ================================================================================================================================ |
---|
262 | |
---|
263 | SUBROUTINE pft_parameters_init(active_flags) |
---|
264 | |
---|
265 | IMPLICIT NONE |
---|
266 | |
---|
267 | !! 0. Variables and parameters declaration |
---|
268 | |
---|
269 | !! 0.1 Input variables |
---|
270 | |
---|
271 | TYPE(control_type),INTENT(in) :: active_flags !! What parts of the code are activated ? (true/false) |
---|
272 | |
---|
273 | !! 0.4 Local variables |
---|
274 | |
---|
275 | INTEGER(i_std) :: jv !! Index (unitless) |
---|
276 | !_ ================================================================================================================================ |
---|
277 | |
---|
278 | ! |
---|
279 | ! 1. Correspondance between the PFTs values and thes MTCs values |
---|
280 | ! |
---|
281 | |
---|
282 | |
---|
283 | ! 1.1 For parameters used anytime |
---|
284 | |
---|
285 | PFT_name(:) = MTC_name(pft_to_mtc(:)) |
---|
286 | ! |
---|
287 | ! Vegetation structure |
---|
288 | ! |
---|
289 | veget_ori_fixed_test_1(:) = veget_ori_fixed_mtc(pft_to_mtc(:)) |
---|
290 | llaimax(:) = llaimax_mtc(pft_to_mtc(:)) |
---|
291 | llaimin(:) = llaimin_mtc(pft_to_mtc(:)) |
---|
292 | height_presc(:) = height_presc_mtc(pft_to_mtc(:)) |
---|
293 | type_of_lai(:) = type_of_lai_mtc(pft_to_mtc(:)) |
---|
294 | natural(:) = natural_mtc(pft_to_mtc(:)) |
---|
295 | ! |
---|
296 | ! Water - sechiba |
---|
297 | ! |
---|
298 | If (active_flags%hydrol_cwrr ) THEN |
---|
299 | humcste(:) = humcste_cwrr(pft_to_mtc(:)) ! values for 2m soil depth |
---|
300 | ELSE |
---|
301 | humcste(:) = humcste_mtc(pft_to_mtc(:)) ! values for 4m soil depth |
---|
302 | END IF |
---|
303 | ! |
---|
304 | ! Soil - vegetation |
---|
305 | ! |
---|
306 | pref_soil_veg(:) = pref_soil_veg_mtc(pft_to_mtc(:)) |
---|
307 | ! |
---|
308 | ! Vegetation - age classes |
---|
309 | ! |
---|
310 | agec_group(:) = agec_group_mtc(pft_to_mtc(:)) |
---|
311 | ! |
---|
312 | ! Photosynthesis |
---|
313 | ! |
---|
314 | is_c4(:) = is_c4_mtc(pft_to_mtc(:)) |
---|
315 | vcmax_fix(:) = vcmax_fix_mtc(pft_to_mtc(:)) |
---|
316 | downregulation_co2_coeff(:) = downregulation_co2_coeff_mtc(pft_to_mtc(:)) |
---|
317 | E_KmC(:) = E_KmC_mtc(pft_to_mtc(:)) |
---|
318 | E_KmO(:) = E_KmO_mtc(pft_to_mtc(:)) |
---|
319 | E_gamma_star(:) = E_gamma_star_mtc(pft_to_mtc(:)) |
---|
320 | E_Vcmax(:) = E_Vcmax_mtc(pft_to_mtc(:)) |
---|
321 | E_Jmax(:) = E_Jmax_mtc(pft_to_mtc(:)) |
---|
322 | aSV(:) = aSV_mtc(pft_to_mtc(:)) |
---|
323 | bSV(:) = bSV_mtc(pft_to_mtc(:)) |
---|
324 | tphoto_min(:) = tphoto_min_mtc(pft_to_mtc(:)) |
---|
325 | tphoto_max(:) = tphoto_max_mtc(pft_to_mtc(:)) |
---|
326 | aSJ(:) = aSJ_mtc(pft_to_mtc(:)) |
---|
327 | bSJ(:) = bSJ_mtc(pft_to_mtc(:)) |
---|
328 | D_Vcmax(:) = D_Vcmax_mtc(pft_to_mtc(:)) |
---|
329 | D_Jmax(:) = D_Jmax_mtc(pft_to_mtc(:)) |
---|
330 | E_Rd(:) = E_Rd_mtc(pft_to_mtc(:)) |
---|
331 | Vcmax25(:) = Vcmax25_mtc(pft_to_mtc(:)) |
---|
332 | arJV(:) = arJV_mtc(pft_to_mtc(:)) |
---|
333 | brJV(:) = brJV_mtc(pft_to_mtc(:)) |
---|
334 | KmC25(:) = KmC25_mtc(pft_to_mtc(:)) |
---|
335 | KmO25(:) = KmO25_mtc(pft_to_mtc(:)) |
---|
336 | gamma_star25(:) = gamma_star25_mtc(pft_to_mtc(:)) |
---|
337 | a1(:) = a1_mtc(pft_to_mtc(:)) |
---|
338 | b1(:) = b1_mtc(pft_to_mtc(:)) |
---|
339 | g0(:) = g0_mtc(pft_to_mtc(:)) |
---|
340 | h_protons(:) = h_protons_mtc(pft_to_mtc(:)) |
---|
341 | fpsir(:) = fpsir_mtc(pft_to_mtc(:)) |
---|
342 | fQ(:) = fQ_mtc(pft_to_mtc(:)) |
---|
343 | fpseudo(:) = fpseudo_mtc(pft_to_mtc(:)) |
---|
344 | kp(:) = kp_mtc(pft_to_mtc(:)) |
---|
345 | alpha(:) = alpha_mtc(pft_to_mtc(:)) |
---|
346 | gbs(:) = gbs_mtc(pft_to_mtc(:)) |
---|
347 | theta(:) = theta_mtc(pft_to_mtc(:)) |
---|
348 | alpha_LL(:) = alpha_LL_mtc(pft_to_mtc(:)) |
---|
349 | ext_coeff(:) = ext_coeff_mtc(pft_to_mtc(:)) |
---|
350 | ! |
---|
351 | !! Define labels from physiologic characteristics |
---|
352 | ! |
---|
353 | leaf_tab(:) = leaf_tab_mtc(pft_to_mtc(:)) |
---|
354 | pheno_model(:) = pheno_model_mtc(pft_to_mtc(:)) |
---|
355 | ! |
---|
356 | is_tree(:) = .FALSE. |
---|
357 | DO jv = 1,nvm |
---|
358 | IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE. |
---|
359 | END DO |
---|
360 | ! |
---|
361 | is_deciduous(:) = .FALSE. |
---|
362 | DO jv = 1,nvm |
---|
363 | IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE. |
---|
364 | END DO |
---|
365 | ! |
---|
366 | is_evergreen(:) = .FALSE. |
---|
367 | DO jv = 1,nvm |
---|
368 | IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE. |
---|
369 | END DO |
---|
370 | ! |
---|
371 | is_needleleaf(:) = .FALSE. |
---|
372 | DO jv = 1,nvm |
---|
373 | IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE. |
---|
374 | END DO |
---|
375 | ! |
---|
376 | is_tropical(:) = is_tropical_mtc(pft_to_mtc(:)) |
---|
377 | is_temperate(:) = is_temperate_mtc(pft_to_mtc(:)) |
---|
378 | is_boreal(:) = is_boreal_mtc(pft_to_mtc(:)) |
---|
379 | |
---|
380 | ! 1.2 For sechiba parameters |
---|
381 | |
---|
382 | IF (active_flags%ok_sechiba) THEN |
---|
383 | ! |
---|
384 | ! Vegetation structure - sechiba |
---|
385 | ! |
---|
386 | rveg_pft(:) = rveg_mtc(pft_to_mtc(:)) |
---|
387 | ! |
---|
388 | ! Evapotranspiration - sechiba |
---|
389 | ! |
---|
390 | rstruct_const(:) = rstruct_const_mtc(pft_to_mtc(:)) |
---|
391 | kzero(:) = kzero_mtc(pft_to_mtc(:)) |
---|
392 | ! |
---|
393 | ! Water - sechiba |
---|
394 | ! |
---|
395 | wmax_veg(:) = wmax_veg_mtc(pft_to_mtc(:)) |
---|
396 | IF ( .NOT.(active_flags%hydrol_cwrr) .OR. (active_flags%hydrol_cwrr .AND. ok_throughfall_by_pft) ) THEN |
---|
397 | throughfall_by_pft(:) = throughfall_by_mtc(pft_to_mtc(:)) |
---|
398 | ENDIF |
---|
399 | ! |
---|
400 | ! Albedo - sechiba |
---|
401 | ! |
---|
402 | snowa_aged(:) = snowa_aged_mtc(pft_to_mtc(:)) |
---|
403 | snowa_dec(:) = snowa_dec_mtc(pft_to_mtc(:)) |
---|
404 | alb_leaf_vis(:) = alb_leaf_vis_mtc(pft_to_mtc(:)) |
---|
405 | alb_leaf_nir(:) = alb_leaf_nir_mtc(pft_to_mtc(:)) |
---|
406 | leaf_ssa(:,ivis) = leaf_ssa_vis_mtc(pft_to_mtc(:)) |
---|
407 | leaf_ssa(:,inir) = leaf_ssa_nir_mtc(pft_to_mtc(:)) |
---|
408 | leaf_psd(:,ivis) = leaf_psd_vis_mtc(pft_to_mtc(:)) |
---|
409 | leaf_psd(:,inir) = leaf_psd_nir_mtc(pft_to_mtc(:)) |
---|
410 | bgd_reflectance(:,ivis) = bgd_reflectance_vis_mtc(pft_to_mtc(:)) |
---|
411 | bgd_reflectance(:,inir) = bgd_reflectance_nir_mtc(pft_to_mtc(:)) |
---|
412 | tune_coupled (:) = tune_coupled_mtc(pft_to_mtc(:)) |
---|
413 | leaf_to_shoot_clumping(:) = leaf_to_shoot_clumping_mtc(pft_to_mtc(:)) |
---|
414 | lai_correction_factor(:) = lai_correction_factor_mtc(pft_to_mtc(:)) |
---|
415 | min_level_sep(:) = min_level_sep_mtc(pft_to_mtc(:)) |
---|
416 | ! |
---|
417 | ! Diffuco and hydrol_arch |
---|
418 | ! |
---|
419 | lai_top(:) = lai_top_mtc(pft_to_mtc(:)) |
---|
420 | |
---|
421 | ENDIF !(active_flags%ok_sechiba) |
---|
422 | |
---|
423 | ! 1.3 For BVOC parameters |
---|
424 | |
---|
425 | IF (active_flags%ok_inca) THEN |
---|
426 | ! |
---|
427 | ! Biogenic Volatile Organic Compounds |
---|
428 | ! |
---|
429 | em_factor_isoprene(:) = em_factor_isoprene_mtc(pft_to_mtc(:)) |
---|
430 | em_factor_monoterpene(:) = em_factor_monoterpene_mtc(pft_to_mtc(:)) |
---|
431 | em_factor_ORVOC(:) = em_factor_ORVOC_mtc(pft_to_mtc(:)) |
---|
432 | em_factor_OVOC(:) = em_factor_OVOC_mtc(pft_to_mtc(:)) |
---|
433 | em_factor_MBO(:) = em_factor_MBO_mtc(pft_to_mtc(:)) |
---|
434 | em_factor_methanol(:) = em_factor_methanol_mtc(pft_to_mtc(:)) |
---|
435 | em_factor_acetone(:) = em_factor_acetone_mtc(pft_to_mtc(:)) |
---|
436 | em_factor_acetal(:) = em_factor_acetal_mtc(pft_to_mtc(:)) |
---|
437 | em_factor_formal(:) = em_factor_formal_mtc(pft_to_mtc(:)) |
---|
438 | em_factor_acetic(:) = em_factor_acetic_mtc(pft_to_mtc(:)) |
---|
439 | em_factor_formic(:) = em_factor_formic_mtc(pft_to_mtc(:)) |
---|
440 | em_factor_no_wet(:) = em_factor_no_wet_mtc(pft_to_mtc(:)) |
---|
441 | em_factor_no_dry(:) = em_factor_no_dry_mtc(pft_to_mtc(:)) |
---|
442 | Larch(:) = Larch_mtc(pft_to_mtc(:)) |
---|
443 | !- |
---|
444 | ENDIF !(active_flags%ok_inca) |
---|
445 | |
---|
446 | ! 1.4 For stomate parameters |
---|
447 | |
---|
448 | IF (active_flags%ok_stomate) THEN |
---|
449 | ! |
---|
450 | ! Vegetation structure - stomate |
---|
451 | ! |
---|
452 | sla(:) = sla_mtc(pft_to_mtc(:)) |
---|
453 | lai_happy(:) = lai_happy_mtc(pft_to_mtc(:)) |
---|
454 | ! |
---|
455 | ! Allocation - stomate |
---|
456 | ! |
---|
457 | S0(:) = S0_mtc(pft_to_mtc(:)) |
---|
458 | ! |
---|
459 | ! Respiration - stomate |
---|
460 | ! |
---|
461 | maint_resp_slope_c(:) = maint_resp_slope_c_mtc(pft_to_mtc(:)) |
---|
462 | maint_resp_slope_b(:) = maint_resp_slope_b_mtc(pft_to_mtc(:)) |
---|
463 | maint_resp_slope_a(:) = maint_resp_slope_a_mtc(pft_to_mtc(:)) |
---|
464 | cm_zero_leaf(:) = cm_zero_leaf_mtc(pft_to_mtc(:)) |
---|
465 | cm_zero_sapabove(:) = cm_zero_sapabove_mtc(pft_to_mtc(:)) |
---|
466 | cm_zero_sapbelow(:) = cm_zero_sapbelow_mtc(pft_to_mtc(:)) |
---|
467 | cm_zero_heartabove(:) = cm_zero_heartabove_mtc(pft_to_mtc(:)) |
---|
468 | cm_zero_heartbelow(:) = cm_zero_heartbelow_mtc(pft_to_mtc(:)) |
---|
469 | cm_zero_root(:) = cm_zero_root_mtc(pft_to_mtc(:)) |
---|
470 | cm_zero_fruit(:) = cm_zero_fruit_mtc(pft_to_mtc(:)) |
---|
471 | coeff_maint_init(:) = coeff_maint_init_mtc(pft_to_mtc(:)) |
---|
472 | IF (active_flags%ok_functional_allocation) THEN |
---|
473 | ! Respiration (functional allocation stomate) |
---|
474 | frac_growthresp(:) = frac_growthresp_fun_all_mtc(pft_to_mtc(:)) |
---|
475 | cm_zero_carbres(:) = cm_zero_carbres_fun_all_mtc(pft_to_mtc(:)) |
---|
476 | cm_zero_labile(:) = cm_zero_labile_fun_all_mtc(pft_to_mtc(:)) |
---|
477 | ELSE |
---|
478 | ! Respiration (resource limitation stomate) |
---|
479 | frac_growthresp(:) = frac_growthresp_res_lim_mtc(pft_to_mtc(:)) |
---|
480 | cm_zero_carbres(:) = cm_zero_carbres_res_lim_mtc(pft_to_mtc(:)) |
---|
481 | cm_zero_labile(:) = cm_zero_labile_res_lim_mtc(pft_to_mtc(:)) |
---|
482 | ENDIF |
---|
483 | gpp_to_labile(:) = gpp_to_labile_mtc(pft_to_mtc(:)) |
---|
484 | |
---|
485 | ! |
---|
486 | ! Stand structure |
---|
487 | ! |
---|
488 | pipe_density(:) = pipe_density_mtc(pft_to_mtc(:)) |
---|
489 | pipe_tune1(:) = pipe_tune1_mtc(pft_to_mtc(:)) |
---|
490 | pipe_tune2(:) = pipe_tune2_mtc(pft_to_mtc(:)) |
---|
491 | pipe_tune3(:) = pipe_tune3_mtc(pft_to_mtc(:)) |
---|
492 | pipe_tune4(:) = pipe_tune4_mtc(pft_to_mtc(:)) |
---|
493 | tree_ff(:) = tree_ff_mtc(pft_to_mtc(:)) |
---|
494 | pipe_k1(:) = pipe_k1_mtc(pft_to_mtc(:)) |
---|
495 | pipe_tune_exp_coeff(:) = pipe_tune_exp_coeff_mtc(pft_to_mtc(:)) |
---|
496 | mass_ratio_heart_sap(:) = mass_ratio_heart_sap_mtc(pft_to_mtc(:)) |
---|
497 | lai_to_height(:) = lai_to_height_mtc(pft_to_mtc(:)) |
---|
498 | canopy_cover = canopy_cover_mtc(pft_to_mtc(:)) |
---|
499 | nmaxtrees(:) = nmaxtrees_mtc(pft_to_mtc(:)) |
---|
500 | height_init_min(:) = height_init_min_mtc(pft_to_mtc(:)) |
---|
501 | height_init_max(:) = height_init_max_mtc(pft_to_mtc(:)) |
---|
502 | alpha_self_thinning(:) = alpha_self_thinning_mtc(pft_to_mtc(:)) |
---|
503 | beta_self_thinning(:) = beta_self_thinning_mtc(pft_to_mtc(:)) |
---|
504 | fuelwood_diameter(:) = fuelwood_diameter_mtc(pft_to_mtc(:)) |
---|
505 | coppice_kill_be_wood(:) = coppice_kill_be_wood_mtc(pft_to_mtc(:)) |
---|
506 | |
---|
507 | ! |
---|
508 | ! Growth - stomate |
---|
509 | ! |
---|
510 | cn_leaf_prescribed(:) = cn_leaf_prescribed_mtc(pft_to_mtc(:)) |
---|
511 | fcn_wood(:) = fcn_wood_mtc(pft_to_mtc(:)) |
---|
512 | fcn_root(:) = fcn_root_mtc(pft_to_mtc(:)) |
---|
513 | k_latosa_max(:) = k_latosa_max_mtc(pft_to_mtc(:)) |
---|
514 | k_latosa_min(:) = k_latosa_min_mtc(pft_to_mtc(:)) |
---|
515 | fruit_alloc(:) = fruit_alloc_mtc(pft_to_mtc(:)) |
---|
516 | m_dv(:) = m_dv_mtc(pft_to_mtc(:)) |
---|
517 | lai_max_to_happy(:) = lai_max_to_happy_mtc(pft_to_mtc(:)) |
---|
518 | |
---|
519 | ! |
---|
520 | ! Hydraulic architecture - sechiba? |
---|
521 | ! |
---|
522 | k_root(:) = k_root_mtc(pft_to_mtc(:)) |
---|
523 | k_sap(:) = k_sap_mtc(pft_to_mtc(:)) |
---|
524 | k_leaf(:) = k_leaf_mtc(pft_to_mtc(:)) |
---|
525 | phi_leaf(:) = phi_leaf_mtc(pft_to_mtc(:)) |
---|
526 | phi_50(:) = phi_50_mtc(pft_to_mtc(:)) |
---|
527 | c_cavitation(:) = c_cavitation_mtc(pft_to_mtc(:)) |
---|
528 | phi_soil_tune(:) = phi_soil_tune_mtc(pft_to_mtc(:)) |
---|
529 | |
---|
530 | !--------------------------------------------------------------------------------------- |
---|
531 | ! Hydraulic architecture - tzjh |
---|
532 | |
---|
533 | gpsi(:)=gpsi_mtc(pft_to_mtc(:)) |
---|
534 | gpsi_50(:)=gpsi_50_mtc(pft_to_mtc(:)) |
---|
535 | gmax(:)=gmax_mtc(pft_to_mtc(:)) |
---|
536 | gmin(:)=gmin_mtc(pft_to_mtc(:)) |
---|
537 | |
---|
538 | kmax_leaf(:)=kmax_leaf_mtc(pft_to_mtc(:)) |
---|
539 | kmax_stem(:)=kmax_stem_mtc(pft_to_mtc(:)) |
---|
540 | kmax_root(:)=kmax_root_mtc(pft_to_mtc(:)) |
---|
541 | a_leaf(:)=a_leaf_mtc(pft_to_mtc(:)) |
---|
542 | a_stem(:)=a_stem_mtc(pft_to_mtc(:)) |
---|
543 | a_root(:)=a_root_mtc(pft_to_mtc(:)) |
---|
544 | P50_leaf(:)=P50_leaf_mtc(pft_to_mtc(:)) |
---|
545 | P50_stem(:)=P50_stem_mtc(pft_to_mtc(:)) |
---|
546 | P50_root(:)=P50_root_mtc(pft_to_mtc(:)) |
---|
547 | |
---|
548 | wood_density(:)=wood_density_mtc(pft_to_mtc(:)) |
---|
549 | w_density_stem(:)=w_density_stem_mtc(pft_to_mtc(:)) |
---|
550 | root_shoot_ratio(:)=root_shoot_ratio_mtc(pft_to_mtc(:)) |
---|
551 | rwc_root(:)=rwc_root_mtc(pft_to_mtc(:)) |
---|
552 | root_density(:)=root_density_mtc(pft_to_mtc(:)) |
---|
553 | LDMC(:)=LDMC_mtc(pft_to_mtc(:)) |
---|
554 | sla_hydro(:)=sla_hydro_mtc(pft_to_mtc(:)) |
---|
555 | |
---|
556 | cxyl(:)=cxyl_mtc(pft_to_mtc(:)) |
---|
557 | cr(:)=cr_mtc(pft_to_mtc(:)) |
---|
558 | cl(:)=cl_mtc(pft_to_mtc(:)) |
---|
559 | !--------------------------------------------------------------------------------------- |
---|
560 | |
---|
561 | ! |
---|
562 | ! Mortality - stomate_kill |
---|
563 | ! |
---|
564 | death_distribution_factor(:) = death_distribution_factor_mtc(pft_to_mtc(:)) |
---|
565 | npp_reset_value(:) = npp_reset_value_mtc(pft_to_mtc(:)) |
---|
566 | |
---|
567 | ! |
---|
568 | ! Fire - stomate |
---|
569 | ! |
---|
570 | flam(:) = flam_mtc(pft_to_mtc(:)) |
---|
571 | resist(:) = resist_mtc(pft_to_mtc(:)) |
---|
572 | ! |
---|
573 | ! Flux - LUC |
---|
574 | ! |
---|
575 | coeff_lcchange_s(:) = coeff_lcchange_s_mtc(pft_to_mtc(:)) |
---|
576 | coeff_lcchange_m(:) = coeff_lcchange_m_mtc(pft_to_mtc(:)) |
---|
577 | coeff_lcchange_l(:) = coeff_lcchange_l_mtc(pft_to_mtc(:)) |
---|
578 | ! |
---|
579 | ! Phenology |
---|
580 | ! |
---|
581 | ! |
---|
582 | ! 1. Stomate |
---|
583 | ! |
---|
584 | lai_max(:) = lai_max_mtc(pft_to_mtc(:)) |
---|
585 | pheno_type(:) = pheno_type_mtc(pft_to_mtc(:)) |
---|
586 | ! |
---|
587 | ! 2. Leaf Onset |
---|
588 | ! |
---|
589 | pheno_gdd_crit_c(:) = pheno_gdd_crit_c_mtc(pft_to_mtc(:)) |
---|
590 | pheno_gdd_crit_b(:) = pheno_gdd_crit_b_mtc(pft_to_mtc(:)) |
---|
591 | pheno_gdd_crit_a(:) = pheno_gdd_crit_a_mtc(pft_to_mtc(:)) |
---|
592 | ngd_crit(:) = ngd_crit_mtc(pft_to_mtc(:)) |
---|
593 | opti_kpheno_crit(:) = opti_kpheno_crit_mtc(pft_to_mtc(:)) |
---|
594 | ncdgdd_temp(:) = ncdgdd_temp_mtc(pft_to_mtc(:)) |
---|
595 | hum_frac(:) = hum_frac_mtc(pft_to_mtc(:)) |
---|
596 | hum_min_time(:) = hum_min_time_mtc(pft_to_mtc(:)) |
---|
597 | tau_sap(:) = tau_sap_mtc(pft_to_mtc(:)) |
---|
598 | tau_fruit(:) = tau_fruit_mtc(pft_to_mtc(:)) |
---|
599 | tau_root(:) = tau_root_mtc(pft_to_mtc(:)) |
---|
600 | tau_leaf(:) = tau_leaf_mtc(pft_to_mtc(:)) |
---|
601 | ecureuil(:) = ecureuil_mtc(pft_to_mtc(:)) |
---|
602 | alloc_min(:) = alloc_min_mtc(pft_to_mtc(:)) |
---|
603 | alloc_max(:) = alloc_max_mtc(pft_to_mtc(:)) |
---|
604 | demi_alloc(:) = demi_alloc_mtc(pft_to_mtc(:)) |
---|
605 | ! |
---|
606 | ! 3. Senescence |
---|
607 | ! |
---|
608 | leaffall(:) = leaffall_mtc(pft_to_mtc(:)) |
---|
609 | senescence_type(:) = senescence_type_mtc(pft_to_mtc(:)) |
---|
610 | senescence_hum(:) = senescence_hum_mtc(pft_to_mtc(:)) |
---|
611 | nosenescence_hum(:) = nosenescence_hum_mtc(pft_to_mtc(:)) |
---|
612 | max_turnover_time(:) = max_turnover_time_mtc(pft_to_mtc(:)) |
---|
613 | min_turnover_time(:) = min_turnover_time_mtc(pft_to_mtc(:)) |
---|
614 | min_leaf_age_for_senescence(:) = min_leaf_age_for_senescence_mtc(pft_to_mtc(:)) |
---|
615 | senescence_temp_c(:) = senescence_temp_c_mtc(pft_to_mtc(:)) |
---|
616 | senescence_temp_b(:) = senescence_temp_b_mtc(pft_to_mtc(:)) |
---|
617 | senescence_temp_a(:) = senescence_temp_a_mtc(pft_to_mtc(:)) |
---|
618 | gdd_senescence(:) = gdd_senescence_mtc(pft_to_mtc(:)) |
---|
619 | ! |
---|
620 | ! DGVM |
---|
621 | ! |
---|
622 | residence_time(:) = residence_time_mtc(pft_to_mtc(:)) |
---|
623 | tmin_crit(:) = tmin_crit_mtc(pft_to_mtc(:)) |
---|
624 | tcm_crit(:) = tcm_crit_mtc(pft_to_mtc(:)) |
---|
625 | mortality_min(:) = mortality_min_mtc(pft_to_mtc(:)) |
---|
626 | mortality_max(:) = mortality_max_mtc(pft_to_mtc(:)) |
---|
627 | ref_mortality(:) = ref_mortality_mtc(pft_to_mtc(:)) |
---|
628 | |
---|
629 | ! added by yitong yao in 07 Jan 2020 08:17 |
---|
630 | |
---|
631 | plc_kill_frac(:)=plc_kill_frac_mtc(pft_to_mtc(:)) |
---|
632 | ! added by yitong yao in 07 Jan 2020 08:17 |
---|
633 | |
---|
634 | ! added by yitong yao in 09 Feb 2020 22:56 |
---|
635 | mor_kill_frac(:) = mor_kill_frac_mtc(pft_to_mtc(:)) |
---|
636 | ! added by yitong yao in 09 Feb 2020 22:56 above line |
---|
637 | |
---|
638 | ! Season average |
---|
639 | ! |
---|
640 | ! Only an effect on the roots has been implemented for the |
---|
641 | ! GPP-based waterstress. We use tau_sap rather than tau_roots |
---|
642 | ! because we only want to implement the long term change in |
---|
643 | ! allocation owing to height-induced drought stress. Short |
---|
644 | ! term adaptation to drought is not accounted for (except |
---|
645 | ! for stomatal closure). |
---|
646 | tau_hum_growingseason(:) = tau_sap_mtc(pft_to_mtc(:)) |
---|
647 | DO jv = 2,nvm |
---|
648 | IF(.NOT. is_tree(jv)) THEN |
---|
649 | ! Grasses have no sapwood so use a constant instead of tau_sap |
---|
650 | tau_hum_growingseason(jv) = tau_hum_growingseason_grass |
---|
651 | ENDIF |
---|
652 | END DO |
---|
653 | |
---|
654 | ! Originally, dens_target was just used in the FM routines. |
---|
655 | ! Now, however, it is used for all forests. |
---|
656 | dens_target(:) = dens_target_mtc(pft_to_mtc(:)) |
---|
657 | |
---|
658 | ! |
---|
659 | ! FOREST MANAGEMENT |
---|
660 | ! |
---|
661 | IF (active_flags%forest_management & |
---|
662 | .OR. active_flags%ok_functional_allocation) THEN |
---|
663 | !!$ plantation(:) = plantation_mtc(pft_to_mtc(:)) |
---|
664 | !!$ fm_allo_a(:) = fm_allo_a_mtc(pft_to_mtc(:)) |
---|
665 | !!$ fm_allo_c(:) = fm_allo_c_mtc(pft_to_mtc(:)) |
---|
666 | !!$ fm_allo_d(:) = fm_allo_d_mtc(pft_to_mtc(:)) |
---|
667 | !!$ fm_allo_p(:) = fm_allo_p_mtc(pft_to_mtc(:)) |
---|
668 | !!$ fm_allo_q(:) = fm_allo_q_mtc(pft_to_mtc(:)) |
---|
669 | !!$ allo_crown_a0(:) = allo_crown_a0_mtc(pft_to_mtc(:)) |
---|
670 | !!$ allo_crown_a1(:) = allo_crown_a1_mtc(pft_to_mtc(:)) |
---|
671 | !!$ allo_crown_a2(:) = allo_crown_a2_mtc(pft_to_mtc(:)) |
---|
672 | !!$ decl_factor(:) = decl_factor_mtc(pft_to_mtc(:)) |
---|
673 | !!$ opt_factor(:) = opt_factor_mtc(pft_to_mtc(:)) |
---|
674 | h_first(:) = h_first_mtc(pft_to_mtc(:)) |
---|
675 | largest_tree_dia(:) = largest_tree_dia_mtc(pft_to_mtc(:)) |
---|
676 | thinstrat(:) = thinstrat_mtc(pft_to_mtc(:)) |
---|
677 | taumin(:) = taumin_mtc(pft_to_mtc(:)) |
---|
678 | taumax(:) = taumax_mtc(pft_to_mtc(:)) |
---|
679 | alpha_rdi_upper(:) = alpha_rdi_upper_mtc(pft_to_mtc(:)) |
---|
680 | beta_rdi_upper(:) = beta_rdi_upper_mtc(pft_to_mtc(:)) |
---|
681 | alpha_rdi_lower(:) = alpha_rdi_lower_mtc(pft_to_mtc(:)) |
---|
682 | beta_rdi_lower(:) = beta_rdi_lower_mtc(pft_to_mtc(:)) |
---|
683 | branch_ratio(:) = branch_ratio_mtc(pft_to_mtc(:)) |
---|
684 | branch_harvest(:) = branch_harvest_mtc(pft_to_mtc(:)) |
---|
685 | coppice_diameter(:) = coppice_diameter_mtc(pft_to_mtc(:)) |
---|
686 | shoots_per_stool(:) = shoots_per_stool_mtc(pft_to_mtc(:)) |
---|
687 | src_rot_length(:) = src_rot_length_mtc(pft_to_mtc(:)) |
---|
688 | src_nrots(:) = src_nrots_mtc(pft_to_mtc(:)) |
---|
689 | deleuze_a(:) = deleuze_a_mtc(pft_to_mtc(:)) |
---|
690 | deleuze_b(:) = deleuze_b_mtc(pft_to_mtc(:)) |
---|
691 | deleuze_p_all(:) = deleuze_p_all_mtc(pft_to_mtc(:)) |
---|
692 | deleuze_p_coppice(:) = deleuze_p_coppice_mtc(pft_to_mtc(:)) |
---|
693 | recruitment_light_threshold(:) = recruitment_light_threshold_mtc(pft_to_mtc(:)) |
---|
694 | dia_recr(:) = dia_recr_mtc(pft_to_mtc(:)) |
---|
695 | hei_recr(:) = hei_recr_mtc(pft_to_mtc(:)) |
---|
696 | END IF |
---|
697 | |
---|
698 | ! |
---|
699 | ! CROPLAND MANAGEMENT |
---|
700 | ! |
---|
701 | harvest_ratio(:) = harvest_ratio_mtc(pft_to_mtc(:)) |
---|
702 | |
---|
703 | ENDIF !(active_flags%ok_stomate) |
---|
704 | |
---|
705 | |
---|
706 | |
---|
707 | END SUBROUTINE pft_parameters_init |
---|
708 | ! |
---|
709 | ! |
---|
710 | ! |
---|
711 | |
---|
712 | !! ================================================================================================================================ |
---|
713 | !! SUBROUTINE : pft_parameters_alloc |
---|
714 | !! |
---|
715 | !>\BRIEF This subroutine allocates memory needed for the PFT parameters |
---|
716 | !! in function of the flags activated. |
---|
717 | !! |
---|
718 | !! DESCRIPTION : None |
---|
719 | !! |
---|
720 | !! RECENT CHANGE(S): None |
---|
721 | !! |
---|
722 | !! MAIN OUTPUT VARIABLE(S): None |
---|
723 | !! |
---|
724 | !! REFERENCE(S) : None |
---|
725 | !! |
---|
726 | !! FLOWCHART : None |
---|
727 | !! \n |
---|
728 | !_ ================================================================================================================================ |
---|
729 | |
---|
730 | SUBROUTINE pft_parameters_alloc(active_flags) |
---|
731 | |
---|
732 | IMPLICIT NONE |
---|
733 | |
---|
734 | !! 0. Variables and parameters declaration |
---|
735 | |
---|
736 | !! 0.1 Input variables |
---|
737 | |
---|
738 | TYPE(control_type),INTENT(in) :: active_flags !! What parts of the code are activated ? (true/false) |
---|
739 | |
---|
740 | !! 0.4 Local variables |
---|
741 | |
---|
742 | LOGICAL :: l_error !! Diagnostic boolean for error allocation (true/false) |
---|
743 | INTEGER :: ier !! Return value for memory allocation (0-N, unitless) |
---|
744 | !_ ================================================================================================================================ |
---|
745 | |
---|
746 | |
---|
747 | ! |
---|
748 | ! 1. Parameters used anytime |
---|
749 | ! |
---|
750 | |
---|
751 | l_error = .FALSE. |
---|
752 | |
---|
753 | ALLOCATE(pft_to_mtc(nvm),stat=ier) |
---|
754 | l_error = l_error .OR. (ier /= 0) |
---|
755 | IF (l_error) THEN |
---|
756 | WRITE(numout,*) ' Memory allocation error for pft_to_mtc. We stop. We need nvm words = ',nvm |
---|
757 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
758 | END IF |
---|
759 | |
---|
760 | ALLOCATE(PFT_name(nvm),stat=ier) |
---|
761 | l_error = l_error .OR. (ier /= 0) |
---|
762 | IF (l_error) THEN |
---|
763 | WRITE(numout,*) ' Memory allocation error for PFT_name. We stop. We need nvm words = ',nvm |
---|
764 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
765 | END IF |
---|
766 | |
---|
767 | ALLOCATE(height_presc(nvm),stat=ier) |
---|
768 | l_error = l_error .OR. (ier /= 0) |
---|
769 | IF (l_error) THEN |
---|
770 | WRITE(numout,*) ' Memory allocation error for height_presc. We stop. We need nvm words = ',nvm |
---|
771 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
772 | END IF |
---|
773 | |
---|
774 | ALLOCATE(is_tree(nvm),stat=ier) |
---|
775 | l_error = l_error .OR. (ier /= 0) |
---|
776 | IF (l_error) THEN |
---|
777 | WRITE(numout,*) ' Memory allocation error for is_tree. We stop. We need nvm words = ',nvm |
---|
778 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
779 | END IF |
---|
780 | |
---|
781 | ALLOCATE(natural(nvm),stat=ier) |
---|
782 | l_error = l_error .OR. (ier /= 0) |
---|
783 | IF (l_error) THEN |
---|
784 | WRITE(numout,*) ' Memory allocation error for natural. We stop. We need nvm words = ',nvm |
---|
785 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
786 | END IF |
---|
787 | |
---|
788 | ALLOCATE(is_c4(nvm),stat=ier) |
---|
789 | l_error = l_error .OR. (ier /= 0) |
---|
790 | IF (l_error) THEN |
---|
791 | WRITE(numout,*) ' Memory allocation error for is_c4. We stop. We need nvm words = ',nvm |
---|
792 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
793 | END IF |
---|
794 | |
---|
795 | ALLOCATE(humcste(nvm),stat=ier) |
---|
796 | l_error = l_error .OR. (ier /= 0) |
---|
797 | IF (l_error) THEN |
---|
798 | WRITE(numout,*) ' Memory allocation error for humcste. We stop. We need nvm words = ',nvm |
---|
799 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
800 | END IF |
---|
801 | |
---|
802 | ALLOCATE(downregulation_co2_coeff(nvm),stat=ier) |
---|
803 | l_error = l_error .OR. (ier /= 0) |
---|
804 | IF (l_error) THEN |
---|
805 | WRITE(numout,*) ' Memory allocation error for downregulation_co2_coeff. We stop. We need nvm words = ',nvm |
---|
806 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
807 | END IF |
---|
808 | |
---|
809 | ALLOCATE(E_KmC(nvm),stat=ier) |
---|
810 | l_error = l_error .OR. (ier /= 0) |
---|
811 | IF (l_error) THEN |
---|
812 | WRITE(numout,*) ' Memory allocation error for E_KmC. We stop. We need nvm words = ',nvm |
---|
813 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
814 | END IF |
---|
815 | |
---|
816 | ALLOCATE(E_KmO(nvm),stat=ier) |
---|
817 | l_error = l_error .OR. (ier /= 0) |
---|
818 | IF (l_error) THEN |
---|
819 | WRITE(numout,*) ' Memory allocation error for E_KmO. We stop. We need nvm words = ',nvm |
---|
820 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
821 | END IF |
---|
822 | |
---|
823 | ALLOCATE(E_gamma_star(nvm),stat=ier) |
---|
824 | l_error = l_error .OR. (ier /= 0) |
---|
825 | IF (l_error) THEN |
---|
826 | WRITE(numout,*) ' Memory allocation error for E_gamma_star. We stop. We need nvm words = ',nvm |
---|
827 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
828 | END IF |
---|
829 | |
---|
830 | ALLOCATE(E_vcmax(nvm),stat=ier) |
---|
831 | l_error = l_error .OR. (ier /= 0) |
---|
832 | IF (l_error) THEN |
---|
833 | WRITE(numout,*) ' Memory allocation error for E_Vcmax. We stop. We need nvm words = ',nvm |
---|
834 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
835 | END IF |
---|
836 | |
---|
837 | ALLOCATE(E_Jmax(nvm),stat=ier) |
---|
838 | l_error = l_error .OR. (ier /= 0) |
---|
839 | IF (l_error) THEN |
---|
840 | WRITE(numout,*) ' Memory allocation error for E_Jmax. We stop. We need nvm words = ',nvm |
---|
841 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
842 | END IF |
---|
843 | |
---|
844 | ALLOCATE(aSV(nvm),stat=ier) |
---|
845 | l_error = l_error .OR. (ier /= 0) |
---|
846 | IF (l_error) THEN |
---|
847 | WRITE(numout,*) ' Memory allocation error for aSV. We stop. We need nvm words = ',nvm |
---|
848 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
849 | END IF |
---|
850 | |
---|
851 | ALLOCATE(bSV(nvm),stat=ier) |
---|
852 | l_error = l_error .OR. (ier /= 0) |
---|
853 | IF (l_error) THEN |
---|
854 | WRITE(numout,*) ' Memory allocation error for bSV. We stop. We need nvm words = ',nvm |
---|
855 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
856 | END IF |
---|
857 | |
---|
858 | ALLOCATE(tphoto_min(nvm),stat=ier) |
---|
859 | l_error = l_error .OR. (ier /= 0) |
---|
860 | IF (l_error) THEN |
---|
861 | WRITE(numout,*) ' Memory allocation error for tphoto_min. We stop. We need nvm words = ',nvm |
---|
862 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
863 | END IF |
---|
864 | |
---|
865 | ALLOCATE(tphoto_max(nvm),stat=ier) |
---|
866 | l_error = l_error .OR. (ier /= 0) |
---|
867 | IF (l_error) THEN |
---|
868 | WRITE(numout,*) ' Memory allocation error for tphoto_max. We stop. We need nvm words = ',nvm |
---|
869 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
870 | END IF |
---|
871 | |
---|
872 | ALLOCATE(aSJ(nvm),stat=ier) |
---|
873 | l_error = l_error .OR. (ier /= 0) |
---|
874 | IF (l_error) THEN |
---|
875 | WRITE(numout,*) ' Memory allocation error for aSJ. We stop. We need nvm words = ',nvm |
---|
876 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
877 | END IF |
---|
878 | |
---|
879 | ALLOCATE(bSJ(nvm),stat=ier) |
---|
880 | l_error = l_error .OR. (ier /= 0) |
---|
881 | IF (l_error) THEN |
---|
882 | WRITE(numout,*) ' Memory allocation error for bSJ. We stop. We need nvm words = ',nvm |
---|
883 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
884 | END IF |
---|
885 | |
---|
886 | ALLOCATE(D_Vcmax(nvm),stat=ier) |
---|
887 | l_error = l_error .OR. (ier /= 0) |
---|
888 | IF (l_error) THEN |
---|
889 | WRITE(numout,*) ' Memory allocation error for D_Vcmax. We stop. We need nvm words = ',nvm |
---|
890 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
891 | END IF |
---|
892 | |
---|
893 | ALLOCATE(D_Jmax(nvm),stat=ier) |
---|
894 | l_error = l_error .OR. (ier /= 0) |
---|
895 | IF (l_error) THEN |
---|
896 | WRITE(numout,*) ' Memory allocation error for D_Jmax. We stop. We need nvm words = ',nvm |
---|
897 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
898 | END IF |
---|
899 | |
---|
900 | ALLOCATE(E_Rd(nvm),stat=ier) |
---|
901 | l_error = l_error .OR. (ier /= 0) |
---|
902 | IF (l_error) THEN |
---|
903 | WRITE(numout,*) ' Memory allocation error for E_Rd. We stop. We need nvm words = ',nvm |
---|
904 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
905 | END IF |
---|
906 | |
---|
907 | ALLOCATE(Vcmax25(nvm),stat=ier) |
---|
908 | l_error = l_error .OR. (ier /= 0) |
---|
909 | IF (l_error) THEN |
---|
910 | WRITE(numout,*) ' Memory allocation error for Vcmax25. We stop. We need nvm words = ',nvm |
---|
911 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
912 | END IF |
---|
913 | |
---|
914 | ALLOCATE(arJV(nvm),stat=ier) |
---|
915 | l_error = l_error .OR. (ier /= 0) |
---|
916 | IF (l_error) THEN |
---|
917 | WRITE(numout,*) ' Memory allocation error for arJV. We stop. We need nvm words = ',nvm |
---|
918 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
919 | END IF |
---|
920 | |
---|
921 | ALLOCATE(brJV(nvm),stat=ier) |
---|
922 | l_error = l_error .OR. (ier /= 0) |
---|
923 | IF (l_error) THEN |
---|
924 | WRITE(numout,*) ' Memory allocation error for brJV. We stop. We need nvm words = ',nvm |
---|
925 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
926 | END IF |
---|
927 | |
---|
928 | ALLOCATE(KmC25(nvm),stat=ier) |
---|
929 | l_error = l_error .OR. (ier /= 0) |
---|
930 | IF (l_error) THEN |
---|
931 | WRITE(numout,*) ' Memory allocation error for KmC25. We stop. We need nvm words = ',nvm |
---|
932 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
933 | END IF |
---|
934 | |
---|
935 | ALLOCATE(KmO25(nvm),stat=ier) |
---|
936 | l_error = l_error .OR. (ier /= 0) |
---|
937 | IF (l_error) THEN |
---|
938 | WRITE(numout,*) ' Memory allocation error for KmO25. We stop. We need nvm words = ',nvm |
---|
939 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
940 | END IF |
---|
941 | |
---|
942 | ALLOCATE(gamma_star25(nvm),stat=ier) |
---|
943 | l_error = l_error .OR. (ier /= 0) |
---|
944 | IF (l_error) THEN |
---|
945 | WRITE(numout,*) ' Memory allocation error for gamma_star25. We stop. We need nvm words = ',nvm |
---|
946 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
947 | END IF |
---|
948 | |
---|
949 | ALLOCATE(a1(nvm),stat=ier) |
---|
950 | l_error = l_error .OR. (ier /= 0) |
---|
951 | IF (l_error) THEN |
---|
952 | WRITE(numout,*) ' Memory allocation error for a1. We stop. We need nvm words = ',nvm |
---|
953 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
954 | END IF |
---|
955 | |
---|
956 | ALLOCATE(b1(nvm),stat=ier) |
---|
957 | l_error = l_error .OR. (ier /= 0) |
---|
958 | IF (l_error) THEN |
---|
959 | WRITE(numout,*) ' Memory allocation error for b1. We stop. We need nvm words = ',nvm |
---|
960 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
961 | END IF |
---|
962 | |
---|
963 | ALLOCATE(g0(nvm),stat=ier) |
---|
964 | l_error = l_error .OR. (ier /= 0) |
---|
965 | IF (l_error) THEN |
---|
966 | WRITE(numout,*) ' Memory allocation error for g0. We stop. We need nvm words = ',nvm |
---|
967 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
968 | END IF |
---|
969 | |
---|
970 | ALLOCATE(h_protons(nvm),stat=ier) |
---|
971 | l_error = l_error .OR. (ier /= 0) |
---|
972 | IF (l_error) THEN |
---|
973 | WRITE(numout,*) ' Memory allocation error for h_protons. We stop. We need nvm words = ',nvm |
---|
974 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
975 | END IF |
---|
976 | |
---|
977 | ALLOCATE(fpsir(nvm),stat=ier) |
---|
978 | l_error = l_error .OR. (ier /= 0) |
---|
979 | IF (l_error) THEN |
---|
980 | WRITE(numout,*) ' Memory allocation error for fpsir. We stop. We need nvm words = ',nvm |
---|
981 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
982 | END IF |
---|
983 | |
---|
984 | ALLOCATE(fQ(nvm),stat=ier) |
---|
985 | l_error = l_error .OR. (ier /= 0) |
---|
986 | IF (l_error) THEN |
---|
987 | WRITE(numout,*) ' Memory allocation error for fQ. We stop. We need nvm words = ',nvm |
---|
988 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
989 | END IF |
---|
990 | |
---|
991 | ALLOCATE(fpseudo(nvm),stat=ier) |
---|
992 | l_error = l_error .OR. (ier /= 0) |
---|
993 | IF (l_error) THEN |
---|
994 | WRITE(numout,*) ' Memory allocation error for fpseudo. We stop. We need nvm words = ',nvm |
---|
995 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
996 | END IF |
---|
997 | |
---|
998 | ALLOCATE(kp(nvm),stat=ier) |
---|
999 | l_error = l_error .OR. (ier /= 0) |
---|
1000 | IF (l_error) THEN |
---|
1001 | WRITE(numout,*) ' Memory allocation error for kp. We stop. We need nvm words = ',nvm |
---|
1002 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1003 | END IF |
---|
1004 | |
---|
1005 | ALLOCATE(alpha(nvm),stat=ier) |
---|
1006 | l_error = l_error .OR. (ier /= 0) |
---|
1007 | IF (l_error) THEN |
---|
1008 | WRITE(numout,*) ' Memory allocation error for alpha. We stop. We need nvm words = ',nvm |
---|
1009 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1010 | END IF |
---|
1011 | |
---|
1012 | ALLOCATE(gbs(nvm),stat=ier) |
---|
1013 | l_error = l_error .OR. (ier /= 0) |
---|
1014 | IF (l_error) THEN |
---|
1015 | WRITE(numout,*) ' Memory allocation error for gbs. We stop. We need nvm words = ',nvm |
---|
1016 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1017 | END IF |
---|
1018 | |
---|
1019 | ALLOCATE(theta(nvm),stat=ier) |
---|
1020 | l_error = l_error .OR. (ier /= 0) |
---|
1021 | IF (l_error) THEN |
---|
1022 | WRITE(numout,*) ' Memory allocation error for theta. We stop. We need nvm words = ',nvm |
---|
1023 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1024 | END IF |
---|
1025 | |
---|
1026 | ALLOCATE(alpha_LL(nvm),stat=ier) |
---|
1027 | l_error = l_error .OR. (ier /= 0) |
---|
1028 | IF (l_error) THEN |
---|
1029 | WRITE(numout,*) ' Memory allocation error for alpha_LL. We stop. We need nvm words = ',nvm |
---|
1030 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1031 | END IF |
---|
1032 | |
---|
1033 | ALLOCATE(ext_coeff(nvm),stat=ier) |
---|
1034 | l_error = l_error .OR. (ier /= 0) |
---|
1035 | IF (l_error) THEN |
---|
1036 | WRITE(numout,*) ' Memory allocation error for ext_coeff. We stop. We need nvm words = ',nvm |
---|
1037 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1038 | END IF |
---|
1039 | |
---|
1040 | ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier) |
---|
1041 | l_error = l_error .OR. (ier /= 0) |
---|
1042 | IF (l_error) THEN |
---|
1043 | WRITE(numout,*) ' Memory allocation error for veget_ori_fixed_test_1. We stop. We need nvm words = ',nvm |
---|
1044 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1045 | END IF |
---|
1046 | |
---|
1047 | ALLOCATE(llaimax(nvm),stat=ier) |
---|
1048 | l_error = l_error .OR. (ier /= 0) |
---|
1049 | IF (l_error) THEN |
---|
1050 | WRITE(numout,*) ' Memory allocation error for llaimax. We stop. We need nvm words = ',nvm |
---|
1051 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1052 | END IF |
---|
1053 | |
---|
1054 | ALLOCATE(llaimin(nvm),stat=ier) |
---|
1055 | l_error = l_error .OR. (ier /= 0) |
---|
1056 | IF (l_error) THEN |
---|
1057 | WRITE(numout,*) ' Memory allocation error for llaimin. We stop. We need nvm words = ',nvm |
---|
1058 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1059 | END IF |
---|
1060 | |
---|
1061 | ALLOCATE(type_of_lai(nvm),stat=ier) |
---|
1062 | l_error = l_error .OR. (ier /= 0) |
---|
1063 | IF (l_error) THEN |
---|
1064 | WRITE(numout,*) ' Memory allocation error for type_of_lai. We stop. We need nvm words = ',nvm |
---|
1065 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1066 | END IF |
---|
1067 | |
---|
1068 | ALLOCATE(vcmax_fix(nvm),stat=ier) |
---|
1069 | l_error = l_error .OR. (ier /= 0) |
---|
1070 | IF (l_error) THEN |
---|
1071 | WRITE(numout,*) ' Memory allocation error for vcmax_fix. We stop. We need nvm words = ',nvm |
---|
1072 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1073 | END IF |
---|
1074 | |
---|
1075 | ALLOCATE(pref_soil_veg(nvm),stat=ier) |
---|
1076 | l_error = l_error .OR. (ier /= 0) |
---|
1077 | IF (l_error) THEN |
---|
1078 | WRITE(numout,*) ' Memory allocation error for pref_soil_veg. We stop. We need nvm words = ',nvm |
---|
1079 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1080 | END IF |
---|
1081 | |
---|
1082 | ALLOCATE(agec_group(nvm),stat=ier) |
---|
1083 | l_error = l_error .OR. (ier /= 0) |
---|
1084 | IF (l_error) THEN |
---|
1085 | WRITE(numout,*) ' Memory allocation error for agec_group. We stop. We need nvm words = ',nvm |
---|
1086 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1087 | END IF |
---|
1088 | |
---|
1089 | ALLOCATE(start_index(nvm),stat=ier) |
---|
1090 | l_error = l_error .OR. (ier /= 0) |
---|
1091 | IF (l_error) THEN |
---|
1092 | WRITE(numout,*) ' Memory allocation error for start_index. We stop. We need nvm words = ',nvm |
---|
1093 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1094 | END IF |
---|
1095 | |
---|
1096 | ALLOCATE(nagec_pft(nvm),stat=ier) |
---|
1097 | l_error = l_error .OR. (ier /= 0) |
---|
1098 | IF (l_error) THEN |
---|
1099 | WRITE(numout,*) ' Memory allocation error for nagec_pft. We stop. We need nvm words = ',nvm |
---|
1100 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1101 | END IF |
---|
1102 | |
---|
1103 | ALLOCATE(leaf_tab(nvm),stat=ier) |
---|
1104 | l_error = l_error .OR. (ier /= 0) |
---|
1105 | IF (l_error) THEN |
---|
1106 | WRITE(numout,*) ' Memory allocation error for leaf_tab. We stop. We need nvm words = ',nvm |
---|
1107 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1108 | END IF |
---|
1109 | |
---|
1110 | ALLOCATE(pheno_model(nvm),stat=ier) |
---|
1111 | l_error = l_error .OR. (ier /= 0) |
---|
1112 | IF (l_error) THEN |
---|
1113 | WRITE(numout,*) ' Memory allocation error for pheno_model. We stop. We need nvm words = ',nvm |
---|
1114 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1115 | END IF |
---|
1116 | |
---|
1117 | ALLOCATE(is_deciduous(nvm),stat=ier) |
---|
1118 | l_error = l_error .OR. (ier /= 0) |
---|
1119 | IF (l_error) THEN |
---|
1120 | WRITE(numout,*) ' Memory allocation error for is_deciduous. We stop. We need nvm words = ',nvm |
---|
1121 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1122 | END IF |
---|
1123 | |
---|
1124 | ALLOCATE(is_temperate(nvm),stat=ier) |
---|
1125 | l_error = l_error .OR. (ier /= 0) |
---|
1126 | IF (l_error) THEN |
---|
1127 | WRITE(numout,*) ' Memory allocation error for is_temperate. We stop. We need nvm words = ',nvm |
---|
1128 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1129 | END IF |
---|
1130 | |
---|
1131 | ALLOCATE(is_boreal(nvm),stat=ier) |
---|
1132 | l_error = l_error .OR. (ier /= 0) |
---|
1133 | IF (l_error) THEN |
---|
1134 | WRITE(numout,*) ' Memory allocation error for is_boreal. We stop. We need nvm words = ',nvm |
---|
1135 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1136 | END IF |
---|
1137 | |
---|
1138 | ALLOCATE(is_evergreen(nvm),stat=ier) |
---|
1139 | l_error = l_error .OR. (ier /= 0) |
---|
1140 | IF (l_error) THEN |
---|
1141 | WRITE(numout,*) ' Memory allocation error for is_evergreen. We stop. We need nvm words = ',nvm |
---|
1142 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1143 | END IF |
---|
1144 | |
---|
1145 | ALLOCATE(is_needleleaf(nvm),stat=ier) |
---|
1146 | l_error = l_error .OR. (ier /= 0) |
---|
1147 | IF (l_error) THEN |
---|
1148 | WRITE(numout,*) ' Memory allocation error for is_needleleaf. We stop. We need nvm words = ',nvm |
---|
1149 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1150 | END IF |
---|
1151 | |
---|
1152 | ALLOCATE(is_tropical(nvm),stat=ier) |
---|
1153 | l_error = l_error .OR. (ier /= 0) |
---|
1154 | IF (l_error) THEN |
---|
1155 | WRITE(numout,*) ' Memory allocation error for is_tropical. We stop. We need nvm words = ',nvm |
---|
1156 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1157 | END IF |
---|
1158 | |
---|
1159 | |
---|
1160 | ! |
---|
1161 | ! 2. Parameters used if ok_sechiba only |
---|
1162 | ! |
---|
1163 | IF ( active_flags%ok_sechiba ) THEN |
---|
1164 | |
---|
1165 | l_error = .FALSE. |
---|
1166 | |
---|
1167 | ALLOCATE(rstruct_const(nvm),stat=ier) |
---|
1168 | l_error = l_error .OR. (ier /= 0) |
---|
1169 | IF (l_error) THEN |
---|
1170 | WRITE(numout,*) ' Memory allocation error for rstruct_const. We stop. We need nvm words = ',nvm |
---|
1171 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1172 | END IF |
---|
1173 | |
---|
1174 | ALLOCATE(kzero(nvm),stat=ier) |
---|
1175 | l_error = l_error .OR. (ier /= 0) |
---|
1176 | IF (l_error) THEN |
---|
1177 | WRITE(numout,*) ' Memory allocation error for kzero. We stop. We need nvm words = ',nvm |
---|
1178 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1179 | END IF |
---|
1180 | |
---|
1181 | ALLOCATE(rveg_pft(nvm),stat=ier) |
---|
1182 | l_error = l_error .OR. (ier /= 0) |
---|
1183 | IF (l_error) THEN |
---|
1184 | WRITE(numout,*) ' Memory allocation error for rveg_pft. We stop. We need nvm words = ',nvm |
---|
1185 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1186 | END IF |
---|
1187 | |
---|
1188 | ALLOCATE(wmax_veg(nvm),stat=ier) |
---|
1189 | l_error = l_error .OR. (ier /= 0) |
---|
1190 | IF (l_error) THEN |
---|
1191 | WRITE(numout,*) ' Memory allocation error for wmax_veg. We stop. We need nvm words = ',nvm |
---|
1192 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1193 | END IF |
---|
1194 | |
---|
1195 | IF ( .NOT.(active_flags%hydrol_cwrr) .OR. (active_flags%hydrol_cwrr .AND. ok_throughfall_by_pft) ) THEN |
---|
1196 | ALLOCATE(throughfall_by_pft(nvm),stat=ier) |
---|
1197 | l_error = l_error .OR. (ier /= 0) |
---|
1198 | IF (l_error) THEN |
---|
1199 | WRITE(numout,*) ' Memory allocation error for throughfall_by_pft. We stop. We need nvm words = ',nvm |
---|
1200 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1201 | END IF |
---|
1202 | END IF |
---|
1203 | |
---|
1204 | ALLOCATE(snowa_aged(nvm),stat=ier) |
---|
1205 | l_error = l_error .OR. (ier /= 0) |
---|
1206 | IF (l_error) THEN |
---|
1207 | WRITE(numout,*) ' Memory allocation error for snowa_aged. We stop. We need nvm words = ',nvm |
---|
1208 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1209 | END IF |
---|
1210 | |
---|
1211 | ALLOCATE(snowa_dec(nvm),stat=ier) |
---|
1212 | l_error = l_error .OR. (ier /= 0) |
---|
1213 | IF (l_error) THEN |
---|
1214 | WRITE(numout,*) ' Memory allocation error for snowa_dec. We stop. We need nvm words = ',nvm |
---|
1215 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1216 | END IF |
---|
1217 | |
---|
1218 | ALLOCATE(alb_leaf_vis(nvm),stat=ier) |
---|
1219 | l_error = l_error .OR. (ier /= 0) |
---|
1220 | IF (l_error) THEN |
---|
1221 | WRITE(numout,*) ' Memory allocation error for alb_leaf_vis. We stop. We need nvm words = ',nvm |
---|
1222 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1223 | END IF |
---|
1224 | |
---|
1225 | ALLOCATE(alb_leaf_nir(nvm),stat=ier) |
---|
1226 | l_error = l_error .OR. (ier /= 0) |
---|
1227 | IF (l_error) THEN |
---|
1228 | WRITE(numout,*) ' Memory allocation error for alb_leaf_nir. We stop. We need nvm words = ',nvm |
---|
1229 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1230 | END IF |
---|
1231 | |
---|
1232 | ALLOCATE(leaf_ssa(nvm,n_spectralbands),stat=ier) |
---|
1233 | l_error = l_error .OR. (ier /= 0) |
---|
1234 | IF (l_error) THEN |
---|
1235 | WRITE(numout,*) ' Memory allocation error for leaf_ssa. We stop. We need nvm*n_spectralbands words = ',& |
---|
1236 | nvm*n_spectralbands |
---|
1237 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1238 | END IF |
---|
1239 | |
---|
1240 | ALLOCATE(leaf_psd(nvm,n_spectralbands),stat=ier) |
---|
1241 | l_error = l_error .OR. (ier /= 0) |
---|
1242 | IF (l_error) THEN |
---|
1243 | WRITE(numout,*) ' Memory allocation error for leaf_psd. We stop. We need nvm*n_spectralbands words = ',& |
---|
1244 | nvm*n_spectralbands |
---|
1245 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1246 | END IF |
---|
1247 | |
---|
1248 | ALLOCATE(bgd_reflectance(nvm,n_spectralbands),stat=ier) |
---|
1249 | l_error = l_error .OR. (ier /= 0) |
---|
1250 | IF (l_error) THEN |
---|
1251 | WRITE(numout,*) ' Memory allocation error for bgd_reflectance. We need nvm*n_spectralbands words = ',& |
---|
1252 | nvm*n_spectralbands |
---|
1253 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1254 | END IF |
---|
1255 | |
---|
1256 | ALLOCATE(leaf_to_shoot_clumping(nvm),stat=ier) |
---|
1257 | l_error = l_error .OR. (ier /= 0) |
---|
1258 | IF (l_error) THEN |
---|
1259 | WRITE(numout,*) ' Memory allocation error for leaf_to_shoot_clumping. We need nvm words = ',& |
---|
1260 | nvm |
---|
1261 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1262 | END IF |
---|
1263 | |
---|
1264 | |
---|
1265 | ALLOCATE(tune_coupled(nvm),stat=ier) |
---|
1266 | l_error = l_error .OR. (ier /= 0) |
---|
1267 | IF (l_error) THEN |
---|
1268 | WRITE(numout,*) ' Memory allocation error for tune_coupled. We need nvm words = ',& |
---|
1269 | nvm |
---|
1270 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1271 | END IF |
---|
1272 | |
---|
1273 | |
---|
1274 | ALLOCATE(lai_correction_factor(nvm),stat=ier) |
---|
1275 | l_error = l_error .OR. (ier /= 0) |
---|
1276 | IF (l_error) THEN |
---|
1277 | WRITE(numout,*) ' Memory allocation error for lai_correction_factor. We need nvm words = ',& |
---|
1278 | nvm |
---|
1279 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1280 | END IF |
---|
1281 | |
---|
1282 | ALLOCATE(min_level_sep(nvm),stat=ier) |
---|
1283 | l_error = l_error .OR. (ier /= 0) |
---|
1284 | IF (l_error) THEN |
---|
1285 | WRITE(numout,*) ' Memory allocation error for min_level_sep. We need nvm words = ',& |
---|
1286 | nvm |
---|
1287 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1288 | END IF |
---|
1289 | |
---|
1290 | ALLOCATE(lai_top(nvm),stat=ier) |
---|
1291 | l_error = l_error .OR. (ier /= 0) |
---|
1292 | IF (l_error) THEN |
---|
1293 | WRITE(numout,*) ' Memory allocation error for lai_top. We need nvm words = ',& |
---|
1294 | nvm |
---|
1295 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1296 | END IF |
---|
1297 | |
---|
1298 | |
---|
1299 | IF( active_flags%ok_inca ) THEN |
---|
1300 | |
---|
1301 | l_error = .FALSE. |
---|
1302 | |
---|
1303 | ALLOCATE(em_factor_isoprene(nvm),stat=ier) |
---|
1304 | l_error = l_error .OR. (ier /= 0) |
---|
1305 | IF (l_error) THEN |
---|
1306 | WRITE(numout,*) ' Memory allocation error for em_factor_isoprene. We stop. We need nvm words = ',nvm |
---|
1307 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1308 | END IF |
---|
1309 | |
---|
1310 | ALLOCATE(em_factor_monoterpene(nvm),stat=ier) |
---|
1311 | l_error = l_error .OR. (ier /= 0) |
---|
1312 | IF (l_error) THEN |
---|
1313 | WRITE(numout,*) ' Memory allocation error for em_factor_monoterpene. We stop. We need nvm words = ',nvm |
---|
1314 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1315 | END IF |
---|
1316 | |
---|
1317 | ALLOCATE(em_factor_ORVOC(nvm),stat=ier) |
---|
1318 | l_error = l_error .OR. (ier /= 0) |
---|
1319 | IF (l_error) THEN |
---|
1320 | WRITE(numout,*) ' Memory allocation error for em_factor_ORVOC. We stop. We need nvm words = ',nvm |
---|
1321 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1322 | END IF |
---|
1323 | |
---|
1324 | ALLOCATE(em_factor_OVOC(nvm),stat=ier) |
---|
1325 | l_error = l_error .OR. (ier /= 0) |
---|
1326 | IF (l_error) THEN |
---|
1327 | WRITE(numout,*) ' Memory allocation error for em_factor_OVOC. We stop. We need nvm words = ',nvm |
---|
1328 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1329 | END IF |
---|
1330 | |
---|
1331 | ALLOCATE(em_factor_MBO(nvm),stat=ier) |
---|
1332 | l_error = l_error .OR. (ier /= 0) |
---|
1333 | IF (l_error) THEN |
---|
1334 | WRITE(numout,*) ' Memory allocation error for em_factor_MBO. We stop. We need nvm words = ',nvm |
---|
1335 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1336 | END IF |
---|
1337 | |
---|
1338 | ALLOCATE(em_factor_methanol(nvm),stat=ier) |
---|
1339 | l_error = l_error .OR. (ier /= 0) |
---|
1340 | IF (l_error) THEN |
---|
1341 | WRITE(numout,*) ' Memory allocation error for em_factor_methanol. We stop. We need nvm words = ',nvm |
---|
1342 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1343 | END IF |
---|
1344 | |
---|
1345 | ALLOCATE(em_factor_acetone(nvm),stat=ier) |
---|
1346 | l_error = l_error .OR. (ier /= 0) |
---|
1347 | IF (l_error) THEN |
---|
1348 | WRITE(numout,*) ' Memory allocation error for em_factor_acetone. We stop. We need nvm words = ',nvm |
---|
1349 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1350 | END IF |
---|
1351 | |
---|
1352 | ALLOCATE(em_factor_acetal(nvm),stat=ier) |
---|
1353 | l_error = l_error .OR. (ier /= 0) |
---|
1354 | IF (l_error) THEN |
---|
1355 | WRITE(numout,*) ' Memory allocation error for em_factor_acetal. We stop. We need nvm words = ',nvm |
---|
1356 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1357 | END IF |
---|
1358 | |
---|
1359 | ALLOCATE(em_factor_formal(nvm),stat=ier) |
---|
1360 | l_error = l_error .OR. (ier /= 0) |
---|
1361 | IF (l_error) THEN |
---|
1362 | WRITE(numout,*) ' Memory allocation error for em_factor_formal. We stop. We need nvm words = ',nvm |
---|
1363 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1364 | END IF |
---|
1365 | |
---|
1366 | ALLOCATE(em_factor_acetic(nvm),stat=ier) |
---|
1367 | l_error = l_error .OR. (ier /= 0) |
---|
1368 | IF (l_error) THEN |
---|
1369 | WRITE(numout,*) ' Memory allocation error for em_factor_acetic. We stop. We need nvm words = ',nvm |
---|
1370 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1371 | END IF |
---|
1372 | |
---|
1373 | ALLOCATE(em_factor_formic(nvm),stat=ier) |
---|
1374 | l_error = l_error .OR. (ier /= 0) |
---|
1375 | IF (l_error) THEN |
---|
1376 | WRITE(numout,*) ' Memory allocation error for em_factor_formic. We stop. We need nvm words = ',nvm |
---|
1377 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1378 | END IF |
---|
1379 | |
---|
1380 | ALLOCATE(em_factor_no_wet(nvm),stat=ier) |
---|
1381 | l_error = l_error .OR. (ier /= 0) |
---|
1382 | IF (l_error) THEN |
---|
1383 | WRITE(numout,*) ' Memory allocation error for em_factor_no_wet. We stop. We need nvm words = ',nvm |
---|
1384 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1385 | END IF |
---|
1386 | |
---|
1387 | ALLOCATE(em_factor_no_dry(nvm),stat=ier) |
---|
1388 | l_error = l_error .OR. (ier /= 0) |
---|
1389 | IF (l_error) THEN |
---|
1390 | WRITE(numout,*) ' Memory allocation error for em_factor_no_dry. We stop. We need nvm words = ',nvm |
---|
1391 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1392 | END IF |
---|
1393 | |
---|
1394 | ALLOCATE(Larch(nvm),stat=ier) |
---|
1395 | l_error = l_error .OR. (ier /= 0) |
---|
1396 | IF (l_error) THEN |
---|
1397 | WRITE(numout,*) ' Memory allocation error for Larch. We stop. We need nvm words = ',nvm |
---|
1398 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1399 | END IF |
---|
1400 | |
---|
1401 | ENDIF ! (active_flags%ok_inca) |
---|
1402 | |
---|
1403 | ENDIF !(active_flags%ok_sechiba) |
---|
1404 | |
---|
1405 | ! |
---|
1406 | ! 3. Parameters used if ok_stomate only |
---|
1407 | ! |
---|
1408 | IF ( active_flags%ok_stomate ) THEN |
---|
1409 | |
---|
1410 | l_error = .FALSE. |
---|
1411 | |
---|
1412 | ! |
---|
1413 | ! PHOTOSYNTHESIS |
---|
1414 | ! |
---|
1415 | ALLOCATE(sla(nvm),stat=ier) |
---|
1416 | l_error = l_error .OR. (ier /= 0) |
---|
1417 | IF (l_error) THEN |
---|
1418 | WRITE(numout,*) ' Memory allocation error for sla. We stop. We need nvm words = ',nvm |
---|
1419 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1420 | END IF |
---|
1421 | |
---|
1422 | !!$ ALLOCATE(tphoto_min_a(nvm),stat=ier) |
---|
1423 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1424 | !!$ IF (l_error) THEN |
---|
1425 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_min_a. We stop. We need nvm words = ',nvm |
---|
1426 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1427 | !!$ END IF |
---|
1428 | !!$ |
---|
1429 | !!$ ALLOCATE(tphoto_min_b(nvm),stat=ier) |
---|
1430 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1431 | !!$ IF (l_error) THEN |
---|
1432 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_min_b. We stop. We need nvm words = ',nvm |
---|
1433 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1434 | !!$ END IF |
---|
1435 | !!$ |
---|
1436 | !!$ ALLOCATE(tphoto_min_c(nvm),stat=ier) |
---|
1437 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1438 | !!$ IF (l_error) THEN |
---|
1439 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_min_c. We stop. We need nvm words = ',nvm |
---|
1440 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1441 | !!$ END IF |
---|
1442 | !!$ |
---|
1443 | !!$ ALLOCATE(tphoto_opt_a(nvm),stat=ier) |
---|
1444 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1445 | !!$ IF (l_error) THEN |
---|
1446 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_opt_a. We stop. We need nvm words = ',nvm |
---|
1447 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1448 | !!$ END IF |
---|
1449 | !!$ |
---|
1450 | !!$ ALLOCATE(tphoto_opt_b(nvm),stat=ier) |
---|
1451 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1452 | !!$ IF (l_error) THEN |
---|
1453 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_opt_b. We stop. We need nvm words = ',nvm |
---|
1454 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1455 | !!$ END IF |
---|
1456 | !!$ |
---|
1457 | !!$ ALLOCATE(tphoto_opt_c(nvm),stat=ier) |
---|
1458 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1459 | !!$ IF (l_error) THEN |
---|
1460 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_opt_c. We stop. We need nvm words = ',nvm |
---|
1461 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1462 | !!$ END IF |
---|
1463 | !!$ |
---|
1464 | !!$ ALLOCATE(tphoto_max_a(nvm),stat=ier) |
---|
1465 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1466 | !!$ IF (l_error) THEN |
---|
1467 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_max_a. We stop. We need nvm words = ',nvm |
---|
1468 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1469 | !!$ END IF |
---|
1470 | !!$ |
---|
1471 | !!$ ALLOCATE(tphoto_max_b(nvm),stat=ier) |
---|
1472 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1473 | !!$ IF (l_error) THEN |
---|
1474 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_max_b. We stop. We need nvm words = ',nvm |
---|
1475 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1476 | !!$ END IF |
---|
1477 | !!$ |
---|
1478 | !!$ ALLOCATE(tphoto_max_c(nvm),stat=ier) |
---|
1479 | !!$ l_error = l_error .OR. (ier /= 0) |
---|
1480 | !!$ IF (l_error) THEN |
---|
1481 | !!$ WRITE(numout,*) ' Memory allocation error for tphoto_max_c. We stop. We need nvm words = ',nvm |
---|
1482 | !!$ CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1483 | !!$ END IF |
---|
1484 | |
---|
1485 | |
---|
1486 | ! |
---|
1487 | ! RESPIRATION |
---|
1488 | ! |
---|
1489 | ALLOCATE(S0(nvm),stat=ier) |
---|
1490 | l_error = l_error .OR. (ier /= 0) |
---|
1491 | IF (l_error) THEN |
---|
1492 | WRITE(numout,*) ' Memory allocation error for S0. We stop. We need nvm words = ',nvm |
---|
1493 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1494 | END IF |
---|
1495 | |
---|
1496 | ALLOCATE(L0(nvm),stat=ier) |
---|
1497 | l_error = l_error .OR. (ier /= 0) |
---|
1498 | IF (l_error) THEN |
---|
1499 | WRITE(numout,*) ' Memory allocation error for L0. We stop. We need nvm words = ',nvm |
---|
1500 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1501 | END IF |
---|
1502 | |
---|
1503 | ALLOCATE(maint_resp_slope(nvm,3),stat=ier) |
---|
1504 | l_error = l_error .OR. (ier /= 0) |
---|
1505 | IF (l_error) THEN |
---|
1506 | WRITE(numout,*) ' Memory allocation error for maint_resp_slope. We stop. We need nvm*3 words = ',nvm*3 |
---|
1507 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1508 | END IF |
---|
1509 | maint_resp_slope(:,:) = zero |
---|
1510 | |
---|
1511 | ALLOCATE(maint_resp_slope_c(nvm),stat=ier) |
---|
1512 | l_error = l_error .OR. (ier /= 0) |
---|
1513 | IF (l_error) THEN |
---|
1514 | WRITE(numout,*) ' Memory allocation error for maint_resp_slope_c. We stop. We need nvm words = ',nvm |
---|
1515 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1516 | END IF |
---|
1517 | |
---|
1518 | ALLOCATE(maint_resp_slope_b(nvm),stat=ier) |
---|
1519 | l_error = l_error .OR. (ier /= 0) |
---|
1520 | IF (l_error) THEN |
---|
1521 | WRITE(numout,*) ' Memory allocation error for maint_resp_slope_b. We stop. We need nvm words = ',nvm |
---|
1522 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1523 | END IF |
---|
1524 | |
---|
1525 | ALLOCATE(maint_resp_slope_a(nvm),stat=ier) |
---|
1526 | l_error = l_error .OR. (ier /= 0) |
---|
1527 | IF (l_error) THEN |
---|
1528 | WRITE(numout,*) ' Memory allocation error for maint_resp_slope_a. We stop. We need nvm words = ',nvm |
---|
1529 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1530 | END IF |
---|
1531 | |
---|
1532 | ALLOCATE(coeff_maint_zero(nvm,nparts),stat=ier) |
---|
1533 | l_error = l_error .OR. (ier /= 0) |
---|
1534 | IF (l_error) THEN |
---|
1535 | WRITE(numout,*) ' Memory allocation error for coeff_maint_zero. We stop. We need nvm*nparts words = ',nvm*nparts |
---|
1536 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1537 | END IF |
---|
1538 | coeff_maint_zero(:,:) = zero |
---|
1539 | |
---|
1540 | ALLOCATE(cm_zero_leaf(nvm),stat=ier) |
---|
1541 | l_error = l_error .OR. (ier /= 0) |
---|
1542 | IF (l_error) THEN |
---|
1543 | WRITE(numout,*) ' Memory allocation error for cm_zero_leaf. We stop. We need nvm words = ',nvm |
---|
1544 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1545 | END IF |
---|
1546 | |
---|
1547 | ALLOCATE(cm_zero_sapabove(nvm),stat=ier) |
---|
1548 | l_error = l_error .OR. (ier /= 0) |
---|
1549 | IF (l_error) THEN |
---|
1550 | WRITE(numout,*) ' Memory allocation error for cm_zero_sapabove. We stop. We need nvm words = ',nvm |
---|
1551 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1552 | END IF |
---|
1553 | |
---|
1554 | ALLOCATE(cm_zero_sapbelow(nvm),stat=ier) |
---|
1555 | l_error = l_error .OR. (ier /= 0) |
---|
1556 | IF (l_error) THEN |
---|
1557 | WRITE(numout,*) ' Memory allocation error for cm_zero_sapbelow. We stop. We need nvm words = ',nvm |
---|
1558 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1559 | END IF |
---|
1560 | |
---|
1561 | ALLOCATE(cm_zero_heartabove(nvm),stat=ier) |
---|
1562 | l_error = l_error .OR. (ier /= 0) |
---|
1563 | IF (l_error) THEN |
---|
1564 | WRITE(numout,*) ' Memory allocation error for cm_zero_heartabove. We stop. We need nvm words = ',nvm |
---|
1565 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1566 | END IF |
---|
1567 | |
---|
1568 | ALLOCATE(cm_zero_heartbelow(nvm),stat=ier) |
---|
1569 | l_error = l_error .OR. (ier /= 0) |
---|
1570 | IF (l_error) THEN |
---|
1571 | WRITE(numout,*) ' Memory allocation error for cm_zero_heartbelow. We stop. We need nvm words = ',nvm |
---|
1572 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1573 | END IF |
---|
1574 | |
---|
1575 | ALLOCATE(cm_zero_root(nvm),stat=ier) |
---|
1576 | l_error = l_error .OR. (ier /= 0) |
---|
1577 | IF (l_error) THEN |
---|
1578 | WRITE(numout,*) ' Memory allocation error for cm_zero_root. We stop. We need nvm words = ',nvm |
---|
1579 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1580 | END IF |
---|
1581 | |
---|
1582 | ALLOCATE(cm_zero_fruit(nvm),stat=ier) |
---|
1583 | l_error = l_error .OR. (ier /= 0) |
---|
1584 | IF (l_error) THEN |
---|
1585 | WRITE(numout,*) ' Memory allocation error for cm_zero_fruit. We stop. We need nvm words = ',nvm |
---|
1586 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1587 | END IF |
---|
1588 | |
---|
1589 | ALLOCATE(cm_zero_carbres(nvm),stat=ier) |
---|
1590 | l_error = l_error .OR. (ier /= 0) |
---|
1591 | IF (l_error) THEN |
---|
1592 | WRITE(numout,*) ' Memory allocation error for cm_zero_carbres. We stop. We need nvm words = ',nvm |
---|
1593 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1594 | END IF |
---|
1595 | |
---|
1596 | ALLOCATE(cm_zero_labile(nvm),stat=ier) |
---|
1597 | l_error = l_error .OR. (ier /= 0) |
---|
1598 | IF (l_error) THEN |
---|
1599 | WRITE(numout,*) ' Memory allocation error for cm_zero_labile. We stop. We need nvm words = ',nvm |
---|
1600 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1601 | END IF |
---|
1602 | |
---|
1603 | ALLOCATE(coeff_maint_init(nvm),stat=ier) |
---|
1604 | l_error = l_error .OR. (ier /= 0) |
---|
1605 | IF (l_error) THEN |
---|
1606 | WRITE(numout,*) ' Memory allocation error for coeff_maint_init. We stop. We need nvm words = ',nvm |
---|
1607 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1608 | END IF |
---|
1609 | |
---|
1610 | ALLOCATE(frac_growthresp(nvm),stat=ier) |
---|
1611 | l_error = l_error .OR. (ier /= 0) |
---|
1612 | IF (l_error) THEN |
---|
1613 | WRITE(numout,*) ' Memory allocation error for frac_growthresp. We stop. We need nvm words = ',nvm |
---|
1614 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1615 | END IF |
---|
1616 | |
---|
1617 | ALLOCATE(gpp_to_labile(nvm),stat=ier) |
---|
1618 | l_error = l_error .OR. (ier /= 0) |
---|
1619 | IF (l_error) THEN |
---|
1620 | WRITE(numout,*) ' Memory allocation error for gpp_to_labile. We stop. We need nvm words = ',nvm |
---|
1621 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1622 | END IF |
---|
1623 | |
---|
1624 | ! |
---|
1625 | ! STAND STRUCTURE |
---|
1626 | ! |
---|
1627 | |
---|
1628 | ALLOCATE(pipe_density(nvm),stat=ier) |
---|
1629 | l_error = l_error .OR. (ier /= 0) |
---|
1630 | IF (l_error) THEN |
---|
1631 | WRITE(numout,*) ' Memory allocation error for pipe_density. We stop. We need nvm words = ',nvm |
---|
1632 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1633 | END IF |
---|
1634 | |
---|
1635 | ALLOCATE(pipe_tune1(nvm),stat=ier) |
---|
1636 | l_error = l_error .OR. (ier /= 0) |
---|
1637 | IF (l_error) THEN |
---|
1638 | WRITE(numout,*) ' Memory allocation error for pipe_tune1. We stop. We need nvm words = ',nvm |
---|
1639 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1640 | END IF |
---|
1641 | |
---|
1642 | ALLOCATE(pipe_tune2(nvm),stat=ier) |
---|
1643 | l_error = l_error .OR. (ier /= 0) |
---|
1644 | IF (l_error) THEN |
---|
1645 | WRITE(numout,*) ' Memory allocation error for pipe_tune2. We stop. We need nvm words = ',nvm |
---|
1646 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1647 | END IF |
---|
1648 | |
---|
1649 | ALLOCATE(pipe_tune3(nvm),stat=ier) |
---|
1650 | l_error = l_error .OR. (ier /= 0) |
---|
1651 | IF (l_error) THEN |
---|
1652 | WRITE(numout,*) ' Memory allocation error for pipe_tune3. We stop. We need nvm words = ',nvm |
---|
1653 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1654 | END IF |
---|
1655 | |
---|
1656 | ALLOCATE(pipe_tune4(nvm),stat=ier) |
---|
1657 | l_error = l_error .OR. (ier /= 0) |
---|
1658 | IF (l_error) THEN |
---|
1659 | WRITE(numout,*) ' Memory allocation error for pipe_tune4. We stop. We need nvm words = ',nvm |
---|
1660 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1661 | END IF |
---|
1662 | |
---|
1663 | ALLOCATE(tree_ff(nvm),stat=ier) |
---|
1664 | l_error = l_error .OR. (ier /= 0) |
---|
1665 | IF (l_error) THEN |
---|
1666 | WRITE(numout,*) ' Memory allocation error for tree_ff. We stop. We need nvm words = ',nvm |
---|
1667 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1668 | END IF |
---|
1669 | |
---|
1670 | ALLOCATE(pipe_k1(nvm),stat=ier) |
---|
1671 | l_error = l_error .OR. (ier /= 0) |
---|
1672 | IF (l_error) THEN |
---|
1673 | WRITE(numout,*) ' Memory allocation error for pipe_k1. We stop. We need nvm words = ',nvm |
---|
1674 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1675 | END IF |
---|
1676 | |
---|
1677 | ALLOCATE(pipe_tune_exp_coeff(nvm),stat=ier) |
---|
1678 | l_error = l_error .OR. (ier /= 0) |
---|
1679 | IF (l_error) THEN |
---|
1680 | WRITE(numout,*) ' Memory allocation error for pipe_tune_exp_coeff. We stop. We need nvm words = ',nvm |
---|
1681 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1682 | END IF |
---|
1683 | |
---|
1684 | ALLOCATE(mass_ratio_heart_sap(nvm),stat=ier) |
---|
1685 | l_error = l_error .OR. (ier /= 0) |
---|
1686 | IF (l_error) THEN |
---|
1687 | WRITE(numout,*) ' Memory allocation error for mass_ratio_heart_sap. We stop. We need nvm words = ',nvm |
---|
1688 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1689 | END IF |
---|
1690 | |
---|
1691 | ALLOCATE(lai_to_height(nvm),stat=ier) |
---|
1692 | l_error = l_error .OR. (ier /= 0) |
---|
1693 | IF (l_error) THEN |
---|
1694 | WRITE(numout,*) ' Memory allocation error for lai_to_height. We stop. We need nvm words = ',nvm |
---|
1695 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1696 | END IF |
---|
1697 | |
---|
1698 | ALLOCATE(canopy_cover(nvm),stat=ier) |
---|
1699 | l_error = l_error .OR. (ier /= 0) |
---|
1700 | IF (l_error) THEN |
---|
1701 | WRITE(numout,*) ' Memory allocation error for canopy_cover. We stop. We need nvm words = ',nvm |
---|
1702 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1703 | END IF |
---|
1704 | |
---|
1705 | ALLOCATE(nmaxtrees(nvm),stat=ier) |
---|
1706 | l_error = l_error .OR. (ier /= 0) |
---|
1707 | IF (l_error) THEN |
---|
1708 | WRITE(numout,*) ' Memory allocation error for nmaxtrees. We stop. We need nvm words = ',nvm |
---|
1709 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1710 | END IF |
---|
1711 | |
---|
1712 | ALLOCATE(height_init_min(nvm),stat=ier) |
---|
1713 | l_error = l_error .OR. (ier /= 0) |
---|
1714 | IF (l_error) THEN |
---|
1715 | WRITE(numout,*) ' Memory allocation error for height_init_min. We stop. We need nvm words = ',nvm |
---|
1716 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1717 | END IF |
---|
1718 | |
---|
1719 | ALLOCATE(height_init_max(nvm),stat=ier) |
---|
1720 | l_error = l_error .OR. (ier /= 0) |
---|
1721 | IF (l_error) THEN |
---|
1722 | WRITE(numout,*) ' Memory allocation error for height_init_max. We stop. We need nvm words = ',nvm |
---|
1723 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1724 | END IF |
---|
1725 | |
---|
1726 | ALLOCATE(alpha_self_thinning(nvm),stat=ier) |
---|
1727 | l_error = l_error .OR. (ier /= 0) |
---|
1728 | IF (l_error) THEN |
---|
1729 | WRITE(numout,*) ' Memory allocation error for alpha_self_thinning. We stop. We need nvm words = ',nvm |
---|
1730 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1731 | END IF |
---|
1732 | |
---|
1733 | ALLOCATE(beta_self_thinning(nvm),stat=ier) |
---|
1734 | l_error = l_error .OR. (ier /= 0) |
---|
1735 | IF (l_error) THEN |
---|
1736 | WRITE(numout,*) ' Memory allocation error for beta_self_thinning. We stop. We need nvm words = ',nvm |
---|
1737 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1738 | END IF |
---|
1739 | |
---|
1740 | ALLOCATE(fuelwood_diameter(nvm),stat=ier) |
---|
1741 | l_error = l_error .OR. (ier /= 0) |
---|
1742 | IF (l_error) THEN |
---|
1743 | WRITE(numout,*) ' Memory allocation error for fuelwood_diameter. We stop. We need nvm words = ',nvm |
---|
1744 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1745 | END IF |
---|
1746 | |
---|
1747 | ALLOCATE(coppice_kill_be_wood(nvm),stat=ier) |
---|
1748 | l_error = l_error .OR. (ier /= 0) |
---|
1749 | IF (l_error) THEN |
---|
1750 | WRITE(numout,*) ' Memory allocation error for coppice_kill_be_wood. We stop. We need nvm words = ',nvm |
---|
1751 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1752 | END IF |
---|
1753 | |
---|
1754 | ! |
---|
1755 | ! GROWTH |
---|
1756 | ! |
---|
1757 | ALLOCATE(cn_leaf_prescribed(nvm),stat=ier) |
---|
1758 | l_error = l_error .OR. (ier /= 0) |
---|
1759 | IF (l_error) THEN |
---|
1760 | WRITE(numout,*) ' Memory allocation error for cn_leaf_prescribed. We stop. We need nvm words = ',nvm |
---|
1761 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1762 | END IF |
---|
1763 | |
---|
1764 | ALLOCATE(fcn_wood(nvm),stat=ier) |
---|
1765 | l_error = l_error .OR. (ier /= 0) |
---|
1766 | IF (l_error) THEN |
---|
1767 | WRITE(numout,*) ' Memory allocation error for fcn_wood. We stop. We need nvm words = ',nvm |
---|
1768 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1769 | END IF |
---|
1770 | |
---|
1771 | ALLOCATE(fcn_root(nvm),stat=ier) |
---|
1772 | l_error = l_error .OR. (ier /= 0) |
---|
1773 | IF (l_error) THEN |
---|
1774 | WRITE(numout,*) ' Memory allocation error for fcn_root. We stop. We need nvm words = ',nvm |
---|
1775 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1776 | END IF |
---|
1777 | |
---|
1778 | ALLOCATE(k_latosa_max(nvm),stat=ier) |
---|
1779 | l_error = l_error .OR. (ier /= 0) |
---|
1780 | IF (l_error) THEN |
---|
1781 | WRITE(numout,*) ' Memory allocation error for k_latosa_max. We stop. We need nvm words = ',nvm |
---|
1782 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1783 | END IF |
---|
1784 | |
---|
1785 | ALLOCATE(k_latosa_min(nvm),stat=ier) |
---|
1786 | l_error = l_error .OR. (ier /= 0) |
---|
1787 | IF (l_error) THEN |
---|
1788 | WRITE(numout,*) ' Memory allocation error for k_latosa_min. We stop. We need nvm words = ',nvm |
---|
1789 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1790 | END IF |
---|
1791 | |
---|
1792 | ALLOCATE(fruit_alloc(nvm),stat=ier) |
---|
1793 | l_error = l_error .OR. (ier /= 0) |
---|
1794 | IF (l_error) THEN |
---|
1795 | WRITE(numout,*) ' Memory allocation error for fruit_alloc. We stop. We need nvm words = ',nvm |
---|
1796 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1797 | END IF |
---|
1798 | |
---|
1799 | ALLOCATE(m_dv(nvm),stat=ier) |
---|
1800 | l_error = l_error .OR. (ier /= 0) |
---|
1801 | IF (l_error) THEN |
---|
1802 | WRITE(numout,*) ' Memory allocation error for m_dv. We stop. We need nvm words = ',nvm |
---|
1803 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1804 | END IF |
---|
1805 | |
---|
1806 | ALLOCATE(recruitment_light_threshold(nvm),stat=ier) |
---|
1807 | l_error = l_error .OR. (ier /= 0) |
---|
1808 | IF (l_error) THEN |
---|
1809 | WRITE(numout,*) ' Memory allocation error for recruitment_light_threshold. We stop. We need nvm words = ',nvm |
---|
1810 | STOP 'pft_parameters_alloc' |
---|
1811 | END IF |
---|
1812 | |
---|
1813 | ALLOCATE(dia_recr(nvm),stat=ier) |
---|
1814 | l_error = l_error .OR. (ier /= 0) |
---|
1815 | IF (l_error) THEN |
---|
1816 | WRITE(numout,*) ' Memory allocation error for dia_recr. We stop. We need nvm words = ',nvm |
---|
1817 | STOP 'pft_parameters_alloc' |
---|
1818 | END IF |
---|
1819 | |
---|
1820 | ALLOCATE(hei_recr(nvm),stat=ier) |
---|
1821 | l_error = l_error .OR. (ier /= 0) |
---|
1822 | IF (l_error) THEN |
---|
1823 | WRITE(numout,*) ' Memory allocation error for hei_recr. We stop. We need nvm words = ',nvm |
---|
1824 | STOP 'pft_parameters_alloc' |
---|
1825 | END IF |
---|
1826 | |
---|
1827 | ALLOCATE(lai_max_to_happy(nvm),stat=ier) |
---|
1828 | l_error = l_error .OR. (ier /= 0) |
---|
1829 | IF (l_error) THEN |
---|
1830 | WRITE(numout,*) ' Memory allocation error for lai_max_to_happy. We stop. We need nvm words = ',nvm |
---|
1831 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1832 | END IF |
---|
1833 | |
---|
1834 | ALLOCATE(k_root(nvm),stat=ier) |
---|
1835 | l_error = l_error .OR. (ier /= 0) |
---|
1836 | IF (l_error) THEN |
---|
1837 | WRITE(numout,*) ' Memory allocation error for k_root. We stop. We need nvm words = ',nvm |
---|
1838 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1839 | END IF |
---|
1840 | |
---|
1841 | ALLOCATE(k_sap(nvm),stat=ier) |
---|
1842 | l_error = l_error .OR. (ier /= 0) |
---|
1843 | IF (l_error) THEN |
---|
1844 | WRITE(numout,*) ' Memory allocation error for k_sap. We stop. We need nvm words = ',nvm |
---|
1845 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1846 | END IF |
---|
1847 | |
---|
1848 | ALLOCATE(k_leaf(nvm),stat=ier) |
---|
1849 | l_error = l_error .OR. (ier /= 0) |
---|
1850 | IF (l_error) THEN |
---|
1851 | WRITE(numout,*) ' Memory allocation error for k_leaf. We stop. We need nvm words = ',nvm |
---|
1852 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1853 | END IF |
---|
1854 | |
---|
1855 | ALLOCATE(phi_leaf(nvm),stat=ier) |
---|
1856 | l_error = l_error .OR. (ier /= 0) |
---|
1857 | IF (l_error) THEN |
---|
1858 | WRITE(numout,*) ' Memory allocation error for phi_leaf. We stop. We need nvm words = ',nvm |
---|
1859 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1860 | END IF |
---|
1861 | |
---|
1862 | ALLOCATE(phi_50(nvm),stat=ier) |
---|
1863 | l_error = l_error .OR. (ier /= 0) |
---|
1864 | IF (l_error) THEN |
---|
1865 | WRITE(numout,*) ' Memory allocation error for phi_50. We stop. We need nvm words = ',nvm |
---|
1866 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1867 | END IF |
---|
1868 | |
---|
1869 | ALLOCATE(c_cavitation(nvm),stat=ier) |
---|
1870 | l_error = l_error .OR. (ier /= 0) |
---|
1871 | IF (l_error) THEN |
---|
1872 | WRITE(numout,*) ' Memory allocation error for c_cavitation. We stop. We need nvm words = ',nvm |
---|
1873 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1874 | END IF |
---|
1875 | |
---|
1876 | ALLOCATE(phi_soil_tune(nvm),stat=ier) |
---|
1877 | l_error = l_error .OR. (ier /= 0) |
---|
1878 | IF (l_error) THEN |
---|
1879 | WRITE(numout,*) ' Memory allocation error for phi_soil_tune. We stop. We need nvm words = ',nvm |
---|
1880 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1881 | END IF |
---|
1882 | |
---|
1883 | ALLOCATE(lai_happy(nvm),stat=ier) |
---|
1884 | l_error = l_error .OR. (ier /= 0) |
---|
1885 | IF (l_error) THEN |
---|
1886 | WRITE(numout,*) ' Memory allocation error for lai_happy. We stop. We need nvm words = ',nvm |
---|
1887 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1888 | END IF |
---|
1889 | |
---|
1890 | |
---|
1891 | !--------------------------------------------------------------------------------------- |
---|
1892 | ! tzjh hydraulic architecture |
---|
1893 | |
---|
1894 | ALLOCATE(gpsi(nvm),stat=ier) |
---|
1895 | l_error = l_error .OR. (ier /= 0) |
---|
1896 | IF (l_error) THEN |
---|
1897 | WRITE(numout,*) ' Memory allocation error for gpsi. We stop. We need nvm words = ',nvm |
---|
1898 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1899 | END IF |
---|
1900 | |
---|
1901 | ALLOCATE(gpsi_50(nvm),stat=ier) |
---|
1902 | l_error = l_error .OR. (ier /= 0) |
---|
1903 | IF (l_error) THEN |
---|
1904 | WRITE(numout,*) ' Memory allocation error for gpsi_50. We stop. We need nvm words = ',nvm |
---|
1905 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1906 | END IF |
---|
1907 | |
---|
1908 | ALLOCATE(gmax(nvm),stat=ier) |
---|
1909 | l_error = l_error .OR. (ier /= 0) |
---|
1910 | IF (l_error) THEN |
---|
1911 | WRITE(numout,*) ' Memory allocation error for gmax. We stop. We need nvm words = ',nvm |
---|
1912 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1913 | END IF |
---|
1914 | |
---|
1915 | ALLOCATE(gmin(nvm),stat=ier) |
---|
1916 | l_error = l_error .OR. (ier /= 0) |
---|
1917 | IF (l_error) THEN |
---|
1918 | WRITE(numout,*) ' Memory allocation error for gmin. We stop. We need nvm words = ',nvm |
---|
1919 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1920 | END IF |
---|
1921 | |
---|
1922 | ALLOCATE(kmax_leaf(nvm),stat=ier) |
---|
1923 | l_error = l_error .OR. (ier /= 0) |
---|
1924 | IF (l_error) THEN |
---|
1925 | WRITE(numout,*) ' Memory allocation error for kmax_leaf. We stop. We need nvm words = ',nvm |
---|
1926 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1927 | END IF |
---|
1928 | |
---|
1929 | ALLOCATE(kmax_stem(nvm),stat=ier) |
---|
1930 | l_error = l_error .OR. (ier /= 0) |
---|
1931 | IF (l_error) THEN |
---|
1932 | WRITE(numout,*) ' Memory allocation error for kmax_stem. We stop. We need nvm words = ',nvm |
---|
1933 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1934 | END IF |
---|
1935 | |
---|
1936 | ALLOCATE(kmax_root(nvm),stat=ier) |
---|
1937 | l_error = l_error .OR. (ier /= 0) |
---|
1938 | IF (l_error) THEN |
---|
1939 | WRITE(numout,*) ' Memory allocation error for kmax_root. We stop. We need nvm words = ',nvm |
---|
1940 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1941 | END IF |
---|
1942 | |
---|
1943 | ALLOCATE(a_leaf(nvm),stat=ier) |
---|
1944 | l_error = l_error .OR. (ier /= 0) |
---|
1945 | IF (l_error) THEN |
---|
1946 | WRITE(numout,*) ' Memory allocation error for a_leaf. We stop. We need nvm words = ',nvm |
---|
1947 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1948 | END IF |
---|
1949 | |
---|
1950 | ALLOCATE(a_stem(nvm),stat=ier) |
---|
1951 | l_error = l_error .OR. (ier /= 0) |
---|
1952 | IF (l_error) THEN |
---|
1953 | WRITE(numout,*) ' Memory allocation error for a_stem. We stop. We need nvm words = ',nvm |
---|
1954 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1955 | END IF |
---|
1956 | |
---|
1957 | ALLOCATE(a_root(nvm),stat=ier) |
---|
1958 | l_error = l_error .OR. (ier /= 0) |
---|
1959 | IF (l_error) THEN |
---|
1960 | WRITE(numout,*) ' Memory allocation error for a_root. We stop. We need nvm words = ',nvm |
---|
1961 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1962 | END IF |
---|
1963 | |
---|
1964 | ALLOCATE(P50_leaf(nvm),stat=ier) |
---|
1965 | l_error = l_error .OR. (ier /= 0) |
---|
1966 | IF (l_error) THEN |
---|
1967 | WRITE(numout,*) ' Memory allocation error for P50_leaf. We stop. We need nvm words = ',nvm |
---|
1968 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1969 | END IF |
---|
1970 | |
---|
1971 | ALLOCATE(P50_stem(nvm),stat=ier) |
---|
1972 | l_error = l_error .OR. (ier /= 0) |
---|
1973 | IF (l_error) THEN |
---|
1974 | WRITE(numout,*) ' Memory allocation error for P50_stem. We stop. We need nvm words = ',nvm |
---|
1975 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1976 | END IF |
---|
1977 | |
---|
1978 | ALLOCATE(P50_root(nvm),stat=ier) |
---|
1979 | l_error = l_error .OR. (ier /= 0) |
---|
1980 | IF (l_error) THEN |
---|
1981 | WRITE(numout,*) ' Memory allocation error for P50_root. We stop. We need nvm words = ',nvm |
---|
1982 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1983 | END IF |
---|
1984 | |
---|
1985 | ALLOCATE(wood_density(nvm),stat=ier) |
---|
1986 | l_error = l_error .OR. (ier /= 0) |
---|
1987 | IF (l_error) THEN |
---|
1988 | WRITE(numout,*) ' Memory allocation error for wood_density. We stop. We need nvm words = ',nvm |
---|
1989 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1990 | END IF |
---|
1991 | |
---|
1992 | ALLOCATE(w_density_stem(nvm),stat=ier) |
---|
1993 | l_error = l_error .OR. (ier /= 0) |
---|
1994 | IF (l_error) THEN |
---|
1995 | WRITE(numout,*) ' Memory allocation error for w_density_stem. We stop. We need nvm words = ',nvm |
---|
1996 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
1997 | END IF |
---|
1998 | |
---|
1999 | ALLOCATE(root_shoot_ratio(nvm),stat=ier) |
---|
2000 | l_error = l_error .OR. (ier /= 0) |
---|
2001 | IF (l_error) THEN |
---|
2002 | WRITE(numout,*) ' Memory allocation error for root_shoot_ration. We stop. We need nvm words = ',nvm |
---|
2003 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2004 | END IF |
---|
2005 | |
---|
2006 | ALLOCATE(rwc_root(nvm),stat=ier) |
---|
2007 | l_error = l_error .OR. (ier /= 0) |
---|
2008 | IF (l_error) THEN |
---|
2009 | WRITE(numout,*) ' Memory allocation error for rwc_root. We stop. We need nvm words = ',nvm |
---|
2010 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2011 | END IF |
---|
2012 | |
---|
2013 | ALLOCATE(root_density(nvm),stat=ier) |
---|
2014 | l_error = l_error .OR. (ier /= 0) |
---|
2015 | IF (l_error) THEN |
---|
2016 | WRITE(numout,*) ' Memory allocation error for root_density. We stop. We need nvm words = ',nvm |
---|
2017 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2018 | END IF |
---|
2019 | |
---|
2020 | ALLOCATE(LDMC(nvm),stat=ier) |
---|
2021 | l_error = l_error .OR. (ier /= 0) |
---|
2022 | IF (l_error) THEN |
---|
2023 | WRITE(numout,*) ' Memory allocation error for LDMC. We stop. We need nvm words = ',nvm |
---|
2024 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2025 | END IF |
---|
2026 | |
---|
2027 | ALLOCATE(sla_hydro(nvm),stat=ier) |
---|
2028 | l_error = l_error .OR. (ier /= 0) |
---|
2029 | IF (l_error) THEN |
---|
2030 | WRITE(numout,*) ' Memory allocation error for sla_hydro. We stop. We need nvm words = ',nvm |
---|
2031 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2032 | END IF |
---|
2033 | |
---|
2034 | ALLOCATE(cxyl(nvm),stat=ier) |
---|
2035 | l_error = l_error .OR. (ier /= 0) |
---|
2036 | IF (l_error) THEN |
---|
2037 | WRITE(numout,*) ' Memory allocation error for cxyl. We stop. We need nvm words = ',nvm |
---|
2038 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2039 | END IF |
---|
2040 | |
---|
2041 | ALLOCATE(cr(nvm),stat=ier) |
---|
2042 | l_error = l_error .OR. (ier /= 0) |
---|
2043 | IF (l_error) THEN |
---|
2044 | WRITE(numout,*) ' Memory allocation error for cr. We stop. We need nvm words = ',nvm |
---|
2045 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2046 | END IF |
---|
2047 | |
---|
2048 | ALLOCATE(cl(nvm),stat=ier) |
---|
2049 | l_error = l_error .OR. (ier /= 0) |
---|
2050 | IF (l_error) THEN |
---|
2051 | WRITE(numout,*) ' Memory allocation error for cl. We stop. We need nvm words = ',nvm |
---|
2052 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2053 | END IF |
---|
2054 | |
---|
2055 | ! |
---|
2056 | ! PRESCRIBE |
---|
2057 | ! |
---|
2058 | |
---|
2059 | ALLOCATE(tune_reserves_in_sapling(nvm),stat=ier) |
---|
2060 | l_error = l_error .OR. (ier /= 0) |
---|
2061 | IF (l_error) THEN |
---|
2062 | WRITE(numout,*) ' Memory allocation error for tune_reserves_in_sapling. We stop. We need nvm words = ',nvm |
---|
2063 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2064 | END IF |
---|
2065 | ! This prevents a crash in getin_p with NAG, though I'm not sure why. |
---|
2066 | tune_reserves_in_sapling(:)=zero |
---|
2067 | |
---|
2068 | |
---|
2069 | ! |
---|
2070 | ! MORTALITY |
---|
2071 | ! |
---|
2072 | |
---|
2073 | ALLOCATE(death_distribution_factor(nvm),stat=ier) |
---|
2074 | l_error = l_error .OR. (ier /= 0) |
---|
2075 | IF (l_error) THEN |
---|
2076 | WRITE(numout,*) ' Memory allocation error for death_distribution_factor. We stop. We need nvm words = ',nvm |
---|
2077 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2078 | END IF |
---|
2079 | |
---|
2080 | ALLOCATE(npp_reset_value(nvm),stat=ier) |
---|
2081 | l_error = l_error .OR. (ier /= 0) |
---|
2082 | IF (l_error) THEN |
---|
2083 | WRITE(numout,*) ' Memory allocation error for npp_reset_value. We stop. We need nvm words = ',nvm |
---|
2084 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2085 | END IF |
---|
2086 | |
---|
2087 | ! |
---|
2088 | ! FIRE |
---|
2089 | ! |
---|
2090 | ALLOCATE(flam(nvm),stat=ier) |
---|
2091 | l_error = l_error .OR. (ier /= 0) |
---|
2092 | IF (l_error) THEN |
---|
2093 | WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm |
---|
2094 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2095 | END IF |
---|
2096 | |
---|
2097 | ALLOCATE(resist(nvm),stat=ier) |
---|
2098 | l_error = l_error .OR. (ier /= 0) |
---|
2099 | IF (l_error) THEN |
---|
2100 | WRITE(numout,*) ' Memory allocation error for resist. We stop. We need nvm words = ',nvm |
---|
2101 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2102 | END IF |
---|
2103 | |
---|
2104 | ! |
---|
2105 | ! LUC |
---|
2106 | ! |
---|
2107 | ALLOCATE(coeff_lcchange_s(nvm),stat=ier) |
---|
2108 | l_error = l_error .OR. (ier /= 0) |
---|
2109 | IF (l_error) THEN |
---|
2110 | WRITE(numout,*) ' Memory allocation error for coeff_lcchange_s. We stop. We need nvm words = ',nvm |
---|
2111 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2112 | END IF |
---|
2113 | |
---|
2114 | ALLOCATE(coeff_lcchange_m(nvm),stat=ier) |
---|
2115 | l_error = l_error .OR. (ier /= 0) |
---|
2116 | IF (l_error) THEN |
---|
2117 | WRITE(numout,*) ' Memory allocation error for coeff_lcchange_m. We stop. We need nvm words = ',nvm |
---|
2118 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2119 | END IF |
---|
2120 | |
---|
2121 | ALLOCATE(coeff_lcchange_l(nvm),stat=ier) |
---|
2122 | l_error = l_error .OR. (ier /= 0) |
---|
2123 | IF (l_error) THEN |
---|
2124 | WRITE(numout,*) ' Memory allocation error for coeff_lcchange_l. We stop. We need nvm words = ',nvm |
---|
2125 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2126 | END IF |
---|
2127 | |
---|
2128 | ! |
---|
2129 | ! PHENOLOGY |
---|
2130 | ! |
---|
2131 | ! 1. stomate |
---|
2132 | ! |
---|
2133 | ALLOCATE(lai_max(nvm),stat=ier) |
---|
2134 | l_error = l_error .OR. (ier /= 0) |
---|
2135 | IF (l_error) THEN |
---|
2136 | WRITE(numout,*) ' Memory allocation error for lai_max. We stop. We need nvm words = ',nvm |
---|
2137 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2138 | END IF |
---|
2139 | |
---|
2140 | ALLOCATE(pheno_type(nvm),stat=ier) |
---|
2141 | l_error = l_error .OR. (ier /= 0) |
---|
2142 | IF (l_error) THEN |
---|
2143 | WRITE(numout,*) ' Memory allocation error for pheno_type. We stop. We need nvm words = ',nvm |
---|
2144 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2145 | END IF |
---|
2146 | |
---|
2147 | ! |
---|
2148 | ! 2. Leaf Onset |
---|
2149 | ! |
---|
2150 | ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier) |
---|
2151 | l_error = l_error .OR. (ier /= 0) |
---|
2152 | IF (l_error) THEN |
---|
2153 | WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_c. We stop. We need nvm words = ',nvm |
---|
2154 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2155 | END IF |
---|
2156 | |
---|
2157 | ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier) |
---|
2158 | l_error = l_error .OR. (ier /= 0) |
---|
2159 | IF (l_error) THEN |
---|
2160 | WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_b. We stop. We need nvm words = ',nvm |
---|
2161 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2162 | END IF |
---|
2163 | |
---|
2164 | ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier) |
---|
2165 | l_error = l_error .OR. (ier /= 0) |
---|
2166 | IF (l_error) THEN |
---|
2167 | WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_a. We stop. We need nvm words = ',nvm |
---|
2168 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2169 | END IF |
---|
2170 | |
---|
2171 | ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier) |
---|
2172 | l_error = l_error .OR. (ier /= 0) |
---|
2173 | IF (l_error) THEN |
---|
2174 | WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit. We stop. We need nvm words = ',nvm*3 |
---|
2175 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2176 | END IF |
---|
2177 | pheno_gdd_crit(:,:) = zero |
---|
2178 | |
---|
2179 | ALLOCATE(ngd_crit(nvm),stat=ier) |
---|
2180 | l_error = l_error .OR. (ier /= 0) |
---|
2181 | IF (l_error) THEN |
---|
2182 | WRITE(numout,*) ' Memory allocation error for ngd_crit. We stop. We need nvm words = ',nvm |
---|
2183 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2184 | END IF |
---|
2185 | |
---|
2186 | ALLOCATE(opti_kpheno_crit(nvm),stat=ier) |
---|
2187 | l_error = l_error .OR. (ier /= 0) |
---|
2188 | IF (l_error) THEN |
---|
2189 | WRITE(numout,*) ' Memory allocation error for opti_kpheno_crit. We stop. We need nvm words = ',nvm |
---|
2190 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2191 | END IF |
---|
2192 | |
---|
2193 | ALLOCATE(ncdgdd_temp(nvm),stat=ier) |
---|
2194 | l_error = l_error .OR. (ier /= 0) |
---|
2195 | IF (l_error) THEN |
---|
2196 | WRITE(numout,*) ' Memory allocation error for ncdgdd_temp. We stop. We need nvm words = ',nvm |
---|
2197 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2198 | END IF |
---|
2199 | |
---|
2200 | ALLOCATE(hum_frac(nvm),stat=ier) |
---|
2201 | l_error = l_error .OR. (ier /= 0) |
---|
2202 | IF (l_error) THEN |
---|
2203 | WRITE(numout,*) ' Memory allocation error for hum_frac. We stop. We need nvm words = ',nvm |
---|
2204 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2205 | END IF |
---|
2206 | |
---|
2207 | ALLOCATE(hum_min_time(nvm),stat=ier) |
---|
2208 | l_error = l_error .OR. (ier /= 0) |
---|
2209 | IF (l_error) THEN |
---|
2210 | WRITE(numout,*) ' Memory allocation error for hum_min_time. We stop. We need nvm words = ',nvm |
---|
2211 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2212 | END IF |
---|
2213 | |
---|
2214 | ALLOCATE(tau_sap(nvm),stat=ier) |
---|
2215 | l_error = l_error .OR. (ier /= 0) |
---|
2216 | IF (l_error) THEN |
---|
2217 | WRITE(numout,*) ' Memory allocation error for tau_sap. We stop. We need nvm words = ',nvm |
---|
2218 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2219 | END IF |
---|
2220 | |
---|
2221 | ALLOCATE(tau_fruit(nvm),stat=ier) |
---|
2222 | l_error = l_error .OR. (ier /= 0) |
---|
2223 | IF (l_error) THEN |
---|
2224 | WRITE(numout,*) ' Memory allocation error for tau_fruit. We stop. We need nvm words = ',nvm |
---|
2225 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2226 | END IF |
---|
2227 | |
---|
2228 | ALLOCATE(tau_root(nvm),stat=ier) |
---|
2229 | l_error = l_error .OR. (ier /= 0) |
---|
2230 | IF (l_error) THEN |
---|
2231 | WRITE(numout,*) ' Memory allocation error for tau_root. We stop. We need nvm words = ',nvm |
---|
2232 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2233 | END IF |
---|
2234 | |
---|
2235 | ALLOCATE(tau_leaf(nvm),stat=ier) |
---|
2236 | l_error = l_error .OR. (ier /= 0) |
---|
2237 | IF (l_error) THEN |
---|
2238 | WRITE(numout,*) ' Memory allocation error for tau_leaf. We stop. We need nvm words = ',nvm |
---|
2239 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2240 | END IF |
---|
2241 | |
---|
2242 | ALLOCATE(ecureuil(nvm),stat=ier) |
---|
2243 | l_error = l_error .OR. (ier /= 0) |
---|
2244 | IF (l_error) THEN |
---|
2245 | WRITE(numout,*) ' Memory allocation error for ecureuil. We stop. We need nvm words = ',nvm |
---|
2246 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2247 | END IF |
---|
2248 | |
---|
2249 | ALLOCATE(alloc_min(nvm),stat=ier) |
---|
2250 | l_error = l_error .OR. (ier /= 0) |
---|
2251 | IF (l_error) THEN |
---|
2252 | WRITE(numout,*) ' Memory allocation error for alloc_min. We stop. We need nvm words = ',nvm |
---|
2253 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2254 | END IF |
---|
2255 | |
---|
2256 | ALLOCATE(alloc_max(nvm),stat=ier) |
---|
2257 | l_error = l_error .OR. (ier /= 0) |
---|
2258 | IF (l_error) THEN |
---|
2259 | WRITE(numout,*) ' Memory allocation error for alloc_max. We stop. We need nvm words = ',nvm |
---|
2260 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2261 | END IF |
---|
2262 | |
---|
2263 | ALLOCATE(demi_alloc(nvm),stat=ier) |
---|
2264 | l_error = l_error .OR. (ier /= 0) |
---|
2265 | IF (l_error) THEN |
---|
2266 | WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm |
---|
2267 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2268 | END IF |
---|
2269 | |
---|
2270 | ! |
---|
2271 | ! 3. Senescence |
---|
2272 | ! |
---|
2273 | ALLOCATE(leaffall(nvm),stat=ier) |
---|
2274 | l_error = l_error .OR. (ier /= 0) |
---|
2275 | IF (l_error) THEN |
---|
2276 | WRITE(numout,*) ' Memory allocation error for leaffall. We stop. We need nvm words = ',nvm |
---|
2277 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2278 | END IF |
---|
2279 | |
---|
2280 | ALLOCATE(senescence_type(nvm),stat=ier) |
---|
2281 | l_error = l_error .OR. (ier /= 0) |
---|
2282 | IF (l_error) THEN |
---|
2283 | WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm |
---|
2284 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2285 | END IF |
---|
2286 | |
---|
2287 | ALLOCATE(senescence_hum(nvm),stat=ier) |
---|
2288 | l_error = l_error .OR. (ier /= 0) |
---|
2289 | IF (l_error) THEN |
---|
2290 | WRITE(numout,*) ' Memory allocation error for senescence_hum. We stop. We need nvm words = ',nvm |
---|
2291 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2292 | END IF |
---|
2293 | |
---|
2294 | ALLOCATE(nosenescence_hum(nvm),stat=ier) |
---|
2295 | l_error = l_error .OR. (ier /= 0) |
---|
2296 | IF (l_error) THEN |
---|
2297 | WRITE(numout,*) ' Memory allocation error for nosenescence_hum. We stop. We need nvm words = ',nvm |
---|
2298 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2299 | END IF |
---|
2300 | |
---|
2301 | ALLOCATE(max_turnover_time(nvm),stat=ier) |
---|
2302 | l_error = l_error .OR. (ier /= 0) |
---|
2303 | IF (l_error) THEN |
---|
2304 | WRITE(numout,*) ' Memory allocation error for max_turnover_time. We stop. We need nvm words = ',nvm |
---|
2305 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2306 | END IF |
---|
2307 | |
---|
2308 | ALLOCATE(min_turnover_time(nvm),stat=ier) |
---|
2309 | l_error = l_error .OR. (ier /= 0) |
---|
2310 | IF (l_error) THEN |
---|
2311 | WRITE(numout,*) ' Memory allocation error for min_turnover_time. We stop. We need nvm words = ',nvm |
---|
2312 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2313 | END IF |
---|
2314 | |
---|
2315 | ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier) |
---|
2316 | l_error = l_error .OR. (ier /= 0) |
---|
2317 | IF (l_error) THEN |
---|
2318 | WRITE(numout,*) ' Memory allocation error for min_leaf_age_for_senescence. We stop. We need nvm words = ',nvm |
---|
2319 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2320 | END IF |
---|
2321 | |
---|
2322 | ALLOCATE(senescence_temp_c(nvm),stat=ier) |
---|
2323 | l_error = l_error .OR. (ier /= 0) |
---|
2324 | IF (l_error) THEN |
---|
2325 | WRITE(numout,*) ' Memory allocation error for senescence_temp_c. We stop. We need nvm words = ',nvm |
---|
2326 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2327 | END IF |
---|
2328 | |
---|
2329 | ALLOCATE(senescence_temp_b(nvm),stat=ier) |
---|
2330 | l_error = l_error .OR. (ier /= 0) |
---|
2331 | IF (l_error) THEN |
---|
2332 | WRITE(numout,*) ' Memory allocation error for senescence_temp_b. We stop. We need nvm words = ',nvm |
---|
2333 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2334 | END IF |
---|
2335 | |
---|
2336 | ALLOCATE(senescence_temp_a(nvm),stat=ier) |
---|
2337 | l_error = l_error .OR. (ier /= 0) |
---|
2338 | IF (l_error) THEN |
---|
2339 | WRITE(numout,*) ' Memory allocation error for senescence_temp_a. We stop. We need nvm words = ',nvm |
---|
2340 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2341 | END IF |
---|
2342 | |
---|
2343 | ALLOCATE(senescence_temp(nvm,3),stat=ier) |
---|
2344 | l_error = l_error .OR. (ier /= 0) |
---|
2345 | IF (l_error) THEN |
---|
2346 | WRITE(numout,*) ' Memory allocation error for senescence_temp. We stop. We need nvm*3 words = ',nvm*3 |
---|
2347 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2348 | END IF |
---|
2349 | senescence_temp(:,:) = zero |
---|
2350 | |
---|
2351 | ALLOCATE(gdd_senescence(nvm),stat=ier) |
---|
2352 | l_error = l_error .OR. (ier /= 0) |
---|
2353 | IF (l_error) THEN |
---|
2354 | WRITE(numout,*) ' Memory allocation error for gdd_senescence. We stop. We need nvm words = ',nvm |
---|
2355 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2356 | END IF |
---|
2357 | |
---|
2358 | ALLOCATE(residence_time(nvm),stat=ier) |
---|
2359 | l_error = l_error .OR. (ier /= 0) |
---|
2360 | IF (l_error) THEN |
---|
2361 | WRITE(numout,*) ' Memory allocation error for residence_time. We stop. We need nvm words = ',nvm |
---|
2362 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2363 | END IF |
---|
2364 | |
---|
2365 | ! added by yitong yao 07 Jan 2020 08:24 |
---|
2366 | |
---|
2367 | ALLOCATE(plc_kill_frac(nvm),stat=ier) |
---|
2368 | l_error = l_error .OR. (ier /= 0) |
---|
2369 | IF (l_error) THEN |
---|
2370 | WRITE(numout,*) ' Memory allocation error for plc_kill_frac. We stop. We need nvm words = ',nvm |
---|
2371 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2372 | END IF |
---|
2373 | |
---|
2374 | ! added by yitong yao 07 Jan 2020 08:24 |
---|
2375 | |
---|
2376 | |
---|
2377 | ! added by yitong yao 09 Feb 2020 22:58 |
---|
2378 | |
---|
2379 | ALLOCATE(mor_kill_frac(nvm),stat=ier) |
---|
2380 | l_error = l_error .OR. (ier /= 0) |
---|
2381 | IF (l_error) THEN |
---|
2382 | WRITE(numout,*) ' Memory allocation error for mor_kill_frac. We stop. We need nvm words = ',nvm |
---|
2383 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2384 | END IF |
---|
2385 | |
---|
2386 | ! added by yitong yao 09 Feb 2020 22:58 |
---|
2387 | |
---|
2388 | |
---|
2389 | ALLOCATE(tmin_crit(nvm),stat=ier) |
---|
2390 | l_error = l_error .OR. (ier /= 0) |
---|
2391 | IF (l_error) THEN |
---|
2392 | WRITE(numout,*) ' Memory allocation error for tmin_crit. We stop. We need nvm words = ',nvm |
---|
2393 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2394 | END IF |
---|
2395 | |
---|
2396 | ALLOCATE(tcm_crit(nvm),stat=ier) |
---|
2397 | l_error = l_error .OR. (ier /= 0) |
---|
2398 | IF (l_error) THEN |
---|
2399 | WRITE(numout,*) ' Memory allocation error for tcm_crit. We stop. We need nvm words = ',nvm |
---|
2400 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2401 | END IF |
---|
2402 | |
---|
2403 | ALLOCATE(mortality_min(nvm),stat=ier) |
---|
2404 | l_error = l_error .OR. (ier /= 0) |
---|
2405 | IF (l_error) THEN |
---|
2406 | WRITE(numout,*) ' Memory allocation error for mortality_min. We stop. We need nvm words = ',nvm |
---|
2407 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2408 | END IF |
---|
2409 | |
---|
2410 | ALLOCATE(mortality_max(nvm),stat=ier) |
---|
2411 | l_error = l_error .OR. (ier /= 0) |
---|
2412 | IF (l_error) THEN |
---|
2413 | WRITE(numout,*) ' Memory allocation error for mortality_max. We stop. We need nvm words = ',nvm |
---|
2414 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2415 | END IF |
---|
2416 | |
---|
2417 | ALLOCATE(ref_mortality(nvm),stat=ier) |
---|
2418 | l_error = l_error .OR. (ier /= 0) |
---|
2419 | IF (l_error) THEN |
---|
2420 | WRITE(numout,*) ' Memory allocation error for ref_mortality. We stop. We need nvm words = ',nvm |
---|
2421 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2422 | END IF |
---|
2423 | |
---|
2424 | ALLOCATE(tau_hum_growingseason(nvm),stat=ier) |
---|
2425 | l_error = l_error .OR. (ier /= 0) |
---|
2426 | IF (l_error) THEN |
---|
2427 | WRITE(numout,*) ' Memory allocation error for tau_hum_growingseason. We stop. We need nvm words = ',nvm |
---|
2428 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2429 | END IF |
---|
2430 | |
---|
2431 | ALLOCATE(lai_initmin(nvm),stat=ier) |
---|
2432 | l_error = l_error .OR. (ier /= 0) |
---|
2433 | IF (l_error) THEN |
---|
2434 | WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm |
---|
2435 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2436 | END IF |
---|
2437 | |
---|
2438 | |
---|
2439 | ! |
---|
2440 | ! DGVM |
---|
2441 | ! |
---|
2442 | |
---|
2443 | ! |
---|
2444 | ! KILL |
---|
2445 | ! |
---|
2446 | |
---|
2447 | ALLOCATE(dens_target(nvm),stat=ier) |
---|
2448 | l_error = l_error .OR. (ier /= 0) |
---|
2449 | IF (l_error) THEN |
---|
2450 | WRITE(numout,*) ' Memory allocation error for dens_target. We stop. We need nvm words = ',nvm |
---|
2451 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2452 | END IF |
---|
2453 | |
---|
2454 | |
---|
2455 | ! |
---|
2456 | ! BVOC |
---|
2457 | ! |
---|
2458 | |
---|
2459 | |
---|
2460 | |
---|
2461 | |
---|
2462 | |
---|
2463 | |
---|
2464 | |
---|
2465 | ! |
---|
2466 | ! FOREST MANAGEMENT |
---|
2467 | ! |
---|
2468 | IF (active_flags%forest_management .OR. & |
---|
2469 | active_flags%ok_functional_allocation) THEN |
---|
2470 | |
---|
2471 | ALLOCATE(plantation(nvm),stat=ier) |
---|
2472 | l_error = l_error .OR. (ier /= 0) |
---|
2473 | IF (l_error) THEN |
---|
2474 | WRITE(numout,*) ' Memory allocation error for plantation. We stop. We need nvm words = ',nvm |
---|
2475 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2476 | END IF |
---|
2477 | |
---|
2478 | ALLOCATE(fm_allo_a(nvm),stat=ier) |
---|
2479 | l_error = l_error .OR. (ier /= 0) |
---|
2480 | IF (l_error) THEN |
---|
2481 | WRITE(numout,*) ' Memory allocation error for fm_allo_a. We stop. We need nvm words = ',nvm |
---|
2482 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2483 | END IF |
---|
2484 | ! To prevent a crash in getin_p with NAG. |
---|
2485 | fm_allo_a(:)=zero |
---|
2486 | |
---|
2487 | ALLOCATE(fm_allo_c(nvm),stat=ier) |
---|
2488 | l_error = l_error .OR. (ier /= 0) |
---|
2489 | IF (l_error) THEN |
---|
2490 | WRITE(numout,*) ' Memory allocation error for fm_allo_c. We stop. We need nvm words = ',nvm |
---|
2491 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2492 | END IF |
---|
2493 | ! To prevent a crash in getin_p with NAG. |
---|
2494 | fm_allo_c(:)=zero |
---|
2495 | |
---|
2496 | ALLOCATE(fm_allo_d(nvm),stat=ier) |
---|
2497 | l_error = l_error .OR. (ier /= 0) |
---|
2498 | IF (l_error) THEN |
---|
2499 | WRITE(numout,*) ' Memory allocation error for fm_allo_d. We stop. We need nvm words = ',nvm |
---|
2500 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2501 | END IF |
---|
2502 | ! To prevent a crash in getin_p with NAG. |
---|
2503 | fm_allo_d(:)=zero |
---|
2504 | |
---|
2505 | ALLOCATE(fm_allo_p(nvm),stat=ier) |
---|
2506 | l_error = l_error .OR. (ier /= 0) |
---|
2507 | IF (l_error) THEN |
---|
2508 | WRITE(numout,*) ' Memory allocation error for fm_allo_p. We stop. We need nvm words = ',nvm |
---|
2509 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2510 | END IF |
---|
2511 | ! To prevent a crash in getin_p with NAG. |
---|
2512 | fm_allo_p(:)=zero |
---|
2513 | |
---|
2514 | ALLOCATE(fm_allo_q(nvm),stat=ier) |
---|
2515 | l_error = l_error .OR. (ier /= 0) |
---|
2516 | IF (l_error) THEN |
---|
2517 | WRITE(numout,*) ' Memory allocation error for fm_allo_q. We stop. We need nvm words = ',nvm |
---|
2518 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2519 | END IF |
---|
2520 | ! To prevent a crash in getin_p with NAG. |
---|
2521 | fm_allo_q(:)=zero |
---|
2522 | |
---|
2523 | ALLOCATE(allo_crown_a0(nvm),stat=ier) |
---|
2524 | l_error = l_error .OR. (ier /= 0) |
---|
2525 | IF (l_error) THEN |
---|
2526 | WRITE(numout,*) ' Memory allocation error for allo_crown_a0. We stop. We need nvm words = ',nvm |
---|
2527 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2528 | END IF |
---|
2529 | |
---|
2530 | ALLOCATE(allo_crown_a1(nvm),stat=ier) |
---|
2531 | l_error = l_error .OR. (ier /= 0) |
---|
2532 | IF (l_error) THEN |
---|
2533 | WRITE(numout,*) ' Memory allocation error for allo_crown_a1. We stop. We need nvm words = ',nvm |
---|
2534 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2535 | END IF |
---|
2536 | |
---|
2537 | ALLOCATE(allo_crown_a2(nvm),stat=ier) |
---|
2538 | l_error = l_error .OR. (ier /= 0) |
---|
2539 | IF (l_error) THEN |
---|
2540 | WRITE(numout,*) ' Memory allocation error for allo_crown_a2. We stop. We need nvm words = ',nvm |
---|
2541 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2542 | END IF |
---|
2543 | |
---|
2544 | ALLOCATE(h_first(nvm),stat=ier) |
---|
2545 | l_error = l_error .OR. (ier /= 0) |
---|
2546 | IF (l_error) THEN |
---|
2547 | WRITE(numout,*) ' Memory allocation error for h_first. We stop. We need nvm words = ',nvm |
---|
2548 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2549 | END IF |
---|
2550 | |
---|
2551 | ALLOCATE(thinstrat(nvm),stat=ier) |
---|
2552 | l_error = l_error .OR. (ier /= 0) |
---|
2553 | IF (l_error) THEN |
---|
2554 | WRITE(numout,*) ' Memory allocation error for thinstrat. We stop. We need nvm words = ',nvm |
---|
2555 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2556 | END IF |
---|
2557 | |
---|
2558 | ALLOCATE(taumin(nvm),stat=ier) |
---|
2559 | l_error = l_error .OR. (ier /= 0) |
---|
2560 | IF (l_error) THEN |
---|
2561 | WRITE(numout,*) ' Memory allocation error for taumin. We stop. We need nvm words = ',nvm |
---|
2562 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2563 | END IF |
---|
2564 | |
---|
2565 | ALLOCATE(taumax(nvm),stat=ier) |
---|
2566 | l_error = l_error .OR. (ier /= 0) |
---|
2567 | IF (l_error) THEN |
---|
2568 | WRITE(numout,*) ' Memory allocation error for taumax. We stop. We need nvm words = ',nvm |
---|
2569 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2570 | END IF |
---|
2571 | |
---|
2572 | ALLOCATE(alpha_rdi_upper(nvm),stat=ier) |
---|
2573 | l_error = l_error .OR. (ier /= 0) |
---|
2574 | IF (l_error) THEN |
---|
2575 | WRITE(numout,*) ' Memory allocation error for alpha_rdi_upper. We stop. We need nvm words = ',nvm |
---|
2576 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2577 | END IF |
---|
2578 | |
---|
2579 | ALLOCATE(beta_rdi_upper(nvm),stat=ier) |
---|
2580 | l_error = l_error .OR. (ier /= 0) |
---|
2581 | IF (l_error) THEN |
---|
2582 | WRITE(numout,*) ' Memory allocation error for beta_rdi_upper. We stop. We need nvm words = ',nvm |
---|
2583 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2584 | END IF |
---|
2585 | |
---|
2586 | ALLOCATE(alpha_rdi_lower(nvm),stat=ier) |
---|
2587 | l_error = l_error .OR. (ier /= 0) |
---|
2588 | IF (l_error) THEN |
---|
2589 | WRITE(numout,*) ' Memory allocation error for alpha_rdi_lower. We stop. We need nvm words = ',nvm |
---|
2590 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2591 | END IF |
---|
2592 | |
---|
2593 | ALLOCATE(beta_rdi_lower(nvm),stat=ier) |
---|
2594 | l_error = l_error .OR. (ier /= 0) |
---|
2595 | IF (l_error) THEN |
---|
2596 | WRITE(numout,*) ' Memory allocation error for beta_rdi_lower. We stop. We need nvm words = ',nvm |
---|
2597 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2598 | END IF |
---|
2599 | |
---|
2600 | ALLOCATE(largest_tree_dia(nvm),stat=ier) |
---|
2601 | l_error = l_error .OR. (ier /= 0) |
---|
2602 | IF (l_error) THEN |
---|
2603 | WRITE(numout,*) ' Memory allocation error for largest_tree_dia. We stop. We need nvm words = ',nvm |
---|
2604 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2605 | END IF |
---|
2606 | |
---|
2607 | ALLOCATE(branch_ratio(nvm),stat=ier) |
---|
2608 | l_error = l_error .OR. (ier /= 0) |
---|
2609 | IF (l_error) THEN |
---|
2610 | WRITE(numout,*) ' Memory allocation error for branch_ratio. We stop. We need nvm words = ',nvm |
---|
2611 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2612 | END IF |
---|
2613 | |
---|
2614 | ALLOCATE(branch_harvest(nvm),stat=ier) |
---|
2615 | l_error = l_error .OR. (ier /= 0) |
---|
2616 | IF (l_error) THEN |
---|
2617 | WRITE(numout,*) ' Memory allocation error for branch_harvest. We stop. We need nvm words = ',nvm |
---|
2618 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2619 | END IF |
---|
2620 | |
---|
2621 | ALLOCATE(decl_factor(nvm),stat=ier) |
---|
2622 | l_error = l_error .OR. (ier /= 0) |
---|
2623 | IF (l_error) THEN |
---|
2624 | WRITE(numout,*) ' Memory allocation error for decl_factor. We stop. We need nvm words = ',nvm |
---|
2625 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2626 | END IF |
---|
2627 | |
---|
2628 | ! ALLOCATE(opt_factor(nvm),stat=ier) |
---|
2629 | ! l_error = l_error .OR. (ier /= 0) |
---|
2630 | ! IF (l_error) THEN |
---|
2631 | ! WRITE(numout,*) ' Memory allocation error for opt_factor. We stop. We need nvm words = ',nvm |
---|
2632 | ! CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2633 | ! END IF |
---|
2634 | |
---|
2635 | ALLOCATE(coppice_diameter(nvm),stat=ier) |
---|
2636 | l_error = l_error .OR. (ier /= 0) |
---|
2637 | IF (l_error) THEN |
---|
2638 | WRITE(numout,*) ' Memory allocation error for coppice_diameter. We stop. We need nvm words = ',nvm |
---|
2639 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2640 | END IF |
---|
2641 | |
---|
2642 | ALLOCATE(shoots_per_stool(nvm),stat=ier) |
---|
2643 | l_error = l_error .OR. (ier /= 0) |
---|
2644 | IF (l_error) THEN |
---|
2645 | WRITE(numout,*) ' Memory allocation error for shoots_per_stool. We stop. We need nvm words = ',nvm |
---|
2646 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2647 | END IF |
---|
2648 | |
---|
2649 | ALLOCATE(src_rot_length(nvm),stat=ier) |
---|
2650 | l_error = l_error .OR. (ier /= 0) |
---|
2651 | IF (l_error) THEN |
---|
2652 | WRITE(numout,*) ' Memory allocation error for src_rot_length. We stop. We need nvm words = ',nvm |
---|
2653 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2654 | END IF |
---|
2655 | |
---|
2656 | ALLOCATE(src_nrots(nvm),stat=ier) |
---|
2657 | l_error = l_error .OR. (ier /= 0) |
---|
2658 | IF (l_error) THEN |
---|
2659 | WRITE(numout,*) ' Memory allocation error for src_nrots. We stop. We need nvm words = ',nvm |
---|
2660 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2661 | END IF |
---|
2662 | |
---|
2663 | ALLOCATE(deleuze_a(nvm),stat=ier) |
---|
2664 | l_error = l_error .OR. (ier /= 0) |
---|
2665 | IF (l_error) THEN |
---|
2666 | WRITE(numout,*) ' Memory allocation error for deleuze_a. We stop. We need nvm words = ',nvm |
---|
2667 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2668 | END IF |
---|
2669 | |
---|
2670 | ALLOCATE(deleuze_b(nvm),stat=ier) |
---|
2671 | l_error = l_error .OR. (ier /= 0) |
---|
2672 | IF (l_error) THEN |
---|
2673 | WRITE(numout,*) ' Memory allocation error for deleuze_b. We stop. We need nvm words = ',nvm |
---|
2674 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2675 | END IF |
---|
2676 | |
---|
2677 | ALLOCATE(deleuze_p_all(nvm),stat=ier) |
---|
2678 | l_error = l_error .OR. (ier /= 0) |
---|
2679 | IF (l_error) THEN |
---|
2680 | WRITE(numout,*) ' Memory allocation error for deleuze_p_all. We stop. We need nvm words = ',nvm |
---|
2681 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2682 | END IF |
---|
2683 | |
---|
2684 | ALLOCATE(deleuze_p_coppice(nvm),stat=ier) |
---|
2685 | l_error = l_error .OR. (ier /= 0) |
---|
2686 | IF (l_error) THEN |
---|
2687 | WRITE(numout,*) ' Memory allocation error for deleuze_p_coppice. We stop. We need nvm words = ',nvm |
---|
2688 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2689 | END IF |
---|
2690 | END IF |
---|
2691 | |
---|
2692 | |
---|
2693 | |
---|
2694 | ! |
---|
2695 | ! CROPLAND MANAGEMENT |
---|
2696 | ! |
---|
2697 | ALLOCATE(harvest_ratio(nvm),stat=ier) |
---|
2698 | l_error = l_error .OR. (ier /= 0) |
---|
2699 | IF (l_error) THEN |
---|
2700 | WRITE(numout,*) ' Memory allocation error for harvest_ratio. We stop. We need nvm words = ',nvm |
---|
2701 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2702 | END IF |
---|
2703 | |
---|
2704 | ! |
---|
2705 | ! OTHER |
---|
2706 | ! |
---|
2707 | ALLOCATE(bm_sapl_old(nvm,nparts,nelements),stat=ier) |
---|
2708 | l_error = l_error .OR. (ier /= 0) |
---|
2709 | IF (l_error) THEN |
---|
2710 | WRITE(numout,*) ' Memory allocation error for bm_sapl_old. We stop. We need nvm*nparts*nelements words = ',& |
---|
2711 | & nvm*nparts*nelements |
---|
2712 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2713 | END IF |
---|
2714 | |
---|
2715 | ALLOCATE(migrate(nvm),stat=ier) |
---|
2716 | l_error = l_error .OR. (ier /= 0) |
---|
2717 | IF (l_error) THEN |
---|
2718 | WRITE(numout,*) ' Memory allocation error for migrate. We stop. We need nvm words = ',nvm |
---|
2719 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2720 | END IF |
---|
2721 | |
---|
2722 | ALLOCATE(maxdia(nvm),stat=ier) |
---|
2723 | l_error = l_error .OR. (ier /= 0) |
---|
2724 | IF (l_error) THEN |
---|
2725 | WRITE(numout,*) ' Memory allocation error for maxdia. We stop. We need nvm words = ',nvm |
---|
2726 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2727 | END IF |
---|
2728 | |
---|
2729 | ALLOCATE(cn_sapl(nvm),stat=ier) |
---|
2730 | l_error = l_error .OR. (ier /= 0) |
---|
2731 | IF (l_error) THEN |
---|
2732 | WRITE(numout,*) ' Memory allocation error for cn_sapl. We stop. We need nvm words = ',nvm |
---|
2733 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2734 | END IF |
---|
2735 | |
---|
2736 | ALLOCATE(leaf_timecst(nvm),stat=ier) |
---|
2737 | l_error = l_error .OR. (ier /= 0) |
---|
2738 | IF (l_error) THEN |
---|
2739 | WRITE(numout,*) ' Memory allocation error for leaf_timecst. We stop. We need nvm words = ',nvm |
---|
2740 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
2741 | END IF |
---|
2742 | |
---|
2743 | ENDIF ! (active_flags%ok_stomate) |
---|
2744 | |
---|
2745 | END SUBROUTINE pft_parameters_alloc |
---|
2746 | ! |
---|
2747 | != |
---|
2748 | ! |
---|
2749 | |
---|
2750 | !! ================================================================================================================================ |
---|
2751 | !! SUBROUTINE : config_pft_parameters |
---|
2752 | !! |
---|
2753 | !>\BRIEF This subroutine will read the imposed values for the global pft |
---|
2754 | !! parameters (sechiba + stomate). It is not called if IMPOSE_PARAM is set to NO. |
---|
2755 | !! |
---|
2756 | !! DESCRIPTION : None |
---|
2757 | !! |
---|
2758 | !! RECENT CHANGE(S): None |
---|
2759 | !! |
---|
2760 | !! MAIN OUTPUT VARIABLE(S): None |
---|
2761 | !! |
---|
2762 | !! REFERENCE(S) : None |
---|
2763 | !! |
---|
2764 | !! FLOWCHART : None |
---|
2765 | !! \n |
---|
2766 | !_ ================================================================================================================================ |
---|
2767 | |
---|
2768 | SUBROUTINE config_pft_parameters |
---|
2769 | |
---|
2770 | IMPLICIT NONE |
---|
2771 | |
---|
2772 | !! 0. Variables and parameters declaration |
---|
2773 | |
---|
2774 | !! 0.4 Local variable |
---|
2775 | |
---|
2776 | LOGICAL, SAVE :: first_call = .TRUE. !! To keep first call trace (true/false) |
---|
2777 | !$OMP THREADPRIVATE(first_call) |
---|
2778 | INTEGER(i_std) :: jv,ivm !! Index (untiless) |
---|
2779 | |
---|
2780 | !_ ================================================================================================================================ |
---|
2781 | |
---|
2782 | IF (first_call) THEN |
---|
2783 | |
---|
2784 | ! |
---|
2785 | ! Vegetation structure |
---|
2786 | ! |
---|
2787 | |
---|
2788 | !Config Key = LEAF_TAB |
---|
2789 | !Config Desc = leaf type : 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bare ground |
---|
2790 | !Config if = OK_STOMATE |
---|
2791 | !Config Def = 4, 1, 1, 2, 1, 1, 2, 1, 2, 3, 3, 3, 3 |
---|
2792 | !Config Help = |
---|
2793 | !Config Units = [-] |
---|
2794 | CALL getin_p('LEAF_TAB',leaf_tab) |
---|
2795 | |
---|
2796 | !Config Key = PHENO_MODEL |
---|
2797 | !Config Desc = which phenology model is used? (tabulated) |
---|
2798 | !Config if = OK_STOMATE |
---|
2799 | !Config Def = none, none, moi, none, none, ncdgdd, none, ncdgdd, ngd, moigdd, moigdd, moigdd, moigdd |
---|
2800 | !Config Help = |
---|
2801 | !Config Units = [-] |
---|
2802 | CALL getin_p('PHENO_MODEL',pheno_model) |
---|
2803 | |
---|
2804 | !! Redefine the values for is_tree, is_deciduous, is_needleleaf, is_evergreen if values have been modified |
---|
2805 | !! in run.def |
---|
2806 | |
---|
2807 | is_tree(:) = .FALSE. |
---|
2808 | DO jv = 1,nvm |
---|
2809 | IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE. |
---|
2810 | END DO |
---|
2811 | ! |
---|
2812 | is_deciduous(:) = .FALSE. |
---|
2813 | DO jv = 1,nvm |
---|
2814 | IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE. |
---|
2815 | END DO |
---|
2816 | ! |
---|
2817 | is_evergreen(:) = .FALSE. |
---|
2818 | DO jv = 1,nvm |
---|
2819 | IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE. |
---|
2820 | END DO |
---|
2821 | ! |
---|
2822 | is_needleleaf(:) = .FALSE. |
---|
2823 | DO jv = 1,nvm |
---|
2824 | IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE. |
---|
2825 | END DO |
---|
2826 | |
---|
2827 | |
---|
2828 | !Config Key = SECHIBA_LAI |
---|
2829 | !Config Desc = laimax for maximum lai(see also type of lai interpolation) |
---|
2830 | !Config if = OK_SECHIBA or IMPOSE_VEG |
---|
2831 | !Config Def = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2. |
---|
2832 | !Config Help = Maximum values of lai used for interpolation of the lai map |
---|
2833 | !Config Units = [m^2/m^2] |
---|
2834 | CALL getin_p('SECHIBA_LAI',llaimax) |
---|
2835 | |
---|
2836 | !Config Key = LLAIMIN |
---|
2837 | !Config Desc = laimin for minimum lai(see also type of lai interpolation) |
---|
2838 | !Config if = OK_SECHIBA or IMPOSE_VEG |
---|
2839 | !Config Def = 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0. |
---|
2840 | !Config Help = Minimum values of lai used for interpolation of the lai map |
---|
2841 | !Config Units = [m^2/m^2] |
---|
2842 | CALL getin_p('LLAIMIN',llaimin) |
---|
2843 | |
---|
2844 | !Config Key = SLOWPROC_HEIGHT |
---|
2845 | !Config Desc = prescribed height of vegetation |
---|
2846 | !Config if = OK_SECHIBA |
---|
2847 | !Config Def = 0., 30., 30., 20., 20., 20., 15., 15., 15., .5, .6, 1., 1. |
---|
2848 | !Config Help = |
---|
2849 | !Config Units = [m] |
---|
2850 | CALL getin_p('SLOWPROC_HEIGHT',height_presc) |
---|
2851 | |
---|
2852 | !Config Key = TYPE_OF_LAI |
---|
2853 | !Config Desc = Type of behaviour of the LAI evolution algorithm |
---|
2854 | !Config if = OK_SECHIBA |
---|
2855 | !Config Def = inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter |
---|
2856 | !Config Help = |
---|
2857 | !Config Units = [-] |
---|
2858 | CALL getin_p('TYPE_OF_LAI',type_of_lai) |
---|
2859 | |
---|
2860 | !Config Key = NATURAL |
---|
2861 | !Config Desc = natural? |
---|
2862 | !Config if = OK_SECHIBA, OK_STOMATE |
---|
2863 | !Config Def = y, y, y, y, y, y, y, y, y, y, y, n, n |
---|
2864 | !Config Help = |
---|
2865 | !Config Units = [BOOLEAN] |
---|
2866 | CALL getin_p('NATURAL',natural) |
---|
2867 | |
---|
2868 | |
---|
2869 | ! |
---|
2870 | ! Photosynthesis |
---|
2871 | ! |
---|
2872 | |
---|
2873 | !Config Key = IS_C4 |
---|
2874 | !Config Desc = flag for C4 vegetation types |
---|
2875 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
2876 | !Config Def = n, n, n, n, n, n, n, n, n, n, n, y, n, y |
---|
2877 | !Config Help = |
---|
2878 | !Config Units = [BOOLEAN] |
---|
2879 | CALL getin_p('IS_C4',is_c4) |
---|
2880 | |
---|
2881 | !Config Key = VCMAX_FIX |
---|
2882 | !Config Desc = values used for vcmax when STOMATE is not activated |
---|
2883 | !Config if = OK_SECHIBA and NOT(OK_STOMATE) |
---|
2884 | !Config Def = 0., 40., 50., 30., 35., 40.,30., 40., 35., 60., 60., 70., 70. |
---|
2885 | !Config Help = |
---|
2886 | !Config Units = [micromol/m^2/s] |
---|
2887 | CALL getin_p('VCMAX_FIX',vcmax_fix) |
---|
2888 | |
---|
2889 | !Config Key = E_KmC |
---|
2890 | !Config Desc = Energy of activation for KmC |
---|
2891 | !Config if = OK_CO2 |
---|
2892 | !Config Def = undef, 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430. |
---|
2893 | !Config Help = See Medlyn et al. (2002) |
---|
2894 | !Config Units = [J mol-1] |
---|
2895 | CALL getin_p('E_KMC',E_KmC) |
---|
2896 | |
---|
2897 | !Config Key = E_KmO |
---|
2898 | !Config Desc = Energy of activation for KmO |
---|
2899 | !Config if = OK_CO2 |
---|
2900 | !Config Def = undef, 36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380. |
---|
2901 | !Config Help = See Medlyn et al. (2002) |
---|
2902 | !Config Units = [J mol-1] |
---|
2903 | CALL getin_p('E_KMO',E_KmO) |
---|
2904 | |
---|
2905 | !Config Key = E_gamma_star |
---|
2906 | !Config Desc = Energy of activation for gamma_star |
---|
2907 | !Config if = OK_CO2 |
---|
2908 | !Config Def = undef, 37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830. |
---|
2909 | !Config Help = See Medlyn et al. (2002) from Bernacchi al. (2001) |
---|
2910 | !Config Units = [J mol-1] |
---|
2911 | CALL getin_p('E_GAMMA_STAR',E_gamma_star) |
---|
2912 | |
---|
2913 | !Config Key = E_Vcmax |
---|
2914 | !Config Desc = Energy of activation for Vcmax |
---|
2915 | !Config if = OK_CO2 |
---|
2916 | !Config Def = undef, 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 67300., 71513., 67300. |
---|
2917 | !Config Help = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3) |
---|
2918 | !Config Units = [J mol-1] |
---|
2919 | CALL getin_p('E_VCMAX',E_Vcmax) |
---|
2920 | |
---|
2921 | !Config Key = E_Jmax |
---|
2922 | !Config Desc = Energy of activation for Jmax |
---|
2923 | !Config if = OK_CO2 |
---|
2924 | !Config Def = undef, 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 77900., 49884., 77900. |
---|
2925 | !Config Help = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3) |
---|
2926 | !Config Units = [J mol-1] |
---|
2927 | CALL getin_p('E_JMAX',E_Jmax) |
---|
2928 | |
---|
2929 | !Config Key = aSV |
---|
2930 | !Config Desc = a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax |
---|
2931 | !Config if = OK_CO2 |
---|
2932 | !Config Def = undef, 668.39, 668.39, 668.39, 668.39, 668.39, 668.39, 668.39, 668.39, 668.39, 641.64, 668.39, 641.64 |
---|
2933 | !Config Help = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation and that at for a temperature of 25°C, aSV is the same for both C4 and C3 plants (no strong jusitification - need further parametrization) |
---|
2934 | !Config Units = [J K-1 mol-1] |
---|
2935 | CALL getin_p('ASV',aSV) |
---|
2936 | |
---|
2937 | !Config Key = bSV |
---|
2938 | !Config Desc = b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax |
---|
2939 | !Config if = OK_CO2 |
---|
2940 | !Config Def = undef, -1.07, -1.07, -1.07, -1.07, -1.07, -1.07, -1.07, -1.07, -1.07, 0., -1.07, 0. |
---|
2941 | !Config Help = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation |
---|
2942 | !Config Units = [J K-1 mol-1 °C-1] |
---|
2943 | CALL getin_p('BSV',bSV) |
---|
2944 | |
---|
2945 | !Config Key = TPHOTO_MIN |
---|
2946 | !Config Desc = minimum photosynthesis temperature (deg C) |
---|
2947 | !Config if = OK_STOMATE |
---|
2948 | !Config Def = undef, -4., -4., -4., -4.,-4.,-4., -4., -4., -4., -4., -4., -4. |
---|
2949 | !Config Help = |
---|
2950 | !Config Units = [-] |
---|
2951 | CALL getin_p('TPHOTO_MIN',tphoto_min) |
---|
2952 | |
---|
2953 | !Config Key = TPHOTO_MAX |
---|
2954 | !Config Desc = maximum photosynthesis temperature (deg C) |
---|
2955 | !Config if = OK_STOMATE |
---|
2956 | !Config Def = undef, 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55. |
---|
2957 | !Config Help = |
---|
2958 | !Config Units = [-] |
---|
2959 | CALL getin_p('TPHOTO_MAX',tphoto_max) |
---|
2960 | |
---|
2961 | !Config Key = aSJ |
---|
2962 | !Config Desc = a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax |
---|
2963 | !Config if = OK_CO2 |
---|
2964 | !Config Def = undef, 659.70, 659.70, 659.70, 659.70, 659.70, 659.70, 659.70, 659.70, 659.70, 630., 659.70, 630. |
---|
2965 | !Config Help = See Table 3 of Kattge & Knorr (2007) - and Table 2 of Yin et al. (2009) for C4 plants |
---|
2966 | !Config Units = [J K-1 mol-1] |
---|
2967 | CALL getin_p('ASJ',aSJ) |
---|
2968 | |
---|
2969 | !Config Key = bSJ |
---|
2970 | !Config Desc = b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax |
---|
2971 | !Config if = OK_CO2 |
---|
2972 | !Config Def = undef, -0.75, -0.75, -0.75, -0.75, -0.75, -0.75, -0.75, -0.75, -0.75, 0., -0.75, 0. |
---|
2973 | !Config Help = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation |
---|
2974 | !Config Units = [J K-1 mol-1 °C-1] |
---|
2975 | CALL getin_p('BSJ',bSJ) |
---|
2976 | |
---|
2977 | !Config Key = D_Vcmax |
---|
2978 | !Config Desc = Energy of deactivation for Vcmax |
---|
2979 | !Config if = OK_CO2 |
---|
2980 | !Config Def = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000. |
---|
2981 | !Config Help = Medlyn et al. (2002) also uses 200000. for C3 plants (same value than D_Jmax). 'Consequently', we use the value of D_Jmax for C4 plants. |
---|
2982 | !Config Units = [J mol-1] |
---|
2983 | CALL getin_p('D_VCMAX',D_Vcmax) |
---|
2984 | |
---|
2985 | !Config Key = D_Jmax |
---|
2986 | !Config Desc = Energy of deactivation for Jmax |
---|
2987 | !Config if = OK_CO2 |
---|
2988 | !Config Def = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000. |
---|
2989 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
2990 | !Config Units = [J mol-1] |
---|
2991 | CALL getin_p('D_JMAX',D_Jmax) |
---|
2992 | |
---|
2993 | !Config Key = E_Rd |
---|
2994 | !Config Desc = Energy of activation for Rd |
---|
2995 | !Config if = OK_CO2 |
---|
2996 | !Config Def = undef, 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390. |
---|
2997 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
2998 | !Config Units = [J mol-1] |
---|
2999 | CALL getin_p('E_RD',E_Rd) |
---|
3000 | |
---|
3001 | !Config Key = VCMAX25 |
---|
3002 | !Config Desc = Maximum rate of Rubisco activity-limited carboxylation at 25°C |
---|
3003 | !Config if = OK_STOMATE |
---|
3004 | !Config Def = undef, 65., 65., 35., 45., 55., 35., 45., 35., 70., 70., 70., 70. |
---|
3005 | !Config Help = |
---|
3006 | !Config Units = [micromol/m^2/s] |
---|
3007 | CALL getin_p('VCMAX25',Vcmax25) |
---|
3008 | |
---|
3009 | !Config Key = ARJV |
---|
3010 | !Config Desc = a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio |
---|
3011 | !Config if = OK_STOMATE |
---|
3012 | !Config Def = undef, 2.59, 2.59, 2.59, 2.59, 2.59, 2.59, 2.59, 2.59, 2.59, 1.715, 2.59, 1.715 |
---|
3013 | !Config Help = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation and that for a temperature of 25°C, aSV is the same for both C4 and C3 plants (no strong jusitification - need further parametrization) |
---|
3014 | !Config Units = [mu mol e- (mu mol CO2)-1] |
---|
3015 | CALL getin_p('ARJV',arJV) |
---|
3016 | |
---|
3017 | !Config Key = BRJV |
---|
3018 | !Config Desc = b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio |
---|
3019 | !Config if = OK_STOMATE |
---|
3020 | !Config Def = undef, -0.035, -0.035, -0.035, -0.035, -0.035, -0.035, -0.035, -0.035, -0.035, 0., -0.035, 0. |
---|
3021 | !Config Help = See Table 3 of Kattge & Knorr (2007) - We assume No acclimation term for C4 plants |
---|
3022 | !Config Units = [(mu mol e- (mu mol CO2)-1) (°C)-1] |
---|
3023 | CALL getin_p('BRJV',brJV) |
---|
3024 | |
---|
3025 | !Config Key = KmC25 |
---|
3026 | !Config Desc = MichaelisâMenten constant of Rubisco for CO2 at 25°C |
---|
3027 | !Config if = OK_CO2 |
---|
3028 | !Config Def = undef, 404.9, 404.9, 404.9, 404.9, 404.9, 404.9, 404.9, 404.9, 404.9, 650., 404.9, 650. |
---|
3029 | !Config Help = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants |
---|
3030 | !Config Units = [ubar] |
---|
3031 | CALL getin_p('KMC25',KmC25) |
---|
3032 | |
---|
3033 | !Config Key = KmO25 |
---|
3034 | !Config Desc = MichaelisâMenten constant of Rubisco for O2 at 25°C |
---|
3035 | !Config if = OK_CO2 |
---|
3036 | !Config Def = undef, 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 450000., 278400., 450000. |
---|
3037 | !Config Help = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants |
---|
3038 | !Config Units = [ubar] |
---|
3039 | CALL getin_p('KMO25',KmO25) |
---|
3040 | |
---|
3041 | !Config Key = gamma_star25 |
---|
3042 | !Config Desc = Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar) |
---|
3043 | !Config if = OK_CO2 |
---|
3044 | !Config Def = undef, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75, 42.75 |
---|
3045 | !Config Help = See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the same value (probably uncorrect) |
---|
3046 | !Config Units = [ubar] |
---|
3047 | CALL getin_p('gamma_star25',gamma_star25) |
---|
3048 | |
---|
3049 | !Config Key = a1 |
---|
3050 | !Config Desc = Empirical factor involved in the calculation of fvpd |
---|
3051 | !Config if = OK_CO2 |
---|
3052 | !Config Def = undef, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85 |
---|
3053 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
3054 | !Config Units = [-] |
---|
3055 | CALL getin_p('A1',a1) |
---|
3056 | |
---|
3057 | !Config Key = b1 |
---|
3058 | !Config Desc = Empirical factor involved in the calculation of fvpd |
---|
3059 | !Config if = OK_CO2 |
---|
3060 | !Config Def = undef, 0.14, 0.14, 0.14, 0.14, 0.14, 0.14, 0.14, 0.14, 0.14, 0.20, 0.14, 0.20 |
---|
3061 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
3062 | !Config Units = [-] |
---|
3063 | CALL getin_p('B1',b1) |
---|
3064 | |
---|
3065 | !Config Key = g0 |
---|
3066 | !Config Desc = Residual stomatal conductance when irradiance approaches zero |
---|
3067 | !Config if = OK_CO2 |
---|
3068 | !Config Def = undef, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.01875, 0.00625, 0.01875 |
---|
3069 | !Config Help = Value from ORCHIDEE - No other reference. |
---|
3070 | !Config Units = [mol mâ2 sâ1 barâ1] |
---|
3071 | CALL getin_p('G0',g0) |
---|
3072 | |
---|
3073 | !Config Key = h_protons |
---|
3074 | !Config Desc = Number of protons required to produce one ATP |
---|
3075 | !Config if = OK_CO2 |
---|
3076 | !Config Def = undef, 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4. |
---|
3077 | !Config Help = See Table 2 of Yin et al. (2009) - h parameter |
---|
3078 | !Config Units = [mol mol-1] |
---|
3079 | CALL getin_p('H_PROTONS',h_protons) |
---|
3080 | |
---|
3081 | !Config Key = fpsir |
---|
3082 | !Config Desc = Fraction of PSII eâ transport rate partitioned to the C4 cycle |
---|
3083 | !Config if = OK_CO2 |
---|
3084 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.4, undef, 0.4 |
---|
3085 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
3086 | !Config Units = [-] |
---|
3087 | CALL getin_p('FPSIR',fpsir) |
---|
3088 | |
---|
3089 | !Config Key = fQ |
---|
3090 | !Config Desc = Fraction of electrons at reduced plastoquinone that follow the Q-cycle |
---|
3091 | !Config if = OK_CO2 |
---|
3092 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 1., undef, 1. |
---|
3093 | !Config Help = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used |
---|
3094 | !Config Units = [-] |
---|
3095 | CALL getin_p('FQ',fQ) |
---|
3096 | |
---|
3097 | !Config Key = fpseudo |
---|
3098 | !Config Desc = Fraction of electrons at PSI that follow pseudocyclic transport |
---|
3099 | !Config if = OK_CO2 |
---|
3100 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1 |
---|
3101 | !Config Help = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used |
---|
3102 | !Config Units = [-] |
---|
3103 | CALL getin_p('FPSEUDO',fpseudo) |
---|
3104 | |
---|
3105 | !Config Key = kp |
---|
3106 | !Config Desc = Initial carboxylation efficiency of the PEP carboxylase |
---|
3107 | !Config if = OK_CO2 |
---|
3108 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.7, undef, 0.7 |
---|
3109 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
3110 | !Config Units = [mol mâ2 sâ1 barâ1] |
---|
3111 | CALL getin_p('KP',kp) |
---|
3112 | |
---|
3113 | !Config Key = alpha |
---|
3114 | !Config Desc = Fraction of PSII activity in the bundle sheath |
---|
3115 | !Config if = OK_CO2 |
---|
3116 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1 |
---|
3117 | !Config Help = See legend of Figure 6 of Yin et al. (2009) |
---|
3118 | !Config Units = [-] |
---|
3119 | CALL getin_p('ALPHA',alpha) |
---|
3120 | |
---|
3121 | !Config Key = gbs |
---|
3122 | !Config Desc = Bundle-sheath conductance |
---|
3123 | !Config if = OK_CO2 |
---|
3124 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.003, undef, 0.003 |
---|
3125 | !Config Help = See legend of Figure 6 of Yin et al. (2009) |
---|
3126 | !Config Units = [mol mâ2 sâ1 barâ1] |
---|
3127 | CALL getin_p('GBS',gbs) |
---|
3128 | |
---|
3129 | !Config Key = theta |
---|
3130 | !Config Desc = Convexity factor for response of J to irradiance |
---|
3131 | !Config if = OK_CO2 |
---|
3132 | !Config Def = undef, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7 |
---|
3133 | !Config Help = See Table 2 of Yin et al. (2009) |
---|
3134 | !Config Units = [â] |
---|
3135 | CALL getin_p('THETA',theta) |
---|
3136 | |
---|
3137 | !Config Key = alpha_LL |
---|
3138 | !Config Desc = Conversion efficiency of absorbed light into J at strictly limiting light |
---|
3139 | !Config if = OK_CO2 |
---|
3140 | !Config Def = undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3 |
---|
3141 | !Config Help = See comment from Yin et al. (2009) after eq. 4 |
---|
3142 | !Config Units = [mol eâ (mol photon)â1] |
---|
3143 | CALL getin_p('ALPHA_LL',alpha_LL) |
---|
3144 | |
---|
3145 | !Config Key = DOWNREGULATION_CO2_COEFF |
---|
3146 | !Config Desc = coefficient for CO2 downregulation (unitless) |
---|
3147 | !Config if = OK_CO2 |
---|
3148 | !Config Def = 0., 0.38, 0.38, 0.28, 0.28, 0.28, 0.22, 0.22, 0.22, 0.26, 0.26, 0.26, 0.26 |
---|
3149 | !Config Help = |
---|
3150 | !Config Units = [-] |
---|
3151 | CALL getin_p('DOWNREGULATION_CO2_COEFF',downregulation_co2_coeff) |
---|
3152 | |
---|
3153 | !Config Key = EXT_COEFF |
---|
3154 | !Config Desc = extinction coefficient of the Monsi&Seaki relationship (1953) |
---|
3155 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
3156 | !Config Def = .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5 |
---|
3157 | !Config Help = |
---|
3158 | !Config Units = [-] |
---|
3159 | CALL getin_p('EXT_COEFF',ext_coeff) |
---|
3160 | |
---|
3161 | ! |
---|
3162 | ! Water-hydrology - sechiba |
---|
3163 | ! |
---|
3164 | |
---|
3165 | !Config Key = HYDROL_HUMCSTE |
---|
3166 | !Config Desc = Root profile |
---|
3167 | !Config Def = 5., .4, .4, 1., .8, .8, 1., 1., .8, 4., 1., 4., 1. |
---|
3168 | !Config if = OK_SECHIBA |
---|
3169 | !Config Help = Default values were defined for 4 meters soil depth. |
---|
3170 | !Config For 2 meters soil depth, you may use those ones : |
---|
3171 | !Config 5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4. |
---|
3172 | !Config Units = [m] |
---|
3173 | CALL getin_p('HYDROL_HUMCSTE',humcste) |
---|
3174 | |
---|
3175 | ! |
---|
3176 | ! Soil - vegetation |
---|
3177 | ! |
---|
3178 | |
---|
3179 | !Config Key = PREF_SOIL_VEG |
---|
3180 | !Config Desc = The soil tile number for each vegetation |
---|
3181 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
3182 | !Config Def = 1, 2, 2, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3 |
---|
3183 | !Config Help = Gives the number of the soil tile on which we will |
---|
3184 | !Config put each vegetation. This allows to divide the hydrological column |
---|
3185 | !Config Units = [-] |
---|
3186 | CALL getin_p('PREF_SOIL_VEG',pref_soil_veg) |
---|
3187 | |
---|
3188 | ! |
---|
3189 | ! Vegetation - Age classes |
---|
3190 | ! |
---|
3191 | !Config Key = NVMAP |
---|
3192 | !Config Desc = The number of PFTs if we ignore age classes. If nagec = 1, this is just nvm. |
---|
3193 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
3194 | !Config Def = nvm |
---|
3195 | !Config Help = Gives the total number of PFTs ignoring age classes. |
---|
3196 | !Config Units = [-] |
---|
3197 | nvmap=nvm |
---|
3198 | CALL getin_p('NVMAP',nvmap) |
---|
3199 | IF(nagec > 1 .AND. nvmap == nvm)THEN |
---|
3200 | WRITE(numout,*) 'WARNING: The number of age classes is greater than one, but' |
---|
3201 | WRITE(numout,*) ' the input file indicates that none of the PFTs have age classes.' |
---|
3202 | WRITE(numout,*) ' You should change either nagec or nvmap.' |
---|
3203 | ENDIF |
---|
3204 | |
---|
3205 | !Config Key = AGEC_GROUP |
---|
3206 | !Config Desc = The group that each PFT belongs to. |
---|
3207 | !Config if = OK_SECHIBA or OK_STOMATE |
---|
3208 | !Config Def = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 |
---|
3209 | !Config Help = The group that each PFT belongs to. If you are not using age classes, this |
---|
3210 | !Config is just equal to the number of the PFT. |
---|
3211 | !Config Units = [-] |
---|
3212 | DO ivm=1,nvm |
---|
3213 | agec_group(ivm)=ivm |
---|
3214 | ENDDO |
---|
3215 | CALL getin_p('AGEC_GROUP',agec_group) |
---|
3216 | |
---|
3217 | first_call = .FALSE. |
---|
3218 | |
---|
3219 | ENDIF !(first_call) |
---|
3220 | |
---|
3221 | END SUBROUTINE config_pft_parameters |
---|
3222 | ! |
---|
3223 | != |
---|
3224 | ! |
---|
3225 | |
---|
3226 | !! ================================================================================================================================ |
---|
3227 | !! SUBROUTINE : config_sechiba_pft_parameters |
---|
3228 | !! |
---|
3229 | !>\BRIEF This subroutine will read the imposed values for the sechiba pft |
---|
3230 | !! parameters. It is not called if IMPOSE_PARAM is set to NO. |
---|
3231 | !! |
---|
3232 | !! DESCRIPTION : None |
---|
3233 | !! |
---|
3234 | !! RECENT CHANGE(S): None |
---|
3235 | !! |
---|
3236 | !! MAIN OUTPUT VARIABLE(S): None |
---|
3237 | !! |
---|
3238 | !! REFERENCE(S) : None |
---|
3239 | !! |
---|
3240 | !! FLOWCHART : None |
---|
3241 | !! \n |
---|
3242 | !_ ================================================================================================================================ |
---|
3243 | |
---|
3244 | SUBROUTINE config_sechiba_pft_parameters(active_flags) |
---|
3245 | |
---|
3246 | IMPLICIT NONE |
---|
3247 | |
---|
3248 | !! 0. Variables and parameters declaration |
---|
3249 | |
---|
3250 | !! 0.1 Input variables |
---|
3251 | |
---|
3252 | TYPE(control_type), INTENT(in) :: active_flags !! What parts of the code are activated ? |
---|
3253 | |
---|
3254 | !! 0.4 Local variable |
---|
3255 | |
---|
3256 | LOGICAL, SAVE :: first_call = .TRUE. !! To keep first call trace (true/false) |
---|
3257 | !$OMP THREADPRIVATE(first_call) |
---|
3258 | |
---|
3259 | !_ ================================================================================================================================ |
---|
3260 | |
---|
3261 | IF (first_call) THEN |
---|
3262 | |
---|
3263 | ! |
---|
3264 | ! Evapotranspiration - sechiba |
---|
3265 | ! |
---|
3266 | |
---|
3267 | !Config Key = RSTRUCT_CONST |
---|
3268 | !Config Desc = Structural resistance |
---|
3269 | !Config if = OK_SECHIBA |
---|
3270 | !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 |
---|
3271 | !Config Help = |
---|
3272 | !Config Units = [s/m] |
---|
3273 | CALL getin_p('RSTRUCT_CONST',rstruct_const) |
---|
3274 | |
---|
3275 | !Config Key = KZERO |
---|
3276 | !Config Desc = A vegetation dependent constant used in the calculation of the surface resistance. |
---|
3277 | !Config if = OK_SECHIBA |
---|
3278 | !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 |
---|
3279 | !Config Help = |
---|
3280 | !Config Units = [kg/m^2/s] |
---|
3281 | CALL getin_p('KZERO',kzero) |
---|
3282 | |
---|
3283 | !Config Key = RVEG_PFT |
---|
3284 | !Config Desc = Artificial parameter to increase or decrease canopy resistance. |
---|
3285 | !Config if = OK_SECHIBA |
---|
3286 | !Config Def = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1. |
---|
3287 | !Config Help = This parameter is set by PFT. |
---|
3288 | !Config Units = [-] |
---|
3289 | CALL getin_p('RVEG_PFT',rveg_pft) |
---|
3290 | |
---|
3291 | ! |
---|
3292 | ! Water-hydrology - sechiba |
---|
3293 | ! |
---|
3294 | |
---|
3295 | !Config Key = WMAX_VEG |
---|
3296 | !Config Desc = Maximum field capacity for each of the vegetations (Temporary): max quantity of water |
---|
3297 | !Config if = OK_SECHIBA |
---|
3298 | !Config Def = 150., 150., 150., 150., 150., 150., 150.,150., 150., 150., 150., 150., 150. |
---|
3299 | !Config Help = |
---|
3300 | !Config Units = [kg/m^3] |
---|
3301 | CALL getin_p('WMAX_VEG',wmax_veg) |
---|
3302 | ! |
---|
3303 | IF ( .NOT.(active_flags%hydrol_cwrr) .OR. (active_flags%hydrol_cwrr .AND. ok_throughfall_by_pft) ) THEN |
---|
3304 | !Config Key = PERCENT_THROUGHFALL_PFT |
---|
3305 | !Config Desc = Percent by PFT of precip that is not intercepted by the canopy |
---|
3306 | !Config if = OK_SECHIBA OR HYDROL_CWRR |
---|
3307 | !Config Def = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. |
---|
3308 | !Config Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall |
---|
3309 | !Config will get directly to the ground without being intercepted, for each PFT. |
---|
3310 | !Config Units = [%] |
---|
3311 | CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft) |
---|
3312 | throughfall_by_pft(:) = throughfall_by_pft(:) / 100. |
---|
3313 | END IF |
---|
3314 | |
---|
3315 | ! |
---|
3316 | ! Albedo - sechiba |
---|
3317 | ! |
---|
3318 | |
---|
3319 | !Config Key = SNOWA_AGED |
---|
3320 | !Config Desc = Minimum snow albedo value for each vegetation type after aging (dirty old snow) |
---|
3321 | !Config if = OK_SECHIBA |
---|
3322 | !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 |
---|
3323 | !Config Help = Values are from the Thesis of S. Chalita (1992) |
---|
3324 | !Config Units = [-] |
---|
3325 | CALL getin_p('SNOWA_AGED',snowa_aged) |
---|
3326 | |
---|
3327 | !Config Key = SNOWA_DEC |
---|
3328 | !Config Desc = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow |
---|
3329 | !Config if = OK_SECHIBA |
---|
3330 | !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 |
---|
3331 | !Config Help = Values are from the Thesis of S. Chalita (1992) |
---|
3332 | !Config Units = [-] |
---|
3333 | CALL getin_p('SNOWA_DEC',snowa_dec) |
---|
3334 | |
---|
3335 | !Config Key = ALB_LEAF_VIS |
---|
3336 | !Config Desc = leaf albedo of vegetation type, visible albedo |
---|
3337 | !Config if = OK_SECHIBA |
---|
3338 | !Config Def = .00, .04, .06, .06, .06,.06, .06, .06, .06, .10, .10, .10, .10 |
---|
3339 | !Config Help = |
---|
3340 | !Config Units = [-] |
---|
3341 | CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis) |
---|
3342 | |
---|
3343 | !Config Key = ALB_LEAF_NIR |
---|
3344 | !Config Desc = leaf albedo of vegetation type, near infrared albedo |
---|
3345 | !Config if = OK_SECHIBA |
---|
3346 | !Config Def = .00, .20, .22, .22, .22,.22, .22, .22, .22, .30, .30, .30, .30 |
---|
3347 | !Config Help = |
---|
3348 | !Config Units = [-] |
---|
3349 | CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir) |
---|
3350 | ! |
---|
3351 | !Config Key = LEAF_SSA_VIS |
---|
3352 | !Config Desc = Leaf_single_scattering_albedo_vis values |
---|
3353 | !Config If = ALBEDO_TYPE == Pinty |
---|
3354 | !Config Def = 0.17192, 0.12560, 0.16230, 0.13838, 0.13202, 0.14720, |
---|
3355 | ! 0.14680, 0.14415, 0.15485, 0.17544, 0.17384, 0.17302, 0.17116 |
---|
3356 | !Config Help = |
---|
3357 | !Config Units = [-] |
---|
3358 | ! |
---|
3359 | CALL getin_p('LEAF_SSA_VIS',leaf_ssa(:,ivis)) |
---|
3360 | WRITE(numout,*) 'Single scattering albedo values for the leaves in the VIS spectrum: ',leaf_ssa(:,ivis) |
---|
3361 | ! |
---|
3362 | !Config Key = LEAF_SSA_NIR |
---|
3363 | !Config Desc = Leaf_single_scattering_albedo_nir values |
---|
3364 | !Config If = ALBEDO_TYPE == Pinty |
---|
3365 | !Config Def = 0.70253, 0.68189, 0.69684, 0.68778, 0.68356, 0.69533, & |
---|
3366 | ! 0.69520, 0.69195, 0.69180, 0.71236, 0.71904, 0.71220, 0.71190 |
---|
3367 | !Config Help = |
---|
3368 | !Config Units = [-] |
---|
3369 | ! |
---|
3370 | CALL getin_p('LEAF_SSA_NIR',leaf_ssa(:,inir)) |
---|
3371 | WRITE(numout,*) 'Single scattering albedo values for the leaves in the NIR spectrum: ',leaf_ssa(:,inir) |
---|
3372 | ! |
---|
3373 | !Config Key = LEAF_PSD_VIS |
---|
3374 | !Config Desc = Preferred scattering direction values in the visibile spectra |
---|
3375 | !Config If = ALBEDO_TYPE == Pinty |
---|
3376 | !Config Def = 1.00170, 0.96776, 0.99250, 0.97170, 0.97119, 0.98077, & |
---|
3377 | ! 0.97672, 0.97810, 0.98605, 1.00490, 1.00360, 1.00320, 1.00130 |
---|
3378 | !Config Help = |
---|
3379 | !Config Units = [-] |
---|
3380 | ! |
---|
3381 | CALL getin_p('LEAF_PSD_VIS',leaf_psd(:,ivis)) |
---|
3382 | WRITE(numout,*) 'Preferred scattering direction values for the leaves in the VIS spectrum: ',leaf_psd(:,ivis) |
---|
3383 | ! |
---|
3384 | !Config Key = LEAF_PSD_NIR |
---|
3385 | !Config Desc = Preferred scattering direction values in the near infrared spectra |
---|
3386 | !Config If = ALBEDO_TYPE == Pinty |
---|
3387 | !Config Def = 2.00520, 1.95120, 1.98990, 1.97020, 1.95900, 1.98190, & |
---|
3388 | ! 1.98890, 1.97400, 1.97780, 2.02430, 2.03350, 2.02070, 2.02150 |
---|
3389 | !Config Help = |
---|
3390 | !Config Units = [-] |
---|
3391 | ! |
---|
3392 | CALL getin_p('LEAF_PSD_NIR',leaf_psd(:,inir)) |
---|
3393 | WRITE(numout,*) 'Preferred scattering direction values for the leaves in the NIR spectrum: ',leaf_psd(:,inir) |
---|
3394 | ! |
---|
3395 | ! |
---|
3396 | !Config Key = BGRD_REF_VIS |
---|
3397 | !Config Desc = Background reflectance values in the visibile spectra |
---|
3398 | !Config If = ALBEDO_TYPE == Pinty |
---|
3399 | !Config Def = 0.2300000, 0.0866667, 0.0800000, 0.0533333, 0.0700000, 0.0933333, 0.0533333, |
---|
3400 | ! 0.0833333, 0.0633333, 0.1033330, 0.1566670, 0.1166670, 0.1200000 |
---|
3401 | !Config Help = |
---|
3402 | !Config Units = [-] |
---|
3403 | ! |
---|
3404 | CALL getin_p('BGRD_REF_VIS',bgd_reflectance(:,ivis)) |
---|
3405 | WRITE(numout,*) 'Background (soil) reflectance values in the VIS spectrum: ',bgd_reflectance(:,ivis) |
---|
3406 | ! |
---|
3407 | !Config Key = BGRD_REF_NIR |
---|
3408 | !Config Desc = Background reflectance values in the near infrared spectra |
---|
3409 | !Config If = ALBEDO_TYPE == Pinty |
---|
3410 | !Config Def = 0.4200000, 0.1500000, 0.1300000, 0.0916667, 0.1066670, 0.1650000, 0.0900000, |
---|
3411 | ! 0.1483330, 0.1066670, 0.1900000, 0.3183330, 0.2200000, 0.2183330 |
---|
3412 | !Config Help = |
---|
3413 | !Config Units = [-] |
---|
3414 | ! |
---|
3415 | CALL getin_p('BGRD_REF_NIR',bgd_reflectance(:,inir)) |
---|
3416 | WRITE(numout,*) 'Background (soil) reflectance values in the NIR spectrum: ',bgd_reflectance(:,inir) |
---|
3417 | |
---|
3418 | ! |
---|
3419 | !Config Key = LEAF_TO_SHOOT_CLUMPING |
---|
3420 | !Config Desc = The leaf-to-shoot clumping factor |
---|
3421 | !Config If = ALBEDO_TYPE == Pinty |
---|
3422 | !Config Def = un, un, un, un, un, un, un, |
---|
3423 | ! un, un, un, un, un, un |
---|
3424 | !Config Help = |
---|
3425 | !Config Units = [-] |
---|
3426 | ! |
---|
3427 | CALL getin_p('LEAF_TO_SHOOT_CLUMPING',leaf_to_shoot_clumping(:)) |
---|
3428 | WRITE(numout,*) 'Leaf-to-shoot clumping factors: ',leaf_to_shoot_clumping(:) |
---|
3429 | ! |
---|
3430 | !Config Key = LAI_CORRECTION_FACTOR |
---|
3431 | !Config Desc = The correction factor for the LAI for grasslands and crops (see note in pft_parameters) |
---|
3432 | !Config If = ALBEDO_TYPE == Pinty |
---|
3433 | !Config Def = un, un, un, un, un, un, un, |
---|
3434 | ! un, un, un, un, un, un |
---|
3435 | !Config Help = |
---|
3436 | !Config Units = [-] |
---|
3437 | |
---|
3438 | CALL getin_p('TUNE_COUPLED',tune_coupled(:)) |
---|
3439 | WRITE(numout,*) 'Tunning the propotion of LAI contributed to transpiration: ', tune_coupled(:) |
---|
3440 | ! |
---|
3441 | !Config Key = TUNE_COUPLED |
---|
3442 | !Config Desc = The correction factor for the LAI which is coupled with atmosphere |
---|
3443 | !Config If = |
---|
3444 | !Config Def = un, un, un, un, un, un, un, |
---|
3445 | ! un, un, un, un, un, un |
---|
3446 | !Config Help = |
---|
3447 | !Config Units = [-] |
---|
3448 | |
---|
3449 | ! |
---|
3450 | CALL getin_p('LAI_CORRECTION_FACTOR',lai_correction_factor(:)) |
---|
3451 | WRITE(numout,*) 'LAI correction factors: ',lai_correction_factor(:) |
---|
3452 | |
---|
3453 | !Config Key = MIN_LEVEL_SEP |
---|
3454 | !Config Desc = The minimum level thickness we use for photosynthesis |
---|
3455 | !Config If = ALBEDO_TYPE == Pinty |
---|
3456 | !Config Def = un, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, |
---|
3457 | ! 0.1, 0.1, 0.1, 0.1, 0.1, 0.1 |
---|
3458 | !Config Help = |
---|
3459 | !Config Units = [m] |
---|
3460 | ! |
---|
3461 | CALL getin_p('MIN_LEVEL_SEP',min_level_sep(:)) |
---|
3462 | WRITE(numout,*) 'Minimum level separation: ',min_level_sep(:) |
---|
3463 | |
---|
3464 | !Config Key = LAI_TOP |
---|
3465 | !Config Desc = Definition, in terms of LAI of the top layer |
---|
3466 | ! (used to calculate one of the resistences of |
---|
3467 | ! vbeta3) to calculate transpiration |
---|
3468 | !Config If = |
---|
3469 | !Config Def = un, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, |
---|
3470 | ! 0.1, 0.1, 0.1, 0.1, 0.1, 0.1 |
---|
3471 | !Config Help = |
---|
3472 | !Config Units = [m2 m2] |
---|
3473 | ! |
---|
3474 | CALL getin_p('LAI_TOP',lai_top(:)) |
---|
3475 | WRITE(numout,*) 'Defining the "top layer" for transpiration in terms of LAI: ',lai_top(:) |
---|
3476 | |
---|
3477 | |
---|
3478 | !Config Key = TUNE_COUPLED |
---|
3479 | !Config Desc = Definition, in terms of LAI of the top layer which is contributed to the transpiration |
---|
3480 | ! (used to calculate one of the resistences of vbeta3) to calculate transpiration |
---|
3481 | !Config If = |
---|
3482 | !Config Def = un, un, un, un, un, un, un, |
---|
3483 | ! un, un, un, un, un, un |
---|
3484 | !Config Help = |
---|
3485 | !Config Units = [-] |
---|
3486 | ! |
---|
3487 | CALL getin_p('TUNE_COUPLED',tune_coupled(:)) |
---|
3488 | WRITE(numout,*) 'tunning the "the porpotion of the coupled layer" for transpiration : ',tune_coupled(:) |
---|
3489 | |
---|
3490 | |
---|
3491 | IF ( active_flags%ok_inca ) THEN |
---|
3492 | ! |
---|
3493 | ! BVOC |
---|
3494 | ! |
---|
3495 | |
---|
3496 | !Config Key = ISO_ACTIVITY |
---|
3497 | !Config Desc = Biogenic activity for each age class : isoprene |
---|
3498 | !Config if = DIFFUCO_OK_INCA |
---|
3499 | !Config Def = 0.5, 1.5, 1.5, 0.5 |
---|
3500 | !Config Help = |
---|
3501 | !Config Units = [-] |
---|
3502 | CALL getin_p('ISO_ACTIVITY',iso_activity) |
---|
3503 | |
---|
3504 | !Config Key = METHANOL_ACTIVITY |
---|
3505 | !Config Desc = Isoprene emission factor for each age class : methanol |
---|
3506 | !Config if = DIFFUCO_OK_INCA |
---|
3507 | !Config Def = 1., 1., 0.5, 0.5 |
---|
3508 | !Config Help = |
---|
3509 | !Config Units = [-] |
---|
3510 | CALL getin_p('METHANOL_ACTIVITY',methanol_activity) |
---|
3511 | |
---|
3512 | !Config Key = EM_FACTOR_ISOPRENE |
---|
3513 | !Config Desc = Isoprene emission factor |
---|
3514 | !Config if = DIFFUCO_OK_INCA |
---|
3515 | !Config Def = 0., 24., 24., 8., 16., 45., 8., 8., 8., 16., 24., 5., 5. |
---|
3516 | !Config Help = |
---|
3517 | !Config Units = [ugC/g/h] |
---|
3518 | CALL getin_p('EM_FACTOR_ISOPRENE',em_factor_isoprene) |
---|
3519 | |
---|
3520 | !Config Key = EM_FACTOR_MONOTERPENE |
---|
3521 | !Config Desc = Monoterpene emission factor |
---|
3522 | !Config if = DIFFUCO_OK_INCA |
---|
3523 | !Config Def = 0., 0.8, 0.8, 2.4, 1.2, 0.8, 2.4, 2.4, 2.4, 0.8, 1.2, 0.2, 0.2 |
---|
3524 | !Config Help = |
---|
3525 | !Config Units = [ugC/g/h] |
---|
3526 | CALL getin_p('EM_FACTOR_MONOTERPENE',em_factor_monoterpene) |
---|
3527 | |
---|
3528 | !Config Key = EM_FACTOR_ORVOC |
---|
3529 | !Config Desc = ORVOC emissions factor |
---|
3530 | !Config if = DIFFUCO_OK_INCA |
---|
3531 | !Config Def = 0., 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5 |
---|
3532 | !Config Help = |
---|
3533 | !Config Units = [ugC/g/h] |
---|
3534 | CALL getin_p('EM_FACTOR_ORVOC',em_factor_ORVOC) |
---|
3535 | |
---|
3536 | !Config Key = EM_FACTOR_OVOC |
---|
3537 | !Config Desc = OVOC emissions factor |
---|
3538 | !Config if = DIFFUCO_OK_INCA |
---|
3539 | !Config Def = 0., 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5 |
---|
3540 | !Config Help = |
---|
3541 | !Config Units = [ugC/g/h] |
---|
3542 | CALL getin_p('EM_FACTOR_OVOC',em_factor_OVOC) |
---|
3543 | |
---|
3544 | !Config Key = EM_FACTOR_MBO |
---|
3545 | !Config Desc = MBO emissions factor |
---|
3546 | !Config if = DIFFUCO_OK_INCA |
---|
3547 | !Config Def = 0., 0., 0., 20.0, 0., 0., 0., 0., 0., 0., 0., 0., 0. |
---|
3548 | !Config Help = |
---|
3549 | !Config Units = [ugC/g/h] |
---|
3550 | CALL getin_p('EM_FACTOR_MBO',em_factor_MBO) |
---|
3551 | |
---|
3552 | !Config Key = EM_FACTOR_METHANOL |
---|
3553 | !Config Desc = Methanol emissions factor |
---|
3554 | !Config if = DIFFUCO_OK_INCA |
---|
3555 | !Config Def = 0., 0.6, 0.6, 1.8, 0.9, 0.6, 1.8, 1.8, 1.8, 0.6, 0.9, 2., 2. |
---|
3556 | !Config Help = |
---|
3557 | !Config Units = [ugC/g/h] |
---|
3558 | CALL getin_p('EM_FACTOR_METHANOL',em_factor_methanol) |
---|
3559 | |
---|
3560 | !Config Key = EM_FACTOR_ACETONE |
---|
3561 | !Config Desc = Acetone emissions factor |
---|
3562 | !Config if = DIFFUCO_OK_INCA |
---|
3563 | !Config Def = 0., 0.29, 0.29, 0.87, 0.43, 0.29, 0.87, 0.87, 0.87, 0.29, 0.43, 0.07, 0.07 |
---|
3564 | !Config Help = |
---|
3565 | !Config Units = [ugC/g/h] |
---|
3566 | CALL getin_p('EM_FACTOR_ACETONE',em_factor_acetone) |
---|
3567 | |
---|
3568 | !Config Key = EM_FACTOR_ACETAL |
---|
3569 | !Config Desc = Acetaldehyde emissions factor |
---|
3570 | !Config if = DIFFUCO_OK_INCA |
---|
3571 | !Config Def = 0., 0.1, 0.1, 0.3, 0.15, 0.1, 0.3, 0.3, 0.3, 0.1, 0.15, 0.025, 0.025 |
---|
3572 | !Config Help = |
---|
3573 | !Config Units = [ugC/g/h] |
---|
3574 | CALL getin_p('EM_FACTOR_ACETAL',em_factor_acetal) |
---|
3575 | |
---|
3576 | !Config Key = EM_FACTOR_FORMAL |
---|
3577 | !Config Desc = Formaldehyde emissions factor |
---|
3578 | !Config if = DIFFUCO_OK_INCA |
---|
3579 | !Config Def = 0., 0.07, 0.07, 0.2, 0.1, 0.07, 0.2, 0.2, 0.2, 0.07, 0.1, 0.017, 0.017 |
---|
3580 | !Config Help = |
---|
3581 | !Config Units = [ugC/g/h] |
---|
3582 | CALL getin_p('EM_FACTOR_FORMAL',em_factor_formal) |
---|
3583 | |
---|
3584 | !Config Key = EM_FACTOR_ACETIC |
---|
3585 | !Config Desc = Acetic Acid emissions factor |
---|
3586 | !Config if = DIFFUCO_OK_INCA |
---|
3587 | !Config Def = 0., 0.002, 0.002, 0.006, 0.003, 0.002, 0.006, 0.006, 0.006, 0.002, 0.003, 0.0005, 0.0005 |
---|
3588 | !Config Help = |
---|
3589 | !Config Units = [ugC/g/h] |
---|
3590 | CALL getin_p('EM_FACTOR_ACETIC',em_factor_acetic) |
---|
3591 | |
---|
3592 | !Config Key = EM_FACTOR_FORMIC |
---|
3593 | !Config Desc = Formic Acid emissions factor |
---|
3594 | !Config if = DIFFUCO_OK_INCA |
---|
3595 | !Config Def = 0., 0.01, 0.01, 0.03, 0.015, 0.01, 0.03, 0.03, 0.03, 0.01, 0.015, 0.0025, 0.0025 |
---|
3596 | !Config Help = |
---|
3597 | !Config Units = [ugC/g/h] |
---|
3598 | CALL getin_p('EM_FACTOR_FORMIC',em_factor_formic) |
---|
3599 | |
---|
3600 | !Config Key = EM_FACTOR_NO_WET |
---|
3601 | !Config Desc = NOx emissions factor wet soil emissions and exponential dependancy factor |
---|
3602 | !Config if = DIFFUCO_OK_INCA |
---|
3603 | !Config Def = 0., 2.6, 0.06, 0.03, 0.03, 0.03, 0.03, 0.03, 0.03, 0.36, 0.36, 0.36, 0.36 |
---|
3604 | !Config Help = |
---|
3605 | !Config Units = [ngN/m^2/s] |
---|
3606 | CALL getin_p('EM_FACTOR_NO_WET',em_factor_no_wet) |
---|
3607 | |
---|
3608 | !Config Key = EM_FACTOR_NO_DRY |
---|
3609 | !Config Desc = NOx emissions factor dry soil emissions and exponential dependancy factor |
---|
3610 | !Config if = DIFFUCO_OK_INCA |
---|
3611 | !Config Def = 0., 8.60, 0.40, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 2.65, 2.65, 2.65, 2.65 |
---|
3612 | !Config Help = |
---|
3613 | !Config Units = [ngN/m^2/s] |
---|
3614 | CALL getin_p('EM_FACTOR_NO_DRY',em_factor_no_dry) |
---|
3615 | |
---|
3616 | !Config Key = LARCH |
---|
3617 | !Config Desc = Larcher 1991 SAI/LAI ratio |
---|
3618 | !Config if = DIFFUCO_OK_INCA |
---|
3619 | !Config Def = 0., 0.015, 0.015, 0.003, 0.005, 0.005, 0.003, 0.005, 0.003, 0.005, 0.005, 0.008, 0.008 |
---|
3620 | !Config Help = |
---|
3621 | !Config Units = [-] |
---|
3622 | CALL getin_p('LARCH',Larch) |
---|
3623 | |
---|
3624 | ENDIF ! (active_flags%ok_inca) |
---|
3625 | |
---|
3626 | first_call = .FALSE. |
---|
3627 | |
---|
3628 | ENDIF !(first_call) |
---|
3629 | |
---|
3630 | END SUBROUTINE config_sechiba_pft_parameters |
---|
3631 | ! |
---|
3632 | != |
---|
3633 | ! |
---|
3634 | |
---|
3635 | !! ================================================================================================================================ |
---|
3636 | !! SUBROUTINE : config_stomate_pft_parameters |
---|
3637 | !! |
---|
3638 | !>\BRIEF This subroutine will read the imposed values for the stomate pft |
---|
3639 | !! parameters. It is not called if IMPOSE_PARAM is set to NO. |
---|
3640 | !! |
---|
3641 | !! DESCRIPTION : None |
---|
3642 | !! |
---|
3643 | !! RECENT CHANGE(S): None |
---|
3644 | !! |
---|
3645 | !! MAIN OUTPUT VARIABLE(S): None |
---|
3646 | !! |
---|
3647 | !! REFERENCE(S) : None |
---|
3648 | !! |
---|
3649 | !! FLOWCHART : None |
---|
3650 | !! \n |
---|
3651 | !_ ================================================================================================================================ |
---|
3652 | |
---|
3653 | SUBROUTINE config_stomate_pft_parameters |
---|
3654 | |
---|
3655 | IMPLICIT NONE |
---|
3656 | |
---|
3657 | !! 0. Variables and parameters declaration |
---|
3658 | |
---|
3659 | !! 0.4 Local variable |
---|
3660 | |
---|
3661 | LOGICAL, SAVE :: first_call = .TRUE. !! To keep first call trace (true/false) |
---|
3662 | !$OMP THREADPRIVATE(first_call) |
---|
3663 | INTEGER(i_std) :: ivma,ivm!! index |
---|
3664 | |
---|
3665 | !_ ================================================================================================================================ |
---|
3666 | |
---|
3667 | IF (first_call) THEN |
---|
3668 | |
---|
3669 | ! |
---|
3670 | ! Vegetation structure |
---|
3671 | ! |
---|
3672 | |
---|
3673 | !Config Key = SLA |
---|
3674 | !Config Desc = specif leaf area |
---|
3675 | !Config if = OK_STOMATE |
---|
3676 | !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 |
---|
3677 | !Config Help = |
---|
3678 | !Config Units = [m^2/gC] |
---|
3679 | CALL getin_p('SLA',sla) |
---|
3680 | |
---|
3681 | !Config Key = IS_TROPICAL |
---|
3682 | !Config Desc = PFT IS TROPICAL |
---|
3683 | !Config if = OK_STOMATE |
---|
3684 | !Config Def = FALSE, TRUE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE |
---|
3685 | !Config Help = |
---|
3686 | !Config Units = [-] |
---|
3687 | CALL getin_p('IS_TROPICAL',is_tropical) |
---|
3688 | |
---|
3689 | !Config Key = IS_TEMPERATE |
---|
3690 | !Config Desc = PFT IS TEMPERATE |
---|
3691 | !Config if = OK_STOMATE |
---|
3692 | !Config Def = FALSE, FALSE, FALSE, TRUE, TRUE, TRUE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE |
---|
3693 | !Config Help = |
---|
3694 | !Config Units = [-] |
---|
3695 | CALL getin_p('IS_TEMPERATE',is_temperate) |
---|
3696 | |
---|
3697 | !Config Key = IS_BOREAL |
---|
3698 | !Config Desc = PFT IS BOREAL |
---|
3699 | !Config if = OK_STOMATE |
---|
3700 | !Config Def = FALSE, FALSE, FALSE, FALSE, FALSE, FALSE,TRUE, TRUE, TRUE, FALSE, FALSE, FALSE, FALSE |
---|
3701 | !Config Help = |
---|
3702 | !Config Units = [-] |
---|
3703 | CALL getin_p('IS_BOREAL',is_boreal) |
---|
3704 | |
---|
3705 | ! |
---|
3706 | ! Photosynthesis |
---|
3707 | ! |
---|
3708 | |
---|
3709 | !!$ !Config Key = TPHOTO_MIN_A |
---|
3710 | !!$ !Config Desc = minimum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated |
---|
3711 | !!$ !Config if = OK_STOMATE |
---|
3712 | !!$ !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.0025, 0., 0., 0. |
---|
3713 | !!$ !Config Help = a coefficient of the quadratic relationship that determines the minimal temperature |
---|
3714 | !!$ !Config below which there is no more photosynthesis |
---|
3715 | !!$ !Config Units = [-] |
---|
3716 | !!$ CALL getin_p('TPHOTO_MIN_A',tphoto_min_a) |
---|
3717 | !!$ |
---|
3718 | !!$ !Config Key = TPHOTO_MIN_B |
---|
3719 | !!$ !Config Desc = minimum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated |
---|
3720 | !!$ !Config if = OK_STOMATE |
---|
3721 | !!$ !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.1, 0.,0.,0. |
---|
3722 | !!$ !Config Help = b coefficient of the quadratic relationship that determines the minimal temperature |
---|
3723 | !!$ !Config below which there is no more photosynthesis |
---|
3724 | !!$ !Config Units = [-] |
---|
3725 | !!$ CALL getin_p('TPHOTO_MIN_B',tphoto_min_b) |
---|
3726 | !!$ |
---|
3727 | !!$ !Config Key = TPHOTO_MIN_C |
---|
3728 | !!$ !Config Desc = minimum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated |
---|
3729 | !!$ !Config if = OK_STOMATE |
---|
3730 | !!$ !Config Def = undef, 2., 2., -4., -3.,-2.,-4., -4., -4., -3.25, 13.,-5.,13. |
---|
3731 | !!$ !Config Help = Offset the quadratic relationship that determines the minimal temperature |
---|
3732 | !!$ !Config below which there is no more photosynthesis |
---|
3733 | !!$ !Config Units = [-] |
---|
3734 | !!$ CALL getin_p('TPHOTO_MIN_C',tphoto_min_c) |
---|
3735 | !!$ |
---|
3736 | !!$ !Config Key = TPHOTO_OPT_A |
---|
3737 | !!$ !Config Desc = optimum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated |
---|
3738 | !!$ !Config if = OK_STOMATE |
---|
3739 | !!$ !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.0025, 0., 0., 0. |
---|
3740 | !!$ !Config Help = a coefficient of the quadratic relationship that determines the optimal temperature |
---|
3741 | !!$ !Config controling Vcmax/Vjmax = f(T) |
---|
3742 | !!$ !Config Units = [-] |
---|
3743 | !!$ CALL getin_p('TPHOTO_OPT_A',tphoto_opt_a) |
---|
3744 | !!$ |
---|
3745 | !!$ !Config Key = TPHOTO_OPT_B |
---|
3746 | !!$ !Config Desc = optimum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated |
---|
3747 | !!$ !Config if = OK_STOMATE |
---|
3748 | !!$ !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.25, 0., 0., 0. |
---|
3749 | !!$ !Config Help = b coefficient of the quadratic relationship that determines the optimal temperature |
---|
3750 | !!$ !Config controling Vcmax/Vjmax = f(T) |
---|
3751 | !!$ !Config Units = [-] |
---|
3752 | !!$ CALL getin_p('TPHOTO_OPT_B',tphoto_opt_b) |
---|
3753 | !!$ |
---|
3754 | !!$ !Config Key = TPHOTO_OPT_C |
---|
3755 | !!$ !Config Desc = optimum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated |
---|
3756 | !!$ !Config if = OK_STOMATE |
---|
3757 | !!$ !Config Def = undef, 37., 37., 25., 32., 26., 25., 25., 25., 27.25, 36., 30., 36. |
---|
3758 | !!$ !Config Help = Offset the quadratic relationship that determines the optimal temperature |
---|
3759 | !!$ !Config controling Vcmax/Vjmax = f(T) |
---|
3760 | !!$ !Config Units = [-] |
---|
3761 | !!$ CALL getin_p('TPHOTO_OPT_C',tphoto_opt_c) |
---|
3762 | !!$ |
---|
3763 | !!$ !Config Key = TPHOTO_MAX_A |
---|
3764 | !!$ !Config Desc = maximum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated |
---|
3765 | !!$ !Config if = OK_STOMATE |
---|
3766 | !!$ !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0.00375, 0., 0., 0. |
---|
3767 | !!$ !Config Help = a coefficient of the quadratic relationship that determines the maximal temperature |
---|
3768 | !!$ !Config beyond which there is no more photosynthesis |
---|
3769 | !!$ !Config Units = [-] |
---|
3770 | !!$ CALL getin_p('TPHOTO_MAX_A',tphoto_max_a) |
---|
3771 | !!$ |
---|
3772 | !!$ !Config Key = TPHOTO_MAX_B |
---|
3773 | !!$ !Config Desc = maximum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated |
---|
3774 | !!$ !Config if = OK_STOMATE |
---|
3775 | !!$ !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0.,0.35, 0., 0., 0. |
---|
3776 | !!$ !Config Help = b coefficient of the quadratic relationship that determines the maximal temperature |
---|
3777 | !!$ !Config beyond which there is no more photosynthesis |
---|
3778 | !!$ !Config Units = [-] |
---|
3779 | !!$ CALL getin_p('TPHOTO_MAX_B',tphoto_max_b) |
---|
3780 | !!$ |
---|
3781 | !!$ !Config Key = TPHOTO_MAX_C |
---|
3782 | !!$ !Config Desc = maximum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated |
---|
3783 | !!$ !Config if = OK_STOMATE |
---|
3784 | !!$ !Config Def = undef, 55., 55.,38., 48.,38.,38., 38., 38., 41.125, 55., 45., 55. |
---|
3785 | !!$ !Config Help = Offset the quadratic relationship that determines the maximal temperature |
---|
3786 | !!$ !Config beyond which there is no more photosynthesis |
---|
3787 | !!$ !Config Units = [-] |
---|
3788 | !!$ CALL getin_p('TPHOTO_MAX_C',tphoto_max_c) |
---|
3789 | |
---|
3790 | ! |
---|
3791 | ! Allocation - stomate |
---|
3792 | ! |
---|
3793 | ! |
---|
3794 | !Config Key = S0 |
---|
3795 | !Config Desc = Standard sapwood allocation |
---|
3796 | !Config If = OK_STOMATE |
---|
3797 | !Config Def = undef, .25, .25, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30 |
---|
3798 | !Config Help = |
---|
3799 | !Config Units = [-] |
---|
3800 | CALL getin_p('S0',S0) |
---|
3801 | |
---|
3802 | ! |
---|
3803 | ! Respiration - stomate |
---|
3804 | ! |
---|
3805 | |
---|
3806 | !Config Key = MAINT_RESP_SLOPE_C |
---|
3807 | !Config Desc = slope of maintenance respiration coefficient (1/K), constant c of aT^2+bT+c , tabulated |
---|
3808 | !Config if = OK_STOMATE |
---|
3809 | !Config Def = undef, .20, .20, .16, .16, .16, .16, .16, .16, .16, .12, .16, .12 |
---|
3810 | !Config Help = Offset of the temperature quadratic function that determines the |
---|
3811 | !Config slope of the function between temperature and maintenance respiration. |
---|
3812 | !Config Units = [-] |
---|
3813 | CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) |
---|
3814 | |
---|
3815 | !Config Key = MAINT_RESP_SLOPE_B |
---|
3816 | !Config Desc = slope of maintenance respiration coefficient (1/K), constant b of aT^2+bT+c , tabulated |
---|
3817 | !Config if = OK_STOMATE |
---|
3818 | !Config Def = undef, .0, .0, .0, .0, .0, .0, .0, .0, -.00133, .0, -.00133, .0 |
---|
3819 | !Config Help = b coefficient of the temperature quadratic function that determines the |
---|
3820 | !Config slope of the function between temperature and maintenance respiration. |
---|
3821 | !Config Units = [-] |
---|
3822 | CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b) |
---|
3823 | |
---|
3824 | !Config Key = MAINT_RESP_SLOPE_A |
---|
3825 | !Config Desc = slope of maintenance respiration coefficient (1/K), constant a of aT^2+bT+c , tabulated |
---|
3826 | !Config if = OK_STOMATE |
---|
3827 | !Config Def = undef, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0 |
---|
3828 | !Config Help = a coefficient of the temperature quadratic function that determines the |
---|
3829 | !Config slope of the function between temperature and maintenance respiration. |
---|
3830 | !Config Units = [-] |
---|
3831 | CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a) |
---|
3832 | |
---|
3833 | !Config Key = CM_ZERO_LEAF |
---|
3834 | !Config Desc = maintenance respiration coefficient at 0 deg C, for leaves, tabulated |
---|
3835 | !Config if = OK_STOMATE |
---|
3836 | !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 |
---|
3837 | !Config Help = |
---|
3838 | !Config Units = [g/g/day] |
---|
3839 | CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf) |
---|
3840 | |
---|
3841 | !Config Key = CM_ZERO_SAPABOVE |
---|
3842 | !Config Desc = maintenance respiration coefficient at 0 deg C,for sapwood above, tabulated |
---|
3843 | !Config if = OK_STOMATE |
---|
3844 | !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 |
---|
3845 | !Config Help = |
---|
3846 | !Config Units = [g/g/day] |
---|
3847 | CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove) |
---|
3848 | |
---|
3849 | !Config Key = CM_ZERO_SAPBELOW |
---|
3850 | !Config Desc = maintenance respiration coefficient at 0 deg C, for sapwood below, tabulated |
---|
3851 | !Config if = OK_STOMATE |
---|
3852 | !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 |
---|
3853 | !Config Help = |
---|
3854 | !Config Units = [g/g/day] |
---|
3855 | CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow) |
---|
3856 | |
---|
3857 | !Config Key = CM_ZERO_HEARTABOVE |
---|
3858 | !Config Desc = maintenance respiration coefficient at 0 deg C, for heartwood above, tabulated |
---|
3859 | !Config if = OK_STOMATE |
---|
3860 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0. |
---|
3861 | !Config Help = |
---|
3862 | !Config Units = [g/g/day] |
---|
3863 | CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove) |
---|
3864 | |
---|
3865 | !Config Key = CM_ZERO_HEARTBELOW |
---|
3866 | !Config Desc = maintenance respiration coefficient at 0 deg C,for heartwood below, tabulated |
---|
3867 | !Config if = OK_STOMATE |
---|
3868 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0. |
---|
3869 | !Config Help = |
---|
3870 | !Config Units = [g/g/day] |
---|
3871 | CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow) |
---|
3872 | |
---|
3873 | !Config Key = CM_ZERO_ROOT |
---|
3874 | !Config Desc = maintenance respiration coefficient at 0 deg C, for roots, tabulated |
---|
3875 | !Config if = OK_STOMATE |
---|
3876 | !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 |
---|
3877 | !Config Help = |
---|
3878 | !Config Units = [g/g/day] |
---|
3879 | CALL getin_p('CM_ZERO_ROOT',cm_zero_root) |
---|
3880 | |
---|
3881 | !Config Key = CM_ZERO_FRUIT |
---|
3882 | !Config Desc = maintenance respiration coefficient at 0 deg C, for fruits, tabulated |
---|
3883 | !Config if = OK_STOMATE |
---|
3884 | !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 |
---|
3885 | !Config Help = |
---|
3886 | !Config Units = [g/g/day] |
---|
3887 | CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit) |
---|
3888 | |
---|
3889 | !+++CHECK+++ |
---|
3890 | ! Default values depend on the growth routine |
---|
3891 | !Config Key = CM_ZERO_CARBRES |
---|
3892 | !Config Desc = maintenance respiration coefficient at 0 deg C, for carbohydrate reserve, tabulated |
---|
3893 | !Config if = OK_STOMATE |
---|
3894 | !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 |
---|
3895 | !Config Help = |
---|
3896 | !Config Units = [g/g/day] |
---|
3897 | CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres) |
---|
3898 | |
---|
3899 | !Config Key = CM_ZERO_LABILE |
---|
3900 | !Config Desc = Caution, depends on the allocation scheme. Maintenance respiration coefficient at 0 deg C, for the labile pool, tabulated |
---|
3901 | !Config if = OK_STOMATE |
---|
3902 | !Config Def = undef, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2, 3.36E-2 |
---|
3903 | !Config Help = |
---|
3904 | !Config Units = [g/g/day] |
---|
3905 | CALL getin_p('CM_ZERO_LABILE',cm_zero_labile) |
---|
3906 | |
---|
3907 | !Config Key = COEFF_MAINT_INIT |
---|
3908 | !Config Desc = initial values for maintenance respiration coefficient, used in functional allocation at 0 deg C |
---|
3909 | !Config if = OK_STOMATE |
---|
3910 | !Config Def = undef, 0.022, 0.022, 0.021, 0.033, 0.033, 0.033, 0.033, 0.033, 0.033, 0.011, 0.011, 0.011 |
---|
3911 | !Config Help = |
---|
3912 | !Config Units = [g/g/day] |
---|
3913 | CALL getin_p('COEFF_MAINT_INIT',coeff_maint_init) |
---|
3914 | |
---|
3915 | !Config Key = FRAC_GROWTHRESP |
---|
3916 | !Config Desc = Depends on the allocation scheme |
---|
3917 | !Config if = |
---|
3918 | !Config Def = 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28, 0.28 |
---|
3919 | !Config Help = |
---|
3920 | !Config Units = |
---|
3921 | CALL getin_p("FRAC_GROWTHRESP",frac_growthresp) |
---|
3922 | |
---|
3923 | !Config Key = GPP_TO_LABILE |
---|
3924 | !Config Desc = Depends on the allocation scheme |
---|
3925 | !Config if = |
---|
3926 | !Config Def = 1., 3., 1., 1., 3., 1., 3., 3., 3., 3., 3., 3. |
---|
3927 | !Config Help = |
---|
3928 | !Config Units = |
---|
3929 | CALL getin_p("GPP_TO_LABILE",gpp_to_labile) |
---|
3930 | |
---|
3931 | ! |
---|
3932 | ! Stand structure - stomate |
---|
3933 | ! |
---|
3934 | |
---|
3935 | !Config Key = PIPE_DENSITY |
---|
3936 | !Config Desc = |
---|
3937 | !Config if = |
---|
3938 | !Config Def = undef, 3.e5, 3.e5, 2.e5, 3.e5, 3.e5, 2.e5, 3.e5, 2.e5, 2.e5, 2.e5, 2.e5, 2.e5 |
---|
3939 | !Config Help = |
---|
3940 | !Config Units = |
---|
3941 | CALL getin_p("PIPE_DENSITY",pipe_density) |
---|
3942 | |
---|
3943 | !Config Key = PIPE_TUNE1 |
---|
3944 | !Config Desc = crown area = pipe_tune1. stem diameter**pipe_tune_exp_coeff (Reinicke's theory) |
---|
3945 | !Config If = OK_STOMATE |
---|
3946 | !Config Def = undef, 100., 100., 100., 100., 100., 100., 100., 100., 0., 0., 0., 0. |
---|
3947 | !Config Help = |
---|
3948 | !Config Units = [-] |
---|
3949 | CALL getin_p('PIPE_TUNE1',pipe_tune1) |
---|
3950 | |
---|
3951 | !Config Key = PIPE_TUNE2 |
---|
3952 | !Config Desc = height=pipe_tune2 * diameter**pipe_tune3 |
---|
3953 | !Config If = OK_STOMATE |
---|
3954 | !Config Def = undef, 40., 40., 40., 40., 40., 40., 40., 40., 0., 0., 0., 0. |
---|
3955 | !Config Help = |
---|
3956 | !Config Units = [-] |
---|
3957 | CALL getin_p('PIPE_TUNE2',pipe_tune2) |
---|
3958 | |
---|
3959 | !Config Key = PIPE_TUNE3 |
---|
3960 | !Config Desc = height=pipe_tune2 * diameter**pipe_tune3 |
---|
3961 | !Config If = OK_STOMATE |
---|
3962 | !Config Def = undef, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0., 0., 0., 0. |
---|
3963 | !Config Help = |
---|
3964 | !Config Units = [-] |
---|
3965 | CALL getin_p('PIPE_TUNE3',pipe_tune3) |
---|
3966 | |
---|
3967 | !Config Key = PIPE_TUNE4 |
---|
3968 | !Config Desc = needed for stem diameter |
---|
3969 | !Config If = OK_STOMATE |
---|
3970 | !Config Def = undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0., 0., 0., 0. |
---|
3971 | !Config Help = |
---|
3972 | !Config Units = [-] |
---|
3973 | CALL getin_p('PIPE_TUNE4',pipe_tune4) |
---|
3974 | |
---|
3975 | !Config Key = TREE_FF |
---|
3976 | !Config Desc = Tree form factor reducing the volume of a cylinder |
---|
3977 | ! to the real volume of the tree shape (including the |
---|
3978 | ! branches) |
---|
3979 | !Config If = OK_STOMATE |
---|
3980 | !Config Def = undef, 0.6, 0.6, 0.6, 0.6, 0.6, 0.8, 0.8, 0.8, 0., 0., 0., 0. |
---|
3981 | !Config Help = |
---|
3982 | !Config Units = [-] |
---|
3983 | CALL getin_p('TREE_FF',tree_ff) |
---|
3984 | |
---|
3985 | !Config Key = PIPE_K1 |
---|
3986 | !Config Desc = |
---|
3987 | !Config If = OK_STOMATE |
---|
3988 | !Config Def = undef, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 0., 0., 0., 0. |
---|
3989 | !Config Help = |
---|
3990 | !Config Units = [-] |
---|
3991 | CALL getin_p('PIPE_K1',pipe_k1) |
---|
3992 | |
---|
3993 | !Config Key = PIPE_TUNE_EXP_COEFF |
---|
3994 | !Config Desc = pipe tune exponential coeff |
---|
3995 | !Config If = OK_STOMATE |
---|
3996 | !Config Def = undef, 1.6, 1.6, 1.6, 1.6, 1.6, 1.6, 1.6, 1.6, 0., 0., 0., 0. |
---|
3997 | !Config Help = |
---|
3998 | !Config Units = [-] |
---|
3999 | CALL getin_p('PIPE_TUNE_EXP_COEFF',pipe_tune_exp_coeff) |
---|
4000 | |
---|
4001 | !Config Key = MASS_RATIO_HEART_SAP |
---|
4002 | !Config Desc = mass ratio (heartwood+sapwood)/heartwood |
---|
4003 | !Config If = OK_STOMATE |
---|
4004 | !Config Def = undef, 3., 3., 3., 3., 3., 3., 3., 3., 0., 0., 0., 0. |
---|
4005 | !Config Help = |
---|
4006 | !Config Units = [-] |
---|
4007 | CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap) |
---|
4008 | |
---|
4009 | !Config Key = LAI_TO_HEIGHT |
---|
4010 | !Config Desc = Convertion factor from lai to vegetation height for grasses and crops |
---|
4011 | !Config if = OK_STOMATE, OK_FUNCTIONAL_ALLOCATION |
---|
4012 | !Config Def = undef, |
---|
4013 | !Config Help = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.2, 0.5, 0.2, 0.5 |
---|
4014 | !Config Units = [m m2 m-2] |
---|
4015 | CALL getin_p('LAI_TO_HEIGHT',lai_to_height) |
---|
4016 | |
---|
4017 | |
---|
4018 | !Config Key = CANOPY_COVER |
---|
4019 | !Config Desc = Test values for canopy cover |
---|
4020 | !Config if = OK_STOMATE, OK_FUNCTIONAL_ALLOCATION |
---|
4021 | !Config Def = undef, 0.9, 0.9, 0.7, 0.7, 0.7, 0.6, 0.5, 0.5, 0.9, 0.9, 0.9, 0.9 |
---|
4022 | !Config Help = |
---|
4023 | !Config Units = [-] |
---|
4024 | CALL getin_p('CANOPY_COVER',canopy_cover) |
---|
4025 | |
---|
4026 | ! |
---|
4027 | ! Growth - Resource limitation stomate |
---|
4028 | ! |
---|
4029 | |
---|
4030 | ! |
---|
4031 | ! Growth - Functional allocation stomate |
---|
4032 | ! |
---|
4033 | |
---|
4034 | !Config Key = CN_LEAF_PRESCRIBED |
---|
4035 | !Config Desc = |
---|
4036 | !Config if = |
---|
4037 | !Config Def = undef, 29., 29., 29., 29., 29., 29., 29., 29., 29., 29., 29., 29. |
---|
4038 | !Config Help = |
---|
4039 | !Config Units = |
---|
4040 | CALL getin_p("CN_LEAF_PRESCRIBED",cn_leaf_prescribed) |
---|
4041 | |
---|
4042 | !Config Key = FCN_WOOD |
---|
4043 | !Config Desc = CN of wood for allocation, relative to leaf CN according to stich et al 2003 |
---|
4044 | !Config if = OK_STOMATE |
---|
4045 | !Config Def = undef, .087, .087, .087, .087, .087, .087, .087, .087, 1., 1., 1. |
---|
4046 | !Config Help = |
---|
4047 | !Config Units = [-] |
---|
4048 | CALL getin_p('FCN_WOOD',fcn_wood) |
---|
4049 | |
---|
4050 | !Config Key = FCN_ROOT |
---|
4051 | !Config Desc = CN roots for allocation, relative to leaf CN according to stich et al 2003 |
---|
4052 | !Config if = OK_STOMATE |
---|
4053 | !Config Def = undef, 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1. |
---|
4054 | !Config Help = |
---|
4055 | !Config Units = [-] |
---|
4056 | CALL getin_p('FCN_ROOT',fcn_root) |
---|
4057 | |
---|
4058 | !Config Key = K_LATOSA_MAX |
---|
4059 | !Config Desc = Maximum leaf-to-sapwood area ratio |
---|
4060 | !Config if = OK_STOMATE |
---|
4061 | !Config Def = (undef, 5., 5., 5., 3., 5., 5., 5., 5., undef, undef, undef, undef)*1.e3 |
---|
4062 | !Config Help = |
---|
4063 | !Config Units = [-] |
---|
4064 | CALL getin_p('K_LATOSA_MAX',k_latosa_max) |
---|
4065 | |
---|
4066 | !Config Key = K_LATOSA_MIN |
---|
4067 | !Config Desc = Minimum leaf-to-sapwood area ratio |
---|
4068 | !Config if = OK_STOMATE |
---|
4069 | !Config Def = (undef, 5., 5., 5., 3., 5., 5., 5., 5., undef, undef, undef, undef)*1.e3 |
---|
4070 | !Config Help = |
---|
4071 | !Config Units = [-] |
---|
4072 | CALL getin_p('K_LATOSA_MIN',k_latosa_min) |
---|
4073 | |
---|
4074 | !Config Key = FRUIT_ALLOC |
---|
4075 | !Config Desc = Guestimates - should be confirmed |
---|
4076 | !Config if = OK_STOMATE |
---|
4077 | !Config Def = (undef, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0., 0., 0., 0.) |
---|
4078 | !Config Help = |
---|
4079 | !Config Units = [-] |
---|
4080 | CALL getin_p('FRUIT_ALLOC',fruit_alloc) |
---|
4081 | |
---|
4082 | !Config Key = LAI_MAX_TO_HAPPY |
---|
4083 | !Config Desc = |
---|
4084 | !Config If = OK_STOMATE |
---|
4085 | !Config Def = undef, 0.5, 0.5, 0.5, 0.5, 0.4, 0.5, 0.36, 0.35, 0.35, 0.5, 0.5, 0.5 |
---|
4086 | !Config Help = Multiplicative factor of lai_max that determines |
---|
4087 | !Config the threshold value of LAI below which the carbohydrate |
---|
4088 | !Config reserve is used. |
---|
4089 | !Config Units = [-] |
---|
4090 | CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy) |
---|
4091 | ! |
---|
4092 | |
---|
4093 | |
---|
4094 | !Config Key = NMAXTREES |
---|
4095 | !Config Desc = number of seedlings planted at the start of a rotation |
---|
4096 | !Config if = FOREST_MANAGEMENT |
---|
4097 | !Config Def = (undef, 10., 10., 10., 10., 10., 2., 2., 2., 10., 10., 10., 10.)*1.e3 |
---|
4098 | !Config Help = |
---|
4099 | !Config Units = [trees ha-1] |
---|
4100 | CALL getin_p("NMAXTREES",nmaxtrees) |
---|
4101 | |
---|
4102 | !Config Key = HEIGHT_INIT_MIN |
---|
4103 | !Config Desc = |
---|
4104 | !Config if = FUNCTIONAL ALLOCATION |
---|
4105 | !Config Def = undef, 2, 2, 2, 2, 2, 3, 3, 3, 3, 0.1, 0.1, 0.1, 0.1 |
---|
4106 | !Config Help = |
---|
4107 | !Config Units = [m] |
---|
4108 | CALL getin_p("HEIGHT_INIT_MIN",height_init_min) |
---|
4109 | |
---|
4110 | !Config Key = HEIGHT_INIT_MAX |
---|
4111 | !Config Desc = |
---|
4112 | !Config if = FUNCTIONAL ALLOCATION |
---|
4113 | !Config Def = undef, 3, 3, 3, 3, 3, 4, 4, 4, 4, 0.2, 0.2, 0.2, 0.2 |
---|
4114 | !Config Help = |
---|
4115 | !Config Units = [m] |
---|
4116 | CALL getin_p("HEIGHT_INIT_MAX",height_init_max) |
---|
4117 | |
---|
4118 | !Config Key = ALPHA_SELF_THINNING |
---|
4119 | !Config Desc = |
---|
4120 | !Config if = FUNCTION NMAX |
---|
4121 | !Config Def = undef, 3000, 3000, 1462, 2262, 1900, 960, 939, 1046, undef, undef, undef, undef |
---|
4122 | !Config Help = |
---|
4123 | !Config Units = [-] |
---|
4124 | CALL getin_p("ALPHA_SELF_THINNING",alpha_self_thinning) |
---|
4125 | |
---|
4126 | !Config Key = BETA_SELF_THINNING |
---|
4127 | !Config Desc = |
---|
4128 | !Config if = FUNCTION NMAX |
---|
4129 | !Config Def = undef, -0.57, -0.57, -0.55, -0.61, -0.58, -0.55, -0.56, -0.56, undef, undef, undef, undef |
---|
4130 | !Config Help = |
---|
4131 | !Config Units = [-] |
---|
4132 | CALL getin_p("BETA_SELF_THINNING",beta_self_thinning) |
---|
4133 | |
---|
4134 | !Config Key = FUELWOOD_DIAMETER |
---|
4135 | !Config Desc = Diameter below which harvest will be used as fuelwood |
---|
4136 | !Config if = |
---|
4137 | !Config Def = undef, 0.3, 0.3, 0.2, 0.3, 0.3, 0.2, 0.2, 0.2, undef, undef, undef, undef |
---|
4138 | !Config Help = |
---|
4139 | !Config Units = [m] |
---|
4140 | CALL getin_p("FUELWOOD_DIAMETER",fuelwood_diameter) |
---|
4141 | |
---|
4142 | !Config Key = COPPICE_KILL_BE_WOOD |
---|
4143 | !Config Desc = The fraction of belowground wood killed during coppicing |
---|
4144 | !Config if = |
---|
4145 | !Config Def = undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, undef, undef, undef, undef |
---|
4146 | !Config Help = |
---|
4147 | !Config Units = [m] |
---|
4148 | CALL getin_p("COPPICE_KBEW",coppice_kill_be_wood) |
---|
4149 | ! |
---|
4150 | ! Hydraulic architecture - sechiba? |
---|
4151 | ! |
---|
4152 | |
---|
4153 | !Config Key = K_ROOT |
---|
4154 | !Config Desc = Fine root specific conductivity |
---|
4155 | !Config if = OK_STOMATE |
---|
4156 | !Config Def = (undef, 4., 4., 4., 4., 4., 4., 4., 4., 50., 50., 50., 50.)*1.e-7 |
---|
4157 | !Config Help = |
---|
4158 | !Config Units = [m^{3} kg^{-1} s^{-1} MPa^{-1}] |
---|
4159 | CALL getin_p('K_ROOT',k_root) |
---|
4160 | |
---|
4161 | !Config Key = K_SAP |
---|
4162 | !Config Desc = Sapwood specific conductivity |
---|
4163 | !Config if = OK_STOMATE |
---|
4164 | !Config Def = (undef, 50., 10., 8., 5., 30., 8., 20., 8., undef, undef, undef, undef)*1.e-4 |
---|
4165 | !Config Help = |
---|
4166 | !Config Units = [m^{2} s^{-1} MPa^{-1}] |
---|
4167 | CALL getin_p('K_SAP',k_sap) |
---|
4168 | |
---|
4169 | !Config Key = K_LEAF |
---|
4170 | !Config Desc = Leaf conductivity |
---|
4171 | !Config if = OK_STOMATE |
---|
4172 | !Config Def = (undef, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5)*1.e-7 |
---|
4173 | !Config Help = |
---|
4174 | !Config Units = [m s^{-1} MPa^{-1})] |
---|
4175 | CALL getin_p('K_LEAF',k_leaf) |
---|
4176 | |
---|
4177 | !Config Key = PHI_LEAF |
---|
4178 | !Config Desc = Minimal leaf potential |
---|
4179 | !Config if = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION |
---|
4180 | !Config Def = undef, -2.2, -2.2, -2.2, -3.5, -2.2, -2.2, -2.2, -2.2, -2.2, -2.2, -2.2, -2.2 |
---|
4181 | !Config Help = |
---|
4182 | !Config Units = [MPa] |
---|
4183 | CALL getin_p('PHI_LEAF',phi_leaf) |
---|
4184 | |
---|
4185 | !Config Key = PHI_50 |
---|
4186 | !Config Desc = Sapwood leaf water potential that causes 50% loss of xylem conductivity through cavitation |
---|
4187 | !Config if = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION |
---|
4188 | !Config Def = undef, -0.3, -1.3, -2.0, -1.7, -1.0, -2.0, -1.0, -2.0, undef, undef, undef, undef |
---|
4189 | !Config Help = |
---|
4190 | !Config Units = [m s^{-1} MPa^{-1})] |
---|
4191 | CALL getin_p('PHI_50',phi_50) |
---|
4192 | |
---|
4193 | !Config Key = C_CAVITATION |
---|
4194 | !Config Desc = Shape parameter for loss of conductance |
---|
4195 | !Config if = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION |
---|
4196 | !Config Def = undef, 5., 3., 3., 3., 3., 3., 3., 3., undef, undef, undef, undef |
---|
4197 | !Config Help = |
---|
4198 | !Config Units = [-] |
---|
4199 | CALL getin_p('C_CAVITATION',c_cavitation) |
---|
4200 | |
---|
4201 | !Config Key = PHI_SOIL_TUNE |
---|
4202 | !Config Desc = Additive tuning parameter to account for soil-root interactions |
---|
4203 | !Config if = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION, HYDRAOL_ARCHITECTURE |
---|
4204 | !Config Def = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0. |
---|
4205 | !Config Help = |
---|
4206 | !Config Units = [MPa] |
---|
4207 | CALL getin_p('PHI_SOIL_TUNE',phi_soil_tune) |
---|
4208 | |
---|
4209 | !Config Key = LAI_HAPPY |
---|
4210 | !Config Desc = The value of LAI below which carbohydrate reserves will be used. Shape parameter for loss of conductance |
---|
4211 | !Config if = OK_STOMATE, FUNCTIONAL ALLOCATION |
---|
4212 | !Config Def = undef, 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1. |
---|
4213 | !Config Help = |
---|
4214 | !Config Units = [m^{2} m^{-2}] |
---|
4215 | CALL getin_p('LAI_HAPPY',lai_happy) |
---|
4216 | |
---|
4217 | !-------------------------------------------------------------------------------------------------------------------------------- |
---|
4218 | ! tzjh hydraulic architecture |
---|
4219 | |
---|
4220 | !Config Key = GPSI |
---|
4221 | !Config Desc = gs vs psi_leaf curve parameter |
---|
4222 | !Config if = OK_STOMATE |
---|
4223 | !Config Def = undef, -1.2, -1.2, -1.2,-1.2, -1.2,-1.2,-1.2, -1.2,-1.2,-1.2,-1.2,-1.2 |
---|
4224 | !Config Help = |
---|
4225 | !Config Units = [-] |
---|
4226 | CALL getin_p('GPSI',gpsi) |
---|
4227 | |
---|
4228 | !Config Key = GPSI_50 |
---|
4229 | !Config Desc = psi_leaf at 50% stomatal closure |
---|
4230 | !Config if = OK_STOMATE |
---|
4231 | !Config Def = undef, 2.5, 2.5, 2.5,2.5, 2.5,2.5,2.5, 2.5,2.5,2.5,2.5,2.5 |
---|
4232 | !Config Help = |
---|
4233 | !Config Units = [-Mpa] |
---|
4234 | CALL getin_p('GPSI_50',gpsi_50) |
---|
4235 | |
---|
4236 | !Config Key = GMAX |
---|
4237 | !Config Desc = maximum stomatal conductance |
---|
4238 | !Config if = OK_STOMATE |
---|
4239 | !Config Def = undef, 1000., 1000., 1000.,1000., 1000.,1000.,1000., 1000.,1000.,1000.,1000.,1000. |
---|
4240 | !Config Help = |
---|
4241 | !Config Units = [mmol m^{-2}s^{-1}] |
---|
4242 | CALL getin_p('GMAX',gmax) |
---|
4243 | |
---|
4244 | !Config Key = GMIN |
---|
4245 | !Config Desc = minimum stomatal conductance |
---|
4246 | !Config if = OK_STOMATE |
---|
4247 | !Config Def = undef, 10., 10., 10.,10., 10.,10.,10., 10.,10.,10.,10.,10. |
---|
4248 | !Config Help = |
---|
4249 | !Config Units = [mmol m^{-2}s^{-1}] |
---|
4250 | CALL getin_p('GMIN',gmin) |
---|
4251 | |
---|
4252 | !Config Key = KMAX_LEAF |
---|
4253 | !Config Desc = maximum hydraulic conductivity of leaf |
---|
4254 | !Config if = OK_STOMATE |
---|
4255 | !Config Def = undef, 10., 10., 10.,10., 10.,10.,10., 10.,10.,10.,10.,10. |
---|
4256 | !Config Help = |
---|
4257 | !Config Units = [mmol m^{-2}s^{-1} MPa^{-1}] |
---|
4258 | CALL getin_p('KMAX_LEAF',kmax_leaf) |
---|
4259 | |
---|
4260 | !Config Key = KMAX_STEM |
---|
4261 | !Config Desc = maximum hydraulic conductivity of stem |
---|
4262 | !Config if = OK_STOMATE |
---|
4263 | !Config Def = undef, 10., 10., 10.,10., 10.,10.,10., 10.,10.,10.,10.,10. |
---|
4264 | !Config Help = |
---|
4265 | !Config Units = [mmol m^{-2}s^{-1} MPa^{-1}] |
---|
4266 | CALL getin_p('KMAX_stem',kmax_stem) |
---|
4267 | |
---|
4268 | !Config Key = KMAX_ROOT |
---|
4269 | !Config Desc = maximum hydraulic conductivity of root |
---|
4270 | !Config if = OK_STOMATE |
---|
4271 | !Config Def = undef, 10., 10., 10.,10., 10.,10.,10., 10.,10.,10.,10.,10. |
---|
4272 | !Config Help = |
---|
4273 | !Config Units = [mmol m^{-2}s^{-1} MPa^{-1}] |
---|
4274 | CALL getin_p('KMAX_ROOT',kmax_root) |
---|
4275 | |
---|
4276 | !Config Key = A_LEAF |
---|
4277 | !Config Desc = kleaf vs. psi_leaf curve parameter |
---|
4278 | !Config if = OK_STOMATE |
---|
4279 | !Config Def = undef, -1.2, -1.2, -1.2,-1.2, -1.2,-1.2,-1.2, -1.2,-1.2,-1.2,-1.2,-1.2 |
---|
4280 | !Config Help = |
---|
4281 | !Config Units = [-] |
---|
4282 | CALL getin_p('A_LEAF',a_leaf) |
---|
4283 | |
---|
4284 | !Config Key = A_STEM |
---|
4285 | !Config Desc = kstem vs. psi_stem curve parameter |
---|
4286 | !Config if = OK_STOMATE |
---|
4287 | !Config Def = undef, -1.2, -1.2, -1.2,-1.2, -1.2,-1.2,-1.2, -1.2,-1.2,-1.2,-1.2,-1.2 |
---|
4288 | !Config Help = |
---|
4289 | !Config Units = [-] |
---|
4290 | CALL getin_p('A_STEM',a_stem) |
---|
4291 | |
---|
4292 | !Config Key = A_ROOT |
---|
4293 | !Config Desc = kroot vs. psi_root curve parameter |
---|
4294 | !Config if = OK_STOMATE |
---|
4295 | !Config Def = undef, -1.2, -1.2, -1.2,-1.2, -1.2,-1.2,-1.2, -1.2,-1.2,-1.2,-1.2,-1.2 |
---|
4296 | !Config Help = |
---|
4297 | !Config Units = [-] |
---|
4298 | CALL getin_p('A_ROOT',a_root) |
---|
4299 | |
---|
4300 | !Config Key = P50_LEAF |
---|
4301 | !Config Desc = psi_leaf at 50% loss of leaf hydraulic conductivity |
---|
4302 | !Config if = OK_STOMATE |
---|
4303 | !Config Def = undef, 2.5, 2.5, 2.5,2.5, 2.5,2.5,2.5, 2.5,2.5,2.5,2.5,2.5 |
---|
4304 | !Config Help = |
---|
4305 | !Config Units = [-MPa] |
---|
4306 | CALL getin_p('P50_LEAF',P50_leaf) |
---|
4307 | |
---|
4308 | !Config Key = P50_STEM |
---|
4309 | !Config Desc = psi_stem at 50% loss of leaf hydraulic conductivity |
---|
4310 | !Config if = OK_STOMATE |
---|
4311 | !Config Def = undef, 2.5, 2.5, 2.5,2.5, 2.5,2.5,2.5, 2.5,2.5,2.5,2.5,2.5 |
---|
4312 | !Config Help = |
---|
4313 | !Config Units = [-MPa] |
---|
4314 | CALL getin_p('P50_STEM',P50_stem) |
---|
4315 | |
---|
4316 | !Config Key = P50_ROOT |
---|
4317 | !Config Desc = psi_root at 50% loss of leaf hydraulic conductivity |
---|
4318 | !Config if = OK_STOMATE |
---|
4319 | !Config Def = undef, 2.5, 2.5, 2.5,2.5, 2.5,2.5,2.5, 2.5,2.5,2.5,2.5,2.5 |
---|
4320 | !Config Help = |
---|
4321 | !Config Units = [-MPa] |
---|
4322 | CALL getin_p('P50_ROOT',P50_root) |
---|
4323 | |
---|
4324 | !Config Key = WOOD_DENSITY |
---|
4325 | !Config Desc = g of stem dry mass per m3 of stem volume |
---|
4326 | !Config if = OK_STOMATE |
---|
4327 | !Config Def = undef, 645000, 645000, 645000,645000, 645000,645000,645000, 645000,645000,645000,645000,645000 |
---|
4328 | !Config Help = |
---|
4329 | !Config Units = [g m^{-3}] |
---|
4330 | CALL getin_p('WOOD_DENSITY',wood_density) |
---|
4331 | |
---|
4332 | !Config Key = W_DENSITY_STEM |
---|
4333 | !Config Desc = mmol H2O per m3 of stem volume |
---|
4334 | !Config if = OK_STOMATE |
---|
4335 | !Config Def = undef, 25000000, 25000000, 25000000,25000000, 25000000,25000000,25000000, 25000000,25000000,25000000,25000000,25000000 |
---|
4336 | !Config Help = |
---|
4337 | !Config Units = [mmol m^{-3}] |
---|
4338 | CALL getin_p('W_DENSITY_STEM',w_density_stem) |
---|
4339 | |
---|
4340 | !Config Key = ROOT_SHOOT_RATIO |
---|
4341 | !Config Desc = ratio of root mass to shoot mass |
---|
4342 | !Config if = OK_STOMATE |
---|
4343 | !Config Def = undef, 0.25, 0.25, 0.25,0.25, 0.25,0.25,0.25, 0.25,0.25,0.25,0.25,0.25 |
---|
4344 | !Config Help = |
---|
4345 | !Config Units = [g g^{-1}] |
---|
4346 | CALL getin_p('ROOT_SHOOT_RATIO',root_shoot_ratio) |
---|
4347 | |
---|
4348 | !Config Key = RWC_ROOT |
---|
4349 | !Config Desc = relative water content in the root |
---|
4350 | !Config if = OK_STOMATE |
---|
4351 | !Config Def = undef, 35, 35, 35,35, 35,35,35, 35,35,35,35,35 |
---|
4352 | !Config Help = |
---|
4353 | !Config Units = [mmol g{-1}] |
---|
4354 | CALL getin_p('RWC_ROOT',rwc_root) |
---|
4355 | |
---|
4356 | !Config Key = ROOT_DENSITY |
---|
4357 | !Config Desc = relative water content in the root |
---|
4358 | !Config if = OK_STOMATE |
---|
4359 | !Config Def = undef, 0.502, 0.502, 0.502,0.502, 0.502,0.502,0.502, 0.502,0.502,0.502,0.502,0.502 |
---|
4360 | !Config Help = |
---|
4361 | !Config Units = [g cm{-3}] |
---|
4362 | CALL getin_p('ROOT_DENSITY',root_density) |
---|
4363 | |
---|
4364 | !Config Key = LDMC |
---|
4365 | !Config Desc = leaf dry matter content |
---|
4366 | !Config if = OK_STOMATE |
---|
4367 | !Config Def = undef, 0.2, 0.2, 0.2,0.2, 0.2,0.2,0.2, 0.2,0.2,0.2,0.2,0.2 |
---|
4368 | !Config Help = |
---|
4369 | !Config Units = [g g{-1}] |
---|
4370 | CALL getin_p('LDMC',LDMC) |
---|
4371 | |
---|
4372 | !Config Key = SLA_HYDRO |
---|
4373 | !Config Desc = specific leaf area for use in the hydraulic architecture |
---|
4374 | !Config if = OK_STOMATE |
---|
4375 | !Config Def = undef, 16.6, 16.6, 16.6,16.6, 16.6,16.6,16.6, 16.6,16.6,16.6,16.6,16.6 |
---|
4376 | !Config Help = |
---|
4377 | !Config Units = [m^{2} g{-1}] |
---|
4378 | CALL getin_p('SLA_HYDRO',sla_hydro) |
---|
4379 | |
---|
4380 | !Config Key = CXYL |
---|
4381 | !Config Desc = stem capacitance |
---|
4382 | !Config if = OK_STOMATE |
---|
4383 | !Config Def = undef, 0.5, 0.5, 0.5,0.5, 0.5,0.5,0.5, 0.5,0.5,0.5,0.5,0.5 |
---|
4384 | !Config Help = |
---|
4385 | !Config Units = [mmol mmol^{-1} MPa^{-1}] |
---|
4386 | CALL getin_p('CXYL',cxyl) |
---|
4387 | |
---|
4388 | !Config Key = CR |
---|
4389 | !Config Desc = root capacitance |
---|
4390 | !Config if = OK_STOMATE |
---|
4391 | !Config Def = undef, 0.5, 0.5, 0.5,0.5, 0.5,0.5,0.5, 0.5,0.5,0.5,0.5,0.5 |
---|
4392 | !Config Help = |
---|
4393 | !Config Units = [mmol mmol^{-1} MPa^{-1}] |
---|
4394 | CALL getin_p('CR',cr) |
---|
4395 | |
---|
4396 | !Config Key = CL |
---|
4397 | !Config Desc = leaf capacitance |
---|
4398 | !Config if = OK_STOMATE |
---|
4399 | !Config Def = undef, 0.1, 0.1, 0.1,0.1, 0.1,0.1,0.1, 0.1,0.1,0.1,0.1,0.1 |
---|
4400 | !Config Help = |
---|
4401 | !Config Units = [mmol mmol^{-1} MPa^{-1}] |
---|
4402 | CALL getin_p('CL',cl) |
---|
4403 | !----------------------------------------------------------------------------------------------------------------- |
---|
4404 | |
---|
4405 | ! |
---|
4406 | ! Mortality - lpj_gap |
---|
4407 | ! |
---|
4408 | !Config Key = DEATH_DISTRIBUTION_FACTOR |
---|
4409 | !Config Desc = Shape parameter for tree mortality |
---|
4410 | !Config if = OK_STOMATE, FUNCTIONAL ALLOCATION |
---|
4411 | !Config Def = undef, 100., 100., 100., 100., 100., 100., 100., 100., undef, undef, undef, undef |
---|
4412 | !Config Help = |
---|
4413 | !Config Units = [-] |
---|
4414 | CALL getin_p('DEATH_DF',death_distribution_factor) |
---|
4415 | |
---|
4416 | !Config Key = NPP_RESET_VALUE |
---|
4417 | !Config Desc = The value longterm NPP is reset to after a non-tree stand dies. |
---|
4418 | !Config if = OK_STOMATE, FUNCTIONAL ALLOCATION |
---|
4419 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 500., 500., 500., 500. |
---|
4420 | !Config Help = |
---|
4421 | !Config Units = [-] CALL getin_p('NPP_RESET_VALUE',npp_reset_value) |
---|
4422 | |
---|
4423 | |
---|
4424 | ! Fire - stomate |
---|
4425 | ! |
---|
4426 | |
---|
4427 | !Config Key = FLAM |
---|
4428 | !Config Desc = flamability: critical fraction of water holding capacity |
---|
4429 | !Config if = OK_STOMATE |
---|
4430 | !Config Def = undef, .15, .25, .25, .25, .25, .25, .25, .25, .25, .25, .35, .35 |
---|
4431 | !Config Help = |
---|
4432 | !Config Units = [-] |
---|
4433 | CALL getin_p('FLAM',flam) |
---|
4434 | |
---|
4435 | !Config Key = RESIST |
---|
4436 | !Config Desc = fire resistance |
---|
4437 | !Config if = OK_STOMATE |
---|
4438 | !Config Def = undef, .95, .90, .12, .50, .12, .12, .12, .12, .0, .0, .0, .0 |
---|
4439 | !Config Help = |
---|
4440 | !Config Units = [-] |
---|
4441 | CALL getin_p('RESIST',resist) |
---|
4442 | |
---|
4443 | ! |
---|
4444 | ! Flux - LUC |
---|
4445 | ! |
---|
4446 | |
---|
4447 | !Config Key = COEFF_LCCHANGE_s |
---|
4448 | !Config Desc = Coeff of biomass export for the year |
---|
4449 | !Config if = OK_STOMATE |
---|
4450 | !Config Def = undef, 0.897, 0.897, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597 |
---|
4451 | !Config Help = |
---|
4452 | !Config Units = [-] |
---|
4453 | CALL getin_p('COEFF_LCCHANGE_s',coeff_lcchange_s) |
---|
4454 | |
---|
4455 | !Config Key = COEFF_LCCHANGE_m |
---|
4456 | !Config Desc = Coeff of biomass export for the decade |
---|
4457 | !Config if = OK_STOMATE |
---|
4458 | !Config Def = undef, 0.103, 0.103, 0.299, 0.299, 0.299, 0.299, 0.299, 0.299, 0.299, 0.403, 0.299, 0.403 |
---|
4459 | !Config Help = |
---|
4460 | !Config Units = [-] |
---|
4461 | CALL getin_p('COEFF_LCCHANGE_m',coeff_lcchange_m) |
---|
4462 | |
---|
4463 | !Config Key = COEFF_LCCHANGE_l |
---|
4464 | !Config Desc = Coeff of biomass export for the century |
---|
4465 | !Config if = OK_STOMATE |
---|
4466 | !Config Def = undef, 0., 0., 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0., 0.104, 0. |
---|
4467 | !Config Help = |
---|
4468 | !Config Units = [-] |
---|
4469 | CALL getin_p('COEFF_LCCHANGE_l',coeff_lcchange_l) |
---|
4470 | |
---|
4471 | ! |
---|
4472 | ! Phenology |
---|
4473 | ! |
---|
4474 | |
---|
4475 | !Config Key = LAI_MAX |
---|
4476 | !Config Desc = maximum LAI, PFT-specific |
---|
4477 | !Config if = OK_STOMATE |
---|
4478 | !Config Def = undef, 7., 7., 5., 5., 5., 4.5, 4.5, 3.0, 2.5, 2.5, 5.,5. |
---|
4479 | !Config Help = |
---|
4480 | !Config Units = [m^2/m^2] |
---|
4481 | CALL getin_p('LAI_MAX',lai_max) |
---|
4482 | |
---|
4483 | !Config Key = PHENO_TYPE |
---|
4484 | !Config Desc = type of phenology, 0=bare ground 1=evergreen, 2=summergreen, 3=raingreen, 4=perennial |
---|
4485 | !Config if = OK_STOMATE |
---|
4486 | !Config Def = 0, 1, 3, 1, 1, 2, 1, 2, 2, 4, 4, 2, 3 |
---|
4487 | !Config Help = |
---|
4488 | !Config Units = [-] |
---|
4489 | CALL getin_p('PHENO_TYPE',pheno_type) |
---|
4490 | |
---|
4491 | ! |
---|
4492 | ! Phenology : Leaf Onset |
---|
4493 | ! |
---|
4494 | |
---|
4495 | !Config Key = PHENO_GDD_CRIT_C |
---|
4496 | !Config Desc = critical gdd, tabulated (C), constant c of aT^2+bT+c |
---|
4497 | !Config if = OK_STOMATE |
---|
4498 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 270., 400., 125., 400. |
---|
4499 | !Config Help = |
---|
4500 | !Config Units = [-] |
---|
4501 | CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c) |
---|
4502 | |
---|
4503 | !Config Key = PHENO_GDD_CRIT_B |
---|
4504 | !Config Desc = critical gdd, tabulated (C), constant b of aT^2+bT+c |
---|
4505 | !Config if = OK_STOMATE |
---|
4506 | !Config Def = undef, undef, undef, undef, undef, undef, undef,undef, undef, 6.25, 0., 0., 0. |
---|
4507 | !Config Help = |
---|
4508 | !Config Units = [-] |
---|
4509 | CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b) |
---|
4510 | |
---|
4511 | !Config Key = PHENO_GDD_CRIT_A |
---|
4512 | !Config Desc = critical gdd, tabulated (C), constant a of aT^2+bT+c |
---|
4513 | !Config if = OK_STOMATE |
---|
4514 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.03125, 0., 0., 0. |
---|
4515 | !Config Help = |
---|
4516 | !Config Units = [-] |
---|
4517 | CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a) |
---|
4518 | |
---|
4519 | !Config Key = NGD_CRIT |
---|
4520 | !Config Desc = critical ngd, tabulated. Threshold -5 degrees |
---|
4521 | !Config if = OK_STOMATE |
---|
4522 | !Config Def = undef, undef, undef, undef, undef, undef, undef, 0., undef, undef, undef, undef, undef |
---|
4523 | !Config Help = NGD : Number of Growing Days. |
---|
4524 | !Config Units = [days] |
---|
4525 | CALL getin_p('NGD_CRIT',ngd_crit) |
---|
4526 | |
---|
4527 | |
---|
4528 | !Config Key = OPTI_KPHENO_CRIT |
---|
4529 | !Config Desc = multiplicative factor to optimize gdd_crit |
---|
4530 | !Config if = OK_STOMATE |
---|
4531 | !Config Def = undef, undef, undef, undef, undef, 1.13, undef, 0.87, 1.08, 0.81, undef, undef, undef |
---|
4532 | !Config Help = |
---|
4533 | !Config Units = [-] |
---|
4534 | CALL getin_p('OPTI_KPHENO_CRIT',opti_kpheno_crit) |
---|
4535 | |
---|
4536 | |
---|
4537 | !Config Key = NCDGDD_TEMP |
---|
4538 | !Config Desc = critical temperature for the ncd vs. gdd function in phenology |
---|
4539 | !Config if = OK_STOMATE |
---|
4540 | !Config Def = undef, undef, undef, undef, undef, 5., undef, 0., undef, undef, undef, undef, undef |
---|
4541 | !Config Help = |
---|
4542 | !Config Units = [C] |
---|
4543 | CALL getin_p('NCDGDD_TEMP',ncdgdd_temp) |
---|
4544 | |
---|
4545 | !Config Key = HUM_FRAC |
---|
4546 | !Config Desc = critical humidity (relative to min/max) for phenology |
---|
4547 | !Config if = OK_STOMATE |
---|
4548 | !Config Def = undef, undef, .5, undef, undef, undef, undef, undef, undef, .5, .5, .5,.5 |
---|
4549 | !Config Help = |
---|
4550 | !Config Units = [%] |
---|
4551 | CALL getin_p('HUM_FRAC',hum_frac) |
---|
4552 | |
---|
4553 | !Config Key = HUM_MIN_TIME |
---|
4554 | !Config Desc = minimum time elapsed since moisture minimum |
---|
4555 | !Config if = OK_STOMATE |
---|
4556 | !Config Def = undef, undef, 50., undef, undef, undef, undef, undef, undef, 35., 35., 75., 75. |
---|
4557 | !Config Help = |
---|
4558 | !Config Units = [days] |
---|
4559 | CALL getin_p('HUM_MIN_TIME',hum_min_time) |
---|
4560 | |
---|
4561 | !Config Key = TAU_SAP |
---|
4562 | !Config Desc = sapwood longivety (sapwood -> heartwood conversion time) |
---|
4563 | !Config if = OK_STOMATE |
---|
4564 | !Config Def = undef, 730., 730., 730., 730., 730., 730., 730., 730., undef, undef, undef, undef |
---|
4565 | !Config Help = |
---|
4566 | !Config Units = [days] |
---|
4567 | CALL getin_p('TAU_SAP',tau_sap) |
---|
4568 | |
---|
4569 | !Config Key = TAU_FRUIT |
---|
4570 | !Config Desc = fruit longivety |
---|
4571 | !Config if = OK_STOMATE |
---|
4572 | !Config Def = undef, 90., 90., 90., 90., 90., 90., 90., 90., undef, undef, undef, undef |
---|
4573 | !Config Help = |
---|
4574 | !Config Units = [days] |
---|
4575 | CALL getin_p('TAU_FRUIT',tau_fruit) |
---|
4576 | |
---|
4577 | !Config Key = TAU_ROOT |
---|
4578 | !Config Desc = root longivety |
---|
4579 | !Config if = OK_STOMATE |
---|
4580 | !Config Def = undef, 256., 256., 256., 256., 256., 256., 256., 256., 256., 256., 256., 256. |
---|
4581 | !Config Help = |
---|
4582 | !Config Units = [days] |
---|
4583 | CALL getin_p('TAU_ROOT',tau_root) |
---|
4584 | |
---|
4585 | !Config Key = TAU_LEAF |
---|
4586 | !Config Desc = leaf longivety |
---|
4587 | !Config if = OK_STOMATE |
---|
4588 | !Config Def = undef, 730., 180., 910., 730., 180., 910., 180., 180., 120., 120., 90., 90. |
---|
4589 | !Config Help = |
---|
4590 | !Config Units = [days] |
---|
4591 | CALL getin_p('TAU_LEAF',tau_leaf) |
---|
4592 | |
---|
4593 | !Config Key = ECUREUIL |
---|
4594 | !Config Desc = fraction of primary leaf and root allocation put into reserve |
---|
4595 | !Config if = OK_STOMATE |
---|
4596 | !Config Def = undef, .0, 1., .0, .0, 1., .0, 1., 1., 1., 1., 1., 1. |
---|
4597 | !Config Help = |
---|
4598 | !Config Units = [-] |
---|
4599 | CALL getin_p('ECUREUIL',ecureuil) |
---|
4600 | |
---|
4601 | !Config Key = ALLOC_MIN |
---|
4602 | !Config Desc = minimum allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
4603 | !Config if = OK_STOMATE |
---|
4604 | !Config Def = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef |
---|
4605 | !Config Help = |
---|
4606 | !Config Units = [-] |
---|
4607 | CALL getin_p('ALLOC_MIN',alloc_min) |
---|
4608 | |
---|
4609 | !Config Key = ALLOC_MAX |
---|
4610 | !Config Desc = maximum allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
4611 | !Config if = OK_STOMATE |
---|
4612 | !Config Def = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef |
---|
4613 | !Config Help = |
---|
4614 | !Config Units = [-] |
---|
4615 | CALL getin_p('ALLOC_MAX',alloc_max) |
---|
4616 | |
---|
4617 | !Config Key = DEMI_ALLOC |
---|
4618 | !Config Desc = mean allocation above/below = f(age) - 30/01/04 NV/JO/PF |
---|
4619 | !Config if = OK_STOMATE |
---|
4620 | !Config Def = undef, 5., 5., 5., 5., 5., 5., 5., 5., undef, undef, undef, undef |
---|
4621 | !Config Help = |
---|
4622 | !Config Units = [-] |
---|
4623 | CALL getin_p('DEMI_ALLOC',demi_alloc) |
---|
4624 | |
---|
4625 | ! |
---|
4626 | ! Phenology : Senescence |
---|
4627 | ! |
---|
4628 | ! |
---|
4629 | !Config Key = LEAFFALL |
---|
4630 | !Config Desc = length of death of leaves, tabulated |
---|
4631 | !Config if = OK_STOMATE |
---|
4632 | !Config Def = undef, undef, 10., undef, undef, 10., undef, 10., 10., 10., 10., 10., 10. |
---|
4633 | !Config Help = |
---|
4634 | !Config Units = [days] |
---|
4635 | CALL getin_p('LEAFFALL',leaffall) |
---|
4636 | |
---|
4637 | !Config Key = SENESCENCE_TYPE |
---|
4638 | !Config Desc = type of senescence, tabulated |
---|
4639 | !Config if = OK_STOMATE |
---|
4640 | !Config Def = none, none, dry, none, none, cold, none, cold, cold, mixed, mixed, mixed, mixed |
---|
4641 | !Config Help = |
---|
4642 | !Config Units = [-] |
---|
4643 | CALL getin_p('SENESCENCE_TYPE',senescence_type) |
---|
4644 | |
---|
4645 | !Config Key = SENESCENCE_HUM |
---|
4646 | !Config Desc = critical relative moisture availability for senescence |
---|
4647 | !Config if = OK_STOMATE |
---|
4648 | !Config Def = undef, undef, .3, undef, undef, undef, undef, undef, undef, .2, .2, .3, .2 |
---|
4649 | !Config Help = |
---|
4650 | !Config Units = [-] |
---|
4651 | CALL getin_p('SENESCENCE_HUM',senescence_hum) |
---|
4652 | |
---|
4653 | !Config Key = NOSENESCENCE_HUM |
---|
4654 | !Config Desc = relative moisture availability above which there is no humidity-related senescence |
---|
4655 | !Config if = OK_STOMATE |
---|
4656 | !Config Def = undef, undef, .8, undef, undef, undef, undef, undef, undef, .3, .3, .3, .3 |
---|
4657 | !Config Help = |
---|
4658 | !Config Units = [-] |
---|
4659 | CALL getin_p('NOSENESCENCE_HUM',nosenescence_hum) |
---|
4660 | |
---|
4661 | !Config Key = MAX_TURNOVER_TIME |
---|
4662 | !Config Desc = maximum turnover time for grasse |
---|
4663 | !Config if = OK_STOMATE |
---|
4664 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 80., 80., 80., 80. |
---|
4665 | !Config Help = |
---|
4666 | !Config Units = [days] |
---|
4667 | CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time) |
---|
4668 | |
---|
4669 | !Config Key = MIN_TURNOVER_TIME |
---|
4670 | !Config Desc = minimum turnover time for grasse |
---|
4671 | !Config if = OK_STOMATE |
---|
4672 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, 10., 10., 10., 10. |
---|
4673 | !Config Help = |
---|
4674 | !Config Units = [days] |
---|
4675 | CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time) |
---|
4676 | |
---|
4677 | !Config Key = MIN_LEAF_AGE_FOR_SENESCENCE |
---|
4678 | !Config Desc = minimum leaf age to allow senescence g |
---|
4679 | !Config if = OK_STOMATE |
---|
4680 | !Config Def = undef, undef, 90., undef, undef, 90., undef, 60., 60., 30., 30., 30., 30. |
---|
4681 | !Config Help = |
---|
4682 | !Config Units = [days] |
---|
4683 | CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE',min_leaf_age_for_senescence) |
---|
4684 | |
---|
4685 | !Config Key = SENESCENCE_TEMP_C |
---|
4686 | !Config Desc = critical temperature for senescence (C), constant c of aT^2+bT+c, tabulated |
---|
4687 | !Config if = OK_STOMATE |
---|
4688 | !Config Def = undef, undef, undef, undef, undef, 12., undef, 7., 2., -1.375, 5., 5., 10. |
---|
4689 | !Config Help = Offset the quadratic relationship that determines the threshold temperature |
---|
4690 | !Config below which senescence occurs |
---|
4691 | !Config Units = [-] |
---|
4692 | CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c) |
---|
4693 | |
---|
4694 | !Config Key = SENESCENCE_TEMP_B |
---|
4695 | !Config Desc = critical temperature for senescence (C), constant b of aT^2+bT+c ,tabulated |
---|
4696 | !Config if = OK_STOMATE |
---|
4697 | !Config Def = undef, undef, undef, undef, undef, 0., undef, 0., 0., .1, 0., 0., 0. |
---|
4698 | !Config Help = |
---|
4699 | !Config Units = [-] |
---|
4700 | CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b) |
---|
4701 | |
---|
4702 | !Config Key = SENESCENCE_TEMP_A |
---|
4703 | !Config Desc = critical temperature for senescence (C), constant a of aT^2+bT+c , tabulated |
---|
4704 | !Config if = OK_STOMATE |
---|
4705 | !Config Def = undef, undef, undef, undef, undef, 0., undef, 0., 0.,.00375, 0., 0., 0. |
---|
4706 | !Config Help = |
---|
4707 | !Config Units = [-] |
---|
4708 | CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a) |
---|
4709 | |
---|
4710 | !Config Key = GDD_SENESCENCE |
---|
4711 | !Config Desc = minimum gdd to allow senescence of crops |
---|
4712 | !Config if = OK_STOMATE |
---|
4713 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 950., 4000. |
---|
4714 | !Config Help = |
---|
4715 | !Config Units = [days] |
---|
4716 | CALL getin_p("GDD_SENESCENCE", gdd_senescence) |
---|
4717 | |
---|
4718 | |
---|
4719 | ! |
---|
4720 | ! CROPLAND MANAGEMENT |
---|
4721 | ! |
---|
4722 | !Config Key = HARVEST_RATIO |
---|
4723 | !Config Desc = Share of biomass that is harvested. This residual = 1 - harvest_ratio |
---|
4724 | !Config if = OK_STOMATE |
---|
4725 | !Config Def = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.5, 0.5 |
---|
4726 | !Config Help = |
---|
4727 | !Config Units = [unitless] |
---|
4728 | CALL getin_p("HARVEST_RATIO", harvest_ratio) |
---|
4729 | |
---|
4730 | ! |
---|
4731 | ! DGVM |
---|
4732 | ! |
---|
4733 | |
---|
4734 | !Config Key = RESIDENCE_TIME |
---|
4735 | !Config Desc = residence time of trees |
---|
4736 | !Config if = OK_DGVM and NOT(LPJ_GAP_CONST_MORT) |
---|
4737 | !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 |
---|
4738 | !Config Help = |
---|
4739 | !Config Units = [years] |
---|
4740 | CALL getin_p('RESIDENCE_TIME',residence_time) |
---|
4741 | |
---|
4742 | |
---|
4743 | ! added by yitong yao 07 Jan 2020 08:26 |
---|
4744 | !Config Key = PLC_KILL_FRAC |
---|
4745 | !Config Desc = fraction of killed trees due to plc >50 |
---|
4746 | !Config if |
---|
4747 | !Config Def = undef, 0.01,0.01,0.01,0.01,0.01,0.01,0.01,... |
---|
4748 | !Config Help = |
---|
4749 | !Config Units =[years] |
---|
4750 | CALL getin_p('PLC_KILL_FRAC',plc_kill_frac) |
---|
4751 | |
---|
4752 | ! added by yitong yao 07 Jan 2020 08:27 |
---|
4753 | CALL getin_p('MOR_KILL_FRAC',mor_kill_frac) |
---|
4754 | |
---|
4755 | |
---|
4756 | !Config Key = TMIN_CRIT |
---|
4757 | !Config Desc = critical tmin, tabulated |
---|
4758 | !Config if = OK_STOMATE |
---|
4759 | !Config Def = undef, 0.0, 0.0, -30.0, -14.0, -30.0, -45.0, -45.0, undef, undef, undef, undef, undef |
---|
4760 | !Config Help = |
---|
4761 | !Config Units = [C] |
---|
4762 | CALL getin_p('TMIN_CRIT',tmin_crit) |
---|
4763 | |
---|
4764 | !Config Key = TCM_CRIT |
---|
4765 | !Config Desc = critical tcm, tabulated |
---|
4766 | !Config if = OK_STOMATE |
---|
4767 | !Config Def = undef, undef, undef, 5.0, 15.5, 15.5, -8.0, -8.0, -8.0, undef, undef, undef, undef |
---|
4768 | !Config Help = |
---|
4769 | !Config Units = [C] |
---|
4770 | CALL getin_p('TCM_CRIT',tcm_crit) |
---|
4771 | |
---|
4772 | !Config Key = MORTALITY_MIN |
---|
4773 | !Config Desc = Asymptotic mortality |
---|
4774 | !Config if = OK_STOMATE, functional allocation, lpj_const_mort |
---|
4775 | !Config Def = undef, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01 |
---|
4776 | !Config Help = |
---|
4777 | !Config Units = [year-1] |
---|
4778 | CALL getin_p('MORTALITY_MIN',mortality_min) |
---|
4779 | |
---|
4780 | !Config Key = MORTALITY_MAX |
---|
4781 | !Config Desc = Maximum mortality, tabulated |
---|
4782 | !Config if = OK_STOMATE, functional allocation + lpj_const_mort |
---|
4783 | !Config Def = undef, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1 |
---|
4784 | !Config Help = |
---|
4785 | !Config Units = [year-1] |
---|
4786 | CALL getin_p('MORTALITY_MIN',mortality_min) |
---|
4787 | |
---|
4788 | !Config Key = REF_MORTALITY |
---|
4789 | !Config Desc = Reference mortality, tabulated |
---|
4790 | !Config if = OK_STOMATE, functional allocation + lpj_const_mort |
---|
4791 | !Config Def = undef, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035, 0.035 |
---|
4792 | !Config Help = |
---|
4793 | !Config Units = [year-1] |
---|
4794 | CALL getin_p('REF_MORTALITY',ref_mortality) |
---|
4795 | |
---|
4796 | !Config Key = TAU_HUM_GROWINGSEASON |
---|
4797 | !Config Desc = time integral for waterstress on KF (allocation) |
---|
4798 | !Config if = OK_STOMATE, functional allocation |
---|
4799 | !Config Def = undef, tau_sap, tau_sap, tau_sap, tau_sap, tau_sap, tau_sap, tau_sap, tau_sap, tau_hum_growingseason_grass, |
---|
4800 | ! tau_hum_growingseason_grass, tau_hum_growingseason_grass, tau_hum_growingseason_grass |
---|
4801 | !Config Help = |
---|
4802 | !Config Units = [days] |
---|
4803 | CALL getin_p('TAU_HUM_GROWINGSEASON',tau_hum_growingseason) |
---|
4804 | |
---|
4805 | !Config Key = DENS_TARGET |
---|
4806 | !Config Desc = |
---|
4807 | !Config if = OK_STOMATE, functional allocation |
---|
4808 | !Config Def = 0.0, 100.0, 100.0, 200.0, 100.0, 100.0, 200.0, 100.0, 200.0, 0.0, 0.0, 0.0, 0.0 |
---|
4809 | !Config Help = |
---|
4810 | !Config Units = |
---|
4811 | CALL getin_p("DENS_TARGET",dens_target) |
---|
4812 | |
---|
4813 | ! Age classes |
---|
4814 | ! I want to create a temporary array that indicates which "real" PFT starts |
---|
4815 | ! on which index. This could probably be put somewhere else, but this |
---|
4816 | ! routine is only called once a year and this loop is not expensive. |
---|
4817 | start_index(:)=-1 |
---|
4818 | nagec_pft(:)=-1 |
---|
4819 | DO ivma=1,nvmap |
---|
4820 | ! The start index is just the first place we find this real PFT. |
---|
4821 | DO ivm=1,nvm |
---|
4822 | IF(agec_group(ivm) .EQ. ivma)THEN |
---|
4823 | start_index(ivma)=ivm |
---|
4824 | ! It is possible that not all forests will have multiple age classes. For example, |
---|
4825 | ! the species might have age classes but metaclasses (running outside Europe) might not. |
---|
4826 | ! Let's check to see how many age classes each PFT has. Right now, the only options |
---|
4827 | ! are 1 or nagec, but this could be changed without too much difficulty. |
---|
4828 | WRITE(numout,*) 'jifoez ',nagec,ivm,ivm+nagec-1 |
---|
4829 | IF((ivm+nagec-1) .LT. nvm)THEN |
---|
4830 | ! This first if loop prevents an out of bounds error |
---|
4831 | IF(agec_group(ivm+nagec-1) == ivma)THEN |
---|
4832 | nagec_pft(ivma)=nagec |
---|
4833 | ELSE |
---|
4834 | nagec_pft(ivma)=1 |
---|
4835 | ENDIF |
---|
4836 | ELSE |
---|
4837 | nagec_pft(ivma)=1 |
---|
4838 | ENDIF |
---|
4839 | EXIT |
---|
4840 | ENDIF |
---|
4841 | ENDDO |
---|
4842 | ENDDO |
---|
4843 | ! Check to see if the calculation worked and we found indices for all of them. |
---|
4844 | DO ivma=1,nvmap |
---|
4845 | IF(start_index(ivma) .LT. 0)THEN |
---|
4846 | WRITE(numout,*) 'Could not find a start index for one age class group!' |
---|
4847 | WRITE(numout,*) 'Check the input file to make sure the following ivma appears in agec_group' |
---|
4848 | WRITE(numout,*) 'ivma,nvmap',ivma,nvmap |
---|
4849 | WRITE(numout,*) 'agec_group',agec_group(:) |
---|
4850 | CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') |
---|
4851 | ENDIF |
---|
4852 | ENDDO |
---|
4853 | |
---|
4854 | first_call = .FALSE. |
---|
4855 | |
---|
4856 | ENDIF !(first_call) |
---|
4857 | |
---|
4858 | END SUBROUTINE config_stomate_pft_parameters |
---|
4859 | ! |
---|
4860 | != |
---|
4861 | ! |
---|
4862 | !! ================================================================================================================================ |
---|
4863 | !! SUBROUTINE : config_forest_management_parameters |
---|
4864 | !! |
---|
4865 | !>\BRIEF This subroutine will read the imposed values for the forest management |
---|
4866 | !! parameters. It is not called if IMPOSE_PARAM is set to NO. |
---|
4867 | !! |
---|
4868 | !! DESCRIPTION : None |
---|
4869 | !! |
---|
4870 | !! RECENT CHANGE(S): None |
---|
4871 | !! |
---|
4872 | !! MAIN OUTPUT VARIABLE(S): None |
---|
4873 | !! |
---|
4874 | !! REFERENCE(S) : None |
---|
4875 | !! |
---|
4876 | !! FLOWCHART : None |
---|
4877 | !! \n |
---|
4878 | !_ ================================================================================================================================ |
---|
4879 | |
---|
4880 | SUBROUTINE config_forest_manage_pft_parameters |
---|
4881 | |
---|
4882 | IMPLICIT NONE |
---|
4883 | |
---|
4884 | !! 0. Variables and parameters declaration |
---|
4885 | |
---|
4886 | !! 0.4 Local variable |
---|
4887 | |
---|
4888 | LOGICAL, SAVE :: first_call = .TRUE. !! To keep first call trace (true/false) |
---|
4889 | !$OMP THREADPRIVATE(first_call) |
---|
4890 | REAL(r_std) :: ss_dens_init !! Sensitivity parameter for dens_init |
---|
4891 | REAL(r_std) :: ss_branch_ratio !! Sensitivity parameter for branch_ratio |
---|
4892 | |
---|
4893 | !_ ================================================================================================================================ |
---|
4894 | |
---|
4895 | !Config Key = PLANTATION |
---|
4896 | !Config Desc = |
---|
4897 | !Config if = FOREST_MANAGEMENT |
---|
4898 | !Config Def = n, n, n, n, n, n, n, n, n, n, n, n, n |
---|
4899 | !Config Help = |
---|
4900 | !Config Units = |
---|
4901 | CALL getin_p("PLANTATION",plantation) |
---|
4902 | |
---|
4903 | !Config Key = FM_ALLO_A |
---|
4904 | !Config Desc = |
---|
4905 | !Config if = FOREST_MANAGEMENT |
---|
4906 | !Config Def = undef, 19.42, 19.42, 9.3, 19.42, 19.42, 9.3, 0.11, 0.35, undef, undef, undef, undef |
---|
4907 | !Config Help = |
---|
4908 | !Config Units = |
---|
4909 | CALL getin_p("FM_ALLO_A",fm_allo_a) |
---|
4910 | |
---|
4911 | !Config Key = FM_ALLO_C |
---|
4912 | !Config Desc = |
---|
4913 | !Config if = FOREST_MANAGEMENT |
---|
4914 | !Config Def = undef, 0.11, 0.11, 0.35, 0.11, 0.11, 0.35, 0.11, 0.35, undef, undef, undef, undef |
---|
4915 | !Config Help = |
---|
4916 | !Config Units = |
---|
4917 | CALL getin_p("FM_ALLO_C",fm_allo_c) |
---|
4918 | |
---|
4919 | !Config Key = FM_ALLO_D |
---|
4920 | !Config Desc = |
---|
4921 | !Config if = FOREST_MANAGEMENT |
---|
4922 | !Config Def = undef, 0.13, 0.13, 0.3, 0.13, 0.13, 0.3, 0.13, 0.3, undef, undef, undef, undef |
---|
4923 | !Config Help = |
---|
4924 | !Config Units = |
---|
4925 | CALL getin_p("FM_ALLO_D",fm_allo_d) |
---|
4926 | |
---|
4927 | !Config Key = FM_ALLO_P |
---|
4928 | !Config Desc = |
---|
4929 | !Config if = FOREST_MANAGEMENT |
---|
4930 | !Config Def = undef, 0.75, 0.75, 0.69, 0.75, 0.75, 0.69, 0.75, 0.69, undef, undef, undef, undef |
---|
4931 | !Config Help = |
---|
4932 | !Config Units = |
---|
4933 | CALL getin_p("FM_ALLO_P",fm_allo_p) |
---|
4934 | |
---|
4935 | !Config Key = FM_ALLO_Q |
---|
4936 | !Config Desc = |
---|
4937 | !Config if = FOREST_MANAGEMENT |
---|
4938 | !Config Def = undef, -0.12, -0.12, -0.32, -0.12, -0.12, -0.32, -0.12, -0.32, undef, undef, undef, undef |
---|
4939 | !Config Help = |
---|
4940 | !Config Units = |
---|
4941 | CALL getin_p("FM_ALLO_Q",fm_allo_q) |
---|
4942 | |
---|
4943 | !Config Key = ALLO_CROWN_A0 |
---|
4944 | !Config Desc = |
---|
4945 | !Config if = FOREST_MANAGEMENT |
---|
4946 | !Config Def = undef, -0.7602, -0.7602, -1.019, -0.7602, -0.7602, -1.019, -0.7602, -1.019, undef, undef, undef, undef |
---|
4947 | !Config Help = |
---|
4948 | !Config Units = |
---|
4949 | CALL getin_p("ALLO_CROWN_A0",allo_crown_a0) |
---|
4950 | |
---|
4951 | !Config Key = ALLO_CROWN_A1 |
---|
4952 | !Config Desc = |
---|
4953 | !Config if = FOREST_MANAGEMENT |
---|
4954 | !Config Def = undef, 0.6672, 0.6672, 0.887, 0.6672, 0.6672, 0.887, 0.6672, 0.887, undef, undef, undef, undef |
---|
4955 | !Config Help = |
---|
4956 | !Config Units = |
---|
4957 | CALL getin_p("ALLO_CROWN_A1",allo_crown_a1) |
---|
4958 | |
---|
4959 | !Config Key = ALLO_CROWN_A2 |
---|
4960 | !Config Desc = |
---|
4961 | !Config if = FOREST_MANAGEMENT |
---|
4962 | !Config Def = undef, 0.12646, 0.12646, 0.188, 0.12646, 0.12646, 0.188, 0.12646, 0.188, undef, undef, undef, undef |
---|
4963 | !Config Help = |
---|
4964 | !Config Units = |
---|
4965 | CALL getin_p("ALLO_CROWN_A2",allo_crown_a2) |
---|
4966 | |
---|
4967 | !Config Key = H_FIRST |
---|
4968 | !Config Desc = |
---|
4969 | !Config if = FOREST_MANAGEMENT |
---|
4970 | !Config Def = 0.0, 10.0, 10.0, 10.0, 10.0, 10.0, 10.0, 10.0, 10.0, 0.0, 0.0, 0.0, 0.0 |
---|
4971 | !Config Help = |
---|
4972 | !Config Units = |
---|
4973 | CALL getin_p("H_FIRST",h_first) |
---|
4974 | |
---|
4975 | !Config Key = RECRUITMENT_LIGHT_THRESHOLD |
---|
4976 | !Config Desc = |
---|
4977 | !Config if = |
---|
4978 | !Config Def = undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0 |
---|
4979 | !Config Help = |
---|
4980 | !Config Units = |
---|
4981 | CALL getin_p("RECRUITMENT_LIGHT_THRESHOLD",recruitment_light_threshold) |
---|
4982 | |
---|
4983 | !Config Key = DIA_RECR |
---|
4984 | !Config Desc = |
---|
4985 | !Config if = |
---|
4986 | !Config Def = undef, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, undef, undef, undef |
---|
4987 | !Config Help = |
---|
4988 | !Config Units = |
---|
4989 | CALL getin_p("DIA_RECR",dia_recr) |
---|
4990 | |
---|
4991 | !Config Key = HEI_RECR |
---|
4992 | !Config Desc = |
---|
4993 | !Config if = |
---|
4994 | !Config Def = undef, 1.8, 1.8, 1.8, 1.8, 1.8, 1.8, 1.8, 1.8, 1.8, undef, undef, undef |
---|
4995 | !Config Help = |
---|
4996 | !Config Units = |
---|
4997 | CALL getin_p("HEI_RECR",hei_recr) |
---|
4998 | |
---|
4999 | |
---|
5000 | ! Sensitivity analysis |
---|
5001 | ! |
---|
5002 | !Config Key = SS_DENS_INIT |
---|
5003 | !Config Desc = |
---|
5004 | !Config if = FOREST_MANAGEMENT |
---|
5005 | !Config Def = 1. |
---|
5006 | !Config Help = |
---|
5007 | !Config Units = |
---|
5008 | ss_dens_init = 1. |
---|
5009 | CALL getin_p("SS_DENS_INIT",ss_dens_init) |
---|
5010 | |
---|
5011 | !! Readjust nmaxtrees values according ss_dens_init value |
---|
5012 | IF (nmaxtrees(1) >= 10) THEN |
---|
5013 | nmaxtrees(:) = nmaxtrees(1)*ss_dens_init |
---|
5014 | ENDIF |
---|
5015 | |
---|
5016 | !Config Key = LARGEST_TREE_DIA |
---|
5017 | !Config Desc = |
---|
5018 | !Config if = FOREST_MANAGEMENT |
---|
5019 | !Config Def = 0.0, 45.0, 45.0, 45.0, 45.0, 45.0, 45.0, 45.0, 45.0, 0.0, 0.0, 0.0, 0.0 |
---|
5020 | !Config Help = |
---|
5021 | !Config Units = |
---|
5022 | CALL getin_p("LARGEST_TREE_DIA",largest_tree_dia) |
---|
5023 | |
---|
5024 | !Config Key = THINSTRAT |
---|
5025 | !Config Desc = |
---|
5026 | !Config if = FOREST_MANAGEMENT |
---|
5027 | !Config Def = 0.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 0.0, 0.0, 0.0, 0.0 |
---|
5028 | !Config Help = |
---|
5029 | !Config Units = |
---|
5030 | CALL getin_p("THINSTRAT",thinstrat) |
---|
5031 | |
---|
5032 | !Config Key = TAUMIN |
---|
5033 | !Config Desc = |
---|
5034 | !Config if = FOREST_MANAGEMENT |
---|
5035 | !Config Def = 0.0, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.0, 0.0, 0.0, 0.0 |
---|
5036 | !Config Help = |
---|
5037 | !Config Units = |
---|
5038 | CALL getin_p("TAUMIN",taumin) |
---|
5039 | |
---|
5040 | !Config Key = TAUMAX |
---|
5041 | !Config Desc = |
---|
5042 | !Config if = FOREST_MANAGEMENT |
---|
5043 | !Config Def = 0.0, 0.05, 0.05, 0.05, 0.05, 0.05, 0.05, 0.05, 0.05, 0.0, 0.0, 0.0, 0.0 |
---|
5044 | !Config Help = |
---|
5045 | !Config Units = |
---|
5046 | CALL getin_p("TAUMAX",taumax) |
---|
5047 | |
---|
5048 | !Config Key = ALPHA_RDI_UPPER |
---|
5049 | !Config Desc = |
---|
5050 | !Config if = FOREST_MANAGEMENT |
---|
5051 | !Config Def = undef, 3000, 3000, 592, 862, 504, 1287, 984, 589, undef, undef, undef, undef |
---|
5052 | !Config Help = |
---|
5053 | !Config Units = |
---|
5054 | CALL getin_p("ALPHA_RDI_UPPER",alpha_rdi_upper) |
---|
5055 | |
---|
5056 | !Config Key = BETA_RDI_UPPER |
---|
5057 | !Config Desc = |
---|
5058 | !Config if = FOREST_MANAGEMENT |
---|
5059 | !Config Def = undef, -0.57, -0.57, -0.46, -0.51, -0.44, -0.59, -0.57, -0.48, undef, undef, undef, undef |
---|
5060 | !Config Help = |
---|
5061 | !Config Units = |
---|
5062 | CALL getin_p("BETA_RDI_UPPER",beta_rdi_upper) |
---|
5063 | |
---|
5064 | !Config Key = ALPHA_RDI_LOWER |
---|
5065 | !Config Desc = |
---|
5066 | !Config if = FOREST_MANAGEMENT |
---|
5067 | !Config Def = undef, 2999, 2999, 433, 445, 369, 1022, 828, 385, undef, undef, undef, undef |
---|
5068 | !Config Help = |
---|
5069 | !Config Units = |
---|
5070 | CALL getin_p("ALPHA_RDI_LOWER",alpha_rdi_lower) |
---|
5071 | |
---|
5072 | !Config Key = BETA_RDI_LOWER |
---|
5073 | !Config Desc = |
---|
5074 | !Config if = FOREST_MANAGEMENT |
---|
5075 | !Config Def = undef, -0.57, -0.57, -0.46, -0.51, -0.44, -0.59, -0.57, -0.48, undef, undef, undef, undef |
---|
5076 | !Config Help = |
---|
5077 | !Config Units = |
---|
5078 | CALL getin_p("BETA_RDI_LOWER",beta_rdi_lower) |
---|
5079 | |
---|
5080 | !Config Key = BRANCH_RATIO |
---|
5081 | !Config Desc = |
---|
5082 | !Config if = FOREST_MANAGEMENT |
---|
5083 | !Config Def = 0.0, 0.38, 0.38, 0.25, 0.38, 0.38, 0.25, 0.38, 0.25, 0.0, 0.0, 0.0, 0.0 |
---|
5084 | !Config Help = |
---|
5085 | !Config Units = |
---|
5086 | CALL getin_p("BRANCH_RATIO",branch_ratio) |
---|
5087 | |
---|
5088 | !Config Key = BRANCH_HARVEST |
---|
5089 | !Config Desc = The fraction of branches which are harvested during FM2 (the rest are left onsite) |
---|
5090 | !Config if = FOREST_MANAGEMENT |
---|
5091 | !Config Def = 0.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 0.0, 0.0, 0.0, 0.0 |
---|
5092 | !Config Help = |
---|
5093 | !Config Units = |
---|
5094 | CALL getin_p("BRANCH_HARVEST",branch_harvest) |
---|
5095 | |
---|
5096 | ! Sensitivity parameter |
---|
5097 | ! |
---|
5098 | !Config Key = SS_BRANCH_RATIO |
---|
5099 | !Config Desc = |
---|
5100 | !Config if = FOREST_MANAGEMENT |
---|
5101 | !Config Def = |
---|
5102 | !Config Help = |
---|
5103 | !Config Units = |
---|
5104 | ss_branch_ratio = 1. |
---|
5105 | CALL getin_p("SS_BRANCH_RATIO",ss_branch_ratio) |
---|
5106 | |
---|
5107 | !! Readjust branch_ratio values |
---|
5108 | branch_ratio(:) = ss_branch_ratio * branch_ratio(:) |
---|
5109 | |
---|
5110 | !Config Key = DECL_FACTOR |
---|
5111 | !Config Desc = |
---|
5112 | !Config if = FOREST_MANAGEMENT |
---|
5113 | !Config Def = 0.0, 0.0005, 0.0005, 0.0007, 0.0005, 0.0005, 0.0009, 0.00075, 0.0005, 1.0, 1.0, 1.0, 1.0 |
---|
5114 | !Config Help = |
---|
5115 | !Config Units = |
---|
5116 | CALL getin_p("DECL_FACTOR",decl_factor) |
---|
5117 | |
---|
5118 | !Config Key = OPT_FACTOR |
---|
5119 | !Config Desc = |
---|
5120 | !Config if = FOREST_MANAGEMENT |
---|
5121 | !Config Def = 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0 |
---|
5122 | !Config Help = |
---|
5123 | !Config Units = |
---|
5124 | !CALL getin_p("OPT_FACTOR",opt_factor) |
---|
5125 | |
---|
5126 | !Config Key = COPPICE_DIAMETER |
---|
5127 | !Config Desc = |
---|
5128 | !Config if = FOREST_MANAGEMENT |
---|
5129 | !Config Def = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef |
---|
5130 | !Config Help = |
---|
5131 | !Config Units = |
---|
5132 | CALL getin_p("COPPICE_DIAMETER",coppice_diameter) |
---|
5133 | |
---|
5134 | !Config Key = SHOOTS_PER_STOOL |
---|
5135 | !Config Desc = |
---|
5136 | !Config if = FOREST_MANAGEMENT |
---|
5137 | !Config Def = undef, 6, 6, 6, 6, 6, 6, 6, 6, undef, undef, undef, undef |
---|
5138 | !Config Help = |
---|
5139 | !Config Units = |
---|
5140 | CALL getin_p("SHOOTS_PER_STOOL",shoots_per_stool) |
---|
5141 | |
---|
5142 | !Config Key = SRC_ROT_LENGTH |
---|
5143 | !Config Desc = |
---|
5144 | !Config if = FOREST_MANAGEMENT |
---|
5145 | !Config Def = undef, 3, 3, 3, 3, 3, 3, 3, 3, undef, undef, undef, undef |
---|
5146 | !Config Help = |
---|
5147 | !Config Units = |
---|
5148 | CALL getin_p("SRC_ROT_LENGTH",src_rot_length) |
---|
5149 | |
---|
5150 | !Config Key = SRC_NROTS |
---|
5151 | !Config Desc = |
---|
5152 | !Config if = FOREST_MANAGEMENT |
---|
5153 | !Config Def = undef, 10, 10, 10, 10, 10, 10, 10, 10, undef, undef, undef, undef |
---|
5154 | !Config Help = |
---|
5155 | !Config Units = |
---|
5156 | CALL getin_p("SRC_NROTS",src_nrots) |
---|
5157 | |
---|
5158 | !Config Key = M_DV |
---|
5159 | !Config Desc = |
---|
5160 | !Config if = FOREST_MANAGEMENT |
---|
5161 | !Config Def = undef, 1.05, 1.05, 1.05, 1.05, 1.05, 1.05, 1.05, 1.05, 1.05, undef, undef, undef, undef |
---|
5162 | !Config Help = |
---|
5163 | !Config Units = |
---|
5164 | CALL getin_p("M_DV",m_dv) |
---|
5165 | |
---|
5166 | !Config Key = DELEUZE_A |
---|
5167 | !Config Desc = intercept of the intra-tree competition within a stand |
---|
5168 | ! based on the competion rule of Deleuze and Dhote 2004 |
---|
5169 | ! Used when n_circ > 6 |
---|
5170 | !Config if = OK_STOMATE, functional allocation |
---|
5171 | !Config Def = undef, 0.23, 0.23, 0.23, 0.23, 0.23, 0.23, 0.23, 0.23, 0.23, undef, undef, undef, undef |
---|
5172 | !Config Help = |
---|
5173 | !Config Units = |
---|
5174 | CALL getin_p("DELEUZE_A",deleuze_a) |
---|
5175 | |
---|
5176 | !Config Key = DELEUZE_B |
---|
5177 | !Config Desc = slope of the intra-tree competition within a stand |
---|
5178 | ! based on the competion rule of Deleuze and Dhote 2004 |
---|
5179 | ! Used when n_circ > 6 |
---|
5180 | !Config if = OK_STOMATE, functional allocation |
---|
5181 | !Config Def = undef, 0.58, 0.58, 0.58, 0.58, 0.58, 0.58, 0.58, 0.58, 0.58, undef, undef, undef, undef |
---|
5182 | !Config Help = |
---|
5183 | !Config Units = |
---|
5184 | CALL getin_p("DELEUZE_B",deleuze_b) |
---|
5185 | |
---|
5186 | !Config Key = DELEUZE_P_ALL |
---|
5187 | !Config Desc = Percentile of the circumferences that receives photosynthates |
---|
5188 | ! based on the competion rule of Deleuze and Dhote 2004 |
---|
5189 | ! Used when n_circ < 6 for FM 1, FM2 and FM4 |
---|
5190 | !Config if = OK_STOMATE, functional allocation |
---|
5191 | !Config Def = undef, 0.5, 0.5, 0.99, 0.99, 0.99, 0.99, 0.99, 0.99, 0.99, undef, undef, undef, undef |
---|
5192 | !Config Help = |
---|
5193 | !Config Units = |
---|
5194 | CALL getin_p("DELEUZE_P_ALL",deleuze_p_all) |
---|
5195 | |
---|
5196 | !Config Key = DELEUZE_P_COPPICE |
---|
5197 | !Config Desc = Percentile of the circumferences that receives photosynthates |
---|
5198 | ! based on the competion rule of Deleuze and Dhote 2004 |
---|
5199 | ! Used when n_circ < 6 for FM3 |
---|
5200 | !Config if = OK_STOMATE, functional allocation |
---|
5201 | !Config Def = undef, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, undef, undef, undef, undef |
---|
5202 | !Config Help = |
---|
5203 | !Config Units = |
---|
5204 | CALL getin_p("DELEUZE_P_COPPICE",deleuze_p_coppice) |
---|
5205 | |
---|
5206 | END SUBROUTINE config_forest_manage_pft_parameters |
---|
5207 | |
---|
5208 | !! ================================================================================================================================ |
---|
5209 | !! SUBROUTINE : pft_parameters_clear |
---|
5210 | !! |
---|
5211 | !>\BRIEF This subroutine deallocates memory at the end of the simulation. |
---|
5212 | !! |
---|
5213 | !! DESCRIPTION : None |
---|
5214 | !! |
---|
5215 | !! RECENT CHANGE(S): None |
---|
5216 | !! |
---|
5217 | !! MAIN OUTPUT VARIABLE(S): None |
---|
5218 | !! |
---|
5219 | !! REFERENCE(S) : None |
---|
5220 | !! |
---|
5221 | !! FLOWCHART : None |
---|
5222 | !! \n |
---|
5223 | !_ ================================================================================================================================ |
---|
5224 | |
---|
5225 | SUBROUTINE pft_parameters_clear |
---|
5226 | |
---|
5227 | l_first_pft_parameters = .TRUE. |
---|
5228 | |
---|
5229 | IF (ALLOCATED(pft_to_mtc)) DEALLOCATE(pft_to_mtc) |
---|
5230 | IF (ALLOCATED(PFT_name)) DEALLOCATE(PFT_name) |
---|
5231 | IF (ALLOCATED(veget_ori_fixed_test_1)) DEALLOCATE(veget_ori_fixed_test_1) |
---|
5232 | IF (ALLOCATED(llaimax)) DEALLOCATE(llaimax) |
---|
5233 | IF (ALLOCATED(llaimin)) DEALLOCATE(llaimin) |
---|
5234 | IF (ALLOCATED(height_presc)) DEALLOCATE(height_presc) |
---|
5235 | IF (ALLOCATED(type_of_lai)) DEALLOCATE(type_of_lai) |
---|
5236 | IF (ALLOCATED(is_tree)) DEALLOCATE(is_tree) |
---|
5237 | IF (ALLOCATED(natural)) DEALLOCATE(natural) |
---|
5238 | IF (ALLOCATED(is_deciduous)) DEALLOCATE(is_deciduous) |
---|
5239 | IF (ALLOCATED(is_tropical)) DEALLOCATE(is_tropical) |
---|
5240 | IF (ALLOCATED(is_temperate)) DEALLOCATE(is_temperate) |
---|
5241 | IF (ALLOCATED(is_boreal)) DEALLOCATE(is_boreal) |
---|
5242 | IF (ALLOCATED(is_evergreen)) DEALLOCATE(is_evergreen) |
---|
5243 | IF (ALLOCATED(is_needleleaf)) DEALLOCATE(is_needleleaf) |
---|
5244 | IF (ALLOCATED(is_tropical)) DEALLOCATE(is_tropical) |
---|
5245 | IF (ALLOCATED(humcste)) DEALLOCATE(humcste) |
---|
5246 | IF (ALLOCATED(pref_soil_veg)) DEALLOCATE(pref_soil_veg) |
---|
5247 | IF (ALLOCATED(agec_group)) DEALLOCATE(agec_group) |
---|
5248 | IF (ALLOCATED(start_index)) DEALLOCATE(start_index) |
---|
5249 | IF (ALLOCATED(nagec_pft)) DEALLOCATE(nagec_pft) |
---|
5250 | IF (ALLOCATED(is_c4)) DEALLOCATE(is_c4) |
---|
5251 | IF (ALLOCATED(vcmax_fix)) DEALLOCATE(vcmax_fix) |
---|
5252 | IF (ALLOCATED(E_KmC)) DEALLOCATE(E_KmC) |
---|
5253 | IF (ALLOCATED(E_KmO)) DEALLOCATE(E_KmO) |
---|
5254 | IF (ALLOCATED(E_gamma_star)) DEALLOCATE(E_gamma_star) |
---|
5255 | IF (ALLOCATED(E_Vcmax)) DEALLOCATE(E_Vcmax) |
---|
5256 | IF (ALLOCATED(E_Jmax)) DEALLOCATE(E_Jmax) |
---|
5257 | IF (ALLOCATED(aSV)) DEALLOCATE(aSV) |
---|
5258 | IF (ALLOCATED(bSV)) DEALLOCATE(bSV) |
---|
5259 | IF (ALLOCATED(tphoto_min)) DEALLOCATE(tphoto_min) |
---|
5260 | IF (ALLOCATED(tphoto_max)) DEALLOCATE(tphoto_max) |
---|
5261 | IF (ALLOCATED(aSJ)) DEALLOCATE(aSJ) |
---|
5262 | IF (ALLOCATED(bSJ)) DEALLOCATE(bSJ) |
---|
5263 | IF (ALLOCATED(D_Vcmax)) DEALLOCATE(D_Vcmax) |
---|
5264 | IF (ALLOCATED(D_Jmax)) DEALLOCATE(D_Jmax) |
---|
5265 | IF (ALLOCATED(E_Rd)) DEALLOCATE(E_Rd) |
---|
5266 | IF (ALLOCATED(Vcmax25)) DEALLOCATE(Vcmax25) |
---|
5267 | IF (ALLOCATED(arJV)) DEALLOCATE(arJV) |
---|
5268 | IF (ALLOCATED(brJV)) DEALLOCATE(brJV) |
---|
5269 | IF (ALLOCATED(KmC25)) DEALLOCATE(KmC25) |
---|
5270 | IF (ALLOCATED(KmO25)) DEALLOCATE(KmO25) |
---|
5271 | IF (ALLOCATED(gamma_star25)) DEALLOCATE(gamma_star25) |
---|
5272 | IF (ALLOCATED(a1)) DEALLOCATE(a1) |
---|
5273 | IF (ALLOCATED(b1)) DEALLOCATE(b1) |
---|
5274 | IF (ALLOCATED(g0)) DEALLOCATE(g0) |
---|
5275 | IF (ALLOCATED(h_protons)) DEALLOCATE(h_protons) |
---|
5276 | IF (ALLOCATED(fpsir)) DEALLOCATE(fpsir) |
---|
5277 | IF (ALLOCATED(fQ)) DEALLOCATE(fQ) |
---|
5278 | IF (ALLOCATED(fpseudo)) DEALLOCATE(fpseudo) |
---|
5279 | IF (ALLOCATED(kp)) DEALLOCATE(kp) |
---|
5280 | IF (ALLOCATED(alpha)) DEALLOCATE(alpha) |
---|
5281 | IF (ALLOCATED(gbs)) DEALLOCATE(gbs) |
---|
5282 | IF (ALLOCATED(theta)) DEALLOCATE(theta) |
---|
5283 | IF (ALLOCATED(alpha_LL)) DEALLOCATE(alpha_LL) |
---|
5284 | IF (ALLOCATED(downregulation_co2_coeff)) DEALLOCATE(downregulation_co2_coeff) |
---|
5285 | IF (ALLOCATED(ext_coeff)) DEALLOCATE(ext_coeff) |
---|
5286 | IF (ALLOCATED(rveg_pft)) DEALLOCATE(rveg_pft) |
---|
5287 | IF (ALLOCATED(rstruct_const)) DEALLOCATE(rstruct_const) |
---|
5288 | IF (ALLOCATED(kzero)) DEALLOCATE(kzero) |
---|
5289 | IF (ALLOCATED(wmax_veg)) DEALLOCATE(wmax_veg) |
---|
5290 | IF (ALLOCATED(throughfall_by_pft)) DEALLOCATE(throughfall_by_pft) |
---|
5291 | IF (ALLOCATED(snowa_aged)) DEALLOCATE(snowa_aged) |
---|
5292 | IF (ALLOCATED(snowa_dec)) DEALLOCATE(snowa_dec) |
---|
5293 | IF (ALLOCATED(alb_leaf_vis)) DEALLOCATE(alb_leaf_vis) |
---|
5294 | IF (ALLOCATED(alb_leaf_nir)) DEALLOCATE(alb_leaf_nir) |
---|
5295 | IF (ALLOCATED(leaf_ssa)) DEALLOCATE(leaf_ssa) |
---|
5296 | IF (ALLOCATED(leaf_psd)) DEALLOCATE(leaf_psd) |
---|
5297 | IF (ALLOCATED(bgd_reflectance)) DEALLOCATE(bgd_reflectance) |
---|
5298 | IF (ALLOCATED(leaf_to_shoot_clumping)) DEALLOCATE(leaf_to_shoot_clumping) |
---|
5299 | IF (ALLOCATED(tune_coupled)) DEALLOCATE (tune_coupled) |
---|
5300 | IF (ALLOCATED(lai_correction_factor)) DEALLOCATE(lai_correction_factor) |
---|
5301 | IF (ALLOCATED(min_level_sep)) DEALLOCATE(min_level_sep) |
---|
5302 | IF (ALLOCATED(lai_top)) DEALLOCATE(lai_top) |
---|
5303 | IF (ALLOCATED(em_factor_isoprene)) DEALLOCATE(em_factor_isoprene) |
---|
5304 | IF (ALLOCATED(em_factor_monoterpene)) DEALLOCATE(em_factor_monoterpene) |
---|
5305 | IF (ALLOCATED(em_factor_ORVOC)) DEALLOCATE(em_factor_ORVOC) |
---|
5306 | IF (ALLOCATED(em_factor_OVOC)) DEALLOCATE(em_factor_OVOC) |
---|
5307 | IF (ALLOCATED(em_factor_MBO)) DEALLOCATE(em_factor_MBO) |
---|
5308 | IF (ALLOCATED(em_factor_methanol)) DEALLOCATE(em_factor_methanol) |
---|
5309 | IF (ALLOCATED(em_factor_acetone)) DEALLOCATE(em_factor_acetone) |
---|
5310 | IF (ALLOCATED(em_factor_acetal)) DEALLOCATE(em_factor_acetal) |
---|
5311 | IF (ALLOCATED(em_factor_formal)) DEALLOCATE(em_factor_formal) |
---|
5312 | IF (ALLOCATED(em_factor_acetic)) DEALLOCATE(em_factor_acetic) |
---|
5313 | IF (ALLOCATED(em_factor_formic)) DEALLOCATE(em_factor_formic) |
---|
5314 | IF (ALLOCATED(em_factor_no_wet)) DEALLOCATE(em_factor_no_wet) |
---|
5315 | IF (ALLOCATED(em_factor_no_dry)) DEALLOCATE(em_factor_no_dry) |
---|
5316 | IF (ALLOCATED(Larch)) DEALLOCATE(Larch) |
---|
5317 | IF (ALLOCATED(leaf_tab)) DEALLOCATE(leaf_tab) |
---|
5318 | IF (ALLOCATED(sla)) DEALLOCATE(sla) |
---|
5319 | !!$ IF (ALLOCATED(tphoto_min_a)) DEALLOCATE(tphoto_min_a) |
---|
5320 | !!$ IF (ALLOCATED(tphoto_min_b)) DEALLOCATE(tphoto_min_b) |
---|
5321 | !!$ IF (ALLOCATED(tphoto_min_c)) DEALLOCATE(tphoto_min_c) |
---|
5322 | !!$ IF (ALLOCATED(tphoto_opt_a)) DEALLOCATE(tphoto_opt_a) |
---|
5323 | !!$ IF (ALLOCATED(tphoto_opt_b)) DEALLOCATE(tphoto_opt_b) |
---|
5324 | !!$ IF (ALLOCATED(tphoto_opt_c)) DEALLOCATE(tphoto_opt_c) |
---|
5325 | !!$ IF (ALLOCATED(tphoto_max_a)) DEALLOCATE(tphoto_max_a) |
---|
5326 | !!$ IF (ALLOCATED(tphoto_max_b)) DEALLOCATE(tphoto_max_b) |
---|
5327 | !!$ IF (ALLOCATED(tphoto_max_c)) DEALLOCATE(tphoto_max_c) |
---|
5328 | IF (ALLOCATED(S0)) DEALLOCATE(S0) |
---|
5329 | IF (ALLOCATED(L0)) DEALLOCATE(L0) |
---|
5330 | IF (ALLOCATED(maint_resp_slope)) DEALLOCATE(maint_resp_slope) |
---|
5331 | IF (ALLOCATED(maint_resp_slope_c)) DEALLOCATE(maint_resp_slope_c) |
---|
5332 | IF (ALLOCATED(maint_resp_slope_b)) DEALLOCATE(maint_resp_slope_b) |
---|
5333 | IF (ALLOCATED(maint_resp_slope_a)) DEALLOCATE(maint_resp_slope_a) |
---|
5334 | IF (ALLOCATED(coeff_maint_zero)) DEALLOCATE(coeff_maint_zero) |
---|
5335 | IF (ALLOCATED(cm_zero_leaf)) DEALLOCATE(cm_zero_leaf) |
---|
5336 | IF (ALLOCATED(cm_zero_sapabove)) DEALLOCATE(cm_zero_sapabove) |
---|
5337 | IF (ALLOCATED(cm_zero_sapbelow)) DEALLOCATE(cm_zero_sapbelow) |
---|
5338 | IF (ALLOCATED(cm_zero_heartabove)) DEALLOCATE(cm_zero_heartabove) |
---|
5339 | IF (ALLOCATED(cm_zero_heartbelow)) DEALLOCATE(cm_zero_heartbelow) |
---|
5340 | IF (ALLOCATED(cm_zero_root)) DEALLOCATE(cm_zero_root) |
---|
5341 | IF (ALLOCATED(cm_zero_fruit)) DEALLOCATE(cm_zero_fruit) |
---|
5342 | IF (ALLOCATED(cm_zero_carbres)) DEALLOCATE(cm_zero_carbres) |
---|
5343 | IF (ALLOCATED(cm_zero_labile)) DEALLOCATE(cm_zero_labile) |
---|
5344 | IF (ALLOCATED(coeff_maint_init)) DEALLOCATE(coeff_maint_init) |
---|
5345 | IF (ALLOCATED(frac_growthresp)) DEALLOCATE(frac_growthresp) |
---|
5346 | IF (ALLOCATED(gpp_to_labile)) DEALLOCATE(gpp_to_labile) |
---|
5347 | IF (ALLOCATED(pipe_density)) DEALLOCATE(pipe_density) |
---|
5348 | IF (ALLOCATED(pipe_tune1)) DEALLOCATE(pipe_tune1) |
---|
5349 | IF (ALLOCATED(pipe_tune2)) DEALLOCATE(pipe_tune2) |
---|
5350 | IF (ALLOCATED(pipe_tune3)) DEALLOCATE(pipe_tune3) |
---|
5351 | IF (ALLOCATED(pipe_tune4)) DEALLOCATE(pipe_tune4) |
---|
5352 | IF (ALLOCATED(tree_ff)) DEALLOCATE(tree_ff) |
---|
5353 | IF (ALLOCATED(pipe_k1)) DEALLOCATE(pipe_k1) |
---|
5354 | IF (ALLOCATED(pipe_tune_exp_coeff)) DEALLOCATE(pipe_tune_exp_coeff) |
---|
5355 | IF (ALLOCATED(mass_ratio_heart_sap)) DEALLOCATE(mass_ratio_heart_sap) |
---|
5356 | IF (ALLOCATED(lai_to_height)) DEALLOCATE(lai_to_height) |
---|
5357 | IF (ALLOCATED(canopy_cover)) DEALLOCATE(canopy_cover) |
---|
5358 | IF (ALLOCATED(nmaxtrees)) DEALLOCATE(nmaxtrees) |
---|
5359 | IF (ALLOCATED(height_init_min)) DEALLOCATE(height_init_min) |
---|
5360 | IF (ALLOCATED(height_init_max)) DEALLOCATE(height_init_max) |
---|
5361 | IF (ALLOCATED(alpha_self_thinning)) DEALLOCATE(alpha_self_thinning) |
---|
5362 | IF (ALLOCATED(beta_self_thinning)) DEALLOCATE(beta_self_thinning) |
---|
5363 | IF (ALLOCATED(fuelwood_diameter)) DEALLOCATE(fuelwood_diameter) |
---|
5364 | IF (ALLOCATED(coppice_kill_be_wood)) DEALLOCATE(coppice_kill_be_wood) |
---|
5365 | IF (ALLOCATED(cn_leaf_prescribed)) DEALLOCATE(cn_leaf_prescribed) |
---|
5366 | IF (ALLOCATED(fcn_wood)) DEALLOCATE(fcn_wood) |
---|
5367 | IF (ALLOCATED(fcn_root)) DEALLOCATE(fcn_root) |
---|
5368 | IF (ALLOCATED(k_latosa_max)) DEALLOCATE(k_latosa_max) |
---|
5369 | IF (ALLOCATED(k_latosa_min)) DEALLOCATE(k_latosa_min) |
---|
5370 | IF (ALLOCATED(fruit_alloc)) DEALLOCATE(fruit_alloc) |
---|
5371 | IF (ALLOCATED(lai_max_to_happy)) DEALLOCATE(lai_max_to_happy) |
---|
5372 | IF (ALLOCATED(flam)) DEALLOCATE(flam) |
---|
5373 | IF (ALLOCATED(k_root)) DEALLOCATE(k_root) |
---|
5374 | IF (ALLOCATED(k_sap)) DEALLOCATE(k_sap) |
---|
5375 | IF (ALLOCATED(k_leaf)) DEALLOCATE(k_leaf) |
---|
5376 | IF (ALLOCATED(phi_leaf)) DEALLOCATE(phi_leaf) |
---|
5377 | IF (ALLOCATED(phi_50)) DEALLOCATE(phi_50) |
---|
5378 | IF (ALLOCATED(c_cavitation)) DEALLOCATE(c_cavitation) |
---|
5379 | IF (ALLOCATED(phi_soil_tune)) DEALLOCATE(phi_soil_tune) |
---|
5380 | IF (ALLOCATED(lai_happy)) DEALLOCATE(lai_happy) |
---|
5381 | !----------------------------------------------------------------------- |
---|
5382 | !tzjh hydraulic architecture |
---|
5383 | |
---|
5384 | IF (ALLOCATED(gpsi)) DEALLOCATE(gpsi) |
---|
5385 | IF (ALLOCATED(gpsi_50)) DEALLOCATE(gpsi_50) |
---|
5386 | IF (ALLOCATED(gmax)) DEALLOCATE(gmax) |
---|
5387 | IF (ALLOCATED(gmin)) DEALLOCATE(gmin) |
---|
5388 | IF (ALLOCATED(kmax_leaf)) DEALLOCATE(kmax_leaf) |
---|
5389 | IF (ALLOCATED(kmax_stem)) DEALLOCATE(kmax_stem) |
---|
5390 | IF (ALLOCATED(kmax_root)) DEALLOCATE(kmax_root) |
---|
5391 | IF (ALLOCATED(a_leaf)) DEALLOCATE(a_leaf) |
---|
5392 | IF (ALLOCATED(a_stem)) DEALLOCATE(a_stem) |
---|
5393 | IF (ALLOCATED(a_root)) DEALLOCATE(a_root) |
---|
5394 | IF (ALLOCATED(P50_leaf)) DEALLOCATE(P50_leaf) |
---|
5395 | IF (ALLOCATED(P50_stem)) DEALLOCATE(P50_stem) |
---|
5396 | IF (ALLOCATED(P50_root)) DEALLOCATE(P50_root) |
---|
5397 | IF (ALLOCATED(wood_density)) DEALLOCATE(wood_density) |
---|
5398 | IF (ALLOCATED(w_density_stem)) DEALLOCATE(w_density_stem) |
---|
5399 | IF (ALLOCATED(root_shoot_ratio)) DEALLOCATE(root_shoot_ratio) |
---|
5400 | IF (ALLOCATED(rwc_root)) DEALLOCATE(rwc_root) |
---|
5401 | IF (ALLOCATED(root_density)) DEALLOCATE(root_density) |
---|
5402 | IF (ALLOCATED(LDMC)) DEALLOCATE(LDMC) |
---|
5403 | IF (ALLOCATED(sla_hydro)) DEALLOCATE(sla_hydro) |
---|
5404 | IF (ALLOCATED(cxyl)) DEALLOCATE(cxyl) |
---|
5405 | IF (ALLOCATED(cr)) DEALLOCATE(cr) |
---|
5406 | IF (ALLOCATED(cl)) DEALLOCATE(cl) |
---|
5407 | |
---|
5408 | !----------------------------------------------------------------------- |
---|
5409 | |
---|
5410 | IF (ALLOCATED(tune_reserves_in_sapling)) DEALLOCATE(tune_reserves_in_sapling) |
---|
5411 | IF (ALLOCATED(death_distribution_factor)) DEALLOCATE(death_distribution_factor) |
---|
5412 | IF (ALLOCATED(npp_reset_value)) DEALLOCATE(npp_reset_value) |
---|
5413 | IF (ALLOCATED(resist)) DEALLOCATE(resist) |
---|
5414 | IF (ALLOCATED(coeff_lcchange_s)) DEALLOCATE(coeff_lcchange_s) |
---|
5415 | IF (ALLOCATED(coeff_lcchange_m)) DEALLOCATE(coeff_lcchange_m) |
---|
5416 | IF (ALLOCATED(coeff_lcchange_l)) DEALLOCATE(coeff_lcchange_l) |
---|
5417 | IF (ALLOCATED(lai_max)) DEALLOCATE(lai_max) |
---|
5418 | IF (ALLOCATED(pheno_model)) DEALLOCATE(pheno_model) |
---|
5419 | IF (ALLOCATED(pheno_type)) DEALLOCATE(pheno_type) |
---|
5420 | IF (ALLOCATED(pheno_gdd_crit_c)) DEALLOCATE(pheno_gdd_crit_c) |
---|
5421 | IF (ALLOCATED(pheno_gdd_crit_b)) DEALLOCATE(pheno_gdd_crit_b) |
---|
5422 | IF (ALLOCATED(pheno_gdd_crit_a)) DEALLOCATE(pheno_gdd_crit_a) |
---|
5423 | IF (ALLOCATED(pheno_gdd_crit)) DEALLOCATE(pheno_gdd_crit) |
---|
5424 | IF (ALLOCATED(ngd_crit)) DEALLOCATE(ngd_crit) |
---|
5425 | IF (ALLOCATED(opti_kpheno_crit)) DEALLOCATE(opti_kpheno_crit) |
---|
5426 | IF (ALLOCATED(ncdgdd_temp)) DEALLOCATE(ncdgdd_temp) |
---|
5427 | IF (ALLOCATED(hum_frac)) DEALLOCATE(hum_frac) |
---|
5428 | IF (ALLOCATED(hum_min_time)) DEALLOCATE(hum_min_time) |
---|
5429 | IF (ALLOCATED(tau_sap)) DEALLOCATE(tau_sap) |
---|
5430 | IF (ALLOCATED(tau_fruit)) DEALLOCATE(tau_fruit) |
---|
5431 | IF (ALLOCATED(tau_root)) DEALLOCATE(tau_root) |
---|
5432 | IF (ALLOCATED(tau_leaf)) DEALLOCATE(tau_leaf) |
---|
5433 | IF (ALLOCATED(ecureuil)) DEALLOCATE(ecureuil) |
---|
5434 | IF (ALLOCATED(alloc_min)) DEALLOCATE(alloc_min) |
---|
5435 | IF (ALLOCATED(alloc_max)) DEALLOCATE(alloc_max) |
---|
5436 | IF (ALLOCATED(demi_alloc)) DEALLOCATE(demi_alloc) |
---|
5437 | IF (ALLOCATED(leaffall)) DEALLOCATE(leaffall) |
---|
5438 | IF (ALLOCATED(senescence_type)) DEALLOCATE(senescence_type) |
---|
5439 | IF (ALLOCATED(senescence_hum)) DEALLOCATE(senescence_hum) |
---|
5440 | IF (ALLOCATED(nosenescence_hum)) DEALLOCATE(nosenescence_hum) |
---|
5441 | IF (ALLOCATED(max_turnover_time)) DEALLOCATE(max_turnover_time) |
---|
5442 | IF (ALLOCATED(min_turnover_time)) DEALLOCATE(min_turnover_time) |
---|
5443 | IF (ALLOCATED(min_leaf_age_for_senescence)) DEALLOCATE(min_leaf_age_for_senescence) |
---|
5444 | IF (ALLOCATED(senescence_temp_c)) DEALLOCATE(senescence_temp_c) |
---|
5445 | IF (ALLOCATED(senescence_temp_b)) DEALLOCATE(senescence_temp_b) |
---|
5446 | IF (ALLOCATED(senescence_temp_a)) DEALLOCATE(senescence_temp_a) |
---|
5447 | IF (ALLOCATED(senescence_temp)) DEALLOCATE(senescence_temp) |
---|
5448 | IF (ALLOCATED(gdd_senescence)) DEALLOCATE(gdd_senescence) |
---|
5449 | IF (ALLOCATED(residence_time)) DEALLOCATE(residence_time) |
---|
5450 | ! added by yitong yao 07 Jan 2020 08:30 |
---|
5451 | IF (ALLOCATED(plc_kill_frac)) DEALLOCATE(plc_kill_frac) |
---|
5452 | ! added by yitong yao 07 Jan 2020 08:30 |
---|
5453 | IF (ALLOCATED(mor_kill_frac)) DEALLOCATE(mor_kill_frac) |
---|
5454 | IF (ALLOCATED(tmin_crit)) DEALLOCATE(tmin_crit) |
---|
5455 | IF (ALLOCATED(tcm_crit)) DEALLOCATE(tcm_crit) |
---|
5456 | IF (ALLOCATED(mortality_min)) DEALLOCATE(mortality_min) |
---|
5457 | IF (ALLOCATED(mortality_max)) DEALLOCATE(mortality_max) |
---|
5458 | IF (ALLOCATED(ref_mortality)) DEALLOCATE(ref_mortality) |
---|
5459 | IF (ALLOCATED(tau_hum_growingseason)) DEALLOCATE(tau_hum_growingseason) |
---|
5460 | IF (ALLOCATED(lai_initmin)) DEALLOCATE(lai_initmin) |
---|
5461 | IF (ALLOCATED(bm_sapl_old)) DEALLOCATE(bm_sapl_old) |
---|
5462 | IF (ALLOCATED(migrate)) DEALLOCATE(migrate) |
---|
5463 | IF (ALLOCATED(maxdia)) DEALLOCATE(maxdia) |
---|
5464 | IF (ALLOCATED(cn_sapl)) DEALLOCATE(cn_sapl) |
---|
5465 | IF (ALLOCATED(leaf_timecst)) DEALLOCATE(leaf_timecst) |
---|
5466 | IF (ALLOCATED(plantation)) DEALLOCATE(plantation) |
---|
5467 | IF (ALLOCATED(fm_allo_a)) DEALLOCATE(fm_allo_a) |
---|
5468 | IF (ALLOCATED(fm_allo_c)) DEALLOCATE(fm_allo_c) |
---|
5469 | IF (ALLOCATED(fm_allo_d)) DEALLOCATE(fm_allo_d) |
---|
5470 | IF (ALLOCATED(fm_allo_p)) DEALLOCATE(fm_allo_p) |
---|
5471 | IF (ALLOCATED(fm_allo_q)) DEALLOCATE(fm_allo_q) |
---|
5472 | IF (ALLOCATED(allo_crown_a0)) DEALLOCATE(allo_crown_a0) |
---|
5473 | IF (ALLOCATED(allo_crown_a1)) DEALLOCATE(allo_crown_a1) |
---|
5474 | IF (ALLOCATED(allo_crown_a2)) DEALLOCATE(allo_crown_a2) |
---|
5475 | IF (ALLOCATED(h_first)) DEALLOCATE(h_first) |
---|
5476 | IF (ALLOCATED(dens_target)) DEALLOCATE(dens_target) |
---|
5477 | IF (ALLOCATED(thinstrat)) DEALLOCATE(thinstrat) |
---|
5478 | IF (ALLOCATED(taumin)) DEALLOCATE(taumin) |
---|
5479 | IF (ALLOCATED(taumax)) DEALLOCATE(taumax) |
---|
5480 | IF (ALLOCATED(alpha_rdi_upper)) DEALLOCATE(alpha_rdi_upper) |
---|
5481 | IF (ALLOCATED(beta_rdi_upper)) DEALLOCATE(beta_rdi_upper) |
---|
5482 | IF (ALLOCATED(alpha_rdi_lower)) DEALLOCATE(alpha_rdi_lower) |
---|
5483 | IF (ALLOCATED(beta_rdi_lower)) DEALLOCATE(beta_rdi_lower) |
---|
5484 | IF (ALLOCATED(largest_tree_dia)) DEALLOCATE(largest_tree_dia) |
---|
5485 | IF (ALLOCATED(branch_ratio)) DEALLOCATE(branch_ratio) |
---|
5486 | IF (ALLOCATED(branch_ratio)) DEALLOCATE(branch_ratio) |
---|
5487 | IF (ALLOCATED(decl_factor)) DEALLOCATE(decl_factor) |
---|
5488 | !IF (ALLOCATED(opt_factor)) DEALLOCATE(opt_factor) |
---|
5489 | IF (ALLOCATED(coppice_diameter)) DEALLOCATE(coppice_diameter) |
---|
5490 | IF (ALLOCATED(shoots_per_stool)) DEALLOCATE(shoots_per_stool) |
---|
5491 | IF (ALLOCATED(src_rot_length)) DEALLOCATE(src_rot_length) |
---|
5492 | IF (ALLOCATED(src_nrots)) DEALLOCATE(src_nrots) |
---|
5493 | IF (ALLOCATED(m_dv)) DEALLOCATE(m_dv) |
---|
5494 | IF (ALLOCATED(recruitment_light_threshold)) DEALLOCATE(recruitment_light_threshold) |
---|
5495 | IF (ALLOCATED(dia_recr)) DEALLOCATE(dia_recr) |
---|
5496 | IF (ALLOCATED(hei_recr)) DEALLOCATE(hei_recr) |
---|
5497 | IF (ALLOCATED(harvest_ratio)) DEALLOCATE(harvest_ratio) |
---|
5498 | |
---|
5499 | END SUBROUTINE pft_parameters_clear |
---|
5500 | |
---|
5501 | END MODULE pft_parameters |
---|