source: branches/ORCHIDEE_2_2/ORCHIDEE/src_parameters/pft_parameters.f90 @ 6289

Last change on this file since 6289 was 5461, checked in by josefine.ghattas, 6 years ago

Remove option STOMATE_OK_CO2 and subroutine diffuco_trans. Previous ok_co2=TRUE is now the only case. See ticket #431. The model stops if STOMATE_OK_CO2=F is in the run.def.

  • Property svn:keywords set to Date Revision
File size: 132.7 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    ! PFT global
94    !
95
96    IF(l_first_pft_parameters) THEN
97
98       !! 1. First time step
99       IF(printlev>=3) THEN
100          WRITE(numout,*) 'l_first_pft_parameters :we read the parameters from the def files'
101       ENDIF
102
103       !! 2. Memory allocation for the pfts-parameters
104       CALL pft_parameters_alloc()
105
106       !! 3. Correspondance table
107
108       !! 3.1 Initialisation of the correspondance table
109       !! Initialisation of the correspondance table
110       IF (nvm == nvmc) THEN
111          pft_to_mtc = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /)
112       ELSE
113          pft_to_mtc(:) = undef_int
114       ENDIF !(nvm  == nvmc)
115
116       !! 3.2 Reading of the conrrespondance table in the .def file
117       !
118       !Config Key   = PFT_TO_MTC
119       !Config Desc  = correspondance array linking a PFT to MTC
120       !Config if    = OK_SECHIBA or OK_STOMATE
121       !Config Def   = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
122       !Config Help  =
123       !Config Units = [-]
124       CALL getin_p('PFT_TO_MTC',pft_to_mtc)
125
126       !! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array
127       !!     If the configuration is wrong, send a error message to the user.
128       IF(nvm /= nvmc ) THEN
129          !
130          IF(pft_to_mtc(1) == undef_int) THEN
131             STOP ' The array PFT_TO_MTC is empty : we stop'
132          ENDIF !(pft_to_mtc(1) == undef_int)
133          !
134       ENDIF !(nvm /= nvmc )
135
136       !! 3.4 Some error messages
137
138       !! 3.4.1 What happened if pft_to_mtc(j) > nvmc or pft_to_mtc(j) <=0 (if the mtc doesn't exist)?
139       DO j = 1, nvm ! Loop over # PFTs 
140          !
141          IF( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) ) THEN
142             WRITE(numout,*) 'the metaclass chosen does not exist'
143             STOP 'we stop reading pft_to_mtc'
144          ENDIF !( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) )
145          !
146       ENDDO  ! Loop over # PFTs 
147
148
149       !! 3.4.2 Check if pft_to_mtc(1) = 1
150       IF(pft_to_mtc(1) /= 1) THEN
151          !
152          WRITE(numout,*) 'the first pft has to be the bare soil'
153          STOP 'we stop reading next values of pft_to_mtc'
154          !
155       ELSE
156          !
157          DO j = 2,nvm ! Loop over # PFTs different from bare soil
158             !
159             IF(pft_to_mtc(j) == 1) THEN
160                WRITE(numout,*) 'only pft_to_mtc(1) has to be the bare soil'
161                STOP 'we stop reading pft_to_mtc'
162             ENDIF ! (pft_to_mtc(j) == 1)
163             !
164          ENDDO ! Loop over # PFTs different from bare soil
165          !
166       ENDIF !(pft_to_mtc(1) /= 1)
167
168
169       !! 4.Initialisation of the pfts-parameters
170       CALL pft_parameters_init()
171
172       !! 5. Useful data
173
174       !! 5.1 Read the name of the PFTs given by the user
175       !
176       !Config Key   = PFT_NAME
177       !Config Desc  = Name of a PFT
178       !Config if    = OK_SECHIBA or OK_STOMATE
179       !Config Def   = bare ground, tropical broad-leaved evergreen, tropical broad-leaved raingreen,
180       !Config         temperate needleleaf evergreen, temperate broad-leaved evergreen temperate broad-leaved summergreen,
181       !Config         boreal needleleaf evergreen, boreal broad-leaved summergreen, boreal needleleaf summergreen,
182       !Config         C3 grass, C4 grass, C3 agriculture, C4 agriculture   
183       !Config Help  = the user can name the new PFTs he/she introducing for new species
184       !Config Units = [-]
185       CALL getin_p('PFT_NAME',pft_name)
186
187       !! 5.2 A useful message to the user: correspondance between the number of the pft
188       !! and the name of the associated mtc
189       IF (printlev >=1 ) THEN
190          WRITE(numout,*) ''
191          DO j = 2,nvm ! Loop over # PFTs
192             WRITE(numout,*) 'The PFT',j, 'called ', trim(PFT_name(j)),' corresponds to the MTC : ',trim(MTC_name(pft_to_mtc(j)))
193          END DO
194          WRITE(numout,*) ''
195       END IF
196
197
198       !! 6. End message
199       IF (printlev>=3) WRITE(numout,*) 'pft_parameters_done'
200
201       !! 8. Reset flag
202       l_first_pft_parameters = .FALSE.
203
204    ELSE
205
206       RETURN
207
208    ENDIF !(l_first_pft_parameters)
209
210  END SUBROUTINE pft_parameters_main
211
212
213!! ================================================================================================================================
214!! SUBROUTINE   : pft_parameters_init
215!!
216!>\BRIEF          This subroutine initializes all the pft parameters by the default values
217!! of the corresponding metaclasse.
218!!
219!! DESCRIPTION  : This subroutine is called after the reading of the number of PFTS and the correspondence
220!!                table defined by the user in the configuration files. \n
221!!                With the correspondence table, the subroutine can search the default values for the parameter
222!!                even if the PFTs are classified in a random order (except bare soil). \n
223!!                With the correspondence table, the subroutine can initialize the pft parameters in function
224!!                of the flags activated (ok_sechiba, ok_stomate, routing,...).\n
225!!
226!! RECENT CHANGE(S): Didier Solyga : Simplified PFT loops : use vector notation.
227!!
228!! MAIN OUTPUT VARIABLE(S): None
229!!
230!! REFERENCE(S) : None
231!!
232!! FLOWCHART    : None
233!! \n
234!_ ================================================================================================================================
235
236  SUBROUTINE pft_parameters_init()
237
238    IMPLICIT NONE
239
240    !! 0. Variables and parameters declaration
241
242    !! 0.1 Input variables
243
244    !! 0.4 Local variables
245
246    INTEGER(i_std)                :: jv            !! Index (unitless)
247    !_ ================================================================================================================================
248
249    !
250    ! 1. Correspondance between the PFTs values and thes MTCs values
251    !
252
253
254    ! 1.1 For parameters used anytime
255
256    PFT_name(:) = MTC_name(pft_to_mtc(:))
257    !
258    ! Vegetation structure
259    !
260    veget_ori_fixed_test_1(:) = veget_ori_fixed_mtc(pft_to_mtc(:))
261    llaimax(:) = llaimax_mtc(pft_to_mtc(:))
262    llaimin(:) = llaimin_mtc(pft_to_mtc(:))
263    height_presc(:) = height_presc_mtc(pft_to_mtc(:))
264    z0_over_height(:) = z0_over_height_mtc(pft_to_mtc(:))
265    ratio_z0m_z0h(:) = ratio_z0m_z0h_mtc(pft_to_mtc(:))
266    type_of_lai(:) = type_of_lai_mtc(pft_to_mtc(:))
267    natural(:) = natural_mtc(pft_to_mtc(:))
268    !
269    ! Water - sechiba
270    !
271    IF (zmaxh == 2.0) THEN
272       IF (printlev>=2) WRITE(numout,*)'Initialize humcst using reference values for 2m soil depth'
273       humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
274    ELSE IF (zmaxh == 4.0) THEN
275       IF (printlev>=2) WRITE(numout,*)'Initialize humcst using reference values for 4m soil depth'
276       humcste(:) = humcste_ref4m(pft_to_mtc(:))  ! values for 4m soil depth
277    ELSE
278       IF (printlev>=2) WRITE(numout,*)'Note that humcste is initialized with values for 2m soil depth bur zmaxh=', zmaxh
279       humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
280    END IF
281    !
282    ! Soil - vegetation
283    !
284    pref_soil_veg(:) = pref_soil_veg_mtc(pft_to_mtc(:))
285    !
286    ! Photosynthesis
287    !
288    is_c4(:) = is_c4_mtc(pft_to_mtc(:))
289    vcmax_fix(:) = vcmax_fix_mtc(pft_to_mtc(:))
290    downregulation_co2_coeff(:) = downregulation_co2_coeff_mtc(pft_to_mtc(:))
291    E_KmC(:)      = E_KmC_mtc(pft_to_mtc(:))
292    E_KmO(:)      = E_KmO_mtc(pft_to_mtc(:))
293    E_Sco(:)      = E_Sco_mtc(pft_to_mtc(:))
294    E_gamma_star(:) = E_gamma_star_mtc(pft_to_mtc(:))
295    E_Vcmax(:)    = E_Vcmax_mtc(pft_to_mtc(:))
296    E_Jmax(:)     = E_Jmax_mtc(pft_to_mtc(:))
297    aSV(:)        = aSV_mtc(pft_to_mtc(:))
298    bSV(:)        = bSV_mtc(pft_to_mtc(:))
299    tphoto_min(:) = tphoto_min_mtc(pft_to_mtc(:))
300    tphoto_max(:) = tphoto_max_mtc(pft_to_mtc(:))
301    aSJ(:)        = aSJ_mtc(pft_to_mtc(:))
302    bSJ(:)        = bSJ_mtc(pft_to_mtc(:))
303    D_Vcmax(:)     = D_Vcmax_mtc(pft_to_mtc(:))
304    D_Jmax(:)     = D_Jmax_mtc(pft_to_mtc(:))
305    E_gm(:)       = E_gm_mtc(pft_to_mtc(:)) 
306    S_gm(:)       = S_gm_mtc(pft_to_mtc(:)) 
307    D_gm(:)       = D_gm_mtc(pft_to_mtc(:)) 
308    E_Rd(:)       = E_Rd_mtc(pft_to_mtc(:))
309    Vcmax25(:)    = Vcmax25_mtc(pft_to_mtc(:))
310    arJV(:)       = arJV_mtc(pft_to_mtc(:))
311    brJV(:)       = brJV_mtc(pft_to_mtc(:))
312    KmC25(:)      = KmC25_mtc(pft_to_mtc(:))
313    KmO25(:)      = KmO25_mtc(pft_to_mtc(:))
314    Sco25(:)      = Sco25_mtc(pft_to_mtc(:))
315    gm25(:)       = gm25_mtc(pft_to_mtc(:)) 
316    gamma_star25(:)  = gamma_star25_mtc(pft_to_mtc(:))
317    a1(:)         = a1_mtc(pft_to_mtc(:))
318    b1(:)         = b1_mtc(pft_to_mtc(:))
319    g0(:)         = g0_mtc(pft_to_mtc(:))
320    h_protons(:)  = h_protons_mtc(pft_to_mtc(:))
321    fpsir(:)      = fpsir_mtc(pft_to_mtc(:))
322    fQ(:)         = fQ_mtc(pft_to_mtc(:))     
323    fpseudo(:)    = fpseudo_mtc(pft_to_mtc(:))   
324    kp(:)         = kp_mtc(pft_to_mtc(:))
325    alpha(:)      = alpha_mtc(pft_to_mtc(:))
326    gbs(:)        = gbs_mtc(pft_to_mtc(:))
327    theta(:)      = theta_mtc(pft_to_mtc(:))       
328    alpha_LL(:)   = alpha_LL_mtc(pft_to_mtc(:))
329    stress_vcmax(:) = stress_vcmax_mtc(pft_to_mtc(:))
330    stress_gs(:)    = stress_gs_mtc(pft_to_mtc(:))
331    stress_gm(:)    = stress_gm_mtc(pft_to_mtc(:))
332    ext_coeff(:) = ext_coeff_mtc(pft_to_mtc(:))
333    ext_coeff_vegetfrac(:) = ext_coeff_vegetfrac_mtc(pft_to_mtc(:))
334    !
335    !! Define labels from physiologic characteristics
336    !
337    leaf_tab(:) = leaf_tab_mtc(pft_to_mtc(:)) 
338    pheno_model(:) = pheno_model_mtc(pft_to_mtc(:))   
339    !
340    is_tree(:) = .FALSE.
341    DO jv = 1,nvm
342       IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
343    END DO
344    !
345    is_deciduous(:) = .FALSE.
346    DO jv = 1,nvm
347       IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
348    END DO
349    !
350    is_evergreen(:) = .FALSE.
351    DO jv = 1,nvm
352       IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
353    END DO
354    !
355    is_needleleaf(:) = .FALSE.
356    DO jv = 1,nvm
357       IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
358    END DO
359
360
361    ! 1.2 For sechiba parameters
362
363    IF (ok_sechiba) THEN
364       !
365       ! Vegetation structure - sechiba
366       !
367       rveg_pft(:) = rveg_mtc(pft_to_mtc(:))
368       !
369       ! Evapotranspiration -  sechiba
370       !
371       rstruct_const(:) = rstruct_const_mtc(pft_to_mtc(:))
372       kzero(:) = kzero_mtc(pft_to_mtc(:))
373       !
374       ! Water - sechiba
375       !
376       wmax_veg(:) = wmax_veg_mtc(pft_to_mtc(:))
377       IF ( OFF_LINE_MODE ) THEN
378          throughfall_by_pft(:) = 0.
379       ELSE
380          throughfall_by_pft(:) = throughfall_by_mtc(pft_to_mtc(:))
381       ENDIF
382       !
383       ! Albedo - sechiba
384       !
385       snowa_aged_vis(:) = snowa_aged_vis_mtc(pft_to_mtc(:))
386       snowa_aged_nir(:) = snowa_aged_nir_mtc(pft_to_mtc(:))
387       snowa_dec_vis(:) = snowa_dec_vis_mtc(pft_to_mtc(:)) 
388       snowa_dec_nir(:) = snowa_dec_nir_mtc(pft_to_mtc(:)) 
389       alb_leaf_vis(:) = alb_leaf_vis_mtc(pft_to_mtc(:)) 
390       alb_leaf_nir(:) = alb_leaf_nir_mtc(pft_to_mtc(:))
391       !-
392    ENDIF !(ok_sechiba)
393
394    ! 1.3 For BVOC parameters
395
396    IF (ok_bvoc) THEN
397       !
398       ! Biogenic Volatile Organic Compounds
399       !
400       em_factor_isoprene(:) = em_factor_isoprene_mtc(pft_to_mtc(:))
401       em_factor_monoterpene(:) = em_factor_monoterpene_mtc(pft_to_mtc(:))
402       LDF_mono = LDF_mono_mtc 
403       LDF_sesq = LDF_sesq_mtc 
404       LDF_meth = LDF_meth_mtc 
405       LDF_acet = LDF_acet_mtc 
406
407       em_factor_apinene(:) = em_factor_apinene_mtc(pft_to_mtc(:))
408       em_factor_bpinene(:) = em_factor_bpinene_mtc(pft_to_mtc(:))
409       em_factor_limonene(:) = em_factor_limonene_mtc(pft_to_mtc(:))
410       em_factor_myrcene(:) = em_factor_myrcene_mtc(pft_to_mtc(:))
411       em_factor_sabinene(:) = em_factor_sabinene_mtc(pft_to_mtc(:))
412       em_factor_camphene(:) = em_factor_camphene_mtc(pft_to_mtc(:))
413       em_factor_3carene(:) = em_factor_3carene_mtc(pft_to_mtc(:))
414       em_factor_tbocimene(:) = em_factor_tbocimene_mtc(pft_to_mtc(:))
415       em_factor_othermonot(:) = em_factor_othermonot_mtc(pft_to_mtc(:))
416       em_factor_sesquiterp(:) = em_factor_sesquiterp_mtc(pft_to_mtc(:))
417
418       beta_mono = beta_mono_mtc
419       beta_sesq = beta_sesq_mtc
420       beta_meth = beta_meth_mtc
421       beta_acet = beta_acet_mtc
422       beta_oxyVOC = beta_oxyVOC_mtc
423
424       em_factor_ORVOC(:) = em_factor_ORVOC_mtc(pft_to_mtc(:)) 
425       em_factor_OVOC(:) = em_factor_OVOC_mtc(pft_to_mtc(:))
426       em_factor_MBO(:) = em_factor_MBO_mtc(pft_to_mtc(:))
427       em_factor_methanol(:) = em_factor_methanol_mtc(pft_to_mtc(:))
428       em_factor_acetone(:) = em_factor_acetone_mtc(pft_to_mtc(:)) 
429       em_factor_acetal(:) = em_factor_acetal_mtc(pft_to_mtc(:))
430       em_factor_formal(:) = em_factor_formal_mtc(pft_to_mtc(:))
431       em_factor_acetic(:) = em_factor_acetic_mtc(pft_to_mtc(:))
432       em_factor_formic(:) = em_factor_formic_mtc(pft_to_mtc(:))
433       em_factor_no_wet(:) = em_factor_no_wet_mtc(pft_to_mtc(:))
434       em_factor_no_dry(:) = em_factor_no_dry_mtc(pft_to_mtc(:))
435       Larch(:) = Larch_mtc(pft_to_mtc(:)) 
436       !-
437    ENDIF !(ok_bvoc)
438
439    ! 1.4 For stomate parameters
440
441    IF (ok_stomate) THEN
442       !
443       ! Vegetation structure - stomate
444       !
445       sla(:) = sla_mtc(pft_to_mtc(:))
446       availability_fact(:) = availability_fact_mtc(pft_to_mtc(:))
447       !
448       ! Allocation - stomate
449       !
450       R0(:) = R0_mtc(pft_to_mtc(:)) 
451       S0(:) = S0_mtc(pft_to_mtc(:)) 
452       !
453       ! Respiration - stomate
454       !
455       frac_growthresp(:) = frac_growthresp_mtc(pft_to_mtc(:)) 
456       maint_resp_slope_c(:) = maint_resp_slope_c_mtc(pft_to_mtc(:))               
457       maint_resp_slope_b(:) = maint_resp_slope_b_mtc(pft_to_mtc(:))
458       maint_resp_slope_a(:) = maint_resp_slope_a_mtc(pft_to_mtc(:))
459       cm_zero_leaf(:) = cm_zero_leaf_mtc(pft_to_mtc(:))
460       cm_zero_sapabove(:) = cm_zero_sapabove_mtc(pft_to_mtc(:))
461       cm_zero_sapbelow(:) = cm_zero_sapbelow_mtc(pft_to_mtc(:)) 
462       cm_zero_heartabove(:) = cm_zero_heartabove_mtc(pft_to_mtc(:)) 
463       cm_zero_heartbelow(:) = cm_zero_heartbelow_mtc(pft_to_mtc(:))
464       cm_zero_root(:) = cm_zero_root_mtc(pft_to_mtc(:))
465       cm_zero_fruit(:) = cm_zero_fruit_mtc(pft_to_mtc(:))
466       cm_zero_carbres(:) = cm_zero_carbres_mtc(pft_to_mtc(:))
467       !
468       ! Fire - stomate
469       !
470       flam(:) = flam_mtc(pft_to_mtc(:))
471       resist(:) = resist_mtc(pft_to_mtc(:))
472       !
473       ! Flux - LUC
474       !
475       coeff_lcchange_1(:) = coeff_lcchange_1_mtc(pft_to_mtc(:))
476       coeff_lcchange_10(:) = coeff_lcchange_10_mtc(pft_to_mtc(:))
477       coeff_lcchange_100(:) = coeff_lcchange_100_mtc(pft_to_mtc(:))
478       !
479       ! Phenology
480       !
481       !
482       ! 1. Stomate
483       !
484       lai_max_to_happy(:) = lai_max_to_happy_mtc(pft_to_mtc(:)) 
485       lai_max(:) = lai_max_mtc(pft_to_mtc(:))
486       pheno_type(:) = pheno_type_mtc(pft_to_mtc(:))
487       !
488       ! 2. Leaf Onset
489       !
490       pheno_gdd_crit_c(:) = pheno_gdd_crit_c_mtc(pft_to_mtc(:))
491       pheno_gdd_crit_b(:) = pheno_gdd_crit_b_mtc(pft_to_mtc(:))         
492       pheno_gdd_crit_a(:) = pheno_gdd_crit_a_mtc(pft_to_mtc(:))
493       pheno_moigdd_t_crit(:) = pheno_moigdd_t_crit_mtc(pft_to_mtc(:))
494       ngd_crit(:) =  ngd_crit_mtc(pft_to_mtc(:))
495       ncdgdd_temp(:) = ncdgdd_temp_mtc(pft_to_mtc(:)) 
496       hum_frac(:) = hum_frac_mtc(pft_to_mtc(:))
497       hum_min_time(:) = hum_min_time_mtc(pft_to_mtc(:))
498       tau_sap(:) = tau_sap_mtc(pft_to_mtc(:))
499       tau_leafinit(:) = tau_leafinit_mtc(pft_to_mtc(:)) 
500       tau_fruit(:) = tau_fruit_mtc(pft_to_mtc(:))
501       ecureuil(:) = ecureuil_mtc(pft_to_mtc(:))
502       alloc_min(:) = alloc_min_mtc(pft_to_mtc(:))
503       alloc_max(:) = alloc_max_mtc(pft_to_mtc(:))
504       demi_alloc(:) = demi_alloc_mtc(pft_to_mtc(:))
505       leaflife_tab(:) = leaflife_mtc(pft_to_mtc(:))
506       !
507       ! 3. Senescence
508       !
509       leaffall(:) = leaffall_mtc(pft_to_mtc(:))
510       leafagecrit(:) = leafagecrit_mtc(pft_to_mtc(:))
511       senescence_type(:) = senescence_type_mtc(pft_to_mtc(:)) 
512       senescence_hum(:) = senescence_hum_mtc(pft_to_mtc(:)) 
513       nosenescence_hum(:) = nosenescence_hum_mtc(pft_to_mtc(:)) 
514       max_turnover_time(:) = max_turnover_time_mtc(pft_to_mtc(:))
515       min_turnover_time(:) = min_turnover_time_mtc(pft_to_mtc(:))
516       min_leaf_age_for_senescence(:) = min_leaf_age_for_senescence_mtc(pft_to_mtc(:))
517       senescence_temp_c(:) = senescence_temp_c_mtc(pft_to_mtc(:))
518       senescence_temp_b(:) = senescence_temp_b_mtc(pft_to_mtc(:))
519       senescence_temp_a(:) = senescence_temp_a_mtc(pft_to_mtc(:))
520       gdd_senescence(:) = gdd_senescence_mtc(pft_to_mtc(:))
521       always_init(:) = always_init_mtc(pft_to_mtc(:))
522       !
523       ! DGVM
524       !
525       residence_time(:) = residence_time_mtc(pft_to_mtc(:))
526       tmin_crit(:) = tmin_crit_mtc(pft_to_mtc(:))
527       tcm_crit(:) = tcm_crit_mtc(pft_to_mtc(:))
528       !-
529    ENDIF !(ok_stomate)
530
531  END SUBROUTINE pft_parameters_init
532
533
534!! ================================================================================================================================
535!! SUBROUTINE   : pft_parameters_alloc
536!!
537!>\BRIEF         This subroutine allocates memory needed for the PFT parameters
538!! in function  of the flags activated. 
539!!
540!! DESCRIPTION  : None
541!!
542!! RECENT CHANGE(S): None
543!!
544!! MAIN OUTPUT VARIABLE(S): None
545!!
546!! REFERENCE(S) : None
547!!
548!! FLOWCHART    : None
549!! \n
550!_ ================================================================================================================================
551
552  SUBROUTINE pft_parameters_alloc()
553
554    IMPLICIT NONE
555
556    !! 0. Variables and parameters declaration
557
558    !! 0.1 Input variables
559
560    !! 0.4 Local variables
561
562    LOGICAL :: l_error                             !! Diagnostic boolean for error allocation (true/false)
563    INTEGER :: ier                                 !! Return value for memory allocation (0-N, unitless)
564
565    !_ ================================================================================================================================
566
567
568    !
569    ! 1. Parameters used anytime
570    !
571
572    l_error = .FALSE.
573
574    ALLOCATE(pft_to_mtc(nvm),stat=ier)
575    l_error = l_error .OR. (ier /= 0)
576    IF (l_error) THEN
577       WRITE(numout,*) ' Memory allocation error for pft_to_mtc. We stop. We need nvm words = ',nvm
578       STOP 'pft_parameters_alloc'
579    END IF
580
581    ALLOCATE(PFT_name(nvm),stat=ier)
582    l_error = l_error .OR. (ier /= 0)
583    IF (l_error) THEN
584       WRITE(numout,*) ' Memory allocation error for PFT_name. We stop. We need nvm words = ',nvm
585       STOP 'pft_parameters_alloc'
586    END IF
587
588    ALLOCATE(height_presc(nvm),stat=ier)
589    l_error = l_error .OR. (ier /= 0)
590    IF (l_error) THEN
591       WRITE(numout,*) ' Memory allocation error for height_presc. We stop. We need nvm words = ',nvm
592       STOP 'pft_parameters_alloc'
593    END IF
594
595    ALLOCATE(z0_over_height(nvm),stat=ier)
596    l_error = l_error .OR. (ier /= 0)
597    IF (l_error) THEN
598       WRITE(numout,*) ' Memory allocation error for z0_over_height. We stop. We need nvm words = ',nvm
599       STOP 'pft_parameters_alloc'
600    END IF
601
602    ALLOCATE(ratio_z0m_z0h(nvm),stat=ier)
603    l_error = l_error .OR. (ier /= 0)
604    IF (l_error) THEN
605       WRITE(numout,*) ' Memory allocation error for ratio_z0m_z0h. We stop. We need nvm words = ',nvm
606       STOP 'pft_parameters_alloc'
607    END IF
608
609    ALLOCATE(is_tree(nvm),stat=ier)
610    l_error = l_error .OR. (ier /= 0)
611    IF (l_error) THEN
612       WRITE(numout,*) ' Memory allocation error for is_tree. We stop. We need nvm words = ',nvm
613       STOP 'pft_parameters_alloc'
614    END IF
615
616    ALLOCATE(natural(nvm),stat=ier)
617    l_error = l_error .OR. (ier /= 0)
618    IF (l_error) THEN
619       WRITE(numout,*) ' Memory allocation error for natural. We stop. We need nvm words = ',nvm
620       STOP 'pft_parameters_alloc'
621    END IF
622
623    ALLOCATE(is_c4(nvm),stat=ier)
624    l_error = l_error .OR. (ier /= 0)
625    IF (l_error) THEN
626       WRITE(numout,*) ' Memory allocation error for is_c4. We stop. We need nvm words = ',nvm
627       STOP 'pft_parameters_alloc'
628    END IF
629
630    ALLOCATE(humcste(nvm),stat=ier)
631    l_error = l_error .OR. (ier /= 0)
632    IF (l_error) THEN
633       WRITE(numout,*) ' Memory allocation error for humcste. We stop. We need nvm words = ',nvm
634       STOP 'pft_parameters_alloc'
635    END IF
636
637    ALLOCATE(downregulation_co2_coeff(nvm),stat=ier)
638    l_error = l_error .OR. (ier /= 0)
639    IF (l_error) THEN
640       WRITE(numout,*) ' Memory allocation error for downregulation_co2_coeff. We stop. We need nvm words = ',nvm
641       STOP 'pft_parameters_alloc'
642    END IF
643
644    ALLOCATE(E_KmC(nvm),stat=ier)
645    l_error = l_error .OR. (ier /= 0)
646    IF (l_error) THEN
647       WRITE(numout,*) ' Memory allocation error for E_KmC. We stop. We need nvm words = ',nvm
648       STOP 'pft_parameters_alloc'
649    END IF
650
651    ALLOCATE(E_KmO(nvm),stat=ier)
652    l_error = l_error .OR. (ier /= 0)
653    IF (l_error) THEN
654       WRITE(numout,*) ' Memory allocation error for E_KmO. We stop. We need nvm words = ',nvm
655       STOP 'pft_parameters_alloc'
656    END IF
657
658    ALLOCATE(E_Sco(nvm),stat=ier)
659    l_error = l_error .OR. (ier /= 0)
660    IF (l_error) THEN
661       WRITE(numout,*) ' Memory allocation error for E_Sco. We stop. We need nvm words = ',nvm
662       STOP 'pft_parameters_alloc'
663    END IF
664
665    ALLOCATE(E_gamma_star(nvm),stat=ier)
666    l_error = l_error .OR. (ier /= 0)
667    IF (l_error) THEN
668       WRITE(numout,*) ' Memory allocation error for E_gamma_star. We stop. We need nvm words = ',nvm
669       STOP 'pft_parameters_alloc'
670    END IF
671
672    ALLOCATE(E_vcmax(nvm),stat=ier)
673    l_error = l_error .OR. (ier /= 0)
674    IF (l_error) THEN
675       WRITE(numout,*) ' Memory allocation error for E_Vcmax. We stop. We need nvm words = ',nvm
676       STOP 'pft_parameters_alloc'
677    END IF
678
679    ALLOCATE(E_Jmax(nvm),stat=ier)
680    l_error = l_error .OR. (ier /= 0)
681    IF (l_error) THEN
682       WRITE(numout,*) ' Memory allocation error for E_Jmax. We stop. We need nvm words = ',nvm
683       STOP 'pft_parameters_alloc'
684    END IF
685
686    ALLOCATE(aSV(nvm),stat=ier)
687    l_error = l_error .OR. (ier /= 0)
688    IF (l_error) THEN
689       WRITE(numout,*) ' Memory allocation error for aSV. We stop. We need nvm words = ',nvm
690       STOP 'pft_parameters_alloc'
691    END IF
692
693    ALLOCATE(bSV(nvm),stat=ier)
694    l_error = l_error .OR. (ier /= 0)
695    IF (l_error) THEN
696       WRITE(numout,*) ' Memory allocation error for bSV. We stop. We need nvm words = ',nvm
697       STOP 'pft_parameters_alloc'
698    END IF
699
700    ALLOCATE(tphoto_min(nvm),stat=ier)
701    l_error = l_error .OR. (ier /= 0)
702    IF (l_error) THEN
703       WRITE(numout,*) ' Memory allocation error for tphoto_min. We stop. We need nvm words = ',nvm
704       STOP 'pft_parameters_alloc'
705    END IF
706
707    ALLOCATE(tphoto_max(nvm),stat=ier)
708    l_error = l_error .OR. (ier /= 0)
709    IF (l_error) THEN
710       WRITE(numout,*) ' Memory allocation error for tphoto_max. We stop. We need nvm words = ',nvm
711       STOP 'pft_parameters_alloc'
712    END IF
713
714    ALLOCATE(aSJ(nvm),stat=ier)
715    l_error = l_error .OR. (ier /= 0)
716    IF (l_error) THEN
717       WRITE(numout,*) ' Memory allocation error for aSJ. We stop. We need nvm words = ',nvm
718       STOP 'pft_parameters_alloc'
719    END IF
720
721    ALLOCATE(bSJ(nvm),stat=ier)
722    l_error = l_error .OR. (ier /= 0)
723    IF (l_error) THEN
724       WRITE(numout,*) ' Memory allocation error for bSJ. We stop. We need nvm words = ',nvm
725       STOP 'pft_parameters_alloc'
726    END IF
727
728    ALLOCATE(D_Vcmax(nvm),stat=ier)
729    l_error = l_error .OR. (ier /= 0)
730    IF (l_error) THEN
731       WRITE(numout,*) ' Memory allocation error for D_Vcmax. We stop. We need nvm words = ',nvm
732       STOP 'pft_parameters_alloc'
733    END IF
734
735    ALLOCATE(D_Jmax(nvm),stat=ier)
736    l_error = l_error .OR. (ier /= 0)
737    IF (l_error) THEN
738       WRITE(numout,*) ' Memory allocation error for D_Jmax. We stop. We need nvm words = ',nvm
739       STOP 'pft_parameters_alloc'
740    END IF
741
742    ALLOCATE(E_gm(nvm),stat=ier) 
743    l_error = l_error .OR. (ier /= 0) 
744    IF (l_error) THEN
745       WRITE(numout,*) ' Memory allocation error for E_gm. We stop. We need nvm words = ',nvm 
746       STOP 'pft_parameters_alloc' 
747    END IF
748   
749    ALLOCATE(S_gm(nvm),stat=ier) 
750    l_error = l_error .OR. (ier /= 0) 
751    IF (l_error) THEN
752       WRITE(numout,*) ' Memory allocation error for S_gm. We stop. We need nvm words = ',nvm 
753       STOP 'pft_parameters_alloc' 
754    END IF
755   
756    ALLOCATE(D_gm(nvm),stat=ier) 
757    l_error = l_error .OR. (ier /= 0) 
758    IF (l_error) THEN
759       WRITE(numout,*) ' Memory allocation error for D_gm. We stop. We need nvm words = ',nvm 
760       STOP 'pft_parameters_alloc' 
761    END IF
762   
763    ALLOCATE(E_Rd(nvm),stat=ier)
764    l_error = l_error .OR. (ier /= 0)
765    IF (l_error) THEN
766       WRITE(numout,*) ' Memory allocation error for E_Rd. We stop. We need nvm words = ',nvm
767       STOP 'pft_parameters_alloc'
768    END IF
769
770    ALLOCATE(Vcmax25(nvm),stat=ier)
771    l_error = l_error .OR. (ier /= 0)
772    IF (l_error) THEN
773       WRITE(numout,*) ' Memory allocation error for Vcmax25. We stop. We need nvm words = ',nvm
774       STOP 'pft_parameters_alloc'
775    END IF
776
777    ALLOCATE(arJV(nvm),stat=ier)
778    l_error = l_error .OR. (ier /= 0)
779    IF (l_error) THEN
780       WRITE(numout,*) ' Memory allocation error for arJV. We stop. We need nvm words = ',nvm
781       STOP 'pft_parameters_alloc'
782    END IF
783
784    ALLOCATE(brJV(nvm),stat=ier)
785    l_error = l_error .OR. (ier /= 0)
786    IF (l_error) THEN
787       WRITE(numout,*) ' Memory allocation error for brJV. We stop. We need nvm words = ',nvm
788       STOP 'pft_parameters_alloc'
789    END IF
790
791    ALLOCATE(KmC25(nvm),stat=ier)
792    l_error = l_error .OR. (ier /= 0)
793    IF (l_error) THEN
794       WRITE(numout,*) ' Memory allocation error for KmC25. We stop. We need nvm words = ',nvm
795       STOP 'pft_parameters_alloc'
796    END IF
797
798    ALLOCATE(KmO25(nvm),stat=ier)
799    l_error = l_error .OR. (ier /= 0)
800    IF (l_error) THEN
801       WRITE(numout,*) ' Memory allocation error for KmO25. We stop. We need nvm words = ',nvm
802       STOP 'pft_parameters_alloc'
803    END IF
804
805    ALLOCATE(Sco25(nvm),stat=ier)
806    l_error = l_error .OR. (ier /= 0)
807    IF (l_error) THEN
808       WRITE(numout,*) ' Memory allocation error for Sco25. We stop. We need nvm words = ',nvm
809       STOP 'pft_parameters_alloc'
810    END IF
811   
812    ALLOCATE(gm25(nvm),stat=ier) 
813    l_error = l_error .OR. (ier /= 0) 
814    IF (l_error) THEN
815       WRITE(numout,*) ' Memory allocation error for gm25. We stop. We need nvm words = ',nvm 
816       STOP 'pft_parameters_alloc' 
817    END IF
818
819    ALLOCATE(gamma_star25(nvm),stat=ier)
820    l_error = l_error .OR. (ier /= 0)
821    IF (l_error) THEN
822       WRITE(numout,*) ' Memory allocation error for gamma_star25. We stop. We need nvm words = ',nvm
823       STOP 'pft_parameters_alloc'
824    END IF
825
826    ALLOCATE(a1(nvm),stat=ier)
827    l_error = l_error .OR. (ier /= 0)
828    IF (l_error) THEN
829       WRITE(numout,*) ' Memory allocation error for a1. We stop. We need nvm words = ',nvm
830       STOP 'pft_parameters_alloc'
831    END IF
832
833    ALLOCATE(b1(nvm),stat=ier)
834    l_error = l_error .OR. (ier /= 0)
835    IF (l_error) THEN
836       WRITE(numout,*) ' Memory allocation error for b1. We stop. We need nvm words = ',nvm
837       STOP 'pft_parameters_alloc'
838    END IF
839
840    ALLOCATE(g0(nvm),stat=ier)
841    l_error = l_error .OR. (ier /= 0)
842    IF (l_error) THEN
843       WRITE(numout,*) ' Memory allocation error for g0. We stop. We need nvm words = ',nvm
844       STOP 'pft_parameters_alloc'
845    END IF
846
847    ALLOCATE(h_protons(nvm),stat=ier)
848    l_error = l_error .OR. (ier /= 0)
849    IF (l_error) THEN
850       WRITE(numout,*) ' Memory allocation error for h_protons. We stop. We need nvm words = ',nvm
851       STOP 'pft_parameters_alloc'
852    END IF
853
854    ALLOCATE(fpsir(nvm),stat=ier)
855    l_error = l_error .OR. (ier /= 0)
856    IF (l_error) THEN
857       WRITE(numout,*) ' Memory allocation error for fpsir. We stop. We need nvm words = ',nvm
858       STOP 'pft_parameters_alloc'
859    END IF
860
861    ALLOCATE(fQ(nvm),stat=ier)
862    l_error = l_error .OR. (ier /= 0)
863    IF (l_error) THEN
864       WRITE(numout,*) ' Memory allocation error for fQ. We stop. We need nvm words = ',nvm
865       STOP 'pft_parameters_alloc'
866    END IF
867
868    ALLOCATE(fpseudo(nvm),stat=ier)
869    l_error = l_error .OR. (ier /= 0)
870    IF (l_error) THEN
871       WRITE(numout,*) ' Memory allocation error for fpseudo. We stop. We need nvm words = ',nvm
872       STOP 'pft_parameters_alloc'
873    END IF
874
875    ALLOCATE(kp(nvm),stat=ier)
876    l_error = l_error .OR. (ier /= 0)
877    IF (l_error) THEN
878       WRITE(numout,*) ' Memory allocation error for kp. We stop. We need nvm words = ',nvm
879       STOP 'pft_parameters_alloc'
880    END IF
881
882    ALLOCATE(alpha(nvm),stat=ier)
883    l_error = l_error .OR. (ier /= 0)
884    IF (l_error) THEN
885       WRITE(numout,*) ' Memory allocation error for alpha. We stop. We need nvm words = ',nvm
886       STOP 'pft_parameters_alloc'
887    END IF
888
889    ALLOCATE(gbs(nvm),stat=ier)
890    l_error = l_error .OR. (ier /= 0)
891    IF (l_error) THEN
892       WRITE(numout,*) ' Memory allocation error for gbs. We stop. We need nvm words = ',nvm
893       STOP 'pft_parameters_alloc'
894    END IF
895
896    ALLOCATE(theta(nvm),stat=ier)
897    l_error = l_error .OR. (ier /= 0)
898    IF (l_error) THEN
899       WRITE(numout,*) ' Memory allocation error for theta. We stop. We need nvm words = ',nvm
900       STOP 'pft_parameters_alloc'
901    END IF
902
903    ALLOCATE(alpha_LL(nvm),stat=ier)
904    l_error = l_error .OR. (ier /= 0)
905    IF (l_error) THEN
906       WRITE(numout,*) ' Memory allocation error for alpha_LL. We stop. We need nvm words = ',nvm
907       STOP 'pft_parameters_alloc'
908    END IF
909
910    ALLOCATE(stress_vcmax(nvm),stat=ier)
911    l_error = l_error .OR. (ier /= 0)
912    IF (l_error) THEN
913       WRITE(numout,*) ' Memory allocation error for stress_vcmax. We stop. We need nvm words = ',nvm
914       STOP 'pft_parameters_alloc'
915    END IF
916   
917    ALLOCATE(stress_gs(nvm),stat=ier)
918    l_error = l_error .OR. (ier /= 0)
919    IF (l_error) THEN
920       WRITE(numout,*) ' Memory allocation error for stress_gs. We stop. We need nvm words = ',nvm
921       STOP 'pft_parameters_alloc'
922    END IF
923   
924    ALLOCATE(stress_gm(nvm),stat=ier)
925    l_error = l_error .OR. (ier /= 0)
926    IF (l_error) THEN
927       WRITE(numout,*) ' Memory allocation error for stress_gm. We stop. We need nvm words = ',nvm
928       STOP 'pft_parameters_alloc'
929    END IF
930
931    ALLOCATE(ext_coeff(nvm),stat=ier)
932    l_error = l_error .OR. (ier /= 0)
933    IF (l_error) THEN
934       WRITE(numout,*) ' Memory allocation error for ext_coeff. We stop. We need nvm words = ',nvm
935       STOP 'pft_parameters_alloc'
936    END IF
937
938    ALLOCATE(ext_coeff_vegetfrac(nvm),stat=ier)
939    l_error = l_error .OR. (ier /= 0)
940    IF (l_error) THEN
941       WRITE(numout,*) ' Memory allocation error for ext_coeff_vegetfrac. We stop. We need nvm words = ',nvm
942       STOP 'pft_parameters_alloc'
943    END IF
944
945    ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier)
946    l_error = l_error .OR. (ier /= 0)
947    IF (l_error) THEN
948       WRITE(numout,*) ' Memory allocation error for veget_ori_fixed_test_1. We stop. We need nvm words = ',nvm
949       STOP 'pft_parameters_alloc'
950    END IF
951
952    ALLOCATE(llaimax(nvm),stat=ier)
953    l_error = l_error .OR. (ier /= 0)
954    IF (l_error) THEN
955       WRITE(numout,*) ' Memory allocation error for llaimax. We stop. We need nvm words = ',nvm
956       STOP 'pft_parameters_alloc'
957    END IF
958
959    ALLOCATE(llaimin(nvm),stat=ier)
960    l_error = l_error .OR. (ier /= 0)
961    IF (l_error) THEN
962       WRITE(numout,*) ' Memory allocation error for llaimin. We stop. We need nvm words = ',nvm
963       STOP 'pft_parameters_alloc'
964    END IF
965
966    ALLOCATE(type_of_lai(nvm),stat=ier)
967    l_error = l_error .OR. (ier /= 0)
968    IF (l_error) THEN
969       WRITE(numout,*) ' Memory allocation error for type_of_lai. We stop. We need nvm words = ',nvm
970       STOP 'pft_parameters_alloc'
971    END IF
972
973    ALLOCATE(vcmax_fix(nvm),stat=ier)
974    l_error = l_error .OR. (ier /= 0)
975    IF (l_error) THEN
976       WRITE(numout,*) ' Memory allocation error for vcmax_fix. We stop. We need nvm words = ',nvm
977       STOP 'pft_parameters_alloc'
978    END IF
979
980    ALLOCATE(pref_soil_veg(nvm),stat=ier)
981    l_error = l_error .OR. (ier /= 0)
982    IF (l_error) THEN
983       WRITE(numout,*) ' Memory allocation error for pref_soil_veg. We stop. We need nvm words = ',nvm
984       STOP 'pft_parameters_alloc'
985    END IF
986
987    ALLOCATE(leaf_tab(nvm),stat=ier)
988    l_error = l_error .OR. (ier /= 0)
989    IF (l_error) THEN
990       WRITE(numout,*) ' Memory allocation error for leaf_tab. We stop. We need nvm words = ',nvm
991       STOP 'pft_parameters_alloc'
992    END IF
993
994    ALLOCATE(pheno_model(nvm),stat=ier)
995    l_error = l_error .OR. (ier /= 0)
996    IF (l_error) THEN
997       WRITE(numout,*) ' Memory allocation error for pheno_model. We stop. We need nvm words = ',nvm
998       STOP 'pft_parameters_alloc'
999    END IF
1000
1001    ALLOCATE(is_deciduous(nvm),stat=ier) 
1002    l_error = l_error .OR. (ier /= 0) 
1003    IF (l_error) THEN
1004       WRITE(numout,*) ' Memory allocation error for is_deciduous. We stop. We need nvm words = ',nvm
1005       STOP 'pft_parameters_alloc'
1006    END IF
1007
1008    ALLOCATE(is_evergreen(nvm),stat=ier) 
1009    l_error = l_error .OR. (ier /= 0)
1010    IF (l_error) THEN
1011       WRITE(numout,*) ' Memory allocation error for is_evergreen. We stop. We need nvm words = ',nvm
1012       STOP 'pft_parameters_alloc'
1013    END IF
1014
1015    ALLOCATE(is_needleleaf(nvm),stat=ier) 
1016    l_error = l_error .OR. (ier /= 0)
1017    IF (l_error) THEN
1018       WRITE(numout,*) ' Memory allocation error for is_needleleaf. We stop. We need nvm words = ',nvm
1019       STOP 'pft_parameters_alloc'
1020    END IF
1021
1022    ALLOCATE(is_tropical(nvm),stat=ier)   
1023    l_error = l_error .OR. (ier /= 0)
1024    IF (l_error) THEN
1025       WRITE(numout,*) ' Memory allocation error for is_tropical. We stop. We need nvm words = ',nvm
1026       STOP 'pft_parameters_alloc'
1027    END IF
1028
1029
1030    !
1031    ! 2. Parameters used if ok_sechiba only
1032    !
1033    IF ( ok_sechiba ) THEN
1034
1035       l_error = .FALSE.
1036
1037       ALLOCATE(rstruct_const(nvm),stat=ier)
1038       l_error = l_error .OR. (ier /= 0)
1039       IF (l_error) THEN
1040          WRITE(numout,*) ' Memory allocation error for rstruct_const. We stop. We need nvm words = ',nvm
1041          STOP 'pft_parameters_alloc'
1042       END IF
1043
1044       ALLOCATE(kzero(nvm),stat=ier)
1045       l_error = l_error .OR. (ier /= 0)
1046       IF (l_error) THEN
1047          WRITE(numout,*) ' Memory allocation error for kzero. We stop. We need nvm words = ',nvm
1048          STOP 'pft_parameters_alloc'
1049       END IF
1050
1051       ALLOCATE(rveg_pft(nvm),stat=ier)
1052       l_error = l_error .OR. (ier /= 0)
1053       IF (l_error) THEN
1054          WRITE(numout,*) ' Memory allocation error for rveg_pft. We stop. We need nvm words = ',nvm
1055          STOP 'pft_parameters_alloc'
1056       END IF
1057
1058       ALLOCATE(wmax_veg(nvm),stat=ier)
1059       l_error = l_error .OR. (ier /= 0)
1060       IF (l_error) THEN
1061          WRITE(numout,*) ' Memory allocation error for wmax_veg. We stop. We need nvm words = ',nvm
1062          STOP 'pft_parameters_alloc'
1063       END IF
1064
1065       ALLOCATE(throughfall_by_pft(nvm),stat=ier)
1066       l_error = l_error .OR. (ier /= 0)
1067       IF (l_error) THEN
1068          WRITE(numout,*) ' Memory allocation error for throughfall_by_pft. We stop. We need nvm words = ',nvm
1069          STOP 'pft_parameters_alloc'
1070       END IF
1071
1072       ALLOCATE(snowa_aged_vis(nvm),stat=ier)
1073       l_error = l_error .OR. (ier /= 0)
1074       IF (l_error) THEN
1075          WRITE(numout,*) ' Memory allocation error for snowa_aged_vis. We stop. We need nvm words = ',nvm
1076          STOP 'pft_parameters_alloc'
1077       END IF
1078
1079       ALLOCATE(snowa_aged_nir(nvm),stat=ier)
1080       l_error = l_error .OR. (ier /= 0)
1081       IF (l_error) THEN
1082          WRITE(numout,*) ' Memory allocation error for snowa_aged_nir. We stop. We need nvm words = ',nvm
1083          STOP 'pft_parameters_alloc'
1084       END IF
1085
1086       ALLOCATE(snowa_dec_vis(nvm),stat=ier)
1087       l_error = l_error .OR. (ier /= 0)
1088       IF (l_error) THEN
1089          WRITE(numout,*) ' Memory allocation error for snowa_dec_vis. We stop. We need nvm words = ',nvm
1090          STOP 'pft_parameters_alloc'
1091       END IF
1092
1093       ALLOCATE(snowa_dec_nir(nvm),stat=ier)
1094       l_error = l_error .OR. (ier /= 0)
1095       IF (l_error) THEN
1096          WRITE(numout,*) ' Memory allocation error for snowa_dec_nir. We stop. We need nvm words = ',nvm
1097          STOP 'pft_parameters_alloc'
1098       END IF
1099
1100       ALLOCATE(alb_leaf_vis(nvm),stat=ier)
1101       l_error = l_error .OR. (ier /= 0)
1102       IF (l_error) THEN
1103          WRITE(numout,*) ' Memory allocation error for alb_leaf_vis. We stop. We need nvm words = ',nvm
1104          STOP 'pft_parameters_alloc'
1105       END IF
1106
1107       ALLOCATE(alb_leaf_nir(nvm),stat=ier)
1108       l_error = l_error .OR. (ier /= 0)
1109       IF (l_error) THEN
1110          WRITE(numout,*) ' Memory allocation error for alb_leaf_nir. We stop. We need nvm words = ',nvm
1111          STOP 'pft_parameters_alloc'
1112       END IF
1113
1114       IF( ok_bvoc ) THEN
1115
1116          l_error = .FALSE.
1117
1118          ALLOCATE(em_factor_isoprene(nvm),stat=ier)
1119          l_error = l_error .OR. (ier /= 0) 
1120          IF (l_error) THEN
1121             WRITE(numout,*) ' Memory allocation error for em_factor_isoprene. We stop. We need nvm words = ',nvm
1122             STOP 'pft_parameters_alloc'
1123          END IF
1124
1125          ALLOCATE(em_factor_monoterpene(nvm),stat=ier)
1126          l_error = l_error .OR. (ier /= 0) 
1127          IF (l_error) THEN
1128             WRITE(numout,*) ' Memory allocation error for em_factor_monoterpene. We stop. We need nvm words = ',nvm
1129             STOP 'pft_parameters_alloc'
1130          END IF
1131
1132          ALLOCATE(em_factor_apinene(nvm),stat=ier)
1133          l_error = l_error .OR. (ier /= 0) 
1134          IF (l_error) THEN
1135             WRITE(numout,*) ' Memory allocation error for em_factor_apinene. We stop. We need nvm words = ',nvm
1136             STOP 'pft_parameters_alloc'
1137          END IF
1138
1139          ALLOCATE(em_factor_bpinene(nvm),stat=ier)
1140          l_error = l_error .OR. (ier /= 0) 
1141          IF (l_error) THEN
1142             WRITE(numout,*) ' Memory allocation error for em_factor_bpinene. We stop. We need nvm words = ',nvm
1143             STOP 'pft_parameters_alloc'
1144          END IF
1145
1146          ALLOCATE(em_factor_limonene(nvm),stat=ier)
1147          l_error = l_error .OR. (ier /= 0) 
1148          IF (l_error) THEN
1149             WRITE(numout,*) ' Memory allocation error for em_factor_limonene. We stop. We need nvm words = ',nvm
1150             STOP 'pft_parameters_alloc'
1151          END IF
1152
1153          ALLOCATE(em_factor_myrcene(nvm),stat=ier)
1154          l_error = l_error .OR. (ier /= 0) 
1155          IF (l_error) THEN
1156             WRITE(numout,*) ' Memory allocation error for em_factor_myrcene. We stop. We need nvm words = ',nvm
1157             STOP 'pft_parameters_alloc'
1158          END IF
1159
1160          ALLOCATE(em_factor_sabinene(nvm),stat=ier)
1161          l_error = l_error .OR. (ier /= 0) 
1162          IF (l_error) THEN
1163             WRITE(numout,*) ' Memory allocation error for em_factor_sabinene. We stop. We need nvm words = ',nvm
1164             STOP 'pft_parameters_alloc'
1165          END IF
1166
1167          ALLOCATE(em_factor_camphene(nvm),stat=ier)
1168          l_error = l_error .OR. (ier /= 0) 
1169          IF (l_error) THEN
1170             WRITE(numout,*) ' Memory allocation error for em_factor_camphene. We stop. We need nvm words = ',nvm
1171             STOP 'pft_parameters_alloc'
1172          END IF
1173
1174          ALLOCATE(em_factor_3carene(nvm),stat=ier)
1175          l_error = l_error .OR. (ier /= 0) 
1176          IF (l_error) THEN
1177             WRITE(numout,*) ' Memory allocation error for em_factor_3carene. We stop. We need nvm words = ',nvm
1178             STOP 'pft_parameters_alloc'
1179          END IF
1180
1181          ALLOCATE(em_factor_tbocimene(nvm),stat=ier)
1182          l_error = l_error .OR. (ier /= 0) 
1183          IF (l_error) THEN
1184             WRITE(numout,*) ' Memory allocation error for em_factor_tbocimene. We stop. We need nvm words = ',nvm
1185             STOP 'pft_parameters_alloc'
1186          END IF
1187
1188          ALLOCATE(em_factor_othermonot(nvm),stat=ier)
1189          l_error = l_error .OR. (ier /= 0) 
1190          IF (l_error) THEN
1191             WRITE(numout,*) ' Memory allocation error for em_factor_othermonot. We stop. We need nvm words = ',nvm
1192             STOP 'pft_parameters_alloc'
1193          END IF
1194
1195          ALLOCATE(em_factor_sesquiterp(nvm),stat=ier)
1196          l_error = l_error .OR. (ier /= 0) 
1197          IF (l_error) THEN
1198             WRITE(numout,*) ' Memory allocation error for em_factor_sesquiterp. We stop. We need nvm words = ',nvm
1199             STOP 'pft_parameters_alloc'
1200          END IF
1201
1202
1203          ALLOCATE(em_factor_ORVOC(nvm),stat=ier)
1204          l_error = l_error .OR. (ier /= 0) 
1205          IF (l_error) THEN
1206             WRITE(numout,*) ' Memory allocation error for em_factor_ORVOC. We stop. We need nvm words = ',nvm
1207             STOP 'pft_parameters_alloc'
1208          END IF
1209
1210          ALLOCATE(em_factor_OVOC(nvm),stat=ier)
1211          l_error = l_error .OR. (ier /= 0)       
1212          IF (l_error) THEN
1213             WRITE(numout,*) ' Memory allocation error for em_factor_OVOC. We stop. We need nvm words = ',nvm
1214             STOP 'pft_parameters_alloc'
1215          END IF
1216
1217          ALLOCATE(em_factor_MBO(nvm),stat=ier)
1218          l_error = l_error .OR. (ier /= 0) 
1219          IF (l_error) THEN
1220             WRITE(numout,*) ' Memory allocation error for em_factor_MBO. We stop. We need nvm words = ',nvm
1221             STOP 'pft_parameters_alloc'
1222          END IF
1223
1224          ALLOCATE(em_factor_methanol(nvm),stat=ier)
1225          l_error = l_error .OR. (ier /= 0) 
1226          IF (l_error) THEN
1227             WRITE(numout,*) ' Memory allocation error for em_factor_methanol. We stop. We need nvm words = ',nvm
1228             STOP 'pft_parameters_alloc'
1229          END IF
1230
1231          ALLOCATE(em_factor_acetone(nvm),stat=ier)
1232          l_error = l_error .OR. (ier /= 0) 
1233          IF (l_error) THEN
1234             WRITE(numout,*) ' Memory allocation error for em_factor_acetone. We stop. We need nvm words = ',nvm
1235             STOP 'pft_parameters_alloc'
1236          END IF
1237
1238          ALLOCATE(em_factor_acetal(nvm),stat=ier)
1239          l_error = l_error .OR. (ier /= 0) 
1240          IF (l_error) THEN
1241             WRITE(numout,*) ' Memory allocation error for em_factor_acetal. We stop. We need nvm words = ',nvm
1242             STOP 'pft_parameters_alloc'
1243          END IF
1244
1245          ALLOCATE(em_factor_formal(nvm),stat=ier)
1246          l_error = l_error .OR. (ier /= 0) 
1247          IF (l_error) THEN
1248             WRITE(numout,*) ' Memory allocation error for em_factor_formal. We stop. We need nvm words = ',nvm
1249             STOP 'pft_parameters_alloc'
1250          END IF
1251
1252          ALLOCATE(em_factor_acetic(nvm),stat=ier)
1253          l_error = l_error .OR. (ier /= 0)       
1254          IF (l_error) THEN
1255             WRITE(numout,*) ' Memory allocation error for em_factor_acetic. We stop. We need nvm words = ',nvm
1256             STOP 'pft_parameters_alloc'
1257          END IF
1258
1259          ALLOCATE(em_factor_formic(nvm),stat=ier)
1260          l_error = l_error .OR. (ier /= 0) 
1261          IF (l_error) THEN
1262             WRITE(numout,*) ' Memory allocation error for em_factor_formic. We stop. We need nvm words = ',nvm
1263             STOP 'pft_parameters_alloc'
1264          END IF
1265
1266          ALLOCATE(em_factor_no_wet(nvm),stat=ier)
1267          l_error = l_error .OR. (ier /= 0)
1268          IF (l_error) THEN
1269             WRITE(numout,*) ' Memory allocation error for em_factor_no_wet. We stop. We need nvm words = ',nvm
1270             STOP 'pft_parameters_alloc'
1271          END IF
1272
1273          ALLOCATE(em_factor_no_dry(nvm),stat=ier)
1274          l_error = l_error .OR. (ier /= 0)       
1275          IF (l_error) THEN
1276             WRITE(numout,*) ' Memory allocation error for em_factor_no_dry. We stop. We need nvm words = ',nvm
1277             STOP 'pft_parameters_alloc'
1278          END IF
1279
1280          ALLOCATE(Larch(nvm),stat=ier)
1281          l_error = l_error .OR. (ier /= 0) 
1282          IF (l_error) THEN
1283             WRITE(numout,*) ' Memory allocation error for Larch. We stop. We need nvm words = ',nvm
1284             STOP 'pft_parameters_alloc'
1285          END IF
1286
1287       ENDIF ! (ok_bvoc)
1288
1289    ENDIF !(ok_sechiba)
1290
1291    !
1292    ! 3. Parameters used if ok_stomate only
1293    !
1294    IF ( ok_stomate ) THEN
1295
1296       l_error = .FALSE.
1297
1298       ALLOCATE(sla(nvm),stat=ier)
1299       l_error = l_error .OR. (ier /= 0)
1300       IF (l_error) THEN
1301          WRITE(numout,*) ' Memory allocation error for sla. We stop. We need nvm words = ',nvm
1302          STOP 'pft_parameters_alloc'
1303       END IF
1304
1305       ALLOCATE(availability_fact(nvm),stat=ier)
1306       l_error = l_error .OR. (ier /= 0)
1307       IF (l_error) THEN
1308          WRITE(numout,*) ' Memory allocation error for availability_fact. We stop. We need nvm words = ',nvm
1309          STOP 'pft_parameters_alloc'
1310       END IF
1311
1312       ALLOCATE(R0(nvm),stat=ier)
1313       l_error = l_error .OR. (ier /= 0)
1314       IF (l_error) THEN
1315          WRITE(numout,*) ' Memory allocation error for R0. We stop. We need nvm words = ',nvm
1316          STOP 'pft_parameters_alloc'
1317       END IF
1318
1319       ALLOCATE(S0(nvm),stat=ier)
1320       l_error = l_error .OR. (ier /= 0)
1321       IF (l_error) THEN
1322          WRITE(numout,*) ' Memory allocation error for S0. We stop. We need nvm words = ',nvm
1323          STOP 'pft_parameters_alloc'
1324       END IF
1325
1326       ALLOCATE(L0(nvm),stat=ier)
1327       l_error = l_error .OR. (ier /= 0)
1328       IF (l_error) THEN
1329          WRITE(numout,*) ' Memory allocation error for L0. We stop. We need nvm words = ',nvm
1330          STOP 'pft_parameters_alloc'
1331       END IF
1332
1333       ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier)
1334       l_error = l_error .OR. (ier /= 0)
1335       IF (l_error) THEN
1336          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_c. We stop. We need nvm words = ',nvm
1337          STOP 'pft_parameters_alloc'
1338       END IF
1339
1340       ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier)
1341       l_error = l_error .OR. (ier /= 0)
1342       IF (l_error) THEN
1343          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_b. We stop. We need nvm words = ',nvm
1344          STOP 'pft_parameters_alloc'
1345       END IF
1346
1347       ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier)
1348       l_error = l_error .OR. (ier /= 0)
1349       IF (l_error) THEN
1350          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_a. We stop. We need nvm words = ',nvm
1351          STOP 'pft_parameters_alloc'
1352       END IF
1353
1354       ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier)
1355       l_error = l_error .OR. (ier /= 0)
1356       IF (l_error) THEN
1357          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit. We stop. We need nvm words = ',nvm*3
1358          STOP 'pft_parameters_alloc'
1359       END IF
1360       pheno_gdd_crit(:,:) = zero
1361
1362       ALLOCATE(pheno_moigdd_t_crit(nvm),stat=ier)
1363       l_error = l_error .OR. (ier /= 0)
1364       IF (l_error) THEN
1365          WRITE(numout,*) ' Memory allocation error for pheno_moigdd_t_crit. We stop. We need nvm words = ',nvm
1366          STOP 'pft_parameters_alloc'
1367       END IF
1368
1369       ALLOCATE(ngd_crit(nvm),stat=ier)
1370       l_error = l_error .OR. (ier /= 0)
1371       IF (l_error) THEN
1372          WRITE(numout,*) ' Memory allocation error for ngd_crit. We stop. We need nvm words = ',nvm
1373          STOP 'pft_parameters_alloc'
1374       END IF
1375
1376       ALLOCATE(ncdgdd_temp(nvm),stat=ier)
1377       l_error = l_error .OR. (ier /= 0)
1378       IF (l_error) THEN
1379          WRITE(numout,*) ' Memory allocation error for ncdgdd_temp. We stop. We need nvm words = ',nvm
1380          STOP 'pft_parameters_alloc'
1381       END IF
1382
1383       ALLOCATE(hum_frac(nvm),stat=ier)
1384       l_error = l_error .OR. (ier /= 0)
1385       IF (l_error) THEN
1386          WRITE(numout,*) ' Memory allocation error for hum_frac. We stop. We need nvm words = ',nvm
1387          STOP 'pft_parameters_alloc'
1388       END IF
1389
1390       ALLOCATE(hum_min_time(nvm),stat=ier)
1391       l_error = l_error .OR. (ier /= 0)
1392       IF (l_error) THEN
1393          WRITE(numout,*) ' Memory allocation error for hum_min_time. We stop. We need nvm words = ',nvm
1394          STOP 'pft_parameters_alloc'
1395       END IF
1396
1397       ALLOCATE(tau_sap(nvm),stat=ier)
1398       l_error = l_error .OR. (ier /= 0)
1399       IF (l_error) THEN
1400          WRITE(numout,*) ' Memory allocation error for tau_sap. We stop. We need nvm words = ',nvm
1401          STOP 'pft_parameters_alloc'
1402       END IF
1403
1404       ALLOCATE(tau_leafinit(nvm),stat=ier)
1405       l_error = l_error .OR. (ier /= 0)
1406       IF (l_error) THEN
1407          WRITE(numout,*) ' Memory allocation error for tau_leafinit. We stop. We need nvm words = ',nvm
1408          STOP 'pft_parameters_alloc'
1409       END IF
1410
1411       ALLOCATE(tau_fruit(nvm),stat=ier)
1412       l_error = l_error .OR. (ier /= 0)
1413       IF (l_error) THEN
1414          WRITE(numout,*) ' Memory allocation error for tau_fruit. We stop. We need nvm words = ',nvm
1415          STOP 'pft_parameters_alloc'
1416       END IF
1417
1418       ALLOCATE(ecureuil(nvm),stat=ier)
1419       l_error = l_error .OR. (ier /= 0)
1420       IF (l_error) THEN
1421          WRITE(numout,*) ' Memory allocation error for ecureuil. We stop. We need nvm words = ',nvm
1422          STOP 'pft_parameters_alloc'
1423       END IF
1424
1425       ALLOCATE(alloc_min(nvm),stat=ier)
1426       l_error = l_error .OR. (ier /= 0)
1427       IF (l_error) THEN
1428          WRITE(numout,*) ' Memory allocation error for alloc_min. We stop. We need nvm words = ',nvm
1429          STOP 'pft_parameters_alloc'
1430       END IF
1431
1432       ALLOCATE(alloc_max(nvm),stat=ier)
1433       l_error = l_error .OR. (ier /= 0)
1434       IF (l_error) THEN
1435          WRITE(numout,*) ' Memory allocation error for alloc_max. We stop. We need nvm words = ',nvm
1436          STOP 'pft_parameters_alloc'
1437       END IF
1438
1439       ALLOCATE(demi_alloc(nvm),stat=ier)
1440       l_error = l_error .OR. (ier /= 0)
1441       IF (l_error) THEN
1442          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
1443          STOP 'pft_parameters_alloc'
1444       END IF
1445
1446       ALLOCATE(frac_growthresp(nvm),stat=ier)
1447       l_error = l_error .OR. (ier /= 0)
1448       IF (l_error) THEN
1449          WRITE(numout,*) ' Memory allocation error for frac_growthresp. We stop. We need nvm words = ',nvm
1450          STOP 'pft_parameters_alloc'
1451       END IF
1452
1453       ALLOCATE(maint_resp_slope(nvm,3),stat=ier)
1454       l_error = l_error .OR. (ier /= 0)
1455       IF (l_error) THEN
1456          WRITE(numout,*) ' Memory allocation error for maint_resp_slope. We stop. We need nvm*3 words = ',nvm*3
1457          STOP 'pft_parameters_alloc'
1458       END IF
1459       maint_resp_slope(:,:) = zero
1460
1461       ALLOCATE(maint_resp_slope_c(nvm),stat=ier)
1462       l_error = l_error .OR. (ier /= 0)
1463       IF (l_error) THEN
1464          WRITE(numout,*) ' Memory allocation error for maint_resp_slope_c. We stop. We need nvm words = ',nvm
1465          STOP 'pft_parameters_alloc'
1466       END IF
1467
1468       ALLOCATE(maint_resp_slope_b(nvm),stat=ier)
1469       l_error = l_error .OR. (ier /= 0)
1470       IF (l_error) THEN
1471          WRITE(numout,*) ' Memory allocation error for maint_resp_slope_b. We stop. We need nvm words = ',nvm
1472          STOP 'pft_parameters_alloc'
1473       END IF
1474
1475       ALLOCATE(maint_resp_slope_a(nvm),stat=ier)
1476       l_error = l_error .OR. (ier /= 0)
1477       IF (l_error) THEN
1478          WRITE(numout,*) ' Memory allocation error for maint_resp_slope_a. We stop. We need nvm words = ',nvm
1479          STOP 'pft_parameters_alloc'
1480       END IF
1481
1482       ALLOCATE(coeff_maint_zero(nvm,nparts),stat=ier)
1483       l_error = l_error .OR. (ier /= 0)
1484       IF (l_error) THEN
1485          WRITE(numout,*) ' Memory allocation error for coeff_maint_zero. We stop. We need nvm*nparts words = ',nvm*nparts
1486          STOP 'pft_parameters_alloc'
1487       END IF
1488       coeff_maint_zero(:,:) = zero
1489
1490       ALLOCATE(cm_zero_leaf(nvm),stat=ier)
1491       l_error = l_error .OR. (ier /= 0)
1492       IF (l_error) THEN
1493          WRITE(numout,*) ' Memory allocation error for cm_zero_leaf. We stop. We need nvm words = ',nvm
1494          STOP 'pft_parameters_alloc'
1495       END IF
1496
1497       ALLOCATE(cm_zero_sapabove(nvm),stat=ier)
1498       l_error = l_error .OR. (ier /= 0)
1499       IF (l_error) THEN
1500          WRITE(numout,*) ' Memory allocation error for cm_zero_sapabove. We stop. We need nvm words = ',nvm
1501          STOP 'pft_parameters_alloc'
1502       END IF
1503
1504       ALLOCATE(cm_zero_sapbelow(nvm),stat=ier)
1505       l_error = l_error .OR. (ier /= 0)
1506       IF (l_error) THEN
1507          WRITE(numout,*) ' Memory allocation error for cm_zero_sapbelow. We stop. We need nvm words = ',nvm
1508          STOP 'pft_parameters_alloc'
1509       END IF
1510
1511       ALLOCATE(cm_zero_heartabove(nvm),stat=ier)
1512       l_error = l_error .OR. (ier /= 0)
1513       IF (l_error) THEN
1514          WRITE(numout,*) ' Memory allocation error for cm_zero_heartabove. We stop. We need nvm words = ',nvm
1515          STOP 'pft_parameters_alloc'
1516       END IF
1517
1518       ALLOCATE(cm_zero_heartbelow(nvm),stat=ier)
1519       l_error = l_error .OR. (ier /= 0)
1520       IF (l_error) THEN
1521          WRITE(numout,*) ' Memory allocation error for cm_zero_heartbelow. We stop. We need nvm words = ',nvm
1522          STOP 'pft_parameters_alloc'
1523       END IF
1524
1525       ALLOCATE(cm_zero_root(nvm),stat=ier)
1526       l_error = l_error .OR. (ier /= 0)
1527       IF (l_error) THEN
1528          WRITE(numout,*) ' Memory allocation error for cm_zero_root. We stop. We need nvm words = ',nvm
1529          STOP 'pft_parameters_alloc'
1530       END IF
1531
1532       ALLOCATE(cm_zero_fruit(nvm),stat=ier)
1533       l_error = l_error .OR. (ier /= 0)
1534       IF (l_error) THEN
1535          WRITE(numout,*) ' Memory allocation error for cm_zero_fruit. We stop. We need nvm words = ',nvm
1536          STOP 'pft_parameters_alloc'
1537       END IF
1538
1539       ALLOCATE(cm_zero_carbres(nvm),stat=ier)
1540       l_error = l_error .OR. (ier /= 0)
1541       IF (l_error) THEN
1542          WRITE(numout,*) ' Memory allocation error for cm_zero_carbres. We stop. We need nvm words = ',nvm
1543          STOP 'pft_parameters_alloc'
1544       END IF
1545
1546       ALLOCATE(flam(nvm),stat=ier)
1547       l_error = l_error .OR. (ier /= 0)
1548       IF (l_error) THEN
1549          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
1550          STOP 'pft_parameters_alloc'
1551       END IF
1552
1553       ALLOCATE(resist(nvm),stat=ier)
1554       l_error = l_error .OR. (ier /= 0)
1555       IF (l_error) THEN
1556          WRITE(numout,*) ' Memory allocation error for resist. We stop. We need nvm words = ',nvm
1557          STOP 'pft_parameters_alloc'
1558       END IF
1559
1560       ALLOCATE(coeff_lcchange_1(nvm),stat=ier)
1561       l_error = l_error .OR. (ier /= 0)
1562       IF (l_error) THEN
1563          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_1. We stop. We need nvm words = ',nvm
1564          STOP 'pft_parameters_alloc'
1565       END IF
1566
1567       ALLOCATE(coeff_lcchange_10(nvm),stat=ier)
1568       l_error = l_error .OR. (ier /= 0)
1569       IF (l_error) THEN
1570          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_10. We stop. We need nvm words = ',nvm
1571          STOP 'pft_parameters_alloc'
1572       END IF
1573
1574       ALLOCATE(coeff_lcchange_100(nvm),stat=ier)
1575       l_error = l_error .OR. (ier /= 0)
1576       IF (l_error) THEN
1577          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_100. We stop. We need nvm words = ',nvm
1578          STOP 'pft_parameters_alloc'
1579       END IF
1580
1581       ALLOCATE(lai_max_to_happy(nvm),stat=ier)
1582       l_error = l_error .OR. (ier /= 0)
1583       IF (l_error) THEN
1584          WRITE(numout,*) ' Memory allocation error for lai_max_to_happy. We stop. We need nvm words = ',nvm
1585          STOP 'pft_parameters_alloc'
1586       END IF
1587
1588       ALLOCATE(lai_max(nvm),stat=ier)
1589       l_error = l_error .OR. (ier /= 0)
1590       IF (l_error) THEN
1591          WRITE(numout,*) ' Memory allocation error for lai_max. We stop. We need nvm words = ',nvm
1592          STOP 'pft_parameters_alloc'
1593       END IF
1594
1595       ALLOCATE(pheno_type(nvm),stat=ier)
1596       l_error = l_error .OR. (ier /= 0)
1597       IF (l_error) THEN
1598          WRITE(numout,*) ' Memory allocation error for pheno_type. We stop. We need nvm words = ',nvm
1599          STOP 'pft_parameters_alloc'
1600       END IF
1601
1602       ALLOCATE(leaffall(nvm),stat=ier)
1603       l_error = l_error .OR. (ier /= 0)
1604       IF (l_error) THEN
1605          WRITE(numout,*) ' Memory allocation error for leaffall. We stop. We need nvm words = ',nvm
1606          STOP 'pft_parameters_alloc'
1607       END IF
1608
1609       ALLOCATE(leafagecrit(nvm),stat=ier)
1610       l_error = l_error .OR. (ier /= 0)
1611       IF (l_error) THEN
1612          WRITE(numout,*) ' Memory allocation error for leafagecrit. We stop. We need nvm words = ',nvm
1613          STOP 'pft_parameters_alloc'
1614       END IF
1615
1616       ALLOCATE(senescence_type(nvm),stat=ier)
1617       l_error = l_error .OR. (ier /= 0)
1618       IF (l_error) THEN
1619          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
1620          STOP 'pft_parameters_alloc'
1621       END IF
1622
1623       ALLOCATE(senescence_hum(nvm),stat=ier)
1624       l_error = l_error .OR. (ier /= 0)
1625       IF (l_error) THEN
1626          WRITE(numout,*) ' Memory allocation error for senescence_hum. We stop. We need nvm words = ',nvm
1627          STOP 'pft_parameters_alloc'
1628       END IF
1629
1630       ALLOCATE(nosenescence_hum(nvm),stat=ier)
1631       l_error = l_error .OR. (ier /= 0)
1632       IF (l_error) THEN
1633          WRITE(numout,*) ' Memory allocation error for nosenescence_hum. We stop. We need nvm words = ',nvm
1634          STOP 'pft_parameters_alloc'
1635       END IF
1636
1637       ALLOCATE(max_turnover_time(nvm),stat=ier)
1638       l_error = l_error .OR. (ier /= 0)
1639       IF (l_error) THEN
1640          WRITE(numout,*) ' Memory allocation error for max_turnover_time. We stop. We need nvm words = ',nvm
1641          STOP 'pft_parameters_alloc'
1642       END IF
1643
1644       ALLOCATE(min_turnover_time(nvm),stat=ier)
1645       l_error = l_error .OR. (ier /= 0)
1646       IF (l_error) THEN
1647          WRITE(numout,*) ' Memory allocation error for min_turnover_time. We stop. We need nvm words = ',nvm
1648          STOP 'pft_parameters_alloc'
1649       END IF
1650
1651       ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier)
1652       l_error = l_error .OR. (ier /= 0)
1653       IF (l_error) THEN
1654          WRITE(numout,*) ' Memory allocation error for min_leaf_age_for_senescence. We stop. We need nvm words = ',nvm
1655          STOP 'pft_parameters_alloc'
1656       END IF
1657
1658       ALLOCATE(senescence_temp_c(nvm),stat=ier)
1659       l_error = l_error .OR. (ier /= 0)
1660       IF (l_error) THEN
1661          WRITE(numout,*) ' Memory allocation error for senescence_temp_c. We stop. We need nvm words = ',nvm
1662          STOP 'pft_parameters_alloc'
1663       END IF
1664
1665       ALLOCATE(senescence_temp_b(nvm),stat=ier)
1666       l_error = l_error .OR. (ier /= 0)
1667       IF (l_error) THEN
1668          WRITE(numout,*) ' Memory allocation error for senescence_temp_b. We stop. We need nvm words = ',nvm
1669          STOP 'pft_parameters_alloc'
1670       END IF
1671
1672       ALLOCATE(senescence_temp_a(nvm),stat=ier)
1673       l_error = l_error .OR. (ier /= 0)
1674       IF (l_error) THEN
1675          WRITE(numout,*) ' Memory allocation error for senescence_temp_a. We stop. We need nvm words = ',nvm
1676          STOP 'pft_parameters_alloc'
1677       END IF
1678
1679       ALLOCATE(senescence_temp(nvm,3),stat=ier)
1680       l_error = l_error .OR. (ier /= 0)
1681       IF (l_error) THEN
1682          WRITE(numout,*) ' Memory allocation error for senescence_temp. We stop. We need nvm*3 words = ',nvm*3
1683          STOP 'pft_parameters_alloc'
1684       END IF
1685       senescence_temp(:,:) = zero
1686
1687       ALLOCATE(gdd_senescence(nvm),stat=ier)
1688       l_error = l_error .OR. (ier /= 0)
1689       IF (l_error) THEN
1690          WRITE(numout,*) ' Memory allocation error for gdd_senescence. We stop. We need nvm words = ',nvm
1691          STOP 'pft_parameters_alloc'
1692       END IF
1693
1694       ALLOCATE(always_init(nvm),stat=ier)
1695       l_error = l_error .OR. (ier /= 0)
1696       IF (l_error) THEN
1697          WRITE(numout,*) ' Memory allocation error for always_init. We stop. We need nvm words = ',nvm
1698          STOP 'pft_parameters_alloc'
1699       END IF
1700
1701       ALLOCATE(residence_time(nvm),stat=ier)
1702       l_error = l_error .OR. (ier /= 0)
1703       IF (l_error) THEN
1704          WRITE(numout,*) ' Memory allocation error for residence_time. We stop. We need nvm words = ',nvm
1705          STOP 'pft_parameters_alloc'
1706       END IF
1707
1708       ALLOCATE(tmin_crit(nvm),stat=ier)
1709       l_error = l_error .OR. (ier /= 0)
1710       IF (l_error) THEN
1711          WRITE(numout,*) ' Memory allocation error for tmin_crit. We stop. We need nvm words = ',nvm
1712          STOP 'pft_parameters_alloc'
1713       END IF
1714
1715       ALLOCATE(tcm_crit(nvm),stat=ier)
1716       l_error = l_error .OR. (ier /= 0)
1717       IF (l_error) THEN
1718          WRITE(numout,*) ' Memory allocation error for tcm_crit. We stop. We need nvm words = ',nvm
1719          STOP 'pft_parameters_alloc'
1720       END IF
1721
1722       ALLOCATE(lai_initmin(nvm),stat=ier)
1723       l_error = l_error .OR. (ier /= 0)
1724       IF (l_error) THEN
1725          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
1726          STOP 'pft_parameters_alloc'
1727       END IF
1728
1729       ALLOCATE(bm_sapl(nvm,nparts,nelements),stat=ier)
1730       l_error = l_error .OR. (ier /= 0)
1731       IF (l_error) THEN
1732          WRITE(numout,*) ' Memory allocation error for bm_sapl. We stop. We need nvm*nparts*nelements words = ',& 
1733               &  nvm*nparts*nelements
1734          STOP 'pft_parameters_alloc'
1735       END IF
1736
1737       ALLOCATE(migrate(nvm),stat=ier)
1738       l_error = l_error .OR. (ier /= 0)
1739       IF (l_error) THEN
1740          WRITE(numout,*) ' Memory allocation error for migrate. We stop. We need nvm words = ',nvm
1741          STOP 'pft_parameters_alloc'
1742       END IF
1743
1744       ALLOCATE(maxdia(nvm),stat=ier)
1745       l_error = l_error .OR. (ier /= 0)
1746       IF (l_error) THEN
1747          WRITE(numout,*) ' Memory allocation error for maxdia. We stop. We need nvm words = ',nvm
1748          STOP 'pft_parameters_alloc'
1749       END IF
1750
1751       ALLOCATE(cn_sapl(nvm),stat=ier)
1752       l_error = l_error .OR. (ier /= 0)
1753       IF (l_error) THEN
1754          WRITE(numout,*) ' Memory allocation error for cn_sapl. We stop. We need nvm words = ',nvm
1755          STOP 'pft_parameters_alloc'
1756       END IF
1757
1758       ALLOCATE(leaf_timecst(nvm),stat=ier)
1759       l_error = l_error .OR. (ier /= 0)
1760       IF (l_error) THEN
1761          WRITE(numout,*) ' Memory allocation error for leaf_timecst. We stop. We need nvm words = ',nvm
1762          STOP 'pft_parameters_alloc'
1763       END IF
1764
1765       ALLOCATE(leaflife_tab(nvm),stat=ier)   
1766       l_error = l_error .OR. (ier /= 0)
1767       IF (l_error) THEN
1768          WRITE(numout,*) ' Memory allocation error for leaflife_tab. We stop. We need nvm words = ',nvm
1769          STOP 'pft_parameters_alloc'
1770       END IF
1771
1772    ENDIF ! (ok_stomate)
1773
1774  END SUBROUTINE pft_parameters_alloc
1775
1776!! ================================================================================================================================
1777!! SUBROUTINE   : config_pft_parameters
1778!!
1779!>\BRIEF          This subroutine will read the imposed values for the global pft
1780!! parameters (sechiba + stomate). It is not called if IMPOSE_PARAM is set to NO.
1781!!
1782!! DESCRIPTION  : None
1783!!
1784!! RECENT CHANGE(S): None
1785!!
1786!! MAIN OUTPUT VARIABLE(S): None
1787!!
1788!! REFERENCE(S) : None
1789!!
1790!! FLOWCHART    : None
1791!! \n
1792!_ ================================================================================================================================
1793
1794  SUBROUTINE config_pft_parameters
1795
1796    IMPLICIT NONE
1797
1798    !! 0. Variables and parameters declaration
1799
1800    !! 0.4 Local variable
1801
1802    INTEGER(i_std) :: jv                   !! Index (untiless)
1803
1804    !_ ================================================================================================================================
1805
1806
1807    !
1808    ! Vegetation structure
1809    !
1810
1811    !Config Key   = LEAF_TAB
1812    !Config Desc  = leaf type : 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bare ground
1813    !Config if    = OK_STOMATE
1814    !Config Def   = 4, 1, 1, 2, 1, 1, 2, 1, 2, 3, 3, 3, 3
1815    !Config Help  =
1816    !Config Units = [-]
1817    CALL getin_p('LEAF_TAB',leaf_tab)
1818
1819    !Config Key   = PHENO_MODEL
1820    !Config Desc  = which phenology model is used? (tabulated)
1821    !Config if    = OK_STOMATE
1822    !Config Def   = none, none, moi, none, none, ncdgdd, none, ncdgdd, ngd, moigdd, moigdd, moigdd, moigdd
1823    !Config Help  =
1824    !Config Units = [-]
1825    CALL getin_p('PHENO_MODEL',pheno_model)
1826
1827    !! Redefine the values for is_tree, is_deciduous, is_needleleaf, is_evergreen if values have been modified
1828    !! in run.def
1829
1830    is_tree(:) = .FALSE.
1831    DO jv = 1,nvm
1832       IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
1833    END DO
1834    !
1835    is_deciduous(:) = .FALSE.
1836    DO jv = 1,nvm
1837       IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
1838    END DO
1839    !
1840    is_evergreen(:) = .FALSE.
1841    DO jv = 1,nvm
1842       IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
1843    END DO
1844    !
1845    is_needleleaf(:) = .FALSE.
1846    DO jv = 1,nvm
1847       IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
1848    END DO
1849
1850
1851    !Config Key   = SECHIBA_LAI
1852    !Config Desc  = laimax for maximum lai(see also type of lai interpolation)
1853    !Config if    = OK_SECHIBA or IMPOSE_VEG
1854    !Config Def   = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2.
1855    !Config Help  = Maximum values of lai used for interpolation of the lai map
1856    !Config Units = [m^2/m^2]
1857    CALL getin_p('SECHIBA_LAI',llaimax)
1858
1859    !Config Key   = LLAIMIN
1860    !Config Desc  = laimin for minimum lai(see also type of lai interpolation)
1861    !Config if    = OK_SECHIBA or IMPOSE_VEG
1862    !Config Def   = 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0.
1863    !Config Help  = Minimum values of lai used for interpolation of the lai map
1864    !Config Units = [m^2/m^2]
1865    CALL getin_p('LLAIMIN',llaimin)
1866
1867    !Config Key   = SLOWPROC_HEIGHT
1868    !Config Desc  = prescribed height of vegetation
1869    !Config if    = OK_SECHIBA
1870    !Config Def   = 0., 30., 30., 20., 20., 20., 15., 15., 15., .5, .6, 1., 1.
1871    !Config Help  =
1872    !Config Units = [m]
1873    CALL getin_p('SLOWPROC_HEIGHT',height_presc)
1874
1875    !Config Key   = Z0_OVER_HEIGHT
1876    !Config Desc  = factor to calculate roughness height from height of canopy
1877    !Config if    = OK_SECHIBA
1878    !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
1879    !Config Help  =
1880    !Config Units = [-]
1881    CALL getin_p('Z0_OVER_HEIGHT',z0_over_height)
1882
1883    !
1884    !Config Key   = RATIO_Z0M_Z0H
1885    !Config Desc  = Ratio between z0m and z0h
1886    !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
1887    !Config if    = OK_SECHIBA
1888    !Config Help  =
1889    !Config Units = [-]
1890    CALL getin_p('RATIO_Z0M_Z0H',ratio_z0m_z0h)
1891
1892
1893    !Config Key   = TYPE_OF_LAI
1894    !Config Desc  = Type of behaviour of the LAI evolution algorithm
1895    !Config if    = OK_SECHIBA
1896    !Config Def   = inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter
1897    !Config Help  =
1898    !Config Units = [-]
1899    CALL getin_p('TYPE_OF_LAI',type_of_lai)
1900
1901    !Config Key   = NATURAL
1902    !Config Desc  = natural?
1903    !Config if    = OK_SECHIBA, OK_STOMATE
1904    !Config Def   = y, y, y, y, y, y, y, y, y, y, y, n, n
1905    !Config Help  =
1906    !Config Units = [BOOLEAN]
1907    CALL getin_p('NATURAL',natural)
1908
1909
1910    !
1911    ! Photosynthesis
1912    !
1913
1914    !Config Key   = IS_C4
1915    !Config Desc  = flag for C4 vegetation types
1916    !Config if    = OK_SECHIBA or OK_STOMATE
1917    !Config Def   = n, n, n, n, n, n, n, n, n, n, n, y, n, y
1918    !Config Help  =
1919    !Config Units = [BOOLEAN]
1920    CALL getin_p('IS_C4',is_c4)
1921
1922    !Config Key   = VCMAX_FIX
1923    !Config Desc  = values used for vcmax when STOMATE is not activated
1924    !Config if    = OK_SECHIBA and NOT(OK_STOMATE)
1925    !Config Def   = 0., 40., 50., 30., 35., 40.,30., 40., 35., 60., 60., 70., 70.
1926    !Config Help  =
1927    !Config Units = [micromol/m^2/s]
1928    CALL getin_p('VCMAX_FIX',vcmax_fix)
1929
1930    !Config Key   = DOWNREG_CO2
1931    !Config Desc  = coefficient for CO2 downregulation (unitless)
1932    !Config if    =
1933    !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
1934    !Config Help  =
1935    !Config Units = [-]
1936    CALL getin_p('DOWNREG_CO2',downregulation_co2_coeff)
1937
1938    !Config Key   = E_KmC
1939    !Config Desc  = Energy of activation for KmC
1940    !Config if    =
1941    !Config Def   = undef,  79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430.
1942    !Config Help  = See Medlyn et al. (2002)
1943    !Config Units = [J mol-1]
1944    CALL getin_p('E_KMC',E_KmC)
1945
1946    !Config Key   = E_KmO
1947    !Config Desc  = Energy of activation for KmO
1948    !Config if    =
1949    !Config Def   = undef, 36380.,  36380.,  36380.,  36380.,  36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380.
1950    !Config Help  = See Medlyn et al. (2002)
1951    !Config Units = [J mol-1]
1952    CALL getin_p('E_KMO',E_KmO)
1953
1954    !Config Key   = E_Sco
1955    !Config Desc  = Energy of activation for Sco
1956    !Config if    =
1957    !Config Def   = undef, -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460.
1958    !Config Help  = See Table 2 of Yin et al. (2009) - Value for C4 plants is not mentioned - We use C3 for all plants
1959    !Config Units = [J mol-1]
1960    CALL getin_p('E_SCO',E_Sco)
1961   
1962    !Config Key   = E_gamma_star
1963    !Config Desc  = Energy of activation for gamma_star
1964    !Config if    =
1965    !Config Def   = undef, 37830.,  37830.,  37830.,  37830.,  37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830.
1966    !Config Help  = See Medlyn et al. (2002) from Bernacchi al. (2001)
1967    !Config Units = [J mol-1]
1968    CALL getin_p('E_GAMMA_STAR',E_gamma_star)
1969
1970    !Config Key   = E_Vcmax
1971    !Config Desc  = Energy of activation for Vcmax
1972    !Config if    =
1973    !Config Def   = undef, 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 67300., 71513., 67300.
1974    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3)
1975    !Config Units = [J mol-1]
1976    CALL getin_p('E_VCMAX',E_Vcmax)
1977
1978    !Config Key   = E_Jmax
1979    !Config Desc  = Energy of activation for Jmax
1980    !Config if    =
1981    !Config Def   = undef, 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 77900., 49884., 77900.
1982    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3)
1983    !Config Units = [J mol-1]
1984    CALL getin_p('E_JMAX',E_Jmax)
1985
1986    !Config Key   = aSV
1987    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax
1988    !Config if    =
1989    !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
1990    !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)
1991    !Config Units = [J K-1 mol-1]
1992    CALL getin_p('ASV',aSV)
1993
1994    !Config Key   = bSV
1995    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax
1996    !Config if    =
1997    !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.
1998    !Config Help  = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation
1999    !Config Units = [J K-1 mol-1 °C-1]
2000    CALL getin_p('BSV',bSV)
2001
2002    !Config Key   = TPHOTO_MIN
2003    !Config Desc  = minimum photosynthesis temperature (deg C)
2004    !Config if    = OK_STOMATE
2005    !Config Def   = undef,  -4., -4., -4., -4.,-4.,-4., -4., -4., -4., -4., -4., -4.
2006    !Config Help  =
2007    !Config Units = [-]
2008    CALL getin_p('TPHOTO_MIN',tphoto_min)
2009
2010    !Config Key   = TPHOTO_MAX
2011    !Config Desc  = maximum photosynthesis temperature (deg C)
2012    !Config if    = OK_STOMATE
2013    !Config Def   = undef, 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55.
2014    !Config Help  =
2015    !Config Units = [-]
2016    CALL getin_p('TPHOTO_MAX',tphoto_max)
2017
2018    !Config Key   = aSJ
2019    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax
2020    !Config if    =
2021    !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.
2022    !Config Help  = See Table 3 of Kattge & Knorr (2007) - and Table 2 of Yin et al. (2009) for C4 plants
2023    !Config Units = [J K-1 mol-1]
2024    CALL getin_p('ASJ',aSJ)
2025
2026    !Config Key   = bSJ
2027    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax
2028    !Config if    =
2029    !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.
2030    !Config Help  = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation
2031    !Config Units = [J K-1 mol-1 °C-1]
2032    CALL getin_p('BSJ',bSJ)
2033
2034    !Config Key   = D_Vcmax
2035    !Config Desc  = Energy of deactivation for Vcmax
2036    !Config if    =
2037    !Config Def   = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000.
2038    !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.
2039    !Config Units = [J mol-1]
2040    CALL getin_p('D_VCMAX',D_Vcmax)
2041
2042    !Config Key   = D_Jmax
2043    !Config Desc  = Energy of deactivation for Jmax
2044    !Config if    =
2045    !Config Def   = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000.
2046    !Config Help  = See Table 2 of Yin et al. (2009)
2047    !Config Units = [J mol-1]
2048    CALL getin_p('D_JMAX',D_Jmax)
2049   
2050    !Config Key   = E_gm
2051    !Config Desc  = Energy of activation for gm
2052    !Config if    = 
2053    !Config Def   = undef, 49600., 49600., 49600., 49600., 49600., 49600., 49600., 49600., 49600., undef, 49600., undef
2054    !Config Help  = See Table 2 of Yin et al. (2009)
2055    !Config Units = [J mol-1]
2056    CALL getin_p('E_GM',E_gm) 
2057   
2058    !Config Key   = S_gm
2059    !Config Desc  = Entropy term for gm
2060    !Config if    = 
2061    !Config Def   = undef, 1400., 1400., 1400., 1400., 1400., 1400., 1400., 1400., 1400., undef, 1400., undef
2062    !Config Help  = See Table 2 of Yin et al. (2009)
2063    !Config Units = [J K-1 mol-1]
2064    CALL getin_p('S_GM',S_gm) 
2065   
2066    !Config Key   = D_gm
2067    !Config Desc  = Energy of deactivation for gm
2068    !Config if    = 
2069    !Config Def   = undef, 437400., 437400., 437400., 437400., 437400., 437400., 437400., 437400., 437400., undef, 437400., undef
2070    !Config Help  = See Table 2 of Yin et al. (2009)
2071    !Config Units = [J mol-1]
2072    CALL getin_p('D_GM',D_gm) 
2073   
2074    !Config Key   = E_Rd
2075    !Config Desc  = Energy of activation for Rd
2076    !Config if    =
2077    !Config Def   = undef, 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390.
2078    !Config Help  = See Table 2 of Yin et al. (2009)
2079    !Config Units = [J mol-1]
2080    CALL getin_p('E_RD',E_Rd)
2081
2082    !Config Key   = VCMAX25
2083    !Config Desc  = Maximum rate of Rubisco activity-limited carboxylation at 25°C
2084    !Config if    = OK_STOMATE
2085    !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
2086    !Config Help  =
2087    !Config Units = [micromol/m^2/s]
2088    CALL getin_p('VCMAX25',Vcmax25)
2089
2090    !Config Key   = ARJV
2091    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio
2092    !Config if    = OK_STOMATE
2093    !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
2094    !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)
2095    !Config Units = [mu mol e- (mu mol CO2)-1]
2096    CALL getin_p('ARJV',arJV)
2097
2098    !Config Key   = BRJV
2099    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio
2100    !Config if    = OK_STOMATE
2101    !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.
2102    !Config Help  = See Table 3 of Kattge & Knorr (2007) -  We assume No acclimation term for C4 plants
2103    !Config Units = [(mu mol e- (mu mol CO2)-1) (°C)-1]
2104    CALL getin_p('BRJV',brJV)
2105
2106    !Config Key   = KmC25
2107    !Config Desc  = Michaelis–Menten constant of Rubisco for CO2 at 25°C
2108    !Config if    =
2109    !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.
2110    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants
2111    !Config Units = [ubar]
2112    CALL getin_p('KMC25',KmC25)
2113
2114    !Config Key   = KmO25
2115    !Config Desc  = Michaelis–Menten constant of Rubisco for O2 at 25°C
2116    !Config if    =
2117    !Config Def   = undef, 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 450000., 278400., 450000.
2118    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants
2119    !Config Units = [ubar]
2120    CALL getin_p('KMO25',KmO25)
2121
2122    !Config Key   = Sco25
2123    !Config Desc  = Relative CO2 /O2 specificity factor for Rubisco at 25°C
2124    !Config if    =
2125    !Config Def   = undef, 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2590., 2800., 2590.
2126    !Config Help  = See Table 2 of Yin et al. (2009)
2127    !Config Units = [bar bar-1]
2128    CALL getin_p('SCO25',Sco25)
2129   
2130    !Config Key   = gm25
2131    !Config Desc  = Mesophyll diffusion conductance at 25°C
2132    !Config if    = 
2133    !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
2134    !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
2135    !Config Units = [mol m-2 s-1 bar-1]
2136    CALL getin_p('GM25',gm25) 
2137   
2138    !Config Key   = gamma_star25
2139    !Config Desc  = Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
2140    !Config if    =
2141    !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
2142    !Config Help  = See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the same value (probably uncorrect)
2143    !Config Units = [ubar]
2144    CALL getin_p('gamma_star25',gamma_star25)
2145
2146    !Config Key   = a1
2147    !Config Desc  = Empirical factor involved in the calculation of fvpd
2148    !Config if    =
2149    !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
2150    !Config Help  = See Table 2 of Yin et al. (2009)
2151    !Config Units = [-]
2152    CALL getin_p('A1',a1)
2153
2154    !Config Key   = b1
2155    !Config Desc  = Empirical factor involved in the calculation of fvpd
2156    !Config if    =
2157    !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
2158    !Config Help  = See Table 2 of Yin et al. (2009)
2159    !Config Units = [-]
2160    CALL getin_p('B1',b1)
2161
2162    !Config Key   = g0
2163    !Config Desc  = Residual stomatal conductance when irradiance approaches zero
2164    !Config if    =
2165    !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
2166    !Config Help  = Value from ORCHIDEE - No other reference.
2167    !Config Units = [mol m−2 s−1 bar−1]
2168    CALL getin_p('G0',g0)
2169
2170    !Config Key   = h_protons
2171    !Config Desc  = Number of protons required to produce one ATP
2172    !Config if    =
2173    !Config Def   = undef, 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4.
2174    !Config Help  = See Table 2 of Yin et al. (2009) - h parameter
2175    !Config Units = [mol mol-1]
2176    CALL getin_p('H_PROTONS',h_protons)
2177
2178    !Config Key   = fpsir
2179    !Config Desc  = Fraction of PSII e− transport rate partitioned to the C4 cycle
2180    !Config if    =
2181    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.4, undef, 0.4
2182    !Config Help  = See Table 2 of Yin et al. (2009)
2183    !Config Units = [-]
2184    CALL getin_p('FPSIR',fpsir)
2185
2186    !Config Key   = fQ
2187    !Config Desc  = Fraction of electrons at reduced plastoquinone that follow the Q-cycle
2188    !Config if    =
2189    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 1., undef, 1.
2190    !Config Help  = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used
2191    !Config Units = [-]
2192    CALL getin_p('FQ',fQ)
2193
2194    !Config Key   = fpseudo
2195    !Config Desc  = Fraction of electrons at PSI that follow pseudocyclic transport
2196    !Config if    =
2197    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1
2198    !Config Help  = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used
2199    !Config Units = [-]
2200    CALL getin_p('FPSEUDO',fpseudo)
2201
2202    !Config Key   = kp
2203    !Config Desc  = Initial carboxylation efficiency of the PEP carboxylase
2204    !Config if    =
2205    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.7, undef, 0.7
2206    !Config Help  = See Table 2 of Yin et al. (2009)
2207    !Config Units = [mol m−2 s−1 bar−1]
2208    CALL getin_p('KP',kp)
2209
2210    !Config Key   = alpha
2211    !Config Desc  = Fraction of PSII activity in the bundle sheath
2212    !Config if    =
2213    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1
2214    !Config Help  = See legend of Figure 6 of Yin et al. (2009)
2215    !Config Units = [-]
2216    CALL getin_p('ALPHA',alpha)
2217
2218    !Config Key   = gbs
2219    !Config Desc  = Bundle-sheath conductance
2220    !Config if    =
2221    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.003, undef, 0.003
2222    !Config Help  = See legend of Figure 6 of Yin et al. (2009)
2223    !Config Units = [mol m−2 s−1 bar−1]
2224    CALL getin_p('GBS',gbs)
2225
2226    !Config Key   = theta
2227    !Config Desc  = Convexity factor for response of J to irradiance
2228    !Config if    =
2229    !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
2230    !Config Help  = See Table 2 of Yin et al. (2009)   
2231    !Config Units = [−]
2232    CALL getin_p('THETA',theta)
2233
2234    !Config Key   = alpha_LL
2235    !Config Desc  = Conversion efficiency of absorbed light into J at strictly limiting light
2236    !Config if    =
2237    !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
2238    !Config Help  = See comment from Yin et al. (2009) after eq. 4
2239    !Config Units = [mol e− (mol photon)−1]
2240    CALL getin_p('ALPHA_LL',alpha_LL)
2241
2242    !Config Key   = STRESS_VCMAX
2243    !Config Desc  = Stress on vcmax
2244    !Config if    = OK_SECHIBA or OK_STOMATE
2245    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
2246    !Config Help  =
2247    !Config Units = [-]
2248    CALL getin_p('STRESS_VCMAX', stress_vcmax)
2249   
2250    !Config Key   = STRESS_GS
2251    !Config Desc  = Stress on gs
2252    !Config if    = OK_SECHIBA or OK_STOMATE
2253    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
2254    !Config Help  =
2255    !Config Units = [-]
2256    CALL getin_p('STRESS_GS', stress_gs)
2257   
2258    !Config Key   = STRESS_GM
2259    !Config Desc  = Stress on gm
2260    !Config if    = OK_SECHIBA or OK_STOMATE
2261    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
2262    !Config Help  =
2263    !Config Units = [-]
2264    CALL getin_p('STRESS_GM', stress_gm)
2265
2266    !Config Key   = EXT_COEFF
2267    !Config Desc  = extinction coefficient of the Monsi&Seaki relationship (1953)
2268    !Config if    = OK_SECHIBA or OK_STOMATE
2269    !Config Def   = .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
2270    !Config Help  =
2271    !Config Units = [-]
2272    CALL getin_p('EXT_COEFF',ext_coeff)
2273
2274    !Config Key   = EXT_COEFF_VEGETFRAC
2275    !Config Desc  = extinction coefficient used for the calculation of the bare soil fraction
2276    !Config if    = OK_SECHIBA or OK_STOMATE
2277    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
2278    !Config Help  =
2279    !Config Units = [-]
2280    CALL getin_p('EXT_COEFF_VEGETFRAC',ext_coeff_vegetfrac)
2281
2282    !
2283    ! Water-hydrology - sechiba
2284    !
2285
2286    !Config Key   = HYDROL_HUMCSTE
2287    !Config Desc  = Root profile
2288    !Config Def   = humcste_ref2m or humcste_ref4m depending on zmaxh
2289    !Config if    = OK_SECHIBA
2290    !Config Help  = See module constantes_mtc for different default values
2291    !Config Units = [m]
2292    CALL getin_p('HYDROL_HUMCSTE',humcste)
2293
2294    !
2295    ! Soil - vegetation
2296    !
2297
2298    !Config Key   = PREF_SOIL_VEG
2299    !Config Desc  = The soil tile number for each vegetation
2300    !Config if    = OK_SECHIBA or OK_STOMATE
2301    !Config Def   = 1, 2, 2, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3
2302    !Config Help  = Gives the number of the soil tile on which we will
2303    !Config         put each vegetation. This allows to divide the hydrological column
2304    !Config Units = [-]       
2305    CALL getin_p('PREF_SOIL_VEG',pref_soil_veg)
2306
2307  END SUBROUTINE config_pft_parameters
2308
2309
2310!! ================================================================================================================================
2311!! SUBROUTINE   : config_sechiba_pft_parameters
2312!!
2313!>\BRIEF        This subroutine will read the imposed values for the sechiba pft
2314!! parameters. It is not called if IMPOSE_PARAM is set to NO.
2315!!
2316!! DESCRIPTION  : None
2317!!
2318!! RECENT CHANGE(S): None
2319!!
2320!! MAIN OUTPUT VARIABLE(S): None
2321!!
2322!! REFERENCE(S) : None
2323!!
2324!! FLOWCHART    : None
2325!! \n
2326!_ ================================================================================================================================
2327
2328  SUBROUTINE config_sechiba_pft_parameters()
2329
2330    IMPLICIT NONE
2331
2332    !! 0. Variables and parameters declaration
2333
2334    !! 0.1 Input variables
2335
2336    !! 0.4 Local variable
2337
2338    !_ ================================================================================================================================
2339
2340    !
2341    ! Evapotranspiration -  sechiba
2342    !
2343
2344    !Config Key   = RSTRUCT_CONST
2345    !Config Desc  = Structural resistance
2346    !Config if    = OK_SECHIBA
2347    !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
2348    !Config Help  =
2349    !Config Units = [s/m]
2350    CALL getin_p('RSTRUCT_CONST',rstruct_const)
2351
2352    !Config Key   = KZERO
2353    !Config Desc  = A vegetation dependent constant used in the calculation of the surface resistance.
2354    !Config if    = OK_SECHIBA
2355    !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
2356    !Config Help  =
2357    !Config Units = [kg/m^2/s]
2358    CALL getin_p('KZERO',kzero)
2359
2360    !Config Key   = RVEG_PFT
2361    !Config Desc  = Artificial parameter to increase or decrease canopy resistance.
2362    !Config if    = OK_SECHIBA
2363    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
2364    !Config Help  = This parameter is set by PFT.
2365    !Config Units = [-]
2366    CALL getin_p('RVEG_PFT',rveg_pft)   
2367
2368    !
2369    ! Water-hydrology - sechiba
2370    !
2371
2372    !Config Key   = WMAX_VEG
2373    !Config Desc  = Maximum field capacity for each of the vegetations (Temporary): max quantity of water
2374    !Config if    = OK_SECHIBA
2375    !Config Def   = 150., 150., 150., 150., 150., 150., 150.,150., 150., 150., 150., 150., 150.
2376    !Config Help  =
2377    !Config Units = [kg/m^3]
2378    CALL getin_p('WMAX_VEG',wmax_veg)
2379
2380    !Config Key   = PERCENT_THROUGHFALL_PFT
2381    !Config Desc  = Percent by PFT of precip that is not intercepted by the canopy. Default value depend on run mode.
2382    !Config if    = OK_SECHIBA
2383    !Config Def   = Case offline [0. 0. 0....] else [30. 30. 30.....]
2384    !Config Help  = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
2385    !Config         will get directly to the ground without being intercepted, for each PFT.
2386    !Config Units = [%]
2387    CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
2388    throughfall_by_pft(:) = throughfall_by_pft(:) / 100. 
2389
2390
2391    !
2392    ! Albedo - sechiba
2393    !
2394
2395    !Config Key   = SNOWA_AGED_VIS
2396    !Config Desc  = Minimum snow albedo value for each vegetation type after aging (dirty old snow), visible albedo
2397    !Config if    = OK_SECHIBA
2398    !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
2399    !Config Help  = Values optimized for ORCHIDEE2.0
2400    !Config Units = [-]
2401    CALL getin_p('SNOWA_AGED_VIS',snowa_aged_vis)
2402
2403    !Config Key   = SNOWA_AGED_NIR
2404    !Config Desc  = Minimum snow albedo value for each vegetation type after aging (dirty old snow), near infrared albedo
2405    !Config if    = OK_SECHIBA
2406    !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 
2407    !Config Help  = Values optimized for ORCHIDEE2.0
2408    !Config Units = [-]
2409    CALL getin_p('SNOWA_AGED_NIR',snowa_aged_nir)
2410
2411    !Config Key   = SNOWA_DEC_VIS
2412    !Config Desc  = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow, visible albedo
2413    !Config if    = OK_SECHIBA
2414    !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
2415    !Config Help  = Values optimized for ORCHIDEE2.0
2416    !Config Units = [-]
2417    CALL getin_p('SNOWA_DEC_VIS',snowa_dec_vis)
2418
2419    !Config Key   = SNOWA_DEC_NIR
2420    !Config Desc  = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow, near infrared albedo
2421    !Config if    = OK_SECHIBA
2422    !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
2423    !Config Help  = Values optimized for ORCHIDEE2.0
2424    !Config Units = [-]
2425    CALL getin_p('SNOWA_DEC_NIR',snowa_dec_nir)
2426
2427    !Config Key   = ALB_LEAF_VIS
2428    !Config Desc  = leaf albedo of vegetation type, visible albedo
2429    !Config if    = OK_SECHIBA
2430    !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
2431    !Config Help  = Values optimized for ORCHIDEE2.0
2432    !Config Units = [-]
2433    CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis)
2434
2435    !Config Key   = ALB_LEAF_NIR
2436    !Config Desc  = leaf albedo of vegetation type, near infrared albedo
2437    !Config if    = OK_SECHIBA
2438    !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
2439    !Config Help  = Values optimized for ORCHIDEE2.0
2440    !Config Units = [-]
2441    CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir)
2442
2443    IF ( ok_bvoc ) THEN
2444       !
2445       ! BVOC
2446       !
2447
2448       !Config Key   = ISO_ACTIVITY
2449       !Config Desc  = Biogenic activity for each age class : isoprene
2450       !Config if    = CHEMISTRY_BVOC
2451       !Config Def   = 0.5, 1.5, 1.5, 0.5
2452       !Config Help  =
2453       !Config Units = [-]
2454       CALL getin_p('ISO_ACTIVITY',iso_activity)
2455
2456       !Config Key   = METHANOL_ACTIVITY
2457       !Config Desc  = Isoprene emission factor for each age class : methanol
2458       !Config if    = CHEMISTRY_BVOC
2459       !Config Def   = 1., 1., 0.5, 0.5
2460       !Config Help  =
2461       !Config Units = [-]
2462       CALL getin_p('METHANOL_ACTIVITY',methanol_activity)
2463
2464       !Config Key   = EM_FACTOR_ISOPRENE
2465       !Config Desc  = Isoprene emission factor
2466       !Config if    = CHEMISTRY_BVOC
2467       !Config Def   = 0., 24., 24., 8., 16., 45., 8., 18., 0.5, 12., 18., 5., 5.
2468       !Config Help  =
2469       !Config Units = [ugC/g/h]
2470       CALL getin_p('EM_FACTOR_ISOPRENE',em_factor_isoprene)
2471
2472       !Config Key   = EM_FACTOR_MONOTERPENE
2473       !Config Desc  = Monoterpene emission factor
2474       !Config if    = CHEMISTRY_BVOC
2475       !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
2476       !Config Help  =
2477       !Config Units = [ugC/g/h]
2478       CALL getin_p('EM_FACTOR_MONOTERPENE',em_factor_monoterpene)
2479
2480       !Config Key   = C_LDF_MONO
2481       !Config Desc  = Monoterpenes fraction dependancy to light
2482       !Config if    = CHEMISTRY_BVOC
2483       !Config Def   = 0.6
2484       !Config Help  =
2485       !Config Units = []
2486       CALL getin_p('C_LDF_MONO',LDF_mono)
2487
2488       !Config Key   = C_LDF_SESQ
2489       !Config Desc  = Sesquiterpenes fraction dependancy to light
2490       !Config if    = CHEMISTRY_BVOC
2491       !Config Def   = 0.5
2492       !Config Help  =
2493       !Config Units = []
2494       CALL getin_p('C_LDF_SESQ',LDF_sesq)
2495
2496       !Config Key   = C_LDF_METH
2497       !Config Desc  = Methanol fraction dependancy to light
2498       !Config if    = CHEMISTRY_BVOC
2499       !Config Def   = 0.8
2500       !Config Help  =
2501       !Config Units = []
2502       CALL getin_p('C_LDF_METH',LDF_meth)
2503
2504       !Config Key   = C_LDF_ACET
2505       !Config Desc  = Acetone fraction dependancy to light
2506       !Config if    = CHEMISTRY_BVOC
2507       !Config Def   = 0.2
2508       !Config Help  =
2509       !Config Units = []
2510       CALL getin_p('C_LDF_ACET',LDF_acet)
2511
2512       !Config Key   = EM_FACTOR_APINENE
2513       !Config Desc  = Alfa pinene  emission factor
2514       !Config if    = CHEMISTRY_BVOC
2515       !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
2516       !Config Help  =
2517       !Config Units = [ugC/g/h]
2518       CALL getin_p('EM_FACTOR_APINENE',em_factor_apinene)
2519
2520       !Config Key   = EM_FACTOR_BPINENE
2521       !Config Desc  = Beta pinene  emission factor
2522       !Config if    = CHEMISTRY_BVOC
2523       !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
2524       !Config Help  =
2525       !Config Units = [ugC/g/h]
2526       CALL getin_p('EM_FACTOR_BPINENE',em_factor_bpinene)
2527
2528       !Config Key   = EM_FACTOR_LIMONENE
2529       !Config Desc  = Limonene  emission factor
2530       !Config if    = CHEMISTRY_BVOC
2531       !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
2532       !Config Help  =
2533       !Config Units = [ugC/g/h]
2534       CALL getin_p('EM_FACTOR_LIMONENE',em_factor_limonene)
2535
2536       !Config Key   = EM_FACTOR_MYRCENE
2537       !Config Desc  = Myrcene  emission factor
2538       !Config if    = CHEMISTRY_BVOC
2539       !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
2540       !Config Help  =
2541       !Config Units = [ugC/g/h]
2542       CALL getin_p('EM_FACTOR_MYRCENE',em_factor_myrcene)
2543
2544       !Config Key   = EM_FACTOR_SABINENE
2545       !Config Desc  = Sabinene  emission factor
2546       !Config if    = CHEMISTRY_BVOC
2547       !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
2548       !Config Help  =
2549       !Config Units = [ugC/g/h]
2550       CALL getin_p('EM_FACTOR_SABINENE',em_factor_sabinene)
2551
2552       !Config Key   = EM_FACTOR_CAMPHENE
2553       !Config Desc  = Camphene  emission factor
2554       !Config if    = CHEMISTRY_BVOC
2555       !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
2556       !Config Help  =
2557       !Config Units = [ugC/g/h]
2558       CALL getin_p('EM_FACTOR_CAMPHENE',em_factor_camphene)
2559
2560       !Config Key   = EM_FACTOR_3CARENE
2561       !Config Desc  = 3-Carene  emission factor
2562       !Config if    = CHEMISTRY_BVOC
2563       !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
2564       !Config Help  =
2565       !Config Units = [ugC/g/h]
2566       CALL getin_p('EM_FACTOR_3CARENE',em_factor_3carene)
2567
2568       !Config Key   = EM_FACTOR_TBOCIMENE
2569       !Config Desc  = T-beta-ocimene  emission factor
2570       !Config if    = CHEMISTRY_BVOC
2571       !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
2572       !Config Help  =
2573       !Config Units = [ugC/g/h]
2574       CALL getin_p('EM_FACTOR_TBOCIMENE', em_factor_tbocimene)
2575
2576       !Config Key   = EM_FACTOR_OTHERMONOT
2577       !Config Desc  = Other monoterpenes  emission factor
2578       !Config if    = CHEMISTRY_BVOC
2579       !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
2580       !Config Help  =
2581       !Config Units = [ugC/g/h]
2582       CALL getin_p('EM_FACTOR_OTHERMONOT',em_factor_othermonot)
2583
2584       !Config Key   = EM_FACTOR_SESQUITERP
2585       !Config Desc  = Sesquiterpenes  emission factor
2586       !Config if    = CHEMISTRY_BVOC
2587       !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
2588       !Config Help  =
2589       !Config Units = [ugC/g/h]
2590       CALL getin_p('EM_FACTOR_SESQUITERP',em_factor_sesquiterp)
2591
2592
2593
2594       !Config Key   = C_BETA_MONO
2595       !Config Desc  = Monoterpenes temperature dependency coefficient
2596       !Config if    = CHEMISTRY_BVOC
2597       !Config Def   = 0.1
2598       !Config Help  =
2599       !Config Units = []
2600       CALL getin_p('C_BETA_MONO',beta_mono)
2601
2602       !Config Key   = C_BETA_SESQ
2603       !Config Desc  = Sesquiterpenes temperature dependency coefficient
2604       !Config if    = CHEMISTRY_BVOC
2605       !Config Def   = 0.17
2606       !Config Help  =
2607       !Config Units = []
2608       CALL getin_p('C_BETA_SESQ',beta_sesq)
2609
2610       !Config Key   = C_BETA_METH
2611       !Config Desc  = Methanol temperature dependency coefficient
2612       !Config if    = CHEMISTRY_BVOC
2613       !Config Def   = 0.08
2614       !Config Help  =
2615       !Config Units = []
2616       CALL getin_p('C_BETA_METH',beta_meth)
2617
2618       !Config Key   = C_BETA_ACET
2619       !Config Desc  = Acetone temperature dependency coefficient
2620       !Config if    = CHEMISTRY_BVOC
2621       !Config Def   = 0.1
2622       !Config Help  =
2623       !Config Units = []
2624       CALL getin_p('C_BETA_ACET',beta_acet)
2625
2626       !Config Key   = C_BETA_OXYVOC
2627       !Config Desc  = Other oxygenated BVOC temperature dependency coefficient
2628       !Config if    = CHEMISTRY_BVOC
2629       !Config Def   = 0.13
2630       !Config Help  =
2631       !Config Units = []
2632       CALL getin_p('C_BETA_OXYVOC',beta_oxyVOC)
2633
2634       !Config Key   = EM_FACTOR_ORVOC
2635       !Config Desc  = ORVOC emissions factor
2636       !Config if    = CHEMISTRY_BVOC
2637       !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
2638       !Config Help  =
2639       !Config Units = [ugC/g/h] 
2640       CALL getin_p('EM_FACTOR_ORVOC',em_factor_ORVOC)
2641
2642       !Config Key   = EM_FACTOR_OVOC
2643       !Config Desc  = OVOC emissions factor
2644       !Config if    = CHEMISTRY_BVOC
2645       !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
2646       !Config Help  =
2647       !Config Units = [ugC/g/h]       
2648       CALL getin_p('EM_FACTOR_OVOC',em_factor_OVOC)
2649
2650       !Config Key   = EM_FACTOR_MBO
2651       !Config Desc  = MBO emissions factor
2652       !Config if    = CHEMISTRY_BVOC
2653       !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
2654       !Config Help  =
2655       !Config Units = [ugC/g/h] 
2656       CALL getin_p('EM_FACTOR_MBO',em_factor_MBO)
2657
2658       !Config Key   = EM_FACTOR_METHANOL
2659       !Config Desc  = Methanol emissions factor
2660       !Config if    = CHEMISTRY_BVOC
2661       !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.
2662       !Config Help  =
2663       !Config Units = [ugC/g/h] 
2664       CALL getin_p('EM_FACTOR_METHANOL',em_factor_methanol)
2665
2666       !Config Key   = EM_FACTOR_ACETONE
2667       !Config Desc  = Acetone emissions factor
2668       !Config if    = CHEMISTRY_BVOC
2669       !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
2670       !Config Help  =
2671       !Config Units = [ugC/g/h]     
2672       CALL getin_p('EM_FACTOR_ACETONE',em_factor_acetone)
2673
2674       !Config Key   = EM_FACTOR_ACETAL
2675       !Config Desc  = Acetaldehyde emissions factor
2676       !Config if    = CHEMISTRY_BVOC
2677       !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
2678       !Config Help  =
2679       !Config Units = [ugC/g/h] 
2680       CALL getin_p('EM_FACTOR_ACETAL',em_factor_acetal)
2681
2682       !Config Key   = EM_FACTOR_FORMAL
2683       !Config Desc  = Formaldehyde emissions factor
2684       !Config if    = CHEMISTRY_BVOC
2685       !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
2686       !Config Help  =
2687       !Config Units = [ugC/g/h] 
2688       CALL getin_p('EM_FACTOR_FORMAL',em_factor_formal)
2689
2690       !Config Key   = EM_FACTOR_ACETIC
2691       !Config Desc  = Acetic Acid emissions factor
2692       !Config if    = CHEMISTRY_BVOC
2693       !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
2694       !Config Help  =
2695       !Config Units = [ugC/g/h] 
2696       CALL getin_p('EM_FACTOR_ACETIC',em_factor_acetic)
2697
2698       !Config Key   = EM_FACTOR_FORMIC
2699       !Config Desc  = Formic Acid emissions factor
2700       !Config if    = CHEMISTRY_BVOC
2701       !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
2702       !Config Help  =
2703       !Config Units = [ugC/g/h] 
2704       CALL getin_p('EM_FACTOR_FORMIC',em_factor_formic)
2705
2706       !Config Key   = EM_FACTOR_NO_WET
2707       !Config Desc  = NOx emissions factor wet soil emissions and exponential dependancy factor
2708       !Config if    = CHEMISTRY_BVOC
2709       !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
2710       !Config Help  =
2711       !Config Units = [ngN/m^2/s]
2712       CALL getin_p('EM_FACTOR_NO_WET',em_factor_no_wet)
2713
2714       !Config Key   = EM_FACTOR_NO_DRY
2715       !Config Desc  = NOx emissions factor dry soil emissions and exponential dependancy factor
2716       !Config if    = CHEMISTRY_BVOC
2717       !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
2718       !Config Help  =
2719       !Config Units = [ngN/m^2/s]
2720       CALL getin_p('EM_FACTOR_NO_DRY',em_factor_no_dry)
2721
2722       !Config Key   = LARCH
2723       !Config Desc  = Larcher 1991 SAI/LAI ratio
2724       !Config if    = CHEMISTRY_BVOC
2725       !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
2726       !Config Help  =
2727       !Config Units = [-] 
2728       CALL getin_p('LARCH',Larch)
2729
2730    ENDIF ! (ok_bvoc)
2731
2732  END SUBROUTINE config_sechiba_pft_parameters
2733
2734
2735!! ================================================================================================================================
2736!! SUBROUTINE   : config_stomate_pft_parameters
2737!!
2738!>\BRIEF         This subroutine will read the imposed values for the stomate pft
2739!! parameters. It is not called if IMPOSE_PARAM is set to NO.
2740!!
2741!! DESCRIPTION  : None
2742!!
2743!! RECENT CHANGE(S): None
2744!!
2745!! MAIN OUTPUT VARIABLE(S): None
2746!!
2747!! REFERENCE(S) : None
2748!!
2749!! FLOWCHART    : None
2750!! \n
2751!_ ================================================================================================================================
2752
2753  SUBROUTINE config_stomate_pft_parameters
2754
2755    IMPLICIT NONE
2756
2757    !! 0. Variables and parameters declaration
2758
2759    !! 0.4 Local variable
2760
2761    !_ ================================================================================================================================
2762
2763    !
2764    ! Vegetation structure
2765    !
2766
2767    !Config Key   = SLA
2768    !Config Desc  = specif leaf area
2769    !Config if    = OK_STOMATE
2770    !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
2771    !Config Help  =
2772    !Config Units = [m^2/gC]
2773    CALL getin_p('SLA',sla)
2774
2775
2776    !Config Key   = AVAILABILITY_FACT
2777    !Config Desc  = Calculate dynamic mortality in lpj_gap, pft dependent parameter
2778    !Config If    = OK_STOMATE
2779    !Config Def   = undef, 0.14, 0.14, 0.10, 0.10, 0.10, 0.05, 0.05, 0.05, undef, undef, undef, undef
2780    !Config Help  =
2781    !Config Units = [-]   
2782    CALL getin_p('AVAILABILITY_FACT',availability_fact)
2783
2784    !
2785    ! Allocation - stomate
2786    !
2787    !
2788    !Config Key   = R0
2789    !Config Desc  = Standard root allocation
2790    !Config If    = OK_STOMATE
2791    !Config Def   = undef, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30
2792    !Config Help  =
2793    !Config Units = [-]   
2794    CALL getin_p('R0',R0)
2795
2796    !Config Key   = S0
2797    !Config Desc  = Standard sapwood allocation
2798    !Config If    = OK_STOMATE
2799    !Config Def   = undef, .25, .25, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30
2800    !Config Help  =
2801    !Config Units = [-]   
2802    CALL getin_p('S0',S0)
2803
2804    !
2805    ! Respiration - stomate
2806    !
2807
2808    !Config Key   = FRAC_GROWTHRESP
2809    !Config Desc  = fraction of GPP which is lost as growth respiration
2810    !Config if    = OK_STOMATE
2811    !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
2812    !Config Help  =
2813    !Config Units = [-]
2814    CALL getin_p('FRAC_GROWTHRESP',frac_growthresp) 
2815
2816    !Config Key   = MAINT_RESP_SLOPE_C
2817    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant c of aT^2+bT+c , tabulated
2818    !Config if    = OK_STOMATE
2819    !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
2820    !Config Help  =
2821    !Config Units = [-]
2822    CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) 
2823
2824    !Config Key   = MAINT_RESP_SLOPE_B
2825    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant b of aT^2+bT+c , tabulated
2826    !Config if    = OK_STOMATE
2827    !Config Def   = undef, .0, .0, .0, .0, .0, .0, .0, .0, -.00133, .0, -.00133, .0
2828    !Config Help  =
2829    !Config Units = [-]
2830    CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b)
2831
2832    !Config Key   = MAINT_RESP_SLOPE_A
2833    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant a of aT^2+bT+c , tabulated
2834    !Config if    = OK_STOMATE
2835    !Config Def   = undef, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0   
2836    !Config Help  =
2837    !Config Units = [-]
2838    CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a)
2839
2840    !Config Key   = CM_ZERO_LEAF
2841    !Config Desc  = maintenance respiration coefficient at 0 deg C, for leaves, tabulated
2842    !Config if    = OK_STOMATE
2843    !Config Def   = undef, 2.35E-3, 2.62E-3, 1.01E-3, 2.35E-3, 2.62E-3, 1.01E-3,2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3
2844    !Config Help  =
2845    !Config Units = [g/g/day]
2846    CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf)
2847
2848    !Config Key   = CM_ZERO_SAPABOVE
2849    !Config Desc  = maintenance respiration coefficient at 0 deg C,for sapwood above, tabulated
2850    !Config if    = OK_STOMATE
2851    !Config Def   = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4
2852    !Config Help  =
2853    !Config Units = [g/g/day]
2854    CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove)
2855
2856    !Config Key   = CM_ZERO_SAPBELOW
2857    !Config Desc  = maintenance respiration coefficient at 0 deg C, for sapwood below, tabulated
2858    !Config if    = OK_STOMATE
2859    !Config Def   = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4
2860    !Config Help  =
2861    !Config Units = [g/g/day]
2862    CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow)
2863
2864    !Config Key   = CM_ZERO_HEARTABOVE
2865    !Config Desc  = maintenance respiration coefficient at 0 deg C, for heartwood above, tabulated
2866    !Config if    = OK_STOMATE
2867    !Config Def   = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
2868    !Config Help  =
2869    !Config Units = [g/g/day]
2870    CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove)
2871
2872    !Config Key   = CM_ZERO_HEARTBELOW
2873    !Config Desc  = maintenance respiration coefficient at 0 deg C,for heartwood below, tabulated
2874    !Config if    = OK_STOMATE
2875    !Config Def   = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
2876    !Config Help  =
2877    !Config Units = [g/g/day]
2878    CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow)
2879
2880    !Config Key   = CM_ZERO_ROOT
2881    !Config Desc  = maintenance respiration coefficient at 0 deg C, for roots, tabulated
2882    !Config if    = OK_STOMATE
2883    !Config Def   = undef,1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3,1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3
2884    !Config Help  =
2885    !Config Units = [g/g/day]
2886    CALL getin_p('CM_ZERO_ROOT',cm_zero_root)
2887
2888    !Config Key   = CM_ZERO_FRUIT
2889    !Config Desc  = maintenance respiration coefficient at 0 deg C, for fruits, tabulated
2890    !Config if    = OK_STOMATE
2891    !Config Def   = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4   
2892    !Config Help  =
2893    !Config Units = [g/g/day]
2894    CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit)
2895
2896    !Config Key   = CM_ZERO_CARBRES
2897    !Config Desc  = maintenance respiration coefficient at 0 deg C, for carbohydrate reserve, tabulated
2898    !Config if    = OK_STOMATE
2899    !Config Def   = undef, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4,1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4
2900    !Config Help  =
2901    !Config Units = [g/g/day]
2902    CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres)
2903
2904    !
2905    ! Fire - stomate
2906    !
2907
2908    !Config Key   = FLAM
2909    !Config Desc  = flamability: critical fraction of water holding capacity
2910    !Config if    = OK_STOMATE
2911    !Config Def   = undef, .15, .25, .25, .25, .25, .25, .25, .25, .25, .25, .35, .35
2912    !Config Help  =
2913    !Config Units = [-]
2914    CALL getin_p('FLAM',flam)
2915
2916    !Config Key   = RESIST
2917    !Config Desc  = fire resistance
2918    !Config if    = OK_STOMATE
2919    !Config Def   = undef, .95, .90, .12, .50, .12, .12, .12, .12, .0, .0, .0, .0
2920    !Config Help  =
2921    !Config Units = [-]
2922    CALL getin_p('RESIST',resist)
2923
2924    !
2925    ! Flux - LUC
2926    !
2927
2928    !Config Key   = COEFF_LCCHANGE_1
2929    !Config Desc  = Coeff of biomass export for the year
2930    !Config if    = OK_STOMATE
2931    !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
2932    !Config Help  =
2933    !Config Units = [-]
2934    CALL getin_p('COEFF_LCCHANGE_1',coeff_lcchange_1)
2935
2936    !Config Key   = COEFF_LCCHANGE_10
2937    !Config Desc  = Coeff of biomass export for the decade
2938    !Config if    = OK_STOMATE
2939    !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
2940    !Config Help  =
2941    !Config Units = [-]
2942    CALL getin_p('COEFF_LCCHANGE_10',coeff_lcchange_10)
2943
2944    !Config Key   = COEFF_LCCHANGE_100
2945    !Config Desc  = Coeff of biomass export for the century
2946    !Config if    = OK_STOMATE
2947    !Config Def   = undef, 0., 0., 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0., 0.104, 0.
2948    !Config Help  =
2949    !Config Units = [-]
2950    CALL getin_p('COEFF_LCCHANGE_100',coeff_lcchange_100)
2951
2952    !
2953    ! Phenology
2954    !
2955
2956    !Config Key   = LAI_MAX_TO_HAPPY
2957    !Config Desc  = threshold of LAI below which plant uses carbohydrate reserves
2958    !Config if    = OK_STOMATE
2959    !Config Def   = undef, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
2960    !Config Help  =
2961    !Config Units = [-]
2962    CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy) 
2963
2964    !Config Key   = LAI_MAX
2965    !Config Desc  = maximum LAI, PFT-specific
2966    !Config if    = OK_STOMATE
2967    !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
2968    !Config Help  =
2969    !Config Units = [m^2/m^2]
2970    CALL getin_p('LAI_MAX',lai_max)
2971
2972    !Config Key   = PHENO_TYPE
2973    !Config Desc  = type of phenology, 0=bare ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
2974    !Config if    = OK_STOMATE
2975    !Config Def   = 0, 1, 3, 1, 1, 2, 1, 2, 2, 4, 4, 2, 3
2976    !Config Help  =
2977    !Config Units = [-]
2978    CALL getin_p('PHENO_TYPE',pheno_type)
2979
2980    !
2981    ! Phenology : Leaf Onset
2982    !
2983
2984    !Config Key   = PHENO_GDD_CRIT_C
2985    !Config Desc  = critical gdd, tabulated (C), constant c of aT^2+bT+c
2986    !Config if    = OK_STOMATE
2987    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 270., 400., 125., 400.
2988    !Config Help  =
2989    !Config Units = [-]
2990    CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c)
2991
2992    !Config Key   = PHENO_GDD_CRIT_B
2993    !Config Desc  = critical gdd, tabulated (C), constant b of aT^2+bT+c
2994    !Config if    = OK_STOMATE
2995    !Config Def   = undef, undef, undef, undef, undef, undef, undef,undef, undef, 6.25, 0., 0., 0.
2996    !Config Help  =
2997    !Config Units = [-]
2998    CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b)
2999
3000    !Config Key   = PHENO_GDD_CRIT_A
3001    !Config Desc  = critical gdd, tabulated (C), constant a of aT^2+bT+c
3002    !Config if    = OK_STOMATE
3003    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.03125,  0., 0., 0.
3004    !Config Help  =
3005    !Config Units = [-]
3006    CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a)
3007
3008    !Config Key   = PHENO_MOIGDD_T_CRIT
3009    !Config Desc  = Average temperature threashold for C4 grass used in pheno_moigdd
3010    !Config if    = OK_STOMATE
3011    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 22.0, undef, undef
3012    !Config Help  =
3013    !Config Units = [C]
3014    CALL getin_p('PHENO_MOIGDD_T_CRIT',pheno_moigdd_t_crit)
3015
3016    !Config Key   = NGD_CRIT
3017    !Config Desc  = critical ngd, tabulated. Threshold -5 degrees
3018    !Config if    = OK_STOMATE
3019    !Config Def   = undef, undef, undef, undef, undef, undef, undef, 0., undef, undef, undef, undef, undef
3020    !Config Help  = NGD : Number of Growing Days.
3021    !Config Units = [days]
3022    CALL getin_p('NGD_CRIT',ngd_crit)
3023
3024    !Config Key   = NCDGDD_TEMP
3025    !Config Desc  = critical temperature for the ncd vs. gdd function in phenology
3026    !Config if    = OK_STOMATE
3027    !Config Def   = undef, undef, undef, undef, undef, 5., undef, 0., undef, undef, undef, undef, undef
3028    !Config Help  =
3029    !Config Units = [C]
3030    CALL getin_p('NCDGDD_TEMP',ncdgdd_temp)
3031
3032    !Config Key   = HUM_FRAC
3033    !Config Desc  = critical humidity (relative to min/max) for phenology
3034    !Config if    = OK_STOMATE
3035    !Config Def   = undef, undef, .5, undef, undef, undef, undef, undef,  undef, .5, .5, .5,.5     
3036    !Config Help  =
3037    !Config Units = [%]
3038    CALL getin_p('HUM_FRAC',hum_frac)
3039
3040    !Config Key   = HUM_MIN_TIME
3041    !Config Desc  = minimum time elapsed since moisture minimum
3042    !Config if    = OK_STOMATE
3043    !Config Def   = undef, undef, 50., undef, undef, undef, undef, undef, undef, 35., 35., 75., 75.
3044    !Config Help  =
3045    !Config Units = [days]
3046    CALL getin_p('HUM_MIN_TIME',hum_min_time)
3047
3048    !Config Key   = TAU_SAP
3049    !Config Desc  = sapwood -> heartwood conversion time
3050    !Config if    = OK_STOMATE
3051    !Config Def   = undef, 730., 730., 730., 730., 730., 730., 730., 730., undef, undef, undef, undef
3052    !Config Help  =
3053    !Config Units = [days]
3054    CALL getin_p('TAU_SAP',tau_sap)
3055
3056    !Config Key   = TAU_LEAFINIT
3057    !Config Desc  = time to attain the initial foliage using the carbohydrate reserve
3058    !Config if    = OK_STOMATE
3059    !Config Def   = undef, 10., 10., 10., 10., 10., 10., 10., 10., 10., 10., 10., 10.
3060    !Config Help  =
3061    !Config Units = [days]
3062    CALL getin_p('TAU_LEAFINIT',tau_leafinit) 
3063
3064    !Config Key   = TAU_FRUIT
3065    !Config Desc  = fruit lifetime
3066    !Config if    = OK_STOMATE
3067    !Config Def   = undef, 90., 90., 90., 90., 90., 90., 90., 90., undef, undef, undef, undef
3068    !Config Help  =
3069    !Config Units = [days]
3070    CALL getin_p('TAU_FRUIT',tau_fruit)
3071
3072    !Config Key   = ECUREUIL
3073    !Config Desc  = fraction of primary leaf and root allocation put into reserve
3074    !Config if    = OK_STOMATE
3075    !Config Def   = undef, .0, 1., .0, .0, 1., .0, 1., 1., 1., 1., 1., 1.
3076    !Config Help  =
3077    !Config Units = [-]
3078    CALL getin_p('ECUREUIL',ecureuil)
3079
3080    !Config Key   = ALLOC_MIN
3081    !Config Desc  = minimum allocation above/below = f(age) - 30/01/04 NV/JO/PF
3082    !Config if    = OK_STOMATE
3083    !Config Def   = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef
3084    !Config Help  =
3085    !Config Units = [-]
3086    CALL getin_p('ALLOC_MIN',alloc_min)
3087
3088    !Config Key   = ALLOC_MAX
3089    !Config Desc  = maximum allocation above/below = f(age) - 30/01/04 NV/JO/PF
3090    !Config if    = OK_STOMATE
3091    !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef
3092    !Config Help  =
3093    !Config Units = [-]
3094    CALL getin_p('ALLOC_MAX',alloc_max)
3095
3096    !Config Key   = DEMI_ALLOC
3097    !Config Desc  = mean allocation above/below = f(age) - 30/01/04 NV/JO/PF
3098    !Config if    = OK_STOMATE
3099    !Config Def   = undef, 5., 5., 5., 5., 5., 5., 5., 5., undef, undef, undef, undef
3100    !Config Help  =
3101    !Config Units = [-]
3102    CALL getin_p('DEMI_ALLOC',demi_alloc)
3103
3104    !Config Key   = LEAFLIFE_TAB
3105    !Config Desc  = leaf longevity
3106    !Config if    = OK_STOMATE
3107    !Config Def   = undef, .5, 2., .33, 1., 2., .33, 2., 2., 2., 2., 2., 2.
3108    !Config Help  =
3109    !Config Units = [years]
3110    CALL getin_p('LEAFLIFE_TAB',leaflife_tab)
3111
3112    !
3113    ! Phenology : Senescence
3114    !
3115    !
3116    !Config Key   = LEAFFALL
3117    !Config Desc  = length of death of leaves, tabulated
3118    !Config if    = OK_STOMATE
3119    !Config Def   = undef, undef, 10., undef, undef, 10., undef, 10., 10., 10., 10., 10., 10.
3120    !Config Help  =
3121    !Config Units = [days]
3122    CALL getin_p('LEAFFALL',leaffall)
3123
3124    !Config Key   = LEAFAGECRIT
3125    !Config Desc  = critical leaf age, tabulated
3126    !Config if    = OK_STOMATE
3127    !Config Def   = undef, 730., 180., 910., 730., 180., 910., 180., 180., 120., 120., 90., 90. 
3128    !Config Help  =
3129    !Config Units = [days]
3130    CALL getin_p('LEAFAGECRIT',leafagecrit) 
3131
3132    !Config Key   = SENESCENCE_TYPE
3133    !Config Desc  = type of senescence, tabulated
3134    !Config if    = OK_STOMATE
3135    !Config Def   = none, none, dry, none, none, cold, none, cold, cold, mixed, mixed, mixed, mixed
3136    !Config Help  =
3137    !Config Units = [-]
3138    CALL getin_p('SENESCENCE_TYPE',senescence_type) 
3139
3140    !Config Key   = SENESCENCE_HUM
3141    !Config Desc  = critical relative moisture availability for senescence
3142    !Config if    = OK_STOMATE
3143    !Config Def   = undef, undef, .3, undef, undef, undef, undef, undef, undef, .2, .2, .3, .2
3144    !Config Help  =
3145    !Config Units = [-]
3146    CALL getin_p('SENESCENCE_HUM',senescence_hum)
3147
3148    !Config Key   = NOSENESCENCE_HUM
3149    !Config Desc  = relative moisture availability above which there is no humidity-related senescence
3150    !Config if    = OK_STOMATE
3151    !Config Def   = undef, undef, .8, undef, undef, undef, undef, undef, undef, .3, .3, .3, .3
3152    !Config Help  =
3153    !Config Units = [-]
3154    CALL getin_p('NOSENESCENCE_HUM',nosenescence_hum) 
3155
3156    !Config Key   = MAX_TURNOVER_TIME
3157    !Config Desc  = maximum turnover time for grasse
3158    !Config if    = OK_STOMATE
3159    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef,  80.,  80., 80., 80.
3160    !Config Help  =
3161    !Config Units = [days]
3162    CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time)
3163
3164    !Config Key   = MIN_TURNOVER_TIME
3165    !Config Desc  = minimum turnover time for grasse
3166    !Config if    = OK_STOMATE
3167    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 10., 10., 10., 10.
3168    !Config Help  =
3169    !Config Units = [days]
3170    CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time)
3171
3172    !Config Key   = MIN_LEAF_AGE_FOR_SENESCENCE
3173    !Config Desc  = minimum leaf age to allow senescence g
3174    !Config if    = OK_STOMATE
3175    !Config Def   = undef, undef, 90., undef, undef, 90., undef, 60., 60., 30., 30., 30., 30.
3176    !Config Help  =
3177    !Config Units = [days]
3178    CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE',min_leaf_age_for_senescence)
3179
3180    !Config Key   = SENESCENCE_TEMP_C
3181    !Config Desc  = critical temperature for senescence (C), constant c of aT^2+bT+c, tabulated
3182    !Config if    = OK_STOMATE
3183    !Config Def   = undef, undef, undef, undef, undef, 12., undef, 7., 2., -1.375, 5., 5., 10.
3184    !Config Help  =
3185    !Config Units = [-]
3186    CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c)
3187
3188    !Config Key   = SENESCENCE_TEMP_B
3189    !Config Desc  = critical temperature for senescence (C), constant b of aT^2+bT+c ,tabulated
3190    !Config if    = OK_STOMATE
3191    !Config Def   = undef, undef, undef, undef, undef, 0., undef, 0., 0., .1, 0., 0., 0.
3192    !Config Help  =
3193    !Config Units = [-]
3194    CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b)
3195
3196    !Config Key   = SENESCENCE_TEMP_A
3197    !Config Desc  = critical temperature for senescence (C), constant a of aT^2+bT+c , tabulated
3198    !Config if    = OK_STOMATE
3199    !Config Def   = undef, undef, undef, undef, undef, 0., undef, 0., 0.,.00375, 0., 0., 0.
3200    !Config Help  =
3201    !Config Units = [-]
3202    CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a)
3203
3204    !Config Key   = GDD_SENESCENCE
3205    !Config Desc  = minimum gdd to allow senescence of crops 
3206    !Config if    = OK_STOMATE
3207    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 950., 4000.
3208    !Config Help  =
3209    !Config Units = [days]
3210    CALL getin_p("GDD_SENESCENCE", gdd_senescence)
3211
3212    !Config Key   = ALWAYS_INIT
3213    !Config Desc  = Take carbon from atmosphere if carbohydrate reserve too small
3214    !Config if    = OK_STOMATE
3215    !Config Def   = y, y, y, y, y, y, y, y, y, y, n, y, y
3216    !Config Help  =
3217    !Config Units = [BOOLEAN]
3218    CALL getin_p('ALWAYS_INIT',always_init)
3219
3220    !
3221    ! DGVM
3222    !
3223
3224    !Config Key   = RESIDENCE_TIME
3225    !Config Desc  = residence time of trees
3226    !Config if    = OK_DGVM and NOT(LPJ_GAP_CONST_MORT)
3227    !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
3228    !Config Help  =
3229    !Config Units = [years]
3230    CALL getin_p('RESIDENCE_TIME',residence_time)
3231
3232    !Config Key   = TMIN_CRIT
3233    !Config Desc  = critical tmin, tabulated
3234    !Config if    = OK_STOMATE
3235    !Config Def   = undef,  0.0, 0.0, -30.0, -14.0, -30.0, -45.0, -45.0, undef, undef, undef, undef, undef
3236    !Config Help  =
3237    !Config Units = [C]
3238    CALL getin_p('TMIN_CRIT',tmin_crit)
3239
3240    !Config Key   = TCM_CRIT
3241    !Config Desc  = critical tcm, tabulated
3242    !Config if    = OK_STOMATE
3243    !Config Def   = undef, undef, undef, 5.0, 15.5, 15.5, -8.0, -8.0, -8.0, undef, undef, undef, undef
3244    !Config Help  =
3245    !Config Units = [C]
3246    CALL getin_p('TCM_CRIT',tcm_crit)
3247
3248  END SUBROUTINE config_stomate_pft_parameters
3249
3250
3251!! ================================================================================================================================
3252!! SUBROUTINE   : pft_parameters_clear
3253!!
3254!>\BRIEF         This subroutine deallocates memory at the end of the simulation.
3255!!
3256!! DESCRIPTION  : None
3257!!
3258!! RECENT CHANGE(S): None
3259!!
3260!! MAIN OUTPUT VARIABLE(S): None
3261!!
3262!! REFERENCE(S) : None
3263!!
3264!! FLOWCHART    : None
3265!! \n
3266!_ ================================================================================================================================
3267
3268  SUBROUTINE pft_parameters_clear
3269
3270    l_first_pft_parameters = .TRUE.
3271
3272    IF (ALLOCATED(pft_to_mtc)) DEALLOCATE(pft_to_mtc)
3273    IF (ALLOCATED(PFT_name)) DEALLOCATE(PFT_name)
3274    IF (ALLOCATED(veget_ori_fixed_test_1)) DEALLOCATE(veget_ori_fixed_test_1)   
3275    IF (ALLOCATED(llaimax)) DEALLOCATE(llaimax)
3276    IF (ALLOCATED(llaimin)) DEALLOCATE(llaimin)
3277    IF (ALLOCATED(height_presc)) DEALLOCATE(height_presc)   
3278    IF (ALLOCATED(z0_over_height)) DEALLOCATE(z0_over_height)   
3279    IF (ALLOCATED(ratio_z0m_z0h)) DEALLOCATE(ratio_z0m_z0h)   
3280    IF (ALLOCATED(type_of_lai)) DEALLOCATE(type_of_lai)
3281    IF (ALLOCATED(is_tree)) DEALLOCATE(is_tree)
3282    IF (ALLOCATED(natural)) DEALLOCATE(natural)
3283    IF (ALLOCATED(is_deciduous)) DEALLOCATE(is_deciduous)
3284    IF (ALLOCATED(is_evergreen)) DEALLOCATE(is_evergreen)
3285    IF (ALLOCATED(is_needleleaf)) DEALLOCATE(is_needleleaf)
3286    IF (ALLOCATED(is_tropical)) DEALLOCATE(is_tropical)
3287    IF (ALLOCATED(humcste)) DEALLOCATE(humcste)
3288    IF (ALLOCATED(pref_soil_veg)) DEALLOCATE(pref_soil_veg)
3289    IF (ALLOCATED(is_c4)) DEALLOCATE(is_c4) 
3290    IF (ALLOCATED(vcmax_fix)) DEALLOCATE(vcmax_fix)
3291    IF (ALLOCATED(downregulation_co2_coeff)) DEALLOCATE(downregulation_co2_coeff) 
3292    IF (ALLOCATED(E_KmC)) DEALLOCATE(E_KmC)
3293    IF (ALLOCATED(E_KmO)) DEALLOCATE(E_KmO)
3294    IF (ALLOCATED(E_Sco)) DEALLOCATE(E_Sco)
3295    IF (ALLOCATED(E_gamma_star)) DEALLOCATE(E_gamma_star)
3296    IF (ALLOCATED(E_Vcmax)) DEALLOCATE(E_Vcmax)
3297    IF (ALLOCATED(E_Jmax)) DEALLOCATE(E_Jmax)
3298    IF (ALLOCATED(aSV)) DEALLOCATE(aSV)
3299    IF (ALLOCATED(bSV)) DEALLOCATE(bSV)
3300    IF (ALLOCATED(tphoto_min)) DEALLOCATE(tphoto_min)
3301    IF (ALLOCATED(tphoto_max)) DEALLOCATE(tphoto_max)
3302    IF (ALLOCATED(aSJ)) DEALLOCATE(aSJ)
3303    IF (ALLOCATED(bSJ)) DEALLOCATE(bSJ)
3304    IF (ALLOCATED(D_Vcmax)) DEALLOCATE(D_Vcmax)
3305    IF (ALLOCATED(D_Jmax)) DEALLOCATE(D_Jmax)
3306    IF (ALLOCATED(E_gm)) DEALLOCATE(E_gm) 
3307    IF (ALLOCATED(S_gm)) DEALLOCATE(S_gm) 
3308    IF (ALLOCATED(D_gm)) DEALLOCATE(D_gm) 
3309    IF (ALLOCATED(E_Rd)) DEALLOCATE(E_Rd)
3310    IF (ALLOCATED(Vcmax25)) DEALLOCATE(Vcmax25)
3311    IF (ALLOCATED(arJV)) DEALLOCATE(arJV)
3312    IF (ALLOCATED(brJV)) DEALLOCATE(brJV)
3313    IF (ALLOCATED(KmC25)) DEALLOCATE(KmC25)
3314    IF (ALLOCATED(KmO25)) DEALLOCATE(KmO25)
3315    IF (ALLOCATED(Sco25)) DEALLOCATE(Sco25)
3316    IF (ALLOCATED(gm25)) DEALLOCATE(gm25) 
3317    IF (ALLOCATED(gamma_star25)) DEALLOCATE(gamma_star25)
3318    IF (ALLOCATED(a1)) DEALLOCATE(a1)
3319    IF (ALLOCATED(b1)) DEALLOCATE(b1)
3320    IF (ALLOCATED(g0)) DEALLOCATE(g0)
3321    IF (ALLOCATED(h_protons)) DEALLOCATE(h_protons)
3322    IF (ALLOCATED(fpsir)) DEALLOCATE(fpsir)
3323    IF (ALLOCATED(fQ)) DEALLOCATE(fQ)
3324    IF (ALLOCATED(fpseudo)) DEALLOCATE(fpseudo)
3325    IF (ALLOCATED(kp)) DEALLOCATE(kp)
3326    IF (ALLOCATED(alpha)) DEALLOCATE(alpha)
3327    IF (ALLOCATED(gbs)) DEALLOCATE(gbs)
3328    IF (ALLOCATED(theta)) DEALLOCATE(theta)
3329    IF (ALLOCATED(alpha_LL)) DEALLOCATE(alpha_LL)
3330    IF (ALLOCATED(stress_vcmax)) DEALLOCATE(stress_vcmax)
3331    IF (ALLOCATED(stress_gs)) DEALLOCATE(stress_gs)
3332    IF (ALLOCATED(stress_gm)) DEALLOCATE(stress_gm)
3333    IF (ALLOCATED(ext_coeff)) DEALLOCATE(ext_coeff)
3334    IF (ALLOCATED(ext_coeff_vegetfrac)) DEALLOCATE(ext_coeff_vegetfrac)
3335    IF (ALLOCATED(rveg_pft)) DEALLOCATE(rveg_pft)
3336    IF (ALLOCATED(rstruct_const)) DEALLOCATE(rstruct_const)
3337    IF (ALLOCATED(kzero)) DEALLOCATE(kzero)
3338    IF (ALLOCATED(wmax_veg)) DEALLOCATE(wmax_veg)
3339    IF (ALLOCATED(throughfall_by_pft)) DEALLOCATE(throughfall_by_pft)
3340    IF (ALLOCATED(snowa_aged_vis)) DEALLOCATE(snowa_aged_vis)
3341    IF (ALLOCATED(snowa_aged_nir)) DEALLOCATE(snowa_aged_nir)
3342    IF (ALLOCATED(snowa_dec_vis)) DEALLOCATE(snowa_dec_vis)
3343    IF (ALLOCATED(snowa_dec_nir)) DEALLOCATE(snowa_dec_nir)
3344    IF (ALLOCATED(alb_leaf_vis)) DEALLOCATE(alb_leaf_vis)
3345    IF (ALLOCATED(alb_leaf_nir)) DEALLOCATE(alb_leaf_nir)   
3346    IF (ALLOCATED(em_factor_isoprene)) DEALLOCATE(em_factor_isoprene)
3347    IF (ALLOCATED(em_factor_monoterpene)) DEALLOCATE(em_factor_monoterpene)
3348    IF (ALLOCATED(em_factor_apinene)) DEALLOCATE(em_factor_apinene)
3349    IF (ALLOCATED(em_factor_bpinene)) DEALLOCATE(em_factor_bpinene)
3350    IF (ALLOCATED(em_factor_limonene)) DEALLOCATE(em_factor_limonene)
3351    IF (ALLOCATED(em_factor_myrcene)) DEALLOCATE(em_factor_myrcene)
3352    IF (ALLOCATED(em_factor_sabinene)) DEALLOCATE(em_factor_sabinene)
3353    IF (ALLOCATED(em_factor_camphene)) DEALLOCATE(em_factor_camphene)
3354    IF (ALLOCATED(em_factor_3carene)) DEALLOCATE(em_factor_3carene)
3355    IF (ALLOCATED(em_factor_tbocimene)) DEALLOCATE(em_factor_tbocimene)
3356    IF (ALLOCATED(em_factor_othermonot)) DEALLOCATE(em_factor_othermonot)
3357    IF (ALLOCATED(em_factor_sesquiterp)) DEALLOCATE(em_factor_sesquiterp)
3358    IF (ALLOCATED(em_factor_ORVOC)) DEALLOCATE(em_factor_ORVOC)
3359    IF (ALLOCATED(em_factor_OVOC)) DEALLOCATE(em_factor_OVOC)
3360    IF (ALLOCATED(em_factor_MBO)) DEALLOCATE(em_factor_MBO)
3361    IF (ALLOCATED(em_factor_methanol)) DEALLOCATE(em_factor_methanol)
3362    IF (ALLOCATED(em_factor_acetone)) DEALLOCATE(em_factor_acetone)
3363    IF (ALLOCATED(em_factor_acetal)) DEALLOCATE(em_factor_acetal)
3364    IF (ALLOCATED(em_factor_formal)) DEALLOCATE(em_factor_formal)
3365    IF (ALLOCATED(em_factor_acetic)) DEALLOCATE(em_factor_acetic)
3366    IF (ALLOCATED(em_factor_formic)) DEALLOCATE(em_factor_formic)
3367    IF (ALLOCATED(em_factor_no_wet)) DEALLOCATE(em_factor_no_wet)
3368    IF (ALLOCATED(em_factor_no_dry)) DEALLOCATE(em_factor_no_dry)
3369    IF (ALLOCATED(Larch)) DEALLOCATE(Larch)
3370    IF (ALLOCATED(leaf_tab)) DEALLOCATE(leaf_tab)
3371    IF (ALLOCATED(sla)) DEALLOCATE(sla)
3372    IF (ALLOCATED(availability_fact)) DEALLOCATE(availability_fact)
3373    IF (ALLOCATED(R0)) DEALLOCATE(R0)
3374    IF (ALLOCATED(S0)) DEALLOCATE(S0)
3375    IF (ALLOCATED(L0)) DEALLOCATE(L0)
3376    IF (ALLOCATED(frac_growthresp)) DEALLOCATE(frac_growthresp)
3377    IF (ALLOCATED(maint_resp_slope)) DEALLOCATE(maint_resp_slope)
3378    IF (ALLOCATED(maint_resp_slope_c)) DEALLOCATE(maint_resp_slope_c)
3379    IF (ALLOCATED(maint_resp_slope_b)) DEALLOCATE(maint_resp_slope_b)
3380    IF (ALLOCATED(maint_resp_slope_a)) DEALLOCATE(maint_resp_slope_a)
3381    IF (ALLOCATED(coeff_maint_zero)) DEALLOCATE(coeff_maint_zero)
3382    IF (ALLOCATED(cm_zero_leaf)) DEALLOCATE(cm_zero_leaf)
3383    IF (ALLOCATED(cm_zero_sapabove)) DEALLOCATE(cm_zero_sapabove)
3384    IF (ALLOCATED(cm_zero_sapbelow)) DEALLOCATE(cm_zero_sapbelow)
3385    IF (ALLOCATED(cm_zero_heartabove)) DEALLOCATE(cm_zero_heartabove)
3386    IF (ALLOCATED(cm_zero_heartbelow)) DEALLOCATE(cm_zero_heartbelow)
3387    IF (ALLOCATED(cm_zero_root)) DEALLOCATE(cm_zero_root)
3388    IF (ALLOCATED(cm_zero_fruit)) DEALLOCATE(cm_zero_fruit)
3389    IF (ALLOCATED(cm_zero_carbres)) DEALLOCATE(cm_zero_carbres)
3390    IF (ALLOCATED(flam)) DEALLOCATE(flam)
3391    IF (ALLOCATED(resist)) DEALLOCATE(resist)
3392    IF (ALLOCATED(coeff_lcchange_1)) DEALLOCATE(coeff_lcchange_1)
3393    IF (ALLOCATED(coeff_lcchange_10)) DEALLOCATE(coeff_lcchange_10)
3394    IF (ALLOCATED(coeff_lcchange_100)) DEALLOCATE(coeff_lcchange_100)
3395    IF (ALLOCATED(lai_max_to_happy)) DEALLOCATE(lai_max_to_happy)
3396    IF (ALLOCATED(lai_max)) DEALLOCATE(lai_max)
3397    IF (ALLOCATED(pheno_model)) DEALLOCATE(pheno_model)
3398    IF (ALLOCATED(pheno_type)) DEALLOCATE(pheno_type)
3399    IF (ALLOCATED(pheno_gdd_crit_c)) DEALLOCATE(pheno_gdd_crit_c)
3400    IF (ALLOCATED(pheno_gdd_crit_b)) DEALLOCATE(pheno_gdd_crit_b)
3401    IF (ALLOCATED(pheno_gdd_crit_a)) DEALLOCATE(pheno_gdd_crit_a)
3402    IF (ALLOCATED(pheno_gdd_crit)) DEALLOCATE(pheno_gdd_crit)
3403    IF (ALLOCATED(pheno_moigdd_t_crit)) DEALLOCATE(pheno_moigdd_t_crit)
3404    IF (ALLOCATED(ngd_crit)) DEALLOCATE(ngd_crit)
3405    IF (ALLOCATED(ncdgdd_temp)) DEALLOCATE(ncdgdd_temp)
3406    IF (ALLOCATED(hum_frac)) DEALLOCATE(hum_frac)
3407    IF (ALLOCATED(hum_min_time)) DEALLOCATE(hum_min_time)
3408    IF (ALLOCATED(tau_sap)) DEALLOCATE(tau_sap)
3409    IF (ALLOCATED(tau_leafinit)) DEALLOCATE(tau_leafinit)
3410    IF (ALLOCATED(tau_fruit)) DEALLOCATE(tau_fruit)
3411    IF (ALLOCATED(ecureuil)) DEALLOCATE(ecureuil)
3412    IF (ALLOCATED(alloc_min)) DEALLOCATE(alloc_min)
3413    IF (ALLOCATED(alloc_max)) DEALLOCATE(alloc_max)
3414    IF (ALLOCATED(demi_alloc)) DEALLOCATE(demi_alloc)
3415    IF (ALLOCATED(leaflife_tab)) DEALLOCATE(leaflife_tab)
3416    IF (ALLOCATED(leaffall)) DEALLOCATE(leaffall)
3417    IF (ALLOCATED(leafagecrit)) DEALLOCATE(leafagecrit)
3418    IF (ALLOCATED(senescence_type)) DEALLOCATE(senescence_type)
3419    IF (ALLOCATED(senescence_hum)) DEALLOCATE(senescence_hum)
3420    IF (ALLOCATED(nosenescence_hum)) DEALLOCATE(nosenescence_hum)
3421    IF (ALLOCATED(max_turnover_time)) DEALLOCATE(max_turnover_time)
3422    IF (ALLOCATED(min_turnover_time)) DEALLOCATE(min_turnover_time)
3423    IF (ALLOCATED(min_leaf_age_for_senescence)) DEALLOCATE(min_leaf_age_for_senescence)
3424    IF (ALLOCATED(senescence_temp_c)) DEALLOCATE(senescence_temp_c)
3425    IF (ALLOCATED(senescence_temp_b)) DEALLOCATE(senescence_temp_b)
3426    IF (ALLOCATED(senescence_temp_a)) DEALLOCATE(senescence_temp_a)
3427    IF (ALLOCATED(senescence_temp)) DEALLOCATE(senescence_temp)
3428    IF (ALLOCATED(gdd_senescence)) DEALLOCATE(gdd_senescence)
3429    IF (ALLOCATED(always_init)) DEALLOCATE(always_init)
3430    IF (ALLOCATED(residence_time)) DEALLOCATE(residence_time)
3431    IF (ALLOCATED(tmin_crit)) DEALLOCATE(tmin_crit)
3432    IF (ALLOCATED(tcm_crit)) DEALLOCATE(tcm_crit)
3433    IF (ALLOCATED(lai_initmin)) DEALLOCATE(lai_initmin)
3434    IF (ALLOCATED(bm_sapl)) DEALLOCATE(bm_sapl)
3435    IF (ALLOCATED(migrate)) DEALLOCATE(migrate)
3436    IF (ALLOCATED(maxdia)) DEALLOCATE(maxdia)
3437    IF (ALLOCATED(cn_sapl)) DEALLOCATE(cn_sapl)
3438    IF (ALLOCATED(leaf_timecst)) DEALLOCATE(leaf_timecst)
3439
3440  END SUBROUTINE pft_parameters_clear
3441
3442END MODULE pft_parameters
Note: See TracBrowser for help on using the repository browser.