source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_parameters/pft_parameters.f90 @ 7541

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