source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_parameters/pft_parameters.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

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