source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_parameters/pft_parameters.f90 @ 8398

Last change on this file since 8398 was 6957, checked in by fabienne.maignan, 4 years ago

Update before parameters optimization

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