source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/pft_parameters.f90 @ 7852

Last change on this file since 7852 was 7555, checked in by sebastiaan.luyssaert, 2 years ago

Contributes to ticket #837. Simplified forest management for young stands a bit

  • Property svn:keywords set to Date Revision
File size: 299.1 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.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 control.f90 (subroutine control_initialize). \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 vertical_soil_var
33  USE constantes_mtc
34  USE constantes
35  USE ioipsl
36  USE ioipsl_para 
37  USE defprec
38
39  IMPLICIT NONE
40
41CONTAINS
42 
43
44!! ================================================================================================================================
45!! SUBROUTINE   : pft_parameters_main
46!!
47!>\BRIEF          This subroutine initializes all the pft parameters in function of the
48!! number of vegetation types chosen by the user.
49!!
50!! DESCRIPTION  : This subroutine is called after the reading of the number of PFTS and the options
51!!                activated by the user in the configuration files. \n
52!!                The allocation is done just before reading the correspondence table  between PFTs and MTCs
53!!                defined by the user in the configuration file.\n
54!!                With the correspondence table, the subroutine can initialize the pft parameters in function
55!!                of the flags activated (ok_sechiba, ok_stomate, routing,...) in order to
56!!                optimize the memory allocation. \n
57!!                If the number of PFTs and pft_to_mtc are not found, the standard configuration will be used
58!!                (13 PFTs, PFT = MTC). \n
59!!                Some restrictions : the pft 1 can only be the bare soil and it is unique. \n
60!!                Algorithm : Build new PFT from 13 generic-PFT or meta-classes.
61!!                1. Read the number of PFTs in "run.def". If nothing is found, it is assumed that the user intend to use
62!!                   the standard of PFTs (13).
63!!                2. Read the index vector in "run.def". The index vector associates one PFT to one meta-classe (or generic PFT).
64!!                   When the association is done, the PFT defined by the user inherited the default values from the meta classe.
65!!                   If nothing is found, it is assumed to use the standard index vector (PFT = MTC).
66!!                3. Check consistency
67!!                4. Memory allocation and initialization.
68!!                5. The parameters are read in the configuration file in config_initialize (control module).
69!!
70!! RECENT CHANGE(S): None
71!!
72!! MAIN OUTPUT VARIABLE(S): None
73!!
74!! REFERENCE(S) : None
75!!
76!! FLOWCHART    : None
77!! \n
78!_ ================================================================================================================================
79
80  SUBROUTINE pft_parameters_main()
81
82    IMPLICIT NONE
83
84    !! 0. Variables and parameters declaration
85
86    !! 0.4 Local variables 
87
88    INTEGER(i_std) :: j                             !! Index (unitless)
89   
90
91    !_ ================================================================================================================================
92
93    !
94    ! PFT global
95    !
96
97    IF(l_first_pft_parameters) THEN
98
99       !! 1. First time step
100       IF(printlev>=3) THEN
101          WRITE(numout,*) 'l_first_pft_parameters :we read the parameters from the def files'
102       ENDIF
103
104       !! 2. Memory allocation for the pfts-parameters
105       CALL pft_parameters_alloc()
106
107       !! 3. Correspondance table
108
109       !! 3.1 Initialisation of the correspondance table
110       !! Initialisation of the correspondance table
111       IF (nvm == nvmc) THEN
112          pft_to_mtc = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /)
113       ELSE
114          pft_to_mtc(:) = undef_int
115       ENDIF !(nvm  == nvmc)
116
117       !! 3.2 Reading of the conrrespondance table in the .def file
118       !
119       !Config Key   = PFT_TO_MTC
120       !Config Desc  = correspondance array linking a PFT to MTC
121       !Config if    = OK_SECHIBA or OK_STOMATE
122       !Config Def   = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
123       !Config Help  =
124       !Config Units = [-]
125       CALL getin_p('PFT_TO_MTC',pft_to_mtc)
126
127       !! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array
128       !!     If the configuration is wrong, send a error message to the user.
129       IF(nvm /= nvmc ) THEN
130          !
131          IF(pft_to_mtc(1) == undef_int) THEN
132             CALL ipslerr_p (3,'The array PFT_TO_MTC is empty : we stop','','','')
133          ENDIF !(pft_to_mtc(1) == undef_int)
134          !
135       ENDIF !(nvm /= nvmc )
136
137       !! 3.4 Some error messages
138
139       !! 3.4.1 What happened if pft_to_mtc(j) > nvmc or pft_to_mtc(j) <=0 (if the mtc doesn't exist)?
140       DO j = 1, nvm ! Loop over # PFTs 
141          !
142          IF( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) ) THEN
143             CALL ipslerr_p(3,'the metaclass chosen does not exist', &
144                  'we stop reading pft_to_mtc','','') 
145          ENDIF !( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) )
146          !
147       ENDDO  ! Loop over # PFTs 
148
149
150       !! 3.4.2 Check if pft_to_mtc(1) = 1
151       IF(pft_to_mtc(1) /= 1) THEN
152          !
153          CALL ipslerr_p(3,'the first pft has to be the bare soil', & 
154               'we stop reading next values of pft_to_mtc','','') 
155          !
156       ELSE
157          !
158          DO j = 2,nvm ! Loop over # PFTs different from bare soil
159             !
160             IF(pft_to_mtc(j) == 1) THEN
161                CALL ipslerr_p(3,'only pft_to_mtc(1) has to be the bare soil',&
162                     'we stop reading pft_to_mtc','','')
163             ENDIF ! (pft_to_mtc(j) == 1)
164             !
165          ENDDO ! Loop over # PFTs different from bare soil
166          !
167       ENDIF !(pft_to_mtc(1) /= 1)
168
169
170       !! 4.Initialisation of the pfts-parameters
171       CALL pft_parameters_init()
172
173       !! 5. Useful data
174
175       !! 5.1 Read the name of the PFTs given by the user
176       !
177       !Config Key   = PFT_NAME
178       !Config Desc  = Name of a PFT
179       !Config if    = OK_SECHIBA or OK_STOMATE
180       !Config Def   = bare ground, tropical broad-leaved evergreen, tropical broad-leaved raingreen,
181       !Config         temperate needleleaf evergreen, temperate broad-leaved evergreen temperate broad-leaved summergreen,
182       !Config         boreal needleleaf evergreen, boreal broad-leaved summergreen, boreal needleleaf summergreen,
183       !Config         C3 grass, C4 grass, C3 agriculture, C4 agriculture   
184       !Config Help  = the user can name the new PFTs he/she introducing for new species
185       !Config Units = [-]
186       CALL getin_p('PFT_NAME',pft_name)
187
188       !! 5.2 A useful message to the user: correspondance between the number of the pft
189       !! and the name of the associated mtc
190       IF (printlev >=1 ) THEN
191          WRITE(numout,*) ''
192          DO j = 2,nvm ! Loop over # PFTs
193             WRITE(numout,*) 'The PFT',j, 'called ', trim(PFT_name(j)),' corresponds to the MTC : ',trim(MTC_name(pft_to_mtc(j)))
194          END DO
195          WRITE(numout,*) ''
196       END IF
197
198
199       !! 6. End message
200       IF (printlev>=3) WRITE(numout,*) 'pft_parameters_done'
201
202       !! 8. Reset flag
203       l_first_pft_parameters = .FALSE.
204
205    ELSE
206
207       RETURN
208
209    ENDIF !(l_first_pft_parameters)
210
211  END SUBROUTINE pft_parameters_main
212
213
214!! ================================================================================================================================
215!! SUBROUTINE   : pft_parameters_init
216!!
217!>\BRIEF          This subroutine initializes all the pft parameters by the default values
218!! of the corresponding metaclasse.
219!!
220!! DESCRIPTION  : This subroutine is called after the reading of the number of PFTS and the correspondence
221!!                table defined by the user in the configuration files. \n
222!!                With the correspondence table, the subroutine can search the default values for the parameter
223!!                even if the PFTs are classified in a random order (except bare soil). \n
224!!                With the correspondence table, the subroutine can initialize the pft parameters in function
225!!                of the flags activated (ok_sechiba, ok_stomate, routing,...).\n
226!!
227!! RECENT CHANGE(S): Didier Solyga : Simplified PFT loops : use vector notation.
228!!
229!! MAIN OUTPUT VARIABLE(S): None
230!!
231!! REFERENCE(S) : None
232!!
233!! FLOWCHART    : None
234!! \n
235!_ ================================================================================================================================
236
237  SUBROUTINE pft_parameters_init()
238
239    IMPLICIT NONE
240
241    !! 0. Variables and parameters declaration
242
243    !! 0.1 Input variables
244
245    !! 0.4 Local variables
246
247    INTEGER(i_std)                :: jv                !! Index (unitless)
248   
249    !_ ================================================================================================================================
250
251    !
252    ! 1. Correspondance between the PFTs values and thes MTCs values
253    !
254
255
256    ! 1.1 For parameters used anytime
257
258    PFT_name(:) = MTC_name(pft_to_mtc(:))
259    !
260    ! Vegetation structure
261    !
262    veget_ori_fixed_test_1(:) = veget_ori_fixed_mtc(pft_to_mtc(:))
263    llaimax(:) = llaimax_mtc(pft_to_mtc(:))
264    llaimin(:) = llaimin_mtc(pft_to_mtc(:))
265    height_presc(:) = height_presc_mtc(pft_to_mtc(:))
266    z0_over_height(:) = z0_over_height_mtc(pft_to_mtc(:))
267    ratio_z0m_z0h(:) = ratio_z0m_z0h_mtc(pft_to_mtc(:))
268    type_of_lai(:) = type_of_lai_mtc(pft_to_mtc(:))
269    natural(:) = natural_mtc(pft_to_mtc(:))
270    !
271    ! Water - sechiba
272    !
273    IF (zmaxh == 2.0) THEN
274       IF (printlev>=2) WRITE(numout,*)'Initialize humcst using reference values for 2m soil depth'
275       humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
276       max_root_depth(:) = max_root_depth_ref2m_mtc(pft_to_mtc(:))
277    ELSE IF (zmaxh == 4.0) THEN
278       IF (printlev>=2) WRITE(numout,*)'Initialize humcst using reference values for 4m soil depth'
279       humcste(:) = humcste_ref4m(pft_to_mtc(:))  ! values for 4m soil depth
280       max_root_depth(:) = max_root_depth_ref4m_mtc(pft_to_mtc(:))
281    ELSE
282       IF (printlev>=2) WRITE(numout,*)'Note that humcste is initialized with values for 2m soil depth bur zmaxh=', zmaxh
283       humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
284    END IF
285
286    !
287    ! Soil - vegetation
288    !
289    pref_soil_veg(:) = pref_soil_veg_mtc(pft_to_mtc(:))
290
291    !
292    ! Vegetation - age classes
293    !
294    agec_group(:) = agec_group_mtc(pft_to_mtc(:))
295   
296    !
297    ! Photosynthesis
298    !
299    is_c4(:) = is_c4_mtc(pft_to_mtc(:))
300    vcmax_fix(:) = vcmax_fix_mtc(pft_to_mtc(:))
301    downregulation_co2_coeff(:) = downregulation_co2_coeff_mtc(pft_to_mtc(:))
302    E_KmC(:)      = E_KmC_mtc(pft_to_mtc(:))
303    E_KmO(:)      = E_KmO_mtc(pft_to_mtc(:))
304    E_Sco(:)      = E_Sco_mtc(pft_to_mtc(:))
305    E_gamma_star(:) = E_gamma_star_mtc(pft_to_mtc(:))
306    E_Vcmax(:)    = E_Vcmax_mtc(pft_to_mtc(:))
307    E_Jmax(:)     = E_Jmax_mtc(pft_to_mtc(:))
308    aSV(:)        = aSV_mtc(pft_to_mtc(:))
309    bSV(:)        = bSV_mtc(pft_to_mtc(:))
310    tphoto_min(:) = tphoto_min_mtc(pft_to_mtc(:))
311    tphoto_max(:) = tphoto_max_mtc(pft_to_mtc(:))
312    aSJ(:)        = aSJ_mtc(pft_to_mtc(:))
313    bSJ(:)        = bSJ_mtc(pft_to_mtc(:))
314    D_Vcmax(:)     = D_Vcmax_mtc(pft_to_mtc(:))
315    D_Jmax(:)     = D_Jmax_mtc(pft_to_mtc(:))
316    E_gm(:)       = E_gm_mtc(pft_to_mtc(:)) 
317    S_gm(:)       = S_gm_mtc(pft_to_mtc(:)) 
318    D_gm(:)       = D_gm_mtc(pft_to_mtc(:)) 
319    E_Rd(:)       = E_Rd_mtc(pft_to_mtc(:))
320    Vcmax25(:)    = Vcmax25_mtc(pft_to_mtc(:))
321    arJV(:)       = arJV_mtc(pft_to_mtc(:))
322    brJV(:)       = brJV_mtc(pft_to_mtc(:))
323    KmC25(:)      = KmC25_mtc(pft_to_mtc(:))
324    KmO25(:)      = KmO25_mtc(pft_to_mtc(:))
325    Sco25(:)      = Sco25_mtc(pft_to_mtc(:))
326    gm25(:)       = gm25_mtc(pft_to_mtc(:)) 
327    gamma_star25(:)  = gamma_star25_mtc(pft_to_mtc(:))
328    a1(:)         = a1_mtc(pft_to_mtc(:))
329    b1(:)         = b1_mtc(pft_to_mtc(:))
330    g0(:)         = g0_mtc(pft_to_mtc(:))
331    h_protons(:)  = h_protons_mtc(pft_to_mtc(:))
332    fpsir(:)      = fpsir_mtc(pft_to_mtc(:))
333    fQ(:)         = fQ_mtc(pft_to_mtc(:))     
334    fpseudo(:)    = fpseudo_mtc(pft_to_mtc(:))   
335    kp(:)         = kp_mtc(pft_to_mtc(:))
336    alpha(:)      = alpha_mtc(pft_to_mtc(:))
337    gbs(:)        = gbs_mtc(pft_to_mtc(:))
338    theta(:)      = theta_mtc(pft_to_mtc(:))       
339    alpha_LL(:)   = alpha_LL_mtc(pft_to_mtc(:))
340    stress_vcmax(:) = stress_vcmax_mtc(pft_to_mtc(:))
341    stress_gs(:)    = stress_gs_mtc(pft_to_mtc(:))
342    stress_gm(:)    = stress_gm_mtc(pft_to_mtc(:))
343    ext_coeff(:) = ext_coeff_mtc(pft_to_mtc(:))
344    ext_coeff_vegetfrac(:) = ext_coeff_vegetfrac_mtc(pft_to_mtc(:))
345    !
346    !! Define labels from physiologic characteristics
347    !
348    leaf_tab(:) = leaf_tab_mtc(pft_to_mtc(:)) 
349    pheno_model(:) = pheno_model_mtc(pft_to_mtc(:))   
350    !
351    is_tree(:) = .FALSE.
352    DO jv = 1,nvm
353       IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
354    END DO
355    !
356    is_deciduous(:) = .FALSE.
357    DO jv = 1,nvm
358       IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
359    END DO
360    !
361    is_evergreen(:) = .FALSE.
362    DO jv = 1,nvm
363       IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
364    END DO
365    !
366    is_needleleaf(:) = .FALSE.
367    DO jv = 1,nvm
368       IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
369    END DO
370
371    is_tropical(:) = is_tropical_mtc(pft_to_mtc(:)) 
372    is_temperate(:) = is_temperate_mtc(pft_to_mtc(:)) 
373    is_boreal(:) = is_boreal_mtc(pft_to_mtc(:)) 
374
375    ! 1.2 For sechiba parameters
376    IF (ok_sechiba) THEN
377       !
378       ! Vegetation structure - sechiba
379       !
380       rveg_pft(:) = rveg_mtc(pft_to_mtc(:))
381       !
382       ! Evapotranspiration -  sechiba
383       !
384       rstruct_const(:) = rstruct_const_mtc(pft_to_mtc(:))
385       kzero(:) = kzero_mtc(pft_to_mtc(:))
386       !
387       ! Water - sechiba
388       !
389       wmax_veg(:) = wmax_veg_mtc(pft_to_mtc(:))
390       IF ( OFF_LINE_MODE ) THEN
391          throughfall_by_pft(:) = 0.
392       ELSE
393          throughfall_by_pft(:) = throughfall_by_mtc(pft_to_mtc(:))
394       ENDIF
395       !
396       ! Albedo - sechiba
397       !
398       snowa_aged_vis(:) = snowa_aged_vis_mtc(pft_to_mtc(:))
399       snowa_aged_nir(:) = snowa_aged_nir_mtc(pft_to_mtc(:))
400       snowa_dec_vis(:) = snowa_dec_vis_mtc(pft_to_mtc(:)) 
401       snowa_dec_nir(:) = snowa_dec_nir_mtc(pft_to_mtc(:)) 
402       alb_leaf_vis(:) = alb_leaf_vis_mtc(pft_to_mtc(:)) 
403       alb_leaf_nir(:) = alb_leaf_nir_mtc(pft_to_mtc(:))
404       
405       leaf_ssa(:,ivis) = leaf_ssa_vis_mtc(pft_to_mtc(:))
406       leaf_ssa(:,inir) = leaf_ssa_nir_mtc(pft_to_mtc(:))
407       leaf_psd(:,ivis) = leaf_psd_vis_mtc(pft_to_mtc(:))
408       leaf_psd(:,inir) = leaf_psd_nir_mtc(pft_to_mtc(:))
409       bgd_reflectance(:,ivis) = bgd_reflectance_vis_mtc(pft_to_mtc(:))
410       bgd_reflectance(:,inir) = bgd_reflectance_nir_mtc(pft_to_mtc(:))
411       leaf_to_shoot_clumping(:) = leaf_to_shoot_clumping_mtc(pft_to_mtc(:))
412       lai_correction_factor(:) = lai_correction_factor_mtc(pft_to_mtc(:))
413       min_level_sep(:) = min_level_sep_mtc(pft_to_mtc(:))
414       !
415       ! Diffuco and hydrol_arch
416       !
417       lai_top(:) = lai_top_mtc(pft_to_mtc(:))
418       k_root(:) = k_root_mtc(pft_to_mtc(:))
419       k_belowground(:) = k_belowground_mtc(pft_to_mtc(:))
420       k_sap(:) = k_sap_mtc(pft_to_mtc(:))
421       k_leaf(:) = k_leaf_mtc(pft_to_mtc(:))
422       psi_leaf(:) = psi_leaf_mtc(pft_to_mtc(:))
423       psi_50(:) = psi_50_mtc(pft_to_mtc(:))
424       c_cavitation(:) = c_cavitation_mtc(pft_to_mtc(:))
425       srl(:) = srl_mtc(pft_to_mtc(:))
426       r_froot(:) = r_froot_mtc(pft_to_mtc(:))
427       psi_root(:) = psi_root_mtc(pft_to_mtc(:))
428       !
429       ! Laieff
430       !
431       crown_to_height(:) = crown_to_height_mtc(pft_to_mtc(:))
432       crown_vertohor_dia(:) = crown_vertohor_dia_mtc(pft_to_mtc(:))
433       pipe_density(:) = pipe_density_mtc(pft_to_mtc(:))
434       tree_ff(:) = tree_ff_mtc(pft_to_mtc(:))
435       pipe_tune2(:) = pipe_tune2_mtc(pft_to_mtc(:)) 
436       pipe_tune3(:) = pipe_tune3_mtc(pft_to_mtc(:))
437       pipe_tune4(:) = pipe_tune4_mtc(pft_to_mtc(:))
438       pipe_k1(:) = pipe_k1_mtc(pft_to_mtc(:)) 
439       sla(:) = sla_mtc(pft_to_mtc(:))
440       slainit(:) = slainit_mtc(pft_to_mtc(:))
441       lai_to_height(:) = lai_to_height_mtc(pft_to_mtc(:)) 
442
443    ENDIF !(ok_sechiba)
444
445    ! 1.3 For BVOC parameters
446
447    IF (ok_bvoc) THEN
448       !
449       ! Biogenic Volatile Organic Compounds
450       !
451       em_factor_isoprene(:) = em_factor_isoprene_mtc(pft_to_mtc(:))
452       em_factor_monoterpene(:) = em_factor_monoterpene_mtc(pft_to_mtc(:))
453       LDF_mono = LDF_mono_mtc 
454       LDF_sesq = LDF_sesq_mtc 
455       LDF_meth = LDF_meth_mtc 
456       LDF_acet = LDF_acet_mtc 
457
458       em_factor_apinene(:) = em_factor_apinene_mtc(pft_to_mtc(:))
459       em_factor_bpinene(:) = em_factor_bpinene_mtc(pft_to_mtc(:))
460       em_factor_limonene(:) = em_factor_limonene_mtc(pft_to_mtc(:))
461       em_factor_myrcene(:) = em_factor_myrcene_mtc(pft_to_mtc(:))
462       em_factor_sabinene(:) = em_factor_sabinene_mtc(pft_to_mtc(:))
463       em_factor_camphene(:) = em_factor_camphene_mtc(pft_to_mtc(:))
464       em_factor_3carene(:) = em_factor_3carene_mtc(pft_to_mtc(:))
465       em_factor_tbocimene(:) = em_factor_tbocimene_mtc(pft_to_mtc(:))
466       em_factor_othermonot(:) = em_factor_othermonot_mtc(pft_to_mtc(:))
467       em_factor_sesquiterp(:) = em_factor_sesquiterp_mtc(pft_to_mtc(:))
468
469       beta_mono = beta_mono_mtc
470       beta_sesq = beta_sesq_mtc
471       beta_meth = beta_meth_mtc
472       beta_acet = beta_acet_mtc
473       beta_oxyVOC = beta_oxyVOC_mtc
474
475       em_factor_ORVOC(:) = em_factor_ORVOC_mtc(pft_to_mtc(:)) 
476       em_factor_OVOC(:) = em_factor_OVOC_mtc(pft_to_mtc(:))
477       em_factor_MBO(:) = em_factor_MBO_mtc(pft_to_mtc(:))
478       em_factor_methanol(:) = em_factor_methanol_mtc(pft_to_mtc(:))
479       em_factor_acetone(:) = em_factor_acetone_mtc(pft_to_mtc(:)) 
480       em_factor_acetal(:) = em_factor_acetal_mtc(pft_to_mtc(:))
481       em_factor_formal(:) = em_factor_formal_mtc(pft_to_mtc(:))
482       em_factor_acetic(:) = em_factor_acetic_mtc(pft_to_mtc(:))
483       em_factor_formic(:) = em_factor_formic_mtc(pft_to_mtc(:))
484       em_factor_no_wet(:) = em_factor_no_wet_mtc(pft_to_mtc(:))
485       em_factor_no_dry(:) = em_factor_no_dry_mtc(pft_to_mtc(:))
486       Larch(:) = Larch_mtc(pft_to_mtc(:)) 
487       !-
488    ENDIF !(ok_bvoc)
489
490    ! 1.4 For stomate parameters
491
492    IF (ok_stomate) THEN
493
494       !
495       ! Vegetation structure - stomate
496       !
497       availability_fact(:) = availability_fact_mtc(pft_to_mtc(:))
498       !
499       ! Respiration - stomate
500       !
501       frac_growthresp(:) = frac_growthresp_mtc(pft_to_mtc(:)) 
502       coeff_maint_init(:) = coeff_maint_init_mtc(pft_to_mtc(:))
503       tref_maint_resp(:) = tref_maint_resp_mtc(pft_to_mtc(:))
504       tmin_maint_resp(:) = tmin_maint_resp_mtc(pft_to_mtc(:))
505       e0_maint_resp(:) = e0_maint_resp_mtc(pft_to_mtc(:))
506       !
507       ! Allocation - stomate
508       !
509       tref_labile(:) = tref_labile_mtc(pft_to_mtc(:))
510       tmin_labile(:) = tmin_labile_mtc(pft_to_mtc(:))
511       e0_labile(:) = e0_labile_mtc(pft_to_mtc(:))
512       always_labile(:) = always_labile_mtc(pft_to_mtc(:))
513       !
514       ! Fire - stomate
515       !
516       flam(:) = flam_mtc(pft_to_mtc(:))
517       resist(:) = resist_mtc(pft_to_mtc(:))
518       !
519       ! Flux - LUC
520       !
521       coeff_lcchange_s(:) = coeff_lcchange_s_mtc(pft_to_mtc(:))
522       coeff_lcchange_m(:) = coeff_lcchange_m_mtc(pft_to_mtc(:))
523       coeff_lcchange_l(:) = coeff_lcchange_l_mtc(pft_to_mtc(:))
524
525       !
526       ! Phenology
527       !
528       !
529       ! 1. Stomate
530       !
531       lai_max_to_happy(:) = lai_max_to_happy_mtc(pft_to_mtc(:)) 
532       lai_max(:) = lai_max_mtc(pft_to_mtc(:))
533       pheno_type(:) = pheno_type_mtc(pft_to_mtc(:))
534       !
535       ! 2. Leaf Onset
536       !
537       force_pheno(:) = force_pheno_mtc(pft_to_mtc(:))
538       pheno_gdd_crit_c(:) = pheno_gdd_crit_c_mtc(pft_to_mtc(:))
539       pheno_gdd_crit_b(:) = pheno_gdd_crit_b_mtc(pft_to_mtc(:))         
540       pheno_gdd_crit_a(:) = pheno_gdd_crit_a_mtc(pft_to_mtc(:))
541       pheno_moigdd_t_crit(:) = pheno_moigdd_t_crit_mtc(pft_to_mtc(:))
542       ngd_crit(:) =  ngd_crit_mtc(pft_to_mtc(:))
543       ncdgdd_temp(:) = ncdgdd_temp_mtc(pft_to_mtc(:)) 
544       hum_frac(:) = hum_frac_mtc(pft_to_mtc(:))
545       hum_min_time(:) = hum_min_time_mtc(pft_to_mtc(:))
546       longevity_sap(:) = longevity_sap_mtc(pft_to_mtc(:))
547       longevity_leaf(:) = longevity_leaf_mtc(pft_to_mtc(:))
548       leaf_age_crit_tref(:) = leaf_age_crit_tref_mtc(pft_to_mtc(:))
549       leaf_age_crit_coeff1(:) = leaf_age_crit_coeff1_mtc(pft_to_mtc(:))
550       leaf_age_crit_coeff2(:) = leaf_age_crit_coeff2_mtc(pft_to_mtc(:))
551       leaf_age_crit_coeff3(:) = leaf_age_crit_coeff3_mtc(pft_to_mtc(:))
552       longevity_fruit(:) = longevity_fruit_mtc(pft_to_mtc(:))
553       longevity_root(:) = longevity_root_mtc(pft_to_mtc(:))
554       ecureuil(:) = ecureuil_mtc(pft_to_mtc(:))
555       alloc_min(:) = alloc_min_mtc(pft_to_mtc(:))
556       alloc_max(:) = alloc_max_mtc(pft_to_mtc(:))
557       demi_alloc(:) = demi_alloc_mtc(pft_to_mtc(:))
558     
559       !
560       ! 3. Senescence
561       !
562       leaffall(:) = leaffall_mtc(pft_to_mtc(:))
563       presenescence_ratio(:) = presenescence_ratio_mtc(pft_to_mtc(:)) 
564       senescence_type(:) = senescence_type_mtc(pft_to_mtc(:)) 
565       senescence_hum(:) = senescence_hum_mtc(pft_to_mtc(:)) 
566       nosenescence_hum(:) = nosenescence_hum_mtc(pft_to_mtc(:)) 
567       max_turnover_time(:) = max_turnover_time_mtc(pft_to_mtc(:))
568       min_turnover_time(:) = min_turnover_time_mtc(pft_to_mtc(:))
569       recycle_leaf(:) = recycle_leaf_mtc(pft_to_mtc(:))
570       recycle_root(:) = recycle_root_mtc(pft_to_mtc(:))
571       min_leaf_age_for_senescence(:) = min_leaf_age_for_senescence_mtc(pft_to_mtc(:))
572       senescence_temp_c(:) = senescence_temp_c_mtc(pft_to_mtc(:))
573       senescence_temp_b(:) = senescence_temp_b_mtc(pft_to_mtc(:))
574       senescence_temp_a(:) = senescence_temp_a_mtc(pft_to_mtc(:))
575       gdd_senescence(:) = gdd_senescence_mtc(pft_to_mtc(:))
576       always_init(:) = always_init_mtc(pft_to_mtc(:))
577
578       !-
579       ! 4. N cycle
580       !-
581       max_soil_n_bnf(:) = max_soil_n_bnf_mtc(pft_to_mtc(:))
582       manure_pftweight(:) =  manure_pftweight_mtc(pft_to_mtc(:))       
583
584       !
585       ! DGVM
586       !
587       residence_time(:) = residence_time_mtc(pft_to_mtc(:))
588       tmin_crit(:) = tmin_crit_mtc(pft_to_mtc(:))
589       tcm_crit(:) = tcm_crit_mtc(pft_to_mtc(:))
590       !-
591       k_latosa_max(:) = k_latosa_max_mtc(pft_to_mtc(:))
592       k_latosa_min(:) = k_latosa_min_mtc(pft_to_mtc(:))
593       
594       !
595       ! Recruitment (stomate) 
596       
597       recruitment_pft(:) = recruitment_pft_mtc(pft_to_mtc(:)) 
598       recruitment_height(:) = recruitment_height_mtc(pft_to_mtc(:)) 
599       recruitment_alpha(:) = recruitment_alpha_mtc(pft_to_mtc(:)) 
600       recruitment_beta(:) = recruitment_beta_mtc(pft_to_mtc(:)) 
601       
602       !
603       ! Mortality - stomate_kill
604       !
605       beetle_pft(:) = beetle_pft_mtc(pft_to_mtc(:))
606       death_distribution_factor(:) = death_distribution_factor_mtc(pft_to_mtc(:))
607       npp_reset_value(:) = npp_reset_value_mtc(pft_to_mtc(:))
608       ndying_year(:) = ndying_year_mtc(pft_to_mtc(:))
609       !
610       ! Bark beetle module (stomate)
611       !
612       remaining_beetles(:) = remaining_beetles_mtc(pft_to_mtc(:))
613       pressure_feedback(:) = pressure_feedback_mtc(pft_to_mtc(:))
614       age_susceptibility_a(:) = age_susceptibility_a_mtc(pft_to_mtc(:))
615       age_susceptibility_b(:) = age_susceptibility_b_mtc(pft_to_mtc(:))
616       age_susceptibility_c(:) = age_susceptibility_c_mtc(pft_to_mtc(:))
617       rdi_susceptibility_a(:) = rdi_susceptibility_a_mtc(pft_to_mtc(:))
618       rdi_susceptibility_b(:) = rdi_susceptibility_b_mtc(pft_to_mtc(:))
619       rdi_target_suscept(:) = rdi_target_suscept_mtc(pft_to_mtc(:))
620       share_susceptibility_a(:) = share_susceptibility_a_mtc(pft_to_mtc(:))
621       share_susceptibility_b(:) = share_susceptibility_b_mtc(pft_to_mtc(:))
622       windthrow_susceptibility_tune(:) = windthrow_susceptibility_tune_mtc(pft_to_mtc(:))
623       drought_susceptibility_a(:) = drought_susceptibility_a_mtc(pft_to_mtc(:))
624       drought_susceptibility_b(:) = drought_susceptibility_b_mtc(pft_to_mtc(:))
625       beetle_generation_a(:) = beetle_generation_a_mtc(pft_to_mtc(:))
626       beetle_generation_b(:) = beetle_generation_b_mtc(pft_to_mtc(:))
627       beetle_generation_c(:) = beetle_generation_c_mtc(pft_to_mtc(:))
628       min_temp_beetle(:) = min_temp_beetle_mtc(pft_to_mtc(:))
629       max_temp_beetle(:) = max_temp_beetle_mtc(pft_to_mtc(:))
630       opt_temp_beetle(:) = opt_temp_beetle_mtc(pft_to_mtc(:))
631       eff_temp_beetle_a(:) = eff_temp_beetle_a_mtc(pft_to_mtc(:))
632       eff_temp_beetle_b(:) = eff_temp_beetle_b_mtc(pft_to_mtc(:))
633       eff_temp_beetle_c(:) = eff_temp_beetle_c_mtc(pft_to_mtc(:))
634       eff_temp_beetle_d(:) = eff_temp_beetle_d_mtc(pft_to_mtc(:))
635       diapause_thres_daylength(:) = diapause_thres_daylength_mtc(pft_to_mtc(:))
636       wght_sirdi_a(:)=wght_sirdi_a_mtc(pft_to_mtc(:))
637       wght_sirdi_b(:)=wght_sirdi_b_mtc(pft_to_mtc(:))
638       wght_sid(:)=wght_sid_mtc(pft_to_mtc(:))
639       wght_sis(:)=wght_sis_mtc(pft_to_mtc(:))
640 
641       !
642       ! Windfall - stomate_windthrow
643       !
644       IF (ok_windthrow) THEN
645          streamlining_c_leaf(:) = streamlining_c_leaf_mtc(pft_to_mtc(:))
646          streamlining_c_leafless(:) = streamlining_c_leafless_mtc(pft_to_mtc(:))
647          streamlining_n_leaf(:) = streamlining_n_leaf_mtc(pft_to_mtc(:))
648          streamlining_n_leafless(:) = streamlining_n_leafless_mtc(pft_to_mtc(:))
649          modulus_rupture(:) = modulus_rupture_mtc(pft_to_mtc(:))
650          f_knot(:) = f_knot_mtc(pft_to_mtc(:))
651          overturning_free_draining_shallow(:) = overturning_free_draining_shallow_mtc(pft_to_mtc(:))
652          overturning_free_draining_shallow_leafless(:) = overturning_free_draining_shallow_leafless_mtc(pft_to_mtc(:))
653          overturning_free_draining_deep(:) = overturning_free_draining_deep_mtc(pft_to_mtc(:))
654          overturning_free_draining_deep_leafless(:) = overturning_free_draining_deep_leafless_mtc(pft_to_mtc(:))
655          overturning_free_draining_average(:) = overturning_free_draining_average_mtc(pft_to_mtc(:))
656          overturning_free_draining_average_leafless(:) = overturning_free_draining_average_leafless_mtc(pft_to_mtc(:))
657          overturning_gleyed_shallow(:) = overturning_gleyed_shallow_mtc(pft_to_mtc(:))
658          overturning_gleyed_shallow_leafless(:) = overturning_gleyed_shallow_leafless_mtc(pft_to_mtc(:))
659          overturning_gleyed_deep(:) = overturning_gleyed_deep_mtc(pft_to_mtc(:))
660          overturning_gleyed_deep_leafless(:) = overturning_gleyed_deep_leafless_mtc(pft_to_mtc(:))
661          overturning_gleyed_average(:) = overturning_gleyed_average_mtc(pft_to_mtc(:))
662          overturning_gleyed_average_leafless(:) = overturning_gleyed_average_leafless_mtc(pft_to_mtc(:))
663          overturning_peaty_shallow(:) = overturning_peaty_shallow_mtc(pft_to_mtc(:))
664          overturning_peaty_shallow_leafless(:) = overturning_peaty_shallow_leafless_mtc(pft_to_mtc(:))
665          overturning_peaty_deep(:) = overturning_peaty_deep_mtc(pft_to_mtc(:))
666          overturning_peaty_deep_leafless(:) = overturning_peaty_deep_leafless_mtc(pft_to_mtc(:))
667          overturning_peaty_average(:) = overturning_peaty_average_mtc(pft_to_mtc(:))
668          overturning_peaty_average_leafless(:) = overturning_peaty_average_leafless_mtc(pft_to_mtc(:))
669          overturning_peat_shallow(:) = overturning_peat_shallow_mtc(pft_to_mtc(:))
670          overturning_peat_shallow_leafless(:) = overturning_peat_shallow_leafless_mtc(pft_to_mtc(:))
671          overturning_peat_deep(:) = overturning_peat_deep_mtc(pft_to_mtc(:))
672          overturning_peat_deep_leafless(:) = overturning_peat_deep_leafless_mtc(pft_to_mtc(:))
673          overturning_peat_average(:) = overturning_peat_average_mtc(pft_to_mtc(:))
674          overturning_peat_average_leafless(:) = overturning_peat_average_leafless_mtc(pft_to_mtc(:))
675          max_damage_further(:) = max_damage_further_mtc(pft_to_mtc(:))
676          max_damage_closer(:) = max_damage_closer_mtc(pft_to_mtc(:))
677          sfactor_further(:) = sfactor_further_mtc(pft_to_mtc(:))
678          sfactor_closer(:) = sfactor_closer_mtc(pft_to_mtc(:))
679          green_density(:) = green_density_mtc(pft_to_mtc(:))
680       END IF
681
682
683       !
684       ! SOM decomposition (stomate)
685       !
686       
687       LC_leaf(:)       = LC_leaf_mtc(pft_to_mtc(:))
688       LC_sapabove(:)   = LC_sapabove_mtc(pft_to_mtc(:))
689       LC_sapbelow(:)   = LC_sapbelow_mtc(pft_to_mtc(:))
690       LC_heartabove(:) = LC_heartabove_mtc(pft_to_mtc(:))
691       LC_heartbelow(:) = LC_heartbelow_mtc(pft_to_mtc(:))
692       LC_fruit(:)      = LC_fruit_mtc(pft_to_mtc(:))
693       LC_root(:)       = LC_root_mtc(pft_to_mtc(:))
694       LC_carbres(:)    = LC_carbres_mtc(pft_to_mtc(:))
695       LC_labile(:)     = LC_labile_mtc(pft_to_mtc(:))
696 
697       decomp_factor(:) = decomp_factor_mtc(pft_to_mtc(:))
698 
699       !
700       ! Stand structure
701       !
702       mass_ratio_heart_sap(:) = mass_ratio_heart_sap_mtc(pft_to_mtc(:))
703       canopy_cover = canopy_cover_mtc(pft_to_mtc(:))
704       nmaxplants(:) = nmaxplants_mtc(pft_to_mtc(:))
705       p_use_reserve(:) = p_use_reserve_mtc(pft_to_mtc(:))
706       height_init(:) = height_init_mtc(pft_to_mtc(:))
707       dia_init_min(:) = dia_init_min_mtc(pft_to_mtc(:))
708       dia_init_max(:) = dia_init_max_mtc(pft_to_mtc(:))
709       deleuze_a(:) = deleuze_a_mtc(pft_to_mtc(:))
710       deleuze_b(:) = deleuze_b_mtc(pft_to_mtc(:))
711       deleuze_p_all(:) = deleuze_p_all_mtc(pft_to_mtc(:))
712       deleuze_p_coppice(:) = deleuze_p_coppice_mtc(pft_to_mtc(:))
713       deleuze_power_a(:) = deleuze_power_a_mtc(pft_to_mtc(:))
714       alpha_self_thinning(:) = alpha_self_thinning_mtc(pft_to_mtc(:))
715       beta_self_thinning(:) = beta_self_thinning_mtc(pft_to_mtc(:))
716       fuelwood_diameter(:) = fuelwood_diameter_mtc(pft_to_mtc(:))
717       coppice_kill_be_wood(:) = coppice_kill_be_wood_mtc(pft_to_mtc(:))
718       largest_tree_dia(:) = largest_tree_dia_mtc(pft_to_mtc(:))
719       thinstrat(:) = thinstrat_mtc(pft_to_mtc(:))
720       taumin(:) = taumin_mtc(pft_to_mtc(:))
721       taumax(:) = taumax_mtc(pft_to_mtc(:))
722       a_rdi_upper_unman(:) =  a_rdi_upper_unman_mtc(pft_to_mtc(:))
723       b_rdi_upper_unman(:) =  b_rdi_upper_unman_mtc(pft_to_mtc(:))
724       c_rdi_upper_unman(:) =  c_rdi_upper_unman_mtc(pft_to_mtc(:))
725       d_rdi_upper_unman(:) =  d_rdi_upper_unman_mtc(pft_to_mtc(:))
726       a_rdi_lower_unman(:) =  a_rdi_lower_unman_mtc(pft_to_mtc(:))
727       b_rdi_lower_unman(:) =  b_rdi_lower_unman_mtc(pft_to_mtc(:))
728       c_rdi_lower_unman(:) =  c_rdi_lower_unman_mtc(pft_to_mtc(:))
729       d_rdi_lower_unman(:) =  d_rdi_lower_unman_mtc(pft_to_mtc(:))
730       a_rdi_upper_man(:) =  a_rdi_upper_man_mtc(pft_to_mtc(:))
731       b_rdi_upper_man(:) =  b_rdi_upper_man_mtc(pft_to_mtc(:))
732       c_rdi_upper_man(:) =  c_rdi_upper_man_mtc(pft_to_mtc(:))
733       d_rdi_upper_man(:) =  d_rdi_upper_man_mtc(pft_to_mtc(:))
734       a_rdi_lower_man(:) =  a_rdi_lower_man_mtc(pft_to_mtc(:))
735       b_rdi_lower_man(:) =  b_rdi_lower_man_mtc(pft_to_mtc(:))
736       c_rdi_lower_man(:) =  c_rdi_lower_man_mtc(pft_to_mtc(:))
737       d_rdi_lower_man(:) =  d_rdi_lower_man_mtc(pft_to_mtc(:))
738       branch_ratio(:) = branch_ratio_mtc(pft_to_mtc(:))
739       branch_harvest(:) = branch_harvest_mtc(pft_to_mtc(:))
740       coppice_diameter(:) = coppice_diameter_mtc(pft_to_mtc(:))
741       shoots_per_stool(:) = shoots_per_stool_mtc(pft_to_mtc(:))
742       src_rot_length(:) = src_rot_length_mtc(pft_to_mtc(:))
743       src_nrots(:) = src_nrots_mtc(pft_to_mtc(:))
744     
745       dens_target(:) = dens_target_mtc(pft_to_mtc(:))
746       m_dv(:) = m_dv_mtc(pft_to_mtc(:))
747       fruit_alloc(:) = fruit_alloc_mtc(pft_to_mtc(:))
748 
749       labile_reserve(:) = labile_reserve_mtc(pft_to_mtc(:))
750       evergreen_reserve(:) = evergreen_reserve_mtc(pft_to_mtc(:))
751       deciduous_reserve(:) = deciduous_reserve_mtc(pft_to_mtc(:))
752       senescense_reserve(:) = senescense_reserve_mtc(pft_to_mtc(:))
753       root_reserve(:) = root_reserve_mtc(pft_to_mtc(:))
754
755       fcn_wood(:) = fcn_wood_mtc(pft_to_mtc(:))
756       fcn_root(:) = fcn_root_mtc(pft_to_mtc(:))
757
758       !
759       ! Cropland management
760       !
761       harvest_ratio(:) = harvest_ratio_mtc(pft_to_mtc(:))
762
763    ENDIF !(ok_stomate)
764   
765    !! Following parameters are used with and without ok_stomate
766    nue_opt(:) = nue_opt_mtc(pft_to_mtc(:))
767    vmax_uptake(:,iammonium) = vmax_uptake_nh4_mtc(pft_to_mtc(:))
768    vmax_uptake(:,initrate) = vmax_uptake_no3_mtc(pft_to_mtc(:))
769    cn_leaf_min(:) = cn_leaf_min_mtc(pft_to_mtc(:))
770    cn_leaf_max(:) = cn_leaf_max_mtc(pft_to_mtc(:))
771    cn_leaf_init(:) = cn_leaf_init_mtc(pft_to_mtc(:))
772    ext_coeff_N(:) = ext_coeff_N_mtc(pft_to_mtc(:))
773    maint_resp_slope_c(:) = maint_resp_slope_c_mtc(pft_to_mtc(:))
774    maint_resp_slope_b(:) = maint_resp_slope_b_mtc(pft_to_mtc(:)) 
775    maint_resp_slope_a(:) = maint_resp_slope_a_mtc(pft_to_mtc(:)) 
776
777  END SUBROUTINE pft_parameters_init
778
779
780!! ================================================================================================================================
781!! SUBROUTINE   : pft_parameters_alloc
782!!
783!>\BRIEF         This subroutine allocates memory needed for the PFT parameters
784!! in function  of the flags activated. 
785!!
786!! DESCRIPTION  : None
787!!
788!! RECENT CHANGE(S): None
789!!
790!! MAIN OUTPUT VARIABLE(S): None
791!!
792!! REFERENCE(S) : None
793!!
794!! FLOWCHART    : None
795!! \n
796!_ ================================================================================================================================
797
798  SUBROUTINE pft_parameters_alloc()
799
800    IMPLICIT NONE
801
802    !! 0. Variables and parameters declaration
803
804    !! 0.1 Input variables
805
806    !! 0.4 Local variables
807
808    LOGICAL :: l_error                             !! Diagnostic boolean for error allocation (true/false)
809    INTEGER :: ier                                 !! Return value for memory allocation (0-N, unitless)
810
811    !_ ================================================================================================================================
812
813
814    !
815    ! 1. Parameters used anytime
816    !
817
818    l_error = .FALSE.
819
820    ALLOCATE(pft_to_mtc(nvm),stat=ier)
821    l_error = l_error .OR. (ier /= 0)
822    IF (l_error) THEN
823       WRITE(numout,*) ' Memory allocation error for pft_to_mtc. We stop. We need nvm words = ',nvm
824       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
825    END IF
826
827    ALLOCATE(PFT_name(nvm),stat=ier)
828    l_error = l_error .OR. (ier /= 0)
829    IF (l_error) THEN
830       WRITE(numout,*) ' Memory allocation error for PFT_name. We stop. We need nvm words = ',nvm
831       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
832    END IF
833
834    ALLOCATE(height_presc(nvm),stat=ier)
835    l_error = l_error .OR. (ier /= 0)
836    IF (l_error) THEN
837       WRITE(numout,*) ' Memory allocation error for height_presc. We stop. We need nvm words = ',nvm
838       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
839    END IF
840
841    ALLOCATE(z0_over_height(nvm),stat=ier)
842    l_error = l_error .OR. (ier /= 0)
843    IF (l_error) THEN
844       WRITE(numout,*) ' Memory allocation error for z0_over_height. We stop. We need nvm words = ',nvm
845       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
846    END IF
847
848    ALLOCATE(ratio_z0m_z0h(nvm),stat=ier)
849    l_error = l_error .OR. (ier /= 0)
850    IF (l_error) THEN
851       WRITE(numout,*) ' Memory allocation error for ratio_z0m_z0h. We stop. We need nvm words = ',nvm
852       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
853    END IF
854
855    ALLOCATE(is_tree(nvm),stat=ier)
856    l_error = l_error .OR. (ier /= 0)
857    IF (l_error) THEN
858       WRITE(numout,*) ' Memory allocation error for is_tree. We stop. We need nvm words = ',nvm
859       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
860    END IF
861
862    ALLOCATE(natural(nvm),stat=ier)
863    l_error = l_error .OR. (ier /= 0)
864    IF (l_error) THEN
865       WRITE(numout,*) ' Memory allocation error for natural. We stop. We need nvm words = ',nvm
866       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
867    END IF
868
869    ALLOCATE(is_c4(nvm),stat=ier)
870    l_error = l_error .OR. (ier /= 0)
871    IF (l_error) THEN
872       WRITE(numout,*) ' Memory allocation error for is_c4. We stop. We need nvm words = ',nvm
873       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
874    END IF
875
876    ALLOCATE(humcste(nvm),stat=ier)
877    l_error = l_error .OR. (ier /= 0)
878    IF (l_error) THEN
879       WRITE(numout,*) ' Memory allocation error for humcste. We stop. We need nvm words = ',nvm
880       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
881    END IF
882
883    ALLOCATE(max_root_depth(nvm),stat=ier)
884    l_error = l_error .OR. (ier /= 0)
885    IF (l_error) THEN
886       WRITE(numout,*) ' Memory allocation error for max_root_depth. We stop. We need nvm words = ',nvm
887       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
888    END IF
889
890    ALLOCATE(downregulation_co2_coeff(nvm),stat=ier)
891    l_error = l_error .OR. (ier /= 0)
892    IF (l_error) THEN
893       WRITE(numout,*) ' Memory allocation error for downregulation_co2_coeff. We stop. We need nvm words = ',nvm
894       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
895    END IF
896
897    ALLOCATE(E_KmC(nvm),stat=ier)
898    l_error = l_error .OR. (ier /= 0)
899    IF (l_error) THEN
900       WRITE(numout,*) ' Memory allocation error for E_KmC. We stop. We need nvm words = ',nvm
901       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
902    END IF
903
904    ALLOCATE(E_KmO(nvm),stat=ier)
905    l_error = l_error .OR. (ier /= 0)
906    IF (l_error) THEN
907       WRITE(numout,*) ' Memory allocation error for E_KmO. We stop. We need nvm words = ',nvm
908       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
909    END IF
910
911    ALLOCATE(E_Sco(nvm),stat=ier)
912    l_error = l_error .OR. (ier /= 0)
913    IF (l_error) THEN
914       WRITE(numout,*) ' Memory allocation error for E_Sco. We stop. We need nvm words = ',nvm
915       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
916    END IF
917
918    ALLOCATE(E_gamma_star(nvm),stat=ier)
919    l_error = l_error .OR. (ier /= 0)
920    IF (l_error) THEN
921       WRITE(numout,*) ' Memory allocation error for E_gamma_star. We stop. We need nvm words = ',nvm
922       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
923    END IF
924
925    ALLOCATE(E_vcmax(nvm),stat=ier)
926    l_error = l_error .OR. (ier /= 0)
927    IF (l_error) THEN
928       WRITE(numout,*) ' Memory allocation error for E_Vcmax. We stop. We need nvm words = ',nvm
929       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
930    END IF
931
932    ALLOCATE(E_Jmax(nvm),stat=ier)
933    l_error = l_error .OR. (ier /= 0)
934    IF (l_error) THEN
935       WRITE(numout,*) ' Memory allocation error for E_Jmax. We stop. We need nvm words = ',nvm
936       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
937    END IF
938
939    ALLOCATE(aSV(nvm),stat=ier)
940    l_error = l_error .OR. (ier /= 0)
941    IF (l_error) THEN
942       WRITE(numout,*) ' Memory allocation error for aSV. We stop. We need nvm words = ',nvm
943       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
944    END IF
945
946    ALLOCATE(bSV(nvm),stat=ier)
947    l_error = l_error .OR. (ier /= 0)
948    IF (l_error) THEN
949       WRITE(numout,*) ' Memory allocation error for bSV. We stop. We need nvm words = ',nvm
950       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
951    END IF
952
953    ALLOCATE(tphoto_min(nvm),stat=ier)
954    l_error = l_error .OR. (ier /= 0)
955    IF (l_error) THEN
956       WRITE(numout,*) ' Memory allocation error for tphoto_min. We stop. We need nvm words = ',nvm
957       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
958    END IF
959
960    ALLOCATE(tphoto_max(nvm),stat=ier)
961    l_error = l_error .OR. (ier /= 0)
962    IF (l_error) THEN
963       WRITE(numout,*) ' Memory allocation error for tphoto_max. We stop. We need nvm words = ',nvm
964       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
965    END IF
966
967    ALLOCATE(aSJ(nvm),stat=ier)
968    l_error = l_error .OR. (ier /= 0)
969    IF (l_error) THEN
970       WRITE(numout,*) ' Memory allocation error for aSJ. We stop. We need nvm words = ',nvm
971       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
972    END IF
973
974    ALLOCATE(bSJ(nvm),stat=ier)
975    l_error = l_error .OR. (ier /= 0)
976    IF (l_error) THEN
977       WRITE(numout,*) ' Memory allocation error for bSJ. We stop. We need nvm words = ',nvm
978       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
979    END IF
980
981    ALLOCATE(D_Vcmax(nvm),stat=ier)
982    l_error = l_error .OR. (ier /= 0)
983    IF (l_error) THEN
984       WRITE(numout,*) ' Memory allocation error for D_Vcmax. We stop. We need nvm words = ',nvm
985       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
986    END IF
987
988    ALLOCATE(D_Jmax(nvm),stat=ier)
989    l_error = l_error .OR. (ier /= 0)
990    IF (l_error) THEN
991       WRITE(numout,*) ' Memory allocation error for D_Jmax. We stop. We need nvm words = ',nvm
992       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
993    END IF
994
995    ALLOCATE(E_gm(nvm),stat=ier) 
996    l_error = l_error .OR. (ier /= 0) 
997    IF (l_error) THEN
998       WRITE(numout,*) ' Memory allocation error for E_gm. We stop. We need nvm words = ',nvm 
999       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') 
1000    END IF
1001   
1002    ALLOCATE(S_gm(nvm),stat=ier) 
1003    l_error = l_error .OR. (ier /= 0) 
1004    IF (l_error) THEN
1005       WRITE(numout,*) ' Memory allocation error for S_gm. We stop. We need nvm words = ',nvm 
1006       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') 
1007    END IF
1008   
1009    ALLOCATE(D_gm(nvm),stat=ier) 
1010    l_error = l_error .OR. (ier /= 0) 
1011    IF (l_error) THEN
1012       WRITE(numout,*) ' Memory allocation error for D_gm. We stop. We need nvm words = ',nvm 
1013       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') 
1014    END IF
1015   
1016    ALLOCATE(E_Rd(nvm),stat=ier)
1017    l_error = l_error .OR. (ier /= 0)
1018    IF (l_error) THEN
1019       WRITE(numout,*) ' Memory allocation error for E_Rd. We stop. We need nvm words = ',nvm
1020       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1021    END IF
1022
1023    ALLOCATE(Vcmax25(nvm),stat=ier)
1024    l_error = l_error .OR. (ier /= 0)
1025    IF (l_error) THEN
1026       WRITE(numout,*) ' Memory allocation error for Vcmax25. We stop. We need nvm words = ',nvm
1027       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1028    END IF
1029
1030    ALLOCATE(arJV(nvm),stat=ier)
1031    l_error = l_error .OR. (ier /= 0)
1032    IF (l_error) THEN
1033       WRITE(numout,*) ' Memory allocation error for arJV. We stop. We need nvm words = ',nvm
1034       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1035    END IF
1036
1037    ALLOCATE(brJV(nvm),stat=ier)
1038    l_error = l_error .OR. (ier /= 0)
1039    IF (l_error) THEN
1040       WRITE(numout,*) ' Memory allocation error for brJV. We stop. We need nvm words = ',nvm
1041       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1042    END IF
1043
1044    ALLOCATE(KmC25(nvm),stat=ier)
1045    l_error = l_error .OR. (ier /= 0)
1046    IF (l_error) THEN
1047       WRITE(numout,*) ' Memory allocation error for KmC25. We stop. We need nvm words = ',nvm
1048       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1049    END IF
1050
1051    ALLOCATE(KmO25(nvm),stat=ier)
1052    l_error = l_error .OR. (ier /= 0)
1053    IF (l_error) THEN
1054       WRITE(numout,*) ' Memory allocation error for KmO25. We stop. We need nvm words = ',nvm
1055       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1056    END IF
1057
1058    ALLOCATE(Sco25(nvm),stat=ier)
1059    l_error = l_error .OR. (ier /= 0)
1060    IF (l_error) THEN
1061       WRITE(numout,*) ' Memory allocation error for Sco25. We stop. We need nvm words = ',nvm
1062       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1063    END IF
1064   
1065    ALLOCATE(gm25(nvm),stat=ier) 
1066    l_error = l_error .OR. (ier /= 0) 
1067    IF (l_error) THEN
1068       WRITE(numout,*) ' Memory allocation error for gm25. We stop. We need nvm words = ',nvm 
1069       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','') 
1070    END IF
1071
1072    ALLOCATE(gamma_star25(nvm),stat=ier)
1073    l_error = l_error .OR. (ier /= 0)
1074    IF (l_error) THEN
1075       WRITE(numout,*) ' Memory allocation error for gamma_star25. We stop. We need nvm words = ',nvm
1076       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1077    END IF
1078
1079    ALLOCATE(a1(nvm),stat=ier)
1080    l_error = l_error .OR. (ier /= 0)
1081    IF (l_error) THEN
1082       WRITE(numout,*) ' Memory allocation error for a1. We stop. We need nvm words = ',nvm
1083       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1084    END IF
1085
1086    ALLOCATE(b1(nvm),stat=ier)
1087    l_error = l_error .OR. (ier /= 0)
1088    IF (l_error) THEN
1089       WRITE(numout,*) ' Memory allocation error for b1. We stop. We need nvm words = ',nvm
1090       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1091    END IF
1092
1093    ALLOCATE(g0(nvm),stat=ier)
1094    l_error = l_error .OR. (ier /= 0)
1095    IF (l_error) THEN
1096       WRITE(numout,*) ' Memory allocation error for g0. We stop. We need nvm words = ',nvm
1097       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1098    END IF
1099
1100    ALLOCATE(h_protons(nvm),stat=ier)
1101    l_error = l_error .OR. (ier /= 0)
1102    IF (l_error) THEN
1103       WRITE(numout,*) ' Memory allocation error for h_protons. We stop. We need nvm words = ',nvm
1104       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1105    END IF
1106
1107    ALLOCATE(fpsir(nvm),stat=ier)
1108    l_error = l_error .OR. (ier /= 0)
1109    IF (l_error) THEN
1110       WRITE(numout,*) ' Memory allocation error for fpsir. We stop. We need nvm words = ',nvm
1111       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1112    END IF
1113
1114    ALLOCATE(fQ(nvm),stat=ier)
1115    l_error = l_error .OR. (ier /= 0)
1116    IF (l_error) THEN
1117       WRITE(numout,*) ' Memory allocation error for fQ. We stop. We need nvm words = ',nvm
1118       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1119    END IF
1120
1121    ALLOCATE(fpseudo(nvm),stat=ier)
1122    l_error = l_error .OR. (ier /= 0)
1123    IF (l_error) THEN
1124       WRITE(numout,*) ' Memory allocation error for fpseudo. We stop. We need nvm words = ',nvm
1125       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1126    END IF
1127
1128    ALLOCATE(kp(nvm),stat=ier)
1129    l_error = l_error .OR. (ier /= 0)
1130    IF (l_error) THEN
1131       WRITE(numout,*) ' Memory allocation error for kp. We stop. We need nvm words = ',nvm
1132       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1133    END IF
1134
1135    ALLOCATE(alpha(nvm),stat=ier)
1136    l_error = l_error .OR. (ier /= 0)
1137    IF (l_error) THEN
1138       WRITE(numout,*) ' Memory allocation error for alpha. We stop. We need nvm words = ',nvm
1139       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1140    END IF
1141
1142    ALLOCATE(gbs(nvm),stat=ier)
1143    l_error = l_error .OR. (ier /= 0)
1144    IF (l_error) THEN
1145       WRITE(numout,*) ' Memory allocation error for gbs. We stop. We need nvm words = ',nvm
1146       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1147    END IF
1148
1149    ALLOCATE(theta(nvm),stat=ier)
1150    l_error = l_error .OR. (ier /= 0)
1151    IF (l_error) THEN
1152       WRITE(numout,*) ' Memory allocation error for theta. We stop. We need nvm words = ',nvm
1153       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1154    END IF
1155
1156    ALLOCATE(alpha_LL(nvm),stat=ier)
1157    l_error = l_error .OR. (ier /= 0)
1158    IF (l_error) THEN
1159       WRITE(numout,*) ' Memory allocation error for alpha_LL. We stop. We need nvm words = ',nvm
1160       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1161    END IF
1162
1163    ALLOCATE(stress_vcmax(nvm),stat=ier)
1164    l_error = l_error .OR. (ier /= 0)
1165    IF (l_error) THEN
1166       WRITE(numout,*) ' Memory allocation error for stress_vcmax. We stop. We need nvm words = ',nvm
1167       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1168    END IF
1169   
1170    ALLOCATE(stress_gs(nvm),stat=ier)
1171    l_error = l_error .OR. (ier /= 0)
1172    IF (l_error) THEN
1173       WRITE(numout,*) ' Memory allocation error for stress_gs. We stop. We need nvm words = ',nvm
1174       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1175    END IF
1176   
1177    ALLOCATE(stress_gm(nvm),stat=ier)
1178    l_error = l_error .OR. (ier /= 0)
1179    IF (l_error) THEN
1180       WRITE(numout,*) ' Memory allocation error for stress_gm. We stop. We need nvm words = ',nvm
1181       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1182    END IF
1183
1184    ALLOCATE(ext_coeff(nvm),stat=ier)
1185    l_error = l_error .OR. (ier /= 0)
1186    IF (l_error) THEN
1187       WRITE(numout,*) ' Memory allocation error for ext_coeff. We stop. We need nvm words = ',nvm
1188       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1189    END IF
1190
1191    ALLOCATE(ext_coeff_vegetfrac(nvm),stat=ier)
1192    l_error = l_error .OR. (ier /= 0)
1193    IF (l_error) THEN
1194       WRITE(numout,*) ' Memory allocation error for ext_coeff_vegetfrac. We stop. We need nvm words = ',nvm
1195       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1196    END IF
1197
1198    ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier)
1199    l_error = l_error .OR. (ier /= 0)
1200    IF (l_error) THEN
1201       WRITE(numout,*) ' Memory allocation error for veget_ori_fixed_test_1. We stop. We need nvm words = ',nvm
1202       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1203    END IF
1204
1205    ALLOCATE(llaimax(nvm),stat=ier)
1206    l_error = l_error .OR. (ier /= 0)
1207    IF (l_error) THEN
1208       WRITE(numout,*) ' Memory allocation error for llaimax. We stop. We need nvm words = ',nvm
1209       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1210    END IF
1211
1212    ALLOCATE(llaimin(nvm),stat=ier)
1213    l_error = l_error .OR. (ier /= 0)
1214    IF (l_error) THEN
1215       WRITE(numout,*) ' Memory allocation error for llaimin. We stop. We need nvm words = ',nvm
1216       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1217    END IF
1218
1219    ALLOCATE(type_of_lai(nvm),stat=ier)
1220    l_error = l_error .OR. (ier /= 0)
1221    IF (l_error) THEN
1222       WRITE(numout,*) ' Memory allocation error for type_of_lai. We stop. We need nvm words = ',nvm
1223       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1224    END IF
1225
1226    ALLOCATE(vcmax_fix(nvm),stat=ier)
1227    l_error = l_error .OR. (ier /= 0)
1228    IF (l_error) THEN
1229       WRITE(numout,*) ' Memory allocation error for vcmax_fix. We stop. We need nvm words = ',nvm
1230       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1231    END IF
1232
1233    ALLOCATE(pref_soil_veg(nvm),stat=ier)
1234    l_error = l_error .OR. (ier /= 0)
1235    IF (l_error) THEN
1236       WRITE(numout,*) ' Memory allocation error for pref_soil_veg. We stop. We need nvm words = ',nvm
1237       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1238    END IF
1239
1240    ALLOCATE(agec_group(nvm),stat=ier)
1241    l_error = l_error .OR. (ier /= 0)
1242    IF (l_error) THEN
1243       WRITE(numout,*) ' Memory allocation error for agec_group. We stop. We need nvm words = ',nvm
1244       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1245    END IF
1246   
1247    ALLOCATE(start_index(nvm),stat=ier)
1248    l_error = l_error .OR. (ier /= 0)
1249    IF (l_error) THEN
1250       WRITE(numout,*) ' Memory allocation error for start_index. We stop. We need nvm words = ',nvm
1251       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1252    END IF
1253   
1254    ALLOCATE(nagec_pft(nvm),stat=ier)
1255    l_error = l_error .OR. (ier /= 0)
1256    IF (l_error) THEN
1257       WRITE(numout,*) ' Memory allocation error for nagec_pft. We stop. We need nvm words = ',nvm
1258       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1259    END IF
1260
1261    ALLOCATE(leaf_tab(nvm),stat=ier)
1262    l_error = l_error .OR. (ier /= 0)
1263    IF (l_error) THEN
1264       WRITE(numout,*) ' Memory allocation error for leaf_tab. We stop. We need nvm words = ',nvm
1265       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1266    END IF
1267
1268    ALLOCATE(pheno_model(nvm),stat=ier)
1269    l_error = l_error .OR. (ier /= 0)
1270    IF (l_error) THEN
1271       WRITE(numout,*) ' Memory allocation error for pheno_model. We stop. We need nvm words = ',nvm
1272       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1273    END IF
1274
1275    ALLOCATE(is_deciduous(nvm),stat=ier) 
1276    l_error = l_error .OR. (ier /= 0) 
1277    IF (l_error) THEN
1278       WRITE(numout,*) ' Memory allocation error for is_deciduous. We stop. We need nvm words = ',nvm
1279       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1280    END IF
1281
1282    ALLOCATE(is_evergreen(nvm),stat=ier) 
1283    l_error = l_error .OR. (ier /= 0)
1284    IF (l_error) THEN
1285       WRITE(numout,*) ' Memory allocation error for is_evergreen. We stop. We need nvm words = ',nvm
1286       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1287    END IF
1288
1289    ALLOCATE(is_needleleaf(nvm),stat=ier) 
1290    l_error = l_error .OR. (ier /= 0)
1291    IF (l_error) THEN
1292       WRITE(numout,*) ' Memory allocation error for is_needleleaf. We stop. We need nvm words = ',nvm
1293       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1294    END IF
1295
1296    ALLOCATE(is_tropical(nvm),stat=ier)   
1297    l_error = l_error .OR. (ier /= 0)
1298    IF (l_error) THEN
1299       WRITE(numout,*) ' Memory allocation error for is_tropical. We stop. We need nvm words = ',nvm
1300       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1301    END IF
1302
1303    ALLOCATE(is_temperate(nvm),stat=ier)   
1304    l_error = l_error .OR. (ier /= 0)
1305    IF (l_error) THEN
1306       WRITE(numout,*) ' Memory allocation error for is_temperate. We stop. We need nvm words = ',nvm
1307       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1308    END IF
1309   
1310    ALLOCATE(is_boreal(nvm),stat=ier)   
1311    l_error = l_error .OR. (ier /= 0)
1312    IF (l_error) THEN
1313       WRITE(numout,*) ' Memory allocation error for is_boreal. We stop. We need nvm words = ',nvm
1314       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1315    END IF
1316
1317    !
1318    ! 2. Parameters used if ok_sechiba only
1319    !
1320    IF ( ok_sechiba ) THEN
1321
1322       l_error = .FALSE.
1323
1324       ALLOCATE(rstruct_const(nvm),stat=ier)
1325       l_error = l_error .OR. (ier /= 0)
1326       IF (l_error) THEN
1327          WRITE(numout,*) ' Memory allocation error for rstruct_const. We stop. We need nvm words = ',nvm
1328          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1329       END IF
1330
1331       ALLOCATE(kzero(nvm),stat=ier)
1332       l_error = l_error .OR. (ier /= 0)
1333       IF (l_error) THEN
1334          WRITE(numout,*) ' Memory allocation error for kzero. We stop. We need nvm words = ',nvm
1335          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1336       END IF
1337
1338       ALLOCATE(rveg_pft(nvm),stat=ier)
1339       l_error = l_error .OR. (ier /= 0)
1340       IF (l_error) THEN
1341          WRITE(numout,*) ' Memory allocation error for rveg_pft. We stop. We need nvm words = ',nvm
1342          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1343       END IF
1344
1345       ALLOCATE(wmax_veg(nvm),stat=ier)
1346       l_error = l_error .OR. (ier /= 0)
1347       IF (l_error) THEN
1348          WRITE(numout,*) ' Memory allocation error for wmax_veg. We stop. We need nvm words = ',nvm
1349          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1350       END IF
1351
1352       ALLOCATE(throughfall_by_pft(nvm),stat=ier)
1353       l_error = l_error .OR. (ier /= 0)
1354       IF (l_error) THEN
1355          WRITE(numout,*) ' Memory allocation error for throughfall_by_pft. We stop. We need nvm words = ',nvm
1356          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1357       END IF
1358
1359       ALLOCATE(snowa_aged_vis(nvm),stat=ier)
1360       l_error = l_error .OR. (ier /= 0)
1361       IF (l_error) THEN
1362          WRITE(numout,*) ' Memory allocation error for snowa_aged_vis. We stop. We need nvm words = ',nvm
1363          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1364       END IF
1365
1366       ALLOCATE(snowa_aged_nir(nvm),stat=ier)
1367       l_error = l_error .OR. (ier /= 0)
1368       IF (l_error) THEN
1369          WRITE(numout,*) ' Memory allocation error for snowa_aged_nir. We stop. We need nvm words = ',nvm
1370          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1371       END IF
1372
1373       ALLOCATE(snowa_dec_vis(nvm),stat=ier)
1374       l_error = l_error .OR. (ier /= 0)
1375       IF (l_error) THEN
1376          WRITE(numout,*) ' Memory allocation error for snowa_dec_vis. We stop. We need nvm words = ',nvm
1377          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1378       END IF
1379
1380       ALLOCATE(snowa_dec_nir(nvm),stat=ier)
1381       l_error = l_error .OR. (ier /= 0)
1382       IF (l_error) THEN
1383          WRITE(numout,*) ' Memory allocation error for snowa_dec_nir. We stop. We need nvm words = ',nvm
1384          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1385       END IF
1386
1387       ALLOCATE(alb_leaf_vis(nvm),stat=ier)
1388       l_error = l_error .OR. (ier /= 0)
1389       IF (l_error) THEN
1390          WRITE(numout,*) ' Memory allocation error for alb_leaf_vis. We stop. We need nvm words = ',nvm
1391          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1392       END IF
1393
1394       ALLOCATE(alb_leaf_nir(nvm),stat=ier)
1395       l_error = l_error .OR. (ier /= 0)
1396       IF (l_error) THEN
1397          WRITE(numout,*) ' Memory allocation error for alb_leaf_nir. We stop. We need nvm words = ',nvm
1398          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1399       END IF
1400
1401       ALLOCATE(leaf_ssa(nvm,n_spectralbands),stat=ier)
1402       l_error = l_error .OR. (ier /= 0)
1403       IF (l_error) THEN
1404          WRITE(numout,*) ' Memory allocation error for leaf_ssa. We stop. We need nvm*n_spectralbands words = ',&
1405               nvm*n_spectralbands
1406          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1407       END IF
1408
1409       ALLOCATE(leaf_psd(nvm,n_spectralbands),stat=ier)
1410       l_error = l_error .OR. (ier /= 0)
1411       IF (l_error) THEN
1412          WRITE(numout,*) ' Memory allocation error for leaf_psd. We stop. We need nvm*n_spectralbands words = ',&
1413               nvm*n_spectralbands
1414          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1415       END IF
1416       
1417       ALLOCATE(bgd_reflectance(nvm,n_spectralbands),stat=ier)
1418       l_error = l_error .OR. (ier /= 0)
1419       IF (l_error) THEN
1420          WRITE(numout,*) ' Memory allocation error for bgd_reflectance. We need nvm*n_spectralbands words = ',&
1421               nvm*n_spectralbands
1422          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1423       END IF
1424       
1425       ALLOCATE(leaf_to_shoot_clumping(nvm),stat=ier)
1426       l_error = l_error .OR. (ier /= 0)
1427       IF (l_error) THEN
1428          WRITE(numout,*) ' Memory allocation error for leaf_to_shoot_clumping. We need nvm words = ',&
1429               nvm
1430          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1431       END IF
1432       
1433       ALLOCATE(lai_correction_factor(nvm),stat=ier)
1434       l_error = l_error .OR. (ier /= 0)
1435       IF (l_error) THEN
1436          WRITE(numout,*) ' Memory allocation error for lai_correction_factor. We need nvm words = ',&
1437               nvm
1438          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1439       END IF
1440       
1441       ALLOCATE(min_level_sep(nvm),stat=ier)
1442       l_error = l_error .OR. (ier /= 0)
1443       IF (l_error) THEN
1444          WRITE(numout,*) ' Memory allocation error for min_level_sep. We need nvm words = ',&
1445               nvm
1446          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1447       END IF
1448       
1449       ALLOCATE(lai_top(nvm),stat=ier)
1450       l_error = l_error .OR. (ier /= 0)
1451       IF (l_error) THEN
1452          WRITE(numout,*) ' Memory allocation error for lai_top. We need nvm words = ',&
1453               nvm
1454          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1455       END IF
1456       
1457       !
1458       ! Hydraulic architecture
1459       !       
1460       ALLOCATE(k_leaf(nvm),stat=ier)
1461       l_error = l_error .OR. (ier /= 0)
1462       IF (l_error) THEN
1463          WRITE(numout,*) ' Memory allocation error for k_leaf. We stop. We need nvm words = ',nvm
1464          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1465       END IF
1466
1467         ALLOCATE(k_root(nvm),stat=ier)
1468       l_error = l_error .OR. (ier /= 0)
1469       IF (l_error) THEN
1470          WRITE(numout,*) ' Memory allocation error for k_root. We stop. We need nvm words = ',nvm
1471          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1472       END IF
1473
1474       ALLOCATE(k_belowground(nvm),stat=ier)
1475       l_error = l_error .OR. (ier /= 0)
1476       IF (l_error) THEN
1477          WRITE(numout,*) ' Memory allocation error for k_belowground. We stop. We need nvm words = ',nvm
1478          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1479       END IF
1480       
1481       ALLOCATE(k_sap(nvm),stat=ier)
1482       l_error = l_error .OR. (ier /= 0)
1483       IF (l_error) THEN
1484          WRITE(numout,*) ' Memory allocation error for k_sap. We stop. We need nvm words = ',nvm
1485          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1486       END IF
1487       
1488       ALLOCATE(psi_leaf(nvm),stat=ier)
1489       l_error = l_error .OR. (ier /= 0)
1490       IF (l_error) THEN
1491          WRITE(numout,*) ' Memory allocation error for psi_leaf. We stop. We need nvm words = ',nvm
1492          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1493       END IF
1494       
1495       ALLOCATE(psi_50(nvm),stat=ier)
1496       l_error = l_error .OR. (ier /= 0)
1497       IF (l_error) THEN
1498          WRITE(numout,*) ' Memory allocation error for psi_50. We stop. We need nvm words = ',nvm
1499          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1500       END IF
1501       
1502       ALLOCATE(c_cavitation(nvm),stat=ier)
1503       l_error = l_error .OR. (ier /= 0)
1504       IF (l_error) THEN
1505          WRITE(numout,*) ' Memory allocation error for c_cavitation. We stop. We need nvm words = ',nvm
1506          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1507       END IF
1508       
1509       ALLOCATE(srl(nvm),stat=ier)
1510       l_error = l_error .OR. (ier /= 0)
1511       IF (l_error) THEN
1512          WRITE(numout,*) ' Memory allocation error for srl. We stop.We need nvm words = ',nvm
1513          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1514       END IF
1515       
1516       ALLOCATE(r_froot(nvm),stat=ier)
1517       l_error = l_error .OR. (ier /= 0)
1518       IF (l_error) THEN
1519          WRITE(numout,*) ' Memory allocation error for r_froot. We stop.We need nvmwords = ',nvm
1520          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1521       END IF
1522
1523       ALLOCATE(psi_root(nvm),stat=ier)
1524       l_error = l_error .OR. (ier /= 0)
1525       IF (l_error) THEN
1526          WRITE(numout,*) ' Memory allocation error for psi_root. We stop.We need nvmwords = ',nvm
1527          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1528       END IF
1529
1530       ALLOCATE(crown_to_height(nvm),stat=ier)
1531       l_error = l_error .OR. (ier /= 0)
1532       IF (l_error) THEN
1533          WRITE(numout,*) ' Memory allocation error for crown_to_height. We stop. We need nvm words = ',nvm
1534          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1535       END IF
1536
1537       ALLOCATE(crown_vertohor_dia(nvm),stat=ier)
1538       l_error = l_error .OR. (ier /= 0)
1539       IF (l_error) THEN
1540          WRITE(numout,*) ' Memory allocation error for crown_vertohor_dia. We stop. We need nvm words = ',nvm
1541          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1542       END IF
1543
1544       ALLOCATE(pipe_density(nvm),stat=ier)   
1545       l_error = l_error .OR. (ier /= 0)
1546       IF (l_error) THEN
1547          WRITE(numout,*) ' Memory allocation error for pipe_density. We stop. We need nvm words = ',nvm
1548          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1549       END IF
1550       
1551       ALLOCATE(tree_ff(nvm),stat=ier)   
1552       l_error = l_error .OR. (ier /= 0)
1553       IF (l_error) THEN
1554          WRITE(numout,*) ' Memory allocation error for tree_ff. We stop. We need nvm words = ',nvm
1555          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1556       END IF
1557       
1558       ALLOCATE(pipe_tune2(nvm),stat=ier)   
1559       l_error = l_error .OR. (ier /= 0)
1560       IF (l_error) THEN
1561          WRITE(numout,*) ' Memory allocation error for pipe_tune2. We stop. We need nvm words = ',nvm
1562          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1563       END IF
1564       
1565       ALLOCATE(pipe_tune3(nvm),stat=ier)   
1566       l_error = l_error .OR. (ier /= 0)
1567       IF (l_error) THEN
1568          WRITE(numout,*) ' Memory allocation error for pipe_tune3. We stop. We need nvm words = ',nvm
1569          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1570       END IF
1571
1572        ALLOCATE(pipe_tune4(nvm),stat=ier)   
1573       l_error = l_error .OR. (ier /= 0)
1574       IF (l_error) THEN
1575          WRITE(numout,*) ' Memory allocation error for pipe_tune4. We stop. We need nvm words = ',nvm
1576          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1577       END IF
1578       
1579       ALLOCATE(pipe_k1(nvm),stat=ier)   
1580       l_error = l_error .OR. (ier /= 0)
1581       IF (l_error) THEN
1582          WRITE(numout,*) ' Memory allocation error for pipe_k1. We stop. We need nvm words = ',nvm
1583          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1584       END IF
1585       
1586       ALLOCATE(sla(nvm),stat=ier)
1587       l_error = l_error .OR. (ier /= 0)
1588       IF (l_error) THEN
1589          WRITE(numout,*) ' Memory allocation error for sla. We stop. We need nvm words = ',nvm
1590          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1591       END IF
1592
1593       ALLOCATE(slainit(nvm),stat=ier)
1594       l_error = l_error .OR. (ier /= 0)
1595       IF (l_error) THEN
1596          WRITE(numout,*) ' Memory allocation error for slainit. We stop. We need nvm words = ',nvm
1597          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1598       END IF
1599
1600        ALLOCATE(lai_to_height(nvm),stat=ier)
1601       l_error = l_error .OR. (ier /= 0)
1602       IF (l_error) THEN
1603          WRITE(numout,*) ' Memory allocation error for lai_to_height. We stop. We need nvm words = ',nvm
1604          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1605       END IF
1606
1607       IF( ok_bvoc ) THEN
1608
1609          l_error = .FALSE.
1610
1611          ALLOCATE(em_factor_isoprene(nvm),stat=ier)
1612          l_error = l_error .OR. (ier /= 0) 
1613          IF (l_error) THEN
1614             WRITE(numout,*) ' Memory allocation error for em_factor_isoprene. We stop. We need nvm words = ',nvm
1615             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1616          END IF
1617
1618          ALLOCATE(em_factor_monoterpene(nvm),stat=ier)
1619          l_error = l_error .OR. (ier /= 0) 
1620          IF (l_error) THEN
1621             WRITE(numout,*) ' Memory allocation error for em_factor_monoterpene. We stop. We need nvm words = ',nvm
1622             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1623          END IF
1624
1625          ALLOCATE(em_factor_apinene(nvm),stat=ier)
1626          l_error = l_error .OR. (ier /= 0) 
1627          IF (l_error) THEN
1628             WRITE(numout,*) ' Memory allocation error for em_factor_apinene. We stop. We need nvm words = ',nvm
1629             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1630          END IF
1631
1632          ALLOCATE(em_factor_bpinene(nvm),stat=ier)
1633          l_error = l_error .OR. (ier /= 0) 
1634          IF (l_error) THEN
1635             WRITE(numout,*) ' Memory allocation error for em_factor_bpinene. We stop. We need nvm words = ',nvm
1636             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1637          END IF
1638
1639          ALLOCATE(em_factor_limonene(nvm),stat=ier)
1640          l_error = l_error .OR. (ier /= 0) 
1641          IF (l_error) THEN
1642             WRITE(numout,*) ' Memory allocation error for em_factor_limonene. We stop. We need nvm words = ',nvm
1643             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1644          END IF
1645
1646          ALLOCATE(em_factor_myrcene(nvm),stat=ier)
1647          l_error = l_error .OR. (ier /= 0) 
1648          IF (l_error) THEN
1649             WRITE(numout,*) ' Memory allocation error for em_factor_myrcene. We stop. We need nvm words = ',nvm
1650             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1651          END IF
1652
1653          ALLOCATE(em_factor_sabinene(nvm),stat=ier)
1654          l_error = l_error .OR. (ier /= 0) 
1655          IF (l_error) THEN
1656             WRITE(numout,*) ' Memory allocation error for em_factor_sabinene. We stop. We need nvm words = ',nvm
1657             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1658          END IF
1659
1660          ALLOCATE(em_factor_camphene(nvm),stat=ier)
1661          l_error = l_error .OR. (ier /= 0) 
1662          IF (l_error) THEN
1663             WRITE(numout,*) ' Memory allocation error for em_factor_camphene. We stop. We need nvm words = ',nvm
1664             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1665          END IF
1666
1667          ALLOCATE(em_factor_3carene(nvm),stat=ier)
1668          l_error = l_error .OR. (ier /= 0) 
1669          IF (l_error) THEN
1670             WRITE(numout,*) ' Memory allocation error for em_factor_3carene. We stop. We need nvm words = ',nvm
1671             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1672          END IF
1673
1674          ALLOCATE(em_factor_tbocimene(nvm),stat=ier)
1675          l_error = l_error .OR. (ier /= 0) 
1676          IF (l_error) THEN
1677             WRITE(numout,*) ' Memory allocation error for em_factor_tbocimene. We stop. We need nvm words = ',nvm
1678             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1679          END IF
1680
1681          ALLOCATE(em_factor_othermonot(nvm),stat=ier)
1682          l_error = l_error .OR. (ier /= 0) 
1683          IF (l_error) THEN
1684             WRITE(numout,*) ' Memory allocation error for em_factor_othermonot. We stop. We need nvm words = ',nvm
1685             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1686          END IF
1687
1688          ALLOCATE(em_factor_sesquiterp(nvm),stat=ier)
1689          l_error = l_error .OR. (ier /= 0) 
1690          IF (l_error) THEN
1691             WRITE(numout,*) ' Memory allocation error for em_factor_sesquiterp. We stop. We need nvm words = ',nvm
1692             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1693          END IF
1694
1695
1696          ALLOCATE(em_factor_ORVOC(nvm),stat=ier)
1697          l_error = l_error .OR. (ier /= 0) 
1698          IF (l_error) THEN
1699             WRITE(numout,*) ' Memory allocation error for em_factor_ORVOC. We stop. We need nvm words = ',nvm
1700             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1701          END IF
1702
1703          ALLOCATE(em_factor_OVOC(nvm),stat=ier)
1704          l_error = l_error .OR. (ier /= 0)       
1705          IF (l_error) THEN
1706             WRITE(numout,*) ' Memory allocation error for em_factor_OVOC. We stop. We need nvm words = ',nvm
1707             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1708          END IF
1709
1710          ALLOCATE(em_factor_MBO(nvm),stat=ier)
1711          l_error = l_error .OR. (ier /= 0) 
1712          IF (l_error) THEN
1713             WRITE(numout,*) ' Memory allocation error for em_factor_MBO. We stop. We need nvm words = ',nvm
1714             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1715          END IF
1716
1717          ALLOCATE(em_factor_methanol(nvm),stat=ier)
1718          l_error = l_error .OR. (ier /= 0) 
1719          IF (l_error) THEN
1720             WRITE(numout,*) ' Memory allocation error for em_factor_methanol. We stop. We need nvm words = ',nvm
1721             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1722          END IF
1723
1724          ALLOCATE(em_factor_acetone(nvm),stat=ier)
1725          l_error = l_error .OR. (ier /= 0) 
1726          IF (l_error) THEN
1727             WRITE(numout,*) ' Memory allocation error for em_factor_acetone. We stop. We need nvm words = ',nvm
1728             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1729          END IF
1730
1731          ALLOCATE(em_factor_acetal(nvm),stat=ier)
1732          l_error = l_error .OR. (ier /= 0) 
1733          IF (l_error) THEN
1734             WRITE(numout,*) ' Memory allocation error for em_factor_acetal. We stop. We need nvm words = ',nvm
1735             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1736          END IF
1737
1738          ALLOCATE(em_factor_formal(nvm),stat=ier)
1739          l_error = l_error .OR. (ier /= 0) 
1740          IF (l_error) THEN
1741             WRITE(numout,*) ' Memory allocation error for em_factor_formal. We stop. We need nvm words = ',nvm
1742             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1743          END IF
1744
1745          ALLOCATE(em_factor_acetic(nvm),stat=ier)
1746          l_error = l_error .OR. (ier /= 0)       
1747          IF (l_error) THEN
1748             WRITE(numout,*) ' Memory allocation error for em_factor_acetic. We stop. We need nvm words = ',nvm
1749             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1750          END IF
1751
1752          ALLOCATE(em_factor_formic(nvm),stat=ier)
1753          l_error = l_error .OR. (ier /= 0) 
1754          IF (l_error) THEN
1755             WRITE(numout,*) ' Memory allocation error for em_factor_formic. We stop. We need nvm words = ',nvm
1756             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1757          END IF
1758
1759          ALLOCATE(em_factor_no_wet(nvm),stat=ier)
1760          l_error = l_error .OR. (ier /= 0)
1761          IF (l_error) THEN
1762             WRITE(numout,*) ' Memory allocation error for em_factor_no_wet. We stop. We need nvm words = ',nvm
1763             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1764          END IF
1765
1766          ALLOCATE(em_factor_no_dry(nvm),stat=ier)
1767          l_error = l_error .OR. (ier /= 0)       
1768          IF (l_error) THEN
1769             WRITE(numout,*) ' Memory allocation error for em_factor_no_dry. We stop. We need nvm words = ',nvm
1770             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1771          END IF
1772
1773          ALLOCATE(Larch(nvm),stat=ier)
1774          l_error = l_error .OR. (ier /= 0) 
1775          IF (l_error) THEN
1776             WRITE(numout,*) ' Memory allocation error for Larch. We stop. We need nvm words = ',nvm
1777             CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1778          END IF
1779
1780       ENDIF ! (ok_bvoc)
1781
1782    ENDIF !(ok_sechiba)
1783
1784    !
1785    ! 3. Parameters used if ok_stomate only
1786    !
1787    IF ( ok_stomate ) THEN
1788
1789       l_error = .FALSE.
1790
1791       ALLOCATE(availability_fact(nvm),stat=ier)
1792       l_error = l_error .OR. (ier /= 0)
1793       IF (l_error) THEN
1794          WRITE(numout,*) ' Memory allocation error for availability_fact. We stop. We need nvm words = ',nvm
1795          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1796       END IF
1797
1798       ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier)
1799       l_error = l_error .OR. (ier /= 0)
1800       IF (l_error) THEN
1801          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_c. We stop. We need nvm words = ',nvm
1802          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1803       END IF
1804
1805       ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier)
1806       l_error = l_error .OR. (ier /= 0)
1807       IF (l_error) THEN
1808          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_b. We stop. We need nvm words = ',nvm
1809          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1810       END IF
1811
1812       ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier)
1813       l_error = l_error .OR. (ier /= 0)
1814       IF (l_error) THEN
1815          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_a. We stop. We need nvm words = ',nvm
1816          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1817       END IF
1818
1819       ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier)
1820       l_error = l_error .OR. (ier /= 0)
1821       IF (l_error) THEN
1822          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit. We stop. We need nvm words = ',nvm*3
1823          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1824       END IF
1825       pheno_gdd_crit(:,:) = zero
1826
1827       ALLOCATE(pheno_moigdd_t_crit(nvm),stat=ier)
1828       l_error = l_error .OR. (ier /= 0)
1829       IF (l_error) THEN
1830          WRITE(numout,*) ' Memory allocation error for pheno_moigdd_t_crit. We stop. We need nvm words = ',nvm
1831          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1832       END IF
1833
1834       ALLOCATE(ngd_crit(nvm),stat=ier)
1835       l_error = l_error .OR. (ier /= 0)
1836       IF (l_error) THEN
1837          WRITE(numout,*) ' Memory allocation error for ngd_crit. We stop. We need nvm words = ',nvm
1838          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1839       END IF
1840
1841       ALLOCATE(ncdgdd_temp(nvm),stat=ier)
1842       l_error = l_error .OR. (ier /= 0)
1843       IF (l_error) THEN
1844          WRITE(numout,*) ' Memory allocation error for ncdgdd_temp. We stop. We need nvm words = ',nvm
1845          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1846       END IF
1847
1848       ALLOCATE(hum_frac(nvm),stat=ier)
1849       l_error = l_error .OR. (ier /= 0)
1850       IF (l_error) THEN
1851          WRITE(numout,*) ' Memory allocation error for hum_frac. We stop. We need nvm words = ',nvm
1852          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1853       END IF
1854
1855       ALLOCATE(hum_min_time(nvm),stat=ier)
1856       l_error = l_error .OR. (ier /= 0)
1857       IF (l_error) THEN
1858          WRITE(numout,*) ' Memory allocation error for hum_min_time. We stop. We need nvm words = ',nvm
1859          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1860       END IF
1861
1862       ALLOCATE(longevity_sap(nvm),stat=ier)
1863       l_error = l_error .OR. (ier /= 0)
1864       IF (l_error) THEN
1865          WRITE(numout,*) ' Memory allocation error for longevity_sap. We stop. We need nvm words = ',nvm
1866          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1867       END IF
1868
1869       ALLOCATE(longevity_leaf(nvm),stat=ier)   
1870       l_error = l_error .OR. (ier /= 0)
1871       IF (l_error) THEN
1872          WRITE(numout,*) ' Memory allocation error for longevity_leaf. We stop. We need nvm words = ',nvm
1873          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1874       END IF
1875
1876       ALLOCATE(leaf_age_crit_tref(nvm),stat=ier)   
1877       l_error = l_error .OR. (ier /= 0)
1878       IF (l_error) THEN
1879          WRITE(numout,*) ' Memory allocation error for leaf_age_crit_tref. We stop. We need nvm words = ',nvm
1880          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1881       END IF
1882
1883       ALLOCATE(leaf_age_crit_coeff1(nvm),stat=ier)   
1884       l_error = l_error .OR. (ier /= 0)
1885       IF (l_error) THEN
1886          WRITE(numout,*) ' Memory allocation error for leaf_age_crit_coeff1. We stop. We need nvm words = ',nvm
1887          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1888       END IF
1889
1890       ALLOCATE(leaf_age_crit_coeff2(nvm),stat=ier)   
1891       l_error = l_error .OR. (ier /= 0)
1892       IF (l_error) THEN
1893          WRITE(numout,*) ' Memory allocation error for leaf_age_crit_coeff2. We stop. We need nvm words = ',nvm
1894          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1895       END IF
1896
1897       ALLOCATE(leaf_age_crit_coeff3(nvm),stat=ier)   
1898       l_error = l_error .OR. (ier /= 0)
1899       IF (l_error) THEN
1900          WRITE(numout,*) ' Memory allocation error for leaf_age_crit_coeff3. We stop. We need nvm words = ',nvm
1901          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1902       END IF
1903
1904       ALLOCATE(longevity_fruit(nvm),stat=ier)
1905       l_error = l_error .OR. (ier /= 0)
1906       IF (l_error) THEN
1907          WRITE(numout,*) ' Memory allocation error for longevity_fruit. We stop. We need nvm words = ',nvm
1908          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1909       END IF
1910
1911       ALLOCATE(longevity_root(nvm),stat=ier)
1912       l_error = l_error .OR. (ier /= 0)
1913       IF (l_error) THEN
1914          WRITE(numout,*) ' Memory allocation error for longevity_root. We stop. We need nvm words = ',nvm
1915          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1916       END IF
1917       
1918       ALLOCATE(ecureuil(nvm),stat=ier)
1919       l_error = l_error .OR. (ier /= 0)
1920       IF (l_error) THEN
1921          WRITE(numout,*) ' Memory allocation error for ecureuil. We stop. We need nvm words = ',nvm
1922          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1923       END IF
1924
1925       ALLOCATE(alloc_min(nvm),stat=ier)
1926       l_error = l_error .OR. (ier /= 0)
1927       IF (l_error) THEN
1928          WRITE(numout,*) ' Memory allocation error for alloc_min. We stop. We need nvm words = ',nvm
1929          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1930       END IF
1931
1932       ALLOCATE(alloc_max(nvm),stat=ier)
1933       l_error = l_error .OR. (ier /= 0)
1934       IF (l_error) THEN
1935          WRITE(numout,*) ' Memory allocation error for alloc_max. We stop. We need nvm words = ',nvm
1936          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1937       END IF
1938
1939       ALLOCATE(demi_alloc(nvm),stat=ier)
1940       l_error = l_error .OR. (ier /= 0)
1941       IF (l_error) THEN
1942          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
1943          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1944       END IF
1945
1946       ALLOCATE(frac_growthresp(nvm),stat=ier)
1947       l_error = l_error .OR. (ier /= 0)
1948       IF (l_error) THEN
1949          WRITE(numout,*) ' Memory allocation error for frac_growthresp. We stop. We need nvm words = ',nvm
1950          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1951       END IF
1952
1953       ALLOCATE(coeff_maint_init(nvm),stat=ier)
1954       l_error = l_error .OR. (ier /= 0)
1955       IF (l_error) THEN
1956          WRITE(numout,*) ' Memory allocation error for coeff_maint_init. We stop. We need nvm words = ',nvm
1957          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1958       END IF
1959 
1960       ALLOCATE(tref_maint_resp(nvm),stat=ier)
1961       l_error = l_error .OR. (ier /= 0)
1962       IF (l_error) THEN
1963          WRITE(numout,*) ' Memory allocation error for tref_maint_resp. We stop. We need nvm words = ',nvm
1964          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1965       END IF
1966       
1967       ALLOCATE(tmin_maint_resp(nvm),stat=ier)
1968       l_error = l_error .OR. (ier /= 0)
1969       IF (l_error) THEN
1970          WRITE(numout,*) ' Memory allocation error for tmin_maint_resp. We stop. We need nvm  words = ',nvm
1971          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1972       END IF
1973
1974       ALLOCATE(e0_maint_resp(nvm),stat=ier)
1975       l_error = l_error .OR. (ier /= 0)
1976       IF (l_error) THEN
1977          WRITE(numout,*) ' Memory allocation error for e0_maint_resp. We stop. We need nvm words = ',nvm
1978          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1979       END IF
1980
1981       ALLOCATE(tref_labile(nvm),stat=ier)
1982       l_error = l_error .OR. (ier /= 0)
1983       IF (l_error) THEN
1984          WRITE(numout,*) ' Memory allocation error for tref_labile. We stop. We need nvm words = ',nvm
1985          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1986       END IF
1987       
1988       ALLOCATE(tmin_labile(nvm),stat=ier)
1989       l_error = l_error .OR. (ier /= 0)
1990       IF (l_error) THEN
1991          WRITE(numout,*) ' Memory allocation error for tmin_labile. We stop. We need nvm  words = ',nvm
1992          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
1993       END IF
1994
1995       ALLOCATE(e0_labile(nvm),stat=ier)
1996       l_error = l_error .OR. (ier /= 0)
1997       IF (l_error) THEN
1998          WRITE(numout,*) ' Memory allocation error for e0_labile. We stop. We need nvm words = ',nvm
1999          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2000       END IF
2001
2002       ALLOCATE(always_labile(nvm),stat=ier)
2003       l_error = l_error .OR. (ier /= 0)
2004       IF (l_error) THEN
2005          WRITE(numout,*) ' Memory allocation error for always_labile. We stop. We need nvm words = ',nvm
2006          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2007       END IF
2008
2009       ALLOCATE(flam(nvm),stat=ier)
2010       l_error = l_error .OR. (ier /= 0)
2011       IF (l_error) THEN
2012          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
2013          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2014       END IF
2015
2016       ALLOCATE(resist(nvm),stat=ier)
2017       l_error = l_error .OR. (ier /= 0)
2018       IF (l_error) THEN
2019          WRITE(numout,*) ' Memory allocation error for resist. We stop. We need nvm words = ',nvm
2020          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2021       END IF
2022
2023       ALLOCATE(coeff_lcchange_s(nvm),stat=ier)
2024       l_error = l_error .OR. (ier /= 0)
2025       IF (l_error) THEN
2026          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_s. We stop. We need nvm words = ',nvm
2027          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2028       END IF
2029       
2030       ALLOCATE(coeff_lcchange_m(nvm),stat=ier)
2031       l_error = l_error .OR. (ier /= 0)
2032       IF (l_error) THEN
2033          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_m. We stop. We need nvm words = ',nvm
2034          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2035       END IF
2036       
2037       ALLOCATE(coeff_lcchange_l(nvm),stat=ier)
2038       l_error = l_error .OR. (ier /= 0)
2039       IF (l_error) THEN
2040          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_l. We stop. We need nvm words = ',nvm
2041          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2042       END IF
2043
2044       ALLOCATE(lai_max_to_happy(nvm),stat=ier)
2045       l_error = l_error .OR. (ier /= 0)
2046       IF (l_error) THEN
2047          WRITE(numout,*) ' Memory allocation error for lai_max_to_happy. We stop. We need nvm words = ',nvm
2048          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2049       END IF
2050
2051       ALLOCATE(lai_max(nvm),stat=ier)
2052       l_error = l_error .OR. (ier /= 0)
2053       IF (l_error) THEN
2054          WRITE(numout,*) ' Memory allocation error for lai_max. We stop. We need nvm words = ',nvm
2055          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2056       END IF
2057
2058       ALLOCATE(pheno_type(nvm),stat=ier)
2059       l_error = l_error .OR. (ier /= 0)
2060       IF (l_error) THEN
2061          WRITE(numout,*) ' Memory allocation error for pheno_type. We stop. We need nvm words = ',nvm
2062          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2063       END IF
2064
2065       ALLOCATE(force_pheno(nvm),stat=ier)
2066       l_error = l_error .OR. (ier /= 0)
2067       IF (l_error) THEN
2068          WRITE(numout,*) ' Memory allocation error for force_pheno. We stop. We need nvm words = ',nvm
2069          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2070       END IF
2071
2072       ALLOCATE(leaffall(nvm),stat=ier)
2073       l_error = l_error .OR. (ier /= 0)
2074       IF (l_error) THEN
2075          WRITE(numout,*) ' Memory allocation error for leaffall. We stop. We need nvm words = ',nvm
2076          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2077       END IF
2078
2079       ALLOCATE(presenescence_ratio(nvm),stat=ier)
2080       l_error = l_error .OR. (ier /= 0)
2081       IF (l_error) THEN
2082          WRITE(numout,*) ' Memory allocation error for presenescence_ratio. We stop. We need nvm words = ',nvm
2083          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2084       END IF
2085
2086       ALLOCATE(senescence_type(nvm),stat=ier)
2087       l_error = l_error .OR. (ier /= 0)
2088       IF (l_error) THEN
2089          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
2090          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2091       END IF
2092
2093       ALLOCATE(senescence_hum(nvm),stat=ier)
2094       l_error = l_error .OR. (ier /= 0)
2095       IF (l_error) THEN
2096          WRITE(numout,*) ' Memory allocation error for senescence_hum. We stop. We need nvm words = ',nvm
2097          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2098       END IF
2099
2100       ALLOCATE(nosenescence_hum(nvm),stat=ier)
2101       l_error = l_error .OR. (ier /= 0)
2102       IF (l_error) THEN
2103          WRITE(numout,*) ' Memory allocation error for nosenescence_hum. We stop. We need nvm words = ',nvm
2104          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2105       END IF
2106
2107       ALLOCATE(max_turnover_time(nvm),stat=ier)
2108       l_error = l_error .OR. (ier /= 0)
2109       IF (l_error) THEN
2110          WRITE(numout,*) ' Memory allocation error for max_turnover_time. We stop. We need nvm words = ',nvm
2111          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2112       END IF
2113
2114       ALLOCATE(min_turnover_time(nvm),stat=ier)
2115       l_error = l_error .OR. (ier /= 0)
2116       IF (l_error) THEN
2117          WRITE(numout,*) ' Memory allocation error for min_turnover_time. We stop. We need nvm words = ',nvm
2118          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2119       END IF
2120
2121       ALLOCATE(recycle_leaf(nvm),stat=ier)
2122       l_error = l_error .OR. (ier /= 0)
2123       IF (l_error) THEN
2124          WRITE(numout,*) ' Memory allocation error for recycle_leaf. We stop. We need nvm words = ',nvm
2125          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2126       END IF
2127       
2128       ALLOCATE(recycle_root(nvm),stat=ier)
2129       l_error = l_error .OR. (ier /= 0)
2130       IF (l_error) THEN
2131          WRITE(numout,*) ' Memory allocation error for recycle_root. We stop. We need nvm words = ',nvm
2132          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2133       END IF
2134
2135       ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier)
2136       l_error = l_error .OR. (ier /= 0)
2137       IF (l_error) THEN
2138          WRITE(numout,*) ' Memory allocation error for min_leaf_age_for_senescence. We stop. We need nvm words = ',nvm
2139          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2140       END IF
2141
2142       ALLOCATE(senescence_temp_c(nvm),stat=ier)
2143       l_error = l_error .OR. (ier /= 0)
2144       IF (l_error) THEN
2145          WRITE(numout,*) ' Memory allocation error for senescence_temp_c. We stop. We need nvm words = ',nvm
2146          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2147       END IF
2148
2149       ALLOCATE(senescence_temp_b(nvm),stat=ier)
2150       l_error = l_error .OR. (ier /= 0)
2151       IF (l_error) THEN
2152          WRITE(numout,*) ' Memory allocation error for senescence_temp_b. We stop. We need nvm words = ',nvm
2153          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2154       END IF
2155
2156       ALLOCATE(senescence_temp_a(nvm),stat=ier)
2157       l_error = l_error .OR. (ier /= 0)
2158       IF (l_error) THEN
2159          WRITE(numout,*) ' Memory allocation error for senescence_temp_a. We stop. We need nvm words = ',nvm
2160          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2161       END IF
2162
2163       ALLOCATE(senescence_temp(nvm,3),stat=ier)
2164       l_error = l_error .OR. (ier /= 0)
2165       IF (l_error) THEN
2166          WRITE(numout,*) ' Memory allocation error for senescence_temp. We stop. We need nvm*3 words = ',nvm*3
2167          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2168       END IF
2169       senescence_temp(:,:) = zero
2170
2171       ALLOCATE(gdd_senescence(nvm),stat=ier)
2172       l_error = l_error .OR. (ier /= 0)
2173       IF (l_error) THEN
2174          WRITE(numout,*) ' Memory allocation error for gdd_senescence. We stop. We need nvm words = ',nvm
2175          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2176       END IF
2177
2178       ALLOCATE(always_init(nvm),stat=ier)
2179       l_error = l_error .OR. (ier /= 0)
2180       IF (l_error) THEN
2181          WRITE(numout,*) ' Memory allocation error for always_init. We stop. We need nvm words = ',nvm
2182          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2183       END IF
2184
2185       ALLOCATE(max_soil_n_bnf(nvm),stat=ier)
2186       l_error = l_error .OR. (ier /= 0)
2187       IF (l_error) THEN
2188          WRITE(numout,*) ' Memory allocation error for max_soil_n_bnf. We stop. We need nvm words = ',nvm
2189          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2190       END IF
2191
2192       ALLOCATE(manure_pftweight(nvm),stat=ier)
2193       l_error = l_error .OR. (ier /= 0)
2194       IF (l_error) THEN
2195          WRITE(numout,*) ' Memory allocation error for manure_pftweight. We stop. We need nvm words = ',nvm
2196          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2197       END IF
2198       
2199       ALLOCATE(residence_time(nvm),stat=ier)
2200       l_error = l_error .OR. (ier /= 0)
2201       IF (l_error) THEN
2202          WRITE(numout,*) ' Memory allocation error for residence_time. We stop. We need nvm words = ',nvm
2203          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2204       END IF
2205
2206       ALLOCATE(tmin_crit(nvm),stat=ier)
2207       l_error = l_error .OR. (ier /= 0)
2208       IF (l_error) THEN
2209          WRITE(numout,*) ' Memory allocation error for tmin_crit. We stop. We need nvm words = ',nvm
2210          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2211       END IF
2212
2213       ALLOCATE(tcm_crit(nvm),stat=ier)
2214       l_error = l_error .OR. (ier /= 0)
2215       IF (l_error) THEN
2216          WRITE(numout,*) ' Memory allocation error for tcm_crit. We stop. We need nvm words = ',nvm
2217          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2218       END IF
2219
2220       ALLOCATE(lai_initmin(nvm),stat=ier)
2221       l_error = l_error .OR. (ier /= 0)
2222       IF (l_error) THEN
2223          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
2224          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2225       END IF
2226
2227       ALLOCATE(bm_sapl(nvm,nparts,nelements),stat=ier)
2228       l_error = l_error .OR. (ier /= 0)
2229       IF (l_error) THEN
2230          WRITE(numout,*) ' Memory allocation error for bm_sapl. We stop. We need nvm*nparts*nelements words = ',& 
2231               &  nvm*nparts*nelements
2232          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2233       END IF
2234
2235       ALLOCATE(migrate(nvm),stat=ier)
2236       l_error = l_error .OR. (ier /= 0)
2237       IF (l_error) THEN
2238          WRITE(numout,*) ' Memory allocation error for migrate. We stop. We need nvm words = ',nvm
2239          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2240       END IF
2241
2242       ALLOCATE(maxdia(nvm),stat=ier)
2243       l_error = l_error .OR. (ier /= 0)
2244       IF (l_error) THEN
2245          WRITE(numout,*) ' Memory allocation error for maxdia. We stop. We need nvm words = ',nvm
2246          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2247       END IF
2248
2249       ALLOCATE(cn_sapl(nvm),stat=ier)
2250       l_error = l_error .OR. (ier /= 0)
2251       IF (l_error) THEN
2252          WRITE(numout,*) ' Memory allocation error for cn_sapl. We stop. We need nvm words = ',nvm
2253          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2254       END IF
2255
2256       ALLOCATE(k_latosa_max(nvm),stat=ier)
2257       l_error = l_error .OR. (ier /= 0)
2258       IF (l_error) THEN
2259          WRITE(numout,*) ' Memory allocation error for k_latosa_max. We stop. We need nvm words = ',nvm
2260          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2261       END IF
2262       
2263       ALLOCATE(k_latosa_min(nvm),stat=ier)
2264       l_error = l_error .OR. (ier /= 0)
2265       IF (l_error) THEN
2266          WRITE(numout,*) ' Memory allocation error for k_latosa_min. We stop. We need nvm words = ',nvm
2267          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2268       END IF
2269       
2270       !
2271       ! SOM decomposition (stomate)
2272       !
2273       ALLOCATE(LC(nvm,nparts),stat=ier)   
2274       l_error = l_error .OR. (ier /= 0)
2275       IF (l_error) THEN
2276          WRITE(numout,*) ' Memory allocation error for LC. We stop. We need nvm*nparts words = ',nvm,nparts
2277          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2278       END IF
2279       
2280       ALLOCATE(LC_leaf(nvm),stat=ier)   
2281       l_error = l_error .OR. (ier /= 0)
2282       IF (l_error) THEN
2283          WRITE(numout,*) ' Memory allocation error for LC_leaf. We stop. We need nvm words = ',nvm
2284          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2285       END IF
2286       
2287       ALLOCATE(LC_sapabove(nvm),stat=ier)   
2288       l_error = l_error .OR. (ier /= 0)
2289       IF (l_error) THEN
2290          WRITE(numout,*) ' Memory allocation error for LC_sapabove. We stop. We need nvm words = ',nvm
2291          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2292       END IF
2293       
2294       ALLOCATE(LC_sapbelow(nvm),stat=ier)   
2295       l_error = l_error .OR. (ier /= 0)
2296       IF (l_error) THEN
2297          WRITE(numout,*) ' Memory allocation error for LC_sapbelow. We stop. We need nvm words = ',nvm
2298          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2299       END IF
2300       
2301       ALLOCATE(LC_heartabove(nvm),stat=ier)   
2302       l_error = l_error .OR. (ier /= 0)
2303       IF (l_error) THEN
2304          WRITE(numout,*) ' Memory allocation error for LC_heartabove. We stop. We need nvm words = ',nvm
2305          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2306       END IF
2307       
2308       ALLOCATE(LC_heartbelow(nvm),stat=ier)   
2309       l_error = l_error .OR. (ier /= 0)
2310       IF (l_error) THEN
2311          WRITE(numout,*) ' Memory allocation error for LC_heartbelow. We stop. We need nvm words = ',nvm
2312          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2313       END IF
2314       
2315       ALLOCATE(LC_fruit(nvm),stat=ier)   
2316       l_error = l_error .OR. (ier /= 0)
2317       IF (l_error) THEN
2318          WRITE(numout,*) ' Memory allocation error for LC_fruit. We stop. We need nvm words = ',nvm
2319          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2320       END IF
2321       
2322       ALLOCATE(LC_root(nvm),stat=ier)   
2323       l_error = l_error .OR. (ier /= 0)
2324       IF (l_error) THEN
2325          WRITE(numout,*) ' Memory allocation error for LC_root. We stop. We need nvm words = ',nvm
2326          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2327       END IF
2328       
2329       ALLOCATE(LC_carbres(nvm),stat=ier)   
2330       l_error = l_error .OR. (ier /= 0)
2331       IF (l_error) THEN
2332          WRITE(numout,*) ' Memory allocation error for LC_carbres. We stop. We need nvm words = ',nvm
2333          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2334       END IF
2335       
2336       ALLOCATE(LC_labile(nvm),stat=ier)   
2337       l_error = l_error .OR. (ier /= 0)
2338       IF (l_error) THEN
2339          WRITE(numout,*) ' Memory allocation error for LC_labile. We stop. We need nvm words = ',nvm
2340          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2341       END IF
2342       
2343       ALLOCATE(decomp_factor(nvm),stat=ier)   
2344       l_error = l_error .OR. (ier /= 0)
2345       IF (l_error) THEN
2346          WRITE(numout,*) ' Memory allocation error for decomp_factor. We stop. We need nvm words = ',nvm
2347          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2348       END IF
2349       
2350       ALLOCATE(mass_ratio_heart_sap(nvm),stat=ier)   
2351       l_error = l_error .OR. (ier /= 0)
2352       IF (l_error) THEN
2353          WRITE(numout,*) ' Memory allocation error for mass_ratio_heart_sap. We stop. We need nvm words = ',nvm
2354          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2355       END IF
2356       
2357       ALLOCATE(canopy_cover(nvm),stat=ier)
2358       l_error = l_error .OR. (ier /= 0)
2359       IF (l_error) THEN
2360          WRITE(numout,*) ' Memory allocation error for canopy_cover. We stop. We need nvm words = ',nvm
2361          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2362       END IF
2363       
2364       ALLOCATE(nmaxplants(nvm),stat=ier)   
2365       l_error = l_error .OR. (ier /= 0)
2366       IF (l_error) THEN
2367          WRITE(numout,*) ' Memory allocation error for nmaxplants. We stop. We need nvm words = ',nvm
2368          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2369       END IF
2370
2371       ALLOCATE(p_use_reserve(nvm),stat=ier)
2372       l_error = l_error .OR. (ier /= 0)
2373       IF (l_error) THEN
2374          WRITE(numout,*) ' Memory allocation error for p_use_reserve. We stop. We need nvm words = ',nvm
2375          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2376       END IF
2377
2378       ALLOCATE(height_init(nvm),stat=ier)   
2379       l_error = l_error .OR. (ier /= 0)
2380       IF (l_error) THEN
2381          WRITE(numout,*) ' Memory allocation error for height_init. We stop. We need nvm words = ',nvm
2382          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2383       END IF
2384       
2385       ALLOCATE(dia_init_min(nvm),stat=ier)
2386       l_error = l_error .OR. (ier /= 0)
2387       IF (l_error) THEN
2388          WRITE(numout,*) ' Memory allocation error for dia_init_min. We stop. We need nvm words = ',nvm
2389          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2390       END IF
2391
2392       ALLOCATE(dia_init_max(nvm),stat=ier)
2393       l_error = l_error .OR. (ier /= 0)
2394       IF (l_error) THEN
2395          WRITE(numout,*) ' Memory allocation error for dia_init_max. We stop. We need nvm words = ',nvm
2396          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2397       END IF
2398       
2399       ALLOCATE(deleuze_a(nvm),stat=ier)   
2400       l_error = l_error .OR. (ier /= 0)
2401       IF (l_error) THEN
2402          WRITE(numout,*) ' Memory allocation error for deleuze_a. We stop. We need nvm words = ',nvm
2403          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2404       END IF
2405       
2406       ALLOCATE(deleuze_b(nvm),stat=ier)   
2407       l_error = l_error .OR. (ier /= 0)
2408       IF (l_error) THEN
2409          WRITE(numout,*) ' Memory allocation error for deleuze_b. We stop. We need nvm words = ',nvm
2410          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2411       END IF
2412       
2413       ALLOCATE(deleuze_p_all(nvm),stat=ier)   
2414       l_error = l_error .OR. (ier /= 0)
2415       IF (l_error) THEN
2416          WRITE(numout,*) ' Memory allocation error for deleuze_p_all. We stop. We need nvm words = ',nvm
2417          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2418       END IF
2419       
2420       ALLOCATE(alpha_self_thinning(nvm),stat=ier)   
2421       l_error = l_error .OR. (ier /= 0)
2422       IF (l_error) THEN
2423          WRITE(numout,*) ' Memory allocation error for alpha_self_thinning. We stop. We need nvm words = ',nvm
2424          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2425       END IF
2426       
2427       ALLOCATE(beta_self_thinning(nvm),stat=ier)   
2428       l_error = l_error .OR. (ier /= 0)
2429       IF (l_error) THEN
2430          WRITE(numout,*) ' Memory allocation error for beta_self_thinning. We stop. We need nvm words = ',nvm
2431          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2432       END IF
2433       
2434       ALLOCATE(fuelwood_diameter(nvm),stat=ier)   
2435       l_error = l_error .OR. (ier /= 0)
2436       IF (l_error) THEN
2437          WRITE(numout,*) ' Memory allocation error for fuelwood_diameter. We stop. We need nvm words = ',nvm
2438          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2439       END IF
2440       
2441       ALLOCATE(coppice_kill_be_wood(nvm),stat=ier)   
2442       l_error = l_error .OR. (ier /= 0)
2443       IF (l_error) THEN
2444          WRITE(numout,*) ' Memory allocation error for coppice_kill_be_wood. We stop. We need nvm words = ',nvm
2445          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2446       END IF
2447       
2448       ALLOCATE(deleuze_p_coppice(nvm),stat=ier)   
2449       l_error = l_error .OR. (ier /= 0)
2450       IF (l_error) THEN
2451          WRITE(numout,*) ' Memory allocation error for deleuze_p_coppice. We stop. We need nvm words = ',nvm
2452          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2453       END IF
2454
2455       ALLOCATE(deleuze_power_a(nvm),stat=ier)
2456       l_error = l_error .OR. (ier /= 0)
2457       IF (l_error) THEN
2458          WRITE(numout,*) ' Memory allocation error for deleuze_power_a. We stop. We need nvm words = ',nvm
2459          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2460       END IF
2461       
2462       ALLOCATE(m_dv(nvm),stat=ier)   
2463       l_error = l_error .OR. (ier /= 0)
2464       IF (l_error) THEN
2465          WRITE(numout,*) ' Memory allocation error for m_dv. We stop. We need nvm words = ',nvm
2466          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2467       END IF
2468       
2469
2470       ALLOCATE(dens_target(nvm),stat=ier)   
2471       l_error = l_error .OR. (ier /= 0)
2472       IF (l_error) THEN
2473          WRITE(numout,*) ' Memory allocation error for dens_target. We stop. We need nvm words = ',nvm
2474          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2475       END IF
2476       
2477       ALLOCATE(thinstrat(nvm),stat=ier)   
2478       l_error = l_error .OR. (ier /= 0)
2479       IF (l_error) THEN
2480          WRITE(numout,*) ' Memory allocation error for thinstrat. We stop. We need nvm words = ',nvm
2481          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2482       END IF
2483       
2484       ALLOCATE(taumin(nvm),stat=ier)   
2485       l_error = l_error .OR. (ier /= 0)
2486       IF (l_error) THEN
2487          WRITE(numout,*) ' Memory allocation error for taumin. We stop. We need nvm words = ',nvm
2488          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2489       END IF
2490       
2491       ALLOCATE(taumax(nvm),stat=ier)   
2492       l_error = l_error .OR. (ier /= 0)
2493       IF (l_error) THEN
2494          WRITE(numout,*) ' Memory allocation error for taumax. We stop. We need nvm words = ',nvm
2495          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2496       END IF
2497
2498       ALLOCATE(a_rdi_upper_unman(nvm),stat=ier)   
2499       l_error = l_error .OR. (ier /= 0)
2500       IF (l_error) THEN
2501          WRITE(numout,*) ' Memory allocation error for a_rdi_upper_unman. We stop. We need nvm words = ',nvm
2502          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2503       END IF
2504       
2505       ALLOCATE(b_rdi_upper_unman(nvm),stat=ier)   
2506       l_error = l_error .OR. (ier /= 0)
2507       IF (l_error) THEN
2508          WRITE(numout,*) ' Memory allocation error for b_rdi_upper_unman. We stop. We need nvm words = ',nvm
2509          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2510       END IF
2511       
2512       ALLOCATE(c_rdi_upper_unman(nvm),stat=ier)   
2513       l_error = l_error .OR. (ier /= 0)
2514       IF (l_error) THEN
2515          WRITE(numout,*) ' Memory allocation error for c_rdi_upper_unman. We stop. We need nvm words = ',nvm
2516          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2517       END IF
2518
2519       ALLOCATE(d_rdi_upper_unman(nvm),stat=ier)   
2520       l_error = l_error .OR. (ier /= 0)
2521       IF (l_error) THEN
2522          WRITE(numout,*) ' Memory allocation error for d_rdi_upper_unman. We stop. We need nvm words = ',nvm
2523          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2524       END IF
2525
2526       ALLOCATE(a_rdi_lower_unman(nvm),stat=ier)   
2527       l_error = l_error .OR. (ier /= 0)
2528       IF (l_error) THEN
2529          WRITE(numout,*) ' Memory allocation error for a_rdi_lower_unman. We stop. We need nvm words = ',nvm
2530          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2531       END IF
2532
2533       ALLOCATE(b_rdi_lower_unman(nvm),stat=ier)   
2534       l_error = l_error .OR. (ier /= 0)
2535       IF (l_error) THEN
2536          WRITE(numout,*) ' Memory allocation error for b_rdi_lower_unman. We stop. We need nvm words = ',nvm
2537          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2538       END IF
2539
2540       ALLOCATE(c_rdi_lower_unman(nvm),stat=ier)   
2541       l_error = l_error .OR. (ier /= 0)
2542       IF (l_error) THEN
2543          WRITE(numout,*) ' Memory allocation error for c_rdi_lower_unman. We stop. We need nvm words = ',nvm
2544          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2545       END IF
2546
2547       ALLOCATE(d_rdi_lower_unman(nvm),stat=ier)   
2548       l_error = l_error .OR. (ier /= 0)
2549       IF (l_error) THEN
2550          WRITE(numout,*) ' Memory allocation error for d_rdi_lower_unman. We stop. We need nvm words = ',nvm
2551          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2552       END IF
2553       
2554       ALLOCATE(a_rdi_upper_man(nvm),stat=ier)   
2555       l_error = l_error .OR. (ier /= 0)
2556       IF (l_error) THEN
2557          WRITE(numout,*) ' Memory allocation error for a_rdi_upper_man. We stop. We need nvm words = ',nvm
2558          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2559       END IF
2560       
2561       ALLOCATE(b_rdi_upper_man(nvm),stat=ier)   
2562       l_error = l_error .OR. (ier /= 0)
2563       IF (l_error) THEN
2564          WRITE(numout,*) ' Memory allocation error for b_rdi_upper_man. We stop. We need nvm words = ',nvm
2565          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2566       END IF
2567       
2568       ALLOCATE(c_rdi_upper_man(nvm),stat=ier)   
2569       l_error = l_error .OR. (ier /= 0)
2570       IF (l_error) THEN
2571          WRITE(numout,*) ' Memory allocation error for c_rdi_upper_man. We stop. We need nvm words = ',nvm
2572          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2573       END IF
2574
2575       ALLOCATE(d_rdi_upper_man(nvm),stat=ier)   
2576       l_error = l_error .OR. (ier /= 0)
2577       IF (l_error) THEN
2578          WRITE(numout,*) ' Memory allocation error for d_rdi_upper_man. We stop. We need nvm words = ',nvm
2579          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2580       END IF
2581
2582       ALLOCATE(a_rdi_lower_man(nvm),stat=ier)   
2583       l_error = l_error .OR. (ier /= 0)
2584       IF (l_error) THEN
2585          WRITE(numout,*) ' Memory allocation error for a_rdi_lower_man. We stop. We need nvm words = ',nvm
2586          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2587       END IF
2588
2589       ALLOCATE(b_rdi_lower_man(nvm),stat=ier)   
2590       l_error = l_error .OR. (ier /= 0)
2591       IF (l_error) THEN
2592          WRITE(numout,*) ' Memory allocation error for b_rdi_lower_man. We stop. We need nvm words = ',nvm
2593          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2594       END IF
2595
2596       ALLOCATE(c_rdi_lower_man(nvm),stat=ier)   
2597       l_error = l_error .OR. (ier /= 0)
2598       IF (l_error) THEN
2599          WRITE(numout,*) ' Memory allocation error for c_rdi_lower_man. We stop. We need nvm words = ',nvm
2600          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2601       END IF
2602
2603       ALLOCATE(d_rdi_lower_man(nvm),stat=ier)   
2604       l_error = l_error .OR. (ier /= 0)
2605       IF (l_error) THEN
2606          WRITE(numout,*) ' Memory allocation error for d_rdi_lower_man. We stop. We need nvm words = ',nvm
2607          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2608       END IF
2609       
2610       ALLOCATE(largest_tree_dia(nvm),stat=ier)   
2611       l_error = l_error .OR. (ier /= 0)
2612       IF (l_error) THEN
2613          WRITE(numout,*) ' Memory allocation error for largest_tree_dia. We stop. We need nvm words = ',nvm
2614          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2615       END IF
2616       
2617       ALLOCATE(branch_ratio(nvm),stat=ier)   
2618       l_error = l_error .OR. (ier /= 0)
2619       IF (l_error) THEN
2620          WRITE(numout,*) ' Memory allocation error for branch_ratio. We stop. We need nvm words = ',nvm
2621          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2622       END IF
2623       
2624       ALLOCATE(branch_harvest(nvm),stat=ier)   
2625       l_error = l_error .OR. (ier /= 0)
2626       IF (l_error) THEN
2627          WRITE(numout,*) ' Memory allocation error for branch_harvest. We stop. We need nvm words = ',nvm
2628          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2629       END IF
2630       
2631       ALLOCATE(coppice_diameter(nvm),stat=ier)   
2632       l_error = l_error .OR. (ier /= 0)
2633       IF (l_error) THEN
2634          WRITE(numout,*) ' Memory allocation error for coppice_diameter. We stop. We need nvm words = ',nvm
2635          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2636       END IF
2637       
2638       ALLOCATE(shoots_per_stool(nvm),stat=ier)   
2639       l_error = l_error .OR. (ier /= 0)
2640       IF (l_error) THEN
2641          WRITE(numout,*) ' Memory allocation error for shoots_per_stool. We stop. We need nvm words = ',nvm
2642          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2643       END IF
2644       
2645       ALLOCATE(src_rot_length(nvm),stat=ier)   
2646       l_error = l_error .OR. (ier /= 0)
2647       IF (l_error) THEN
2648          WRITE(numout,*) ' Memory allocation error for src_rot_length. We stop. We need nvm words = ',nvm
2649          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2650       END IF
2651       
2652       ALLOCATE(src_nrots(nvm),stat=ier)   
2653       l_error = l_error .OR. (ier /= 0)
2654       IF (l_error) THEN
2655          WRITE(numout,*) ' Memory allocation error for src_nrots. We stop. We need nvm words = ',nvm
2656          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2657       END IF
2658     
2659       ALLOCATE(fruit_alloc(nvm),stat=ier)
2660       l_error = l_error .OR. (ier /= 0)
2661       IF (l_error) THEN
2662          WRITE(numout,*) ' Memory allocation error for fruit_alloc. We stop. We need nvm words = ',nvm
2663          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2664       END IF
2665       
2666       ALLOCATE(labile_reserve(nvm),stat=ier)   
2667       l_error = l_error .OR. (ier /= 0)
2668       IF (l_error) THEN
2669          WRITE(numout,*) ' Memory allocation error for labile_reserve. We stop. We need nvm words = ',nvm
2670          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2671       END IF
2672       
2673       ALLOCATE(evergreen_reserve(nvm),stat=ier)
2674       l_error = l_error .OR. (ier /= 0)
2675       IF (l_error) THEN
2676          WRITE(numout,*) ' Memory allocation error for evergreen_reserve. We stop. We need nvm words = ',nvm
2677          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2678       END IF
2679       
2680       ALLOCATE(deciduous_reserve(nvm),stat=ier)
2681       l_error = l_error .OR. (ier /= 0)
2682       IF (l_error) THEN
2683          WRITE(numout,*) ' Memory allocation error for deciudous_reserve. We stop. We need nvm words = ',nvm
2684          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2685       END IF
2686       
2687       ALLOCATE(senescense_reserve(nvm),stat=ier)
2688       l_error = l_error .OR. (ier /= 0)
2689       IF (l_error) THEN
2690          WRITE(numout,*) ' Memory allocation error for senescense_reserve. We stop. We need nvm words = ',nvm
2691          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2692       END IF
2693
2694       ALLOCATE(root_reserve(nvm),stat=ier)
2695       l_error = l_error .OR. (ier /= 0)
2696       IF (l_error) THEN
2697          WRITE(numout,*) ' Memory allocation error for root_reserve. We stop. We need nvm words = ',nvm
2698          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2699       END IF
2700       
2701       ALLOCATE(fcn_wood(nvm),stat=ier)
2702       l_error = l_error .OR. (ier /= 0)
2703       IF (l_error) THEN
2704          WRITE(numout,*) ' Memory allocation error for fcn_wood. We stop. We need nvm words = ',nvm
2705          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2706       END IF
2707       
2708       ALLOCATE(fcn_root(nvm),stat=ier)
2709       l_error = l_error .OR. (ier /= 0)
2710       IF (l_error) THEN
2711          WRITE(numout,*) ' Memory allocation error for fcn_root. We stop. We need nvm words = ',nvm
2712          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2713       END IF
2714       
2715       !
2716       ! RECRUITMENT
2717       !
2718       ALLOCATE(recruitment_pft(nvm),stat=ier)     
2719       l_error = l_error .OR. (ier /= 0) 
2720       IF (l_error) THEN 
2721          WRITE(numout,*) ' Memory allocation error for recruitment_pft. We stop. We need nvm words = ',nvm 
2722          CALL ipslerr_p (3, 'pft_parameters','pft_parameters_alloc','','') 
2723       END IF
2724
2725       ALLOCATE(recruitment_height(nvm),stat=ier)     
2726       l_error = l_error .OR. (ier /= 0) 
2727       IF (l_error) THEN 
2728          WRITE(numout,*) ' Memory allocation error for recruitment_height. We stop. We need nvm words = ',nvm 
2729          CALL ipslerr_p (3, 'pft_parameters','pft_parameters_alloc','','') 
2730       END IF
2731
2732       ALLOCATE(recruitment_alpha(nvm),stat=ier)     
2733       l_error = l_error .OR. (ier /= 0) 
2734       IF (l_error) THEN 
2735          WRITE(numout,*) ' Memory allocation error for recruitment_alpha. We stop. We need nvm words = ',nvm 
2736          CALL ipslerr_p (3, 'pft_parameters','pft_parameters_alloc','','') 
2737       END IF
2738
2739       ALLOCATE(recruitment_beta(nvm),stat=ier)     
2740       l_error = l_error .OR. (ier /= 0) 
2741       IF (l_error) THEN 
2742          WRITE(numout,*) ' Memory allocation error for recruitment_beta. We stop. We need nvm words = ',nvm 
2743          CALL ipslerr_p (3, 'pft_parameters','pft_parameters_alloc','','') 
2744       END IF
2745
2746       !
2747       ! MORTALITY
2748       !
2749
2750       ALLOCATE(beetle_pft(nvm),stat=ier)
2751       l_error = l_error .OR. (ier /= 0)
2752       IF (l_error) THEN
2753          WRITE(numout,*) ' Memory allocation error for beetle_pft. We stop. We need nvm words = ',nvm
2754          CALL ipslerr_p (3, 'pft_parameters','pft_parameters_alloc','','')
2755       END IF
2756
2757       ALLOCATE(death_distribution_factor(nvm),stat=ier)
2758       l_error = l_error .OR. (ier /= 0)
2759       IF (l_error) THEN
2760          WRITE(numout,*) ' Memory allocation error for death_distribution_factor. We stop. We need nvm words = ',nvm
2761          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2762       END IF
2763
2764       ALLOCATE(npp_reset_value(nvm),stat=ier)
2765       l_error = l_error .OR. (ier /= 0)
2766       IF (l_error) THEN
2767          WRITE(numout,*) ' Memory allocation error for npp_reset_value. We stop. We need nvm words = ',nvm
2768          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2769       END IF
2770
2771       ALLOCATE(ndying_year(nvm),stat=ier)
2772       l_error = l_error .OR. (ier /= 0)
2773       IF (l_error) THEN
2774          WRITE(numout,*) ' Memory allocation error for ndying_year. We stop. We need nvm words = ',nvm
2775          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2776       END IF
2777
2778       !BEETLE
2779
2780
2781       ALLOCATE(remaining_beetles(nvm),stat=ier)
2782       l_error = l_error .OR. (ier /= 0)
2783       IF (l_error) THEN
2784          WRITE(numout,*) ' Memory allocation error for remaining_beetles. We stop. We need nvm words = ',nvm
2785          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2786       END IF
2787
2788       ALLOCATE(pressure_feedback(nvm),stat=ier)
2789       l_error = l_error .OR. (ier /= 0)
2790       IF (l_error) THEN
2791          WRITE(numout,*) ' Memory allocation error for pressure_feedback. We stop. We need nvm words = ',nvm
2792          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2793       END IF
2794
2795       ALLOCATE(age_susceptibility_a(nvm),stat=ier)
2796       l_error = l_error .OR. (ier /= 0)
2797       IF (l_error) THEN
2798          WRITE(numout,*) ' Memory allocation error for age_susceptibility_a. We stop. We need nvm words = ',nvm
2799          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2800       END IF
2801
2802       ALLOCATE(age_susceptibility_b(nvm),stat=ier)
2803       l_error = l_error .OR. (ier /= 0)
2804       IF (l_error) THEN
2805          WRITE(numout,*) ' Memory allocation error for age_susceptibility_b. We stop. We need nvm words = ',nvm
2806          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2807       END IF
2808
2809       ALLOCATE(age_susceptibility_c(nvm),stat=ier)
2810       l_error = l_error .OR. (ier /= 0)
2811       IF (l_error) THEN
2812          WRITE(numout,*) ' Memory allocation error for age_susceptibility_c. We stop. We need nvm words = ',nvm
2813          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2814       END IF
2815
2816       ALLOCATE(rdi_susceptibility_a(nvm),stat=ier)
2817       l_error = l_error .OR. (ier /= 0)
2818       IF (l_error) THEN
2819          WRITE(numout,*) ' Memory allocation error for rdi_susceptibility_a. We stop. We need nvm words = ',nvm
2820          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2821       END IF
2822
2823       ALLOCATE(rdi_susceptibility_b(nvm),stat=ier)
2824       l_error = l_error .OR. (ier /= 0)
2825       IF (l_error) THEN
2826          WRITE(numout,*) ' Memory allocation error for rdi_susceptibility_b. We stop. We need nvm words = ',nvm
2827          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2828       END IF
2829
2830       ALLOCATE(rdi_target_suscept(nvm),stat=ier)
2831       l_error = l_error .OR. (ier /= 0)
2832       IF (l_error) THEN
2833          WRITE(numout,*) ' Memory allocation error for rdi_target_suscept. We stop. We need nvm words = ',nvm
2834          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2835       END IF
2836
2837       ALLOCATE(share_susceptibility_a(nvm),stat=ier)
2838       l_error = l_error .OR. (ier /= 0)
2839       IF (l_error) THEN
2840          WRITE(numout,*) ' Memory allocation error for share_susceptibility_a. We stop. We need nvm words = ',nvm
2841          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2842       END IF
2843
2844       ALLOCATE(share_susceptibility_b(nvm),stat=ier)
2845       l_error = l_error .OR. (ier /= 0)
2846       IF (l_error) THEN
2847          WRITE(numout,*) ' Memory allocation error for share_susceptibility_b. We stop. We need nvm words = ',nvm
2848          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2849       END IF
2850
2851       ALLOCATE(drought_susceptibility_a(nvm),stat=ier)
2852       l_error = l_error .OR. (ier /= 0)
2853       IF (l_error) THEN
2854          WRITE(numout,*) ' Memory allocation error for drought_susceptibility_a. We stop. We need nvm words = ',nvm
2855          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2856       END IF
2857
2858       ALLOCATE(drought_susceptibility_b(nvm),stat=ier)
2859       l_error = l_error .OR. (ier /= 0)
2860       IF (l_error) THEN
2861          WRITE(numout,*) ' Memory allocation error for drought_susceptibility_b. We stop. We need nvm words = ',nvm
2862          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2863       END IF
2864
2865       ALLOCATE(windthrow_susceptibility_tune(nvm),stat=ier)
2866       l_error = l_error .OR. (ier /= 0)
2867       IF (l_error) THEN
2868          WRITE(numout,*) ' Memory allocation error for windthrow_susceptibility_tune. We stop. We need nvm words = ',nvm
2869          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2870       END IF
2871
2872      ALLOCATE(beetle_generation_a(nvm),stat=ier)
2873       l_error = l_error .OR. (ier /= 0)
2874       IF (l_error) THEN
2875          WRITE(numout,*) ' Memory allocation error for beetle_generation_a. We stop. We need nvm words = ',nvm
2876          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2877       END IF
2878
2879      ALLOCATE(beetle_generation_b(nvm),stat=ier)
2880       l_error = l_error .OR. (ier /= 0)
2881       IF (l_error) THEN
2882          WRITE(numout,*) ' Memory allocation error for beetle_generation_b. We stop. We need nvm words = ',nvm
2883          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2884       END IF
2885
2886      ALLOCATE(beetle_generation_c(nvm),stat=ier)
2887       l_error = l_error .OR. (ier /= 0)
2888       IF (l_error) THEN
2889          WRITE(numout,*) ' Memory allocation error for beetle_generation_c. We stop. We need nvm words = ',nvm
2890          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2891       END IF
2892
2893      ALLOCATE(min_temp_beetle(nvm),stat=ier)
2894       l_error = l_error .OR. (ier /= 0)
2895       IF (l_error) THEN
2896          WRITE(numout,*) ' Memory allocation error for min_temp_beetle. We stop. We need nvm words = ',nvm
2897          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2898       END IF
2899
2900      ALLOCATE(max_temp_beetle(nvm),stat=ier)
2901       l_error = l_error .OR. (ier /= 0)
2902       IF (l_error) THEN
2903          WRITE(numout,*) ' Memory allocation error for max_temp_beetle. We stop. We need nvm words = ',nvm
2904          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2905       END IF
2906
2907      ALLOCATE(opt_temp_beetle(nvm),stat=ier)
2908       l_error = l_error .OR. (ier /= 0)
2909       IF (l_error) THEN
2910          WRITE(numout,*) ' Memory allocation error for opt_temp_beetle. We stop. We need nvm words = ',nvm
2911          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2912       END IF
2913
2914
2915      ALLOCATE(eff_temp_beetle_a(nvm),stat=ier)
2916       l_error = l_error .OR. (ier /= 0)
2917       IF (l_error) THEN
2918          WRITE(numout,*) ' Memory allocation error for eff_temp_beetle_a. We stop. We need nvm words = ',nvm
2919          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2920       END IF
2921
2922      ALLOCATE(eff_temp_beetle_b(nvm),stat=ier)
2923       l_error = l_error .OR. (ier /= 0)
2924       IF (l_error) THEN
2925          WRITE(numout,*) ' Memory allocation error for eff_temp_beetle_b. We stop. We need nvm words = ',nvm
2926          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2927       END IF
2928
2929      ALLOCATE(eff_temp_beetle_c(nvm),stat=ier)
2930       l_error = l_error .OR. (ier /= 0)
2931       IF (l_error) THEN
2932          WRITE(numout,*) ' Memory allocation error for eff_temp_beetle_c. We stop. We need nvm words = ',nvm
2933          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2934       END IF
2935
2936      ALLOCATE(eff_temp_beetle_d(nvm),stat=ier)
2937       l_error = l_error .OR. (ier /= 0)
2938       IF (l_error) THEN
2939          WRITE(numout,*) ' Memory allocation error for eff_temp_beetle_d. We stop. We need nvm words = ',nvm
2940          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2941       END IF
2942
2943      ALLOCATE(diapause_thres_daylength(nvm),stat=ier)
2944       l_error = l_error .OR. (ier /= 0)
2945       IF (l_error) THEN
2946          WRITE(numout,*) ' Memory allocation error for diapause_thres_daylength. We stop. We need nvm words = ',nvm
2947          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2948       END IF
2949       ALLOCATE(wght_sirdi_a(nvm),stat=ier)
2950       l_error = l_error .OR. (ier /= 0)
2951       IF (l_error) THEN
2952          WRITE(numout,*) ' Memory allocation error for wgth_sirdi_a. We stop. We need nvm words = ',nvm
2953          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2954       END IF
2955
2956       ALLOCATE(wght_sirdi_b(nvm),stat=ier)
2957       l_error = l_error .OR. (ier /= 0)
2958       IF (l_error) THEN
2959          WRITE(numout,*) ' Memory allocation error for wgth_sirdi_b. We stop. We need nvm words = ',nvm
2960          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2961       END IF
2962
2963       ALLOCATE(wght_sid(nvm),stat=ier)
2964       l_error = l_error .OR. (ier /= 0)
2965       IF (l_error) THEN
2966          WRITE(numout,*) ' Memory allocation error for wgth_sid. We stop. We need nvm words = ',nvm
2967          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2968       END IF
2969
2970       ALLOCATE(wght_sis(nvm),stat=ier)
2971       l_error = l_error .OR. (ier /= 0)
2972       IF (l_error) THEN
2973          WRITE(numout,*) ' Memory allocation error for wgth_sis. We stop. We need nvm words = ',nvm
2974          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2975       END IF
2976
2977
2978       !
2979       ! WINDTHROW
2980       !
2981
2982       ALLOCATE(streamlining_c_leaf(nvm),stat=ier)
2983       l_error = l_error .OR. (ier /= 0)
2984       IF (l_error) THEN
2985          WRITE(numout,*) ' Memory allocation error for streamlining_c_leaf. We stop. We need nvm words = ',nvm
2986          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2987       END IF
2988
2989       ALLOCATE(streamlining_c_leafless(nvm),stat=ier)
2990       l_error = l_error .OR. (ier /= 0)
2991       IF (l_error) THEN
2992          WRITE(numout,*) ' Memory allocation error for streamlining_c_leafless. We stop. We need nvm words = ',nvm
2993          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
2994       END IF
2995
2996       ALLOCATE(streamlining_n_leaf(nvm),stat=ier)
2997       l_error = l_error .OR. (ier /= 0)
2998       IF (l_error) THEN
2999          WRITE(numout,*) ' Memory allocation error for streamlining_n_leaf. We stop. We need nvm words = ',nvm
3000          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3001       END IF
3002
3003       ALLOCATE(streamlining_n_leafless(nvm),stat=ier)
3004       l_error = l_error .OR. (ier /= 0)
3005       IF (l_error) THEN
3006          WRITE(numout,*) ' Memory allocation error for streamlining_n_leafless. We stop. We need nvm words = ',nvm
3007          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3008       END IF
3009
3010       ALLOCATE(modulus_rupture(nvm),stat=ier)
3011       l_error = l_error .OR. (ier /= 0)
3012       IF (l_error) THEN
3013          WRITE(numout,*) ' Memory allocation error for modulus_rupture. We stop. We need nvm words = ',nvm
3014          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3015       END IF
3016
3017       ALLOCATE(f_knot(nvm),stat=ier)
3018       l_error = l_error .OR. (ier /= 0)
3019       IF (l_error) THEN
3020          WRITE(numout,*) ' Memory allocation error for f_knot. We stop. We need nvm words = ',nvm
3021          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3022       END IF
3023
3024       ALLOCATE(overturning_free_draining_shallow(nvm),stat=ier)
3025       l_error = l_error .OR. (ier /= 0)
3026       IF (l_error) THEN
3027          WRITE(numout,*) ' Memory allocation error for overturning_free_draining_shallow. We stop. We need nvm words = ',nvm
3028          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3029       END IF
3030
3031       ALLOCATE(overturning_free_draining_shallow_leafless(nvm),stat=ier)
3032       l_error = l_error .OR. (ier /= 0)
3033       IF (l_error) THEN
3034          WRITE(numout,*) ' Memory allocation error for overturning_free_draining_shallow_leafless.',&
3035               ' We stop. We need nvm words = ',nvm
3036          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3037       END IF
3038
3039       ALLOCATE(overturning_free_draining_deep(nvm),stat=ier)
3040       l_error = l_error .OR. (ier /= 0)
3041       IF (l_error) THEN
3042          WRITE(numout,*) ' Memory allocation error for overturning_free_draining_deep. We stop. We need nvm words = ',nvm
3043          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3044       END IF
3045
3046       ALLOCATE(overturning_free_draining_deep_leafless(nvm),stat=ier)
3047       l_error = l_error .OR. (ier /= 0)
3048       IF (l_error) THEN
3049          WRITE(numout,*) ' Memory allocation error for overturning_free_draining_deep_leafles. We stop. We need nvm words = ',nvm
3050          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3051       END IF
3052
3053       ALLOCATE(overturning_free_draining_average(nvm),stat=ier)
3054       l_error = l_error .OR. (ier /= 0)
3055       IF (l_error) THEN
3056          WRITE(numout,*) ' Memory allocation error for overturning_free_draining_average. We stop. We need nvm words = ',nvm
3057          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3058       END IF
3059
3060       ALLOCATE(overturning_free_draining_average_leafless(nvm),stat=ier)
3061       l_error = l_error .OR. (ier /= 0)
3062       IF (l_error) THEN
3063          WRITE(numout,*) ' Memory allocation error for overturning_free_draining_average_leafless. ', &
3064               ' We stop. We need nvm words = ',nvm
3065          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3066       END IF
3067
3068       ALLOCATE(overturning_gleyed_shallow(nvm),stat=ier)
3069       l_error = l_error .OR. (ier /= 0)
3070       IF (l_error) THEN
3071          WRITE(numout,*) ' Memory allocation error for overturning_gleyed_shallow. We stop. We need nvm words = ',nvm
3072          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3073       END IF
3074
3075       ALLOCATE(overturning_gleyed_shallow_leafless(nvm),stat=ier)
3076       l_error = l_error .OR. (ier /= 0)
3077       IF (l_error) THEN
3078          WRITE(numout,*) ' Memory allocation error for overturning_gleyed_shallow_leafless. We stop. We need nvm words = ',nvm
3079          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3080       END IF
3081
3082       ALLOCATE(overturning_gleyed_deep(nvm),stat=ier)
3083       l_error = l_error .OR. (ier /= 0)
3084       IF (l_error) THEN
3085          WRITE(numout,*) ' Memory allocation error for overturning_gleyed_deep. We stop. We need nvm words = ',nvm
3086          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3087       END IF
3088
3089       ALLOCATE(overturning_gleyed_deep_leafless(nvm),stat=ier)
3090       l_error = l_error .OR. (ier /= 0)
3091       IF (l_error) THEN
3092          WRITE(numout,*) ' Memory allocation error for overturning_gleyed_deep_leafless. We stop. We need nvm words = ',nvm
3093          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3094       END IF
3095
3096       ALLOCATE(overturning_gleyed_average(nvm),stat=ier)
3097       l_error = l_error .OR. (ier /= 0)
3098       IF (l_error) THEN
3099          WRITE(numout,*) ' Memory allocation error for overturning_gleyed_average. We stop. We need nvm words = ',nvm
3100          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3101       END IF
3102
3103       ALLOCATE(overturning_gleyed_average_leafless(nvm),stat=ier)
3104       l_error = l_error .OR. (ier /= 0)
3105       IF (l_error) THEN
3106          WRITE(numout,*) ' Memory allocation error for overturning_gleyed_average_leafless. We stop. We need nvm words = ',nvm
3107          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3108       END IF
3109
3110       ALLOCATE(overturning_peaty_shallow(nvm),stat=ier)
3111       l_error = l_error .OR. (ier /= 0)
3112       IF (l_error) THEN
3113          WRITE(numout,*) ' Memory allocation error for overturning_peaty_shallow. We stop. We need nvm words = ',nvm
3114          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3115       END IF
3116
3117       ALLOCATE(overturning_peaty_shallow_leafless(nvm),stat=ier)
3118       l_error = l_error .OR. (ier /= 0)
3119       IF (l_error) THEN
3120          WRITE(numout,*) ' Memory allocation error for overturning_peaty_shallow_leafless. We stop. We need nvm words = ',nvm
3121          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3122       END IF
3123
3124       ALLOCATE(overturning_peaty_deep(nvm),stat=ier)
3125       l_error = l_error .OR. (ier /= 0)
3126       IF (l_error) THEN
3127          WRITE(numout,*) ' Memory allocation error for overturning_peaty_deep. We stop. We need nvm words = ',nvm
3128          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3129       END IF
3130
3131       ALLOCATE(overturning_peaty_deep_leafless(nvm),stat=ier)
3132       l_error = l_error .OR. (ier /= 0)
3133       IF (l_error) THEN
3134          WRITE(numout,*) ' Memory allocation error for overturning_peaty_deep_leafless. We stop. We need nvm words = ',nvm
3135          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3136       END IF
3137
3138       ALLOCATE(overturning_peaty_average(nvm),stat=ier)
3139       l_error = l_error .OR. (ier /= 0)
3140       IF (l_error) THEN
3141          WRITE(numout,*) ' Memory allocation error for overturning_peaty_average. We stop. We need nvm words = ',nvm
3142          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3143       END IF
3144
3145       ALLOCATE(overturning_peaty_average_leafless(nvm),stat=ier)
3146       l_error = l_error .OR. (ier /= 0)
3147       IF (l_error) THEN
3148          WRITE(numout,*) ' Memory allocation error for overturning_peaty_average_leafless. We stop. We need nvm words = ',nvm
3149          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3150       END IF
3151
3152       ALLOCATE(overturning_peat_shallow(nvm),stat=ier)
3153       l_error = l_error .OR. (ier /= 0)
3154       IF (l_error) THEN
3155          WRITE(numout,*) ' Memory allocation error for overturning_peat_shallow. We stop. We need nvm words = ',nvm
3156          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3157       END IF
3158
3159       ALLOCATE(overturning_peat_shallow_leafless(nvm),stat=ier)
3160       l_error = l_error .OR. (ier /= 0)
3161       IF (l_error) THEN
3162          WRITE(numout,*) ' Memory allocation error for overturning_peat_shallow_leafless. We stop. We need nvm words = ',nvm
3163          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3164       END IF
3165
3166       ALLOCATE(overturning_peat_deep(nvm),stat=ier)
3167       l_error = l_error .OR. (ier /= 0)
3168       IF (l_error) THEN
3169          WRITE(numout,*) ' Memory allocation error for overturning_peat_deep. We stop. We need nvm words = ',nvm
3170          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3171       END IF
3172
3173       ALLOCATE(overturning_peat_deep_leafless(nvm),stat=ier)
3174       l_error = l_error .OR. (ier /= 0)
3175       IF (l_error) THEN
3176          WRITE(numout,*) ' Memory allocation error for overturning_peat_deep_leafless. We stop. We need nvm words = ',nvm
3177          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3178       END IF
3179
3180       ALLOCATE(overturning_peat_average(nvm),stat=ier)
3181       l_error = l_error .OR. (ier /= 0)
3182       IF (l_error) THEN
3183          WRITE(numout,*) ' Memory allocation error for overturning_peat_average. We stop. We need nvm words = ',nvm
3184          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3185       END IF
3186
3187       ALLOCATE(overturning_peat_average_leafless(nvm),stat=ier)
3188       l_error = l_error .OR. (ier /= 0)
3189       IF (l_error) THEN
3190          WRITE(numout,*) ' Memory allocation error for overturning_peat_average_leafles. We stop. We need nvm words = ',nvm
3191          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3192       END IF
3193
3194       ALLOCATE(max_damage_further(nvm),stat=ier)
3195       l_error = l_error .OR. (ier /= 0)
3196       IF (l_error) THEN
3197          WRITE(numout,*) ' Memory allocation error for max_damage_further. We stop. We need nvm words = ',nvm
3198          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3199       END IF
3200
3201       ALLOCATE(max_damage_closer(nvm),stat=ier)
3202       l_error = l_error .OR. (ier /= 0)
3203       IF (l_error) THEN
3204          WRITE(numout,*) ' Memory allocation error for max_damage_cloeer. We stop. We need nvm words = ',nvm
3205          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3206       END IF
3207
3208       ALLOCATE(sfactor_further(nvm),stat=ier)
3209       l_error = l_error .OR. (ier /= 0)
3210       IF (l_error) THEN
3211          WRITE(numout,*) ' Memory allocation error for sfactor_further. We stop. We need nvm words = ',nvm
3212          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3213       END IF
3214
3215       ALLOCATE(sfactor_closer(nvm),stat=ier)
3216       l_error = l_error .OR. (ier /= 0)
3217       IF (l_error) THEN
3218          WRITE(numout,*) ' Memory allocation error for sfactor_closer. We stop. We need nvm words = ',nvm
3219          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3220       END IF
3221
3222       ALLOCATE(green_density(nvm),stat=ier)
3223       l_error = l_error .OR. (ier /= 0)
3224       IF (l_error) THEN
3225          WRITE(numout,*) ' Memory allocation error for green_density. We stop. We need nvm words = ',nvm
3226          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3227       END IF
3228
3229
3230       !
3231       ! CROPLAND MANAGEMENT
3232       !
3233       ALLOCATE(harvest_ratio(nvm),stat=ier)   
3234       l_error = l_error .OR. (ier /= 0)
3235       IF (l_error) THEN
3236          WRITE(numout,*) ' Memory allocation error for harvest_ratio. We stop. We need nvm words = ',nvm
3237          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3238       END IF
3239
3240    ENDIF ! (ok_stomate)
3241
3242    !! Following parameters are used with and without ok_stomate
3243
3244    ALLOCATE(nue_opt(nvm),stat=ier)
3245    l_error = l_error .OR. (ier /= 0)
3246    IF (l_error) THEN
3247       WRITE(numout,*) ' Memory allocation error for nue_opt. We stop. We need nvm words = ',nvm
3248       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3249    END IF
3250
3251    ALLOCATE(vmax_uptake(nvm,nionspec),stat=ier)
3252    l_error = l_error .OR. (ier /= 0)
3253    IF (l_error) THEN
3254       WRITE(numout,*) ' Memory allocation error for nue_opt. We stop. We need nvm*nionspec words = ',nvm,nionspec
3255       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3256    END IF
3257
3258    ALLOCATE(cn_leaf_min(nvm),stat=ier)
3259    l_error = l_error .OR. (ier /= 0)
3260    IF (l_error) THEN
3261       WRITE(numout,*) ' Memory allocation error for cn_leaf_min. We stop. We need nvm words = ',nvm
3262       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3263    END IF
3264   
3265    ALLOCATE(cn_leaf_max(nvm),stat=ier)
3266    l_error = l_error .OR. (ier /= 0)
3267    IF (l_error) THEN
3268       WRITE(numout,*) ' Memory allocation error for cn_leaf_max. We stop. We need nvm words = ',nvm
3269       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3270    END IF
3271
3272    ALLOCATE(cn_leaf_init(nvm),stat=ier)
3273    l_error = l_error .OR. (ier /= 0)
3274    IF (l_error) THEN
3275       WRITE(numout,*) ' Memory allocation error for cn_leaf_init. We stop. We need nvm words = ',nvm
3276       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3277    END IF
3278   
3279    ALLOCATE(ext_coeff_N(nvm),stat=ier)
3280    l_error = l_error .OR. (ier /= 0)
3281    IF (l_error) THEN
3282       WRITE(numout,*) ' Memory allocation error for ext_coeff_N. We stop. We need nvm words = ',nvm
3283       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3284    END IF
3285
3286    ALLOCATE(maint_resp_slope(nvm,3),stat=ier) 
3287    l_error = l_error .OR. (ier /= 0) 
3288    IF (l_error) THEN
3289       WRITE(numout,*) ' Memory allocation error for maint_resp_slope. We stop. We need nvm*3 words = ',nvm*3 
3290       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3291    END IF
3292    maint_resp_slope(:,:) = zero 
3293   
3294    ALLOCATE(maint_resp_slope_c(nvm),stat=ier) 
3295    l_error = l_error .OR. (ier /= 0) 
3296    IF (l_error) THEN
3297       WRITE(numout,*) ' Memory allocation error for maint_resp_slope_c. We stop. We need nvm words = ',nvm 
3298       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3299    END IF
3300   
3301    ALLOCATE(maint_resp_slope_b(nvm),stat=ier) 
3302    l_error = l_error .OR. (ier /= 0) 
3303    IF (l_error) THEN
3304       WRITE(numout,*) ' Memory allocation error for maint_resp_slope_b. We stop. We need nvm words = ',nvm 
3305       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3306    END IF
3307   
3308    ALLOCATE(maint_resp_slope_a(nvm),stat=ier) 
3309    l_error = l_error .OR. (ier /= 0) 
3310    IF (l_error) THEN
3311       WRITE(numout,*) ' Memory allocation error for maint_resp_slope_a. We stop. We need nvm words = ',nvm 
3312       CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
3313    END IF
3314
3315  END SUBROUTINE pft_parameters_alloc
3316
3317!! ================================================================================================================================
3318!! SUBROUTINE   : config_pft_parameters
3319!!
3320!>\BRIEF          This subroutine will read the imposed values for the global pft
3321!! parameters (sechiba + stomate). It is not called if IMPOSE_PARAM is set to NO.
3322!!
3323!! DESCRIPTION  : None
3324!!
3325!! RECENT CHANGE(S): None
3326!!
3327!! MAIN OUTPUT VARIABLE(S): None
3328!!
3329!! REFERENCE(S) : None
3330!!
3331!! FLOWCHART    : None
3332!! \n
3333!_ ================================================================================================================================
3334
3335  SUBROUTINE config_pft_parameters
3336
3337    IMPLICIT NONE
3338
3339    !! 0. Variables and parameters declaration
3340
3341    !! 0.4 Local variable
3342
3343    INTEGER(i_std) :: jv, ivm                   !! Index (untiless)
3344
3345    !_ ================================================================================================================================
3346
3347
3348    !
3349    ! Vegetation structure
3350    !
3351
3352    !Config Key   = LEAF_TAB
3353    !Config Desc  = leaf type : 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bare ground
3354    !Config if    = OK_STOMATE
3355    !Config Def   = 4, 1, 1, 2, 1, 1, 2, 1, 2, 3, 3, 3, 3
3356    !Config Help  =
3357    !Config Units = [-]
3358    CALL getin_p('LEAF_TAB',leaf_tab)
3359
3360    !Config Key   = PHENO_MODEL
3361    !Config Desc  = which phenology model is used? (tabulated)
3362    !Config if    = OK_STOMATE
3363    !Config Def   = none, none, moi, none, none, ncdgdd, none, ncdgdd, ngd, moigdd, moigdd, moigdd, moigdd
3364    !Config Help  =
3365    !Config Units = [-]
3366    CALL getin_p('PHENO_MODEL',pheno_model)
3367
3368    !! Redefine the values for is_tree, is_deciduous, is_needleleaf, is_evergreen if values have been modified
3369    !! in run.def
3370
3371    is_tree(:) = .FALSE.
3372    DO jv = 1,nvm
3373       IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
3374    END DO
3375    !
3376    is_deciduous(:) = .FALSE.
3377    DO jv = 1,nvm
3378       IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
3379    END DO
3380    !
3381    is_evergreen(:) = .FALSE.
3382    DO jv = 1,nvm
3383       IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
3384    END DO
3385    !
3386    is_needleleaf(:) = .FALSE.
3387    DO jv = 1,nvm
3388       IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
3389    END DO
3390
3391
3392    !Config Key   = SECHIBA_LAI
3393    !Config Desc  = laimax for maximum lai(see also type of lai interpolation)
3394    !Config if    = OK_SECHIBA or IMPOSE_VEG
3395    !Config Def   = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2.
3396    !Config Help  = Maximum values of lai used for interpolation of the lai map
3397    !Config Units = [m^2/m^2]
3398    CALL getin_p('SECHIBA_LAI',llaimax)
3399
3400    !Config Key   = LLAIMIN
3401    !Config Desc  = laimin for minimum lai(see also type of lai interpolation)
3402    !Config if    = OK_SECHIBA or IMPOSE_VEG
3403    !Config Def   = 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0.
3404    !Config Help  = Minimum values of lai used for interpolation of the lai map
3405    !Config Units = [m^2/m^2]
3406    CALL getin_p('LLAIMIN',llaimin)
3407
3408    !Config Key   = SLOWPROC_HEIGHT
3409    !Config Desc  = prescribed height of vegetation
3410    !Config if    = OK_SECHIBA
3411    !Config Def   = 0., 30., 30., 20., 20., 20., 15., 15., 15., .5, .6, 1., 1.
3412    !Config Help  =
3413    !Config Units = [m]
3414    CALL getin_p('SLOWPROC_HEIGHT',height_presc)
3415
3416    !Config Key   = Z0_OVER_HEIGHT
3417    !Config Desc  = factor to calculate roughness height from height of canopy
3418    !Config if    = OK_SECHIBA
3419    !Config Def   = 0., 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625
3420    !Config Help  =
3421    !Config Units = [-]
3422    CALL getin_p('Z0_OVER_HEIGHT',z0_over_height)
3423
3424    !
3425    !Config Key   = RATIO_Z0M_Z0H
3426    !Config Desc  = Ratio between z0m and z0h
3427    !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
3428    !Config if    = OK_SECHIBA
3429    !Config Help  =
3430    !Config Units = [-]
3431    CALL getin_p('RATIO_Z0M_Z0H',ratio_z0m_z0h)
3432
3433
3434    !Config Key   = TYPE_OF_LAI
3435    !Config Desc  = Type of behaviour of the LAI evolution algorithm
3436    !Config if    = OK_SECHIBA
3437    !Config Def   = inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter
3438    !Config Help  =
3439    !Config Units = [-]
3440    CALL getin_p('TYPE_OF_LAI',type_of_lai)
3441
3442    !Config Key   = NATURAL
3443    !Config Desc  = natural?
3444    !Config if    = OK_SECHIBA, OK_STOMATE
3445    !Config Def   = y, y, y, y, y, y, y, y, y, y, y, n, n
3446    !Config Help  =
3447    !Config Units = [BOOLEAN]
3448    CALL getin_p('NATURAL',natural)
3449
3450    !Config Key   = IS_TROPICAL
3451    !Config Desc  = PFT IS TROPICAL
3452    !Config if    = OK_STOMATE
3453    !Config Def   = FALSE, TRUE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE
3454    !Config Help  =
3455    !Config Units = [-]
3456    CALL getin_p('IS_TROPICAL',is_tropical)
3457
3458    !Config Key   = IS_TEMPERATE
3459    !Config Desc  = PFT IS TEMPERATE
3460    !Config if    = OK_STOMATE
3461    !Config Def   = FALSE, FALSE, FALSE, TRUE, TRUE, TRUE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE
3462    !Config Help  =
3463    !Config Units = [-]
3464    CALL getin_p('IS_TEMPERATE',is_temperate)
3465   
3466    !Config Key   = IS_BOREAL
3467    !Config Desc  = PFT IS BOREAL
3468    !Config if    = OK_STOMATE
3469    !Config Def   = FALSE, FALSE, FALSE, FALSE, FALSE, FALSE,TRUE, TRUE, TRUE, FALSE, FALSE, FALSE, FALSE
3470    !Config Help  =
3471    !Config Units = [-]
3472    CALL getin_p('IS_BOREAL',is_boreal)
3473
3474    !
3475    ! Photosynthesis
3476    !
3477
3478    !Config Key   = IS_C4
3479    !Config Desc  = flag for C4 vegetation types
3480    !Config if    = OK_SECHIBA or OK_STOMATE
3481    !Config Def   = n, n, n, n, n, n, n, n, n, n, n, y, n, y
3482    !Config Help  =
3483    !Config Units = [BOOLEAN]
3484    CALL getin_p('IS_C4',is_c4)
3485
3486    !Config Key   = VCMAX_FIX
3487    !Config Desc  = values used for vcmax when STOMATE is not activated
3488    !Config if    = OK_SECHIBA and NOT(OK_STOMATE)
3489    !Config Def   = 0., 40., 50., 30., 35., 40.,30., 40., 35., 60., 60., 70., 70.
3490    !Config Help  =
3491    !Config Units = [micromol/m^2/s]
3492    CALL getin_p('VCMAX_FIX',vcmax_fix)
3493
3494    !Config Key   = DOWNREG_CO2
3495    !Config Desc  = coefficient for CO2 downregulation (unitless)
3496    !Config if    =
3497    !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
3498    !Config Help  =
3499    !Config Units = [-]
3500    CALL getin_p('DOWNREG_CO2',downregulation_co2_coeff)
3501
3502    !Config Key   = E_KmC
3503    !Config Desc  = Energy of activation for KmC
3504    !Config if    =
3505    !Config Def   = undef,  79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430.
3506    !Config Help  = See Medlyn et al. (2002)
3507    !Config Units = [J mol-1]
3508    CALL getin_p('E_KMC',E_KmC)
3509
3510    !Config Key   = E_KmO
3511    !Config Desc  = Energy of activation for KmO
3512    !Config if    =
3513    !Config Def   = undef, 36380.,  36380.,  36380.,  36380.,  36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380.
3514    !Config Help  = See Medlyn et al. (2002)
3515    !Config Units = [J mol-1]
3516    CALL getin_p('E_KMO',E_KmO)
3517
3518    !Config Key   = E_Sco
3519    !Config Desc  = Energy of activation for Sco
3520    !Config if    =
3521    !Config Def   = undef, -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460.
3522    !Config Help  = See Table 2 of Yin et al. (2009) - Value for C4 plants is not mentioned - We use C3 for all plants
3523    !Config Units = [J mol-1]
3524    CALL getin_p('E_SCO',E_Sco)
3525   
3526    !Config Key   = E_gamma_star
3527    !Config Desc  = Energy of activation for gamma_star
3528    !Config if    =
3529    !Config Def   = undef, 37830.,  37830.,  37830.,  37830.,  37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830.
3530    !Config Help  = See Medlyn et al. (2002) from Bernacchi al. (2001)
3531    !Config Units = [J mol-1]
3532    CALL getin_p('E_GAMMA_STAR',E_gamma_star)
3533
3534    !Config Key   = E_Vcmax
3535    !Config Desc  = Energy of activation for Vcmax
3536    !Config if    =
3537    !Config Def   = undef, 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 67300., 71513., 67300.
3538    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3)
3539    !Config Units = [J mol-1]
3540    CALL getin_p('E_VCMAX',E_Vcmax)
3541
3542    !Config Key   = E_Jmax
3543    !Config Desc  = Energy of activation for Jmax
3544    !Config if    =
3545    !Config Def   = undef, 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 77900., 49884., 77900.
3546    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3)
3547    !Config Units = [J mol-1]
3548    CALL getin_p('E_JMAX',E_Jmax)
3549
3550    !Config Key   = aSV
3551    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax
3552    !Config if    =
3553    !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
3554    !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)
3555    !Config Units = [J K-1 mol-1]
3556    CALL getin_p('ASV',aSV)
3557
3558    !Config Key   = bSV
3559    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax
3560    !Config if    =
3561    !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.
3562    !Config Help  = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation
3563    !Config Units = [J K-1 mol-1 °C-1]
3564    CALL getin_p('BSV',bSV)
3565
3566    !Config Key   = TPHOTO_MIN
3567    !Config Desc  = minimum photosynthesis temperature (deg C)
3568    !Config if    = OK_STOMATE
3569    !Config Def   = undef,  -4., -4., -4., -4.,-4.,-4., -4., -4., -4., -4., -4., -4.
3570    !Config Help  =
3571    !Config Units = [-]
3572    CALL getin_p('TPHOTO_MIN',tphoto_min)
3573
3574    !Config Key   = TPHOTO_MAX
3575    !Config Desc  = maximum photosynthesis temperature (deg C)
3576    !Config if    = OK_STOMATE
3577    !Config Def   = undef, 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55.
3578    !Config Help  =
3579    !Config Units = [-]
3580    CALL getin_p('TPHOTO_MAX',tphoto_max)
3581
3582    !Config Key   = aSJ
3583    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax
3584    !Config if    =
3585    !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.
3586    !Config Help  = See Table 3 of Kattge & Knorr (2007) - and Table 2 of Yin et al. (2009) for C4 plants
3587    !Config Units = [J K-1 mol-1]
3588    CALL getin_p('ASJ',aSJ)
3589
3590    !Config Key   = bSJ
3591    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax
3592    !Config if    =
3593    !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.
3594    !Config Help  = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation
3595    !Config Units = [J K-1 mol-1 °C-1]
3596    CALL getin_p('BSJ',bSJ)
3597
3598    !Config Key   = D_Vcmax
3599    !Config Desc  = Energy of deactivation for Vcmax
3600    !Config if    =
3601    !Config Def   = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000.
3602    !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.
3603    !Config Units = [J mol-1]
3604    CALL getin_p('D_VCMAX',D_Vcmax)
3605
3606    !Config Key   = D_Jmax
3607    !Config Desc  = Energy of deactivation for Jmax
3608    !Config if    =
3609    !Config Def   = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000.
3610    !Config Help  = See Table 2 of Yin et al. (2009)
3611    !Config Units = [J mol-1]
3612    CALL getin_p('D_JMAX',D_Jmax)
3613   
3614    !Config Key   = E_gm
3615    !Config Desc  = Energy of activation for gm
3616    !Config if    = 
3617    !Config Def   = undef, 49600., 49600., 49600., 49600., 49600., 49600., 49600., 49600., 49600., undef, 49600., undef
3618    !Config Help  = See Table 2 of Yin et al. (2009)
3619    !Config Units = [J mol-1]
3620    CALL getin_p('E_GM',E_gm) 
3621   
3622    !Config Key   = S_gm
3623    !Config Desc  = Entropy term for gm
3624    !Config if    = 
3625    !Config Def   = undef, 1400., 1400., 1400., 1400., 1400., 1400., 1400., 1400., 1400., undef, 1400., undef
3626    !Config Help  = See Table 2 of Yin et al. (2009)
3627    !Config Units = [J K-1 mol-1]
3628    CALL getin_p('S_GM',S_gm) 
3629   
3630    !Config Key   = D_gm
3631    !Config Desc  = Energy of deactivation for gm
3632    !Config if    = 
3633    !Config Def   = undef, 437400., 437400., 437400., 437400., 437400., 437400., 437400., 437400., 437400., undef, 437400., undef
3634    !Config Help  = See Table 2 of Yin et al. (2009)
3635    !Config Units = [J mol-1]
3636    CALL getin_p('D_GM',D_gm) 
3637   
3638    !Config Key   = E_Rd
3639    !Config Desc  = Energy of activation for Rd
3640    !Config if    =
3641    !Config Def   = undef, 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390.
3642    !Config Help  = See Table 2 of Yin et al. (2009)
3643    !Config Units = [J mol-1]
3644    CALL getin_p('E_RD',E_Rd)
3645
3646    !Config Key   = VCMAX25
3647    !Config Desc  = Maximum rate of Rubisco activity-limited carboxylation at 25°C
3648    !Config if    = OK_STOMATE
3649    !Config Def   = undef, 45.0, 45.0, 35.0, 40.0, 50.0, 45.0, 35.0, 35.0, 50.0, 50.0, 60.0, 60.0
3650    !Config Help  = Notice that, with the introduction of the nitrogen cycle, this
3651    !Config         parameter is no longer used to influence the simulation.  It is kept solely as
3652    !Config         a way to compare to old revisions (nue_opt is the new parameter that controls
3653    !Config         photosynthesis in this way).
3654    !Config Units = [micromol/m^2/s]
3655    CALL getin_p('VCMAX25',Vcmax25)
3656
3657    !Config Key   = ARJV
3658    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio
3659    !Config if    = OK_STOMATE
3660    !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
3661    !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)
3662    !Config Units = [mu mol e- (mu mol CO2)-1]
3663    CALL getin_p('ARJV',arJV)
3664
3665    !Config Key   = BRJV
3666    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio
3667    !Config if    = OK_STOMATE
3668    !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.
3669    !Config Help  = See Table 3 of Kattge & Knorr (2007) -  We assume No acclimation term for C4 plants
3670    !Config Units = [(mu mol e- (mu mol CO2)-1) (°C)-1]
3671    CALL getin_p('BRJV',brJV)
3672
3673    !Config Key   = KmC25
3674    !Config Desc  = Michaelis–Menten constant of Rubisco for CO2 at 25°C
3675    !Config if    =
3676    !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.
3677    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants
3678    !Config Units = [ubar]
3679    CALL getin_p('KMC25',KmC25)
3680
3681    !Config Key   = KmO25
3682    !Config Desc  = Michaelis–Menten constant of Rubisco for O2 at 25°C
3683    !Config if    =
3684    !Config Def   = undef, 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 450000., 278400., 450000.
3685    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants
3686    !Config Units = [ubar]
3687    CALL getin_p('KMO25',KmO25)
3688
3689    !Config Key   = Sco25
3690    !Config Desc  = Relative CO2 /O2 specificity factor for Rubisco at 25°C
3691    !Config if    =
3692    !Config Def   = undef, 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2590., 2800., 2590.
3693    !Config Help  = See Table 2 of Yin et al. (2009)
3694    !Config Units = [bar bar-1]
3695    CALL getin_p('SCO25',Sco25)
3696   
3697    !Config Key   = gm25
3698    !Config Desc  = Mesophyll diffusion conductance at 25°C
3699    !Config if    = 
3700    !Config Def   = undef, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, undef, 0.4, undef
3701    !Config Help  = See legend of Figure 6 of Yin et al. (2009) and review by Flexas et al. (2008) - gm is not used for C4 plants
3702    !Config Units = [mol m-2 s-1 bar-1]
3703    CALL getin_p('GM25',gm25) 
3704   
3705    !Config Key   = gamma_star25
3706    !Config Desc  = Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
3707    !Config if    =
3708    !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
3709    !Config Help  = See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the same value (probably uncorrect)
3710    !Config Units = [ubar]
3711    CALL getin_p('gamma_star25',gamma_star25)
3712
3713    !Config Key   = a1
3714    !Config Desc  = Empirical factor involved in the calculation of fvpd
3715    !Config if    =
3716    !Config Def   = undef, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.72, 0.85, 0.72
3717    !Config Help  = See Table 2 of Yin et al. (2009)
3718    !Config Units = [-]
3719    CALL getin_p('A1',a1)
3720
3721    !Config Key   = b1
3722    !Config Desc  = Empirical factor involved in the calculation of fvpd
3723    !Config if    =
3724    !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
3725    !Config Help  = See Table 2 of Yin et al. (2009)
3726    !Config Units = [-]
3727    CALL getin_p('B1',b1)
3728
3729    !Config Key   = g0
3730    !Config Desc  = Residual stomatal conductance when irradiance approaches zero
3731    !Config if    =
3732    !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
3733    !Config Help  = Value from ORCHIDEE - No other reference.
3734    !Config Units = [mol m−2 s−1 bar−1]
3735    CALL getin_p('G0',g0)
3736
3737    !Config Key   = h_protons
3738    !Config Desc  = Number of protons required to produce one ATP
3739    !Config if    =
3740    !Config Def   = undef, 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4.
3741    !Config Help  = See Table 2 of Yin et al. (2009) - h parameter
3742    !Config Units = [mol mol-1]
3743    CALL getin_p('H_PROTONS',h_protons)
3744
3745    !Config Key   = fpsir
3746    !Config Desc  = Fraction of PSII e− transport rate partitioned to the C4 cycle
3747    !Config if    =
3748    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.4, undef, 0.4
3749    !Config Help  = See Table 2 of Yin et al. (2009)
3750    !Config Units = [-]
3751    CALL getin_p('FPSIR',fpsir)
3752
3753    !Config Key   = fQ
3754    !Config Desc  = Fraction of electrons at reduced plastoquinone that follow the Q-cycle
3755    !Config if    =
3756    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 1., undef, 1.
3757    !Config Help  = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used
3758    !Config Units = [-]
3759    CALL getin_p('FQ',fQ)
3760
3761    !Config Key   = fpseudo
3762    !Config Desc  = Fraction of electrons at PSI that follow pseudocyclic transport
3763    !Config if    =
3764    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1
3765    !Config Help  = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used
3766    !Config Units = [-]
3767    CALL getin_p('FPSEUDO',fpseudo)
3768
3769    !Config Key   = kp
3770    !Config Desc  = Initial carboxylation efficiency of the PEP carboxylase
3771    !Config if    =
3772    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.7, undef, 0.7
3773    !Config Help  = See Table 2 of Yin et al. (2009)
3774    !Config Units = [mol m−2 s−1 bar−1]
3775    CALL getin_p('KP',kp)
3776
3777    !Config Key   = alpha
3778    !Config Desc  = Fraction of PSII activity in the bundle sheath
3779    !Config if    =
3780    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1
3781    !Config Help  = See legend of Figure 6 of Yin et al. (2009)
3782    !Config Units = [-]
3783    CALL getin_p('ALPHA',alpha)
3784
3785    !Config Key   = gbs
3786    !Config Desc  = Bundle-sheath conductance
3787    !Config if    =
3788    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.003, undef, 0.003
3789    !Config Help  = See legend of Figure 6 of Yin et al. (2009)
3790    !Config Units = [mol m−2 s−1 bar−1]
3791    CALL getin_p('GBS',gbs)
3792
3793    !Config Key   = theta
3794    !Config Desc  = Convexity factor for response of J to irradiance
3795    !Config if    =
3796    !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
3797    !Config Help  = See Table 2 of Yin et al. (2009)   
3798    !Config Units = [−]
3799    CALL getin_p('THETA',theta)
3800
3801    !Config Key   = alpha_LL
3802    !Config Desc  = Conversion efficiency of absorbed light into J at strictly limiting light
3803    !Config if    =
3804    !Config Def   = undef, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372, 0.372
3805    !Config Help  = See comment from Yin et al. (2009) after eq. 4
3806    !Config Units = [mol e− (mol photon)−1]
3807    CALL getin_p('ALPHA_LL',alpha_LL)
3808
3809    !Config Key   = STRESS_VCMAX
3810    !Config Desc  = Stress on vcmax
3811    !Config if    = OK_SECHIBA or OK_STOMATE
3812    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3813    !Config Help  =
3814    !Config Units = [-]
3815    CALL getin_p('STRESS_VCMAX', stress_vcmax)
3816   
3817    !Config Key   = STRESS_GS
3818    !Config Desc  = Stress on gs
3819    !Config if    = OK_SECHIBA or OK_STOMATE
3820    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3821    !Config Help  =
3822    !Config Units = [-]
3823    CALL getin_p('STRESS_GS', stress_gs)
3824   
3825    !Config Key   = STRESS_GM
3826    !Config Desc  = Stress on gm
3827    !Config if    = OK_SECHIBA or OK_STOMATE
3828    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3829    !Config Help  =
3830    !Config Units = [-]
3831    CALL getin_p('STRESS_GM', stress_gm)
3832
3833    !Config Key   = EXT_COEFF
3834    !Config Desc  = extinction coefficient of the Monsi&Seaki relationship (1953)
3835    !Config if    = OK_SECHIBA or OK_STOMATE
3836    !Config Def   = .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
3837    !Config Help  =
3838    !Config Units = [-]
3839    CALL getin_p('EXT_COEFF',ext_coeff)
3840
3841    !Config Key   = EXT_COEFF_VEGETFRAC
3842    !Config Desc  = extinction coefficient used for the calculation of the bare soil fraction
3843    !Config if    = OK_SECHIBA or OK_STOMATE
3844    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3845    !Config Help  =
3846    !Config Units = [-]
3847    CALL getin_p('EXT_COEFF_VEGETFRAC',ext_coeff_vegetfrac)
3848
3849    !
3850    ! Water-hydrology - sechiba
3851    !
3852
3853    !Config Key   = HYDROL_HUMCSTE
3854    !Config Desc  = Parameter to describe the shape of the structural root profile
3855    !Config Def   = humcste_ref2m or humcste_ref4m depending on zmaxh
3856    !Config if    = OK_SECHIBA
3857    !Config Help  = See module constantes_mtc for different default values
3858    !Config Units = [-]
3859    CALL getin_p('HYDROL_HUMCSTE',humcste)
3860
3861    !Config Key   = MAX_ROOT_DEPTH
3862    !Config Desc  = Maximum depth of the root profile
3863    !Config Def   = Maximum depth of the root profile irrespective of the active layer thickness
3864    !Config if    = OK_SECHIBA
3865    !Config Help  = See module constantes_mtc for different default values
3866    !Config Units = [m]
3867    CALL getin_p('MAX_ROOT_DEPTH',max_root_depth)
3868
3869    !
3870    ! Soil - vegetation
3871    !
3872
3873    !Config Key   = PREF_SOIL_VEG
3874    !Config Desc  = The soil tile number for each vegetation
3875    !Config if    = OK_SECHIBA or OK_STOMATE
3876    !Config Def   = 1, 2, 2, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3
3877    !Config Help  = Gives the number of the soil tile on which we will
3878    !Config         put each vegetation. This allows to divide the hydrological column
3879    !Config Units = [-]       
3880    CALL getin_p('PREF_SOIL_VEG',pref_soil_veg)
3881
3882    !Config Key   = MAINT_RESP_SLOPE_C
3883    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant c of aT^2+bT+c , tabulated
3884    !Config if    = OK_STOMATE
3885    !Config Def   = undef, 0.12, 0.12, 0.16, 0.16, 0.16, 0.25, 0.25, 0.25, 0.16, 0.12, 0.16, 0.12
3886    !Config Help  =
3887    !Config Units = [-]
3888    CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) 
3889   
3890    !Config Key   = MAINT_RESP_SLOPE_B
3891    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant b of aT^2+bT+c , tabulated
3892    !Config if    = OK_STOMATE
3893    !Config Def   = undef, .0, .0, .0, .0, .0, .0, .0, .0, -.00133, .0, -.00133, .0 
3894    !Config Help  =
3895    !Config Units = [-]
3896    CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b) 
3897   
3898    !Config Key   = MAINT_RESP_SLOPE_A
3899    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant a of aT^2+bT+c , tabulated
3900    !Config if    = OK_STOMATE
3901    !Config Def   = undef, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0     
3902    !Config Help  =
3903    !Config Units = [-]
3904    CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a)
3905   
3906    !
3907    ! Vegetation - Age classes
3908    !
3909   
3910    !Config Key   = NVMAP
3911    !Config Desc  = The number of PFTs if we ignore age classes. 
3912    !Config if    = OK_SECHIBA or OK_STOMATE
3913    !Config Def   = nvm
3914    !Config Help  = Gives the total number of PFTs ignoring age classes.
3915    !               If nagec equals to 1, nvmap is just nvm.
3916    !Config Units = [-] 
3917    nvmap=nvm
3918    CALL getin_p('NVMAP',nvmap)
3919    WRITE(numout,*)'the number of pfts for nvmap used by the model: ',nvmap
3920    IF(nagec > 1 .AND. nvmap == nvm)THEN
3921       WRITE(numout,*) 'WARNING: The number of age classes is greater than one, but'
3922       WRITE(numout,*) '         the input file indicates that none of the PFTs have age classes.'
3923       WRITE(numout,*) '         You should change either nagec or nvmap.'
3924    ENDIF
3925   
3926    !Config Key   = AGEC_GROUP
3927    !Config Desc  = The species group that each PFT belongs to. 
3928    !Config if    = OK_SECHIBA or OK_STOMATE
3929    !Config Def   = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
3930    !Config Help  = The species group that each PFT belongs to.
3931    !Config         A single species/MTC can be represented by a fixed numeber
3932    !               of age classes. All age classes of the same species make up the
3933    !               species group. Within a species group it is assumed that the
3934    !               age classes are sorted from young to old. Note that it was chosen
3935    !               to represent the age classes by a diameter threshold rather than
3936    !               an age threshold. Diameter was picked because this relates better
3937    !               to height and stand structure and thus the biophysics of the stand
3938    !               than age (in different climate zone the canopy of stands with the
3939    !               same age is thought to differ much more than of stands with the
3940    !               same diameter).
3941    !Config Units = [-]   
3942    DO ivm=1,nvm
3943       agec_group(ivm)=ivm
3944    ENDDO
3945    CALL getin_p('AGEC_GROUP',agec_group)
3946   
3947  END SUBROUTINE config_pft_parameters
3948
3949
3950!! ================================================================================================================================
3951!! SUBROUTINE   : config_sechiba_pft_parameters
3952!!
3953!>\BRIEF        This subroutine will read the imposed values for the sechiba pft
3954!! parameters. It is not called if IMPOSE_PARAM is set to NO.
3955!!
3956!! DESCRIPTION  : None
3957!!
3958!! RECENT CHANGE(S): None
3959!!
3960!! MAIN OUTPUT VARIABLE(S): None
3961!!
3962!! REFERENCE(S) : None
3963!!
3964!! FLOWCHART    : None
3965!! \n
3966!_ ================================================================================================================================
3967
3968  SUBROUTINE config_sechiba_pft_parameters()
3969
3970    IMPLICIT NONE
3971
3972    !! 0. Variables and parameters declaration
3973
3974    !! 0.1 Input variables
3975
3976    !! 0.4 Local variable
3977
3978    !_ ================================================================================================================================
3979
3980    !
3981    ! Evapotranspiration -  sechiba
3982    !
3983
3984    !Config Key   = RSTRUCT_CONST
3985    !Config Desc  = Structural resistance
3986    !Config if    = OK_SECHIBA
3987    !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
3988    !Config Help  =
3989    !Config Units = [s/m]
3990    CALL getin_p('RSTRUCT_CONST',rstruct_const)
3991
3992    !Config Key   = KZERO
3993    !Config Desc  = A vegetation dependent constant used in the calculation of the surface resistance.
3994    !Config if    = OK_SECHIBA
3995    !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
3996    !Config Help  =
3997    !Config Units = [kg/m^2/s]
3998    CALL getin_p('KZERO',kzero)
3999
4000    !Config Key   = RVEG_PFT
4001    !Config Desc  = Artificial parameter to increase or decrease canopy resistance.
4002    !Config if    = OK_SECHIBA
4003    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
4004    !Config Help  = This parameter is set by PFT.
4005    !Config Units = [-]
4006    CALL getin_p('RVEG_PFT',rveg_pft)   
4007
4008    !
4009    ! Water-hydrology - sechiba
4010    !
4011
4012    !Config Key   = WMAX_VEG
4013    !Config Desc  = Maximum field capacity for each of the vegetations (Temporary): max quantity of water
4014    !Config if    = OK_SECHIBA
4015    !Config Def   = 150., 150., 150., 150., 150., 150., 150.,150., 150., 150., 150., 150., 150.
4016    !Config Help  =
4017    !Config Units = [kg/m^3]
4018    CALL getin_p('WMAX_VEG',wmax_veg)
4019
4020    !Config Key   = PERCENT_THROUGHFALL_PFT
4021    !Config Desc  = Percent by PFT of precip that is not intercepted by the canopy. Default value depend on run mode.
4022    !Config if    = OK_SECHIBA
4023    !Config Def   = Case offline [0. 0. 0....] else [30. 30. 30.....]
4024    !Config Help  = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
4025    !Config         will get directly to the ground without being intercepted, for each PFT.
4026    !Config Units = [%]
4027    CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
4028    throughfall_by_pft(:) = throughfall_by_pft(:) / 100. 
4029
4030
4031    !
4032    ! Albedo - sechiba
4033    !
4034
4035    !Config Key   = SNOWA_AGED_VIS
4036    !Config Desc  = Minimum snow albedo value for each vegetation type after aging (dirty old snow), visible albedo
4037    !Config if    = OK_SECHIBA
4038    !Config Def   = 0.74, 0.0, 0.0, 0.08, 0.24, 0.07, 0.18, 0.18, 0.33, 0.57, 0.57, 0.57, 0.57
4039    !Config Help  = Values optimized for ORCHIDEE2.0
4040    !Config Units = [-]
4041    CALL getin_p('SNOWA_AGED_VIS',snowa_aged_vis)
4042
4043    !Config Key   = SNOWA_AGED_NIR
4044    !Config Desc  = Minimum snow albedo value for each vegetation type after aging (dirty old snow), near infrared albedo
4045    !Config if    = OK_SECHIBA
4046    !Config Def   = 0.50, 0.0, 0.0, 0.10, 0.37, 0.08, 0.16, 0.17, 0.27, 0.44, 0.44, 0.44, 0.44 
4047    !Config Help  = Values optimized for ORCHIDEE2.0
4048    !Config Units = [-]
4049    CALL getin_p('SNOWA_AGED_NIR',snowa_aged_nir)
4050
4051    !Config Key   = SNOWA_DEC_VIS
4052    !Config Desc  = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow, visible albedo
4053    !Config if    = OK_SECHIBA
4054    !Config Def   = 0.21, 0.0, 0.0, 0.14, 0.08, 0.17, 0.05, 0.06, 0.09, 0.15, 0.15, 0.15, 0.15
4055    !Config Help  = Values optimized for ORCHIDEE2.0
4056    !Config Units = [-]
4057    CALL getin_p('SNOWA_DEC_VIS',snowa_dec_vis)
4058
4059    !Config Key   = SNOWA_DEC_NIR
4060    !Config Desc  = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow, near infrared albedo
4061    !Config if    = OK_SECHIBA
4062    !Config Def   = 0.13, 0.0, 0.0, 0.10, 0.10, 0.16, 0.04, 0.07, 0.08, 0.12, 0.12, 0.12, 0.12
4063    !Config Help  = Values optimized for ORCHIDEE2.0
4064    !Config Units = [-]
4065    CALL getin_p('SNOWA_DEC_NIR',snowa_dec_nir)
4066
4067    !Config Key   = ALB_LEAF_VIS
4068    !Config Desc  = leaf albedo of vegetation type, visible albedo
4069    !Config if    = OK_SECHIBA
4070    !Config Def   = 0.00, 0.04, 0.04, 0.04, 0.04, 0.03, 0.03, 0.03, 0.03, 0.06, 0.06, 0.06, 0.06
4071    !Config Help  = Values optimized for ORCHIDEE2.0
4072    !Config Units = [-]
4073    CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis)
4074
4075    !Config Key   = ALB_LEAF_NIR
4076    !Config Desc  = leaf albedo of vegetation type, near infrared albedo
4077    !Config if    = OK_SECHIBA
4078    !Config Def   = 0.00, 0.23, 0.18, 0.18, 0.20, 0.24, 0.15, 0.26, 0.20, 0.24, 0.27, 0.28, 0.26
4079    !Config Help  = Values optimized for ORCHIDEE2.0
4080    !Config Units = [-]
4081    CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir)
4082
4083    !Config Key  = LEAF_SSA_VIS
4084    !Config Desc = Leaf_single_scattering_albedo_vis values
4085    !Config If   = ALBEDO_TYPE is Pinty
4086    !Config Def  = 0.17192, 0.12560, 0.16230, 0.13838, 0.13202, 0.14720, 0.14680, 0.14415, 0.15485, 0.17544, 0.17384, 0.17302, 0.17116
4087    !Config Help  =
4088    !Config Units = [-]
4089    CALL getin_p('LEAF_SSA_VIS',leaf_ssa(:,ivis))
4090
4091    !Config Key  = LEAF_SSA_NIR
4092    !Config Desc = Leaf_single_scattering_albedo_nir values
4093    !Config If   = ALBEDO_TYPE is Pinty
4094    !Config Def  = 0.70253, 0.68189, 0.69684, 0.68778, 0.68356, 0.69533, 0.69520, 0.69195, 0.69180, 0.71236, 0.71904, 0.71220, 0.71190
4095    !Config Help  =
4096    !Config Units = [-]
4097    CALL getin_p('LEAF_SSA_NIR',leaf_ssa(:,inir))
4098    !
4099    !Config Key  = LEAF_PSD_VIS
4100    !Config Desc = Preferred scattering direction values in the visibile spectra
4101    !Config If   = ALBEDO_TYPE is Pinty
4102    !Config Def  = 1.00170, 0.96776, 0.99250, 0.97170, 0.97119, 0.98077, 0.97672, 0.97810, 0.98605, 1.00490, 1.00360, 1.00320, 1.00130
4103    !Config Help  =
4104    !Config Units = [-]
4105    CALL getin_p('LEAF_PSD_VIS',leaf_psd(:,ivis))
4106    !
4107    !Config Key  = LEAF_PSD_NIR
4108    !Config Desc =  Preferred scattering direction values in the near infrared spectra
4109    !Config If   = ALBEDO_TYPE is Pinty
4110    !Config Def  = 2.00520, 1.95120, 1.98990, 1.97020, 1.95900, 1.98190, 1.98890, 1.97400, 1.97780, 2.02430, 2.03350, 2.02070, 2.02150
4111    !Config Help  =
4112    !Config Units = [-]
4113    CALL getin_p('LEAF_PSD_NIR',leaf_psd(:,inir)) 
4114    !
4115    !Config Key  = BGRD_REF_VIS
4116    !Config Desc = Background reflectance values in the visibile spectra
4117    !Config If   = ALBEDO_TYPE is Pinty
4118    !Config Def   = 0.2300000,   0.0866667,   0.0800000,   0.0533333,   0.0700000,   0.0933333,   0.0533333, 0.0833333,   0.0633333,   0.1033330,   0.1566670,   0.1166670,   0.1200000
4119    !Config Help  =
4120    !Config Units = [-]
4121    CALL getin_p('BGRD_REF_VIS',bgd_reflectance(:,ivis)) 
4122    !
4123    !Config Key  = BGRD_REF_NIR
4124    !Config Desc = Background reflectance values in the near infrared spectra
4125    !Config If   = ALBEDO_TYPE is Pinty
4126    !Config Def   = 0.4200000,   0.1500000,   0.1300000,   0.0916667,   0.1066670,   0.1650000,   0.0900000, 0.1483330,   0.1066670,   0.1900000,   0.3183330,   0.2200000,   0.2183330
4127    !Config Help  =
4128    !Config Units = [-]
4129    CALL getin_p('BGRD_REF_NIR',bgd_reflectance(:,inir)) 
4130
4131    !Config Key  = LEAF_TO_SHOOT_CLUMPING
4132    !Config Desc = The leaf-to-shoot clumping factor
4133    !Config If   = ALBEDO_TYPE is Pinty
4134    !Config Def   = un, un, un, un, un, un, un, un, un, un, un, un, un
4135    !Config Help  =
4136    !Config Units = [-]
4137    CALL getin_p('LEAF_TO_SHOOT_CLUMPING',leaf_to_shoot_clumping(:)) 
4138    !
4139    !Config Key  = LAI_CORRECTION_FACTOR
4140    !Config Desc = The correction factor for the LAI for grasslands
4141    !              and crops (see note in pft_parameters)
4142    !Config If   = ALBEDO_TYPE is Pinty
4143    !Config Def   = un, un, un, un, un, un, un, un, un, un, un, un, un
4144    !Config Help  =
4145    !Config Units = [-]
4146    CALL getin_p('LAI_CORRECTION_FACTOR',lai_correction_factor(:)) 
4147
4148    !Config Key  = MIN_LEVEL_SEP
4149    !Config Desc = The minimum level thickness we use for photosynthesis
4150    !Config If   = ALBEDO_TYPE is Pinty
4151    !Config Def  = un, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1
4152    !Config Help  =
4153    !Config Units = [m]
4154    CALL getin_p('MIN_LEVEL_SEP',min_level_sep(:)) 
4155
4156    !Config Key  = LAI_TOP
4157    !Config Desc = Definition, in terms of LAI of the top layer
4158    !              (used to calculate one of the resistences of
4159    !              vbeta3) to calculate transpiration
4160    !Config If   = OK_SECHIBA
4161    !Config Def  = un, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1
4162    !Config Help  = Coupling of the canopy to the atmosphere. See ADVANCES IN ECOLOGICAL
4163    !               RESEARCH, VOLUME 15. Stomatal Control of Transpiration: Scaling Up
4164    !               from Leaf to Region. 1986. P. G. JARVIS and K. G. MCNAUGHTON
4165    !Config Units = [m2 m2]
4166    CALL getin_p('LAI_TOP',lai_top(:)) 
4167
4168    !
4169    ! Hydraulic architecture
4170    !
4171    !Config Key   = K_ROOT
4172    !Config Desc  = Fine root specific conductivity
4173    !Config if    = OK_STOMATE
4174    !Config Def   = (undef, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02, 7.02)*1.e-4
4175    !Config Help  =
4176    !Config Units = [m^{3} kg^{-1} s^{-1} MPa^{-1}]
4177    CALL getin_p('K_ROOT',k_root) 
4178
4179    !Config Key   = K_BELOWGROUND
4180    !Config Desc  = Belowground (roots + soil) specific conductivity used in allocation
4181    !Config if    = OK_STOMATE
4182    !Config Def   = (undef, 7., 7., 7., 7., 7., 7., 7., 7., 42., 42., 42., 42.)*1.e-7
4183    !Config Help  =
4184    !Config Units = [m^{3} kg^{-1} s^{-1} MPa^{-1}]
4185    CALL getin_p('K_BELOWGROUND',k_belowground)
4186
4187    !Config Key   = K_SAP
4188    !Config Desc  = Sapwood specific conductivity
4189    !Config if    = OK_STOMATE
4190    !Config Def   = (undef, 50., 10., 8., 5., 30., 8., 20., 8., undef, undef, undef, undef)*1.e-4
4191    !Config Help  =
4192    !Config Units = [m^{2} s^{-1} MPa^{-1}]
4193    CALL getin_p('K_SAP',k_sap)
4194
4195    !Config Key   = K_LEAF
4196    !Config Desc  = Leaf conductivity
4197    !Config if    = OK_STOMATE
4198    !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
4199    !Config Help  =
4200    !Config Units = [m s^{-1} MPa^{-1})]
4201    CALL getin_p('K_LEAF',k_leaf)
4202
4203    !Config Key   = PSI_LEAF
4204    !Config Desc  = Minimal leaf potential
4205    !Config if    = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION
4206    !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
4207    !Config Help  =
4208    !Config Units = [MPa]
4209    CALL getin_p('PSI_LEAF',psi_leaf)
4210
4211    !Config Key   = PSI_50
4212    !Config Desc  = Sapwood leaf water potential that causes 50% loss of xylem conductivity through cavitation
4213    !Config if    = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION
4214    !Config Def   = undef, -0.3, -1.3, -2.0, -1.7, -1.0, -2.0, -1.0, -2.0, undef, undef, undef, undef
4215    !Config Help  =
4216    !Config Units = [m s^{-1} MPa^{-1})]
4217    CALL getin_p('PSI_50',psi_50)     
4218
4219    !Config Key   = C_CAVITATION
4220    !Config Desc  = Shape parameter for loss of conductance
4221    !Config if    = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION
4222    !Config Def   = undef, 5., 3., 3., 3., 3., 3., 3., 3., undef, undef, undef, undef 
4223    !Config Help  =
4224    !Config Units = [-]
4225    CALL getin_p('C_CAVITATION',c_cavitation)
4226
4227    !Config Key   = SRL
4228    !Config Desc  = Specific root length
4229    !Config if    = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION,
4230    !Config if      HYDRAULIC_ARCHITECTURE
4231    !Config Def   = undef, 10, 10, 9.2, 9.2, 14, 18.3, 18.3, 18.3, undef, undef, undef, undef
4232    !Config Help  = Specific root length for the calculations of soil to root resistance.
4233    !Config Units = [m g^(-1)]
4234    CALL getin_p('SRL',srl)
4235
4236    !Config Key   = R_FROOT
4237    !Config Desc  = Fine root radius
4238    !Config if    = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION,
4239    !Config if      HYDRAULIC_ARCHITECTURE
4240    !Config Def   = undef,  0.29E-3, 0.29E-3,  0.29E-3,  0.29E-3, 0.29E-3,  0.24E-3, 0.21E-3,  0.21E-3, undef, undef,  undef,  undef
4241    !Config Help  = Fine root radius for the calculations of soil to root resistance
4242    !Config Units = [m]
4243    CALL getin_p('R_FROOT',r_froot)
4244
4245    !Config Key   = PSI_ROOT
4246    !Config Desc  = Minimum root water potential
4247    !Config if    = OK_STOMATE, 11-LAYERS, FUNCTIONAL ALLOCATION,
4248    !Config if      HYDRAULIC_ARCHITECTURE
4249    !Config Def   = undef, -4, -4, -4, -4, -4, -4, -4, -4, undef, undef, undef, undef
4250    !Config Help  = Minimum root water potential for the calculations of
4251    !               soil to root resistance.
4252    !Config Units = [MPa]
4253    CALL getin_p('PSI_ROOT',psi_root)
4254    !
4255    ! Laieff - .NOT. ok_stomate
4256    !
4257    !Config Key   = CROWN_TO_HEIGHT
4258    !Config Desc  = Ratio between tree height and the vertical crown diameter.
4259    !Config If    = OK_STOMATE
4260    !Config Def   = undef, 0.6, 0.6, 0.6, 0.6, 0.6, 0.8, 0.8, 0.8, 0., 0., 0.,
4261    !0.
4262    !Config Help  = Ratio between tree height and the vertical crown diameter.
4263    !If this value is changed check beforehand that the crown diameter will
4264    !never exceed the tree height.
4265    !Config Units = [-] 
4266    CALL getin_p('CROWN_TO_HEIGHT',crown_to_height)
4267
4268    !Config Key   = CROWN_VERTOHOR_DIA
4269    !Config Desc  = Ratio between the vertical and horizontal crown diameter height.
4270    !diameter
4271    !Config If    = OK_STOMATE
4272    !Config Def   = undef, 1.0, 1.0, 0.66, 1.0, 1.0, 0.66, 1.0, 1.0, 1.0, 1.0, 1.0,
4273    !1.0
4274    !Config Help  = Ratio between the vertical and horizontal crown diameter
4275    !height, so indirectly the horizontal crown diameter also depends on crown
4276    !diameter
4277    !Config Units = [-] 
4278    CALL getin_p('CROWN_VERTOHOR_DIA',crown_vertohor_dia)
4279
4280    !Config Key   = PIPE_DENSITY
4281    !Config Desc  =
4282    !Config if    =
4283    !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
4284    !Config Help  =
4285    !Config Units =
4286    CALL getin_p("PIPE_DENSITY",pipe_density)
4287    !
4288    !Config Key   = TREE_FF
4289    !Config Desc  = Tree form factor reducing the volume of a cylinder
4290    !               to the real volume of the tree shape (including the
4291    !               branches)
4292    !Config If    = OK_STOMATE
4293    !Config Def   = undef, 0.6, 0.6, 0.6, 0.6, 0.6, 0.8, 0.8, 0.8, 0., 0., 0., 0.
4294    !Config Help  =
4295    !Config Units = [-] 
4296    CALL getin_p('TREE_FF',tree_ff)
4297    !
4298    !Config Key   = PIPE_TUNE2
4299    !Config Desc  = height=pipe_tune2 * diameter**pipe_tune3
4300    !Config If    = OK_STOMATE
4301    !Config Def   = undef, 40., 40., 40., 40., 40., 40., 40., 40., 0., 0., 0., 0. 
4302    !Config Help  =
4303    !Config Units = [-]     
4304    CALL getin_p('PIPE_TUNE2',pipe_tune2) 
4305    !
4306    !Config Key   = PIPE_TUNE3
4307    !Config Desc  = height=pipe_tune2 * diameter**pipe_tune3
4308    !Config If    = OK_STOMATE
4309    !Config Def   = undef, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0., 0., 0., 0.   
4310    !Config Help  =
4311    !Config Units = [-]   
4312    CALL getin_p('PIPE_TUNE3',pipe_tune3)
4313    !
4314    !Config Key   = PIPE_TUNE4
4315    !Config Desc  = needed for stem diameter
4316    !Config If    = OK_STOMATE
4317    !Config Def   = undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0., 0., 0., 0.
4318    !Config Help  =
4319    !Config Units = [-] 
4320    CALL getin_p('PIPE_TUNE4',pipe_tune4)
4321    !
4322    !Config Key   = PIPE_K1
4323    !Config Desc  =
4324    !Config If    = OK_STOMATE
4325    !Config Def   = undef, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 8.e3, 0., 0., 0., 0.
4326    !Config Help  =
4327    !Config Units = [-]   
4328    CALL getin_p('PIPE_K1',pipe_k1)
4329    !
4330    !Config Key   = SLA
4331    !Config Desc  = specif leaf area
4332    !Config if    = OK_STOMATE
4333    !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
4334    !Config Help  =
4335    !Config Units = [m^2/gC]
4336    CALL getin_p('SLA',sla)
4337    !
4338    !Config Key   = SLAINIT
4339    !Config Desc  = initial specif leaf area at (ie at bottom of canopy eq. lai=0)
4340    !Config if    = OK_STOMATE
4341    !Config Def   = 2.6E-2, 2.6E-2, 4.4E-2, 1.4E-2, 3.0E-2, 3.9E-2, 1.3E-2, 3.7E-2, 2.4E-2, 3.1E-2, 3.1E-2, 3.9E-2, 3.9E-2
4342    !Config Help  =
4343    !Config Units = [m^2/gC]
4344    CALL getin_p('SLAINIT',slainit)
4345    !
4346    !Config Key   = LAI_TO_HEIGHT
4347    !Config Desc  = Convertion factor from lai to vegetation height for grasses and crops
4348    !Config if    = OK_STOMATE
4349    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, 0.2, 0.5, 0.2, 0.5
4350    !Config Help  =
4351    !Config Units = [m m2 m-2]
4352    CALL getin_p('LAI_TO_HEIGHT',lai_to_height)
4353
4354    IF ( ok_bvoc ) THEN
4355       !
4356       ! BVOC
4357       !
4358
4359       !Config Key   = ISO_ACTIVITY
4360       !Config Desc  = Biogenic activity for each age class : isoprene
4361       !Config if    = CHEMISTRY_BVOC
4362       !Config Def   = 0.5, 1.5, 1.5, 0.5
4363       !Config Help  =
4364       !Config Units = [-]
4365       CALL getin_p('ISO_ACTIVITY',iso_activity)
4366
4367       !Config Key   = METHANOL_ACTIVITY
4368       !Config Desc  = Isoprene emission factor for each age class : methanol
4369       !Config if    = CHEMISTRY_BVOC
4370       !Config Def   = 1., 1., 0.5, 0.5
4371       !Config Help  =
4372       !Config Units = [-]
4373       CALL getin_p('METHANOL_ACTIVITY',methanol_activity)
4374
4375       !Config Key   = EM_FACTOR_ISOPRENE
4376       !Config Desc  = Isoprene emission factor
4377       !Config if    = CHEMISTRY_BVOC
4378       !Config Def   = 0., 24., 24., 8., 16., 45., 8., 18., 0.5, 12., 18., 5., 5.
4379       !Config Help  =
4380       !Config Units = [ugC/g/h]
4381       CALL getin_p('EM_FACTOR_ISOPRENE',em_factor_isoprene)
4382
4383       !Config Key   = EM_FACTOR_MONOTERPENE
4384       !Config Desc  = Monoterpene emission factor
4385       !Config if    = CHEMISTRY_BVOC
4386       !Config Def   = 0., 2.0, 2.0, 1.8, 1.4, 1.6, 1.8, 1.4, 1.8, 0.8, 0.8,  0.22, 0.22
4387       !Config Help  =
4388       !Config Units = [ugC/g/h]
4389       CALL getin_p('EM_FACTOR_MONOTERPENE',em_factor_monoterpene)
4390
4391       !Config Key   = C_LDF_MONO
4392       !Config Desc  = Monoterpenes fraction dependancy to light
4393       !Config if    = CHEMISTRY_BVOC
4394       !Config Def   = 0.6
4395       !Config Help  =
4396       !Config Units = []
4397       CALL getin_p('C_LDF_MONO',LDF_mono)
4398
4399       !Config Key   = C_LDF_SESQ
4400       !Config Desc  = Sesquiterpenes fraction dependancy to light
4401       !Config if    = CHEMISTRY_BVOC
4402       !Config Def   = 0.5
4403       !Config Help  =
4404       !Config Units = []
4405       CALL getin_p('C_LDF_SESQ',LDF_sesq)
4406
4407       !Config Key   = C_LDF_METH
4408       !Config Desc  = Methanol fraction dependancy to light
4409       !Config if    = CHEMISTRY_BVOC
4410       !Config Def   = 0.8
4411       !Config Help  =
4412       !Config Units = []
4413       CALL getin_p('C_LDF_METH',LDF_meth)
4414
4415       !Config Key   = C_LDF_ACET
4416       !Config Desc  = Acetone fraction dependancy to light
4417       !Config if    = CHEMISTRY_BVOC
4418       !Config Def   = 0.2
4419       !Config Help  =
4420       !Config Units = []
4421       CALL getin_p('C_LDF_ACET',LDF_acet)
4422
4423       !Config Key   = EM_FACTOR_APINENE
4424       !Config Desc  = Alfa pinene  emission factor
4425       !Config if    = CHEMISTRY_BVOC
4426       !Config Def   = 0., 1.35, 1.35, 0.85, 0.95, 0.75, 0.85, 0.60, 1.98, 0.30, 0.30, 0.09, 0.09
4427       !Config Help  =
4428       !Config Units = [ugC/g/h]
4429       CALL getin_p('EM_FACTOR_APINENE',em_factor_apinene)
4430
4431       !Config Key   = EM_FACTOR_BPINENE
4432       !Config Desc  = Beta pinene  emission factor
4433       !Config if    = CHEMISTRY_BVOC
4434       !Config Def   = 0., 0.30, 0.30, 0.35, 0.25, 0.20, 0.35, 0.12, 0.45, 0.16, 0.12, 0.05, 0.05
4435       !Config Help  =
4436       !Config Units = [ugC/g/h]
4437       CALL getin_p('EM_FACTOR_BPINENE',em_factor_bpinene)
4438
4439       !Config Key   = EM_FACTOR_LIMONENE
4440       !Config Desc  = Limonene  emission factor
4441       !Config if    = CHEMISTRY_BVOC
4442       !Config Def   = 0., 0.25, 0.25, 0.20, 0.25, 0.14, 0.20, 0.135, 0.11, 0.19, 0.42, 0.03, 0.03
4443       !Config Help  =
4444       !Config Units = [ugC/g/h]
4445       CALL getin_p('EM_FACTOR_LIMONENE',em_factor_limonene)
4446
4447       !Config Key   = EM_FACTOR_MYRCENE
4448       !Config Desc  = Myrcene  emission factor
4449       !Config if    = CHEMISTRY_BVOC
4450       !Config Def   = 0., 0.20, 0.20, 0.12, 0.11, 0.065, 0.12, 0.036, 0.075, 0.08,  0.085, 0.015, 0.015
4451       !Config Help  =
4452       !Config Units = [ugC/g/h]
4453       CALL getin_p('EM_FACTOR_MYRCENE',em_factor_myrcene)
4454
4455       !Config Key   = EM_FACTOR_SABINENE
4456       !Config Desc  = Sabinene  emission factor
4457       !Config if    = CHEMISTRY_BVOC
4458       !Config Def   = 0., 0.20, 0.20, 0.12, 0.17, 0.70, 0.12, 0.50, 0.09, 0.085, 0.075, 0.02, 0.02
4459       !Config Help  =
4460       !Config Units = [ugC/g/h]
4461       CALL getin_p('EM_FACTOR_SABINENE',em_factor_sabinene)
4462
4463       !Config Key   = EM_FACTOR_CAMPHENE
4464       !Config Desc  = Camphene  emission factor
4465       !Config if    = CHEMISTRY_BVOC
4466       !Config Def   = 0., 0.15, 0.15, 0.10, 0.10, 0.01, 0.10, 0.01, 0.07, 0.07, 0.08, 0.01, 0.01
4467       !Config Help  =
4468       !Config Units = [ugC/g/h]
4469       CALL getin_p('EM_FACTOR_CAMPHENE',em_factor_camphene)
4470
4471       !Config Key   = EM_FACTOR_3CARENE
4472       !Config Desc  = 3-Carene  emission factor
4473       !Config if    = CHEMISTRY_BVOC
4474       !Config Def   = 0., 0.13, 0.13, 0.42, 0.02, 0.055, 0.42,0.025, 0.125, 0.085, 0.085, 0.065, 0.065
4475       !Config Help  =
4476       !Config Units = [ugC/g/h]
4477       CALL getin_p('EM_FACTOR_3CARENE',em_factor_3carene)
4478
4479       !Config Key   = EM_FACTOR_TBOCIMENE
4480       !Config Desc  = T-beta-ocimene  emission factor
4481       !Config if    = CHEMISTRY_BVOC
4482       !Config Def   = 0., 0.25, 0.25, 0.13, 0.09, 0.26, 0.13, 0.20, 0.085, 0.18, 0.18, 0.01, 0.01
4483       !Config Help  =
4484       !Config Units = [ugC/g/h]
4485       CALL getin_p('EM_FACTOR_TBOCIMENE', em_factor_tbocimene)
4486
4487       !Config Key   = EM_FACTOR_OTHERMONOT
4488       !Config Desc  = Other monoterpenes  emission factor
4489       !Config if    = CHEMISTRY_BVOC
4490       !Config Def   = 0., 0.17, 0.17, 0.11, 0.11, 0.125, 0.11, 0.274, 0.01, 0.15, 0.155, 0.035, 0.035
4491       !Config Help  =
4492       !Config Units = [ugC/g/h]
4493       CALL getin_p('EM_FACTOR_OTHERMONOT',em_factor_othermonot)
4494
4495       !Config Key   = EM_FACTOR_SESQUITERP
4496       !Config Desc  = Sesquiterpenes  emission factor
4497       !Config if    = CHEMISTRY_BVOC
4498       !Config Def   = 0., 0.45, 0.45, 0.13, 0.3, 0.36, 0.15, 0.3, 0.25, 0.6, 0.6, 0.08, 0.08
4499       !Config Help  =
4500       !Config Units = [ugC/g/h]
4501       CALL getin_p('EM_FACTOR_SESQUITERP',em_factor_sesquiterp)
4502
4503
4504
4505       !Config Key   = C_BETA_MONO
4506       !Config Desc  = Monoterpenes temperature dependency coefficient
4507       !Config if    = CHEMISTRY_BVOC
4508       !Config Def   = 0.1
4509       !Config Help  =
4510       !Config Units = []
4511       CALL getin_p('C_BETA_MONO',beta_mono)
4512
4513       !Config Key   = C_BETA_SESQ
4514       !Config Desc  = Sesquiterpenes temperature dependency coefficient
4515       !Config if    = CHEMISTRY_BVOC
4516       !Config Def   = 0.17
4517       !Config Help  =
4518       !Config Units = []
4519       CALL getin_p('C_BETA_SESQ',beta_sesq)
4520
4521       !Config Key   = C_BETA_METH
4522       !Config Desc  = Methanol temperature dependency coefficient
4523       !Config if    = CHEMISTRY_BVOC
4524       !Config Def   = 0.08
4525       !Config Help  =
4526       !Config Units = []
4527       CALL getin_p('C_BETA_METH',beta_meth)
4528
4529       !Config Key   = C_BETA_ACET
4530       !Config Desc  = Acetone temperature dependency coefficient
4531       !Config if    = CHEMISTRY_BVOC
4532       !Config Def   = 0.1
4533       !Config Help  =
4534       !Config Units = []
4535       CALL getin_p('C_BETA_ACET',beta_acet)
4536
4537       !Config Key   = C_BETA_OXYVOC
4538       !Config Desc  = Other oxygenated BVOC temperature dependency coefficient
4539       !Config if    = CHEMISTRY_BVOC
4540       !Config Def   = 0.13
4541       !Config Help  =
4542       !Config Units = []
4543       CALL getin_p('C_BETA_OXYVOC',beta_oxyVOC)
4544
4545       !Config Key   = EM_FACTOR_ORVOC
4546       !Config Desc  = ORVOC emissions factor
4547       !Config if    = CHEMISTRY_BVOC
4548       !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
4549       !Config Help  =
4550       !Config Units = [ugC/g/h] 
4551       CALL getin_p('EM_FACTOR_ORVOC',em_factor_ORVOC)
4552
4553       !Config Key   = EM_FACTOR_OVOC
4554       !Config Desc  = OVOC emissions factor
4555       !Config if    = CHEMISTRY_BVOC
4556       !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
4557       !Config Help  =
4558       !Config Units = [ugC/g/h]       
4559       CALL getin_p('EM_FACTOR_OVOC',em_factor_OVOC)
4560
4561       !Config Key   = EM_FACTOR_MBO
4562       !Config Desc  = MBO emissions factor
4563       !Config if    = CHEMISTRY_BVOC
4564       !Config Def   = 0., 2.e-5, 2.e-5, 1.4, 2.e-5, 2.e-5, 0.14, 2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5
4565       !Config Help  =
4566       !Config Units = [ugC/g/h] 
4567       CALL getin_p('EM_FACTOR_MBO',em_factor_MBO)
4568
4569       !Config Key   = EM_FACTOR_METHANOL
4570       !Config Desc  = Methanol emissions factor
4571       !Config if    = CHEMISTRY_BVOC
4572       !Config Def   = 0., 0.8, 0.8, 1.8, 0.9, 1.9, 1.8, 1.8, 1.8, 0.7, 0.9, 2., 2.
4573       !Config Help  =
4574       !Config Units = [ugC/g/h] 
4575       CALL getin_p('EM_FACTOR_METHANOL',em_factor_methanol)
4576
4577       !Config Key   = EM_FACTOR_ACETONE
4578       !Config Desc  = Acetone emissions factor
4579       !Config if    = CHEMISTRY_BVOC
4580       !Config Def   = 0., 0.25, 0.25, 0.3, 0.2, 0.33, 0.3, 0.25, 0.25, 0.2, 0.2, 0.08, 0.08
4581       !Config Help  =
4582       !Config Units = [ugC/g/h]     
4583       CALL getin_p('EM_FACTOR_ACETONE',em_factor_acetone)
4584
4585       !Config Key   = EM_FACTOR_ACETAL
4586       !Config Desc  = Acetaldehyde emissions factor
4587       !Config if    = CHEMISTRY_BVOC
4588       !Config Def   = 0., 0.2, 0.2, 0.2, 0.2, 0.25, 0.25, 0.16, 0.16, 0.12, 0.12, 0.035, 0.02
4589       !Config Help  =
4590       !Config Units = [ugC/g/h] 
4591       CALL getin_p('EM_FACTOR_ACETAL',em_factor_acetal)
4592
4593       !Config Key   = EM_FACTOR_FORMAL
4594       !Config Desc  = Formaldehyde emissions factor
4595       !Config if    = CHEMISTRY_BVOC
4596       !Config Def   = 0., 0.04, 0.04, 0.08, 0.04, 0.04, 0.04, 0.04, 0.04, 0.025, 0.025, 0.013, 0.013
4597       !Config Help  =
4598       !Config Units = [ugC/g/h] 
4599       CALL getin_p('EM_FACTOR_FORMAL',em_factor_formal)
4600
4601       !Config Key   = EM_FACTOR_ACETIC
4602       !Config Desc  = Acetic Acid emissions factor
4603       !Config if    = CHEMISTRY_BVOC
4604       !Config Def   = 0., 0.025, 0.025,0.025,0.022,0.08,0.025,0.022,0.013,0.012,0.012,0.008,0.008
4605       !Config Help  =
4606       !Config Units = [ugC/g/h] 
4607       CALL getin_p('EM_FACTOR_ACETIC',em_factor_acetic)
4608
4609       !Config Key   = EM_FACTOR_FORMIC
4610       !Config Desc  = Formic Acid emissions factor
4611       !Config if    = CHEMISTRY_BVOC
4612       !Config Def   = 0., 0.015, 0.015, 0.02, 0.02, 0.025, 0.025, 0.015, 0.015,0.010,0.010,0.008,0.008
4613       !Config Help  =
4614       !Config Units = [ugC/g/h] 
4615       CALL getin_p('EM_FACTOR_FORMIC',em_factor_formic)
4616
4617       !Config Key   = EM_FACTOR_NO_WET
4618       !Config Desc  = NOx emissions factor wet soil emissions and exponential dependancy factor
4619       !Config if    = CHEMISTRY_BVOC
4620       !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
4621       !Config Help  =
4622       !Config Units = [ngN/m^2/s]
4623       CALL getin_p('EM_FACTOR_NO_WET',em_factor_no_wet)
4624
4625       !Config Key   = EM_FACTOR_NO_DRY
4626       !Config Desc  = NOx emissions factor dry soil emissions and exponential dependancy factor
4627       !Config if    = CHEMISTRY_BVOC
4628       !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
4629       !Config Help  =
4630       !Config Units = [ngN/m^2/s]
4631       CALL getin_p('EM_FACTOR_NO_DRY',em_factor_no_dry)
4632
4633       !Config Key   = LARCH
4634       !Config Desc  = Larcher 1991 SAI/LAI ratio
4635       !Config if    = CHEMISTRY_BVOC
4636       !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
4637       !Config Help  =
4638       !Config Units = [-] 
4639       CALL getin_p('LARCH',Larch)
4640
4641    ENDIF ! (ok_bvoc)
4642
4643
4644    !Config Key   = NUE_OPT
4645    !Config Desc  = Nitrogen use efficiency of Vcmax
4646    !Config if    = OK_STOMATE
4647    !Config Def   = undef,  14.,  30., 20., 33.,  38., 15., 38., 22.,  45.,  45.,  60.,  60. 
4648    !Config Help  =
4649    !Config Units = [(mumol[CO2] s-1) (gN[leaf])-1]
4650    CALL getin_p('NUE_OPT',nue_opt)
4651
4652    !Config Key   = VMAX_UPTAKE_NH4
4653    !Config Desc  = Vmax of ammonium uptake by plant roots
4654    !Config if    = OK_STOMATE
4655    !Config Def   = undef,  9., 9., 9., 9., 9., 9., 9., 9., 9., 9., 9., 9. 
4656    !Config Help  =
4657    !Config Units = umol (g DryWeight_root)-1 h-1
4658    CALL getin_p('VMAX_UPTAKE_NH4',vmax_uptake(:,iammonium))
4659
4660    !Config Key   = VMAX_UPTAKE_NO3
4661    !Config Desc  = Vmax of nitrate uptake by plant roots
4662    !Config if    = OK_STOMATE
4663    !Config Def   = undef,  9., 9., 9., 9., 9., 9., 9., 9., 9., 9., 9., 9. 
4664    !Config Help  =
4665    !Config Units = umol (g DryWeight_root)-1 h-1
4666    CALL getin_p('VMAX_UPTAKE_NO3',vmax_uptake(:,initrate))
4667   
4668    !Config Key   = CN_LEAF_MIN
4669    !Config Desc  = minimum CN ratio of leaves 
4670    !Config if    = OK_STOMATE
4671    !Config Def   = undef, 16., 16., 28., 16., 16., 28., 16., 16., 16., 16., 16., 16.
4672    !Config Help  =
4673    !Config Units = [gC/gN]
4674    CALL getin_p("CN_LEAF_MIN", cn_leaf_min)
4675   
4676    !Config Key   = CN_LEAF_MAX
4677    !Config Desc  = maximum CN ratio of leaves 
4678    !Config if    = OK_STOMATE
4679    !Config Def   = undef, 45., 45., 75., 45., 45., 75., 45., 45., 45., 45., 45., 45.
4680    !Config Help  =
4681    !Config Units = [gC/gN]
4682    CALL getin_p("CN_LEAF_MAX", cn_leaf_max)
4683   
4684    !Config Key   = CN_LEAF_INIT
4685    !Config Desc  =
4686    !Config if    =
4687    !Config Def   = undef, 25.,  25.,  41.7,  25.,  25.,  43., 25.,  25.,  25.,  25.,  25.,  25.
4688    !Config Help  = Comes from Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x),
4689    !Config         although the defaults have changed for an unknown reason.  In Sitch et al,
4690    !Config         the leaf ratio is 29.
4691    !Config Units =
4692    CALL getin_p("CN_LEAF_INIT",cn_leaf_init)
4693
4694    !Config Key   = EXT_COEFF_N
4695    !Config Desc  = Extinction coefficient of the leaf N content profile within the canopy
4696    !Config if    = OK_STOMATE
4697    !Config Def   =  0.15, 0.15, 0.15,0.15,0.15, 0.15,0.15,0.15,0.15, 0.15, 0.15, 0.15, 0.15
4698    !Config Help  =
4699    !Config Units = [(m2[ground]) (m-2[leaf])]
4700    CALL getin_p('EXT_COEFF_N',ext_coeff_N)
4701
4702
4703  END SUBROUTINE config_sechiba_pft_parameters
4704
4705
4706!! ================================================================================================================================
4707!! SUBROUTINE   : config_stomate_pft_parameters
4708!!
4709!>\BRIEF         This subroutine will read the imposed values for the stomate pft
4710!! parameters. It is not called if IMPOSE_PARAM is set to NO.
4711!!
4712!! DESCRIPTION  : None
4713!!
4714!! RECENT CHANGE(S): None
4715!!
4716!! MAIN OUTPUT VARIABLE(S): None
4717!!
4718!! REFERENCE(S) : None
4719!!
4720!! FLOWCHART    : None
4721!! \n
4722!_ ================================================================================================================================
4723
4724  SUBROUTINE config_stomate_pft_parameters
4725
4726    IMPLICIT NONE
4727
4728    !! 0. Variables and parameters declaration
4729
4730    !! 0.4 Local variable
4731    INTEGER(i_std)  ::  ivma, ivm             !! indices for number of pfts with and without age classes
4732
4733    !_ ================================================================================================================================
4734
4735    !
4736    ! Vegetation structure
4737    !
4738    !Config Key   = AVAILABILITY_FACT
4739    !Config Desc  = Calculate dynamic mortality in lpj_gap, pft dependent parameter
4740    !Config If    = OK_STOMATE
4741    !Config Def   = undef, 0.14, 0.14, 0.10, 0.10, 0.10, 0.05, 0.05, 0.05, undef, undef, undef, undef
4742    !Config Help  =
4743    !Config Units = [-]   
4744    CALL getin_p('AVAILABILITY_FACT',availability_fact)
4745
4746    !
4747    ! Respiration - stomate
4748    !
4749
4750    !Config Key   = FRAC_GROWTHRESP
4751    !Config Desc  = fraction of GPP which is lost as growth respiration
4752    !Config if    = OK_STOMATE
4753    !Config Def   = undef, 0.35, 0.35, 0.28, 0.28, 0.28, 0.35, 0.35, 0.35, 0.28, 0.28, 0.28, 0.28
4754    !Config Help  =
4755    !Config Units = [-]
4756    CALL getin_p('FRAC_GROWTHRESP',frac_growthresp) 
4757   
4758    !Config Key   = COEFF_MAINT_INIT
4759    !Config Desc  = maintenance respiration coefficient at 10 deg C
4760    !Config if    = OK_STOMATE
4761    !Config Def   = undef, 3.06E-2, 3.06E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2, 6.46E-2
4762    !Config Help  =
4763    !Config Units = [gC/gN/day]
4764    CALL getin_p('COEFF_MAINT_INIT',coeff_maint_init)
4765
4766    !Config Key   = TREF_MAINT_RESP
4767    !Config Desc  = maintenance respiration Temperature coefficient
4768    !Config if    = OK_STOMATE
4769    !Config Def   =   &  undef, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02, 56.02   
4770    !Config Help  =
4771    !Config Units = [degC]
4772    CALL getin_p('TREF_MAINT_RESP',tref_maint_resp)
4773
4774    !Config Key   = TMIN_MAINT_RESP
4775    !Config Desc  = maintenance respiration Temperature coefficient
4776    !Config if    = OK_STOMATE
4777    !Config Def   =  undef, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02, 46.02   
4778    !Config Help  =
4779    !Config Units = [degC]
4780    CALL getin_p('TMIN_MAINT_RESP',tmin_maint_resp)
4781
4782    !Config Key   = E0_MAINT_RESP
4783    !Config Desc  = maintenance respiration Temperature coefficient
4784    !Config if    = OK_STOMATE
4785    !Config Def   = undef, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56, 308.56   
4786    !Config Help  =
4787    !Config Units = [-]
4788    CALL getin_p('E0_MAINT_RESP',e0_maint_resp)
4789
4790    !
4791    ! Allocation
4792    !
4793    !Config Key   = TREF_LABILE
4794    !Config Desc  = Growth from labile pool - temperature at which all labile Cmaintenance respiration Temperature coefficient
4795    !Config if    = OK_STOMATE
4796    !Config Def   = undef, 5, 5, 5, 5, 5, 5, 5, 5, 5, 5, 5, 5   
4797    !Config Help  =
4798    !Config Units = [degC]
4799    CALL getin_p('TREF_LABILE',tref_labile)
4800
4801    !Config Key   = TMIN_LABILE
4802    !Config Desc  = Growth from labile pool  - temperature above which labile will be allocated to growth
4803    !Config if    = OK_STOMATE
4804    !Config Def   = undef, -2, -2, -2, -2, -2, -2, -2, -2, -2, -2, -2, -2
4805    !Config Help  =
4806    !Config Units = [degC]
4807    CALL getin_p('TMIN_LABILE',tmin_labile)
4808
4809    !Config Key   = E0_LABILE
4810    !Config Desc  = Growth temperature coefficient - tuned see stomate_growth_fun_all.f90
4811    !Config if    = OK_STOMATE
4812    !Config Def   = undef, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15
4813    !Config Help  =
4814    !Config Units = [-]
4815    CALL getin_p('E0_LABILE',e0_labile)
4816
4817    !Config Key   = ALWAYS_LABILE
4818    !Config Desc  = share of the labile pool that will remain in the labile pool
4819    !Config if    = OK_STOMATE
4820    !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
4821    !Config Help  =
4822    !Config Units = [-]
4823    CALL getin_p('ALWAYS_LABILE',always_labile)
4824
4825    !
4826    ! Fire - stomate
4827    !
4828
4829    !Config Key   = FLAM
4830    !Config Desc  = flamability: critical fraction of water holding capacity
4831    !Config if    = OK_STOMATE
4832    !Config Def   = undef, .15, .25, .25, .25, .25, .25, .25, .25, .25, .25, .35, .35
4833    !Config Help  =
4834    !Config Units = [-]
4835    CALL getin_p('FLAM',flam)
4836
4837    !Config Key   = RESIST
4838    !Config Desc  = fire resistance
4839    !Config if    = OK_STOMATE
4840    !Config Def   = undef, .95, .90, .12, .50, .12, .12, .12, .12, .0, .0, .0, .0
4841    !Config Help  =
4842    !Config Units = [-]
4843    CALL getin_p('RESIST',resist)
4844
4845    !
4846    ! Flux - LUC
4847    !
4848    !Config Key   = COEFF_LCCHANGE_s
4849    !Config Desc  = Coeff of biomass export for the year
4850    !Config if    = OK_STOMATE
4851    !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
4852    !Config Help  =
4853    !Config Units = [-]
4854    CALL getin_p('COEFF_LCCHANGE_s',coeff_lcchange_s)
4855   
4856    !Config Key   = COEFF_LCCHANGE_m
4857    !Config Desc  = Coeff of biomass export for the decade
4858    !Config if    = OK_STOMATE
4859    !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
4860    !Config Help  =
4861    !Config Units = [-]
4862    CALL getin_p('COEFF_LCCHANGE_m',coeff_lcchange_m)
4863   
4864    !Config Key   = COEFF_LCCHANGE_l
4865    !Config Desc  = Coeff of biomass export for the century
4866    !Config if    = OK_STOMATE
4867    !Config Def   = undef, 0., 0., 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0., 0.104, 0.
4868    !Config Help  =
4869    !Config Units = [-]
4870    CALL getin_p('COEFF_LCCHANGE_l',coeff_lcchange_l)
4871
4872    !
4873    ! Phenology
4874    !
4875
4876    !Config Key   = LAI_MAX_TO_HAPPY
4877    !Config Desc  = threshold of LAI below which plant uses carbohydrate reserves
4878    !Config if    = OK_STOMATE
4879    !Config Def   = undef, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
4880    !Config Help  =
4881    !Config Units = [-]
4882    CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy) 
4883
4884    !Config Key   = LAI_MAX
4885    !Config Desc  = maximum LAI, PFT-specific
4886    !Config if    = OK_STOMATE
4887    !Config Def   = undef, 7.0, 5.0, 5.0, 4.0, 5.0, 3.5, 4.0, 3.0, 2.5, 2.0, 5.0, 5.0
4888    !Config Help  =
4889    !Config Units = [m^2/m^2]
4890    CALL getin_p('LAI_MAX',lai_max)
4891
4892    !Config Key   = PHENO_TYPE
4893    !Config Desc  = type of phenology, 0=bare ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
4894    !Config if    = OK_STOMATE
4895    !Config Def   = 0, 1, 3, 1, 1, 2, 1, 2, 2, 4, 4, 2, 3
4896    !Config Help  =
4897    !Config Units = [-]
4898    CALL getin_p('PHENO_TYPE',pheno_type)
4899
4900    !
4901    ! Phenology : Leaf Onset
4902    !
4903    !Config Key   = FORCE_PHENO
4904    !Config Desc  = Offset from mean doy at which phenology will be forced
4905    !Config if    = OK_STOMATE
4906    !Config Def   = undef, undef, 42, undef, undef, 42, undef, 28, 28, 35, 35, 28, 28
4907    !Config Help  =
4908    !Config Units = [days]
4909    CALL getin_p('FORCE_PHENO',force_pheno)
4910
4911    !Config Key   = PHENO_GDD_CRIT_C
4912    !Config Desc  = critical gdd, tabulated (C), constant c of aT^2+bT+c
4913    !Config if    = OK_STOMATE
4914    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 270., 400., 125., 400.
4915    !Config Help  =
4916    !Config Units = [-]
4917    CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c)
4918
4919    !Config Key   = PHENO_GDD_CRIT_B
4920    !Config Desc  = critical gdd, tabulated (C), constant b of aT^2+bT+c
4921    !Config if    = OK_STOMATE
4922    !Config Def   = undef, undef, undef, undef, undef, undef, undef,undef, undef, 6.25, 0., 0., 0.
4923    !Config Help  =
4924    !Config Units = [-]
4925    CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b)
4926
4927    !Config Key   = PHENO_GDD_CRIT_A
4928    !Config Desc  = critical gdd, tabulated (C), constant a of aT^2+bT+c
4929    !Config if    = OK_STOMATE
4930    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.03125,  0., 0., 0.
4931    !Config Help  =
4932    !Config Units = [-]
4933    CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a)
4934
4935    !Config Key   = PHENO_MOIGDD_T_CRIT
4936    !Config Desc  = Average temperature threashold for C4 grass used in pheno_moigdd
4937    !Config if    = OK_STOMATE
4938    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 22.0, undef, undef
4939    !Config Help  =
4940    !Config Units = [C]
4941    CALL getin_p('PHENO_MOIGDD_T_CRIT',pheno_moigdd_t_crit)
4942
4943    !Config Key   = NGD_CRIT
4944    !Config Desc  = critical ngd, tabulated. Threshold -5 degrees
4945    !Config if    = OK_STOMATE
4946    !Config Def   = undef, undef, undef, undef, undef, undef, undef, 0., undef, undef, undef, undef, undef
4947    !Config Help  = NGD : Number of Growing Days.
4948    !Config Units = [days]
4949    CALL getin_p('NGD_CRIT',ngd_crit)
4950
4951    !Config Key   = NCDGDD_TEMP
4952    !Config Desc  = critical temperature for the ncd vs. gdd function in phenology
4953    !Config if    = OK_STOMATE
4954    !Config Def   = undef, undef, undef, undef, undef, 5., undef, 0., undef, undef, undef, undef, undef
4955    !Config Help  =
4956    !Config Units = [C]
4957    CALL getin_p('NCDGDD_TEMP',ncdgdd_temp)
4958
4959    !Config Key   = HUM_FRAC
4960    !Config Desc  = critical humidity (relative to min/max) for phenology
4961    !Config if    = OK_STOMATE
4962    !Config Def   = undef, undef, .5, undef, undef, undef, undef, undef,  undef, .5, .5, .5,.5     
4963    !Config Help  =
4964    !Config Units = [%]
4965    CALL getin_p('HUM_FRAC',hum_frac)
4966
4967    !Config Key   = HUM_MIN_TIME
4968    !Config Desc  = minimum time elapsed since moisture minimum
4969    !Config if    = OK_STOMATE
4970    !Config Def   = undef, undef, 50., undef, undef, undef, undef, undef, undef, 35., 35., 75., 75.
4971    !Config Help  =
4972    !Config Units = [days]
4973    CALL getin_p('HUM_MIN_TIME',hum_min_time)
4974
4975    !Config Key   = LONGEVITY_SAP
4976    !Config Desc  = sapwood -> heartwood conversion time
4977    !Config if    = OK_STOMATE
4978    !Config Def   = undef, 730., 730., 730., 730., 730., 730., 730., 730., undef, undef, undef, undef
4979    !Config Help  =
4980    !Config Units = [days]
4981    CALL getin_p('LONGEVITY_SAP',longevity_sap)
4982
4983    !Config Key   = LONGEVITY_LEAF
4984    !Config Desc  = leaf longivety
4985    !Config if    = OK_STOMATE
4986    !Config Def   = undef, 730., 180., 910., 730., 180., 910., 180., 180., 120., 120., 90., 90.
4987    !Config Help  =
4988    !Config Units = [days]
4989    CALL getin_p('LONGEVITY_LEAF',longevity_leaf)
4990
4991    !Config Key   = LEAF_AGE_CRIT_TREF
4992    !Config Desc  = Reference temperature
4993    !Config if    = OK_STOMATE
4994    !Config Def   = undef, 25., 25., 15., 20., 15., 5., 5., 5., 15., 20., 15., 20.
4995    !Config Help  = Reference temperature of the PFT (degrees Celsius)
4996    !               Used to calculate the leaf_age_crit as a function of longevity_leaf
4997    !Config Units = [degrees C]
4998    CALL getin_p('LEAF_AGE_CRIT_TREF',leaf_age_crit_tref)
4999
5000    !Config Key   = LEAF_AGE_CRIT_COEFF1
5001    !Config Desc  = Coeff1 (unitless) to link leaf_age_crit to leaf_age_crit_tref
5002    !Config if    = OK_STOMATE
5003    !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
5004    !Config Help  =
5005    !Config Units = [-]
5006    CALL getin_p('LEAF_AGE_CRIT_COEFF1',leaf_age_crit_coeff1)
5007
5008    !Config Key   = LEAF_AGE_CRIT_COEFF2
5009    !Config Desc  = Coeff1 (unitless) to link leaf_age_crit to leaf_age_crit_tref
5010    !Config if    = OK_STOMATE
5011    !Config Def   = undef, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75, 0.75
5012    !Config Help  =
5013    !Config Units = [-]
5014    CALL getin_p('LEAF_AGE_CRIT_COEFF2',leaf_age_crit_coeff2)
5015
5016    !Config Key   = LEAF_AGE_CRIT_COEFF3
5017    !Config Desc  = Coeff1 (unitless) to link leaf_age_crit to leaf_age_crit_tref
5018    !Config if    = OK_STOMATE
5019    !Config Def   = undef, 10., 10., 10., 10., 10., 10., 10., 10., 10., 10., 10., 10.
5020    !Config Help  =
5021    !Config Units = [-]
5022    CALL getin_p('LEAF_AGE_CRIT_COEFF3',leaf_age_crit_coeff3)
5023   
5024
5025    !Config Key   = LONGEVITY_FRUIT
5026    !Config Desc  = fruit lifetime
5027    !Config if    = OK_STOMATE
5028    !Config Def   = undef, 90., 90., 90., 90., 90., 90., 90., 90., undef, undef, undef, undef
5029    !Config Help  =
5030    !Config Units = [days]
5031    CALL getin_p('LONGEVITY_FRUIT',longevity_fruit)
5032
5033    !Config Key   = LONGEVITY_ROOT
5034    !Config Desc  = root longivety
5035    !Config if    = OK_STOMATE
5036    !Config Def   = undef, 256., 256., 256., 256., 256., 256., 256., 256., 256., 256., 256., 256.
5037    !Config Help  =
5038    !Config Units = [days]
5039    CALL getin_p('LONGEVITY_ROOT',longevity_root)
5040
5041    !Config Key   = ECUREUIL
5042    !Config Desc  = fraction of primary leaf and root allocation put into reserve
5043    !Config if    = OK_STOMATE
5044    !Config Def   = undef, .0, 1., .0, .0, 1., .0, 1., 1., 1., 1., 1., 1.
5045    !Config Help  =
5046    !Config Units = [-]
5047    CALL getin_p('ECUREUIL',ecureuil)
5048
5049    !Config Key   = ALLOC_MIN
5050    !Config Desc  = minimum allocation above/below = f(age) - 30/01/04 NV/JO/PF
5051    !Config if    = OK_STOMATE
5052    !Config Def   = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef
5053    !Config Help  =
5054    !Config Units = [-]
5055    CALL getin_p('ALLOC_MIN',alloc_min)
5056
5057    !Config Key   = ALLOC_MAX
5058    !Config Desc  = maximum allocation above/below = f(age) - 30/01/04 NV/JO/PF
5059    !Config if    = OK_STOMATE
5060    !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef
5061    !Config Help  =
5062    !Config Units = [-]
5063    CALL getin_p('ALLOC_MAX',alloc_max)
5064
5065    !Config Key   = DEMI_ALLOC
5066    !Config Desc  = mean allocation above/below = f(age) - 30/01/04 NV/JO/PF
5067    !Config if    = OK_STOMATE
5068    !Config Def   = undef, 5., 5., 5., 5., 5., 5., 5., 5., undef, undef, undef, undef
5069    !Config Help  =
5070    !Config Units = [-]
5071    CALL getin_p('DEMI_ALLOC',demi_alloc)
5072
5073    !Config Key   = K_LATOSA_MAX
5074    !Config Desc  = Maximum leaf-to-sapwood area ratio
5075    !Config if    = OK_STOMATE
5076    !Config Def   = (undef, 5., 5., 5., 3., 5., 5., 5., 5., undef, undef, undef, undef)*1.e3
5077    !Config Help  =
5078    !Config Units = [-]
5079    CALL getin_p('K_LATOSA_MAX',k_latosa_max)
5080
5081    !Config Key   = K_LATOSA_MIN
5082    !Config Desc  = Minimum leaf-to-sapwood area ratio
5083    !Config if    = OK_STOMATE
5084    !Config Def   = (undef, 5., 5., 5., 3., 5., 5., 5., 5., undef, undef, undef, undef)*1.e3
5085    !Config Help  =
5086    !Config Units = [-]
5087    CALL getin_p('K_LATOSA_MIN',k_latosa_min) 
5088
5089    !
5090    ! SOM decomposition (stomate)
5091    !
5092
5093    !Config Key   = LC_leaf
5094    !Config Desc  = Lignine/C ratio of leaf pool
5095    !Config If    = OK_STOMATE
5096    !Config Def   = undef, 0.18, 0.18, 0.24, 0.18, 0.18, 0.24, 0.18, 0.24, 0.09, 0.09, 0.09, 0.09
5097    !Config Help  =
5098    !Config Units = [-]   
5099    CALL getin_p('LC_leaf',LC_leaf)
5100
5101    !Config Key   = LC_sapabove
5102    !Config Desc  = Lignine/C ratio of sapabove pool
5103    !Config If    = OK_STOMATE
5104    !Config Def   = undef, 0.23, 0.23, 0.29, 0.23, 0.23, 0.29, 0.23, 0.29, 0.09, 0.09, 0.09, 0.09
5105    !Config Help  =
5106    !Config Units = [-]   
5107    CALL getin_p('LC_sapabove',LC_sapabove)
5108
5109    !Config Key   = LC_sapbelow
5110    !Config Desc  = Lignine/C ratio of sapbelow pool
5111    !Config If    = OK_STOMATE
5112    !Config Def   = undef, 0.23, 0.23, 0.29, 0.23, 0.23, 0.29, 0.23, 0.29, 0.09, 0.09, 0.09, 0.09
5113    !Config Help  =
5114    !Config Units = [-]   
5115    CALL getin_p('LC_sapbelow',LC_sapbelow)
5116
5117    !Config Key   = LC_heartabove
5118    !Config Desc  = Lignine/C ratio of heartabove pool
5119    !Config If    = OK_STOMATE
5120    !Config Def   = undef, 0.23, 0.23, 0.29, 0.23, 0.23, 0.29, 0.23, 0.29, 0.09, 0.09, 0.09, 0.09
5121    !Config Help  =
5122    !Config Units = [-]   
5123    CALL getin_p('LC_heartabove',LC_heartabove)
5124
5125    !Config Key   = LC_heartbelow
5126    !Config Desc  = Lignine/C ratio of heartbelow pool
5127    !Config If    = OK_STOMATE
5128    !Config Def   = undef, 0.23, 0.23, 0.29, 0.23, 0.23, 0.29, 0.23, 0.29, 0.09, 0.09, 0.09, 0.09
5129    !Config Help  =
5130    !Config Units = [-]   
5131    CALL getin_p('LC_heartbelow',LC_heartbelow)
5132
5133    !Config Key   = LC_fruit
5134    !Config Desc  = Lignine/C ratio of fruit pool
5135    !Config If    = OK_STOMATE
5136    !Config Def   = undef, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09, 0.09
5137    !Config Help  =
5138    !Config Units = [-]   
5139    CALL getin_p('LC_fruit',LC_fruit)
5140
5141    !Config Key   = LC_root
5142    !Config Desc  = Lignine/C ratio of fruit pool
5143    !Config If    = OK_STOMATE
5144    !Config Def   = undef, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22, 0.22
5145    !Config Help  =
5146    !Config Units = [-]   
5147    CALL getin_p('LC_root',LC_root)
5148
5149    !Config Key   = LC_carbres
5150    !Config Desc  = Lignine/C ratio of carbres pool
5151    !Config If    = OK_STOMATE
5152    !Config Def   = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
5153    !Config Help  =
5154    !Config Units = [-]   
5155    CALL getin_p('LC_carbres',LC_carbres)
5156
5157    !Config Key   = LC_labile
5158    !Config Desc  = Lignine/C ratio of labile pool
5159    !Config If    = OK_STOMATE
5160    !Config Def   = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
5161    !Config Help  =
5162    !Config Units = [-]   
5163    CALL getin_p('LC_labile',LC_labile)
5164
5165    !Config Key   = DECOMP_FACTOR
5166    !Config Desc  = Multpliactive factor modifying the standard decomposition factor for each SOM pool
5167    !Config if    =
5168    !Config Def   = undef, 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.2, 1.4
5169    !Config Help  =
5170    !Config Units =
5171    CALL getin_p("DECOMP_FACTOR",decomp_factor)
5172
5173    !
5174    ! Stand structure - stomate
5175    !
5176    !Config Key   = MASS_RATIO_HEART_SAP
5177    !Config Desc  = mass ratio (heartwood+sapwood)/heartwood
5178    !Config If    = OK_STOMATE
5179    !Config Def   = undef, 3., 3., 3., 3., 3., 3., 3., 3., 0., 0., 0., 0. 
5180    !Config Help  =
5181    !Config Units = [-]   
5182    CALL getin_p('MASS_RATIO_HEART_SAP',mass_ratio_heart_sap)
5183
5184    !Config Key   = CANOPY_COVER
5185    !Config Desc  = Test values for canopy cover
5186    !Config if    = OK_STOMATE
5187    !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
5188    !Config Help  =
5189    !Config Units = [-]
5190    CALL getin_p('CANOPY_COVER',canopy_cover)
5191
5192    !Config Key   = NMAXPLANTS
5193    !Config Desc  = number of grasses and crops planted at the start of a rotation
5194    !Config if    = OK_STOMATE
5195    !Config Def   = (undef, 15, 15, 15, 15, 15, 15, 15, 15, 10., 10., 10., 10.)*1.e3
5196    !Cofig Help   = An individual grass or crop is 1m2. Number of grasses and crops
5197    !               planted at the start of a rotation
5198    !Config Units = [trees ha-1]
5199    CALL getin_p("NMAXPLANTS",nmaxplants)
5200
5201    !Config Key   = P_USE_RESERVE
5202    !Config Dest  = Maximum ratio to use reserve to fill labile N in case of N limitation
5203    !Config If    = OK_STOMATE
5204    !Config Def   =
5205    !undef,0.9,0.9,0.9,0.9,0.9,0.9,0.9,0.9,undef,undef,undef,undef
5206    !Config Help  =
5207    !Config Units = [-]
5208    CALL getin_p("P_USE_RESERVE",p_use_reserve)
5209
5210    !Config Key   = HEIGHT_INIT
5211    !Config Desc  = height of a newly established vegetation
5212    !Config if    = OK_STOMATE
5213    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.3, 0.3, 0.3, 0.3
5214    !Config Help  = Initially defined for trees, grasses and crops. Now
5215    !               only used for grasses and crops.
5216    !Config Units = [m]
5217    CALL getin_p("HEIGHT_INIT",height_init)
5218
5219    !Config Key   = DIA_INIT_MIN
5220    !Config Desc  = minimum diameter of a newly established forest stand
5221    !Config if    = OK_STOMATE
5222    !Config Def   = undef, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, 0.02, undef, undef, undef, undef
5223    !Config Help  =
5224    !Config Units = [m]
5225    CALL getin_p("DIA_INIT_MIN",dia_init_min)
5226
5227    !Config Key   = DIA_INIT_MAX
5228    !Config Desc  = maximum diameter of a newly established forest stand
5229    !Config if    = OK_STOMATE
5230    !Config Def   = undef, 0.03, 0.03, 0.03, 0.03, 0.03, 0.03, 0.03, 0.03, 0.03, undef, undef, undef,undef
5231    !Config Help  =
5232    !Config Units = [m]
5233    CALL getin_p("DIA_INIT_MAX",dia_init_max)
5234
5235    !Config Key   = ALPHA_SELF_THINNING
5236    !Config Desc  = alpha coefficient of the self thinning relationship
5237    !Config if    = OK_STOMATE
5238    !Config Def   = undef, 3000, 3000, 1462, 2262, 1900, 960, 939, 1046, undef, undef, undef, undef
5239    !Config Help  =
5240    !Config Units = [-]
5241    CALL getin_p("ALPHA_SELF_THINNING",alpha_self_thinning)
5242   
5243    !Config Key   = BETA_SELF_THINNING
5244    !Config Desc  = beta coefficient of the self thinning relationship
5245    !Config if    = OK_STOMATE
5246    !Config Def   = undef, -0.57, -0.57, -0.55, -0.61, -0.58, -0.55, -0.56, -0.56, undef, undef, undef, undef
5247    !Config Help  =
5248    !Config Units = [-]
5249    CALL getin_p("BETA_SELF_THINNING",beta_self_thinning)
5250   
5251    !Config Key   = FUELWOOD_DIAMETER
5252    !Config Desc  = Diameter below which harvest will be used as fuelwood
5253    !Config if    = OK_STOMATE, DIMENSIONAL WOOD PRODUCTS
5254    !Config Def   = undef, 0.3, 0.3, 0.2, 0.3, 0.3, 0.2, 0.2, 0.2, undef, undef, undef, undef
5255    !Config Help  =
5256    !Config Units = [m]
5257    CALL getin_p("FUELWOOD_DIAMETER",fuelwood_diameter)
5258   
5259    !Config Key   = COPPICE_KILL_BE_WOOD
5260    !Config Desc  = The fraction of belowground wood killed during coppicing
5261    !Config if    = FOREST_MANAGED equals to 3 (Coppice)
5262    !Config Def   = undef, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, undef, undef, undef, undef
5263    !Config Help  =
5264    !Config Units = [m]
5265    CALL getin_p("COPPICE_KBEW",coppice_kill_be_wood)
5266
5267    !Config Key   = DELEUZE_A
5268    !Config Desc  = intercept of the intra-tree competition within a stand
5269    !Config if    = OK_STOMATE, NCIRC>6
5270    !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
5271    !Config Help  = intercept of the intra-tree competition within a stand
5272    !               based on the competion rule of Deleuze and Dhote 2004
5273    !               Used when n_circ > 6
5274    !Config Units = [-]
5275    CALL getin_p("DELEUZE_A",deleuze_a)
5276
5277    !Config Key   = DELEUZE_B
5278    !Config Desc  = slope of the intra-tree competition within a stand
5279    !Config if    = OK_STOMATE, NCIRC>6
5280    !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
5281    !Config Help  = slope of the intra-tree competition within a stand
5282    !               based on the competion rule of Deleuze and Dhote 2004
5283    !               Used when n_circ > 6
5284    !Config Units = [-]
5285    CALL getin_p("DELEUZE_B",deleuze_b)
5286
5287    !Config Key   = DELEUZE_P_ALL
5288    !Config Desc  = Percentile of the circumferences that receives photosynthates
5289    !Config if    = OK_STOMATE, NCIRC>1 AND NCIRC<6
5290    !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
5291    !Config Help  = Percentile of the circumferences that receives photosynthates
5292    !               based on the competion rule of Deleuze and Dhote 2004
5293    !               Used when n_circ < 6 for FM 1, FM2 and FM4
5294    !Config Units = [0-1]
5295    CALL getin_p("DELEUZE_P_ALL",deleuze_p_all)
5296 
5297    !Config Key   = DELEUZE_P_COPPICE
5298    !Config Desc  = Percentile of the circumferences that receives photosynthates
5299    !Config if    = OK_STOMATE, functional allocation 
5300    !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
5301    !Config Help  = Percentile of the circumferences that receives photosynthates
5302    !               based on the competion rule of Deleuze and Dhote 2004
5303    !               Used when n_circ < 6 for FM3
5304    !Config Units = [0-1]
5305    CALL getin_p("DELEUZE_P_COPPICE",deleuze_p_coppice)
5306   
5307    !Config Key   = DELEUZE_POWER_A
5308    !Config Desc  = Slope parameter for intra-specific competition
5309    !Config if    = OK_STOMATE
5310    !Config Def   = undef, 0, 0, 0, 0, 0, 0, 0, 0, 0, undef, undef, undef, undef
5311    !Config Help  = Divisor of the power for the slope of the intra-tree competition within a stand
5312    !               based on the competion rule of Deleuze and Dhote 2004.
5313    !Config Units = [-]
5314    CALL getin_p("DELEUZE_POWER_A",deleuze_power_a)
5315   
5316    !Config Key   = M_DV
5317    !Config Desc  = Relaxation factor of deleuze relationship
5318    !Config if    = OK_STOMATE, NCIRC>1
5319    !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
5320    !Config Help  = Allows some allocation to trees below the threshold (sigma) if
5321    !               the value exceeds 0.
5322    !Config Units = [-]
5323    CALL getin_p("M_DV",m_dv)
5324   
5325    !Config Key   = DENS_TARGET
5326    !Config Desc  = Maximum tree density of a stand
5327    !Config if    = OK_STOMATE
5328    !Config Def   = 0.0, 100, 100, 200, 100, 100, 200, 100, 200, 0.0, 0.0, 0.0, 0.0
5329    !Config Help  = If the stand density drops below this number the stand will
5330    !               killed and replanted.
5331    !Config Units = [tree ha-1]
5332    CALL getin_p("DENS_TARGET",dens_target)
5333
5334    !Config Key   = LARGEST_TREE_DIA
5335    !Config Desc  = Maximum tree diameter of a stand
5336    !Config if    = OK_STOMATE
5337    !Config Def   = 0.0, .45, .45, .45, .45, .45, .45, .45, .45, 0.0, 0.0, 0.0, 0.0
5338    !Config Help  = If the mean diameter of the largest diameter class
5339    !               exceeds this threshold, the stand will be killed and replanted.
5340    !Config Units = [m]
5341    CALL getin_p("LARGEST_TREE_DIA",largest_tree_dia)
5342
5343    !Config Key   = TAUMIN
5344    !Config Desc  = Minimum probability that a tree get thinned
5345    !Config if    = FOREST_MANAGEMENT
5346    !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
5347    !Config Help  =
5348    !Config Units = [-]
5349    CALL getin_p("TAUMIN",taumin)
5350
5351    !Config Key   = TAUMAX
5352    !Config Desc  = Maximum probability that a tree get thinned
5353    !Config if    = FOREST_MANAGEMENT
5354    !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
5355    !Config Help  =
5356    !Config Units = [-]
5357    CALL getin_p("TAUMAX",taumax)
5358
5359    !Config Key   = A_RDI_UPPER_UNMAN
5360    !Config Desc  = Intercept of rdi relationship of unmanaged forests
5361    !Config if    = OK_STOMATE
5362    !Config Def   = undef, 0.16, 0.16, 0.16, 0.16, 0.16, 0.16, 0.16, 0.16, undef, undef, undef, undef
5363    !Config Help  =
5364    !Config Units = [-]
5365    CALL getin_p("A_RDI_UPPER_UNMAN",a_rdi_upper_unman)
5366
5367    !Config Key   = B_RDI_UPPER_UNMAN
5368    !Config Desc  = Slope of rdi relationship of unmanaged forests
5369    !Config if    = OK_STOMATE
5370    !Config Def   = undef, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, undef, undef, undef, undef
5371    !Config Help  =
5372    !Config Units = [-]
5373    CALL getin_p("B_RDI_UPPER_UNMAN",b_rdi_upper_unman)
5374
5375    !Config Key   = C_RDI_UPPER_UNMAN
5376    !Config Desc  = Upper boundary for upper rdi for unmanaged forests
5377    !Config if    = OK_STOMATE
5378    !Config Def   = undef, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, undef, undef, undef, undef
5379    !Config Help  =
5380    !Config Units = [-]
5381    CALL getin_p("C_RDI_UPPER_UNMAN",c_rdi_upper_unman)
5382
5383    !Config Key   = D_RDI_UPPER_UNMAN
5384    !Config Desc  = Lower boundary for upper rdi for unmanaged forests
5385    !Config if    = OK_STOMATE
5386    !Config Def   = undef, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, undef, undef, undef, undef
5387    !Config Help  =
5388    !Config Units = [-]
5389    CALL getin_p("D_RDI_UPPER_UNMAN",d_rdi_upper_unman)
5390
5391    !Config Key   = A_RDI_LOWER_UNMAN
5392    !Config Desc  = Intercept of rdi relationship of unmanaged forests
5393    !Config if    = OK_STOMATE
5394    !Config Def   = undef, 0.051, 0.051, 0.051, 0.051, 0.051, 0.051, 0.051, 0.051, undef, undef, undef, undef
5395    !Config Help  =
5396    !Config Units = [-]
5397    CALL getin_p("A_RDI_LOWER_UNMAN",a_rdi_lower_unman)
5398
5399    !Config Key   = B_RDI_LOWER_UNMAN
5400    !Config Desc  = Slope of rdi relationship of unmanaged forests
5401    !Config if    = OK_STOMATE
5402    !Config Def   = undef, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, undef, undef, undef, undef
5403    !Config Help  =
5404    !Config Units = [-]
5405    CALL getin_p("B_RDI_LOWER_UNMAN",b_rdi_lower_unman)
5406
5407    !Config Key   = C_RDI_LOWER_UNMAN
5408    !Config Desc  = Upper boundary for lower rdi for unmanaged forests
5409    !Config if    = OK_STOMATE
5410    !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef
5411    !Config Help  =
5412    !Config Units = [-]
5413    CALL getin_p("C_RDI_LOWER_UNMAN",c_rdi_lower_unman)
5414
5415    !Config Key   = D_RDI_LOWER_UNMAN
5416    !Config Desc  = Lower boundary for lower rdi for unmanaged forests
5417    !Config if    = OK_STOMATE
5418    !Config Def   = undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, undef, undef, undef, undef
5419    !Config Help  =
5420    !Config Units = [-]
5421    CALL getin_p("D_RDI_LOWER_UNMAN",d_rdi_lower_unman)
5422
5423    !Config Key   = A_RDI_UPPER_MAN
5424    !Config Desc  = Intercept of the yield-table derived thinning relationship D=alpha*N^beta
5425    !Config if    = FOREST_MANAGEMENT
5426    !Config Def   = undef, 0.16, 0.16, 0.16, 0.16, 0.16, 0.16, 0.16, 0.16, undef, undef, undef, undef
5427    !Config Help  =
5428    !Config Units = [-]
5429    CALL getin_p("A_RDI_UPPER_MAN",a_rdi_upper_man)
5430
5431    !Config Key   = B_RDI_UPPER_MAN
5432    !Config Desc  = Slope of the yield-table derived thinning relationship D=alpha*N^beta
5433    !Config if    = FOREST_MANAGEMENT
5434    !Config Def   = undef, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, 0.0264, undef, undef, undef, undef
5435    !Config Help  =
5436    !Config Units = [-]
5437    CALL getin_p("B_RDI_UPPER_MAN",b_rdi_upper_man)
5438
5439    !Config Key   = C_RDI_UPPER_MAN
5440    !Config Desc  = Upper boundary for upper rdi for managed forests
5441    !Config if    = FOREST_MANAGEMENT
5442    !Config Def   = undef, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, 0.7, undef, undef, undef, undef
5443    !Config Help  =
5444    !Config Units = [-]
5445    CALL getin_p("C_RDI_UPPER_MAN",c_rdi_upper_man)
5446
5447    !Config Key   = D_RDI_UPPER_MAN
5448    !Config Desc  = Lower boundary for upper rdi for managed forests
5449    !Config if    = FOREST_MANAGEMENT
5450    !Config Def   = undef, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, undef, undef, undef, undef
5451    !Config Help  =
5452    !Config Units = [-]
5453    CALL getin_p("D_RDI_UPPER_MAN",d_rdi_upper_man)
5454
5455    !Config Key   = A_RDI_LOWER_MAN
5456    !Config Desc  = Intercept of the yield-table derived thinning relationship D=alpha*N^beta
5457    !Config if    = FOREST_MANAGEMENT
5458    !Config Def   = undef, 0.051, 0.051, 0.051, 0.051, 0.051, 0.051, 0.051, 0.051, undef, undef, undef, undef
5459    !Config Help  =
5460    !Config Units = [-]
5461    CALL getin_p("A_RDI_LOWER_MAN",a_rdi_lower_man)
5462
5463    !Config Key   = B_RDI_LOWER_MAN
5464    !Config Desc  = Slope of the yield-table derived thinning relationship D=alpha*N^beta
5465    !Config if    = FOREST_MANAGEMENT
5466    !Config Def   = undef, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, 0.0255, undef, undef, undef, undef
5467    !Config Help  =
5468    !Config Units = [-]
5469    CALL getin_p("B_RDI_LOWER_MAN",b_rdi_lower_man)
5470
5471    !Config Key   = C_RDI_LOWER_MAN
5472    !Config Desc  = Upper boundary for lower rdi for managed forests
5473    !Config if    = FOREST_MANAGEMENT
5474    !Config Def   = undef, 0.9, 0.9, 0.9, 0.9, 0.9, 0.9, 0.9, 0.9, undef, undef, undef, undef
5475    !Config Help  =
5476    !Config Units = [-]
5477    CALL getin_p("C_RDI_LOWER_MAN",c_rdi_lower_man)
5478
5479    !Config Key   = D_RDI_LOWER_MAN
5480    !Config Desc  = Lower boundary for lower rdi for managed forests
5481    !Config if    = FOREST_MANAGEMENT
5482    !Config Def   = undef, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, 0.3, undef, undef, undef, undef
5483    !Config Help  =
5484    !Config Units = [-]
5485    CALL getin_p("D_RDI_LOWER_MAN",d_rdi_lower_man)
5486
5487    !Config Key   = BRANCH_HARVEST
5488    !Config Desc  = The fraction of branches which are harvested during FM2 (the rest are left onsite)
5489    !Config if    = FOREST_MANAGEMENT
5490    !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 
5491    !Config Help  =
5492    !Config Units = [-]
5493    CALL getin_p("BRANCH_HARVEST",branch_harvest)
5494
5495    !Config Key   = COPPICE_DIAMETER
5496    !Config Desc  = The trunk diameter at which a coppice will be cut
5497    !Config if    = FOREST_MANAGEMENT
5498    !Config Def   = undef, 0.2, 0.2, 0.2, 0.2, 0.1, 0.2, 0.2, 0.2, undef, undef, undef, undef
5499    !Config Help  =
5500    !Config Units = [m]
5501    CALL getin_p("COPPICE_DIAMETER",coppice_diameter)
5502
5503    !Config Key   = SHOOTS_PER_STOOL
5504    !Config Desc  = The number of shoots that will regrow per stool after the first coppice cut
5505    !Config if    = FOREST_MANAGEMENT
5506    !Config Def   = undef, 6, 6, 6, 6, 6, 6, 6, 6, undef, undef, undef, undef
5507    !Config Help  =
5508    !Config Units = [shoots.stool-1]
5509    CALL getin_p("SHOOTS_PER_STOOL",shoots_per_stool)
5510
5511    !Config Key   = SRC_ROT_LENGTH
5512    !Config Desc  = The number of years between cuttings for short rotation coppices
5513    !Config if    = FOREST_MANAGEMENT
5514    !Config Def   = undef, 3, 3, 3, 3, 3, 3, 3, 3, undef, undef, undef, undef
5515    !Config Help  =
5516    !Config Units = [years]
5517    CALL getin_p("SRC_ROT_LENGTH",src_rot_length)
5518
5519    !Config Key   = SRC_NROTS
5520    !Config Desc  = Number of rotations before  afinal cut
5521    !Config if    = FOREST_MANAGEMENT
5522    !Config Def   = undef, 10, 10, 10, 10, 10, 10, 10, 10, undef, undef, undef, undef
5523    !Config Help  = The number of rotations for short rotations coppices
5524    !               after which the roots/stools are supposed to be exhausted. The
5525    !               stool is killed and replanted.
5526    !Config Units = [-]
5527    CALL getin_p("SRC_NROTS",src_nrots)
5528
5529    !Config Key   = FRUIT_ALLOC
5530    !Config Desc  = Fraction of allocatable carbon that will go to fruit production
5531    !Config if    = OK_STOMATE
5532    !Config Def   = (undef, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0.1, 0., 0., 0., 0.)
5533    !Config Help  = Guestimates - should be confirmed
5534    !Config Units = [-]
5535    CALL getin_p('FRUIT_ALLOC',fruit_alloc)
5536
5537    !Config Key   = LABILE_RESERVE
5538    !Config Desc  = Depends on the allocation scheme
5539    !Config if    = OK_STOMATE
5540    !Config Def   = undef, 60, 30, 60, 60, 30, 60, 10, 10, 2, 2, 2, 2
5541    !Config Help  = The lab_fac is divided by this value to obtain
5542    !               a new parameter. This new parameter is a fraction
5543    !               that is multiplied with the plant biomass to obatin
5544    !               the optimal size of the labile pool. The dependency
5545    !               on lab_fac is a nice feature but the whole
5546    !               parameterization is arbitrary
5547    !Config Units = [-]
5548    CALL getin_p("LABILE_RESERVE",labile_reserve)
5549
5550    !Config Key   = EVERGREEN_RESERVE
5551    !Config Desc  = Fraction of sapwood mass stored in the reserve pool of evergreen trees
5552    !Config If    = OK_STOMATE
5553    !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
5554    !Config Help  =
5555    !Config Units = [-] 
5556    CALL getin_p('EVERGREEN_RESERVE',evergreen_reserve)
5557
5558    !Config Key   = DECIDUOUS_RESERVE
5559    !Config Desc  = Fraction of sapwood mass stored in the reserve pool
5560    !Config If    = OK_STOMATE
5561    !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
5562    !Config Help  = Fraction of sapwood mass stored in the reserve pool of
5563    !               deciduous trees during the growing season
5564    !Config Units = [-] 
5565    CALL getin_p('DECIDUOUS_RESERVE',deciduous_reserve)
5566
5567    !Config Key   = SENESCENSE_RESERVE
5568    !Config Desc  = Fraction of sapwood mass stored in the reserve pool of
5569    !               deciduous trees during the senescense
5570    !Config If    = OK_STOMATE
5571    !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
5572    !Config Help  = Fraction of sapwood mass stored in the reserve pool of
5573    !               deciduous trees during the senescense
5574    !Config Units = [-] 
5575    CALL getin_p('SENESCENSE_RESERVE',senescense_reserve)
5576
5577    !Config Key   = ROOT_RESERVE
5578    !Config Desc  = Fraction of max root biomass which are covered by the carbon reserve
5579    !Config If    = OK_STOMATE
5580    !Config Def   = undef, 0.3, 1., 0.3, 0.3, 1., 0.3, 1.,  1., 1., 1., 1., 1.
5581    !Config Help  = Fraction of max root biomass which are covered by the carbon reserve.
5582    !               For evergreens we are happy with 30%, for deciduous we use 100%. In
5583    !               other words the reserves contain enough C to regrow 100% of the root
5584    !               biomass for deciduous species.
5585    !Config Units = [-] 
5586    CALL getin_p('ROOT_RESERVE',root_reserve)
5587
5588    !Config Key   = FCN_WOOD
5589    !Config Desc  = CN of wood for allocation, relative to leaf CN
5590    !Config if    = OK_STOMATE
5591    !Config Def   = undef, .087, .087, .087, .087, .087, .087, .087, .087, .087, .087, .087
5592    !Config Help  = Comes from Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x),
5593    !Config         although the variables are respresented a bit differntly here.  The sapwood CN
5594    !Config         ratio in Sitch et al is 330, and that for the leaves and roots is 29. 29/330=0.088.
5595    !Config Units = [-]
5596    CALL getin_p('FCN_WOOD',fcn_wood) 
5597
5598    !Config Key   = FCN_ROOT
5599    !Config Desc  = CN roots for allocation, relative to leaf CN
5600    !Config if    = OK_STOMATE
5601    !Config Def   = undef, 0.86, 0.86, 0.86, 0.86, 0.86, 0.86, 0.86, 0.86, 0.86, 0.86, 0.86
5602    !Config Help  = Comes from Sitch et al 2003 (https://doi.org/10.1046/j.1365-2486.2003.00569.x),
5603    !Config         although the variables are respresented a bit differntly here.  The root CN
5604    !Config         ratio in Sitch et al is 29, the same as leaves. 29/29=1.0.  Unclear why
5605    !Config         the default changed to 0.86.
5606    !Config Units = [-]
5607    CALL getin_p('FCN_ROOT',fcn_root) 
5608
5609    !Config Key   = BRANCH_RATIO
5610    !Config Desc  = Share of the sapwood and heartwood that is used for branches
5611    !Config if    = FOREST_MANAGEMENT
5612    !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 
5613    !Config Help  =
5614    !Config Units = [-]
5615    CALL getin_p("BRANCH_RATIO",branch_ratio)
5616
5617    !
5618    ! Recruitment - stomate_prescribe 
5619    !     
5620    !Config Key   = RECRUITMENT_PFT 
5621    !Config Desc  = Logical recruitment flag for each pft
5622    !Config if    = OK_STOMATE 
5623    !Config Def   = FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE 
5624    !Config Help  = Logical recruitment flag for each pft. So PFTs with recruitment or no recruitment can coexist 
5625    !Config Units = [FLAG] 
5626    CALL getin_p("RECRUITMENT_PFT",recruitment_pft) 
5627
5628    !Config Key   = RECRUITMENT_HEIGHT 
5629    !Config Desc  = Prescribed height for tree recruits (m)   
5630    !Config if    = OK_STOMATE 
5631    !Config Def   = undef, 1, 1, 1, 1, 1, 1, 1, 1, 1, undef, undef, undef 
5632    !Config Help  =
5633    !Config Units = [m] 
5634    CALL getin_p("RECRUITMENT_HEIGHT",recruitment_height) 
5635
5636    !Config Key   = RECRUITMENT_ALPHA 
5637    !Config Desc  = Intercept of power model relating light and recruitment numbers 
5638    !Config if    = OK_STOMATE 
5639    !Config Def   = undef, -3.0, -3.0, -3.0, -3.0, -3.0, -3.0, -3.0, -3.0, undef, undef, undef, undef 
5640    !Config Help  =   
5641    !Config Units = [-] 
5642    CALL getin_p("RECRUITMENT_ALPHA",recruitment_alpha) 
5643
5644    !Config Key   = RECRUITMENT_BETA 
5645    !Config Desc  = Slope of power model relating light and recruitment numbers 
5646    !Config if    = OK_STOMATE 
5647    !Config Def   = undef, 0.8, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, 1.0, undef, undef, undef, undef 
5648    !Config Help  =   
5649    !Config Units = [-] 
5650    CALL getin_p("RECRUITMENT_BETA",recruitment_beta) 
5651
5652    !
5653    ! Mortality
5654    !
5655    !Config Key   = DEATH_DISTRIBUTION_FACTOR
5656    !Config Desc  = Shape parameter for tree mortality
5657    !Config if    = OK_STOMATE, FUNCTIONAL ALLOCATION
5658    !Config Def   = undef, 100., 100., 100., 100., 100., 100., 100., 100., undef, undef, undef, undef 
5659    !Config Help  = The scale factor between the smallest and largest
5660    !               circ class for tree mortality in stomate_mark_kill.
5661    !Config Units = [-]
5662    CALL getin_p('DEATH_DF',death_distribution_factor) 
5663
5664    !Config Key   = NPP_RESET_VALUE
5665    !Config Desc  = The value longterm NPP is reset to npp_reset_value after a non-tree stand dies.
5666    !Config if    = OK_STOMATE, FUNCTIONAL ALLOCATION
5667    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 500., 500., 500., 500. 
5668    !Config Help  =
5669    !Config Units = [gC m-2 y-1]
5670    CALL getin_p('NPP_RESET_VALUE',npp_reset_value) 
5671
5672    !Config Key   = NDYING_YEAR
5673    !Config Desc  = Number of year for a forest to die
5674    !Config if    = OK_STOMATE
5675    !Config Def   = undef, 15.0, 15.0, 15.0, 15.0, 15.0, 15.0, 15.0,
5676    !15.0, 15.0, 15.0, 15.0, 15.0 
5677    !Config Help  = Number of year during which an unmanaged forest will
5678    ! decay and eventually die after reaching stem density threshold
5679    !Config Units = [year]
5680    CALL getin_p('NDYING_YEAR',ndying_year)
5681
5682    ! Recruitment - stomate_prescribe 
5683    !     
5684    !Config Key   = BEETLE_PFT 
5685    !Config Desc  = Logical bark beetle mortality flag for each pft
5686    !Config if    = OK_STOMATE 
5687    !Config Def   = FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE,
5688    !FALSE, FALSE, FALSE, FALSE, FALSE 
5689    !Config Help  = Logical bark beetle mortality flag for each pft. So PFTs with
5690    !               bark beetle attack or not bark beetle can coexist.   
5691    !Config Units = [FLAG] 
5692    CALL getin_p("BEETLE_PFT",beetle_pft)
5693
5694
5695    IF (ok_pest) THEN
5696
5697       !Config Key   = REMAINING_BEETLES
5698       !Config Desc  = beetles population fraction that remain on the stand
5699       !after beetle departure at the end of an epidemic phase
5700       !Config if    = OK_STOMATE, OK_PEST
5701       !Config Def   = undef, undef, undef, 0.5, undef, undef, 0.5, undef,
5702       !undef, undef, undef, undef, undef
5703       !Config Help  =
5704       !Config Units = [-]
5705       CALL getin_p('REMAINING_BEETLES',remaining_beetles)
5706
5707       !Config Key   = PRESSURE_FEEDBACK
5708       !Config Desc  = parameter wich control the feedback of the previous
5709       !instation on the calculation of the BPI (Beetle pressure index)
5710       !Config if    = OK_STOMATE, OK_PEST
5711       !Config Def   = undef, undef, undef, 0.75, undef, undef, 0.75, undef,
5712       !undef, undef, undef, undef, undef
5713       !Config Help  =
5714       !Config Units = [-]
5715       CALL getin_p('PRESSURE_FEEDBACK',pressure_feedback)
5716
5717       !Config Key   = AGE_SUSCEPTIBILITY_A
5718       !Config Desc  = a parameter for the relationship between stand age and beetle susceptibility
5719       !Config if    = OK_STOMATE, OK_PEST
5720       !Config Def   = undef, undef, undef, 0.2, undef, undef, 0.2, undef, undef, undef, undef, undef, undef
5721       !Config Help  =
5722       !Config Units = [-]
5723       CALL getin_p('AGE_SUSCEPTIBILITY_A',age_susceptibility_a)
5724
5725       !Config Key   = AGE_SUSCEPTIBILITY_B
5726       !Config Desc  = b parameter for the relationship between stand age and beetle susceptibility
5727       !Config if    = OK_STOMATE, OK_PEST
5728       !Config Def   = undef, undef, undef, 0.01094542, undef, undef, 0.01094542, undef, undef, undef, undef, undef, undef
5729       !Config Help  =
5730       !Config Units = [-]
5731       CALL getin_p('AGE_SUSCEPTIBILITY_B',age_susceptibility_b)
5732
5733       !Config Key   = AGE_SUSCEPTIBILITY_C
5734       !Config Desc  = c parameter for the relationship between stand age and beetle susceptibility
5735       !Config if    = OK_STOMATE, OK_PEST
5736       !Config Def   = undef, undef, undef, 70.0, undef, undef, 70.0, undef, undef, undef, undef, undef, undef
5737       !Config Help  =
5738       !Config Units = [-]
5739       CALL getin_p('AGE_SUSCEPTIBILITY_C',age_susceptibility_c)
5740
5741       !Config Key   = RDI_SUSCEPTIBILITY_A
5742       !Config Desc  = a parameter for the relationship between rdi and
5743       !beetle susceptibility
5744       !Config if    = OK_STOMATE, OK_PEST
5745       !Config Def   = undef, undef, undef, 15.5, undef, undef, 15.5, undef,
5746       !undef, undef, undef, undef, undef
5747       !Config Help  =
5748       !Config Units = [-]
5749       CALL getin_p('RDI_SUSCEPTIBILITY_A',rdi_susceptibility_a)
5750
5751       !Config Key   = RDI_SUSCEPTIBILITY_B
5752       !Config Desc  = b parameter for the relationship between rdi and
5753       !beetle susceptibility
5754       !Config if    = OK_STOMATE, OK_PEST
5755       !Config Def   = undef, undef, undef, 0.6, undef, undef,
5756       !0.6, undef, undef, undef, undef, undef, undef
5757       !Config Help  =
5758       !Config Units = [-]
5759       CALL getin_p('RDI_SUSCEPTIBILITY_B',rdi_susceptibility_b)
5760
5761       !Config Key   = RDI_TARGET_SUSCEPT
5762       !Config Desc  = target susceptibility when we come back to endemic
5763       !Config if    = OK_STOMATE, OK_PEST
5764       !Config Def   = undef, undef, undef, 0.25, undef, undef,
5765       !0.25, undef, undef, undef, undef, undef, undef
5766       !Config Help  =
5767       !Config Units = [-]
5768       CALL getin_p('RDI_TARGET_SUSCEPT',rdi_target_suscept)
5769
5770       !Config Key   = SHARE_SUSCEPTIBILITY_A
5771       !Config Desc  = a parameter for the relationship between share and
5772       !beetle susceptibility
5773       !Config if    = OK_STOMATE, OK_PEST
5774       !Config Def   = undef, undef, undef, 1.5, undef, undef, 15.5, undef,
5775       !undef, undef, undef, undef, undef
5776       !Config Help  =
5777       !Config Units = [-]
5778       CALL getin_p('SHARE_SUSCEPTIBILITY_A',share_susceptibility_a)
5779
5780       !Config Key   = SHARE_SUSCEPTIBILITY_B
5781       !Config Desc  = b parameter for the relationship between share and
5782       !beetle susceptibility
5783       !Config if    = OK_STOMATE, OK_PEST
5784       !Config Def   = undef, undef, undef, 0.6, undef, undef,
5785       !0.6, undef, undef, undef, undef, undef, undef
5786       !Config Help  =
5787       !Config Units = [-]
5788       CALL getin_p('SHARE_SUSCEPTIBILITY_B',share_susceptibility_b)
5789
5790       !Config Key   = DROUGHT_SUSCEPTIBILITY_A
5791       !Config Desc  = a parameter for the relationship between drought and beetle susceptibility
5792       !Config if    = OK_STOMATE, OK_PEST
5793       !Config Def   = undef, undef, undef, -9.5, undef, undef, -9.5, undef, undef, undef, undef, undef, undef
5794       !Config Help  =
5795       !Config Units = [-]
5796       CALL getin_p('DROUGHT_SUSCEPTIBILITY_A',drought_susceptibility_a)
5797
5798       !Config Key   = DROUGHT_SUSCEPTIBILITY_B
5799       !Config Desc  = b parameter for the relationship between drought and beetle susceptibility
5800       !Config if    = OK_STOMATE, OK_PEST
5801       !Config Def   = undef, undef, undef, 0.4, undef, undef, 0.4, undef, undef, undef, undef, undef, undef
5802       !Config Help  =
5803       !Config Units = [-]
5804       CALL getin_p('DROUGHT_SUSCEPTIBILITY_B',drought_susceptibility_b)
5805
5806       !Config Key   = WINDTHROW_SUSCEPTIBILITY_TUNE
5807       !Config Desc  = tune parameter for the relationship between woodleftover and beetle susceptibility
5808       !Config if    = OK_STOMATE, OK_PEST
5809       !Config Def   = undef, undef, undef, 1.0, undef, undef, 0.5, undef, undef, undef, undef, undef, undef
5810       !Config Help  =
5811       !Config Units = [-]
5812       CALL getin_p('WINDTHROW_SUSCEPTIBILITY_TUNE',windthrow_susceptibility_tune)
5813
5814       !Config Key   = BEETLE_GENERATION_A
5815       !Config Desc  = a parameter for the calculation of the number of beetle generation per year
5816       !Config if    = OK_STOMATE
5817       !Config Def   = undef, undef, undef, 3.307963, undef, undef, 3.307963, undef, undef, undef, undef, undef, undef
5818       !Config Help  =
5819       !Config Units = [-]
5820       CALL getin_p('BEETLE_GENERATION_A',beetle_generation_a)
5821
5822       !Config Key   = BEETLE_GENERATION_B
5823       !Config Desc  = b parameter for the calculation of the number of beetle generation per year
5824       !Config if    = OK_STOMATE
5825       !Config Def   = undef, undef, undef, 557.0, undef, undef, 557.0, undef, undef, undef, undef, undef, undef
5826       !Config Help  = This parameter is the one we have to change across species. It represent the number of DD needed to breed 1 generation
5827       !Config Units = [degrees day]
5828       CALL getin_p('BEETLE_GENERATION_B',beetle_generation_b)
5829
5830       !Config Key   = BEETLE_GENERATION_C
5831       !Config Desc  = c parameter for the calculation of the number of beetle generation per year
5832       !Config if    = OK_STOMATE
5833       !Config Def   = undef, undef, undef, 1.980938, undef, undef, 1.980938, undef, undef, undef, undef, undef, undef
5834       !Config Help  =
5835       !Config Units = [-]
5836       CALL getin_p('BEETLE_GENERATION_C',beetle_generation_c)
5837
5838       !Config Key   = MIN_TEMP_BEETLE
5839       !Config Desc  = temperature threshold below which Teff is not calculated
5840       !Config if    = OK_STOMATE
5841       !Config Def   = undef, undef, undef, 38.4, undef, undef, 38.4, undef, undef, undef, undef, undef, undef
5842       !Config Help  =
5843       !Config Units = [degree celcius]
5844       CALL getin_p('MIN_TEMP_BEETLE',min_temp_beetle)
5845
5846       !Config Key   = MAX_TEMP_BEETLE
5847       !Config Desc  = temperature threshold above which Teff is not calculated
5848       !Config if    = OK_STOMATE
5849       !Config Def   = undef, undef, undef, 38.4, undef, undef, 38.4, undef, undef, undef, undef, undef, undef
5850       !Config Help  =
5851       !Config Units = [ degree celcius]
5852       CALL getin_p('MAX_TEMP_BEETLE',max_temp_beetle)
5853
5854       !Config Key   = OPT_TEMP_BEETLE
5855       !Config Desc  = a parameter for the calculation of the effective temperature used in beetle phenology
5856       !Config if    = OK_STOMATE
5857       !Config Def   = undef, undef, undef, 30.3, undef, undef, 30.3, undef, undef, undef, undef, undef, undef
5858       !Config Help  =
5859       !Config Units = [-]
5860       CALL getin_p('OPT_TEMP_BEETLE',opt_temp_beetle)
5861
5862       !Config Key   = EFF_TEMP_BEETLE_A
5863       !Config Desc  = a parameter for the calculation of the effective temperature used in beetle phenology
5864       !Config if    = OK_STOMATE
5865       !Config Def   = undef, undef, undef, 0.02876507, undef, undef, 0.02876507, undef, undef, undef, undef, undef, undef
5866       !Config Help  =
5867       !Config Units = [-]
5868       CALL getin_p('EFF_TEMP_BEETLE_A',eff_temp_beetle_a)
5869
5870       !Config Key   = EFF_TEMP_BEETLE_B
5871       !Config Desc  = b parameter for the calculation of the effective temperature used in beetle phenology
5872       !Config if    = OK_STOMATE
5873       !Config Def   = undef, undef, undef, 40.9958913, undef, undef, 40.9958913, undef, undef, undef, undef, undef, undef
5874       !Config Help  =
5875       !Config Units = [-]
5876       CALL getin_p('EFF_TEMP_BEETLE_B',eff_temp_beetle_b)
5877
5878       !Config Key   = EFF_TEMP_BEETLE_C
5879       !Config Desc  = c parameter for the calculation of the effective temperature used in beetle phenology
5880       !Config if    = OK_STOMATE
5881       !Config Def   = undef, undef, undef, 3.5922336, undef, undef, 3.5922336, undef, undef, undef, undef, undef, undef
5882       !Config Help  =
5883       !Config Units = [-]
5884       CALL getin_p('EFF_TEMP_BEETLE_C',eff_temp_beetle_c)
5885
5886       !Config Key   = EFF_TEMP_BEETLE_D
5887       !Config Desc  = d parameter for the calculation of the effective temperature used in beetle phenology
5888       !Config if    = OK_STOMATE
5889       !Config Def   = undef, undef, undef, 1.24657367, undef, undef, 1.24657367, undef, undef, undef, undef, undef, undef
5890       !Config Help  =
5891       !Config Units = [-]
5892       CALL getin_p('EFF_TEMP_BEETLE_D',eff_temp_beetle_d)
5893
5894       !Config Key   = DIAPAUSE_THRES_DAYLENGTH
5895       !Config Desc  = daylength in hour above which bark beetle start diapause
5896       !Config if    = OK_STOMATE
5897       !Config Def   = undef, undef, undef, 14.5, undef, undef, 14.5, undef, undef, undef, undef, undef, undef
5898       !Config Help  =
5899       !Config Units = [hour]
5900       CALL getin_p('DIAPAUSE_THRES_DAYLENGTH',diapause_thres_daylength)
5901
5902       !Config Key   = WGHT_SIRDI_A
5903       !Config Desc  = ""
5904       !Config if    = OK_STOMATE
5905       !Config Def   = undef, undef, undef, 15.5, undef, undef, 15.5, undef,
5906       !undef, undef, undef, undef, undef
5907       !Config Help  =
5908       !Config Units = [hour]
5909       CALL getin_p('WGHT_SIRDI_A',wght_sirdi_a)
5910
5911       !Config Key   = WGHT_SIRDI_B
5912       !Config Desc  = ""
5913       !Config if    = OK_STOMATE
5914       !Config Def   = undef, undef, undef, 0.5, undef, undef, 0.5, undef,
5915       !undef, undef, undef, undef, undef
5916       !Config Help  =
5917       !Config Units = [hour]
5918       CALL getin_p('WGHT_SIRDI_B',wght_sirdi_b)
5919
5920       !Config Key   = WGHT_SID
5921       !Config Desc  = ""
5922       !Config if    = OK_STOMATE
5923       !Config Def   = undef, undef, undef, 0.1, undef, undef, 0.1, undef,
5924       !undef, undef, undef, undef, undef
5925       !Config Help  =
5926       !Config Units = [hour]
5927       CALL getin_p('WGHT_SID',wght_sid)
5928
5929       !Config Key   = WGHT_SIS
5930       !Config Desc  = ""
5931       !Config if    = OK_STOMATE
5932       !Config Def   = undef, undef, undef, 0.1, undef, undef, 0.1, undef,
5933       !undef, undef, undef, undef, undef
5934       !Config Help  =
5935       !Config Units = [hour]
5936       CALL getin_p('WGHT_SIS',wght_sis)
5937
5938    ENDIF
5939   
5940    !
5941    ! Windthrow - stomate
5942    !
5943    IF (ok_windthrow) THEN
5944
5945       !Config Key   = STREAMLINING_C_LEAF
5946       !Config Desc  = streamlining parameter for crown with leaves
5947       !Config if    = OK_STOMATE, OK_WINDTHROW
5948       !Config Def   = undef, 2.34, 2.34, 2.70, 2.66, 2.34, 2.71, 2.15, 3.07, undef, undef, undef, undef
5949       !Config Help  =
5950       !Config Units = [-]
5951       CALL getin_p('STREAMLINING_C_LEAF',streamlining_c_leaf)
5952
5953       !Config Key   = STREAMLINING_C_LEAFLESS
5954       !Config Desc  = streamlining parameter for crown without leaves
5955       !Config if    = OK_STOMATE, OK_WINDTHROW
5956       !Config Def   = undef, 2.34, 2.34, 2.70, 2.66, 2.34, 2.71, 2.15, 3.07, undef, undef, undef, undef
5957       !Config Help  =
5958       !Config Units = [-]
5959       CALL getin_p('STREAMLINING_C_LEAFLESS',streamlining_c_leafless)
5960
5961       !Config Key   = STREAMLINING_N_LEAF
5962       !Config Desc  = streamlining parameter for crown with leaves
5963       !Config if    = OK_STOMATE, OK_WINDTHROW
5964       !Config Def   = undef, 0.88, 0.88, 0.64, 0.85, 0.88, 0.63, 0.88, 0.75, undef, undef, undef, undef
5965       !Config Help  =
5966       !Config Units = [-]
5967       CALL getin_p('STREAMLINING_N_LEAF',streamlining_n_leaf)
5968
5969       !Config Key   = STREAMLINING_N_LEAFLESS
5970       !Config Desc  = streamlining parameter for crown without leaves
5971       !Config if    = OK_STOMATE, OK_WINDTHROW
5972       !Config Def   = undef, 0.88, 0.88, 0.64, 0.85, 0.88, 0.63, 0.88, 0.75, undef, undef, undef, undef
5973       !Config Help  =
5974       !Config Units = [-]
5975       CALL getin_p('STREAMLINING_N_LEAFLESS',streamlining_n_leafless)
5976       
5977       !Config Key   = MODULUS_RUPTURE
5978       !Config Desc  = Modulus of rupture
5979       !Config if    = OK_STOMATE, OK_WINDTHROW
5980       !Config Def   = undef, 6.23E7, 6.23E7, 4.13E7, 5.90E7, 6.23E7, 4.10E7, 6.27E7, 5.30E7, undef, undef, undef, undef
5981       !Config Help  = The measure of a species’ strength before rupture
5982       !               when being bent. Used in the calculation of the critical
5983       !               wind speed according to the GALES (Hale et al. 2015) model.
5984       !               IMPORTANT: greenwood values are used and not the more frequently
5985       !               available drywood modulus of rupture.
5986       !Config Units = [Pa]
5987       CALL getin_p('MODULUS_RUPTURE',modulus_rupture)
5988
5989       !Config Key   = F_KNOT
5990       !Config Desc  = Knot factor
5991       !Config if    = OK_STOMATE, OK_WINDTHROW
5992       !Config Def   = undef, 1.0, 1.0, 0.87, 1.0, 1.0, 0.88, 1.0, 0.85, undef, undef, undef, undef
5993       !Config Help  = This modifier represents the knot in the wood, and hence
5994       !               the decrease in structural strength. Used in the calculation
5995       !               of the critical wind speed according to the GALES
5996       !               (Hale et al. 2015) model.
5997       !Config Units = [unitless]
5998       CALL getin_p('F_KNOT',f_knot)
5999
6000       !Config Key   = GREEN_DENSITY
6001       !Config Desc  = Green density of the tree
6002       !Config if    = OK_STOMATE, OK_WINDTHROW
6003       !Config Def   = undef, 1007, 1007, 985, 1060, 1007, 990, 968, 900, undef, undef, undef, undef
6004       !Config Help  =
6005       !Config Units = [kg.m-3]
6006       CALL getin_p('GREEN_DENSITY',green_density)
6007
6008       !Config Key   = OV_FD_SHALLOW
6009       !Config Desc  = Regression coefficient for overturning in free draining and shallow soil type
6010       !Config if    = OK_STOMATE, OK_WINDTHROW
6011       !Config Def   = undef, 175.3, 175.3, 134.7, 198.5, 175.3, 132.6, 152.0, 145.2, undef, undef, undef, undef
6012       !Config Help  = Values derived from generic soil types (free_draining mineral
6013       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6014       !               and the soil depth (shallow, deep, average)
6015       !Config Units = [Nm/kg]
6016       CALL getin_p('OV_FD_SHALLOW',overturning_free_draining_shallow)
6017
6018       !Config Key   = OV_FD_SHALLOW_LESS
6019       !Config Desc  = Regression coefficient for overturning in free draining and shallow soil type leafless
6020       !Config if    = OK_STOMATE, OK_WINDTHROW
6021       !Config Def   = undef, 175.3, 175.3, 134.7, 198.5, 175.3, 132.6, 152.0, 145.2, undef, undef, undef, undef
6022       !Config Help  = Values derived from generic soil types (free_draining mineral
6023       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6024       !               and the soil depth (shallow, deep, average)
6025       !Config Units = [Nm/Kg]
6026       CALL getin_p('OV_FD_SHALLOW_LESS',overturning_free_draining_shallow_leafless)
6027
6028       !Config Key   = OV_FD_DEEP
6029       !Config Desc  = Regression coefficient for overturning in free draining and deep soil type
6030       !Config if    = OK_STOMATE, OK_WINDTHROW
6031       !Config Def   = undef, 203.8, 203.8, 157.2, 230.8, 230.8, 154.8, 176.7, 169.4, undef, undef, undef, undef
6032       !Config Help  = Values derived from generic soil types (free_draining mineral
6033       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6034       !               and the soil depth (shallow, deep, average)
6035       !Config Units = [Nm/Kg]
6036       CALL getin_p('OV_FD_DEEP',overturning_free_draining_deep)
6037
6038       !Config Key   = OV_FD_DEEP_LESS
6039       !Config Desc  = Regression coefficient for overturning in free draining and deep soil type leafless
6040       !Config if    = OK_STOMATE, OK_WINDTHROW
6041       !Config Def   = undef, 203.8, 203.8, 157.2, 230.8, 230.8, 154.8, 176.7, 169.4, undef, undef, undef, undef 
6042       !Config Help  = Values derived from generic soil types (free_draining mineral
6043       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6044       !               and the soil depth (shallow, deep, average)
6045       !Config Units = [Nm/Kg]
6046       CALL getin_p('OV_FD_DEEP_LESS',overturning_free_draining_deep_leafless)
6047
6048       !Config Key   = OV_FD_AVERAGE
6049       !Config Desc  = Regression coefficient for overturning in free draining and medium soil type 
6050       !Config if    = OK_STOMATE, OK_WINDTHROW
6051       !Config Def   = undef, 178.7, 178.7, 137.8, 202.4, 178.7, 135.7, 155.0, 148.6, undef, undef, undef, undef 
6052       !Config Help  = Values derived from generic soil types (free_draining mineral
6053       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6054       !               and the soil depth (shallow, deep, average)
6055       !Config Units = [Nm/Kg]
6056       CALL getin_p('OV_FD_AVERAGE',overturning_free_draining_average)
6057
6058       !Config Key   = OV_FD_AVERAGE_LESS
6059       !Config Desc  = Regression coefficient for overturning in free draining and medium soil type leafless
6060       !Config if    = OK_STOMATE, OK_WINDTHROW
6061       !Config Def   = undef, 178.7, 178.7, 137.8, 202.4, 178.7, 135.7, 155.0, 148.6, undef, undef, undef, undef
6062       !Config Help  = Values derived from generic soil types (free_draining mineral
6063       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6064       !               and the soil depth (shallow, deep, average)
6065       !Config Units = [Nm/Kg]
6066       CALL getin_p('OV_FD_AVERAGE_LESS',overturning_free_draining_average_leafless)
6067
6068       !Config Key   = OV_GLEYED_SHALLOW
6069       !Config Desc  = Regression coefficient for overturning in gleyed and shallow soil type
6070       !Config if    = OK_STOMATE, OK_WINDTHROW
6071       !Config Def   = undef, 155.4, 155.4, 119.4, 176.0, 155.4, 117.6, 134.8, 128.7, undef, undef, undef, undef
6072       !Config Help  = Values derived from generic soil types (free_draining mineral
6073       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6074       !               and the soil depth (shallow, deep, average)
6075       !Config Units = [Nm/Kg]
6076       CALL getin_p('OV_GLEYED_SHALLOW',overturning_gleyed_shallow)
6077
6078       !Config Key   = OV_GLEYED_SHALLOW_LESS
6079       !Config Desc  = Regression coefficient for overturning in gleyed and shallow soil type leafless
6080       !Config if    = OK_STOMATE, OK_WINDTHROW
6081       !Config Def   = undef, 155.4, 155.4, 119.4, 176.0, 155.4, 117.6, 134.8, 128.7, undef, undef, undef, undef 
6082       !Config Help  = Values derived from generic soil types (free_draining mineral
6083       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6084       !               and the soil depth (shallow, deep, average)
6085       !Config Units = [Nm/Kg]
6086       CALL getin_p('OV_GLEYED_SHALLOW_LESS',overturning_gleyed_shallow_leafless)
6087
6088       !Config Key   = OV_GLEYED_DEEP
6089       !Config Desc  = Regression coefficient for overturning in gleyed and deep soil type
6090       !Config if    = OK_STOMATE, OK_WINDTHROW
6091       !Config Def   = undef, 180.6, 180.6, 139.3, 204.6, 180.6, 137.2, 156.7, 150.2, undef, undef, undef, undef
6092       !Config Help  = Values derived from generic soil types (free_draining mineral
6093       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6094       !               and the soil depth (shallow, deep, average)
6095       !Config Units = [Nm/Kg
6096       CALL getin_p('OV_GLEYED_DEEP',overturning_gleyed_deep)
6097
6098       !Config Key   = OV_GLEYED_DEEP_LESS
6099       !Config Desc  = Regression coefficient for overturning in gleyed and deep soil type leafless
6100       !Config if    = OK_STOMATE, OK_WINDTHROW
6101       !Config Def   = undef, 180.6, 180.6, 139.3, 204.6, 180.6, 137.2, 156.7, 150.2, undef, undef, undef, undef 
6102       !Config Help  = Values derived from generic soil types (free_draining mineral
6103       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6104       !               and the soil depth (shallow, deep, average)
6105       !Config Units = [Nm/Kg]
6106       CALL getin_p('OV_GLEYED_DEEP_LESS',overturning_gleyed_deep_leafless)
6107
6108       !Config Key   = OV_GLEYED_AVERAGE
6109       !Config Desc  = Regression coefficient for overturning in gleyed and medium soil type
6110       !Config if    = OK_STOMATE, OK_WINDTHROW
6111       !Config Def   = undef, 158.5, 158.5, 122.2, 179.5, 158.5, 120.3, 137.4, 131.7, undef, undef, undef, undef 
6112       !Config Help  = Values derived from generic soil types (free_draining mineral
6113       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6114       !               and the soil depth (shallow, deep, average)
6115       !Config Units = [Nm/Kg]
6116       CALL getin_p('OV_GLEYED_AVERAGE',overturning_gleyed_average)
6117
6118       !Config Key   = OV_GLEYED_AVERAGE_LESS
6119       !Config Desc  = Regression coefficient for overturning in gleyed and medium soil type leafless
6120       !Config if    = OK_STOMATE, OK_WINDTHROW
6121       !Config Def   = undef, 158.5, 158.5, 122.2, 179.5, 158.5, 120.3, 137.4, 131.7, undef, undef, undef, undef 
6122       !Config Help  = Values derived from generic soil types (free_draining mineral
6123       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6124       !               and the soil depth (shallow, deep, average)
6125       !Config Units = [Nm/Kg]
6126       CALL getin_p('OV_GLEYED_AVERAGE_LESS',overturning_gleyed_average_leafless)
6127
6128       !Config Key   = OV_PEATY_SHALLOW
6129       !Config Desc  = Regression coefficient for overturning in peaty and shallow soil type
6130       !Config if    = OK_STOMATE, OK_WINDTHROW
6131       !Config Def   = undef, 169.7, 169.7, 130.4, 192.2, 169.7, 128.4, 147.2, 140.6, undef, undef, undef, undef 
6132       !Config Help  = Values derived from generic soil types (free_draining mineral
6133       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6134       !               and the soil depth (shallow, deep, average)
6135       !Config Units = [Nm/Kg]
6136       CALL getin_p('OV_PEATY_SHALLOW',overturning_peaty_shallow)
6137
6138       !Config Key   = OV_PEATY_SHALLOW_LESS
6139       !Config Desc  = Regression coefficient for overturning in peaty and shallow soil type leafless
6140       !Config if    = OK_STOMATE, OK_WINDTHROW
6141       !Config Def   = undef, 169.7, 169.7, 130.4, 192.2, 169.7, 128.4, 147.2, 140.6, undef, undef, undef, undef 
6142       !Config Help  = Values derived from generic soil types (free_draining mineral
6143       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6144       !               and the soil depth (shallow, deep, average)
6145       !Config Units = [Nm/Kg]
6146       CALL getin_p('OV_PEATY_SHALLOW_LESS',overturning_peaty_shallow_leafless)
6147
6148       !Config Key   = OV_PEATY_DEEP
6149       !Config Desc  = Regression coefficient for overturning in peaty and deep soil type
6150       !Config if    = OK_STOMATE, OK_WINDTHROW
6151       !Config Def   = undef, 191.4, 191.4, 152.1, 223.5, 191.4, 141.9, 159.2, 164.0, undef, undef, undef, undef   
6152       !Config Help  = Values derived from generic soil types (free_draining mineral
6153       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6154       !               and the soil depth (shallow, deep, average)
6155       !Config Units = [Nm/Kg]
6156       CALL getin_p('OV_PEATY_DEEP',overturning_peaty_deep)
6157
6158       !Config Key   = OV_PEATY_DEEP_LESS
6159       !Config Desc  = Regression coefficient for overturning in peaty and deep soil type leafless 
6160       !Config if    = OK_STOMATE, OK_WINDTHROW
6161       !Config Def   = undef, 191.4, 191.4, 152.1, 223.5, 191.4, 141.9, 159.2, 164.0, undef, undef, undef, undef 
6162       !Config Help  = Values derived from generic soil types (free_draining mineral
6163       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6164       !               and the soil depth (shallow, deep, average)
6165       !Config Units = [Nm/Kg]
6166       CALL getin_p('OV_PEATY_DEEP_LESS',overturning_peaty_deep_leafless)
6167
6168       !Config Key   = OV_PEATY_AVERAGE
6169       !Config Desc  = Regression coefficient for overturning in peaty and medium soil type
6170       !Config if    = OK_STOMATE, OK_WINDTHROW
6171       !Config Def   = undef, 178.9, 178.9, 133.4, 195.9, 178.9, 131.4, 162.0, 143.8, undef, undef, undef, undef
6172       !Config Help  = Values derived from generic soil types (free_draining mineral
6173       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6174       !               and the soil depth (shallow, deep, average)
6175       !Config Units = [Nm/Kg]
6176       CALL getin_p('OV_PEATY_AVERAGE',overturning_peaty_average)
6177
6178       !Config Key   = OV_PEATY_AVERAGE_LESS
6179       !Config Desc  = Regression coefficient for overturning in peaty and medium soil type leafless
6180       !Config if    = OK_STOMATE, OK_WINDTHROW
6181       !Config Def   = undef, 178.9, 178.9, 133.4, 195.9, 178.9, 131.4, 162.0, 143.8, undef, undef, undef, undef   
6182       !Config Help  = Values derived from generic soil types (free_draining mineral
6183       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6184       !               and the soil depth (shallow, deep, average)
6185       !Config Units = [Nm/Kg]
6186       CALL getin_p('OV_PEATY_AVERAGE_LESS',overturning_peaty_average_leafless)
6187
6188       !Config Key   = OV_PEAT_SHALLOW
6189       !Config Desc  = Regression coefficient for overturning in shallow peat soil type
6190       !Config if    = OK_STOMATE, OK_WINDTHROW
6191       !Config Def   = undef, 193.0, 193.0, 148.3, 218.6, 193.0, 146.0, 167.4, 159.9, undef, undef, undef, undef 
6192       !Config Help  = Values derived from generic soil types (free_draining mineral
6193       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6194       !               and the soil depth (shallow, deep, average)
6195       !Config Units = [Nm/Kg]
6196       CALL getin_p('OV_PEAT_SHALLOW',overturning_peat_shallow)
6197
6198       !Config Key   = OV_PEAT_SHALLOW_LESS
6199       !Config Desc  = Regression coefficient for overturning in shallow peat soil leafless
6200       !Config if    = OK_STOMATE, OK_WINDTHROW
6201       !Config Def   = undef, 193.0, 193.0, 148.3, 218.6, 193.0, 146.0, 167.4, 159.9, undef, undef, undef, undef
6202       !Config Help  = Values derived from generic soil types (free_draining mineral
6203       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6204       !               and the soil depth (shallow, deep, average)
6205       !Config Units = [Nm/Kg]
6206       CALL getin_p('OV_PEAT_SHALLOW_LESS',overturning_peat_shallow_leafless)
6207
6208       !Config Key   = OV_PEAT_DEEP
6209       !Config Desc  = Regression coefficient for overturning in deep peat soil
6210       !Config if    = OK_STOMATE, OK_WINDTHROW
6211       !Config Def   = undef, 224.4, 224.4, 173.1, 254.2, 224.4, 170.4, 194.7, 186.6, undef, undef, undef, undef
6212       !Config Help  = Values derived from generic soil types (free_draining mineral
6213       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6214       !               and the soil depth (shallow, deep, average)
6215       !Config Units = [Nm/Kg]
6216       CALL getin_p('OV_PEAT_DEEP',overturning_peat_deep)
6217
6218       !Config Key   = OV_PEAT_DEEP_LESS
6219       !Config Desc  = Regression coefficient for overturning in deep peat soil leafless
6220       !Config if    = OK_STOMATE, OK_WINDTHROW
6221       !Config Def   = undef, 224.4, 224.4, 173.1, 254.2, 224.4, 170.4, 194.7, 186.6, undef, undef, undef, undef
6222       !Config Help  = Values derived from generic soil types (free_draining mineral
6223       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6224       !               and the soil depth (shallow, deep, average)
6225       !Config Units = [Nm/Kg]
6226       CALL getin_p('OV_PEAT_DEEP_LESS',overturning_peat_deep_leafless)
6227
6228       !Config Key   = OV_PEAT_AVERAGE
6229       !Config Desc  = Regression coefficient for overturning in medium peat soil
6230       !Config if    = OK_STOMATE, OK_WINDTHROW
6231       !Config Def   = undef, 196.9, 196.9, 151.8, 223.0, 196.9, 149.4, 170.8, 163.6, undef, undef, undef, undef 
6232       !Config Help  = Values derived from generic soil types (free_draining mineral
6233       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6234       !               and the soil depth (shallow, deep, average)
6235       !Config Units = [Nm/Kg]
6236       CALL getin_p('OV_PEAT_AVERAGE',overturning_peat_average)
6237
6238       !Config Key   = OV_PEAT_AVERAGE_LESS
6239       !Config Desc  = Regression coefficient for overturning in medium peat soil leafless
6240       !Config if    = OK_STOMATE, OK_WINDTHROW
6241       !Config Def   = undef, 196.9, 196.9, 151.8, 223.0, 196.9, 149.4, 170.8, 163.6, undef, undef, undef, undef
6242       !Config Help  = Values derived from generic soil types (free_draining mineral
6243       !               soils; Gleyed mineral soils; Peaty mineral soils; Deep peats)
6244       !               and the soil depth (shallow, deep, average)
6245       !Config Units = [Nm/Kg]
6246       CALL getin_p('OV_PEAT_AVERAGE_LESS',overturning_peat_average_leafless)
6247
6248       !Config Key   = MDF
6249       !Config Desc  = Maximum damage rate away from the forest edge
6250       !Config if    = OK_STOMATE, OK_WINDTHROW
6251       !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8
6252       !Config Help  = A tuning parameter for determining wind damage rate/level
6253       !Config Units = [unitless]
6254       CALL getin_p('MAX_DAMAGE_FURTHER',max_damage_further)
6255
6256       !Config Key   = MDC
6257       !Config Desc  = Maximum damage rate nearby the forest edge
6258       !Config if    = OK_STOMATE, OK_WINDTHROW
6259       !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8
6260       !Config Help  = A tuning parameter for determining wind damage rate/level
6261       !Config Units = [unitless]
6262       CALL getin_p('MAX_DAMAGE_CLOSER',max_damage_closer)
6263
6264       !Config Key   = SFF
6265       !Config Desc  = Scaling factor for maximum damage rate away from the forest edge
6266       !Config if    = OK_STOMATE, OK_WINDTHROW
6267       !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8
6268       !Config Help  = A tuning parameter for determining wind damage rate/level
6269       !Config Units = [unitless]
6270       CALL getin_p('SFACTOR_FURTHER',sfactor_further)
6271
6272       !Config Key   = SFC
6273       !Config Desc  = Scaling factor for maximum damage rate nearby the forest edge
6274       !Config if    = OK_STOMATE, OK_WINDTHROW
6275       !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8
6276       !Config Help  = A tuning parameter for determining wind damage rate/level
6277       !Config Units = [unitless]
6278       CALL getin_p('SFACTOR_CLOSER',sfactor_closer)
6279
6280    ENDIF
6281   
6282    !
6283    ! Phenology : Senescence
6284    !
6285    !
6286    !Config Key   = LEAFFALL
6287    !Config Desc  = length of death of leaves, tabulated
6288    !Config if    = OK_STOMATE
6289    !Config Def   = undef, undef, 10., undef, undef, 10., undef, 10., 10., 10., 10., 10., 10.
6290    !Config Help  =
6291    !Config Units = [days]
6292    CALL getin_p('LEAFFALL',leaffall)
6293
6294    !Config Key   = PRESENESCENCE_RATIO
6295    !Config Desc  = The ratio of maintenance respiration to gpp beyond which presenescence
6296    !               stage of plant phenology is declared to begin.
6297    !Config if    = OK_STOMATE
6298    !Config Def   =
6299    !Config Help  =
6300    !Config Units = [0-1, unitless]
6301    CALL getin_p('PRESENESCENCE_RATIO',presenescence_ratio)
6302
6303    !Config Key   = SENESCENCE_TYPE
6304    !Config Desc  = type of senescence, tabulated
6305    !Config if    = OK_STOMATE
6306    !Config Def   = none, none, dry, none, none, cold, none, cold, cold, mixed, mixed, mixed, mixed
6307    !Config Help  =
6308    !Config Units = [-]
6309    CALL getin_p('SENESCENCE_TYPE',senescence_type) 
6310
6311    !Config Key   = SENESCENCE_HUM
6312    !Config Desc  = critical relative moisture availability for senescence
6313    !Config if    = OK_STOMATE
6314    !Config Def   = undef, undef, .3, undef, undef, undef, undef, undef, undef, .2, .2, .3, .2
6315    !Config Help  =
6316    !Config Units = [-]
6317    CALL getin_p('SENESCENCE_HUM',senescence_hum)
6318
6319    !Config Key   = NOSENESCENCE_HUM
6320    !Config Desc  = relative moisture availability above which there is no humidity-related senescence
6321    !Config if    = OK_STOMATE
6322    !Config Def   = undef, undef, .8, undef, undef, undef, undef, undef, undef, .3, .3, .3, .3
6323    !Config Help  =
6324    !Config Units = [-]
6325    CALL getin_p('NOSENESCENCE_HUM',nosenescence_hum) 
6326
6327    !Config Key   = MAX_TURNOVER_TIME
6328    !Config Desc  = maximum turnover time for grasse
6329    !Config if    = OK_STOMATE
6330    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef,  80.,  80., 80., 80.
6331    !Config Help  =
6332    !Config Units = [days]
6333    CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time)
6334
6335    !Config Key   = MIN_TURNOVER_TIME
6336    !Config Desc  = minimum turnover time for grasse
6337    !Config if    = OK_STOMATE
6338    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 10., 10., 10., 10.
6339    !Config Help  =
6340    !Config Units = [days]
6341    CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time)
6342
6343    !Config Key   = RECYCLE_LEAF
6344    !Config Desc  = Fraction of N leaf that is recycled when leaves are senescent
6345    !Config if    = OK_STOMATE
6346    !Config Def   = undef, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5, 0.5
6347    !Config Help  =
6348    !Config Units = [-]
6349    CALL getin_p('RECYCLE_LEAF',recycle_leaf)
6350
6351    !Config Key   = RECYCLE_ROOT
6352    !Config Desc  = Fraction of N root that is recycled when roots are senescent
6353    !Config if    = OK_STOMATE
6354    !Config Def   = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2
6355    !Config Help  =
6356    !Config Units = [-]
6357    CALL getin_p('RECYCLE_ROOT',recycle_root)
6358
6359    !Config Key   = MIN_LEAF_AGE_FOR_SENESCENCE
6360    !Config Desc  = minimum leaf age to allow senescence g
6361    !Config if    = OK_STOMATE
6362    !Config Def   = undef, undef, 90., undef, undef, 90., undef, 60., 60., 30., 30., 30., 30.
6363    !Config Help  =
6364    !Config Units = [days]
6365    CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE',min_leaf_age_for_senescence)
6366
6367    !Config Key   = SENESCENCE_TEMP_C
6368    !Config Desc  = critical temperature for senescence (C), constant c of aT^2+bT+c, tabulated
6369    !Config if    = OK_STOMATE
6370    !Config Def   = undef, undef, undef, undef, undef, 12., undef, 7., 2., -1.375, 5., 5., 10.
6371    !Config Help  =
6372    !Config Units = [-]
6373    CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c)
6374
6375    !Config Key   = SENESCENCE_TEMP_B
6376    !Config Desc  = critical temperature for senescence (C), constant b of aT^2+bT+c ,tabulated
6377    !Config if    = OK_STOMATE
6378    !Config Def   = undef, undef, undef, undef, undef, 0., undef, 0., 0., .1, 0., 0., 0.
6379    !Config Help  =
6380    !Config Units = [-]
6381    CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b)
6382
6383    !Config Key   = SENESCENCE_TEMP_A
6384    !Config Desc  = critical temperature for senescence (C), constant a of aT^2+bT+c , tabulated
6385    !Config if    = OK_STOMATE
6386    !Config Def   = undef, undef, undef, undef, undef, 0., undef, 0., 0.,.00375, 0., 0., 0.
6387    !Config Help  =
6388    !Config Units = [-]
6389    CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a)
6390
6391    !Config Key   = GDD_SENESCENCE
6392    !Config Desc  = minimum gdd to allow senescence of crops 
6393    !Config if    = OK_STOMATE
6394    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 950., 4000.
6395    !Config Help  =
6396    !Config Units = [days]
6397    CALL getin_p("GDD_SENESCENCE", gdd_senescence)
6398
6399    !Config Key   = ALWAYS_INIT
6400    !Config Desc  = Take carbon from atmosphere if carbohydrate reserve too small
6401    !Config if    = OK_STOMATE
6402    !Config Def   = y, y, y, y, y, y, y, y, y, y, n, y, y
6403    !Config Help  =
6404    !Config Units = [BOOLEAN]
6405    CALL getin_p('ALWAYS_INIT',always_init)
6406
6407    !
6408    ! N cycle
6409
6410    !Config Key   = MAX_SOIL_N_BNF
6411    !Config Desc  = Value of total N (NH4+NO3) above which we stop adding N via BNF (gN/m**2) 
6412    !Config if    = OK_STOMATE
6413    !Config Def   = 0.0, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 1.5, 2., 2., 2., 2.
6414    !Config Help  =
6415    !Config Units = [gN/m**2]
6416    CALL getin_p("MAX_SOIL_N_BNF", max_soil_n_bnf)
6417
6418    !Config Key   = MANURE_PFTWEIGHT
6419    !Config Desc  = Weight of the distribution of manure over the PFT surface
6420    !Config if    = OK_STOMATE
6421    !Config Def   = 0., 0., 0., 0., 0., 0., 0., 0., 0., 1., 1., 1., 1.
6422    !Config Help  =
6423    !Config Units = [gC/gN]
6424    CALL getin_p("MANURE_PFTWEIGHT", manure_pftweight)
6425
6426    !
6427    ! CROPLAND MANAGEMENT
6428    !
6429    !Config Key   = HARVEST_RATIO
6430    !Config Desc  = Share of biomass that is harvested
6431    !Config if    = OK_STOMATE
6432    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.5, 0.5
6433    !Config Help  = Share of biomass that is harvested. This residual equal to 1 minus harvest_ratio
6434    !Config Units = [unitless]
6435    CALL getin_p("HARVEST_RATIO", harvest_ratio)
6436   
6437
6438    !
6439    ! DGVM
6440    !
6441
6442    !Config Key   = RESIDENCE_TIME
6443    !Config Desc  = residence time of trees
6444    !Config if    = OK_DGVM and NOT(LPJ_GAP_CONST_MORT)
6445    !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
6446    !Config Help  =
6447    !Config Units = [years]
6448    CALL getin_p('RESIDENCE_TIME',residence_time)
6449
6450    !Config Key   = TMIN_CRIT
6451    !Config Desc  = critical tmin, tabulated
6452    !Config if    = OK_STOMATE
6453    !Config Def   = undef,  0.0, 0.0, -30.0, -14.0, -30.0, -45.0, -45.0, undef, undef, undef, undef, undef
6454    !Config Help  =
6455    !Config Units = [C]
6456    CALL getin_p('TMIN_CRIT',tmin_crit)
6457
6458    !Config Key   = TCM_CRIT
6459    !Config Desc  = critical tcm, tabulated
6460    !Config if    = OK_STOMATE
6461    !Config Def   = undef, undef, undef, 5.0, 15.5, 15.5, -8.0, -8.0, -8.0, undef, undef, undef, undef
6462    !Config Help  =
6463    !Config Units = [C]
6464    CALL getin_p('TCM_CRIT',tcm_crit)
6465
6466
6467    ! Age classes
6468    ! I want to create a temporary array that indicates which "real" PFT starts
6469    ! on which index.  This could probably be put somewhere else, but this
6470    ! routine is only called once a year and this loop is not expensive.
6471    start_index(:)=-1
6472    nagec_pft(:)=-1
6473    DO ivma=1,nvmap
6474       ! The start index is just the first place we find this real PFT.
6475       DO ivm=1,nvm
6476          IF(agec_group(ivm) .EQ. ivma)THEN
6477             start_index(ivma)=ivm
6478             ! It is possible that not all forests will have multiple age
6479             ! classes.  For example, the species might have age classes
6480             ! but metaclasses (running outside Europe) might not. Let's
6481             ! check to see how many age classes each PFT has. Right now,
6482             ! the only options are 1 or nagec, but this could be changed
6483             ! without too much difficulty.
6484             IF((ivm+nagec-1) .LT. nvm)THEN
6485                ! This first if loop prevents an out of bounds error
6486                IF(agec_group(ivm+nagec-1) == ivma)THEN
6487                   nagec_pft(ivma)=nagec
6488                ELSE
6489                   nagec_pft(ivma)=1
6490                ENDIF
6491             ELSE
6492                nagec_pft(ivma)=1
6493             ENDIF
6494             EXIT
6495          ENDIF
6496       ENDDO
6497    ENDDO
6498    ! Check to see if the calculation worked and we found indices for all of them.
6499    DO ivma=1,nvmap
6500       IF(start_index(ivma) .LT. 0)THEN
6501          WRITE(numout,*) 'Could not find a start index for one age class group!'
6502          WRITE(numout,*) 'Check the input file and ',&
6503               'make sure the following ivma appears in agec_group'
6504          WRITE(numout,*) 'ivma,nvmap',ivma,nvmap
6505          WRITE(numout,*) 'agec_group',agec_group(:)
6506          CALL ipslerr_p (3,'pft_parameters','pft_parameters_alloc','','')
6507       ENDIF
6508    ENDDO
6509   
6510  END SUBROUTINE config_stomate_pft_parameters
6511
6512
6513!! ================================================================================================================================
6514!! SUBROUTINE   : pft_parameters_clear
6515!!
6516!>\BRIEF         This subroutine deallocates memory at the end of the simulation.
6517!!
6518!! DESCRIPTION  : None
6519!!
6520!! RECENT CHANGE(S): None
6521!!
6522!! MAIN OUTPUT VARIABLE(S): None
6523!!
6524!! REFERENCE(S) : None
6525!!
6526!! FLOWCHART    : None
6527!! \n
6528!_ ================================================================================================================================
6529
6530  SUBROUTINE pft_parameters_clear
6531
6532    l_first_pft_parameters = .TRUE.
6533
6534    IF (ALLOCATED(pft_to_mtc)) DEALLOCATE(pft_to_mtc)
6535    IF (ALLOCATED(PFT_name)) DEALLOCATE(PFT_name)
6536    IF (ALLOCATED(veget_ori_fixed_test_1)) DEALLOCATE(veget_ori_fixed_test_1)   
6537    IF (ALLOCATED(llaimax)) DEALLOCATE(llaimax)
6538    IF (ALLOCATED(llaimin)) DEALLOCATE(llaimin)
6539    IF (ALLOCATED(height_presc)) DEALLOCATE(height_presc)   
6540    IF (ALLOCATED(z0_over_height)) DEALLOCATE(z0_over_height)   
6541    IF (ALLOCATED(ratio_z0m_z0h)) DEALLOCATE(ratio_z0m_z0h)   
6542    IF (ALLOCATED(type_of_lai)) DEALLOCATE(type_of_lai)
6543    IF (ALLOCATED(is_tree)) DEALLOCATE(is_tree)
6544    IF (ALLOCATED(natural)) DEALLOCATE(natural)
6545    IF (ALLOCATED(is_deciduous)) DEALLOCATE(is_deciduous)
6546    IF (ALLOCATED(is_evergreen)) DEALLOCATE(is_evergreen)
6547    IF (ALLOCATED(is_needleleaf)) DEALLOCATE(is_needleleaf)
6548    IF (ALLOCATED(is_tropical)) DEALLOCATE(is_tropical)
6549    IF (ALLOCATED(is_temperate)) DEALLOCATE(is_temperate)
6550    IF (ALLOCATED(is_boreal)) DEALLOCATE(is_boreal)
6551    IF (ALLOCATED(agec_group)) DEALLOCATE(agec_group)
6552    IF (ALLOCATED(start_index)) DEALLOCATE(start_index)
6553    IF (ALLOCATED(nagec_pft)) DEALLOCATE(nagec_pft)
6554    IF (ALLOCATED(humcste)) DEALLOCATE(humcste)
6555    IF (ALLOCATED(max_root_depth)) DEALLOCATE(max_root_depth)
6556    IF (ALLOCATED(pref_soil_veg)) DEALLOCATE(pref_soil_veg)
6557    IF (ALLOCATED(is_c4)) DEALLOCATE(is_c4) 
6558    IF (ALLOCATED(vcmax_fix)) DEALLOCATE(vcmax_fix)
6559    IF (ALLOCATED(downregulation_co2_coeff)) DEALLOCATE(downregulation_co2_coeff) 
6560    IF (ALLOCATED(E_KmC)) DEALLOCATE(E_KmC)
6561    IF (ALLOCATED(E_KmO)) DEALLOCATE(E_KmO)
6562    IF (ALLOCATED(E_Sco)) DEALLOCATE(E_Sco)
6563    IF (ALLOCATED(E_gamma_star)) DEALLOCATE(E_gamma_star)
6564    IF (ALLOCATED(E_Vcmax)) DEALLOCATE(E_Vcmax)
6565    IF (ALLOCATED(E_Jmax)) DEALLOCATE(E_Jmax)
6566    IF (ALLOCATED(aSV)) DEALLOCATE(aSV)
6567    IF (ALLOCATED(bSV)) DEALLOCATE(bSV)
6568    IF (ALLOCATED(tphoto_min)) DEALLOCATE(tphoto_min)
6569    IF (ALLOCATED(tphoto_max)) DEALLOCATE(tphoto_max)
6570    IF (ALLOCATED(aSJ)) DEALLOCATE(aSJ)
6571    IF (ALLOCATED(bSJ)) DEALLOCATE(bSJ)
6572    IF (ALLOCATED(D_Vcmax)) DEALLOCATE(D_Vcmax)
6573    IF (ALLOCATED(D_Jmax)) DEALLOCATE(D_Jmax)
6574    IF (ALLOCATED(E_gm)) DEALLOCATE(E_gm) 
6575    IF (ALLOCATED(S_gm)) DEALLOCATE(S_gm) 
6576    IF (ALLOCATED(D_gm)) DEALLOCATE(D_gm) 
6577    IF (ALLOCATED(E_Rd)) DEALLOCATE(E_Rd)
6578    IF (ALLOCATED(Vcmax25)) DEALLOCATE(Vcmax25)
6579    IF (ALLOCATED(arJV)) DEALLOCATE(arJV)
6580    IF (ALLOCATED(brJV)) DEALLOCATE(brJV)
6581    IF (ALLOCATED(KmC25)) DEALLOCATE(KmC25)
6582    IF (ALLOCATED(KmO25)) DEALLOCATE(KmO25)
6583    IF (ALLOCATED(Sco25)) DEALLOCATE(Sco25)
6584    IF (ALLOCATED(gm25)) DEALLOCATE(gm25) 
6585    IF (ALLOCATED(gamma_star25)) DEALLOCATE(gamma_star25)
6586    IF (ALLOCATED(a1)) DEALLOCATE(a1)
6587    IF (ALLOCATED(b1)) DEALLOCATE(b1)
6588    IF (ALLOCATED(g0)) DEALLOCATE(g0)
6589    IF (ALLOCATED(h_protons)) DEALLOCATE(h_protons)
6590    IF (ALLOCATED(fpsir)) DEALLOCATE(fpsir)
6591    IF (ALLOCATED(fQ)) DEALLOCATE(fQ)
6592    IF (ALLOCATED(fpseudo)) DEALLOCATE(fpseudo)
6593    IF (ALLOCATED(kp)) DEALLOCATE(kp)
6594    IF (ALLOCATED(alpha)) DEALLOCATE(alpha)
6595    IF (ALLOCATED(gbs)) DEALLOCATE(gbs)
6596    IF (ALLOCATED(theta)) DEALLOCATE(theta)
6597    IF (ALLOCATED(alpha_LL)) DEALLOCATE(alpha_LL)
6598    IF (ALLOCATED(stress_vcmax)) DEALLOCATE(stress_vcmax)
6599    IF (ALLOCATED(stress_gs)) DEALLOCATE(stress_gs)
6600    IF (ALLOCATED(stress_gm)) DEALLOCATE(stress_gm)
6601    IF (ALLOCATED(ext_coeff)) DEALLOCATE(ext_coeff)
6602    IF (ALLOCATED(ext_coeff_vegetfrac)) DEALLOCATE(ext_coeff_vegetfrac)
6603    IF (ALLOCATED(rveg_pft)) DEALLOCATE(rveg_pft)
6604    IF (ALLOCATED(rstruct_const)) DEALLOCATE(rstruct_const)
6605    IF (ALLOCATED(kzero)) DEALLOCATE(kzero)
6606    IF (ALLOCATED(wmax_veg)) DEALLOCATE(wmax_veg)
6607    IF (ALLOCATED(throughfall_by_pft)) DEALLOCATE(throughfall_by_pft)
6608    IF (ALLOCATED(snowa_aged_vis)) DEALLOCATE(snowa_aged_vis)
6609    IF (ALLOCATED(snowa_aged_nir)) DEALLOCATE(snowa_aged_nir)
6610    IF (ALLOCATED(snowa_dec_vis)) DEALLOCATE(snowa_dec_vis)
6611    IF (ALLOCATED(snowa_dec_nir)) DEALLOCATE(snowa_dec_nir)
6612    IF (ALLOCATED(alb_leaf_vis)) DEALLOCATE(alb_leaf_vis)
6613    IF (ALLOCATED(alb_leaf_nir)) DEALLOCATE(alb_leaf_nir) 
6614    IF (ALLOCATED(leaf_ssa)) DEALLOCATE(leaf_ssa)   
6615    IF (ALLOCATED(leaf_psd)) DEALLOCATE(leaf_psd)   
6616    IF (ALLOCATED(bgd_reflectance)) DEALLOCATE(bgd_reflectance)
6617    IF (ALLOCATED(leaf_to_shoot_clumping)) DEALLOCATE(leaf_to_shoot_clumping) 
6618    IF (ALLOCATED(lai_correction_factor)) DEALLOCATE(lai_correction_factor) 
6619    IF (ALLOCATED(min_level_sep)) DEALLOCATE(min_level_sep)
6620    IF (ALLOCATED(lai_top)) DEALLOCATE(lai_top)   
6621    IF (ALLOCATED(em_factor_isoprene)) DEALLOCATE(em_factor_isoprene)
6622    IF (ALLOCATED(em_factor_monoterpene)) DEALLOCATE(em_factor_monoterpene)
6623    IF (ALLOCATED(em_factor_apinene)) DEALLOCATE(em_factor_apinene)
6624    IF (ALLOCATED(em_factor_bpinene)) DEALLOCATE(em_factor_bpinene)
6625    IF (ALLOCATED(em_factor_limonene)) DEALLOCATE(em_factor_limonene)
6626    IF (ALLOCATED(em_factor_myrcene)) DEALLOCATE(em_factor_myrcene)
6627    IF (ALLOCATED(em_factor_sabinene)) DEALLOCATE(em_factor_sabinene)
6628    IF (ALLOCATED(em_factor_camphene)) DEALLOCATE(em_factor_camphene)
6629    IF (ALLOCATED(em_factor_3carene)) DEALLOCATE(em_factor_3carene)
6630    IF (ALLOCATED(em_factor_tbocimene)) DEALLOCATE(em_factor_tbocimene)
6631    IF (ALLOCATED(em_factor_othermonot)) DEALLOCATE(em_factor_othermonot)
6632    IF (ALLOCATED(em_factor_sesquiterp)) DEALLOCATE(em_factor_sesquiterp)
6633    IF (ALLOCATED(em_factor_ORVOC)) DEALLOCATE(em_factor_ORVOC)
6634    IF (ALLOCATED(em_factor_OVOC)) DEALLOCATE(em_factor_OVOC)
6635    IF (ALLOCATED(em_factor_MBO)) DEALLOCATE(em_factor_MBO)
6636    IF (ALLOCATED(em_factor_methanol)) DEALLOCATE(em_factor_methanol)
6637    IF (ALLOCATED(em_factor_acetone)) DEALLOCATE(em_factor_acetone)
6638    IF (ALLOCATED(em_factor_acetal)) DEALLOCATE(em_factor_acetal)
6639    IF (ALLOCATED(em_factor_formal)) DEALLOCATE(em_factor_formal)
6640    IF (ALLOCATED(em_factor_acetic)) DEALLOCATE(em_factor_acetic)
6641    IF (ALLOCATED(em_factor_formic)) DEALLOCATE(em_factor_formic)
6642    IF (ALLOCATED(em_factor_no_wet)) DEALLOCATE(em_factor_no_wet)
6643    IF (ALLOCATED(em_factor_no_dry)) DEALLOCATE(em_factor_no_dry)
6644    IF (ALLOCATED(Larch)) DEALLOCATE(Larch)
6645    IF (ALLOCATED(leaf_tab)) DEALLOCATE(leaf_tab)
6646    IF (ALLOCATED(sla)) DEALLOCATE(sla)
6647    IF (ALLOCATED(slainit)) DEALLOCATE(slainit)
6648    IF (ALLOCATED(availability_fact)) DEALLOCATE(availability_fact)
6649    IF (ALLOCATED(nue_opt)) DEALLOCATE(nue_opt)
6650    IF (ALLOCATED(vmax_uptake)) DEALLOCATE(vmax_uptake)
6651    IF (ALLOCATED(ext_coeff_N)) DEALLOCATE(ext_coeff_N)
6652    IF (ALLOCATED(frac_growthresp)) DEALLOCATE(frac_growthresp)
6653    IF (ALLOCATED(coeff_maint_init)) DEALLOCATE(coeff_maint_init)
6654    IF (ALLOCATED(tref_maint_resp)) DEALLOCATE(tref_maint_resp)
6655    IF (ALLOCATED(tmin_maint_resp)) DEALLOCATE(tmin_maint_resp)
6656    IF (ALLOCATED(e0_maint_resp)) DEALLOCATE(e0_maint_resp)
6657    IF (ALLOCATED(tref_labile)) DEALLOCATE(tref_labile)
6658    IF (ALLOCATED(tmin_labile)) DEALLOCATE(tmin_labile)
6659    IF (ALLOCATED(e0_labile)) DEALLOCATE(e0_labile)
6660    IF (ALLOCATED(always_labile)) DEALLOCATE(always_labile)
6661    IF (ALLOCATED(flam)) DEALLOCATE(flam)
6662    IF (ALLOCATED(resist)) DEALLOCATE(resist)
6663    IF (ALLOCATED(coeff_lcchange_s)) DEALLOCATE(coeff_lcchange_s)
6664    IF (ALLOCATED(coeff_lcchange_m)) DEALLOCATE(coeff_lcchange_m)
6665    IF (ALLOCATED(coeff_lcchange_l)) DEALLOCATE(coeff_lcchange_l)
6666    IF (ALLOCATED(lai_max_to_happy)) DEALLOCATE(lai_max_to_happy)
6667    IF (ALLOCATED(lai_max)) DEALLOCATE(lai_max)
6668    IF (ALLOCATED(pheno_model)) DEALLOCATE(pheno_model)
6669    IF (ALLOCATED(pheno_type)) DEALLOCATE(pheno_type)
6670    IF (ALLOCATED(force_pheno)) DEALLOCATE(force_pheno)
6671    IF (ALLOCATED(pheno_gdd_crit_c)) DEALLOCATE(pheno_gdd_crit_c)
6672    IF (ALLOCATED(pheno_gdd_crit_b)) DEALLOCATE(pheno_gdd_crit_b)
6673    IF (ALLOCATED(pheno_gdd_crit_a)) DEALLOCATE(pheno_gdd_crit_a)
6674    IF (ALLOCATED(pheno_gdd_crit)) DEALLOCATE(pheno_gdd_crit)
6675    IF (ALLOCATED(pheno_moigdd_t_crit)) DEALLOCATE(pheno_moigdd_t_crit)
6676    IF (ALLOCATED(ngd_crit)) DEALLOCATE(ngd_crit)
6677    IF (ALLOCATED(ncdgdd_temp)) DEALLOCATE(ncdgdd_temp)
6678    IF (ALLOCATED(hum_frac)) DEALLOCATE(hum_frac)
6679    IF (ALLOCATED(hum_min_time)) DEALLOCATE(hum_min_time)
6680    IF (ALLOCATED(longevity_sap)) DEALLOCATE(longevity_sap)
6681    IF (ALLOCATED(longevity_leaf)) DEALLOCATE(longevity_leaf)
6682    IF (ALLOCATED(leaf_age_crit_tref)) DEALLOCATE(leaf_age_crit_tref)
6683    IF (ALLOCATED(leaf_age_crit_coeff1)) DEALLOCATE(leaf_age_crit_coeff1)
6684    IF (ALLOCATED(leaf_age_crit_coeff2)) DEALLOCATE(leaf_age_crit_coeff2)
6685    IF (ALLOCATED(leaf_age_crit_coeff3)) DEALLOCATE(leaf_age_crit_coeff3)
6686    IF (ALLOCATED(longevity_fruit)) DEALLOCATE(longevity_fruit)
6687    IF (ALLOCATED(longevity_root)) DEALLOCATE(longevity_root)
6688    IF (ALLOCATED(ecureuil)) DEALLOCATE(ecureuil)
6689    IF (ALLOCATED(alloc_min)) DEALLOCATE(alloc_min)
6690    IF (ALLOCATED(alloc_max)) DEALLOCATE(alloc_max)
6691    IF (ALLOCATED(demi_alloc)) DEALLOCATE(demi_alloc)
6692    IF (ALLOCATED(leaffall)) DEALLOCATE(leaffall)
6693    IF (ALLOCATED(presenescence_ratio)) DEALLOCATE(presenescence_ratio)
6694    IF (ALLOCATED(senescence_type)) DEALLOCATE(senescence_type)
6695    IF (ALLOCATED(senescence_hum)) DEALLOCATE(senescence_hum)
6696    IF (ALLOCATED(nosenescence_hum)) DEALLOCATE(nosenescence_hum)
6697    IF (ALLOCATED(max_turnover_time)) DEALLOCATE(max_turnover_time)
6698    IF (ALLOCATED(min_turnover_time)) DEALLOCATE(min_turnover_time)
6699    IF (ALLOCATED(recycle_leaf)) DEALLOCATE(recycle_leaf)
6700    IF (ALLOCATED(recycle_root)) DEALLOCATE(recycle_root)
6701    IF (ALLOCATED(min_leaf_age_for_senescence)) DEALLOCATE(min_leaf_age_for_senescence)
6702    IF (ALLOCATED(senescence_temp_c)) DEALLOCATE(senescence_temp_c)
6703    IF (ALLOCATED(senescence_temp_b)) DEALLOCATE(senescence_temp_b)
6704    IF (ALLOCATED(senescence_temp_a)) DEALLOCATE(senescence_temp_a)
6705    IF (ALLOCATED(senescence_temp)) DEALLOCATE(senescence_temp)
6706    IF (ALLOCATED(gdd_senescence)) DEALLOCATE(gdd_senescence)
6707    IF (ALLOCATED(always_init)) DEALLOCATE(always_init)
6708    IF (ALLOCATED(cn_leaf_min)) DEALLOCATE(cn_leaf_min)
6709    IF (ALLOCATED(cn_leaf_max)) DEALLOCATE(cn_leaf_max)
6710    IF (ALLOCATED(max_soil_n_bnf)) DEALLOCATE(max_soil_n_bnf)
6711    IF (ALLOCATED(manure_pftweight)) DEALLOCATE(manure_pftweight)
6712    IF (ALLOCATED(residence_time)) DEALLOCATE(residence_time)
6713    IF (ALLOCATED(tmin_crit)) DEALLOCATE(tmin_crit)
6714    IF (ALLOCATED(tcm_crit)) DEALLOCATE(tcm_crit)
6715    IF (ALLOCATED(lai_initmin)) DEALLOCATE(lai_initmin)
6716    IF (ALLOCATED(bm_sapl)) DEALLOCATE(bm_sapl)
6717    IF (ALLOCATED(migrate)) DEALLOCATE(migrate)
6718    IF (ALLOCATED(maxdia)) DEALLOCATE(maxdia)
6719    IF (ALLOCATED(cn_sapl)) DEALLOCATE(cn_sapl)
6720    IF (ALLOCATED(k_latosa_max)) DEALLOCATE(k_latosa_max)
6721    IF (ALLOCATED(k_latosa_min)) DEALLOCATE(k_latosa_min)
6722    IF (ALLOCATED(LC)) DEALLOCATE(LC)
6723    IF (ALLOCATED(LC_leaf)) DEALLOCATE(LC_leaf)
6724    IF (ALLOCATED(LC_sapabove)) DEALLOCATE(LC_sapabove)
6725    IF (ALLOCATED(LC_sapbelow)) DEALLOCATE(LC_sapbelow)
6726    IF (ALLOCATED(LC_heartabove)) DEALLOCATE(LC_heartabove)
6727    IF (ALLOCATED(LC_heartbelow)) DEALLOCATE(LC_heartbelow)
6728    IF (ALLOCATED(LC_fruit)) DEALLOCATE(LC_fruit)
6729    IF (ALLOCATED(LC_root)) DEALLOCATE(LC_root)
6730    IF (ALLOCATED(LC_carbres)) DEALLOCATE(LC_carbres)
6731    IF (ALLOCATED(LC_labile)) DEALLOCATE(LC_labile)
6732    IF (ALLOCATED(decomp_factor)) DEALLOCATE(decomp_factor)
6733    IF (ALLOCATED(crown_vertohor_dia)) DEALLOCATE(crown_vertohor_dia)
6734    IF (ALLOCATED(crown_to_height)) DEALLOCATE(crown_to_height)   
6735    IF (ALLOCATED(pipe_density)) DEALLOCATE(pipe_density)
6736    IF (ALLOCATED(tree_ff)) DEALLOCATE(tree_ff)
6737    IF (ALLOCATED(pipe_tune2)) DEALLOCATE(pipe_tune2)
6738    IF (ALLOCATED(pipe_tune3)) DEALLOCATE(pipe_tune3)
6739    IF (ALLOCATED(pipe_tune4)) DEALLOCATE(pipe_tune4)
6740    IF (ALLOCATED(pipe_k1)) DEALLOCATE(pipe_k1)
6741    IF (ALLOCATED(mass_ratio_heart_sap)) DEALLOCATE(mass_ratio_heart_sap)
6742    IF (ALLOCATED(canopy_cover)) DEALLOCATE(canopy_cover)
6743    IF (ALLOCATED(nmaxplants)) DEALLOCATE(nmaxplants)
6744    IF (ALLOCATED(p_use_reserve)) DEALLOCATE(p_use_reserve)
6745    IF (ALLOCATED(height_init)) DEALLOCATE(height_init)
6746    IF (ALLOCATED(dia_init_min)) DEALLOCATE(dia_init_min)
6747    IF (ALLOCATED(dia_init_max)) DEALLOCATE(dia_init_max)
6748    IF (ALLOCATED(alpha_self_thinning)) DEALLOCATE(alpha_self_thinning)
6749    IF (ALLOCATED(beta_self_thinning)) DEALLOCATE(beta_self_thinning)
6750    IF (ALLOCATED(fuelwood_diameter)) DEALLOCATE(fuelwood_diameter)
6751    IF (ALLOCATED(coppice_kill_be_wood)) DEALLOCATE(coppice_kill_be_wood)
6752    IF (ALLOCATED(lai_to_height)) DEALLOCATE(lai_to_height)
6753    IF (ALLOCATED(deleuze_a)) DEALLOCATE(deleuze_a)
6754    IF (ALLOCATED(deleuze_b)) DEALLOCATE(deleuze_b)
6755    IF (ALLOCATED(deleuze_p_all)) DEALLOCATE(deleuze_p_all)
6756    IF (ALLOCATED(deleuze_power_a)) DEALLOCATE(deleuze_power_a)
6757    IF (ALLOCATED(m_dv)) DEALLOCATE(m_dv)
6758    IF (ALLOCATED(dens_target)) DEALLOCATE(dens_target)
6759    IF (ALLOCATED(thinstrat)) DEALLOCATE(thinstrat)
6760    IF (ALLOCATED(taumin)) DEALLOCATE(taumin)
6761    IF (ALLOCATED(taumax)) DEALLOCATE(taumax)
6762    IF (ALLOCATED(a_rdi_upper_unman)) DEALLOCATE(a_rdi_upper_unman)
6763    IF (ALLOCATED(b_rdi_upper_unman)) DEALLOCATE(b_rdi_upper_unman)
6764    IF (ALLOCATED(c_rdi_upper_unman)) DEALLOCATE(c_rdi_upper_unman)
6765    IF (ALLOCATED(d_rdi_upper_unman)) DEALLOCATE(d_rdi_upper_unman)
6766    IF (ALLOCATED(a_rdi_lower_unman)) DEALLOCATE(a_rdi_lower_unman)
6767    IF (ALLOCATED(b_rdi_lower_unman)) DEALLOCATE(b_rdi_lower_unman)
6768    IF (ALLOCATED(c_rdi_lower_unman)) DEALLOCATE(c_rdi_lower_unman)
6769    IF (ALLOCATED(d_rdi_lower_unman)) DEALLOCATE(d_rdi_lower_unman)
6770    IF (ALLOCATED(a_rdi_upper_man)) DEALLOCATE(a_rdi_upper_man)
6771    IF (ALLOCATED(b_rdi_upper_man)) DEALLOCATE(b_rdi_upper_man)
6772    IF (ALLOCATED(c_rdi_upper_man)) DEALLOCATE(c_rdi_upper_man)
6773    IF (ALLOCATED(d_rdi_upper_man)) DEALLOCATE(d_rdi_upper_man)
6774    IF (ALLOCATED(a_rdi_lower_man)) DEALLOCATE(a_rdi_lower_man)
6775    IF (ALLOCATED(b_rdi_lower_man)) DEALLOCATE(b_rdi_lower_man)
6776    IF (ALLOCATED(c_rdi_lower_man)) DEALLOCATE(c_rdi_lower_man)
6777    IF (ALLOCATED(d_rdi_lower_man)) DEALLOCATE(d_rdi_lower_man)
6778    IF (ALLOCATED(largest_tree_dia)) DEALLOCATE(largest_tree_dia)
6779    IF (ALLOCATED(coppice_diameter)) DEALLOCATE(coppice_diameter)
6780    IF (ALLOCATED(shoots_per_stool)) DEALLOCATE(shoots_per_stool)
6781    IF (ALLOCATED(src_rot_length)) DEALLOCATE(src_rot_length)
6782    IF (ALLOCATED(src_nrots)) DEALLOCATE(src_nrots)
6783    IF (ALLOCATED(fruit_alloc)) DEALLOCATE(fruit_alloc)
6784    IF (ALLOCATED(labile_reserve)) DEALLOCATE(labile_reserve)
6785    IF (ALLOCATED(evergreen_reserve)) DEALLOCATE(evergreen_reserve)
6786    IF (ALLOCATED(deciduous_reserve)) DEALLOCATE(deciduous_reserve)
6787    IF (ALLOCATED(senescense_reserve)) DEALLOCATE(senescense_reserve)
6788    IF (ALLOCATED(root_reserve)) DEALLOCATE(root_reserve)
6789    IF (ALLOCATED(fcn_wood)) DEALLOCATE(fcn_wood)
6790    IF (ALLOCATED(fcn_root)) DEALLOCATE(fcn_root)
6791    IF (ALLOCATED(branch_ratio)) DEALLOCATE(branch_ratio)
6792    IF (ALLOCATED(cn_leaf_init)) DEALLOCATE(cn_leaf_init)
6793    IF (ALLOCATED(k_root)) DEALLOCATE(k_root)
6794    IF (ALLOCATED(k_belowground)) DEALLOCATE(k_belowground)
6795    IF (ALLOCATED(k_sap)) DEALLOCATE(k_sap)
6796    IF (ALLOCATED(k_leaf)) DEALLOCATE(k_leaf)
6797    IF (ALLOCATED(psi_leaf)) DEALLOCATE(psi_leaf)
6798    IF (ALLOCATED(psi_50)) DEALLOCATE(psi_50)
6799    IF (ALLOCATED(c_cavitation)) DEALLOCATE(c_cavitation)
6800    IF (ALLOCATED(srl)) DEALLOCATE(srl)
6801    IF (ALLOCATED(r_froot)) DEALLOCATE(r_froot)
6802    IF (ALLOCATED(psi_root)) DEALLOCATE(psi_root)
6803    IF (ALLOCATED(recruitment_pft)) DEALLOCATE(recruitment_pft) 
6804    IF (ALLOCATED(beetle_pft)) DEALLOCATE(beetle_pft) 
6805    IF (ALLOCATED(recruitment_height)) DEALLOCATE(recruitment_height) 
6806    IF (ALLOCATED(recruitment_alpha)) DEALLOCATE(recruitment_alpha) 
6807    IF (ALLOCATED(recruitment_beta)) DEALLOCATE(recruitment_beta) 
6808    IF (ALLOCATED(harvest_ratio)) DEALLOCATE(harvest_ratio)
6809    IF (ALLOCATED(death_distribution_factor)) DEALLOCATE(death_distribution_factor)
6810    IF (ALLOCATED(npp_reset_value)) DEALLOCATE(npp_reset_value)
6811    IF (ALLOCATED(ndying_year)) DEALLOCATE(ndying_year)
6812    IF (ALLOCATED(remaining_beetles)) DEALLOCATE(remaining_beetles)
6813    IF (ALLOCATED(pressure_feedback)) DEALLOCATE(pressure_feedback)
6814    IF (ALLOCATED(age_susceptibility_a)) DEALLOCATE(age_susceptibility_a)
6815    IF (ALLOCATED(age_susceptibility_b)) DEALLOCATE(age_susceptibility_b)
6816    IF (ALLOCATED(age_susceptibility_c)) DEALLOCATE(age_susceptibility_c)
6817    IF (ALLOCATED(rdi_susceptibility_a)) DEALLOCATE(rdi_susceptibility_a)
6818    IF (ALLOCATED(rdi_susceptibility_b)) DEALLOCATE(rdi_susceptibility_b)
6819    IF (ALLOCATED(rdi_target_suscept)) DEALLOCATE(rdi_target_suscept)
6820    IF (ALLOCATED(share_susceptibility_a)) DEALLOCATE(share_susceptibility_a)
6821    IF (ALLOCATED(share_susceptibility_b)) DEALLOCATE(share_susceptibility_b)
6822    IF (ALLOCATED(drought_susceptibility_a)) DEALLOCATE(drought_susceptibility_a)
6823    IF (ALLOCATED(drought_susceptibility_b)) DEALLOCATE(drought_susceptibility_b)
6824    IF (ALLOCATED(windthrow_susceptibility_tune)) DEALLOCATE(windthrow_susceptibility_tune)
6825    IF (ALLOCATED(beetle_generation_a))DEALLOCATE(beetle_generation_a)
6826    IF (ALLOCATED(beetle_generation_b))DEALLOCATE(beetle_generation_b)
6827    IF (ALLOCATED(beetle_generation_c))DEALLOCATE(beetle_generation_c)
6828    IF (ALLOCATED(min_temp_beetle))DEALLOCATE(min_temp_beetle)
6829    IF (ALLOCATED(max_temp_beetle))DEALLOCATE(max_temp_beetle)
6830    IF (ALLOCATED(opt_temp_beetle))DEALLOCATE(opt_temp_beetle)
6831    IF (ALLOCATED(eff_temp_beetle_a))DEALLOCATE(eff_temp_beetle_a)
6832    IF (ALLOCATED(eff_temp_beetle_b))DEALLOCATE(eff_temp_beetle_b)
6833    IF (ALLOCATED(eff_temp_beetle_c))DEALLOCATE(eff_temp_beetle_c)
6834    IF (ALLOCATED(eff_temp_beetle_d))DEALLOCATE(eff_temp_beetle_d)
6835    IF (ALLOCATED(diapause_thres_daylength))DEALLOCATE(diapause_thres_daylength)
6836    IF (ALLOCATED(wght_sirdi_a)) DEALLOCATE(wght_sirdi_a)
6837    IF (ALLOCATED(wght_sirdi_b)) DEALLOCATE(wght_sirdi_b)
6838    IF (ALLOCATED(wght_sid)) DEALLOCATE(wght_sid)
6839    IF (ALLOCATED(wght_sis)) DEALLOCATE(wght_sis)
6840    IF (ALLOCATED(streamlining_c_leaf)) DEALLOCATE(streamlining_c_leaf)
6841    IF (ALLOCATED(streamlining_c_leafless)) DEALLOCATE(streamlining_c_leafless)
6842    IF (ALLOCATED(streamlining_n_leaf)) DEALLOCATE(streamlining_n_leaf)
6843    IF (ALLOCATED(streamlining_n_leafless)) DEALLOCATE(streamlining_n_leafless)
6844    IF (ALLOCATED(modulus_rupture)) DEALLOCATE(modulus_rupture)
6845    IF (ALLOCATED(f_knot)) DEALLOCATE(f_knot)
6846    IF (ALLOCATED(overturning_free_draining_shallow)) DEALLOCATE(overturning_free_draining_shallow)
6847    IF (ALLOCATED(overturning_free_draining_shallow_leafless)) DEALLOCATE(overturning_free_draining_shallow_leafless)
6848    IF (ALLOCATED(overturning_free_draining_deep)) DEALLOCATE(overturning_free_draining_deep)
6849    IF (ALLOCATED(overturning_free_draining_deep_leafless)) DEALLOCATE(overturning_free_draining_deep_leafless)
6850    IF (ALLOCATED(overturning_free_draining_average)) DEALLOCATE(overturning_free_draining_average)
6851    IF (ALLOCATED(overturning_free_draining_average_leafless)) DEALLOCATE(overturning_free_draining_average_leafless)
6852    IF (ALLOCATED(overturning_gleyed_shallow)) DEALLOCATE(overturning_gleyed_shallow)
6853    IF (ALLOCATED(overturning_gleyed_shallow_leafless)) DEALLOCATE(overturning_gleyed_shallow_leafless)
6854    IF (ALLOCATED(overturning_gleyed_deep)) DEALLOCATE(overturning_gleyed_deep)
6855    IF (ALLOCATED(overturning_gleyed_deep_leafless)) DEALLOCATE(overturning_gleyed_deep_leafless)
6856    IF (ALLOCATED(overturning_gleyed_average)) DEALLOCATE(overturning_gleyed_average)
6857    IF (ALLOCATED(overturning_gleyed_average_leafless)) DEALLOCATE(overturning_gleyed_average_leafless)
6858    IF (ALLOCATED(overturning_peaty_shallow)) DEALLOCATE(overturning_peaty_shallow)
6859    IF (ALLOCATED(overturning_peaty_shallow_leafless)) DEALLOCATE(overturning_peaty_shallow_leafless)
6860    IF (ALLOCATED(overturning_peaty_deep)) DEALLOCATE(overturning_peaty_deep)
6861    IF (ALLOCATED(overturning_peaty_deep_leafless)) DEALLOCATE(overturning_peaty_deep_leafless)
6862    IF (ALLOCATED(overturning_peaty_average)) DEALLOCATE(overturning_peaty_average)
6863    IF (ALLOCATED(overturning_peaty_average_leafless)) DEALLOCATE(overturning_peaty_average_leafless)
6864    IF (ALLOCATED(overturning_peat_shallow)) DEALLOCATE(overturning_peat_shallow)
6865    IF (ALLOCATED(overturning_peat_shallow_leafless)) DEALLOCATE(overturning_peat_shallow_leafless)
6866    IF (ALLOCATED(overturning_peat_deep)) DEALLOCATE(overturning_peat_deep)
6867    IF (ALLOCATED(overturning_peat_deep_leafless)) DEALLOCATE(overturning_peat_deep_leafless)
6868    IF (ALLOCATED(overturning_peat_average)) DEALLOCATE(overturning_peat_average)
6869    IF (ALLOCATED(overturning_peat_average_leafless)) DEALLOCATE(overturning_peat_average_leafless)
6870    IF (ALLOCATED(max_damage_further)) DEALLOCATE(max_damage_further)
6871    IF (ALLOCATED(max_damage_closer)) DEALLOCATE(max_damage_closer)
6872    IF (ALLOCATED(sfactor_further)) DEALLOCATE(sfactor_further)
6873    IF (ALLOCATED(sfactor_closer)) DEALLOCATE(sfactor_closer)
6874    IF (ALLOCATED(green_density)) DEALLOCATE(green_density)
6875    IF (ALLOCATED(maint_resp_slope)) DEALLOCATE(maint_resp_slope) 
6876    IF (ALLOCATED(maint_resp_slope_c)) DEALLOCATE(maint_resp_slope_c) 
6877    IF (ALLOCATED(maint_resp_slope_b)) DEALLOCATE(maint_resp_slope_b) 
6878    IF (ALLOCATED(maint_resp_slope_a)) DEALLOCATE(maint_resp_slope_a) 
6879
6880  END SUBROUTINE pft_parameters_clear
6881
6882END MODULE pft_parameters
Note: See TracBrowser for help on using the repository browser.