source: branches/publications/ORCHIDEE_CAN_r3069/src_parameters/pft_parameters.f90 @ 7346

Last change on this file since 7346 was 2945, checked in by sebastiaan.luyssaert, 9 years ago

DEV: tested 1 year global. This code contains the latest version for anthropogenic tree species channges, several bug fixes to forest management as well as the code for the fully integrated multi-layer energy budget. This implies that the multi-layer energy budget makes use Pinty's albedo scheme, the rognostic canopy structure as well as a vertical profile for stomatal conductance. This is an intermediate version because species change code is not complete as some management changes have not been implemented yet. Further the multi-layer albedo code needs more work in terms of calculating average fluxes at the pixel rather than the PFT level

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