source: branches/publications/ORCHIDEE_gmd_2018_MICT-LEAK/src_parameters/pft_parameters.f90 @ 7442

Last change on this file since 7442 was 4977, checked in by simon.bowring, 6 years ago

Currently running (13/02/2018) version includes all necessarily changes to include DOC in MICT code... further parametrisation necessary to equate soil pools with those of normal forcesoil restarts

  • Property svn:keywords set to Date Revision
File size: 190.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module initializes all the pft parameters in function of the
10!!              number of vegetation types and of the values chosen by the user.
11!!
12!!\n DESCRIPTION:  This module allocates and initializes the pft parameters in function of the number of pfts
13!!                 and the values of the parameters. \n
14!!                 The number of PFTs is read in control.f90 (subroutine control_initialize). \n
15!!                 Then we can initialize the parameters. \n
16!!                 This module is the result of the merge of constantes_co2, constantes_veg, stomate_constants.\n
17!!
18!! RECENT CHANGE(S): Josefine Ghattas 2013 : The declaration part has been extracted and moved to module pft_parameters_var
19!!
20!! REFERENCE(S) : None
21!!
22!! SVN          :
23!! $HeadURL: $
24!! $Date$
25!! $Revision$
26!! \n
27!_ ================================================================================================================================
28
29MODULE pft_parameters
30
31  USE pft_parameters_var
32  USE vertical_soil_var
33  USE constantes_mtc
34  USE constantes
35  USE constantes_soil_var !!! only for nstm & pref_soil_veg
36  USE ioipsl
37  USE ioipsl_para 
38  USE defprec
39
40  IMPLICIT NONE
41
42CONTAINS
43 
44
45!! ================================================================================================================================
46!! SUBROUTINE   : pft_parameters_main
47!!
48!>\BRIEF          This subroutine initializes all the pft parameters in function of the
49!! number of vegetation types chosen by the user.
50!!
51!! DESCRIPTION  : This subroutine is called after the reading of the number of PFTS and the options
52!!                activated by the user in the configuration files. \n
53!!                The allocation is done just before reading the correspondence table  between PFTs and MTCs
54!!                defined by the user in the configuration file.\n
55!!                With the correspondence table, the subroutine can initialize the pft parameters in function
56!!                of the flags activated (ok_sechiba, ok_stomate, ok_co2, routing, new_hydrol...) in order to
57!!                optimize the memory allocation. \n
58!!                If the number of PFTs and pft_to_mtc are not found, the standard configuration will be used
59!!                (13 PFTs, PFT = MTC). \n
60!!                Some restrictions : the pft 1 can only be the bare soil and it is unique. \n
61!!                Algorithm : Build new PFT from 13 generic-PFT or meta-classes.
62!!                1. Read the number of PFTs in "run.def". If nothing is found, it is assumed that the user intend to use
63!!                   the standard of PFTs (13).
64!!                2. Read the index vector in "run.def". The index vector associates one PFT to one meta-classe (or generic PFT).
65!!                   When the association is done, the PFT defined by the user inherited the default values from the meta classe.
66!!                   If nothing is found, it is assumed to use the standard index vector (PFT = MTC).
67!!                3. Check consistency
68!!                4. Memory allocation and initialization.
69!!                5. The parameters are read in the configuration file in config_initialize (control module).
70!!
71!! RECENT CHANGE(S): None
72!!
73!! MAIN OUTPUT VARIABLE(S): None
74!!
75!! REFERENCE(S) : None
76!!
77!! FLOWCHART    : None
78!! \n
79!_ ================================================================================================================================
80
81  SUBROUTINE pft_parameters_main()
82
83    IMPLICIT NONE
84
85    !! 0. Variables and parameters declaration
86
87    !! 0.4 Local variables 
88
89    INTEGER(i_std) :: j                             !! Index (unitless)
90
91    !_ ================================================================================================================================
92
93    !
94    ! PFT global
95    !
96
97    IF(l_first_pft_parameters) THEN
98
99       !! 1. First time step
100       IF(printlev>=3) THEN
101          WRITE(numout,*) 'l_first_pft_parameters :we read the parameters from the def files'
102       ENDIF
103
104       !! 2. Memory allocation for the pfts-parameters
105       CALL pft_parameters_alloc()
106
107       !! 3. Correspondance table
108
109       !! 3.1 Initialisation of the correspondance table
110       !! Initialisation of the correspondance table
111       DO j = 1, nvm
112          pft_to_mtc(j) = j
113       ENDDO ! j=1, nvm
114
115       !! 3.2 Reading of the conrrespondance table in the .def file
116       !
117       !Config Key   = PFT_TO_MTC
118       !Config Desc  = correspondance array linking a PFT to MTC
119       !Config if    = OK_SECHIBA or OK_STOMATE
120       !Config Def   = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
121       !Config Help  =
122       !Config Units = [-]
123       CALL getin_p('PFT_TO_MTC',pft_to_mtc)
124
125       !! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array
126       !!     If the configuration is wrong, send a error message to the user.
127       IF(nvm /= nvmc ) THEN
128          !
129          IF(pft_to_mtc(1) == undef_int) THEN
130             STOP ' The array PFT_TO_MTC is empty : we stop'
131          ENDIF !(pft_to_mtc(1) == undef_int)
132          !
133       ENDIF !(nvm /= nvmc )
134
135       !! 3.4 Some error messages
136
137       !! 3.4.1 What happened if pft_to_mtc(j) > nvmc or pft_to_mtc(j) <=0 (if the mtc doesn't exist)?
138       DO j = 1, nvm ! Loop over # PFTs 
139          !
140          IF( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) ) THEN
141             WRITE(numout,*) 'the metaclass chosen does not exist'
142             STOP 'we stop reading pft_to_mtc'
143          ENDIF !( (pft_to_mtc(j) > nvmc) .OR. (pft_to_mtc(j) <= 0) )
144          !
145       ENDDO  ! Loop over # PFTs 
146
147
148       !! 3.4.2 Check if pft_to_mtc(1) = 1
149       IF(pft_to_mtc(1) /= 1) THEN
150          !
151          WRITE(numout,*) 'the first pft has to be the bare soil'
152          STOP 'we stop reading next values of pft_to_mtc'
153          !
154       ELSE
155          !
156          DO j = 2,nvm ! Loop over # PFTs different from bare soil
157             !
158             IF(pft_to_mtc(j) == 1) THEN
159                WRITE(numout,*) 'only pft_to_mtc(1) has to be the bare soil'
160                STOP 'we stop reading pft_to_mtc'
161             ENDIF ! (pft_to_mtc(j) == 1)
162             !
163          ENDDO ! Loop over # PFTs different from bare soil
164          !
165       ENDIF !(pft_to_mtc(1) /= 1)
166
167
168       !! 4.Initialisation of the pfts-parameters
169       CALL pft_parameters_init()
170
171       !! 5. Useful data
172
173       !! 5.1 Read the name of the PFTs given by the user
174       !
175       !Config Key   = PFT_NAME
176       !Config Desc  = Name of a PFT
177       !Config if    = OK_SECHIBA or OK_STOMATE
178       !Config Def   = bare ground, tropical broad-leaved evergreen, tropical broad-leaved raingreen,
179       !Config         temperate needleleaf evergreen, temperate broad-leaved evergreen temperate broad-leaved summergreen,
180       !Config         boreal needleleaf evergreen, boreal broad-leaved summergreen, boreal needleleaf summergreen,
181       !Config         C3 grass, C4 grass, C3 agriculture, C4 agriculture   
182       !Config Help  = the user can name the new PFTs he/she introducing for new species
183       !Config Units = [-]
184       CALL getin_p('PFT_NAME',pft_name)
185
186       !! 5.2 A useful message to the user: correspondance between the number of the pft
187       !! and the name of the associated mtc
188       DO j = 1,nvm ! Loop over # PFTs
189          !
190          WRITE(numout,*) 'the PFT',j, 'called  ', PFT_name(j),'corresponds to the MTC : ',MTC_name(pft_to_mtc(j))
191          !
192       ENDDO ! Loop over # PFTs
193
194
195       !! 6. End message
196       IF(printlev>=3) THEN
197          WRITE(numout,*) 'pft_parameters_done'
198       ENDIF
199
200       !! 8. Reset flag
201       l_first_pft_parameters = .FALSE.
202
203    ELSE
204
205       RETURN
206
207    ENDIF !(l_first_pft_parameters)
208
209  END SUBROUTINE pft_parameters_main
210
211
212!! ================================================================================================================================
213!! SUBROUTINE   : pft_parameters_init
214!!
215!>\BRIEF          This subroutine initializes all the pft parameters by the default values
216!! of the corresponding metaclasse.
217!!
218!! DESCRIPTION  : This subroutine is called after the reading of the number of PFTS and the correspondence
219!!                table defined by the user in the configuration files. \n
220!!                With the correspondence table, the subroutine can search the default values for the parameter
221!!                even if the PFTs are classified in a random order (except bare soil). \n
222!!                With the correspondence table, the subroutine can initialize the pft parameters in function
223!!                of the flags activated (ok_sechiba, ok_stomate, ok_co2, routing, new_hydrol...).\n
224!!
225!! RECENT CHANGE(S): Didier Solyga : Simplified PFT loops : use vector notation.
226!!
227!! MAIN OUTPUT VARIABLE(S): None
228!!
229!! REFERENCE(S) : None
230!!
231!! FLOWCHART    : None
232!! \n
233!_ ================================================================================================================================
234
235  SUBROUTINE pft_parameters_init()
236
237    IMPLICIT NONE
238
239    !! 0. Variables and parameters declaration
240
241    !! 0.1 Input variables
242    INTEGER(i_std)                :: jv            !! Index (unitless)
243    !_ ================================================================================================================================
244
245   ! 1.1 For parameters used anytime
246   
247   PFT_name(:) = MTC_name(pft_to_mtc(:))
248   !
249   ! Vegetation structure
250   !
251   veget_ori_fixed_test_1(:) = veget_ori_fixed_mtc(pft_to_mtc(:))
252   llaimax(:) = llaimax_mtc(pft_to_mtc(:))
253   llaimin(:) = llaimin_mtc(pft_to_mtc(:))
254   height_presc(:) = height_presc_mtc(pft_to_mtc(:))
255   z0_over_height(:) = z0_over_height_mtc(pft_to_mtc(:))
256   ratio_z0m_z0h(:) = ratio_z0m_z0h_mtc(pft_to_mtc(:))
257   type_of_lai(:) = type_of_lai_mtc(pft_to_mtc(:))
258   natural(:) = natural_mtc(pft_to_mtc(:))
259! dgvmjc
260    pasture(:) = pasture_mtc(pft_to_mtc(:))
261! end dgvmjc
262   !
263   ! Water - sechiba
264   !
265   IF (zmaxh == 2.0) THEN
266      WRITE(numout,*)'Initialize humcst using reference values for 2m soil depth'
267      humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
268   ELSE IF (zmaxh == 4.0) THEN
269      WRITE(numout,*)'Initialize humcst using reference values for 4m soil depth'
270      humcste(:) = humcste_ref4m(pft_to_mtc(:))  ! values for 4m soil depth
271   ELSE
272      WRITE(numout,*)'Note that humcste is initialized with values for 2m soil depth bur zmaxh=', zmaxh
273      humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
274   END IF
275
276   irrig_threshold(:) = irrig_threshold_mtc(pft_to_mtc(:))
277   irrig_fulfill(:) = irrig_fulfill_mtc(pft_to_mtc(:))
278   !
279   ! Soil - vegetation
280   !
281   pref_soil_veg(:) = pref_soil_veg_mtc(pft_to_mtc(:))
282   !
283   !
284   ! Vegetation - age classes
285   !
286   agec_group(:) = agec_group_mtc(pft_to_mtc(:))
287   !
288   ! Photosynthesis
289   !
290   is_c4(:) = is_c4_mtc(pft_to_mtc(:))
291   vcmax_fix(:) = vcmax_fix_mtc(pft_to_mtc(:))
292   downregulation_co2_coeff(:) = downregulation_co2_coeff_mtc(pft_to_mtc(:))
293   E_KmC(:)      = E_KmC_mtc(pft_to_mtc(:))
294   E_KmO(:)      = E_KmO_mtc(pft_to_mtc(:))
295   E_Sco(:)      = E_Sco_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_gm(:)       = E_gm_mtc(pft_to_mtc(:)) 
308   S_gm(:)       = S_gm_mtc(pft_to_mtc(:)) 
309   D_gm(:)       = D_gm_mtc(pft_to_mtc(:))
310   E_Rd(:)       = E_Rd_mtc(pft_to_mtc(:))
311   Vcmax25(:)    = Vcmax25_mtc(pft_to_mtc(:))
312   arJV(:)       = arJV_mtc(pft_to_mtc(:))
313   brJV(:)       = brJV_mtc(pft_to_mtc(:))
314   KmC25(:)      = KmC25_mtc(pft_to_mtc(:))
315   KmO25(:)      = KmO25_mtc(pft_to_mtc(:))
316   Sco25(:)      = Sco25_mtc(pft_to_mtc(:)) 
317   gm25(:)       = gm25_mtc(pft_to_mtc(:)) 
318   gamma_star25(:)  = gamma_star25_mtc(pft_to_mtc(:))
319   a1(:)         = a1_mtc(pft_to_mtc(:))
320   b1(:)         = b1_mtc(pft_to_mtc(:))
321   g0(:)         = g0_mtc(pft_to_mtc(:))
322   h_protons(:)  = h_protons_mtc(pft_to_mtc(:))
323   fpsir(:)      = fpsir_mtc(pft_to_mtc(:))
324   fQ(:)         = fQ_mtc(pft_to_mtc(:))     
325   fpseudo(:)    = fpseudo_mtc(pft_to_mtc(:))   
326   kp(:)         = kp_mtc(pft_to_mtc(:))
327   alpha(:)      = alpha_mtc(pft_to_mtc(:))
328   gbs(:)        = gbs_mtc(pft_to_mtc(:))
329   theta(:)      = theta_mtc(pft_to_mtc(:))       
330   alpha_LL(:)   = alpha_LL_mtc(pft_to_mtc(:))
331   stress_vcmax(:) = stress_vcmax_mtc(pft_to_mtc(:)) 
332   stress_gs(:)    = stress_gs_mtc(pft_to_mtc(:)) 
333   stress_gm(:)    = stress_gm_mtc(pft_to_mtc(:)) 
334   ext_coeff(:) = ext_coeff_mtc(pft_to_mtc(:))
335   ext_coeff_vegetfrac(:) = ext_coeff_vegetfrac_mtc(pft_to_mtc(:))
336   !
337   !! Define labels from physiologic characteristics
338   !
339   leaf_tab(:) = leaf_tab_mtc(pft_to_mtc(:)) 
340   pheno_model(:) = pheno_model_mtc(pft_to_mtc(:))   
341   !
342   is_tree(:) = .FALSE.
343   DO jv = 1,nvm
344      IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
345   END DO
346      !
347   is_deciduous(:) = .FALSE.
348   DO jv = 1,nvm
349      IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
350   END DO
351   !
352   is_evergreen(:) = .FALSE.
353   DO jv = 1,nvm
354      IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
355   END DO
356   !
357   is_needleleaf(:) = .FALSE.
358   DO jv = 1,nvm
359      IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
360   END DO
361
362
363    !
364    ! 1. Correspondance between the PFTs values and thes MTCs values
365    !
366
367   IF (ok_sechiba) THEN
368      !
369      ! Vegetation structure - sechiba
370      !
371      rveg_pft(:) = rveg_mtc(pft_to_mtc(:))
372      !
373      ! Evapotranspiration -  sechiba
374      !
375      rstruct_const(:) = rstruct_const_mtc(pft_to_mtc(:))
376      kzero(:) = kzero_mtc(pft_to_mtc(:))
377      !
378      ! Water - sechiba
379      !
380      wmax_veg(:) = wmax_veg_mtc(pft_to_mtc(:))
381      IF ( hydrol_cwrr .AND. OFF_LINE_MODE ) THEN
382         throughfall_by_pft(:) = 0.
383      ELSE
384         throughfall_by_pft(:) = throughfall_by_mtc(pft_to_mtc(:))
385      ENDIF
386      !
387      ! Albedo - sechiba
388      !
389      snowa_aged_vis(:) = snowa_aged_vis_mtc(pft_to_mtc(:))
390      snowa_aged_nir(:) = snowa_aged_nir_mtc(pft_to_mtc(:))
391      snowa_dec_vis(:) = snowa_dec_vis_mtc(pft_to_mtc(:)) 
392      snowa_dec_nir(:) = snowa_dec_nir_mtc(pft_to_mtc(:)) 
393      alb_leaf_vis(:) = alb_leaf_vis_mtc(pft_to_mtc(:)) 
394      alb_leaf_nir(:) = alb_leaf_nir_mtc(pft_to_mtc(:))
395      !-
396
397      !chaoyue+
398      ! Permafrost - sechiba
399      permafrost_veg_exists(:)= permafrost_veg_exists_mtc(pft_to_mtc(:))
400      !chaoyue-
401     
402   ENDIF !(ok_sechiba)
403
404    ! 1.1 For parameters used anytime
405
406    PFT_name(:) = MTC_name(pft_to_mtc(:))
407    !
408    ! Vegetation structure
409    !
410    veget_ori_fixed_test_1(:) = veget_ori_fixed_mtc(pft_to_mtc(:))
411    llaimax(:) = llaimax_mtc(pft_to_mtc(:))
412    llaimin(:) = llaimin_mtc(pft_to_mtc(:))
413    height_presc(:) = height_presc_mtc(pft_to_mtc(:))
414    z0_over_height(:) = z0_over_height_mtc(pft_to_mtc(:))
415    ratio_z0m_z0h(:) = ratio_z0m_z0h_mtc(pft_to_mtc(:))
416    type_of_lai(:) = type_of_lai_mtc(pft_to_mtc(:))
417    natural(:) = natural_mtc(pft_to_mtc(:))
418    !
419    ! Water - sechiba
420    !
421    IF (zmaxh == 2.0) THEN
422       WRITE(numout,*)'Initialize humcst using reference values for 2m soil depth'
423       humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
424    ELSE IF (zmaxh == 4.0) THEN
425       WRITE(numout,*)'Initialize humcst using reference values for 4m soil depth'
426       humcste(:) = humcste_ref4m(pft_to_mtc(:))  ! values for 4m soil depth
427    ELSE
428       WRITE(numout,*)'Note that humcste is initialized with values for 2m soil depth bur zmaxh=', zmaxh
429       humcste(:) = humcste_ref2m(pft_to_mtc(:))  ! values for 2m soil depth
430    END IF
431    !
432    ! Soil - vegetation
433    !
434    pref_soil_veg(:) = pref_soil_veg_mtc(pft_to_mtc(:))
435    !
436    ! Photosynthesis
437    !
438    is_c4(:) = is_c4_mtc(pft_to_mtc(:))
439    vcmax_fix(:) = vcmax_fix_mtc(pft_to_mtc(:))
440    downregulation_co2_coeff(:) = downregulation_co2_coeff_mtc(pft_to_mtc(:))
441    E_KmC(:)      = E_KmC_mtc(pft_to_mtc(:))
442    E_KmO(:)      = E_KmO_mtc(pft_to_mtc(:))
443    E_Sco(:)      = E_Sco_mtc(pft_to_mtc(:))
444    E_gamma_star(:) = E_gamma_star_mtc(pft_to_mtc(:))
445    E_Vcmax(:)    = E_Vcmax_mtc(pft_to_mtc(:))
446    E_Jmax(:)     = E_Jmax_mtc(pft_to_mtc(:))
447    aSV(:)        = aSV_mtc(pft_to_mtc(:))
448    bSV(:)        = bSV_mtc(pft_to_mtc(:))
449    tphoto_min(:) = tphoto_min_mtc(pft_to_mtc(:))
450    tphoto_max(:) = tphoto_max_mtc(pft_to_mtc(:))
451    aSJ(:)        = aSJ_mtc(pft_to_mtc(:))
452    bSJ(:)        = bSJ_mtc(pft_to_mtc(:))
453    D_Vcmax(:)     = D_Vcmax_mtc(pft_to_mtc(:))
454    D_Jmax(:)     = D_Jmax_mtc(pft_to_mtc(:))
455    E_gm(:)       = E_gm_mtc(pft_to_mtc(:)) 
456    S_gm(:)       = S_gm_mtc(pft_to_mtc(:)) 
457    D_gm(:)       = D_gm_mtc(pft_to_mtc(:)) 
458    E_Rd(:)       = E_Rd_mtc(pft_to_mtc(:))
459    Vcmax25(:)    = Vcmax25_mtc(pft_to_mtc(:))
460    arJV(:)       = arJV_mtc(pft_to_mtc(:))
461    brJV(:)       = brJV_mtc(pft_to_mtc(:))
462    KmC25(:)      = KmC25_mtc(pft_to_mtc(:))
463    KmO25(:)      = KmO25_mtc(pft_to_mtc(:))
464    Sco25(:)      = Sco25_mtc(pft_to_mtc(:))
465    gm25(:)       = gm25_mtc(pft_to_mtc(:)) 
466    gamma_star25(:)  = gamma_star25_mtc(pft_to_mtc(:))
467    a1(:)         = a1_mtc(pft_to_mtc(:))
468    b1(:)         = b1_mtc(pft_to_mtc(:))
469    g0(:)         = g0_mtc(pft_to_mtc(:))
470    h_protons(:)  = h_protons_mtc(pft_to_mtc(:))
471    fpsir(:)      = fpsir_mtc(pft_to_mtc(:))
472    fQ(:)         = fQ_mtc(pft_to_mtc(:))     
473    fpseudo(:)    = fpseudo_mtc(pft_to_mtc(:))   
474    kp(:)         = kp_mtc(pft_to_mtc(:))
475    alpha(:)      = alpha_mtc(pft_to_mtc(:))
476    gbs(:)        = gbs_mtc(pft_to_mtc(:))
477    theta(:)      = theta_mtc(pft_to_mtc(:))       
478    alpha_LL(:)   = alpha_LL_mtc(pft_to_mtc(:))
479    stress_vcmax(:) = stress_vcmax_mtc(pft_to_mtc(:))
480    stress_gs(:)    = stress_gs_mtc(pft_to_mtc(:))
481    stress_gm(:)    = stress_gm_mtc(pft_to_mtc(:))
482    ext_coeff(:) = ext_coeff_mtc(pft_to_mtc(:))
483    ext_coeff_vegetfrac(:) = ext_coeff_vegetfrac_mtc(pft_to_mtc(:))
484    !
485    !! Define labels from physiologic characteristics
486    !
487    leaf_tab(:) = leaf_tab_mtc(pft_to_mtc(:)) 
488    pheno_model(:) = pheno_model_mtc(pft_to_mtc(:))   
489    !
490    is_tree(:) = .FALSE.
491    DO jv = 1,nvm
492       IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
493    END DO
494    !
495    is_deciduous(:) = .FALSE.
496    DO jv = 1,nvm
497       IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
498    END DO
499    !
500    is_evergreen(:) = .FALSE.
501    DO jv = 1,nvm
502       IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
503    END DO
504    !
505    is_needleleaf(:) = .FALSE.
506    DO jv = 1,nvm
507       IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
508    END DO
509
510
511    ! 1.2 For sechiba parameters
512
513   IF (ok_stomate) THEN
514      bm_sapl(:,:,:) = zero
515      maxdia(:) = undef
516      migrate(:) = undef
517      cn_sapl(:) = undef
518      leaf_timecst(:) = undef
519      lai_initmin(:) = undef
520      !
521      ! Vegetation structure - stomate
522      !
523      sla(:) = sla_mtc(pft_to_mtc(:))
524      availability_fact(:) = availability_fact_mtc(pft_to_mtc(:))
525      !
526      ! Allocation - stomate
527      !
528      R0(:) = R0_mtc(pft_to_mtc(:)) 
529      S0(:) = S0_mtc(pft_to_mtc(:)) 
530      !
531      !pss+:Wetland CH4 methane
532      !
533      rdepth_v(:) = rdepth_v_mtc(pft_to_mtc(:))
534      sdepth_v(:) = sdepth_v_mtc(pft_to_mtc(:))
535      tveg_v(:) = tveg_v_mtc(pft_to_mtc(:))
536      !pss-
537
538      !
539      ! Respiration - stomate
540      !
541      frac_growthresp(:) = frac_growthresp_mtc(pft_to_mtc(:)) 
542      maint_resp_slope_c(:) = maint_resp_slope_c_mtc(pft_to_mtc(:))               
543      maint_resp_slope_b(:) = maint_resp_slope_b_mtc(pft_to_mtc(:))
544      maint_resp_slope_a(:) = maint_resp_slope_a_mtc(pft_to_mtc(:))
545      cm_zero_leaf(:) = cm_zero_leaf_mtc(pft_to_mtc(:))
546      cm_zero_sapabove(:) = cm_zero_sapabove_mtc(pft_to_mtc(:))
547      cm_zero_sapbelow(:) = cm_zero_sapbelow_mtc(pft_to_mtc(:)) 
548      cm_zero_heartabove(:) = cm_zero_heartabove_mtc(pft_to_mtc(:)) 
549      cm_zero_heartbelow(:) = cm_zero_heartbelow_mtc(pft_to_mtc(:))
550      cm_zero_root(:) = cm_zero_root_mtc(pft_to_mtc(:))
551      cm_zero_fruit(:) = cm_zero_fruit_mtc(pft_to_mtc(:))
552      cm_zero_carbres(:) = cm_zero_carbres_mtc(pft_to_mtc(:))
553      !
554      ! Fire - stomate
555      !
556      flam(:) = flam_mtc(pft_to_mtc(:))
557      resist(:) = resist_mtc(pft_to_mtc(:))
558      !spitfire
559      dens_fuel(:) = dens_fuel_mtc(pft_to_mtc(:))
560      f_sh(:) = f_sh_mtc(pft_to_mtc(:))
561      crown_length(:) = crown_length_mtc(pft_to_mtc(:))
562      BTpar1(:) = BTpar1_mtc(pft_to_mtc(:))
563      BTpar2(:) = BTpar2_mtc(pft_to_mtc(:))
564      r_ck(:) = r_ck_mtc(pft_to_mtc(:))
565      p_ck(:) = p_ck_mtc(pft_to_mtc(:))
566      ef_CO2(:) = ef_CO2_mtc(pft_to_mtc(:))
567      ef_CO(:) = ef_CO_mtc(pft_to_mtc(:))
568      ef_CH4(:) = ef_CH4_mtc(pft_to_mtc(:))
569      ef_VOC(:) = ef_VOC_mtc(pft_to_mtc(:))
570      ef_TPM(:) = ef_TPM_mtc(pft_to_mtc(:))
571      ef_NOx(:) = ef_NOx_mtc(pft_to_mtc(:))
572      me(:) = me_mtc(pft_to_mtc(:))
573      fire_max_cf_100hr(:) = fire_max_cf_100hr_mtc(pft_to_mtc(:))
574      fire_max_cf_1000hr(:) = fire_max_cf_1000hr_mtc(pft_to_mtc(:))
575      !endspit
576      !
577      ! grassland management
578      !
579      !gmjc
580      is_grassland_manag(:) = is_grassland_manag_mtc(pft_to_mtc(:))
581      is_grassland_cut(:) = is_grassland_cut_mtc(pft_to_mtc(:))
582      is_grassland_grazed(:) = is_grassland_grazed_mtc(pft_to_mtc(:))
583      management_intensity(:) = management_intensity_mtc(pft_to_mtc(:))
584      management_start(:) = management_start_mtc(pft_to_mtc(:))
585      deposition_start(:) = deposition_start_mtc(pft_to_mtc(:))
586      nb_year_management(:) = nb_year_management_mtc(pft_to_mtc(:))
587      sla_min(:) = sla_min_mtc(pft_to_mtc(:))
588      sla_max(:) = sla_max_mtc(pft_to_mtc(:))
589      !end gmjc
590
591      !
592      ! Flux - LUC
593      !
594      coeff_lcchange_1(:) = coeff_lcchange_1_mtc(pft_to_mtc(:))
595      coeff_lcchange_10(:) = coeff_lcchange_10_mtc(pft_to_mtc(:))
596      coeff_lcchange_100(:) = coeff_lcchange_100_mtc(pft_to_mtc(:))
597      !
598      ! Phenology
599      !
600      !
601      ! 1. Stomate
602      !
603      lai_max_to_happy(:) = lai_max_to_happy_mtc(pft_to_mtc(:)) 
604      lai_max(:) = lai_max_mtc(pft_to_mtc(:))
605      pheno_type(:) = pheno_type_mtc(pft_to_mtc(:))
606      !
607      ! 2. Leaf Onset
608      !
609      pheno_gdd_crit_c(:) = pheno_gdd_crit_c_mtc(pft_to_mtc(:))
610      pheno_gdd_crit_b(:) = pheno_gdd_crit_b_mtc(pft_to_mtc(:))         
611      pheno_gdd_crit_a(:) = pheno_gdd_crit_a_mtc(pft_to_mtc(:))
612      pheno_moigdd_t_crit(:) = pheno_moigdd_t_crit_mtc(pft_to_mtc(:))
613      ngd_crit(:) =  ngd_crit_mtc(pft_to_mtc(:))
614      ncdgdd_temp(:) = ncdgdd_temp_mtc(pft_to_mtc(:)) 
615      hum_frac(:) = hum_frac_mtc(pft_to_mtc(:))
616      hum_min_time(:) = hum_min_time_mtc(pft_to_mtc(:))
617      tau_sap(:) = tau_sap_mtc(pft_to_mtc(:))
618      tau_leafinit(:) = tau_leafinit_mtc(pft_to_mtc(:)) 
619      tau_fruit(:) = tau_fruit_mtc(pft_to_mtc(:))
620      ecureuil(:) = ecureuil_mtc(pft_to_mtc(:))
621      alloc_min(:) = alloc_min_mtc(pft_to_mtc(:))
622      alloc_max(:) = alloc_max_mtc(pft_to_mtc(:))
623      demi_alloc(:) = demi_alloc_mtc(pft_to_mtc(:))
624      leaflife_tab(:) = leaflife_mtc(pft_to_mtc(:))
625      !
626      ! 3. Senescence
627      !
628      leaffall(:) = leaffall_mtc(pft_to_mtc(:))
629      leafagecrit(:) = leafagecrit_mtc(pft_to_mtc(:))
630      senescence_type(:) = senescence_type_mtc(pft_to_mtc(:)) 
631      senescence_hum(:) = senescence_hum_mtc(pft_to_mtc(:)) 
632      nosenescence_hum(:) = nosenescence_hum_mtc(pft_to_mtc(:)) 
633      max_turnover_time(:) = max_turnover_time_mtc(pft_to_mtc(:))
634      min_turnover_time(:) = min_turnover_time_mtc(pft_to_mtc(:))
635      min_leaf_age_for_senescence(:) = min_leaf_age_for_senescence_mtc(pft_to_mtc(:))
636      senescence_temp_c(:) = senescence_temp_c_mtc(pft_to_mtc(:))
637      senescence_temp_b(:) = senescence_temp_b_mtc(pft_to_mtc(:))
638      senescence_temp_a(:) = senescence_temp_a_mtc(pft_to_mtc(:))
639      gdd_senescence(:) = gdd_senescence_mtc(pft_to_mtc(:))
640      !
641      ! DGVM
642      !
643      residence_time(:) = residence_time_mtc(pft_to_mtc(:))
644      tmin_crit(:) = tmin_crit_mtc(pft_to_mtc(:))
645      tcm_crit(:) = tcm_crit_mtc(pft_to_mtc(:))
646      !-
647
648      !!!!! crop parameters
649
650      ! STICS:: main LAIdev
651      ok_LAIdev(:) = ok_LAIdev_mtc(pft_to_mtc(:))
652      ! STICS::
653      SP_codeplante(:) = SP_codeplante_mtc(pft_to_mtc(:))
654      SP_stade0(:) = SP_stade0_mtc(pft_to_mtc(:))
655      SP_iplt0(:) = SP_iplt0_mtc(pft_to_mtc(:))
656      SP_nbox(:) = SP_nbox_mtc(pft_to_mtc(:))
657      SP_iwater(:) = SP_iwater_mtc(pft_to_mtc(:))
658      SP_codesimul(:) = SP_codesimul_mtc(pft_to_mtc(:))
659      SP_codelaitr(:) = SP_codelaitr_mtc(pft_to_mtc(:))
660      SP_slamax(:) = SP_slamax_mtc(pft_to_mtc(:))
661      SP_slamin(:) = SP_slamin_mtc(pft_to_mtc(:))
662      SP_codeperenne(:) = SP_codeperenne_mtc(pft_to_mtc(:))
663
664      SP_codcueille(:) = SP_codcueille_mtc(pft_to_mtc(:))
665      SP_codegdh(:) = SP_codegdh_mtc(pft_to_mtc(:))
666      SP_codetemp(:) = SP_codetemp_mtc(pft_to_mtc(:))
667      SP_coderetflo(:) = SP_coderetflo_mtc(pft_to_mtc(:))
668      SP_codeinnact(:) = SP_codeinnact_mtc(pft_to_mtc(:))
669      SP_codeh2oact(:) = SP_codeh2oact_mtc(pft_to_mtc(:))
670      SP_stressdev(:) = SP_stressdev_mtc(pft_to_mtc(:))
671      SP_innlai(:) = SP_innlai_mtc(pft_to_mtc(:))
672      SP_innsenes(:) = SP_innsenes_mtc(pft_to_mtc(:))
673      SP_codebfroid(:) = SP_codebfroid_mtc(pft_to_mtc(:))
674
675      SP_codephot(:) = SP_codephot_mtc(pft_to_mtc(:))
676      SP_codedormance(:) = SP_codedormance_mtc(pft_to_mtc(:))
677      SP_codefauche(:) = SP_codefauche_mtc(pft_to_mtc(:))
678      SP_codetempfauche(:) = SP_codetempfauche_mtc(pft_to_mtc(:))
679      SP_codlainet(:) = SP_codlainet_mtc(pft_to_mtc(:))
680      SP_codeindetermin(:) = SP_codeindetermin_mtc(pft_to_mtc(:))
681      SP_codeinitprec(:) = SP_codeinitprec_mtc(pft_to_mtc(:))
682      SP_culturean(:) = SP_culturean_mtc(pft_to_mtc(:))
683
684      SP_jvc(:) = SP_jvc_mtc(pft_to_mtc(:))
685      SP_tfroid(:) = SP_tfroid_mtc(pft_to_mtc(:))
686      SP_ampfroid(:) = SP_ampfroid_mtc(pft_to_mtc(:))
687      SP_jvcmini(:) = SP_jvcmini_mtc(pft_to_mtc(:))
688      SP_tgmin(:) = SP_tgmin_mtc(pft_to_mtc(:))
689      SP_stpltger(:) = SP_stpltger_mtc(pft_to_mtc(:))
690      SP_profsem(:) = SP_profsem_mtc(pft_to_mtc(:))
691      SP_propjgermin(:) = SP_propjgermin_mtc(pft_to_mtc(:))
692
693      SP_tdmax(:) = SP_tdmax_mtc(pft_to_mtc(:))
694      SP_nbjgerlim(:) = SP_nbjgerlim_mtc(pft_to_mtc(:))
695      SP_densitesem(:) = SP_densitesem_mtc(pft_to_mtc(:))
696      SP_vigueurbat(:) = SP_vigueurbat_mtc(pft_to_mtc(:))
697      SP_codepluiepoquet(:) = SP_codepluiepoquet_mtc(pft_to_mtc(:))
698      SP_codehypo(:) = SP_codehypo_mtc(pft_to_mtc(:))
699      SP_elmax(:) = SP_elmax_mtc(pft_to_mtc(:))
700      SP_belong(:) = SP_belong_mtc(pft_to_mtc(:))
701
702      SP_celong(:) = SP_celong_mtc(pft_to_mtc(:))
703      SP_nlevlim1(:) = SP_nlevlim1_mtc(pft_to_mtc(:))
704      SP_nlevlim2(:) = SP_nlevlim2_mtc(pft_to_mtc(:))
705      SP_codrecolte(:) = SP_codrecolte_mtc(pft_to_mtc(:))
706      SP_variete(:) = SP_variete_mtc(pft_to_mtc(:))
707      SP_codegermin(:) = SP_codegermin_mtc(pft_to_mtc(:))
708
709      S_codeulaivernal(:) = S_codeulaivernal_mtc(pft_to_mtc(:))
710      SP_swfacmin(:) = SP_swfacmin_mtc(pft_to_mtc(:))
711      SP_neffmax(:) = SP_neffmax_mtc(pft_to_mtc(:))
712      SP_nsatrat(:) = SP_nsatrat_mtc(pft_to_mtc(:))
713
714
715      ! STICS:: LAI CALCULATION
716      SP_laiplantule(:) = SP_laiplantule_mtc(pft_to_mtc(:))
717      SP_vlaimax(:) = SP_vlaimax_mtc(pft_to_mtc(:))
718      SP_stlevamf(:) = SP_stlevamf_mtc(pft_to_mtc(:))
719      SP_stdrpmat(:) = SP_stdrpmat_mtc(pft_to_mtc(:))
720      SP_stamflax(:) = SP_stamflax_mtc(pft_to_mtc(:))
721      SP_udlaimax(:) = SP_udlaimax_mtc(pft_to_mtc(:))
722      SP_laicomp(:) = SP_laicomp_mtc(pft_to_mtc(:))
723      SP_adens(:) = SP_adens_mtc(pft_to_mtc(:))
724      SP_bdens(:) = SP_bdens_mtc(pft_to_mtc(:))
725
726      SP_tcxstop(:) = SP_tcxstop_mtc(pft_to_mtc(:))
727      SP_tcmax(:) = SP_tcmax_mtc(pft_to_mtc(:))
728      SP_tcmin(:) = SP_tcmin_mtc(pft_to_mtc(:))
729      SP_dlaimax(:) = SP_dlaimax_mtc(pft_to_mtc(:))
730      SP_dlaimin(:) = SP_dlaimin_mtc(pft_to_mtc(:))
731      SP_pentlaimax(:) = SP_pentlaimax_mtc(pft_to_mtc(:))
732      SP_tigefeuil(:) = SP_tigefeuil_mtc(pft_to_mtc(:))
733     
734      SP_stlaxsen(:) = SP_stlaxsen_mtc(pft_to_mtc(:))
735      SP_stsenlan(:) = SP_stsenlan_mtc(pft_to_mtc(:))
736      SP_stlevdrp(:) = SP_stlevdrp_mtc(pft_to_mtc(:))
737      SP_stflodrp(:) = SP_stflodrp_mtc(pft_to_mtc(:))
738      SP_stdrpdes(:) = SP_stdrpdes_mtc(pft_to_mtc(:))
739     
740      SP_phyllotherme(:) = SP_phyllotherme_mtc(pft_to_mtc(:))
741      SP_lai0(:) = SP_lai0_mtc(pft_to_mtc(:))
742      SP_tustressmin(:) = SP_tustressmin_mtc(pft_to_mtc(:))
743
744 
745      ! STICS:: LAI SENESCENCE
746      SP_nbfgellev(:) = SP_nbfgellev_mtc(pft_to_mtc(:))
747      SP_ratiodurvieI(:) = SP_ratiodurvieI_mtc(pft_to_mtc(:))
748      SP_durvieF(:) = SP_durvieF_mtc(pft_to_mtc(:))
749      SP_ratiosen(:) = SP_ratiosen_mtc(pft_to_mtc(:))
750      SP_tdmin(:) = SP_tdmin_mtc(pft_to_mtc(:))
751     
752      ! STICS:: F_humerac
753 
754      SP_sensrsec(:) = SP_sensrsec_mtc(pft_to_mtc(:))
755
756      ! STICS:: gel
757
758      SP_codgellev(:) = SP_codgellev_mtc(pft_to_mtc(:))
759      SP_tletale(:) = SP_tletale_mtc(pft_to_mtc(:))
760      SP_tdebgel(:) = SP_tdebgel_mtc(pft_to_mtc(:))
761      SP_tgellev10(:) = SP_tgellev10_mtc(pft_to_mtc(:))
762      SP_tgellev90(:) = SP_tgellev90_mtc(pft_to_mtc(:))
763
764      SP_tgeljuv10(:) = SP_tgeljuv10_mtc(pft_to_mtc(:))
765      SP_tgeljuv90(:) = SP_tgeljuv90_mtc(pft_to_mtc(:))
766      SP_tgelveg10(:) = SP_tgelveg10_mtc(pft_to_mtc(:))
767      SP_tgelveg90(:) = SP_tgelveg90_mtc(pft_to_mtc(:))
768
769
770      ! STICS:: PHOTOPERIOD
771
772      SP_sensiphot(:) = SP_sensiphot_mtc(pft_to_mtc(:))
773      SP_phosat(:) = SP_phosat_mtc(pft_to_mtc(:))
774      SP_phobase(:) = SP_phobase_mtc(pft_to_mtc(:))
775 
776      ! STICS:: CARBON ALLOCATION
777     
778      SP_stoprac(:) = SP_stoprac_mtc(pft_to_mtc(:))
779      SP_zracplantule(:) = SP_zracplantule_mtc(pft_to_mtc(:))
780      SP_codtrophrac(:) = SP_codtrophrac_mtc(pft_to_mtc(:))
781      SP_repracpermax(:) = SP_repracpermax_mtc(pft_to_mtc(:))
782      SP_repracpermin(:) = SP_repracpermin_mtc(pft_to_mtc(:))
783      SP_krepracperm(:) = SP_krepracperm_mtc(pft_to_mtc(:))
784      SP_repracseumax(:) = SP_repracseumax_mtc(pft_to_mtc(:))
785      SP_repracseumin(:) = SP_repracseumin_mtc(pft_to_mtc(:))
786      SP_krepracseu(:) = SP_krepracseu_mtc(pft_to_mtc(:))
787      SP_codetemprac(:) = SP_codetemprac_mtc(pft_to_mtc(:))
788      SP_codedyntalle(:) = SP_codedyntalle_mtc(pft_to_mtc(:))
789      SP_nbjgrain(:) = SP_nbjgrain_mtc(pft_to_mtc(:))
790      SP_maxgs(:) = SP_maxgs_mtc(pft_to_mtc(:))
791      SP_codgelflo(:) = SP_codgelflo_mtc(pft_to_mtc(:))
792      SP_tgelflo10(:) = SP_tgelflo10_mtc(pft_to_mtc(:))
793      SP_tgelflo90(:) = SP_tgelflo90_mtc(pft_to_mtc(:))
794      SP_cgrain(:) = SP_cgrain_mtc(pft_to_mtc(:))
795      SP_cgrainv0(:) = SP_cgrainv0_mtc(pft_to_mtc(:))
796      SP_nbgrmax(:) = SP_nbgrmax_mtc(pft_to_mtc(:))
797      SP_nbgrmin(:) = SP_nbgrmin_mtc(pft_to_mtc(:))
798      SP_codazofruit(:) = SP_codazofruit_mtc(pft_to_mtc(:))
799      SP_codeir(:) = SP_codeir_mtc(pft_to_mtc(:))
800      SP_vitircarb(:) = SP_vitircarb_mtc(pft_to_mtc(:))
801      SP_irmax(:) = SP_irmax_mtc(pft_to_mtc(:))
802      SP_vitircarbT(:) = SP_vitircarbT_mtc(pft_to_mtc(:))
803      SP_codetremp(:) = SP_codetremp_mtc(pft_to_mtc(:))
804      SP_tminremp(:) = SP_tminremp_mtc(pft_to_mtc(:))
805      SP_tmaxremp(:) = SP_tmaxremp_mtc(pft_to_mtc(:))
806      SP_pgrainmaxi(:) = SP_pgrainmaxi_mtc(pft_to_mtc(:))
807     
808      !! SPECIFIC FOR DYNAMIC INN STRATEGY
809     
810      SP_DY_INN(:) = SP_DY_INN_mtc(pft_to_mtc(:))
811      SP_avenfert(:) = SP_avenfert_mtc(pft_to_mtc(:))
812     
813      !!!!! end crop parameters
814   ENDIF !(ok_stomate)
815
816    ! 1.3 For BVOC parameters
817
818    IF (ok_bvoc) THEN
819       !
820       ! Biogenic Volatile Organic Compounds
821       !
822       em_factor_isoprene(:) = em_factor_isoprene_mtc(pft_to_mtc(:))
823       em_factor_monoterpene(:) = em_factor_monoterpene_mtc(pft_to_mtc(:))
824       LDF_mono = LDF_mono_mtc 
825       LDF_sesq = LDF_sesq_mtc 
826       LDF_meth = LDF_meth_mtc 
827       LDF_acet = LDF_acet_mtc 
828
829       em_factor_apinene(:) = em_factor_apinene_mtc(pft_to_mtc(:))
830       em_factor_bpinene(:) = em_factor_bpinene_mtc(pft_to_mtc(:))
831       em_factor_limonene(:) = em_factor_limonene_mtc(pft_to_mtc(:))
832       em_factor_myrcene(:) = em_factor_myrcene_mtc(pft_to_mtc(:))
833       em_factor_sabinene(:) = em_factor_sabinene_mtc(pft_to_mtc(:))
834       em_factor_camphene(:) = em_factor_camphene_mtc(pft_to_mtc(:))
835       em_factor_3carene(:) = em_factor_3carene_mtc(pft_to_mtc(:))
836       em_factor_tbocimene(:) = em_factor_tbocimene_mtc(pft_to_mtc(:))
837       em_factor_othermonot(:) = em_factor_othermonot_mtc(pft_to_mtc(:))
838       em_factor_sesquiterp(:) = em_factor_sesquiterp_mtc(pft_to_mtc(:))
839
840       beta_mono = beta_mono_mtc
841       beta_sesq = beta_sesq_mtc
842       beta_meth = beta_meth_mtc
843       beta_acet = beta_acet_mtc
844       beta_oxyVOC = beta_oxyVOC_mtc
845
846       em_factor_ORVOC(:) = em_factor_ORVOC_mtc(pft_to_mtc(:)) 
847       em_factor_OVOC(:) = em_factor_OVOC_mtc(pft_to_mtc(:))
848       em_factor_MBO(:) = em_factor_MBO_mtc(pft_to_mtc(:))
849       em_factor_methanol(:) = em_factor_methanol_mtc(pft_to_mtc(:))
850       em_factor_acetone(:) = em_factor_acetone_mtc(pft_to_mtc(:)) 
851       em_factor_acetal(:) = em_factor_acetal_mtc(pft_to_mtc(:))
852       em_factor_formal(:) = em_factor_formal_mtc(pft_to_mtc(:))
853       em_factor_acetic(:) = em_factor_acetic_mtc(pft_to_mtc(:))
854       em_factor_formic(:) = em_factor_formic_mtc(pft_to_mtc(:))
855       em_factor_no_wet(:) = em_factor_no_wet_mtc(pft_to_mtc(:))
856       em_factor_no_dry(:) = em_factor_no_dry_mtc(pft_to_mtc(:))
857       Larch(:) = Larch_mtc(pft_to_mtc(:)) 
858       !-
859    ENDIF !(ok_bvoc)
860
861    ! 1.4 For stomate parameters
862
863    IF (ok_stomate) THEN
864       !
865       ! Vegetation structure - stomate
866       !
867       sla(:) = sla_mtc(pft_to_mtc(:))
868       availability_fact(:) = availability_fact_mtc(pft_to_mtc(:))
869       !
870       ! Allocation - stomate
871       !
872       R0(:) = R0_mtc(pft_to_mtc(:)) 
873       S0(:) = S0_mtc(pft_to_mtc(:)) 
874       !
875       ! Respiration - stomate
876       !
877       frac_growthresp(:) = frac_growthresp_mtc(pft_to_mtc(:)) 
878       maint_resp_slope_c(:) = maint_resp_slope_c_mtc(pft_to_mtc(:))               
879       maint_resp_slope_b(:) = maint_resp_slope_b_mtc(pft_to_mtc(:))
880       maint_resp_slope_a(:) = maint_resp_slope_a_mtc(pft_to_mtc(:))
881       cm_zero_leaf(:) = cm_zero_leaf_mtc(pft_to_mtc(:))
882       cm_zero_sapabove(:) = cm_zero_sapabove_mtc(pft_to_mtc(:))
883       cm_zero_sapbelow(:) = cm_zero_sapbelow_mtc(pft_to_mtc(:)) 
884       cm_zero_heartabove(:) = cm_zero_heartabove_mtc(pft_to_mtc(:)) 
885       cm_zero_heartbelow(:) = cm_zero_heartbelow_mtc(pft_to_mtc(:))
886       cm_zero_root(:) = cm_zero_root_mtc(pft_to_mtc(:))
887       cm_zero_fruit(:) = cm_zero_fruit_mtc(pft_to_mtc(:))
888       cm_zero_carbres(:) = cm_zero_carbres_mtc(pft_to_mtc(:))
889       !
890       ! Fire - stomate
891       !
892       flam(:) = flam_mtc(pft_to_mtc(:))
893       resist(:) = resist_mtc(pft_to_mtc(:))
894       !
895       ! Flux - LUC
896       !
897       coeff_lcchange_1(:) = coeff_lcchange_1_mtc(pft_to_mtc(:))
898       coeff_lcchange_10(:) = coeff_lcchange_10_mtc(pft_to_mtc(:))
899       coeff_lcchange_100(:) = coeff_lcchange_100_mtc(pft_to_mtc(:))
900       !
901       ! Phenology
902       !
903       !
904       ! 1. Stomate
905       !
906       lai_max_to_happy(:) = lai_max_to_happy_mtc(pft_to_mtc(:)) 
907       lai_max(:) = lai_max_mtc(pft_to_mtc(:))
908       pheno_type(:) = pheno_type_mtc(pft_to_mtc(:))
909       !
910       ! 2. Leaf Onset
911       !
912       pheno_gdd_crit_c(:) = pheno_gdd_crit_c_mtc(pft_to_mtc(:))
913       pheno_gdd_crit_b(:) = pheno_gdd_crit_b_mtc(pft_to_mtc(:))         
914       pheno_gdd_crit_a(:) = pheno_gdd_crit_a_mtc(pft_to_mtc(:))
915       pheno_moigdd_t_crit(:) = pheno_moigdd_t_crit_mtc(pft_to_mtc(:))
916       ngd_crit(:) =  ngd_crit_mtc(pft_to_mtc(:))
917       ncdgdd_temp(:) = ncdgdd_temp_mtc(pft_to_mtc(:)) 
918       hum_frac(:) = hum_frac_mtc(pft_to_mtc(:))
919       hum_min_time(:) = hum_min_time_mtc(pft_to_mtc(:))
920       tau_sap(:) = tau_sap_mtc(pft_to_mtc(:))
921       tau_leafinit(:) = tau_leafinit_mtc(pft_to_mtc(:)) 
922       tau_fruit(:) = tau_fruit_mtc(pft_to_mtc(:))
923       ecureuil(:) = ecureuil_mtc(pft_to_mtc(:))
924       alloc_min(:) = alloc_min_mtc(pft_to_mtc(:))
925       alloc_max(:) = alloc_max_mtc(pft_to_mtc(:))
926       demi_alloc(:) = demi_alloc_mtc(pft_to_mtc(:))
927       leaflife_tab(:) = leaflife_mtc(pft_to_mtc(:))
928       !
929       ! 3. Senescence
930       !
931       leaffall(:) = leaffall_mtc(pft_to_mtc(:))
932       leafagecrit(:) = leafagecrit_mtc(pft_to_mtc(:))
933       senescence_type(:) = senescence_type_mtc(pft_to_mtc(:)) 
934       senescence_hum(:) = senescence_hum_mtc(pft_to_mtc(:)) 
935       nosenescence_hum(:) = nosenescence_hum_mtc(pft_to_mtc(:)) 
936       max_turnover_time(:) = max_turnover_time_mtc(pft_to_mtc(:))
937       min_turnover_time(:) = min_turnover_time_mtc(pft_to_mtc(:))
938       min_leaf_age_for_senescence(:) = min_leaf_age_for_senescence_mtc(pft_to_mtc(:))
939       senescence_temp_c(:) = senescence_temp_c_mtc(pft_to_mtc(:))
940       senescence_temp_b(:) = senescence_temp_b_mtc(pft_to_mtc(:))
941       senescence_temp_a(:) = senescence_temp_a_mtc(pft_to_mtc(:))
942       gdd_senescence(:) = gdd_senescence_mtc(pft_to_mtc(:))
943       !
944       ! DGVM
945       !
946       residence_time(:) = residence_time_mtc(pft_to_mtc(:))
947       tmin_crit(:) = tmin_crit_mtc(pft_to_mtc(:))
948       tcm_crit(:) = tcm_crit_mtc(pft_to_mtc(:))
949       !-
950    ENDIF !(ok_stomate)
951
952  END SUBROUTINE pft_parameters_init
953
954
955!! ================================================================================================================================
956!! SUBROUTINE   : pft_parameters_alloc
957!!
958!>\BRIEF         This subroutine allocates memory needed for the PFT parameters
959!! in function  of the flags activated. 
960!!
961!! DESCRIPTION  : None
962!!
963!! RECENT CHANGE(S): None
964!!
965!! MAIN OUTPUT VARIABLE(S): None
966!!
967!! REFERENCE(S) : None
968!!
969!! FLOWCHART    : None
970!! \n
971!_ ================================================================================================================================
972
973  SUBROUTINE pft_parameters_alloc()
974
975    IMPLICIT NONE
976
977    !! 0. Variables and parameters declaration
978
979    !! 0.1 Input variables
980
981    !! 0.4 Local variables
982
983    LOGICAL :: l_error                             !! Diagnostic boolean for error allocation (true/false)
984    INTEGER :: ier                                 !! Return value for memory allocation (0-N, unitless)
985
986    !_ ================================================================================================================================
987
988
989    !
990    ! 1. Parameters used anytime
991    !
992
993    l_error = .FALSE.
994
995    ALLOCATE(pft_to_mtc(nvm),stat=ier)
996    l_error = l_error .OR. (ier /= 0)
997    IF (l_error) THEN
998       WRITE(numout,*) ' Memory allocation error for pft_to_mtc. We stop. We need nvm words = ',nvm
999       STOP 'pft_parameters_alloc'
1000    END IF
1001
1002    ALLOCATE(PFT_name(nvm),stat=ier)
1003    l_error = l_error .OR. (ier /= 0)
1004    IF (l_error) THEN
1005       WRITE(numout,*) ' Memory allocation error for PFT_name. We stop. We need nvm words = ',nvm
1006       STOP 'pft_parameters_alloc'
1007    END IF
1008
1009    ALLOCATE(height_presc(nvm),stat=ier)
1010    l_error = l_error .OR. (ier /= 0)
1011    IF (l_error) THEN
1012       WRITE(numout,*) ' Memory allocation error for height_presc. We stop. We need nvm words = ',nvm
1013       STOP 'pft_parameters_alloc'
1014    END IF
1015
1016    ALLOCATE(z0_over_height(nvm),stat=ier)
1017    l_error = l_error .OR. (ier /= 0)
1018    IF (l_error) THEN
1019       WRITE(numout,*) ' Memory allocation error for z0_over_height. We stop. We need nvm words = ',nvm
1020       STOP 'pft_parameters_alloc'
1021    END IF
1022
1023    ALLOCATE(ratio_z0m_z0h(nvm),stat=ier)
1024    l_error = l_error .OR. (ier /= 0)
1025    IF (l_error) THEN
1026       WRITE(numout,*) ' Memory allocation error for ratio_z0m_z0h. We stop. We need nvm words = ',nvm
1027       STOP 'pft_parameters_alloc'
1028    END IF
1029! dgvmjc
1030    ALLOCATE(pasture(nvm),stat=ier)
1031    l_error = l_error .OR. (ier /= 0)
1032    IF (l_error) THEN
1033       WRITE(numout,*) ' Memory allocation error for pasture. We stop. We need nvm words = ',nvm
1034       STOP 'pft_parameters_alloc'
1035    END IF
1036! end dgvmjc
1037!!! crop irrig
1038   ALLOCATE(irrig_threshold(nvm),stat=ier)
1039   l_error = l_error .OR. (ier /= 0)
1040   IF (l_error) THEN
1041      WRITE(numout,*) ' Memory allocation error for irrig_threshold. We stop. We need nvm words = ',nvm
1042      STOP 'pft_parameters_alloc'
1043   END IF
1044
1045   ALLOCATE(irrig_fulfill(nvm),stat=ier)
1046   l_error = l_error .OR. (ier /= 0)
1047   IF (l_error) THEN
1048      WRITE(numout,*) ' Memory allocation error for irrig_fulfill. We stop. We need nvm words = ',nvm
1049      STOP 'pft_parameters_alloc'
1050   END IF
1051!!! end crop irrig, xuhui
1052    ALLOCATE(natural(nvm),stat=ier)
1053    l_error = l_error .OR. (ier /= 0)
1054    IF (l_error) THEN
1055       WRITE(numout,*) ' Memory allocation error for natural. We stop. We need nvm words = ',nvm
1056       STOP 'pft_parameters_alloc'
1057    END IF
1058
1059    ALLOCATE(is_tree(nvm),stat=ier) 
1060       l_error = l_error .OR. (ier /= 0) 
1061       IF (l_error) THEN
1062          WRITE(numout,*) ' Memory allocation error for is_tree. We stop. We need nvm words = ',nvm 
1063       STOP 'pft_parameters_alloc' 
1064    END IF
1065
1066    ALLOCATE(is_c4(nvm),stat=ier)
1067    l_error = l_error .OR. (ier /= 0)
1068    IF (l_error) THEN
1069       WRITE(numout,*) ' Memory allocation error for is_c4. We stop. We need nvm words = ',nvm
1070       STOP 'pft_parameters_alloc'
1071    END IF
1072
1073    ALLOCATE(vcmax_fix(nvm),stat=ier)
1074    l_error = l_error .OR. (ier /= 0)
1075    IF (l_error) THEN
1076       WRITE(numout,*) ' Memory allocation error for vcmax_fix. We stop. We need nvm words = ',nvm
1077       STOP 'pft_parameters_alloc'
1078    END IF
1079
1080    ALLOCATE(humcste(nvm),stat=ier)
1081    l_error = l_error .OR. (ier /= 0)
1082    IF (l_error) THEN
1083       WRITE(numout,*) ' Memory allocation error for humcste. We stop. We need nvm words = ',nvm
1084       STOP 'pft_parameters_alloc'
1085    END IF
1086
1087    ALLOCATE(downregulation_co2_coeff(nvm),stat=ier)
1088    l_error = l_error .OR. (ier /= 0)
1089    IF (l_error) THEN
1090       WRITE(numout,*) ' Memory allocation error for downregulation_co2_coeff. We stop. We need nvm words = ',nvm
1091       STOP 'pft_parameters_alloc'
1092    END IF
1093
1094    ALLOCATE(E_KmC(nvm),stat=ier)
1095    l_error = l_error .OR. (ier /= 0)
1096    IF (l_error) THEN
1097       WRITE(numout,*) ' Memory allocation error for E_KmC. We stop. We need nvm words = ',nvm
1098       STOP 'pft_parameters_alloc'
1099    END IF
1100
1101    ALLOCATE(E_KmO(nvm),stat=ier)
1102    l_error = l_error .OR. (ier /= 0)
1103    IF (l_error) THEN
1104       WRITE(numout,*) ' Memory allocation error for E_KmO. We stop. We need nvm words = ',nvm
1105       STOP 'pft_parameters_alloc'
1106    END IF
1107
1108    ALLOCATE(E_Sco(nvm),stat=ier)
1109    l_error = l_error .OR. (ier /= 0)
1110    IF (l_error) THEN
1111       WRITE(numout,*) ' Memory allocation error for E_Sco. We stop. We need nvm words = ',nvm
1112       STOP 'pft_parameters_alloc'
1113    END IF
1114
1115    ALLOCATE(E_gamma_star(nvm),stat=ier)
1116    l_error = l_error .OR. (ier /= 0)
1117    IF (l_error) THEN
1118       WRITE(numout,*) ' Memory allocation error for E_gamma_star. We stop. We need nvm words = ',nvm
1119       STOP 'pft_parameters_alloc'
1120    END IF
1121
1122    ALLOCATE(E_vcmax(nvm),stat=ier)
1123    l_error = l_error .OR. (ier /= 0)
1124    IF (l_error) THEN
1125       WRITE(numout,*) ' Memory allocation error for E_Vcmax. We stop. We need nvm words = ',nvm
1126       STOP 'pft_parameters_alloc'
1127    END IF
1128
1129    ALLOCATE(E_Jmax(nvm),stat=ier)
1130    l_error = l_error .OR. (ier /= 0)
1131    IF (l_error) THEN
1132       WRITE(numout,*) ' Memory allocation error for E_Jmax. We stop. We need nvm words = ',nvm
1133       STOP 'pft_parameters_alloc'
1134    END IF
1135
1136    ALLOCATE(aSV(nvm),stat=ier)
1137    l_error = l_error .OR. (ier /= 0)
1138    IF (l_error) THEN
1139       WRITE(numout,*) ' Memory allocation error for aSV. We stop. We need nvm words = ',nvm
1140       STOP 'pft_parameters_alloc'
1141    END IF
1142
1143    ALLOCATE(bSV(nvm),stat=ier)
1144    l_error = l_error .OR. (ier /= 0)
1145    IF (l_error) THEN
1146       WRITE(numout,*) ' Memory allocation error for bSV. We stop. We need nvm words = ',nvm
1147       STOP 'pft_parameters_alloc'
1148    END IF
1149
1150    ALLOCATE(tphoto_min(nvm),stat=ier)
1151    l_error = l_error .OR. (ier /= 0)
1152    IF (l_error) THEN
1153       WRITE(numout,*) ' Memory allocation error for tphoto_min. We stop. We need nvm words = ',nvm
1154       STOP 'pft_parameters_alloc'
1155    END IF
1156
1157    ALLOCATE(tphoto_max(nvm),stat=ier)
1158    l_error = l_error .OR. (ier /= 0)
1159    IF (l_error) THEN
1160       WRITE(numout,*) ' Memory allocation error for tphoto_max. We stop. We need nvm words = ',nvm
1161       STOP 'pft_parameters_alloc'
1162    END IF
1163
1164    ALLOCATE(aSJ(nvm),stat=ier)
1165    l_error = l_error .OR. (ier /= 0)
1166    IF (l_error) THEN
1167       WRITE(numout,*) ' Memory allocation error for aSJ. We stop. We need nvm words = ',nvm
1168       STOP 'pft_parameters_alloc'
1169    END IF
1170
1171    ALLOCATE(bSJ(nvm),stat=ier)
1172    l_error = l_error .OR. (ier /= 0)
1173    IF (l_error) THEN
1174       WRITE(numout,*) ' Memory allocation error for bSJ. We stop. We need nvm words = ',nvm
1175       STOP 'pft_parameters_alloc'
1176    END IF
1177
1178    ALLOCATE(D_Vcmax(nvm),stat=ier)
1179    l_error = l_error .OR. (ier /= 0)
1180    IF (l_error) THEN
1181       WRITE(numout,*) ' Memory allocation error for D_Vcmax. We stop. We need nvm words = ',nvm
1182       STOP 'pft_parameters_alloc'
1183    END IF
1184
1185    ALLOCATE(D_Jmax(nvm),stat=ier)
1186    l_error = l_error .OR. (ier /= 0)
1187    IF (l_error) THEN
1188       WRITE(numout,*) ' Memory allocation error for D_Jmax. We stop. We need nvm words = ',nvm
1189       STOP 'pft_parameters_alloc'
1190    END IF
1191
1192    ALLOCATE(E_gm(nvm),stat=ier) 
1193    l_error = l_error .OR. (ier /= 0) 
1194    IF (l_error) THEN
1195       WRITE(numout,*) ' Memory allocation error for E_gm. We stop. We need nvm words = ',nvm 
1196       STOP 'pft_parameters_alloc' 
1197    END IF
1198   
1199    ALLOCATE(S_gm(nvm),stat=ier) 
1200    l_error = l_error .OR. (ier /= 0) 
1201    IF (l_error) THEN
1202       WRITE(numout,*) ' Memory allocation error for S_gm. We stop. We need nvm words = ',nvm 
1203       STOP 'pft_parameters_alloc' 
1204    END IF
1205   
1206    ALLOCATE(D_gm(nvm),stat=ier) 
1207    l_error = l_error .OR. (ier /= 0) 
1208    IF (l_error) THEN
1209       WRITE(numout,*) ' Memory allocation error for D_gm. We stop. We need nvm words = ',nvm 
1210       STOP 'pft_parameters_alloc' 
1211    END IF
1212   
1213    ALLOCATE(E_Rd(nvm),stat=ier)
1214    l_error = l_error .OR. (ier /= 0)
1215    IF (l_error) THEN
1216       WRITE(numout,*) ' Memory allocation error for E_Rd. We stop. We need nvm words = ',nvm
1217       STOP 'pft_parameters_alloc'
1218    END IF
1219
1220    ALLOCATE(Vcmax25(nvm),stat=ier)
1221    l_error = l_error .OR. (ier /= 0)
1222    IF (l_error) THEN
1223       WRITE(numout,*) ' Memory allocation error for Vcmax25. We stop. We need nvm words = ',nvm
1224       STOP 'pft_parameters_alloc'
1225    END IF
1226
1227    ALLOCATE(arJV(nvm),stat=ier)
1228    l_error = l_error .OR. (ier /= 0)
1229    IF (l_error) THEN
1230       WRITE(numout,*) ' Memory allocation error for arJV. We stop. We need nvm words = ',nvm
1231       STOP 'pft_parameters_alloc'
1232    END IF
1233
1234    ALLOCATE(brJV(nvm),stat=ier)
1235    l_error = l_error .OR. (ier /= 0)
1236    IF (l_error) THEN
1237       WRITE(numout,*) ' Memory allocation error for brJV. We stop. We need nvm words = ',nvm
1238       STOP 'pft_parameters_alloc'
1239    END IF
1240
1241    ALLOCATE(KmC25(nvm),stat=ier)
1242    l_error = l_error .OR. (ier /= 0)
1243    IF (l_error) THEN
1244       WRITE(numout,*) ' Memory allocation error for KmC25. We stop. We need nvm words = ',nvm
1245       STOP 'pft_parameters_alloc'
1246    END IF
1247
1248    ALLOCATE(KmO25(nvm),stat=ier)
1249    l_error = l_error .OR. (ier /= 0)
1250    IF (l_error) THEN
1251       WRITE(numout,*) ' Memory allocation error for KmO25. We stop. We need nvm words = ',nvm
1252       STOP 'pft_parameters_alloc'
1253    END IF
1254
1255    ALLOCATE(Sco25(nvm),stat=ier)
1256    l_error = l_error .OR. (ier /= 0)
1257    IF (l_error) THEN
1258       WRITE(numout,*) ' Memory allocation error for Sco25. We stop. We need nvm words = ',nvm
1259       STOP 'pft_parameters_alloc'
1260    END IF
1261   
1262    ALLOCATE(gm25(nvm),stat=ier) 
1263    l_error = l_error .OR. (ier /= 0) 
1264    IF (l_error) THEN
1265       WRITE(numout,*) ' Memory allocation error for gm25. We stop. We need nvm words = ',nvm 
1266       STOP 'pft_parameters_alloc' 
1267    END IF
1268
1269    ALLOCATE(gamma_star25(nvm),stat=ier)
1270    l_error = l_error .OR. (ier /= 0)
1271    IF (l_error) THEN
1272       WRITE(numout,*) ' Memory allocation error for gamma_star25. We stop. We need nvm words = ',nvm
1273       STOP 'pft_parameters_alloc'
1274    END IF
1275
1276    ALLOCATE(a1(nvm),stat=ier)
1277    l_error = l_error .OR. (ier /= 0)
1278    IF (l_error) THEN
1279       WRITE(numout,*) ' Memory allocation error for a1. We stop. We need nvm words = ',nvm
1280       STOP 'pft_parameters_alloc'
1281    END IF
1282
1283    ALLOCATE(b1(nvm),stat=ier)
1284    l_error = l_error .OR. (ier /= 0)
1285    IF (l_error) THEN
1286       WRITE(numout,*) ' Memory allocation error for b1. We stop. We need nvm words = ',nvm
1287       STOP 'pft_parameters_alloc'
1288    END IF
1289
1290    ALLOCATE(g0(nvm),stat=ier)
1291    l_error = l_error .OR. (ier /= 0)
1292    IF (l_error) THEN
1293       WRITE(numout,*) ' Memory allocation error for g0. We stop. We need nvm words = ',nvm
1294       STOP 'pft_parameters_alloc'
1295    END IF
1296
1297    ALLOCATE(h_protons(nvm),stat=ier)
1298    l_error = l_error .OR. (ier /= 0)
1299    IF (l_error) THEN
1300       WRITE(numout,*) ' Memory allocation error for h_protons. We stop. We need nvm words = ',nvm
1301       STOP 'pft_parameters_alloc'
1302    END IF
1303
1304    ALLOCATE(fpsir(nvm),stat=ier)
1305    l_error = l_error .OR. (ier /= 0)
1306    IF (l_error) THEN
1307       WRITE(numout,*) ' Memory allocation error for fpsir. We stop. We need nvm words = ',nvm
1308       STOP 'pft_parameters_alloc'
1309    END IF
1310
1311    ALLOCATE(fQ(nvm),stat=ier)
1312    l_error = l_error .OR. (ier /= 0)
1313    IF (l_error) THEN
1314       WRITE(numout,*) ' Memory allocation error for fQ. We stop. We need nvm words = ',nvm
1315       STOP 'pft_parameters_alloc'
1316    END IF
1317
1318    ALLOCATE(fpseudo(nvm),stat=ier)
1319    l_error = l_error .OR. (ier /= 0)
1320    IF (l_error) THEN
1321       WRITE(numout,*) ' Memory allocation error for fpseudo. We stop. We need nvm words = ',nvm
1322       STOP 'pft_parameters_alloc'
1323    END IF
1324
1325    ALLOCATE(kp(nvm),stat=ier)
1326    l_error = l_error .OR. (ier /= 0)
1327    IF (l_error) THEN
1328       WRITE(numout,*) ' Memory allocation error for kp. We stop. We need nvm words = ',nvm
1329       STOP 'pft_parameters_alloc'
1330    END IF
1331
1332    ALLOCATE(alpha(nvm),stat=ier)
1333    l_error = l_error .OR. (ier /= 0)
1334    IF (l_error) THEN
1335       WRITE(numout,*) ' Memory allocation error for alpha. We stop. We need nvm words = ',nvm
1336       STOP 'pft_parameters_alloc'
1337    END IF
1338
1339    ALLOCATE(gbs(nvm),stat=ier)
1340    l_error = l_error .OR. (ier /= 0)
1341    IF (l_error) THEN
1342       WRITE(numout,*) ' Memory allocation error for gbs. We stop. We need nvm words = ',nvm
1343       STOP 'pft_parameters_alloc'
1344    END IF
1345
1346    ALLOCATE(theta(nvm),stat=ier)
1347    l_error = l_error .OR. (ier /= 0)
1348    IF (l_error) THEN
1349       WRITE(numout,*) ' Memory allocation error for theta. We stop. We need nvm words = ',nvm
1350       STOP 'pft_parameters_alloc'
1351    END IF
1352
1353    ALLOCATE(alpha_LL(nvm),stat=ier)
1354    l_error = l_error .OR. (ier /= 0)
1355    IF (l_error) THEN
1356       WRITE(numout,*) ' Memory allocation error for alpha_LL. We stop. We need nvm words = ',nvm
1357       STOP 'pft_parameters_alloc'
1358    END IF
1359
1360    ALLOCATE(stress_vcmax(nvm),stat=ier)
1361    l_error = l_error .OR. (ier /= 0)
1362    IF (l_error) THEN
1363       WRITE(numout,*) ' Memory allocation error for stress_vcmax. We stop. We need nvm words = ',nvm
1364       STOP 'pft_parameters_alloc'
1365    END IF
1366   
1367    ALLOCATE(stress_gs(nvm),stat=ier)
1368    l_error = l_error .OR. (ier /= 0)
1369    IF (l_error) THEN
1370       WRITE(numout,*) ' Memory allocation error for stress_gs. We stop. We need nvm words = ',nvm
1371       STOP 'pft_parameters_alloc'
1372    END IF
1373   
1374    ALLOCATE(stress_gm(nvm),stat=ier)
1375    l_error = l_error .OR. (ier /= 0)
1376    IF (l_error) THEN
1377       WRITE(numout,*) ' Memory allocation error for stress_gm. We stop. We need nvm words = ',nvm
1378       STOP 'pft_parameters_alloc'
1379    END IF
1380
1381    ALLOCATE(ext_coeff(nvm),stat=ier)
1382    l_error = l_error .OR. (ier /= 0)
1383    IF (l_error) THEN
1384       WRITE(numout,*) ' Memory allocation error for ext_coeff. We stop. We need nvm words = ',nvm
1385       STOP 'pft_parameters_alloc'
1386    END IF
1387
1388    ALLOCATE(ext_coeff_vegetfrac(nvm),stat=ier)
1389    l_error = l_error .OR. (ier /= 0)
1390    IF (l_error) THEN
1391       WRITE(numout,*) ' Memory allocation error for ext_coeff_vegetfrac. We stop. We need nvm words = ',nvm
1392       STOP 'pft_parameters_alloc'
1393    END IF
1394
1395    ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier)
1396    l_error = l_error .OR. (ier /= 0)
1397    IF (l_error) THEN
1398       WRITE(numout,*) ' Memory allocation error for veget_ori_fixed_test_1. We stop. We need nvm words = ',nvm
1399       STOP 'pft_parameters_alloc'
1400    END IF
1401
1402    ALLOCATE(llaimax(nvm),stat=ier)
1403    l_error = l_error .OR. (ier /= 0)
1404    IF (l_error) THEN
1405       WRITE(numout,*) ' Memory allocation error for llaimax. We stop. We need nvm words = ',nvm
1406       STOP 'pft_parameters_alloc'
1407    END IF
1408
1409    ALLOCATE(llaimin(nvm),stat=ier)
1410    l_error = l_error .OR. (ier /= 0)
1411    IF (l_error) THEN
1412       WRITE(numout,*) ' Memory allocation error for llaimin. We stop. We need nvm words = ',nvm
1413       STOP 'pft_parameters_alloc'
1414    END IF
1415
1416    ALLOCATE(type_of_lai(nvm),stat=ier)
1417    l_error = l_error .OR. (ier /= 0)
1418    IF (l_error) THEN
1419       WRITE(numout,*) ' Memory allocation error for type_of_lai. We stop. We need nvm words = ',nvm
1420       STOP 'pft_parameters_alloc'
1421    END IF
1422
1423   ALLOCATE(agec_group(nvm),stat=ier)
1424   l_error = l_error .OR. (ier /= 0)
1425   IF (l_error) THEN
1426      WRITE(numout,*) ' Memory allocation error for agec_group. We stop. We need nvm words = ',nvm
1427      STOP 'pft_parameters_alloc'
1428   END IF
1429
1430   ALLOCATE(age_class_bound(nvm),stat=ier)
1431   l_error = l_error .OR. (ier /= 0)
1432   IF (l_error) THEN
1433      WRITE(numout,*) ' Memory allocation error for age_class_bound. We stop. We need nvm words = ',nvm
1434      STOP 'pft_parameters_alloc'
1435   END IF
1436   age_class_bound(:)=0.
1437
1438   ALLOCATE(start_index(nvm),stat=ier)
1439   l_error = l_error .OR. (ier /= 0)
1440   IF (l_error) THEN
1441      WRITE(numout,*) ' Memory allocation error for start_index. We stop. We need nvm words = ',nvm
1442      STOP 'pft_parameters_alloc'
1443   END IF
1444
1445   ALLOCATE(nagec_pft(nvm),stat=ier)
1446   l_error = l_error .OR. (ier /= 0)
1447   IF (l_error) THEN
1448      WRITE(numout,*) ' Memory allocation error for nagec_pft. We stop. We need nvm words = ',nvm
1449      STOP 'pft_parameters_alloc'
1450   END IF
1451
1452   ALLOCATE(leaf_tab(nvm),stat=ier)
1453   l_error = l_error .OR. (ier /= 0)
1454   IF (l_error) THEN
1455      WRITE(numout,*) ' Memory allocation error for leaf_tab. We stop. We need nvm words = ',nvm
1456      STOP 'pft_parameters_alloc'
1457   END IF
1458
1459    ALLOCATE(pref_soil_veg(nvm),stat=ier)
1460    l_error = l_error .OR. (ier /= 0)
1461    IF (l_error) THEN
1462       WRITE(numout,*) ' Memory allocation error for pref_soil_veg. We stop. We need nvm words = ',nvm
1463       STOP 'pft_parameters_alloc'
1464    END IF
1465
1466    ALLOCATE(pheno_model(nvm),stat=ier)
1467    l_error = l_error .OR. (ier /= 0)
1468    IF (l_error) THEN
1469       WRITE(numout,*) ' Memory allocation error for pheno_model. We stop. We need nvm words = ',nvm
1470       STOP 'pft_parameters_alloc'
1471    END IF
1472
1473    ALLOCATE(is_deciduous(nvm),stat=ier) 
1474    l_error = l_error .OR. (ier /= 0) 
1475    IF (l_error) THEN
1476       WRITE(numout,*) ' Memory allocation error for is_deciduous. We stop. We need nvm words = ',nvm
1477       STOP 'pft_parameters_alloc'
1478    END IF
1479
1480    ALLOCATE(is_evergreen(nvm),stat=ier) 
1481    l_error = l_error .OR. (ier /= 0)
1482    IF (l_error) THEN
1483       WRITE(numout,*) ' Memory allocation error for is_evergreen. We stop. We need nvm words = ',nvm
1484       STOP 'pft_parameters_alloc'
1485    END IF
1486
1487    ALLOCATE(is_needleleaf(nvm),stat=ier) 
1488    l_error = l_error .OR. (ier /= 0)
1489    IF (l_error) THEN
1490       WRITE(numout,*) ' Memory allocation error for is_needleleaf. We stop. We need nvm words = ',nvm
1491       STOP 'pft_parameters_alloc'
1492    END IF
1493
1494    ALLOCATE(is_tropical(nvm),stat=ier)   
1495    l_error = l_error .OR. (ier /= 0)
1496    IF (l_error) THEN
1497       WRITE(numout,*) ' Memory allocation error for is_tropical. We stop. We need nvm words = ',nvm
1498       STOP 'pft_parameters_alloc'
1499    END IF
1500
1501
1502    !
1503    ! 2. Parameters used if ok_sechiba only
1504    !
1505    IF ( ok_sechiba ) THEN
1506
1507       l_error = .FALSE.
1508
1509       ALLOCATE(rstruct_const(nvm),stat=ier)
1510       l_error = l_error .OR. (ier /= 0)
1511       IF (l_error) THEN
1512          WRITE(numout,*) ' Memory allocation error for rstruct_const. We stop. We need nvm words = ',nvm
1513          STOP 'pft_parameters_alloc'
1514       END IF
1515
1516       ALLOCATE(kzero(nvm),stat=ier)
1517       l_error = l_error .OR. (ier /= 0)
1518       IF (l_error) THEN
1519          WRITE(numout,*) ' Memory allocation error for kzero. We stop. We need nvm words = ',nvm
1520          STOP 'pft_parameters_alloc'
1521       END IF
1522
1523       ALLOCATE(rveg_pft(nvm),stat=ier)
1524       l_error = l_error .OR. (ier /= 0)
1525       IF (l_error) THEN
1526          WRITE(numout,*) ' Memory allocation error for rveg_pft. We stop. We need nvm words = ',nvm
1527          STOP 'pft_parameters_alloc'
1528       END IF
1529
1530       ALLOCATE(wmax_veg(nvm),stat=ier)
1531       l_error = l_error .OR. (ier /= 0)
1532       IF (l_error) THEN
1533          WRITE(numout,*) ' Memory allocation error for wmax_veg. We stop. We need nvm words = ',nvm
1534          STOP 'pft_parameters_alloc'
1535       END IF
1536
1537       ALLOCATE(throughfall_by_pft(nvm),stat=ier)
1538       l_error = l_error .OR. (ier /= 0)
1539       IF (l_error) THEN
1540          WRITE(numout,*) ' Memory allocation error for throughfall_by_pft. We stop. We need nvm words = ',nvm
1541          STOP 'pft_parameters_alloc'
1542       END IF
1543
1544       ALLOCATE(snowa_dec_vis(nvm),stat=ier)
1545       l_error = l_error .OR. (ier /= 0)
1546       IF (l_error) THEN
1547          WRITE(numout,*) ' Memory allocation error for snowa_dec_nir. We stop. We need nvm words = ',nvm
1548          STOP 'pft_parameters_alloc'
1549       END IF
1550
1551       ALLOCATE(snowa_dec_nir(nvm),stat=ier)
1552       l_error = l_error .OR. (ier /= 0)
1553       IF (l_error) THEN
1554          WRITE(numout,*) ' Memory allocation error for snowa_dec_nir. We stop. We need nvm words = ',nvm
1555          STOP 'pft_parameters_alloc'
1556       END IF
1557
1558       ALLOCATE(snowa_aged_vis(nvm),stat=ier)
1559       l_error = l_error .OR. (ier /= 0)
1560       IF (l_error) THEN
1561          WRITE(numout,*) ' Memory allocation error for snowa_aged_vis. We stop. We need nvm words = ',nvm
1562          STOP 'pft_parameters_alloc'
1563       END IF
1564
1565       ALLOCATE(snowa_aged_nir(nvm),stat=ier)
1566       l_error = l_error .OR. (ier /= 0)
1567       IF (l_error) THEN
1568          WRITE(numout,*) ' Memory allocation error for snowa_aged_nir. We stop. We need nvm words = ',nvm
1569          STOP 'pft_parameters_alloc'
1570       END IF
1571
1572       ALLOCATE(alb_leaf_vis(nvm),stat=ier)
1573       l_error = l_error .OR. (ier /= 0)
1574       IF (l_error) THEN
1575          WRITE(numout,*) ' Memory allocation error for alb_leaf_vis. We stop. We need nvm words = ',nvm
1576          STOP 'pft_parameters_alloc'
1577       END IF
1578
1579       ALLOCATE(alb_leaf_nir(nvm),stat=ier)
1580       l_error = l_error .OR. (ier /= 0)
1581       IF (l_error) THEN
1582          WRITE(numout,*) ' Memory allocation error for alb_leaf_nir. We stop. We need nvm words = ',nvm
1583          STOP 'pft_parameters_alloc'
1584       END IF
1585
1586      !chaoyue+
1587      ALLOCATE(permafrost_veg_exists(nvm),stat=ier)
1588      l_error = l_error .OR. (ier /= 0)
1589      IF (l_error) THEN
1590         WRITE(numout,*) ' Memory allocation error for permafrost_veg_exists. We stop. We need nvm words = ',nvm
1591         STOP 'pft_parameters_alloc'
1592      END IF
1593      !chaoyue-
1594
1595      IF( ok_bvoc ) THEN
1596
1597          l_error = .FALSE.
1598
1599          ALLOCATE(em_factor_isoprene(nvm),stat=ier)
1600          l_error = l_error .OR. (ier /= 0) 
1601          IF (l_error) THEN
1602             WRITE(numout,*) ' Memory allocation error for em_factor_isoprene. We stop. We need nvm words = ',nvm
1603             STOP 'pft_parameters_alloc'
1604          END IF
1605
1606          ALLOCATE(em_factor_monoterpene(nvm),stat=ier)
1607          l_error = l_error .OR. (ier /= 0) 
1608          IF (l_error) THEN
1609             WRITE(numout,*) ' Memory allocation error for em_factor_monoterpene. We stop. We need nvm words = ',nvm
1610             STOP 'pft_parameters_alloc'
1611          END IF
1612
1613          ALLOCATE(em_factor_apinene(nvm),stat=ier)
1614          l_error = l_error .OR. (ier /= 0) 
1615          IF (l_error) THEN
1616             WRITE(numout,*) ' Memory allocation error for em_factor_apinene. We stop. We need nvm words = ',nvm
1617             STOP 'pft_parameters_alloc'
1618          END IF
1619
1620          ALLOCATE(em_factor_bpinene(nvm),stat=ier)
1621          l_error = l_error .OR. (ier /= 0) 
1622          IF (l_error) THEN
1623             WRITE(numout,*) ' Memory allocation error for em_factor_bpinene. We stop. We need nvm words = ',nvm
1624             STOP 'pft_parameters_alloc'
1625          END IF
1626
1627          ALLOCATE(em_factor_limonene(nvm),stat=ier)
1628          l_error = l_error .OR. (ier /= 0) 
1629          IF (l_error) THEN
1630             WRITE(numout,*) ' Memory allocation error for em_factor_limonene. We stop. We need nvm words = ',nvm
1631             STOP 'pft_parameters_alloc'
1632          END IF
1633
1634          ALLOCATE(em_factor_myrcene(nvm),stat=ier)
1635          l_error = l_error .OR. (ier /= 0) 
1636          IF (l_error) THEN
1637             WRITE(numout,*) ' Memory allocation error for em_factor_myrcene. We stop. We need nvm words = ',nvm
1638             STOP 'pft_parameters_alloc'
1639          END IF
1640
1641          ALLOCATE(em_factor_sabinene(nvm),stat=ier)
1642          l_error = l_error .OR. (ier /= 0) 
1643          IF (l_error) THEN
1644             WRITE(numout,*) ' Memory allocation error for em_factor_sabinene. We stop. We need nvm words = ',nvm
1645             STOP 'pft_parameters_alloc'
1646          END IF
1647
1648          ALLOCATE(em_factor_camphene(nvm),stat=ier)
1649          l_error = l_error .OR. (ier /= 0) 
1650          IF (l_error) THEN
1651             WRITE(numout,*) ' Memory allocation error for em_factor_camphene. We stop. We need nvm words = ',nvm
1652             STOP 'pft_parameters_alloc'
1653          END IF
1654
1655          ALLOCATE(em_factor_3carene(nvm),stat=ier)
1656          l_error = l_error .OR. (ier /= 0) 
1657          IF (l_error) THEN
1658             WRITE(numout,*) ' Memory allocation error for em_factor_3carene. We stop. We need nvm words = ',nvm
1659             STOP 'pft_parameters_alloc'
1660          END IF
1661
1662          ALLOCATE(em_factor_tbocimene(nvm),stat=ier)
1663          l_error = l_error .OR. (ier /= 0) 
1664          IF (l_error) THEN
1665             WRITE(numout,*) ' Memory allocation error for em_factor_tbocimene. We stop. We need nvm words = ',nvm
1666             STOP 'pft_parameters_alloc'
1667          END IF
1668
1669          ALLOCATE(em_factor_othermonot(nvm),stat=ier)
1670          l_error = l_error .OR. (ier /= 0) 
1671          IF (l_error) THEN
1672             WRITE(numout,*) ' Memory allocation error for em_factor_othermonot. We stop. We need nvm words = ',nvm
1673             STOP 'pft_parameters_alloc'
1674          END IF
1675
1676          ALLOCATE(em_factor_sesquiterp(nvm),stat=ier)
1677          l_error = l_error .OR. (ier /= 0) 
1678          IF (l_error) THEN
1679             WRITE(numout,*) ' Memory allocation error for em_factor_sesquiterp. We stop. We need nvm words = ',nvm
1680             STOP 'pft_parameters_alloc'
1681          END IF
1682
1683
1684          ALLOCATE(em_factor_ORVOC(nvm),stat=ier)
1685          l_error = l_error .OR. (ier /= 0) 
1686          IF (l_error) THEN
1687             WRITE(numout,*) ' Memory allocation error for em_factor_ORVOC. We stop. We need nvm words = ',nvm
1688             STOP 'pft_parameters_alloc'
1689          END IF
1690
1691          ALLOCATE(em_factor_OVOC(nvm),stat=ier)
1692          l_error = l_error .OR. (ier /= 0)       
1693          IF (l_error) THEN
1694             WRITE(numout,*) ' Memory allocation error for em_factor_OVOC. We stop. We need nvm words = ',nvm
1695             STOP 'pft_parameters_alloc'
1696          END IF
1697
1698          ALLOCATE(em_factor_MBO(nvm),stat=ier)
1699          l_error = l_error .OR. (ier /= 0) 
1700          IF (l_error) THEN
1701             WRITE(numout,*) ' Memory allocation error for em_factor_MBO. We stop. We need nvm words = ',nvm
1702             STOP 'pft_parameters_alloc'
1703          END IF
1704
1705          ALLOCATE(em_factor_methanol(nvm),stat=ier)
1706          l_error = l_error .OR. (ier /= 0) 
1707          IF (l_error) THEN
1708             WRITE(numout,*) ' Memory allocation error for em_factor_methanol. We stop. We need nvm words = ',nvm
1709             STOP 'pft_parameters_alloc'
1710          END IF
1711
1712          ALLOCATE(em_factor_acetone(nvm),stat=ier)
1713          l_error = l_error .OR. (ier /= 0) 
1714          IF (l_error) THEN
1715             WRITE(numout,*) ' Memory allocation error for em_factor_acetone. We stop. We need nvm words = ',nvm
1716             STOP 'pft_parameters_alloc'
1717          END IF
1718
1719          ALLOCATE(em_factor_acetal(nvm),stat=ier)
1720          l_error = l_error .OR. (ier /= 0) 
1721          IF (l_error) THEN
1722             WRITE(numout,*) ' Memory allocation error for em_factor_acetal. We stop. We need nvm words = ',nvm
1723             STOP 'pft_parameters_alloc'
1724          END IF
1725
1726          ALLOCATE(em_factor_formal(nvm),stat=ier)
1727          l_error = l_error .OR. (ier /= 0) 
1728          IF (l_error) THEN
1729             WRITE(numout,*) ' Memory allocation error for em_factor_formal. We stop. We need nvm words = ',nvm
1730             STOP 'pft_parameters_alloc'
1731          END IF
1732
1733          ALLOCATE(em_factor_acetic(nvm),stat=ier)
1734          l_error = l_error .OR. (ier /= 0)       
1735          IF (l_error) THEN
1736             WRITE(numout,*) ' Memory allocation error for em_factor_acetic. We stop. We need nvm words = ',nvm
1737             STOP 'pft_parameters_alloc'
1738          END IF
1739
1740          ALLOCATE(em_factor_formic(nvm),stat=ier)
1741          l_error = l_error .OR. (ier /= 0) 
1742          IF (l_error) THEN
1743             WRITE(numout,*) ' Memory allocation error for em_factor_formic. We stop. We need nvm words = ',nvm
1744             STOP 'pft_parameters_alloc'
1745          END IF
1746
1747          ALLOCATE(em_factor_no_wet(nvm),stat=ier)
1748          l_error = l_error .OR. (ier /= 0)
1749          IF (l_error) THEN
1750             WRITE(numout,*) ' Memory allocation error for em_factor_no_wet. We stop. We need nvm words = ',nvm
1751             STOP 'pft_parameters_alloc'
1752          END IF
1753
1754          ALLOCATE(em_factor_no_dry(nvm),stat=ier)
1755          l_error = l_error .OR. (ier /= 0)       
1756          IF (l_error) THEN
1757             WRITE(numout,*) ' Memory allocation error for em_factor_no_dry. We stop. We need nvm words = ',nvm
1758             STOP 'pft_parameters_alloc'
1759          END IF
1760
1761          ALLOCATE(Larch(nvm),stat=ier)
1762          l_error = l_error .OR. (ier /= 0) 
1763          IF (l_error) THEN
1764             WRITE(numout,*) ' Memory allocation error for Larch. We stop. We need nvm words = ',nvm
1765             STOP 'pft_parameters_alloc'
1766          END IF
1767
1768       ENDIF ! (ok_bvoc)
1769
1770    ENDIF !(ok_sechiba)
1771
1772    !
1773    ! 3. Parameters used if ok_stomate only
1774    !
1775    IF ( ok_stomate ) THEN
1776
1777       l_error = .FALSE.
1778
1779       ALLOCATE(sla(nvm),stat=ier)
1780       l_error = l_error .OR. (ier /= 0)
1781       IF (l_error) THEN
1782          WRITE(numout,*) ' Memory allocation error for sla. We stop. We need nvm words = ',nvm
1783          STOP 'pft_parameters_alloc'
1784       END IF
1785
1786       ALLOCATE(availability_fact(nvm),stat=ier)
1787       l_error = l_error .OR. (ier /= 0)
1788       IF (l_error) THEN
1789          WRITE(numout,*) ' Memory allocation error for availability_fact. We stop. We need nvm words = ',nvm
1790          STOP 'pft_parameters_alloc'
1791       END IF
1792
1793       ALLOCATE(R0(nvm),stat=ier)
1794       l_error = l_error .OR. (ier /= 0)
1795       IF (l_error) THEN
1796          WRITE(numout,*) ' Memory allocation error for R0. We stop. We need nvm words = ',nvm
1797          STOP 'pft_parameters_alloc'
1798       END IF
1799
1800       ALLOCATE(S0(nvm),stat=ier)
1801       l_error = l_error .OR. (ier /= 0)
1802       IF (l_error) THEN
1803          WRITE(numout,*) ' Memory allocation error for S0. We stop. We need nvm words = ',nvm
1804          STOP 'pft_parameters_alloc'
1805       END IF
1806
1807       ALLOCATE(L0(nvm),stat=ier)
1808       l_error = l_error .OR. (ier /= 0)
1809       IF (l_error) THEN
1810          WRITE(numout,*) ' Memory allocation error for L0. We stop. We need nvm words = ',nvm
1811          STOP 'pft_parameters_alloc'
1812       END IF
1813
1814       ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier)
1815       l_error = l_error .OR. (ier /= 0)
1816       IF (l_error) THEN
1817          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_c. We stop. We need nvm words = ',nvm
1818          STOP 'pft_parameters_alloc'
1819       END IF
1820
1821       ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier)
1822       l_error = l_error .OR. (ier /= 0)
1823       IF (l_error) THEN
1824          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_b. We stop. We need nvm words = ',nvm
1825          STOP 'pft_parameters_alloc'
1826       END IF
1827
1828       ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier)
1829       l_error = l_error .OR. (ier /= 0)
1830       IF (l_error) THEN
1831          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit_a. We stop. We need nvm words = ',nvm
1832          STOP 'pft_parameters_alloc'
1833       END IF
1834
1835       ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier)
1836       l_error = l_error .OR. (ier /= 0)
1837       IF (l_error) THEN
1838          WRITE(numout,*) ' Memory allocation error for pheno_gdd_crit. We stop. We need nvm words = ',nvm*3
1839          STOP 'pft_parameters_alloc'
1840       END IF
1841       pheno_gdd_crit(:,:) = zero
1842
1843       ALLOCATE(pheno_moigdd_t_crit(nvm),stat=ier)
1844       l_error = l_error .OR. (ier /= 0)
1845       IF (l_error) THEN
1846          WRITE(numout,*) ' Memory allocation error for pheno_moigdd_t_crit. We stop. We need nvm words = ',nvm
1847          STOP 'pft_parameters_alloc'
1848       END IF
1849
1850       ALLOCATE(ngd_crit(nvm),stat=ier)
1851       l_error = l_error .OR. (ier /= 0)
1852       IF (l_error) THEN
1853          WRITE(numout,*) ' Memory allocation error for ngd_crit. We stop. We need nvm words = ',nvm
1854          STOP 'pft_parameters_alloc'
1855       END IF
1856
1857       ALLOCATE(ncdgdd_temp(nvm),stat=ier)
1858       l_error = l_error .OR. (ier /= 0)
1859       IF (l_error) THEN
1860          WRITE(numout,*) ' Memory allocation error for ncdgdd_temp. We stop. We need nvm words = ',nvm
1861          STOP 'pft_parameters_alloc'
1862       END IF
1863
1864       ALLOCATE(hum_frac(nvm),stat=ier)
1865       l_error = l_error .OR. (ier /= 0)
1866       IF (l_error) THEN
1867          WRITE(numout,*) ' Memory allocation error for hum_frac. We stop. We need nvm words = ',nvm
1868          STOP 'pft_parameters_alloc'
1869       END IF
1870
1871       ALLOCATE(hum_min_time(nvm),stat=ier)
1872       l_error = l_error .OR. (ier /= 0)
1873       IF (l_error) THEN
1874          WRITE(numout,*) ' Memory allocation error for hum_min_time. We stop. We need nvm words = ',nvm
1875          STOP 'pft_parameters_alloc'
1876       END IF
1877
1878       ALLOCATE(tau_sap(nvm),stat=ier)
1879       l_error = l_error .OR. (ier /= 0)
1880       IF (l_error) THEN
1881          WRITE(numout,*) ' Memory allocation error for tau_sap. We stop. We need nvm words = ',nvm
1882          STOP 'pft_parameters_alloc'
1883       END IF
1884
1885       ALLOCATE(tau_leafinit(nvm),stat=ier)
1886       l_error = l_error .OR. (ier /= 0)
1887       IF (l_error) THEN
1888          WRITE(numout,*) ' Memory allocation error for tau_leafinit. We stop. We need nvm words = ',nvm
1889          STOP 'pft_parameters_alloc'
1890       END IF
1891
1892       ALLOCATE(tau_fruit(nvm),stat=ier)
1893       l_error = l_error .OR. (ier /= 0)
1894       IF (l_error) THEN
1895          WRITE(numout,*) ' Memory allocation error for tau_fruit. We stop. We need nvm words = ',nvm
1896          STOP 'pft_parameters_alloc'
1897       END IF
1898
1899       ALLOCATE(ecureuil(nvm),stat=ier)
1900       l_error = l_error .OR. (ier /= 0)
1901       IF (l_error) THEN
1902          WRITE(numout,*) ' Memory allocation error for ecureuil. We stop. We need nvm words = ',nvm
1903          STOP 'pft_parameters_alloc'
1904       END IF
1905
1906       ALLOCATE(alloc_min(nvm),stat=ier)
1907       l_error = l_error .OR. (ier /= 0)
1908       IF (l_error) THEN
1909          WRITE(numout,*) ' Memory allocation error for alloc_min. We stop. We need nvm words = ',nvm
1910          STOP 'pft_parameters_alloc'
1911       END IF
1912
1913       ALLOCATE(alloc_max(nvm),stat=ier)
1914       l_error = l_error .OR. (ier /= 0)
1915       IF (l_error) THEN
1916          WRITE(numout,*) ' Memory allocation error for alloc_max. We stop. We need nvm words = ',nvm
1917          STOP 'pft_parameters_alloc'
1918       END IF
1919
1920       ALLOCATE(demi_alloc(nvm),stat=ier)
1921       l_error = l_error .OR. (ier /= 0)
1922       IF (l_error) THEN
1923          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
1924          STOP 'pft_parameters_alloc'
1925       END IF
1926
1927       ALLOCATE(frac_growthresp(nvm),stat=ier)
1928       l_error = l_error .OR. (ier /= 0)
1929       IF (l_error) THEN
1930          WRITE(numout,*) ' Memory allocation error for frac_growthresp. We stop. We need nvm words = ',nvm
1931          STOP 'pft_parameters_alloc'
1932       END IF
1933
1934       ALLOCATE(maint_resp_slope(nvm,3),stat=ier)
1935       l_error = l_error .OR. (ier /= 0)
1936       IF (l_error) THEN
1937          WRITE(numout,*) ' Memory allocation error for maint_resp_slope. We stop. We need nvm*3 words = ',nvm*3
1938          STOP 'pft_parameters_alloc'
1939       END IF
1940       maint_resp_slope(:,:) = zero
1941
1942       ALLOCATE(maint_resp_slope_c(nvm),stat=ier)
1943       l_error = l_error .OR. (ier /= 0)
1944       IF (l_error) THEN
1945          WRITE(numout,*) ' Memory allocation error for maint_resp_slope_c. We stop. We need nvm words = ',nvm
1946          STOP 'pft_parameters_alloc'
1947       END IF
1948
1949       ALLOCATE(maint_resp_slope_b(nvm),stat=ier)
1950       l_error = l_error .OR. (ier /= 0)
1951       IF (l_error) THEN
1952          WRITE(numout,*) ' Memory allocation error for maint_resp_slope_b. We stop. We need nvm words = ',nvm
1953          STOP 'pft_parameters_alloc'
1954       END IF
1955
1956       ALLOCATE(maint_resp_slope_a(nvm),stat=ier)
1957       l_error = l_error .OR. (ier /= 0)
1958       IF (l_error) THEN
1959          WRITE(numout,*) ' Memory allocation error for maint_resp_slope_a. We stop. We need nvm words = ',nvm
1960          STOP 'pft_parameters_alloc'
1961       END IF
1962
1963       ALLOCATE(coeff_maint_zero(nvm,nparts),stat=ier)
1964       l_error = l_error .OR. (ier /= 0)
1965       IF (l_error) THEN
1966          WRITE(numout,*) ' Memory allocation error for coeff_maint_zero. We stop. We need nvm*nparts words = ',nvm*nparts
1967          STOP 'pft_parameters_alloc'
1968       END IF
1969       coeff_maint_zero(:,:) = zero
1970
1971       ALLOCATE(cm_zero_leaf(nvm),stat=ier)
1972       l_error = l_error .OR. (ier /= 0)
1973       IF (l_error) THEN
1974          WRITE(numout,*) ' Memory allocation error for cm_zero_leaf. We stop. We need nvm words = ',nvm
1975          STOP 'pft_parameters_alloc'
1976       END IF
1977
1978       ALLOCATE(cm_zero_sapabove(nvm),stat=ier)
1979       l_error = l_error .OR. (ier /= 0)
1980       IF (l_error) THEN
1981          WRITE(numout,*) ' Memory allocation error for cm_zero_sapabove. We stop. We need nvm words = ',nvm
1982          STOP 'pft_parameters_alloc'
1983       END IF
1984
1985       ALLOCATE(cm_zero_sapbelow(nvm),stat=ier)
1986       l_error = l_error .OR. (ier /= 0)
1987       IF (l_error) THEN
1988          WRITE(numout,*) ' Memory allocation error for cm_zero_sapbelow. We stop. We need nvm words = ',nvm
1989          STOP 'pft_parameters_alloc'
1990       END IF
1991
1992       ALLOCATE(cm_zero_heartabove(nvm),stat=ier)
1993       l_error = l_error .OR. (ier /= 0)
1994       IF (l_error) THEN
1995          WRITE(numout,*) ' Memory allocation error for cm_zero_heartabove. We stop. We need nvm words = ',nvm
1996          STOP 'pft_parameters_alloc'
1997       END IF
1998       
1999       ALLOCATE(cm_zero_heartbelow(nvm),stat=ier)
2000       l_error = l_error .OR. (ier /= 0)
2001       IF (l_error) THEN
2002          WRITE(numout,*) ' Memory allocation error for cm_zero_heartbelow. We stop. We need nvm words = ',nvm
2003          STOP 'pft_parameters_alloc'
2004       END IF
2005
2006       ALLOCATE(cm_zero_root(nvm),stat=ier)
2007       l_error = l_error .OR. (ier /= 0)
2008       IF (l_error) THEN
2009          WRITE(numout,*) ' Memory allocation error for cm_zero_root. We stop. We need nvm words = ',nvm
2010          STOP 'pft_parameters_alloc'
2011       END IF
2012
2013       ALLOCATE(cm_zero_fruit(nvm),stat=ier)
2014       l_error = l_error .OR. (ier /= 0)
2015       IF (l_error) THEN
2016          WRITE(numout,*) ' Memory allocation error for cm_zero_fruit. We stop. We need nvm words = ',nvm
2017          STOP 'pft_parameters_alloc'
2018       END IF
2019
2020       ALLOCATE(cm_zero_carbres(nvm),stat=ier)
2021       l_error = l_error .OR. (ier /= 0)
2022       IF (l_error) THEN
2023          WRITE(numout,*) ' Memory allocation error for cm_zero_carbres. We stop. We need nvm words = ',nvm
2024          STOP 'pft_parameters_alloc'
2025       END IF
2026
2027      !spitfire
2028      ALLOCATE(dens_fuel(nvm),stat=ier)
2029      l_error = l_error .OR. (ier /= 0)
2030      IF (l_error) THEN
2031         WRITE(numout,*) ' Memory allocation error for dens_fuel. We stop. We need nvm words = ',nvm
2032         STOP 'pft_parameters_alloc'
2033      END IF
2034
2035      ALLOCATE(f_sh(nvm),stat=ier)
2036      l_error = l_error .OR. (ier /= 0)
2037      IF (l_error) THEN
2038         WRITE(numout,*) ' Memory allocation error for f_sh. We stop. We need nvm words = ',nvm
2039         STOP 'pft_parameters_alloc'
2040      END IF
2041
2042      ALLOCATE(crown_length(nvm),stat=ier)
2043      l_error = l_error .OR. (ier /= 0)
2044      IF (l_error) THEN
2045         WRITE(numout,*) ' Memory allocation error for crown_length. We stop. We need nvm words = ',nvm
2046         STOP 'pft_parameters_alloc'
2047      END IF
2048
2049      ALLOCATE(BTpar1(nvm),stat=ier)
2050      l_error = l_error .OR. (ier /= 0)
2051      IF (l_error) THEN
2052         WRITE(numout,*) ' Memory allocation error for BTpar1. We stop. We need nvm words = ',nvm
2053         STOP 'pft_parameters_alloc'
2054      END IF
2055
2056      ALLOCATE(BTpar2(nvm),stat=ier)
2057      l_error = l_error .OR. (ier /= 0)
2058      IF (l_error) THEN
2059         WRITE(numout,*) ' Memory allocation error for BTpar2. We stop. We need nvm words = ',nvm
2060         STOP 'pft_parameters_alloc'
2061      END IF
2062
2063      ALLOCATE(r_ck(nvm),stat=ier)
2064      l_error = l_error .OR. (ier /= 0)
2065      IF (l_error) THEN
2066         WRITE(numout,*) ' Memory allocation error for r_ck. We stop. We need nvm words = ',nvm
2067         STOP 'pft_parameters_alloc'
2068      END IF
2069
2070      ALLOCATE(p_ck(nvm),stat=ier)
2071      l_error = l_error .OR. (ier /= 0)
2072      IF (l_error) THEN
2073         WRITE(numout,*) ' Memory allocation error for p_ck. We stop. We need nvm words = ',nvm
2074         STOP 'pft_parameters_alloc'
2075      END IF
2076
2077      ALLOCATE(ef_CO2(nvm),stat=ier)
2078      l_error = l_error .OR. (ier /= 0)
2079      IF (l_error) THEN
2080         WRITE(numout,*) ' Memory allocation error for ef_CO2. We stop. We need nvm words = ',nvm
2081         STOP 'pft_parameters_alloc'
2082      END IF
2083
2084      ALLOCATE(ef_CO(nvm),stat=ier)
2085      l_error = l_error .OR. (ier /= 0)
2086      IF (l_error) THEN
2087         WRITE(numout,*) ' Memory allocation error for ef_CO. We stop. We need nvm words = ',nvm
2088         STOP 'pft_parameters_alloc'
2089      END IF
2090
2091      ALLOCATE(ef_CH4(nvm),stat=ier)
2092      l_error = l_error .OR. (ier /= 0)
2093      IF (l_error) THEN
2094         WRITE(numout,*) ' Memory allocation error for ef_CH4. We stop. We need nvm words = ',nvm
2095         STOP 'pft_parameters_alloc'
2096      END IF
2097
2098      ALLOCATE(ef_VOC(nvm),stat=ier)
2099      l_error = l_error .OR. (ier /= 0)
2100      IF (l_error) THEN
2101         WRITE(numout,*) ' Memory allocation error for ef_VOC. We stop. We need nvm words = ',nvm
2102         STOP 'pft_parameters_alloc'
2103      END IF
2104
2105      ALLOCATE(ef_TPM(nvm),stat=ier)
2106      l_error = l_error .OR. (ier /= 0)
2107      IF (l_error) THEN
2108         WRITE(numout,*) ' Memory allocation error for ef_TPM. We stop. We need nvm words = ',nvm
2109         STOP 'pft_parameters_alloc'
2110      END IF
2111
2112      ALLOCATE(ef_NOx(nvm),stat=ier)
2113      l_error = l_error .OR. (ier /= 0)
2114      IF (l_error) THEN
2115         WRITE(numout,*) ' Memory allocation error for ef_NOx. We stop. We need nvm words = ',nvm
2116         STOP 'pft_parameters_alloc'
2117      END IF
2118
2119      ALLOCATE(me(nvm),stat=ier)
2120      l_error = l_error .OR. (ier /= 0)
2121      IF (l_error) THEN
2122         WRITE(numout,*) ' Memory allocation error for me. We stop. We need nvm words = ',nvm
2123         STOP 'pft_parameters_alloc'
2124      END IF
2125
2126      ALLOCATE(fire_max_cf_100hr(nvm),stat=ier)
2127      l_error = l_error .OR. (ier /= 0)
2128      IF (l_error) THEN
2129         WRITE(numout,*) ' Memory allocation error for fire_max_cf_100hr. We stop. We need nvm words = ',nvm
2130         STOP 'pft_parameters_alloc'
2131      END IF
2132
2133      ALLOCATE(fire_max_cf_1000hr(nvm),stat=ier)
2134      l_error = l_error .OR. (ier /= 0)
2135      IF (l_error) THEN
2136         WRITE(numout,*) ' Memory allocation error for fire_max_cf_1000hr. We stop. We need nvm words = ',nvm
2137         STOP 'pft_parameters_alloc'
2138      END IF
2139      !endspit
2140
2141      ! grassland management
2142!gmjc
2143      ALLOCATE(is_grassland_manag(nvm),stat=ier)
2144      l_error = l_error .OR. (ier .NE. 0)
2145      IF (l_error) THEN
2146         WRITE(numout,*) ' Memory allocation error for is_grassland_manag. We stop. We need nvm words = ',nvm
2147         STOP 'pft_parameters_alloc'
2148      END IF
2149      ALLOCATE(is_grassland_cut(nvm),stat=ier)
2150      l_error = l_error .OR. (ier .NE. 0)
2151      IF (l_error) THEN
2152         WRITE(numout,*) ' Memory allocation error for is_grassland_cut. We stop. We need nvm words = ',nvm
2153         STOP 'pft_parameters_alloc'
2154      END IF
2155      ALLOCATE(is_grassland_grazed(nvm),stat=ier)
2156      l_error = l_error .OR. (ier .NE. 0)
2157      IF (l_error) THEN
2158         WRITE(numout,*) ' Memory allocation error for is_grassland_grazed. We stop. We need nvm words = ',nvm
2159         STOP 'pft_parameters_alloc'
2160      END IF
2161      ALLOCATE(management_intensity(nvm),stat=ier)
2162      l_error = l_error .OR. (ier .NE. 0)
2163      IF (l_error) THEN
2164         WRITE(numout,*) ' Memory allocation error for management_intensity. We stop. We need nvm words = ',nvm
2165         STOP 'pft_parameters_alloc'
2166      END IF
2167      ALLOCATE(management_start(nvm),stat=ier)
2168      l_error = l_error .OR. (ier .NE. 0)
2169      IF (l_error) THEN
2170         WRITE(numout,*) ' Memory allocation error for management_start. We stop. We need nvm words = ',nvm
2171         STOP 'pft_parameters_alloc'
2172      END IF
2173      ALLOCATE(deposition_start(nvm),stat=ier)
2174      l_error = l_error .OR. (ier .NE. 0)
2175      IF (l_error) THEN
2176         WRITE(numout,*) ' Memory allocation error for deposition_start. We stop. We need nvm words = ',nvm
2177         STOP 'pft_parameters_alloc'
2178      END IF
2179      ALLOCATE(nb_year_management(nvm),stat=ier)
2180      l_error = l_error .OR. (ier .NE. 0)
2181      IF (l_error) THEN
2182         WRITE(numout,*) ' Memory allocation error for nb_year_management. We stop. We need nvm words = ',nvm
2183         STOP 'pft_parameters_alloc'
2184      END IF
2185      ALLOCATE(sla_max(nvm),stat=ier)
2186      l_error = l_error .OR. (ier .NE. 0)
2187      IF (l_error) THEN
2188         WRITE(numout,*) ' Memory allocation error for sla_max. We stop. We need nvm words = ',nvm
2189         STOP 'pft_parameters_alloc'
2190      END IF
2191      ALLOCATE(sla_min(nvm),stat=ier)
2192      l_error = l_error .OR. (ier .NE. 0)
2193      IF (l_error) THEN
2194         WRITE(numout,*) ' Memory allocation error for sla_min. We stop. We need nvm words = ',nvm
2195         STOP 'pft_parameters_alloc'
2196      END IF
2197!end gmjc
2198
2199       ALLOCATE(flam(nvm),stat=ier)
2200       l_error = l_error .OR. (ier /= 0)
2201       IF (l_error) THEN
2202          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
2203          STOP 'pft_parameters_alloc'
2204       END IF
2205       ALLOCATE(resist(nvm),stat=ier)
2206       l_error = l_error .OR. (ier /= 0)
2207       IF (l_error) THEN
2208          WRITE(numout,*) ' Memory allocation error for resist. We stop. We need nvm words = ',nvm
2209          STOP 'pft_parameters_alloc'
2210       END IF
2211
2212       ALLOCATE(coeff_lcchange_1(nvm),stat=ier)
2213       l_error = l_error .OR. (ier /= 0)
2214       IF (l_error) THEN
2215          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_1. We stop. We need nvm words = ',nvm
2216          STOP 'pft_parameters_alloc'
2217       END IF
2218
2219       ALLOCATE(coeff_lcchange_10(nvm),stat=ier)
2220       l_error = l_error .OR. (ier /= 0)
2221       IF (l_error) THEN
2222          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_10. We stop. We need nvm words = ',nvm
2223          STOP 'pft_parameters_alloc'
2224       END IF
2225
2226       ALLOCATE(coeff_lcchange_100(nvm),stat=ier)
2227       l_error = l_error .OR. (ier /= 0)
2228       IF (l_error) THEN
2229          WRITE(numout,*) ' Memory allocation error for coeff_lcchange_100. We stop. We need nvm words = ',nvm
2230          STOP 'pft_parameters_alloc'
2231       END IF
2232
2233       ALLOCATE(lai_max_to_happy(nvm),stat=ier)
2234       l_error = l_error .OR. (ier /= 0)
2235       IF (l_error) THEN
2236          WRITE(numout,*) ' Memory allocation error for lai_max_to_happy. We stop. We need nvm words = ',nvm
2237          STOP 'pft_parameters_alloc'
2238       END IF
2239
2240       ALLOCATE(lai_max(nvm),stat=ier)
2241       l_error = l_error .OR. (ier /= 0)
2242       IF (l_error) THEN
2243          WRITE(numout,*) ' Memory allocation error for lai_max. We stop. We need nvm words = ',nvm
2244          STOP 'pft_parameters_alloc'
2245       END IF
2246
2247       ALLOCATE(pheno_type(nvm),stat=ier)
2248       l_error = l_error .OR. (ier /= 0)
2249       IF (l_error) THEN
2250          WRITE(numout,*) ' Memory allocation error for pheno_type. We stop. We need nvm words = ',nvm
2251          STOP 'pft_parameters_alloc'
2252       END IF
2253
2254       ALLOCATE(leaffall(nvm),stat=ier)
2255       l_error = l_error .OR. (ier /= 0)
2256       IF (l_error) THEN
2257          WRITE(numout,*) ' Memory allocation error for leaffall. We stop. We need nvm words = ',nvm
2258          STOP 'pft_parameters_alloc'
2259       END IF
2260
2261       ALLOCATE(leafagecrit(nvm),stat=ier)
2262       l_error = l_error .OR. (ier /= 0)
2263       IF (l_error) THEN
2264          WRITE(numout,*) ' Memory allocation error for leafagecrit. We stop. We need nvm words = ',nvm
2265          STOP 'pft_parameters_alloc'
2266       END IF
2267
2268       ALLOCATE(senescence_type(nvm),stat=ier)
2269       l_error = l_error .OR. (ier /= 0)
2270       IF (l_error) THEN
2271          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
2272          STOP 'pft_parameters_alloc'
2273       END IF
2274
2275       ALLOCATE(senescence_hum(nvm),stat=ier)
2276       l_error = l_error .OR. (ier /= 0)
2277       IF (l_error) THEN
2278          WRITE(numout,*) ' Memory allocation error for senescence_hum. We stop. We need nvm words = ',nvm
2279          STOP 'pft_parameters_alloc'
2280       END IF
2281
2282       ALLOCATE(nosenescence_hum(nvm),stat=ier)
2283       l_error = l_error .OR. (ier /= 0)
2284       IF (l_error) THEN
2285          WRITE(numout,*) ' Memory allocation error for nosenescence_hum. We stop. We need nvm words = ',nvm
2286          STOP 'pft_parameters_alloc'
2287       END IF
2288
2289       ALLOCATE(max_turnover_time(nvm),stat=ier)
2290       l_error = l_error .OR. (ier /= 0)
2291       IF (l_error) THEN
2292          WRITE(numout,*) ' Memory allocation error for max_turnover_time. We stop. We need nvm words = ',nvm
2293          STOP 'pft_parameters_alloc'
2294       END IF
2295
2296       ALLOCATE(min_turnover_time(nvm),stat=ier)
2297       l_error = l_error .OR. (ier /= 0)
2298       IF (l_error) THEN
2299          WRITE(numout,*) ' Memory allocation error for min_turnover_time. We stop. We need nvm words = ',nvm
2300          STOP 'pft_parameters_alloc'
2301       END IF
2302
2303       ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier)
2304       l_error = l_error .OR. (ier /= 0)
2305       IF (l_error) THEN
2306          WRITE(numout,*) ' Memory allocation error for min_leaf_age_for_senescence. We stop. We need nvm words = ',nvm
2307          STOP 'pft_parameters_alloc'
2308       END IF
2309
2310       ALLOCATE(senescence_temp_c(nvm),stat=ier)
2311       l_error = l_error .OR. (ier /= 0)
2312       IF (l_error) THEN
2313          WRITE(numout,*) ' Memory allocation error for senescence_temp_c. We stop. We need nvm words = ',nvm
2314          STOP 'pft_parameters_alloc'
2315       END IF
2316
2317       ALLOCATE(senescence_temp_b(nvm),stat=ier)
2318       l_error = l_error .OR. (ier /= 0)
2319       IF (l_error) THEN
2320          WRITE(numout,*) ' Memory allocation error for senescence_temp_b. We stop. We need nvm words = ',nvm
2321          STOP 'pft_parameters_alloc'
2322       END IF
2323
2324       ALLOCATE(senescence_temp_a(nvm),stat=ier)
2325       l_error = l_error .OR. (ier /= 0)
2326       IF (l_error) THEN
2327          WRITE(numout,*) ' Memory allocation error for senescence_temp_a. We stop. We need nvm words = ',nvm
2328          STOP 'pft_parameters_alloc'
2329       END IF
2330
2331       ALLOCATE(senescence_temp(nvm,3),stat=ier)
2332       l_error = l_error .OR. (ier /= 0)
2333       IF (l_error) THEN
2334          WRITE(numout,*) ' Memory allocation error for senescence_temp. We stop. We need nvm*3 words = ',nvm*3
2335          STOP 'pft_parameters_alloc'
2336       END IF
2337       senescence_temp(:,:) = zero
2338
2339       ALLOCATE(gdd_senescence(nvm),stat=ier)
2340       l_error = l_error .OR. (ier /= 0)
2341       IF (l_error) THEN
2342          WRITE(numout,*) ' Memory allocation error for gdd_senescence. We stop. We need nvm words = ',nvm
2343          STOP 'pft_parameters_alloc'
2344       END IF
2345
2346       ALLOCATE(residence_time(nvm),stat=ier)
2347       l_error = l_error .OR. (ier /= 0)
2348       IF (l_error) THEN
2349          WRITE(numout,*) ' Memory allocation error for residence_time. We stop. We need nvm words = ',nvm
2350          STOP 'pft_parameters_alloc'
2351       END IF
2352
2353       ALLOCATE(tmin_crit(nvm),stat=ier)
2354       l_error = l_error .OR. (ier /= 0)
2355       IF (l_error) THEN
2356          WRITE(numout,*) ' Memory allocation error for tmin_crit. We stop. We need nvm words = ',nvm
2357          STOP 'pft_parameters_alloc'
2358       END IF
2359
2360       ALLOCATE(tcm_crit(nvm),stat=ier)
2361       l_error = l_error .OR. (ier /= 0)
2362       IF (l_error) THEN
2363          WRITE(numout,*) ' Memory allocation error for tcm_crit. We stop. We need nvm words = ',nvm
2364          STOP 'pft_parameters_alloc'
2365       END IF
2366
2367       ALLOCATE(lai_initmin(nvm),stat=ier)
2368       l_error = l_error .OR. (ier /= 0)
2369       IF (l_error) THEN
2370          WRITE(numout,*) ' Memory allocation error for . We stop. We need nvm words = ',nvm
2371          STOP 'pft_parameters_alloc'
2372       END IF
2373
2374       ALLOCATE(bm_sapl(nvm,nparts,nelements),stat=ier)
2375       l_error = l_error .OR. (ier /= 0)
2376       IF (l_error) THEN
2377          WRITE(numout,*) ' Memory allocation error for bm_sapl. We stop. We need nvm*nparts*nelements words = ',& 
2378               &  nvm*nparts*nelements
2379          STOP 'pft_parameters_alloc'
2380       END IF
2381
2382!pss+
2383      ALLOCATE(rdepth_v(nvm),stat=ier)
2384      l_error = l_error .OR. (ier /= 0)
2385      IF (l_error) THEN
2386         WRITE(numout,*) ' Memory allocation error for rdepth_v. We stop. We need nvm words = ',nvm
2387         STOP 'pft_parameters_alloc'
2388      END IF
2389
2390      ALLOCATE(sdepth_v(nvm),stat=ier)
2391      l_error = l_error .OR. (ier /= 0)
2392      IF (l_error) THEN
2393         WRITE(numout,*) ' Memory allocation error for sdepth_v. We stop. We need nvm words = ',nvm
2394         STOP 'pft_parameters_alloc'
2395      END IF
2396
2397      ALLOCATE(tveg_v(nvm),stat=ier)
2398      l_error = l_error .OR. (ier /= 0)
2399      IF (l_error) THEN
2400         WRITE(numout,*) ' Memory allocation error for tveg_v. We stop. We need nvm words = ',nvm
2401         STOP 'pft_parameters_alloc'
2402      END IF
2403!pss-
2404
2405!!!!! crop parameters
2406
2407      ALLOCATE(ok_LAIdev(nvm),stat=ier)
2408      l_error = l_error .OR. (ier /= 0)
2409      ALLOCATE(SP_codeplante(nvm),stat=ier)
2410      l_error = l_error .OR. (ier /= 0)   
2411      ALLOCATE(SP_stade0(nvm),stat=ier)
2412      l_error = l_error .OR. (ier /= 0)   
2413      ALLOCATE(SP_iplt0(nvm),stat=ier)
2414      l_error = l_error .OR. (ier /= 0) 
2415      IF (cyc_rot_max .GT. 1) THEN
2416         ALLOCATE(SP_iplt1(nvm), stat=ier)
2417         l_error = l_error .OR. (ier /= 0)
2418      ENDIF
2419      IF (cyc_rot_max .GT. 2) THEN
2420         ALLOCATE(SP_iplt2(nvm), stat=ier)
2421         l_error = l_error .OR. (ier /= 0)
2422      ENDIF
2423      ALLOCATE(SP_nbox(nvm),stat=ier)
2424      l_error = l_error .OR. (ier /= 0) 
2425      ALLOCATE(SP_iwater(nvm),stat=ier)
2426      l_error = l_error .OR. (ier /= 0)
2427
2428      ALLOCATE(SP_codesimul(nvm),stat=ier)
2429      l_error = l_error .OR. (ier /= 0) 
2430      ALLOCATE(SP_codelaitr(nvm),stat=ier)
2431      l_error = l_error .OR. (ier /= 0)
2432
2433      ALLOCATE(SP_slamax(nvm),stat=ier)
2434      l_error = l_error .OR. (ier /= 0) 
2435      ALLOCATE(SP_slamin(nvm),stat=ier)
2436      l_error = l_error .OR. (ier /= 0)
2437
2438      ALLOCATE(SP_codeperenne(nvm),stat=ier)
2439      l_error = l_error .OR. (ier /= 0) 
2440      ALLOCATE(SP_codcueille(nvm),stat=ier)
2441      l_error = l_error .OR. (ier /= 0)
2442
2443      ALLOCATE(SP_codegdh(nvm),stat=ier)
2444      l_error = l_error .OR. (ier /= 0) 
2445      ALLOCATE(SP_codetemp(nvm),stat=ier)
2446      l_error = l_error .OR. (ier /= 0)
2447
2448      ALLOCATE(SP_coderetflo(nvm),stat=ier)
2449      l_error = l_error .OR. (ier /= 0) 
2450      ALLOCATE(SP_codeinnact(nvm),stat=ier)
2451      l_error = l_error .OR. (ier /= 0)
2452
2453      ALLOCATE(SP_codeh2oact(nvm),stat=ier)
2454      l_error = l_error .OR. (ier /= 0) 
2455      ALLOCATE(SP_stressdev(nvm),stat=ier)
2456      l_error = l_error .OR. (ier /= 0)
2457
2458      ALLOCATE(SP_innlai(nvm),stat=ier)
2459      l_error = l_error .OR. (ier /= 0)
2460      ALLOCATE(SP_innsenes(nvm),stat=ier)
2461      l_error = l_error .OR. (ier /= 0)
2462      ALLOCATE(SP_codebfroid(nvm),stat=ier)
2463      l_error = l_error .OR. (ier /= 0)
2464
2465      ALLOCATE(SP_codephot(nvm),stat=ier)
2466      l_error = l_error .OR. (ier /= 0)
2467      ALLOCATE(SP_codedormance(nvm),stat=ier)
2468      l_error = l_error .OR. (ier /= 0)
2469      ALLOCATE(SP_codefauche(nvm),stat=ier)
2470      l_error = l_error .OR. (ier /= 0)
2471      ALLOCATE(SP_codetempfauche(nvm),stat=ier)
2472      l_error = l_error .OR. (ier /= 0)
2473      ALLOCATE(SP_codlainet(nvm),stat=ier)
2474      l_error = l_error .OR. (ier /= 0)
2475      ALLOCATE(SP_codeindetermin(nvm),stat=ier)
2476      l_error = l_error .OR. (ier /= 0)
2477      ALLOCATE(SP_codeinitprec(nvm),stat=ier)
2478      l_error = l_error .OR. (ier /= 0)
2479      ALLOCATE(SP_culturean(nvm),stat=ier)
2480      l_error = l_error .OR. (ier /= 0)
2481      ALLOCATE(SP_jvc(nvm),stat=ier)
2482      l_error = l_error .OR. (ier /= 0)
2483      ALLOCATE(SP_tfroid(nvm),stat=ier)
2484      l_error = l_error .OR. (ier /= 0)
2485      ALLOCATE(SP_ampfroid(nvm),stat=ier)
2486      l_error = l_error .OR. (ier /= 0)
2487      ALLOCATE(SP_jvcmini(nvm),stat=ier)
2488      l_error = l_error .OR. (ier /= 0)
2489      ALLOCATE(SP_tgmin(nvm),stat=ier)
2490      l_error = l_error .OR. (ier /= 0)
2491      ALLOCATE(SP_stpltger(nvm),stat=ier)
2492      l_error = l_error .OR. (ier /= 0)
2493      ALLOCATE(SP_profsem(nvm),stat=ier)
2494      l_error = l_error .OR. (ier /= 0)
2495      ALLOCATE(SP_propjgermin(nvm),stat=ier)
2496      l_error = l_error .OR. (ier /= 0)
2497      ALLOCATE(SP_tdmax(nvm),stat=ier)
2498      l_error = l_error .OR. (ier /= 0)
2499      ALLOCATE(SP_nbjgerlim(nvm),stat=ier)
2500      l_error = l_error .OR. (ier /= 0)
2501      ALLOCATE(SP_densitesem(nvm),stat=ier)
2502      l_error = l_error .OR. (ier /= 0)
2503      ALLOCATE(SP_vigueurbat(nvm),stat=ier)
2504      l_error = l_error .OR. (ier /= 0)
2505      ALLOCATE(SP_codepluiepoquet(nvm),stat=ier)
2506      l_error = l_error .OR. (ier /= 0)
2507      ALLOCATE(SP_codehypo(nvm),stat=ier)
2508      l_error = l_error .OR. (ier /= 0)
2509      ALLOCATE(SP_elmax(nvm),stat=ier)
2510      l_error = l_error .OR. (ier /= 0)
2511      ALLOCATE(SP_belong(nvm),stat=ier)
2512      l_error = l_error .OR. (ier /= 0)
2513      ALLOCATE(SP_celong(nvm),stat=ier)
2514      l_error = l_error .OR. (ier /= 0)
2515      ALLOCATE(SP_nlevlim1(nvm),stat=ier)
2516      l_error = l_error .OR. (ier /= 0)
2517      ALLOCATE(SP_nlevlim2(nvm),stat=ier)
2518      l_error = l_error .OR. (ier /= 0)
2519      ALLOCATE(SP_codrecolte(nvm),stat=ier)
2520      l_error = l_error .OR. (ier /= 0)
2521      ALLOCATE(SP_variete(nvm),stat=ier)
2522      l_error = l_error .OR. (ier /= 0)
2523      ALLOCATE(SP_codegermin(nvm),stat=ier)
2524      l_error = l_error .OR. (ier /= 0)
2525
2526      ALLOCATE(S_codeulaivernal(nvm),stat=ier)
2527      l_error = l_error .OR. (ier /= 0)
2528      ALLOCATE(SP_swfacmin(nvm),stat=ier)
2529      l_error = l_error .OR. (ier /= 0)
2530      ALLOCATE(SP_neffmax(nvm),stat=ier)
2531      l_error = l_error .OR. (ier /= 0)
2532      ALLOCATE(SP_nsatrat(nvm),stat=ier)
2533      l_error = l_error .OR. (ier /= 0)
2534
2535
2536      ALLOCATE(SP_laiplantule(nvm),stat=ier)
2537      l_error = l_error .OR. (ier /= 0)
2538
2539      ALLOCATE(SP_vlaimax(nvm),stat=ier)
2540      l_error = l_error .OR. (ier /= 0)
2541      ALLOCATE(SP_stlevamf(nvm),stat=ier)
2542      l_error = l_error .OR. (ier /= 0)
2543      ALLOCATE(SP_stdrpmat(nvm),stat=ier)
2544      l_error = l_error .OR. (ier /= 0)
2545      ALLOCATE(SP_stamflax(nvm),stat=ier)
2546      l_error = l_error .OR. (ier /= 0)
2547      ALLOCATE(SP_udlaimax(nvm),stat=ier)
2548      l_error = l_error .OR. (ier /= 0)
2549      ALLOCATE(SP_laicomp(nvm),stat=ier)
2550      l_error = l_error .OR. (ier /= 0)
2551      ALLOCATE(SP_adens(nvm),stat=ier)
2552      l_error = l_error .OR. (ier /= 0)
2553      ALLOCATE(SP_bdens(nvm),stat=ier)
2554      l_error = l_error .OR. (ier /= 0)
2555      ALLOCATE(SP_tcxstop(nvm),stat=ier)
2556      l_error = l_error .OR. (ier /= 0)
2557      ALLOCATE(SP_tcmax(nvm),stat=ier)
2558      l_error = l_error .OR. (ier /= 0)
2559      ALLOCATE(SP_tcmin(nvm),stat=ier)
2560      l_error = l_error .OR. (ier /= 0)
2561      ALLOCATE(SP_dlaimax(nvm),stat=ier)
2562      l_error = l_error .OR. (ier /= 0)
2563      ALLOCATE(SP_dlaimin(nvm),stat=ier)
2564      l_error = l_error .OR. (ier /= 0)
2565      ALLOCATE(SP_pentlaimax(nvm),stat=ier)
2566      l_error = l_error .OR. (ier /= 0)
2567      ALLOCATE(SP_tigefeuil(nvm),stat=ier)
2568      l_error = l_error .OR. (ier /= 0)
2569     
2570      ALLOCATE(SP_stlaxsen(nvm),stat=ier)
2571      l_error = l_error .OR. (ier /= 0)
2572      ALLOCATE(SP_stsenlan(nvm),stat=ier)
2573      l_error = l_error .OR. (ier /= 0)
2574      ALLOCATE(SP_stlevdrp(nvm),stat=ier)
2575      l_error = l_error .OR. (ier /= 0)
2576      ALLOCATE(SP_stflodrp(nvm),stat=ier)
2577      l_error = l_error .OR. (ier /= 0)
2578      ALLOCATE(SP_stdrpdes(nvm),stat=ier)
2579      l_error = l_error .OR. (ier /= 0)
2580      ALLOCATE(SP_phyllotherme(nvm),stat=ier)
2581      l_error = l_error .OR. (ier /= 0)
2582
2583      ALLOCATE(SP_lai0(nvm),stat=ier)
2584      l_error = l_error .OR. (ier /= 0)
2585      ALLOCATE(SP_tustressmin(nvm),stat=ier)
2586      l_error = l_error .OR. (ier /= 0)
2587
2588
2589
2590      ! STICS:: LAI SENESCENCE
2591      ALLOCATE(SP_nbfgellev(nvm),stat=ier)
2592      l_error = l_error .OR. (ier /= 0)
2593      ALLOCATE(SP_ratiodurvieI(nvm),stat=ier)
2594      l_error = l_error .OR. (ier /= 0)
2595      ALLOCATE(SP_durvieF(nvm),stat=ier)
2596      l_error = l_error .OR. (ier /= 0)
2597      ALLOCATE(SP_ratiosen(nvm),stat=ier)
2598      l_error = l_error .OR. (ier /= 0)
2599      ALLOCATE(SP_tdmin(nvm),stat=ier)
2600      l_error = l_error .OR. (ier /= 0)
2601   
2602      ! STICS:: F_humerac
2603
2604      ALLOCATE(SP_sensrsec(nvm),stat=ier)
2605      l_error = l_error .OR. (ier /= 0)
2606      ! STICS:: GEL
2607
2608      ALLOCATE(SP_codgellev(nvm),stat=ier)
2609      l_error = l_error .OR. (ier /= 0)
2610      ALLOCATE(SP_codgeljuv(nvm),stat=ier)
2611      l_error = l_error .OR. (ier /= 0)
2612      ALLOCATE(SP_codgelveg(nvm),stat=ier)
2613      l_error = l_error .OR. (ier /= 0)
2614      ALLOCATE(SP_tletale(nvm),stat=ier)
2615      l_error = l_error .OR. (ier /= 0)
2616      ALLOCATE(SP_tdebgel(nvm),stat=ier)
2617      l_error = l_error .OR. (ier /= 0)
2618      ALLOCATE(SP_tgellev10(nvm),stat=ier)
2619      l_error = l_error .OR. (ier /= 0)
2620      ALLOCATE(SP_tgellev90(nvm),stat=ier)
2621      l_error = l_error .OR. (ier /= 0)
2622
2623
2624      ALLOCATE(SP_tgeljuv10(nvm),stat=ier)
2625      l_error = l_error .OR. (ier /= 0)
2626      ALLOCATE(SP_tgeljuv90(nvm),stat=ier)
2627      l_error = l_error .OR. (ier /= 0)
2628      ALLOCATE(SP_tgelveg10(nvm),stat=ier)
2629      l_error = l_error .OR. (ier /= 0)
2630      ALLOCATE(SP_tgelveg90(nvm),stat=ier)
2631      l_error = l_error .OR. (ier /= 0)
2632
2633
2634
2635
2636
2637
2638      ! STICS:: Photoperiod
2639
2640      ALLOCATE(SP_sensiphot(nvm),stat=ier)
2641      l_error = l_error .OR. (ier /= 0)
2642      ALLOCATE(SP_phosat(nvm),stat=ier)
2643      l_error = l_error .OR. (ier /= 0)
2644      ALLOCATE(SP_phobase(nvm),stat=ier)
2645      l_error = l_error .OR. (ier /= 0)
2646
2647      ! STICS:: CARBON ALLOCATION
2648
2649      ALLOCATE(SP_stoprac(nvm),stat=ier)
2650      l_error = l_error .OR. (ier /= 0)
2651      ALLOCATE(SP_zracplantule(nvm),stat=ier)
2652      l_error = l_error .OR. (ier /= 0)
2653      ALLOCATE(SP_codtrophrac(nvm),stat=ier)
2654      l_error = l_error .OR. (ier /= 0)
2655      ALLOCATE(SP_repracpermax(nvm),stat=ier)
2656      l_error = l_error .OR. (ier /= 0)
2657      ALLOCATE(SP_repracpermin(nvm),stat=ier)
2658      l_error = l_error .OR. (ier /= 0)
2659      ALLOCATE(SP_krepracperm(nvm),stat=ier)
2660      l_error = l_error .OR. (ier /= 0)
2661      ALLOCATE(SP_repracseumax(nvm),stat=ier)
2662      l_error = l_error .OR. (ier /= 0)
2663      ALLOCATE(SP_repracseumin(nvm),stat=ier)
2664      l_error = l_error .OR. (ier /= 0)
2665      ALLOCATE(SP_krepracseu(nvm),stat=ier)
2666      l_error = l_error .OR. (ier /= 0)
2667      ALLOCATE(SP_codetemprac(nvm),stat=ier)
2668      l_error = l_error .OR. (ier /= 0)
2669      ALLOCATE(SP_codedyntalle(nvm),stat=ier)
2670      l_error = l_error .OR. (ier /= 0)
2671      ALLOCATE(SP_nbjgrain(nvm),stat=ier)
2672      l_error = l_error .OR. (ier /= 0)
2673      ALLOCATE(SP_maxgs(nvm),stat=ier)
2674      l_error = l_error .OR. (ier /= 0)
2675      ALLOCATE(SP_codgelflo(nvm),stat=ier)
2676      l_error = l_error .OR. (ier /= 0)
2677      ALLOCATE(SP_tgelflo10(nvm),stat=ier)
2678      l_error = l_error .OR. (ier /= 0)
2679      ALLOCATE(SP_tgelflo90(nvm),stat=ier)
2680      l_error = l_error .OR. (ier /= 0)
2681      ALLOCATE(SP_cgrain(nvm),stat=ier)
2682      l_error = l_error .OR. (ier /= 0)
2683      ALLOCATE(SP_cgrainv0(nvm),stat=ier)
2684      l_error = l_error .OR. (ier /= 0)
2685      ALLOCATE(SP_nbgrmax(nvm),stat=ier)
2686      l_error = l_error .OR. (ier /= 0)
2687      ALLOCATE(SP_nbgrmin(nvm),stat=ier)
2688      l_error = l_error .OR. (ier /= 0)
2689      ALLOCATE(SP_codazofruit(nvm),stat=ier)
2690      l_error = l_error .OR. (ier /= 0)
2691      ALLOCATE(SP_codeir(nvm),stat=ier)
2692      l_error = l_error .OR. (ier /= 0)
2693      ALLOCATE(SP_vitircarb(nvm),stat=ier)
2694      l_error = l_error .OR. (ier /= 0)
2695      ALLOCATE(SP_irmax(nvm),stat=ier)
2696      l_error = l_error .OR. (ier /= 0)
2697      ALLOCATE(SP_vitircarbT(nvm),stat=ier)
2698      l_error = l_error .OR. (ier /= 0)
2699      ALLOCATE(SP_codetremp(nvm),stat=ier)
2700      l_error = l_error .OR. (ier /= 0)
2701      ALLOCATE(SP_tminremp(nvm),stat=ier)
2702      l_error = l_error .OR. (ier /= 0)
2703      ALLOCATE(SP_tmaxremp(nvm),stat=ier)
2704      l_error = l_error .OR. (ier /= 0)
2705      ALLOCATE(SP_pgrainmaxi(nvm),stat=ier)
2706      l_error = l_error .OR. (ier /= 0)
2707
2708      !! for dynamic nitrogen process
2709
2710      ALLOCATE(SP_DY_INN(nvm),stat=ier)
2711      l_error = l_error .OR. (ier /= 0)
2712
2713      ALLOCATE(SP_avenfert(nvm),stat=ier)
2714      l_error = l_error .OR. (ier /= 0)
2715
2716      IF (l_error) THEN
2717          STOP 'pft_alloc : error in memory allocation of crop pft parameters'
2718      ENDIF
2719!!!!! end crop parameters
2720
2721       ALLOCATE(migrate(nvm),stat=ier)
2722       l_error = l_error .OR. (ier /= 0)
2723       IF (l_error) THEN
2724          WRITE(numout,*) ' Memory allocation error for migrate. We stop. We need nvm words = ',nvm
2725          STOP 'pft_parameters_alloc'
2726       END IF
2727
2728       ALLOCATE(maxdia(nvm),stat=ier)
2729       l_error = l_error .OR. (ier /= 0)
2730       IF (l_error) THEN
2731          WRITE(numout,*) ' Memory allocation error for maxdia. We stop. We need nvm words = ',nvm
2732          STOP 'pft_parameters_alloc'
2733       END IF
2734
2735       ALLOCATE(cn_sapl(nvm),stat=ier)
2736       l_error = l_error .OR. (ier /= 0)
2737       IF (l_error) THEN
2738          WRITE(numout,*) ' Memory allocation error for cn_sapl. We stop. We need nvm words = ',nvm
2739          STOP 'pft_parameters_alloc'
2740       END IF
2741
2742       ALLOCATE(leaf_timecst(nvm),stat=ier)
2743       l_error = l_error .OR. (ier /= 0)
2744       IF (l_error) THEN
2745          WRITE(numout,*) ' Memory allocation error for leaf_timecst. We stop. We need nvm words = ',nvm
2746          STOP 'pft_parameters_alloc'
2747       END IF
2748
2749       ALLOCATE(leaflife_tab(nvm),stat=ier)   
2750       l_error = l_error .OR. (ier /= 0)
2751       IF (l_error) THEN
2752          WRITE(numout,*) ' Memory allocation error for leaflife_tab. We stop. We need nvm words = ',nvm
2753          STOP 'pft_parameters_alloc'
2754       END IF
2755
2756    ENDIF ! (ok_stomate)
2757
2758  END SUBROUTINE pft_parameters_alloc
2759
2760!! ================================================================================================================================
2761!! SUBROUTINE   : config_pft_parameters
2762!!
2763!>\BRIEF          This subroutine will read the imposed values for the global pft
2764!! parameters (sechiba + stomate). It is not called if IMPOSE_PARAM is set to NO.
2765!!
2766!! DESCRIPTION  : None
2767!!
2768!! RECENT CHANGE(S): None
2769!!
2770!! MAIN OUTPUT VARIABLE(S): None
2771!!
2772!! REFERENCE(S) : None
2773!!
2774!! FLOWCHART    : None
2775!! \n
2776!_ ================================================================================================================================
2777
2778  SUBROUTINE config_pft_parameters
2779
2780    IMPLICIT NONE
2781
2782    !! 0. Variables and parameters declaration
2783
2784    !! 0.4 Local variable
2785
2786    INTEGER(i_std) :: jv, ivm                   !! Index (untiless)
2787
2788    !_ ================================================================================================================================
2789
2790
2791    !
2792    ! Vegetation structure
2793    !
2794!gmjc
2795     !Config  Key  = IS_GRASSLAND_MANAG
2796     !Config  Desc = Is the vegetation type a managed grassland ?
2797     !Config  if  = OK_STOMATE
2798     !Config  Def  = n, n, n, n, n, n, n, n, n, y, n, n, n
2799     !Config  Help =
2800     !Config  Units = NONE
2801     CALL getin_p('GRM_IS_GRASSLAND_MANAG',is_grassland_manag)
2802     WRITE(numout,*) 'GRM_IS_GRASSLAND_MANAG',is_grassland_manag
2803     ![chaoyue] we have to warn temporarily if use_age_class is .TRUE.
2804     !but none of grassland is managed.
2805     IF (use_age_class .AND. ALL(.NOT.(is_grassland_manag))) THEN
2806       CALL ipslerr_p(3, 'config_pft_parameters', &
2807                         'Age classes are used but none of the ', &
2808                         'grasslands are managed! looks wierd, please confirm and uncoment this', &
2809                         'line if this is really what you want.' )
2810     ENDIF   
2811
2812     !Config  Key  = IS_GRASSLAND_CUT
2813     !Config  Desc = Is the vegetation type a cut grassland for management
2814     !adaptation ?
2815     !Config  if  = OK_STOMATE
2816     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, n, n
2817     !Config  Help =
2818     !Config  Units = NONE
2819     CALL getin_p('GRM_IS_GRASSLAND_CUT',is_grassland_cut)
2820     WRITE(numout,*) 'GRM_IS_GRASSLAND_CUT',is_grassland_cut
2821     !Config  Key  = IS_GRASSLAND_GRAZED
2822     !Config  Desc = Is the vegetation type a grazed grassland for management
2823     !adaptation ?
2824     !Config  if  = OK_STOMATE
2825     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, n, n
2826     !Config  Help =
2827     !Config  Units = NONE
2828     CALL getin_p('GRM_IS_GRASSLAND_GRAZED',is_grassland_grazed)
2829     WRITE(numout,*) 'GRM_IS_GRASSLAND_GRAZED',is_grassland_grazed
2830     !Config  Key  = MANAGEMENT_INTENSITY
2831     !Config  Desc = management intensity for grassland management
2832     !adaptation ?
2833     !Config  if  = OK_STOMATE
2834     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, n, n
2835     !Config  Help =
2836     !Config  Units = NONE
2837     CALL getin_p('GRM_MANAGE_INTENSITY',management_intensity)
2838     WRITE(numout,*) 'GRM_MANAGE_INTENSITY',management_intensity
2839     !Config  Key  = NB_YEAR_MANAGEMENT
2840     !Config  Desc = number of years for grassland management
2841     !adaptation ?
2842     !Config  if  = OK_STOMATE
2843     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, n, n
2844     !Config  Help =
2845     !Config  Units = NONE
2846     CALL getin_p('GRM_NB_YEAR_MANAGEMENT',nb_year_management)
2847     !Config  Key  = MANAGEMENT_START
2848     !Config  Desc = start time of grassland management
2849     !adaptation ?
2850     !Config  if  = OK_STOMATE
2851     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, n, n
2852     !Config  Help =
2853     !Config  Units = NONE
2854     CALL getin_p('GRM_MANAGEMENT_START',management_start)
2855     !Config  Key  = DEPOSITION_START
2856     !Config  Desc = start time of N depostion for grassland management
2857     !adaptation ?
2858     !Config  if  = OK_STOMATE
2859     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, n, n
2860     !Config  Help =
2861     !Config  Units = NONE
2862     CALL getin_p('GRM_DEPOSITION_START',deposition_start)
2863!end gmjc
2864
2865     !Config  Key  = PERMAFROST_VEG_EXISTS
2866     !Config  Desc = Is the vegetation type a permafrost vegetation
2867     !adaptation ?
2868     !Config  if  = OK_SECHIBA
2869     !Config  Def  = y, y, y, y, y, y, y, y, y, y, y, y, y
2870     !Config  Help =
2871     !Config  Units = NONE
2872     CALL getin_p('PERMAFROST_VEG_EXISTS', permafrost_veg_exists)
2873     
2874      !Config Key   = SECHIBA_LAI
2875      !Config Desc  = laimax for maximum lai(see also type of lai interpolation)
2876      !Config if    = OK_SECHIBA or IMPOSE_VEG
2877      !Config Def   = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2.
2878      !Config Help  = Maximum values of lai used for interpolation of the lai map
2879      !Config Units = [m^2/m^2]
2880      CALL getin_p('SECHIBA_LAI',llaimax)
2881
2882    !! Redefine the values for is_tree, is_deciduous, is_needleleaf, is_evergreen if values have been modified
2883    !! in run.def
2884
2885    is_tree(:) = .FALSE.
2886    DO jv = 1,nvm
2887       IF ( leaf_tab(jv) <= 2 ) is_tree(jv) = .TRUE.
2888    END DO
2889    !
2890    is_deciduous(:) = .FALSE.
2891    DO jv = 1,nvm
2892       IF ( is_tree(jv) .AND. (pheno_model(jv) /= "none") ) is_deciduous(jv) = .TRUE.
2893    END DO
2894    !
2895    is_evergreen(:) = .FALSE.
2896    DO jv = 1,nvm
2897       IF ( is_tree(jv) .AND. (pheno_model(jv) == "none") ) is_evergreen(jv) = .TRUE.
2898    END DO
2899    !
2900    is_needleleaf(:) = .FALSE.
2901    DO jv = 1,nvm
2902       IF ( leaf_tab(jv) == 2 ) is_needleleaf(jv) = .TRUE.
2903    END DO
2904
2905
2906    !Config Key   = SECHIBA_LAI
2907    !Config Desc  = laimax for maximum lai(see also type of lai interpolation)
2908    !Config if    = OK_SECHIBA or IMPOSE_VEG
2909    !Config Def   = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2.
2910    !Config Help  = Maximum values of lai used for interpolation of the lai map
2911    !Config Units = [m^2/m^2]
2912    CALL getin_p('SECHIBA_LAI',llaimax)
2913
2914    !Config Key   = LLAIMIN
2915    !Config Desc  = laimin for minimum lai(see also type of lai interpolation)
2916    !Config if    = OK_SECHIBA or IMPOSE_VEG
2917    !Config Def   = 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0.
2918    !Config Help  = Minimum values of lai used for interpolation of the lai map
2919    !Config Units = [m^2/m^2]
2920    CALL getin_p('LLAIMIN',llaimin)
2921
2922    !Config Key   = SLOWPROC_HEIGHT
2923    !Config Desc  = prescribed height of vegetation
2924    !Config if    = OK_SECHIBA
2925    !Config Def   = 0., 30., 30., 20., 20., 20., 15., 15., 15., .5, .6, 1., 1.
2926    !Config Help  =
2927    !Config Units = [m]
2928    CALL getin_p('SLOWPROC_HEIGHT',height_presc)
2929
2930      !Config Key   = NATURAL
2931      !Config Desc  = natural?
2932      !Config if    = OK_SECHIBA, OK_STOMATE
2933      !Config Def   = y, y, y, y, y, y, y, y, y, y, y, n, n, n
2934      !Config Help  =
2935      !Config Units = [BOOLEAN]
2936      CALL getin_p('NATURAL',natural)
2937      !!?? [chaoyue] could this give problems to downstream codes?
2938      ! [chaoyue] set all managed grassland to unnatural
2939      DO jv = 1,nvm
2940        IF (is_grassland_manag(jv) == .TRUE.) THEN
2941          natural(jv) = .FALSE.
2942        ENDIF
2943      ENDDO
2944! dgvmjc
2945    !Config Key   = PASTURE
2946    !Config Desc  = pasture?
2947    !Config if    = OK_SECHIBA, OK_STOMATE
2948    !Config Def   = y, y, y, y, y, y, y, y, y, y, y, n, n
2949    !Config Help  =
2950    !Config Units = [BOOLEAN]
2951    CALL getin_p('PASTURE',pasture)
2952! end dgvmjc
2953
2954    !
2955    !Config Key   = RATIO_Z0M_Z0H
2956    !Config Desc  = Ratio between z0m and z0h
2957    !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
2958    !Config if    = OK_SECHIBA
2959    !Config Help  =
2960    !Config Units = [-]
2961    CALL getin_p('RATIO_Z0M_Z0H',ratio_z0m_z0h)
2962
2963      !Config Key   = IS_C4
2964      !Config Desc  = flag for C4 vegetation types
2965      !Config if    = OK_SECHIBA or OK_STOMATE
2966      !Config Def   = n, n, n, n, n, n, n, n, n, n, n, y, n, y, n
2967      !Config Help  =
2968      !Config Units = [BOOLEAN]
2969      CALL getin_p('IS_C4',is_c4)
2970
2971    !Config Key   = TYPE_OF_LAI
2972    !Config Desc  = Type of behaviour of the LAI evolution algorithm
2973    !Config if    = OK_SECHIBA
2974    !Config Def   = inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter, inter
2975    !Config Help  =
2976    !Config Units = [-]
2977    CALL getin_p('TYPE_OF_LAI',type_of_lai)
2978
2979    !Config Key   = NATURAL
2980    !Config Desc  = natural?
2981    !Config if    = OK_SECHIBA, OK_STOMATE
2982    !Config Def   = y, y, y, y, y, y, y, y, y, y, y, n, n
2983    !Config Help  =
2984    !Config Units = [BOOLEAN]
2985    CALL getin_p('NATURAL',natural)
2986
2987
2988    !
2989    ! Photosynthesis
2990    !
2991
2992    !Config Key   = VCMAX_FIX
2993    !Config Desc  = values used for vcmax when STOMATE is not activated
2994    !Config if    = OK_SECHIBA and NOT(OK_STOMATE)
2995    !Config Def   = 0., 40., 50., 30., 35., 40.,30., 40., 35., 60., 60., 70., 70.
2996    !Config Help  =
2997    !Config Units = [micromol/m^2/s]
2998    CALL getin_p('VCMAX_FIX',vcmax_fix)
2999
3000    !Config Key   = DOWNREG_CO2
3001    !Config Desc  = coefficient for CO2 downregulation (unitless)
3002    !Config if    = OK_CO2
3003    !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
3004    !Config Help  =
3005    !Config Units = [-]
3006    CALL getin_p('DOWNREG_CO2',downregulation_co2_coeff)
3007
3008    !Config Key   = E_KmC
3009    !Config Desc  = Energy of activation for KmC
3010    !Config if    = OK_CO2
3011    !Config Def   = undef,  79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430., 79430.
3012    !Config Help  = See Medlyn et al. (2002)
3013    !Config Units = [J mol-1]
3014    CALL getin_p('E_KMC',E_KmC)
3015
3016    !Config Key   = E_KmO
3017    !Config Desc  = Energy of activation for KmO
3018    !Config if    = OK_CO2
3019    !Config Def   = undef, 36380.,  36380.,  36380.,  36380.,  36380., 36380., 36380., 36380., 36380., 36380., 36380., 36380.
3020    !Config Help  = See Medlyn et al. (2002)
3021    !Config Units = [J mol-1]
3022    CALL getin_p('E_KMO',E_KmO)
3023
3024    !Config Key   = E_Sco
3025    !Config Desc  = Energy of activation for Sco
3026    !Config if    = OK_CO2
3027    !Config Def   = undef, -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460., -24460.
3028    !Config Help  = See Table 2 of Yin et al. (2009) - Value for C4 plants is not mentioned - We use C3 for all plants
3029    !Config Units = [J mol-1]
3030    CALL getin_p('E_SCO',E_Sco)
3031   
3032    !Config Key   = E_gamma_star
3033    !Config Desc  = Energy of activation for gamma_star
3034    !Config if    = OK_CO2
3035    !Config Def   = undef, 37830.,  37830.,  37830.,  37830.,  37830., 37830., 37830., 37830., 37830., 37830., 37830., 37830.
3036    !Config Help  = See Medlyn et al. (2002) from Bernacchi al. (2001)
3037    !Config Units = [J mol-1]
3038    CALL getin_p('E_GAMMA_STAR',E_gamma_star)
3039
3040    !Config Key   = E_Vcmax
3041    !Config Desc  = Energy of activation for Vcmax
3042    !Config if    = OK_CO2
3043    !Config Def   = undef, 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 71513., 67300., 71513., 67300.
3044    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3)
3045    !Config Units = [J mol-1]
3046    CALL getin_p('E_VCMAX',E_Vcmax)
3047
3048    !Config Key   = E_Jmax
3049    !Config Desc  = Energy of activation for Jmax
3050    !Config if    = OK_CO2
3051    !Config Def   = undef, 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 49884., 77900., 49884., 77900.
3052    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Kattge & Knorr (2007) for C3 plants (table 3)
3053    !Config Units = [J mol-1]
3054    CALL getin_p('E_JMAX',E_Jmax)
3055
3056    !Config Key   = aSV
3057    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax
3058    !Config if    = OK_CO2
3059    !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
3060    !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)
3061    !Config Units = [J K-1 mol-1]
3062    CALL getin_p('ASV',aSV)
3063
3064    !Config Key   = bSV
3065    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax
3066    !Config if    = OK_CO2
3067    !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.
3068    !Config Help  = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation
3069    !Config Units = [J K-1 mol-1 °C-1]
3070    CALL getin_p('BSV',bSV)
3071
3072    !Config Key   = TPHOTO_MIN
3073    !Config Desc  = minimum photosynthesis temperature (deg C)
3074    !Config if    = OK_STOMATE
3075    !Config Def   = undef,  -4., -4., -4., -4.,-4.,-4., -4., -4., -4., -4., -4., -4.
3076    !Config Help  =
3077    !Config Units = [-]
3078    CALL getin_p('TPHOTO_MIN',tphoto_min)
3079
3080    !Config Key   = TPHOTO_MAX
3081    !Config Desc  = maximum photosynthesis temperature (deg C)
3082    !Config if    = OK_STOMATE
3083    !Config Def   = undef, 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55., 55.
3084    !Config Help  =
3085    !Config Units = [-]
3086    CALL getin_p('TPHOTO_MAX',tphoto_max)
3087
3088    !Config Key   = aSJ
3089    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax
3090    !Config if    = OK_CO2
3091    !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.
3092    !Config Help  = See Table 3 of Kattge & Knorr (2007) - and Table 2 of Yin et al. (2009) for C4 plants
3093    !Config Units = [J K-1 mol-1]
3094    CALL getin_p('ASJ',aSJ)
3095
3096    !Config Key   = bSJ
3097    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax
3098    !Config if    = OK_CO2
3099    !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.
3100    !Config Help  = See Table 3 of Kattge & Knorr (2007) - For C4 plants, we assume that there is no acclimation
3101    !Config Units = [J K-1 mol-1 °C-1]
3102    CALL getin_p('BSJ',bSJ)
3103
3104    !Config Key   = D_Vcmax
3105    !Config Desc  = Energy of deactivation for Vcmax
3106    !Config if    = OK_CO2
3107    !Config Def   = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000.
3108    !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.
3109    !Config Units = [J mol-1]
3110    CALL getin_p('D_VCMAX',D_Vcmax)
3111
3112    !Config Key   = D_Jmax
3113    !Config Desc  = Energy of deactivation for Jmax
3114    !Config if    = OK_CO2
3115    !Config Def   = undef, 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 200000., 192000., 200000., 192000.
3116    !Config Help  = See Table 2 of Yin et al. (2009)
3117    !Config Units = [J mol-1]
3118    CALL getin_p('D_JMAX',D_Jmax)
3119   
3120    !Config Key   = E_gm
3121    !Config Desc  = Energy of activation for gm
3122    !Config if    = OK_CO2
3123    !Config Def   = undef, 49600., 49600., 49600., 49600., 49600., 49600., 49600., 49600., 49600., undef, 49600., undef
3124    !Config Help  = See Table 2 of Yin et al. (2009)
3125    !Config Units = [J mol-1]
3126    CALL getin_p('E_GM',E_gm) 
3127   
3128    !Config Key   = S_gm
3129    !Config Desc  = Entropy term for gm
3130    !Config if    = OK_CO2
3131    !Config Def   = undef, 1400., 1400., 1400., 1400., 1400., 1400., 1400., 1400., 1400., undef, 1400., undef
3132    !Config Help  = See Table 2 of Yin et al. (2009)
3133    !Config Units = [J K-1 mol-1]
3134    CALL getin_p('S_GM',S_gm) 
3135   
3136    !Config Key   = D_gm
3137    !Config Desc  = Energy of deactivation for gm
3138    !Config if    = OK_CO2
3139    !Config Def   = undef, 437400., 437400., 437400., 437400., 437400., 437400., 437400., 437400., 437400., undef, 437400., undef
3140    !Config Help  = See Table 2 of Yin et al. (2009)
3141    !Config Units = [J mol-1]
3142    CALL getin_p('D_GM',D_gm) 
3143   
3144    !Config Key   = E_Rd
3145    !Config Desc  = Energy of activation for Rd
3146    !Config if    = OK_CO2
3147    !Config Def   = undef, 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390., 46390.
3148    !Config Help  = See Table 2 of Yin et al. (2009)
3149    !Config Units = [J mol-1]
3150    CALL getin_p('E_RD',E_Rd)
3151
3152    !Config Key   = VCMAX25
3153    !Config Desc  = Maximum rate of Rubisco activity-limited carboxylation at 25°C
3154    !Config if    = OK_STOMATE
3155    !Config Def   = undef, 50., 65., 35., 45., 55., 35., 45., 35., 70., 70., 70., 70.
3156    !Config Help  =
3157    !Config Units = [micromol/m^2/s]
3158    CALL getin_p('VCMAX25',Vcmax25)
3159
3160    !Config Key   = ARJV
3161    !Config Desc  = a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio
3162    !Config if    = OK_STOMATE
3163    !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
3164    !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)
3165    !Config Units = [mu mol e- (mu mol CO2)-1]
3166    CALL getin_p('ARJV',arJV)
3167
3168    !Config Key   = BRJV
3169    !Config Desc  = b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio
3170    !Config if    = OK_STOMATE
3171    !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.
3172    !Config Help  = See Table 3 of Kattge & Knorr (2007) -  We assume No acclimation term for C4 plants
3173    !Config Units = [(mu mol e- (mu mol CO2)-1) (°C)-1]
3174    CALL getin_p('BRJV',brJV)
3175
3176    !Config Key   = KmC25
3177    !Config Desc  = Michaelis–Menten constant of Rubisco for CO2 at 25°C
3178    !Config if    = OK_CO2
3179    !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.
3180    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants
3181    !Config Units = [ubar]
3182    CALL getin_p('KMC25',KmC25)
3183
3184    !Config Key   = KmO25
3185    !Config Desc  = Michaelis–Menten constant of Rubisco for O2 at 25°C
3186    !Config if    = OK_CO2
3187    !Config Def   = undef, 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 278400., 450000., 278400., 450000.
3188    !Config Help  = See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3 plants
3189    !Config Units = [ubar]
3190    CALL getin_p('KMO25',KmO25)
3191
3192    !Config Key   = Sco25
3193    !Config Desc  = Relative CO2 /O2 specificity factor for Rubisco at 25°C
3194    !Config if    = OK_CO2
3195    !Config Def   = undef, 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2800., 2590., 2800., 2590.
3196    !Config Help  = See Table 2 of Yin et al. (2009)
3197    !Config Units = [bar bar-1]
3198    CALL getin_p('SCO25',Sco25)
3199   
3200    !Config Key   = gm25
3201    !Config Desc  = Mesophyll diffusion conductance at 25°C
3202    !Config if    = OK_CO2
3203    !Config Def   = undef, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, 0.4, undef, 0.4, undef
3204    !Config Help  = See legend of Figure 6 of Yin et al. (2009) and review by Flexas et al. (2008) - gm is not used for C4 plants
3205    !Config Units = [mol m-2 s-1 bar-1]
3206    CALL getin_p('GM25',gm25) 
3207   
3208    !Config Key   = gamma_star25
3209    !Config Desc  = Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
3210    !Config if    = OK_CO2
3211    !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
3212    !Config Help  = See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the same value (probably uncorrect)
3213    !Config Units = [ubar]
3214    CALL getin_p('gamma_star25',gamma_star25)
3215
3216    !Config Key   = a1
3217    !Config Desc  = Empirical factor involved in the calculation of fvpd
3218    !Config if    = OK_CO2
3219    !Config Def   = undef, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.85, 0.72, 0.85, 0.72
3220    !Config Help  = See Table 2 of Yin et al. (2009)
3221    !Config Units = [-]
3222    CALL getin_p('A1',a1)
3223
3224    !Config Key   = b1
3225    !Config Desc  = Empirical factor involved in the calculation of fvpd
3226    !Config if    = OK_CO2
3227    !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
3228    !Config Help  = See Table 2 of Yin et al. (2009)
3229    !Config Units = [-]
3230    CALL getin_p('B1',b1)
3231
3232    !Config Key   = g0
3233    !Config Desc  = Residual stomatal conductance when irradiance approaches zero
3234    !Config if    = OK_CO2
3235    !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
3236    !Config Help  = Value from ORCHIDEE - No other reference.
3237    !Config Units = [mol m−2 s−1 bar−1]
3238    CALL getin_p('G0',g0)
3239
3240    !Config Key   = h_protons
3241    !Config Desc  = Number of protons required to produce one ATP
3242    !Config if    = OK_CO2
3243    !Config Def   = undef, 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4., 4.
3244    !Config Help  = See Table 2 of Yin et al. (2009) - h parameter
3245    !Config Units = [mol mol-1]
3246    CALL getin_p('H_PROTONS',h_protons)
3247
3248    !Config Key   = fpsir
3249    !Config Desc  = Fraction of PSII e− transport rate partitioned to the C4 cycle
3250    !Config if    = OK_CO2
3251    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.4, undef, 0.4
3252    !Config Help  = See Table 2 of Yin et al. (2009)
3253    !Config Units = [-]
3254    CALL getin_p('FPSIR',fpsir)
3255
3256    !Config Key   = fQ
3257    !Config Desc  = Fraction of electrons at reduced plastoquinone that follow the Q-cycle
3258    !Config if    = OK_CO2
3259    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 1., undef, 1.
3260    !Config Help  = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used
3261    !Config Units = [-]
3262    CALL getin_p('FQ',fQ)
3263
3264    !Config Key   = fpseudo
3265    !Config Desc  = Fraction of electrons at PSI that follow pseudocyclic transport
3266    !Config if    = OK_CO2
3267    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1
3268    !Config Help  = See Table 2 of Yin et al. (2009) - Values for C3 plants are not used
3269    !Config Units = [-]
3270    CALL getin_p('FPSEUDO',fpseudo)
3271
3272    !Config Key   = kp
3273    !Config Desc  = Initial carboxylation efficiency of the PEP carboxylase
3274    !Config if    = OK_CO2
3275    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.7, undef, 0.7
3276    !Config Help  = See Table 2 of Yin et al. (2009)
3277    !Config Units = [mol m−2 s−1 bar−1]
3278    CALL getin_p('KP',kp)
3279
3280    !Config Key   = alpha
3281    !Config Desc  = Fraction of PSII activity in the bundle sheath
3282    !Config if    = OK_CO2
3283    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.1, undef, 0.1
3284    !Config Help  = See legend of Figure 6 of Yin et al. (2009)
3285    !Config Units = [-]
3286    CALL getin_p('ALPHA',alpha)
3287
3288    !Config Key   = gbs
3289    !Config Desc  = Bundle-sheath conductance
3290    !Config if    = OK_CO2
3291    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.003, undef, 0.003
3292    !Config Help  = See legend of Figure 6 of Yin et al. (2009)
3293    !Config Units = [mol m−2 s−1 bar−1]
3294    CALL getin_p('GBS',gbs)
3295
3296    !Config Key   = theta
3297    !Config Desc  = Convexity factor for response of J to irradiance
3298    !Config if    = OK_CO2
3299    !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
3300    !Config Help  = See Table 2 of Yin et al. (2009)   
3301    !Config Units = [−]
3302    CALL getin_p('THETA',theta)
3303
3304    !Config Key   = STRESS_VCMAX
3305    !Config Desc  = Stress on vcmax
3306    !Config if    = OK_SECHIBA or OK_STOMATE
3307    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3308    !Config Help  =
3309    !Config Units = [-]
3310    CALL getin_p('STRESS_VCMAX', stress_vcmax)
3311   
3312    !Config Key   = STRESS_GS
3313    !Config Desc  = Stress on gs
3314    !Config if    = OK_SECHIBA or OK_STOMATE
3315    !Config Def   = 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
3316    !Config Help  =
3317    !Config Units = [-]
3318    CALL getin_p('STRESS_GS', stress_gs)
3319   
3320    !Config Key   = STRESS_GM
3321    !Config Desc  = Stress on gm
3322    !Config if    = OK_SECHIBA or OK_STOMATE
3323    !Config Def   = 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
3324    !Config Help  =
3325    !Config Units = [-]
3326    CALL getin_p('STRESS_GM', stress_gm)
3327
3328    !Config Key   = EXT_COEFF
3329    !Config Desc  = extinction coefficient of the Monsi&Seaki relationship (1953)
3330    !Config if    = OK_SECHIBA or OK_STOMATE
3331    !Config Def   = .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
3332    !Config Help  =
3333    !Config Units = [-]
3334    CALL getin_p('EXT_COEFF',ext_coeff)
3335
3336!!!!! xuhui for crop rotation
3337      CALL getin_p('NSTM',nstm)
3338      IF ( (nstm .LT. 2) .OR. (nstm .GT. 20) ) THEN
3339        WRITE(numout,*) 'bad value for nstm: ',nstm
3340        WRITE(numout,*) 'set nstm as 6 (default)'
3341      ENDIF
3342      IF ( nstm .LT. 6) THEN
3343        ! default value did not work properly
3344        WHERE (pref_soil_veg(:) .GT. nstm)
3345            pref_soil_veg(:) = nstm
3346        ENDWHERE
3347!        Make sure model can work anyway
3348      ENDIF
3349!!!!! end crop rotation, xuhui
3350
3351      !Config Key   = PREF_SOIL_VEG
3352      !Config Desc  = The soil tile number for each vegetation
3353      !Config if    = OK_SECHIBA or OK_STOMATE
3354      !Config Def   = 1, 2, 2, 2, 2, 2, 2, 2, 2, 3, 3, 4, 5, 6
3355      !Config Help  = Gives the number of the soil tile on which we will
3356      !Config         put each vegetation. This allows to divide the hydrological column
3357      !Config Units = [-]       
3358      CALL getin_p('PREF_SOIL_VEG',pref_soil_veg)
3359      !! we should judge whether the pref_soil_veg is larger than nstm
3360
3361!!!!! crop parameters     
3362      !Config Key   = IRRIG_THRESHOLD
3363      !Config if    = OK_SECHIBA, OK_STOMATE, DO_IRRIGATION
3364      CALL getin_p('IRRIG_THRESHOLD',irrig_threshold) 
3365
3366      CALL getin_p('IRRIG_FULFILL',irrig_fulfill) 
3367     
3368     
3369      !
3370      !
3371      !Config Key   = OK_LAIDEV
3372      !Config Desc  = whether or not we open the STICS module
3373      !Config if    = OK_STOMATE
3374      !Config Def   = .false., .false., .false., .false., .false., .false., .false., .false., .false., .false., .false.,  .true., .true.
3375      !Config Help  =
3376      !Config Units = [C]
3377      CALL getin_p('OK_LAIDEV',ok_LAIdev)
3378
3379      !
3380      !Config Key   = SP_CODEPHOT
3381      !Config Desc  = whether or not sensitive to photoperiod
3382      !Config if    = OK_STOMATE
3383      !Config Def   = undef_int,undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, 1, 1
3384      !Config Help  =
3385      !Config Units = [C]
3386      CALL getin_p('SP_CODEPHOT',SP_codephot)
3387     
3388
3389      !
3390      !Config Key   = SP_iplt0
3391      !Config Desc  = sowing date
3392      !Config if    = OK_STOMATE
3393      !Config Def   = undef_int,  undef_int,undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, undef_int, 292, 117
3394      !Config Help  =
3395      !Config Units = [C]
3396      CALL getin_p('SP_IPLT0',SP_iplt0)
3397      IF (cyc_rot_max .GT. 1) THEN
3398          CALL getin_p('SP_IPLT1',SP_iplt1)
3399      ENDIF
3400      IF (cyc_rot_max .GT. 2) THEN
3401          CALL getin_p('SP_IPLT2',SP_iplt2)
3402      ENDIF
3403
3404      CALL getin_p('CODELAINET',SP_codlainet)
3405      CALL getin_p('STPLTGER',SP_stpltger)
3406      CALL getin_p('STADE0',SP_stade0)
3407      CALL getin_p('DLAIMAX',SP_dlaimax)
3408!      CALL getin_p('INNSENES',SP_innsenes)
3409      CALL getin_p('CODEHYPO',SP_codehypo)
3410      CALL getin_p('LAIPLANTULE',SP_laiplantule)
3411      CALL getin_p('INNLAI',SP_innlai)
3412      CALL getin_P('DURVIEF',SP_durvieF)
3413      CALL getin_p('VLAIMAX',SP_vlaimax)
3414      CALL getin_p('STLEVAMF',SP_stlevamf)
3415      CALL getin_p('STDRPMAT',SP_stdrpmat)
3416      CALL getin_p('STLEVDRP',SP_stlevdrp)
3417      CALL getin_p('STAMFLAX',SP_stamflax)
3418      CALL getin_p('NUMAGEBOX',SP_nbox)
3419      CALL getin_p('LAI0',SP_lai0)
3420      CALL getin_p('TDMAX',SP_tdmax)
3421      CALL getin_p('TDMIN',SP_tdmin)
3422      CALL getin_p('TCXSTOP',SP_tcxstop)
3423      CALL getin_p('TCMAX',SP_tcmax)
3424      CALL getin_p('TCMIN',SP_tcmin)
3425      CALL getin_p('NEFFMAX',SP_neffmax)
3426      CALL getin_p('NSATRAT',SP_nsatrat)
3427      CALL getin_p('CODEIR',SP_codeir)
3428      CALL getin_p('VITIRCARB',SP_vitircarb)
3429      CALL getin_p('VITIRCARBT',SP_vitircarbT)
3430      CALL getin_p('SWFACMIN',SP_swfacmin)
3431      CALL getin_p('IRMAX',SP_irmax)
3432      CALL getin_p('REPRACMAX',SP_repracpermax)
3433      CALL getin_p('REPRACMIN',SP_repracpermin)
3434      CALL getin_p('TMINREMP',SP_tminremp)
3435      CALL getin_p('TMAXREMP',SP_tmaxremp)
3436      CALL getin_p('NBJGRAIN',SP_nbjgrain)
3437
3438      CALL getin_p('DENSITESEM',SP_densitesem)
3439      CALL getin_p('SLAMAX',SP_slamax)
3440      CALL getin_p('STLAXSEN',SP_stlaxsen)
3441      CALL getin_p('STSENLAN',SP_stsenlan)
3442      CALL getin_p('ZRACPLANTULE',SP_zracplantule)
3443      CALL getin_p('TGMIN',SP_tgmin)
3444      CALL getin_p('BDENS',SP_bdens)
3445       
3446
3447      !! for dynamic nitrogen processes
3448
3449      !
3450      !
3451      !Config Key   = DY_INN
3452      !Config Desc  = whether or not we use the dynamic nitrogen processes
3453      !Config if    = OK_STOMATE
3454      !Config Def   = .false., .false., .false., .false., .false., .false., .false., .false., .false., .false., .false.,  .false., .false.
3455      !Config Help  =
3456      !Config Units = logic
3457      CALL getin_p('DY_INN',SP_DY_INN)
3458
3459
3460      !! for dynamic nitrogen processes
3461
3462      !
3463      !
3464      !Config Key   = SP_AVENFERT
3465      !Config Desc  = the average nitrogen fertilization
3466      !Config if    = OK_STOMATE
3467      !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 150.0, 100.0, 100.0
3468      !Config Help  =
3469      !Config Units = kg N ha-1
3470      CALL getin_p('SP_AVENFERT',SP_avenfert)
3471
3472
3473!!!!! end crop parameters, xuhui
3474
3475      !
3476      ! Vegetation - Age classes
3477      !
3478      !Config Key   = NVMAP
3479      !Config Desc  = The number of PFTs if we ignore age classes. 
3480      !               i.e., the number of metaclasses.
3481      !Config if    = OK_SECHIBA or OK_STOMATE
3482      !Config Def   = nvm
3483      !Config Help  = Gives the total number of PFTs ignoring age classes.
3484      !Config Units = [-] 
3485      nvmap=nvm
3486      IF (use_age_class) THEN
3487         CALL getin_p('GLUC_NVMAP',nvmap)
3488         IF(nvmap == nvm .AND. .NOT. SingleAgeClass)THEN
3489            WRITE(numout,*) 'WARNING: The age classes will be used, but'
3490            WRITE(numout,*) '         the input file indicates that none of the PFTs have age classes.'
3491            WRITE(numout,*) '         You should change nvmap.'
3492         ENDIF
3493
3494         !Config Key   = AGEC_GROUP
3495         !Config Desc  = The group that each PFT belongs to. 
3496         !Config if    = OK_SECHIBA or OK_STOMATE
3497         !Config Def   = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
3498         !Config Help  = The group that each PFT belongs to.  If you are not using age classes, this
3499         !Config         is just equal to the number of the PFT.
3500         !Config Units = [-]   
3501         DO ivm=1,nvm
3502            agec_group(ivm)=ivm
3503         ENDDO
3504         CALL getin_p('GLUC_AGEC_GROUP',agec_group)
3505         IF (.NOT. use_bound_spa) THEN
3506           CALL getin_p('GLUC_AGE_CLASS_BOUND',age_class_bound)
3507         ENDIF
3508      ENDIF
3509
3510    !Config Key   = EXT_COEFF_VEGETFRAC
3511    !Config Desc  = extinction coefficient used for the calculation of the bare soil fraction
3512    !Config if    = OK_SECHIBA or OK_STOMATE
3513    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3514    !Config Help  =
3515    !Config Units = [-]
3516    CALL getin_p('EXT_COEFF_VEGETFRAC',ext_coeff_vegetfrac)
3517
3518    !
3519    ! Water-hydrology - sechiba
3520    !
3521
3522    !Config Key   = HYDROL_HUMCSTE
3523    !Config Desc  = Root profile
3524    !Config Def   = humcste_ref2m or humcste_ref4m depending on zmaxh
3525    !Config if    = OK_SECHIBA
3526    !Config Help  = See module constantes_mtc for different default values
3527    !Config Units = [m]
3528    CALL getin_p('HYDROL_HUMCSTE',humcste)
3529
3530    !
3531    ! Soil - vegetation
3532    !
3533
3534    !Config Key   = PREF_SOIL_VEG
3535    !Config Desc  = The soil tile number for each vegetation
3536    !Config if    = OK_SECHIBA or OK_STOMATE
3537    !Config Def   = 1, 2, 2, 2, 2, 2, 2, 2, 2, 3, 3, 3, 3
3538    !Config Help  = Gives the number of the soil tile on which we will
3539    !Config         put each vegetation. This allows to divide the hydrological column
3540    !Config Units = [-]       
3541    CALL getin_p('PREF_SOIL_VEG',pref_soil_veg)
3542
3543  END SUBROUTINE config_pft_parameters
3544
3545
3546!! ================================================================================================================================
3547!! SUBROUTINE   : config_sechiba_pft_parameters
3548!!
3549!>\BRIEF        This subroutine will read the imposed values for the sechiba pft
3550!! parameters. It is not called if IMPOSE_PARAM is set to NO.
3551!!
3552!! DESCRIPTION  : None
3553!!
3554!! RECENT CHANGE(S): None
3555!!
3556!! MAIN OUTPUT VARIABLE(S): None
3557!!
3558!! REFERENCE(S) : None
3559!!
3560!! FLOWCHART    : None
3561!! \n
3562!_ ================================================================================================================================
3563
3564  SUBROUTINE config_sechiba_pft_parameters()
3565
3566    IMPLICIT NONE
3567
3568    !! 0. Variables and parameters declaration
3569
3570    !! 0.1 Input variables
3571
3572    !! 0.4 Local variable
3573
3574    !_ ================================================================================================================================
3575
3576    !
3577    ! Evapotranspiration -  sechiba
3578    !
3579
3580    !Config Key   = RSTRUCT_CONST
3581    !Config Desc  = Structural resistance
3582    !Config if    = OK_SECHIBA
3583    !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
3584    !Config Help  =
3585    !Config Units = [s/m]
3586    CALL getin_p('RSTRUCT_CONST',rstruct_const)
3587
3588    !Config Key   = KZERO
3589    !Config Desc  = A vegetation dependent constant used in the calculation of the surface resistance.
3590    !Config if    = OK_SECHIBA
3591    !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
3592    !Config Help  =
3593    !Config Units = [kg/m^2/s]
3594    CALL getin_p('KZERO',kzero)
3595
3596    !Config Key   = RVEG_PFT
3597    !Config Desc  = Artificial parameter to increase or decrease canopy resistance.
3598    !Config if    = OK_SECHIBA
3599    !Config Def   = 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1., 1.
3600    !Config Help  = This parameter is set by PFT.
3601    !Config Units = [-]
3602    CALL getin_p('RVEG_PFT',rveg_pft)   
3603
3604    !
3605    ! Water-hydrology - sechiba
3606    !
3607
3608    !Config Key   = WMAX_VEG
3609    !Config Desc  = Maximum field capacity for each of the vegetations (Temporary): max quantity of water
3610    !Config if    = OK_SECHIBA
3611    !Config Def   = 150., 150., 150., 150., 150., 150., 150.,150., 150., 150., 150., 150., 150.
3612    !Config Help  =
3613    !Config Units = [kg/m^3]
3614    CALL getin_p('WMAX_VEG',wmax_veg)
3615
3616    !Config Key   = PERCENT_THROUGHFALL_PFT
3617    !Config Desc  = Percent by PFT of precip that is not intercepted by the canopy. Default value depend on run mode.
3618    !Config if    = OK_SECHIBA
3619    !Config Def   = Case offline+CWRR [0. 0. 0....] else [30. 30. 30.....]
3620    !Config Help  = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
3621    !Config         will get directly to the ground without being intercepted, for each PFT.
3622    !Config Units = [%]
3623    CALL getin_p('PERCENT_THROUGHFALL_PFT',throughfall_by_pft)
3624    throughfall_by_pft(:) = throughfall_by_pft(:) / 100. 
3625
3626
3627    !
3628    ! Albedo - sechiba
3629    !
3630
3631    !Config Key   = SNOWA_AGED_VIS
3632    !Config Desc  = Minimum snow albedo value for each vegetation type after aging (dirty old snow), visible albedo
3633    !Config if    = OK_SECHIBA
3634    !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
3635    !Config Help  = Values are from the Thesis of S. Chalita (1992), optimized on 04/07/2016
3636    !Config Units = [-]
3637    CALL getin_p('SNOWA_AGED_VIS',snowa_aged_vis)
3638
3639    !Config Key   = SNOWA_AGED_NIR
3640    !Config Desc  = Minimum snow albedo value for each vegetation type after aging (dirty old snow), near infrared albedo
3641    !Config if    = OK_SECHIBA
3642    !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
3643    !Config Help  = Values are from the Thesis of S. Chalita (1992)
3644    !Config Units = [-]
3645    CALL getin_p('SNOWA_AGED_NIR',snowa_aged_nir)
3646
3647    !Config Key   = SNOWA_DEC_VIS
3648    !Config Desc  = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow, visible albedo
3649    !Config if    = OK_SECHIBA
3650    !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
3651    !Config Help  = Values are from the Thesis of S. Chalita (1992), optimized on 04/07/2016
3652    !Config Units = [-]
3653    CALL getin_p('SNOWA_DEC_VIS',snowa_dec_vis)
3654
3655    !Config Key   = SNOWA_DEC_NIR
3656    !Config Desc  = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow, near infrared albedo
3657    !Config if    = OK_SECHIBA
3658    !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
3659    !Config Help  = Values are from the Thesis of S. Chalita (1992)
3660    !Config Units = [-]
3661    CALL getin_p('SNOWA_DEC_NIR',snowa_dec_nir)
3662
3663    !Config Key   = ALB_LEAF_VIS
3664    !Config Desc  = leaf albedo of vegetation type, visible albedo
3665    !Config if    = OK_SECHIBA
3666    !Config Def   = .0, .0397, .0474, .0386, .0484, .0411, .041, .0541, .0435, .0524, .0508, .0509, .0606
3667    !Config Help  = optimized on 04/07/2016
3668    !Config Units = [-]
3669    CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis)
3670
3671    !Config Key   = ALB_LEAF_NIR
3672    !Config Desc  = leaf albedo of vegetation type, near infrared albedo
3673    !Config if    = OK_SECHIBA
3674    !Config Def   = .0, .227, .214, .193, .208, .244, .177, .218, .213, .252, .265, .272, .244
3675    !Config Help  = optimized on 04/07/2016
3676    !Config Units = [-]
3677    CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir)
3678
3679    IF ( ok_bvoc ) THEN
3680       !
3681       ! BVOC
3682       !
3683
3684       !Config Key   = ISO_ACTIVITY
3685       !Config Desc  = Biogenic activity for each age class : isoprene
3686       !Config if    = CHEMISTRY_BVOC
3687       !Config Def   = 0.5, 1.5, 1.5, 0.5
3688       !Config Help  =
3689       !Config Units = [-]
3690       CALL getin_p('ISO_ACTIVITY',iso_activity)
3691
3692       !Config Key   = METHANOL_ACTIVITY
3693       !Config Desc  = Isoprene emission factor for each age class : methanol
3694       !Config if    = CHEMISTRY_BVOC
3695       !Config Def   = 1., 1., 0.5, 0.5
3696       !Config Help  =
3697       !Config Units = [-]
3698       CALL getin_p('METHANOL_ACTIVITY',methanol_activity)
3699
3700       !Config Key   = EM_FACTOR_ISOPRENE
3701       !Config Desc  = Isoprene emission factor
3702       !Config if    = CHEMISTRY_BVOC
3703       !Config Def   = 0., 24., 24., 8., 16., 45., 8., 18., 0.5, 12., 18., 5., 5.
3704       !Config Help  =
3705       !Config Units = [ugC/g/h]
3706       CALL getin_p('EM_FACTOR_ISOPRENE',em_factor_isoprene)
3707
3708       !Config Key   = EM_FACTOR_MONOTERPENE
3709       !Config Desc  = Monoterpene emission factor
3710       !Config if    = CHEMISTRY_BVOC
3711       !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
3712       !Config Help  =
3713       !Config Units = [ugC/g/h]
3714       CALL getin_p('EM_FACTOR_MONOTERPENE',em_factor_monoterpene)
3715
3716       !Config Key   = C_LDF_MONO
3717       !Config Desc  = Monoterpenes fraction dependancy to light
3718       !Config if    = CHEMISTRY_BVOC
3719       !Config Def   = 0.6
3720       !Config Help  =
3721       !Config Units = []
3722       CALL getin_p('C_LDF_MONO',LDF_mono)
3723
3724       !Config Key   = C_LDF_SESQ
3725       !Config Desc  = Sesquiterpenes fraction dependancy to light
3726       !Config if    = CHEMISTRY_BVOC
3727       !Config Def   = 0.5
3728       !Config Help  =
3729       !Config Units = []
3730       CALL getin_p('C_LDF_SESQ',LDF_sesq)
3731
3732       !Config Key   = C_LDF_METH
3733       !Config Desc  = Methanol fraction dependancy to light
3734       !Config if    = CHEMISTRY_BVOC
3735       !Config Def   = 0.8
3736       !Config Help  =
3737       !Config Units = []
3738       CALL getin_p('C_LDF_METH',LDF_meth)
3739
3740       !Config Key   = C_LDF_ACET
3741       !Config Desc  = Acetone fraction dependancy to light
3742       !Config if    = CHEMISTRY_BVOC
3743       !Config Def   = 0.2
3744       !Config Help  =
3745       !Config Units = []
3746       CALL getin_p('C_LDF_ACET',LDF_acet)
3747
3748       !Config Key   = EM_FACTOR_APINENE
3749       !Config Desc  = Alfa pinene  emission factor
3750       !Config if    = CHEMISTRY_BVOC
3751       !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
3752       !Config Help  =
3753       !Config Units = [ugC/g/h]
3754       CALL getin_p('EM_FACTOR_APINENE',em_factor_apinene)
3755
3756       !Config Key   = EM_FACTOR_BPINENE
3757       !Config Desc  = Beta pinene  emission factor
3758       !Config if    = CHEMISTRY_BVOC
3759       !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
3760       !Config Help  =
3761       !Config Units = [ugC/g/h]
3762       CALL getin_p('EM_FACTOR_BPINENE',em_factor_bpinene)
3763
3764       !Config Key   = EM_FACTOR_LIMONENE
3765       !Config Desc  = Limonene  emission factor
3766       !Config if    = CHEMISTRY_BVOC
3767       !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
3768       !Config Help  =
3769       !Config Units = [ugC/g/h]
3770       CALL getin_p('EM_FACTOR_LIMONENE',em_factor_limonene)
3771
3772       !Config Key   = EM_FACTOR_MYRCENE
3773       !Config Desc  = Myrcene  emission factor
3774       !Config if    = CHEMISTRY_BVOC
3775       !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
3776       !Config Help  =
3777       !Config Units = [ugC/g/h]
3778       CALL getin_p('EM_FACTOR_MYRCENE',em_factor_myrcene)
3779
3780       !Config Key   = EM_FACTOR_SABINENE
3781       !Config Desc  = Sabinene  emission factor
3782       !Config if    = CHEMISTRY_BVOC
3783       !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
3784       !Config Help  =
3785       !Config Units = [ugC/g/h]
3786       CALL getin_p('EM_FACTOR_SABINENE',em_factor_sabinene)
3787
3788       !Config Key   = EM_FACTOR_CAMPHENE
3789       !Config Desc  = Camphene  emission factor
3790       !Config if    = CHEMISTRY_BVOC
3791       !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
3792       !Config Help  =
3793       !Config Units = [ugC/g/h]
3794       CALL getin_p('EM_FACTOR_CAMPHENE',em_factor_camphene)
3795
3796       !Config Key   = EM_FACTOR_3CARENE
3797       !Config Desc  = 3-Carene  emission factor
3798       !Config if    = CHEMISTRY_BVOC
3799       !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
3800       !Config Help  =
3801       !Config Units = [ugC/g/h]
3802       CALL getin_p('EM_FACTOR_3CARENE',em_factor_3carene)
3803
3804       !Config Key   = EM_FACTOR_TBOCIMENE
3805       !Config Desc  = T-beta-ocimene  emission factor
3806       !Config if    = CHEMISTRY_BVOC
3807       !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
3808       !Config Help  =
3809       !Config Units = [ugC/g/h]
3810       CALL getin_p('EM_FACTOR_TBOCIMENE', em_factor_tbocimene)
3811
3812       !Config Key   = EM_FACTOR_OTHERMONOT
3813       !Config Desc  = Other monoterpenes  emission factor
3814       !Config if    = CHEMISTRY_BVOC
3815       !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
3816       !Config Help  =
3817       !Config Units = [ugC/g/h]
3818       CALL getin_p('EM_FACTOR_OTHERMONOT',em_factor_othermonot)
3819
3820       !Config Key   = EM_FACTOR_SESQUITERP
3821       !Config Desc  = Sesquiterpenes  emission factor
3822       !Config if    = CHEMISTRY_BVOC
3823       !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
3824       !Config Help  =
3825       !Config Units = [ugC/g/h]
3826       CALL getin_p('EM_FACTOR_SESQUITERP',em_factor_sesquiterp)
3827
3828
3829
3830       !Config Key   = C_BETA_MONO
3831       !Config Desc  = Monoterpenes temperature dependency coefficient
3832       !Config if    = CHEMISTRY_BVOC
3833       !Config Def   = 0.1
3834       !Config Help  =
3835       !Config Units = []
3836       CALL getin_p('C_BETA_MONO',beta_mono)
3837
3838       !Config Key   = C_BETA_SESQ
3839       !Config Desc  = Sesquiterpenes temperature dependency coefficient
3840       !Config if    = CHEMISTRY_BVOC
3841       !Config Def   = 0.17
3842       !Config Help  =
3843       !Config Units = []
3844       CALL getin_p('C_BETA_SESQ',beta_sesq)
3845
3846       !Config Key   = C_BETA_METH
3847       !Config Desc  = Methanol temperature dependency coefficient
3848       !Config if    = CHEMISTRY_BVOC
3849       !Config Def   = 0.08
3850       !Config Help  =
3851       !Config Units = []
3852       CALL getin_p('C_BETA_METH',beta_meth)
3853
3854       !Config Key   = C_BETA_ACET
3855       !Config Desc  = Acetone temperature dependency coefficient
3856       !Config if    = CHEMISTRY_BVOC
3857       !Config Def   = 0.1
3858       !Config Help  =
3859       !Config Units = []
3860       CALL getin_p('C_BETA_ACET',beta_acet)
3861
3862       !Config Key   = C_BETA_OXYVOC
3863       !Config Desc  = Other oxygenated BVOC temperature dependency coefficient
3864       !Config if    = CHEMISTRY_BVOC
3865       !Config Def   = 0.13
3866       !Config Help  =
3867       !Config Units = []
3868       CALL getin_p('C_BETA_OXYVOC',beta_oxyVOC)
3869
3870       !Config Key   = EM_FACTOR_ORVOC
3871       !Config Desc  = ORVOC emissions factor
3872       !Config if    = CHEMISTRY_BVOC
3873       !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
3874       !Config Help  =
3875       !Config Units = [ugC/g/h] 
3876       CALL getin_p('EM_FACTOR_ORVOC',em_factor_ORVOC)
3877
3878       !Config Key   = EM_FACTOR_OVOC
3879       !Config Desc  = OVOC emissions factor
3880       !Config if    = CHEMISTRY_BVOC
3881       !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
3882       !Config Help  =
3883       !Config Units = [ugC/g/h]       
3884       CALL getin_p('EM_FACTOR_OVOC',em_factor_OVOC)
3885
3886       !Config Key   = EM_FACTOR_MBO
3887       !Config Desc  = MBO emissions factor
3888       !Config if    = CHEMISTRY_BVOC
3889       !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
3890       !Config Help  =
3891       !Config Units = [ugC/g/h] 
3892       CALL getin_p('EM_FACTOR_MBO',em_factor_MBO)
3893
3894       !Config Key   = EM_FACTOR_METHANOL
3895       !Config Desc  = Methanol emissions factor
3896       !Config if    = CHEMISTRY_BVOC
3897       !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.
3898       !Config Help  =
3899       !Config Units = [ugC/g/h] 
3900       CALL getin_p('EM_FACTOR_METHANOL',em_factor_methanol)
3901
3902       !Config Key   = EM_FACTOR_ACETONE
3903       !Config Desc  = Acetone emissions factor
3904       !Config if    = CHEMISTRY_BVOC
3905       !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
3906       !Config Help  =
3907       !Config Units = [ugC/g/h]     
3908       CALL getin_p('EM_FACTOR_ACETONE',em_factor_acetone)
3909
3910       !Config Key   = EM_FACTOR_ACETAL
3911       !Config Desc  = Acetaldehyde emissions factor
3912       !Config if    = CHEMISTRY_BVOC
3913       !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
3914       !Config Help  =
3915       !Config Units = [ugC/g/h] 
3916       CALL getin_p('EM_FACTOR_ACETAL',em_factor_acetal)
3917
3918       !Config Key   = EM_FACTOR_FORMAL
3919       !Config Desc  = Formaldehyde emissions factor
3920       !Config if    = CHEMISTRY_BVOC
3921       !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
3922       !Config Help  =
3923       !Config Units = [ugC/g/h] 
3924       CALL getin_p('EM_FACTOR_FORMAL',em_factor_formal)
3925
3926       !Config Key   = EM_FACTOR_ACETIC
3927       !Config Desc  = Acetic Acid emissions factor
3928       !Config if    = CHEMISTRY_BVOC
3929       !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
3930       !Config Help  =
3931       !Config Units = [ugC/g/h] 
3932       CALL getin_p('EM_FACTOR_ACETIC',em_factor_acetic)
3933
3934       !Config Key   = EM_FACTOR_FORMIC
3935       !Config Desc  = Formic Acid emissions factor
3936       !Config if    = CHEMISTRY_BVOC
3937       !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
3938       !Config Help  =
3939       !Config Units = [ugC/g/h] 
3940       CALL getin_p('EM_FACTOR_FORMIC',em_factor_formic)
3941
3942       !Config Key   = EM_FACTOR_NO_WET
3943       !Config Desc  = NOx emissions factor wet soil emissions and exponential dependancy factor
3944       !Config if    = CHEMISTRY_BVOC
3945       !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
3946       !Config Help  =
3947       !Config Units = [ngN/m^2/s]
3948       CALL getin_p('EM_FACTOR_NO_WET',em_factor_no_wet)
3949
3950       !Config Key   = EM_FACTOR_NO_DRY
3951       !Config Desc  = NOx emissions factor dry soil emissions and exponential dependancy factor
3952       !Config if    = CHEMISTRY_BVOC
3953       !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
3954       !Config Help  =
3955       !Config Units = [ngN/m^2/s]
3956       CALL getin_p('EM_FACTOR_NO_DRY',em_factor_no_dry)
3957
3958       !Config Key   = LARCH
3959       !Config Desc  = Larcher 1991 SAI/LAI ratio
3960       !Config if    = CHEMISTRY_BVOC
3961       !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
3962       !Config Help  =
3963       !Config Units = [-] 
3964       CALL getin_p('LARCH',Larch)
3965
3966    ENDIF ! (ok_bvoc)
3967
3968  END SUBROUTINE config_sechiba_pft_parameters
3969
3970
3971!! ================================================================================================================================
3972!! SUBROUTINE   : config_stomate_pft_parameters
3973!!
3974!>\BRIEF         This subroutine will read the imposed values for the stomate pft
3975!! parameters. It is not called if IMPOSE_PARAM is set to NO.
3976!!
3977!! DESCRIPTION  : None
3978!!
3979!! RECENT CHANGE(S): None
3980!!
3981!! MAIN OUTPUT VARIABLE(S): None
3982!!
3983!! REFERENCE(S) : None
3984!!
3985!! FLOWCHART    : None
3986!! \n
3987!_ ================================================================================================================================
3988
3989  SUBROUTINE config_stomate_pft_parameters
3990
3991    IMPLICIT NONE
3992
3993    !! 0. Variables and parameters declaration
3994
3995    !! 0.4 Local variable
3996   INTEGER(i_std)               :: ivma,ivm,j,k!! index
3997
3998    !_ ================================================================================================================================
3999
4000    !
4001    ! Vegetation structure
4002    !
4003
4004    !Config Key   = SLA
4005    !Config Desc  = specif leaf area
4006    !Config if    = OK_STOMATE
4007    !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
4008    !Config Help  =
4009    !Config Units = [m^2/gC]
4010    CALL getin_p('SLA',sla)
4011
4012    !Config Key   = AVAILABILITY_FACT
4013    !Config Desc  = Calculate dynamic mortality in lpj_gap, pft dependent parameter
4014    !Config If    = OK_STOMATE
4015    !Config Def   = undef, 0.14, 0.14, 0.10, 0.10, 0.10, 0.05, 0.05, 0.05, undef, undef, undef, undef
4016    !Config Help  =
4017    !Config Units = [-]   
4018    CALL getin_p('AVAILABILITY_FACT',availability_fact)
4019
4020    !
4021    ! Allocation - stomate
4022    !
4023    !
4024    !Config Key   = R0
4025    !Config Desc  = Standard root allocation
4026    !Config If    = OK_STOMATE
4027    !Config Def   = undef, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30
4028    !Config Help  =
4029    !Config Units = [-]   
4030    CALL getin_p('R0',R0)
4031
4032    !Config Key   = S0
4033    !Config Desc  = Standard sapwood allocation
4034    !Config If    = OK_STOMATE
4035    !Config Def   = undef, .25, .25, .30, .30, .30, .30, .30, .30, .30, .30, .30, .30
4036    !Config Help  =
4037    !Config Units = [-]   
4038    CALL getin_p('S0',S0)
4039
4040    !
4041    ! Respiration - stomate
4042    !
4043
4044    !Config Key   = FRAC_GROWTHRESP
4045    !Config Desc  = fraction of GPP which is lost as growth respiration
4046    !Config if    = OK_STOMATE
4047    !Config Def   = undef, .28, .28, .28, .28, .28, .28, .28, .28, .28, .28, .28, .28
4048    !Config Help  =
4049    !Config Units = [-]
4050    CALL getin_p('FRAC_GROWTHRESP',frac_growthresp) 
4051
4052    !Config Key   = MAINT_RESP_SLOPE_C
4053    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant c of aT^2+bT+c , tabulated
4054    !Config if    = OK_STOMATE
4055    !Config Def   = undef, .20, .20, .16, .16, .16, .16, .16, .16, .16, .12, .16, .12
4056    !Config Help  =
4057    !Config Units = [-]
4058    CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) 
4059
4060    !Config Key   = MAINT_RESP_SLOPE_B
4061    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant b of aT^2+bT+c , tabulated
4062    !Config if    = OK_STOMATE
4063    !Config Def   = undef, .0, .0, .0, .0, .0, .0, .0, .0, -.00133, .0, -.00133, .0
4064    !Config Help  =
4065    !Config Units = [-]
4066    CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b)
4067
4068    !Config Key   = MAINT_RESP_SLOPE_A
4069    !Config Desc  = slope of maintenance respiration coefficient (1/K), constant a of aT^2+bT+c , tabulated
4070    !Config if    = OK_STOMATE
4071    !Config Def   = undef, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0, .0   
4072    !Config Help  =
4073    !Config Units = [-]
4074    CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a)
4075
4076    !Config Key   = CM_ZERO_LEAF
4077    !Config Desc  = maintenance respiration coefficient at 0 deg C, for leaves, tabulated
4078    !Config if    = OK_STOMATE
4079    !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
4080    !Config Help  =
4081    !Config Units = [g/g/day]
4082    CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf)
4083
4084    !Config Key   = CM_ZERO_SAPABOVE
4085    !Config Desc  = maintenance respiration coefficient at 0 deg C,for sapwood above, tabulated
4086    !Config if    = OK_STOMATE
4087    !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
4088    !Config Help  =
4089    !Config Units = [g/g/day]
4090    CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove)
4091
4092    !Config Key   = CM_ZERO_SAPBELOW
4093    !Config Desc  = maintenance respiration coefficient at 0 deg C, for sapwood below, tabulated
4094    !Config if    = OK_STOMATE
4095    !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
4096    !Config Help  =
4097    !Config Units = [g/g/day]
4098    CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow)
4099
4100    !Config Key   = CM_ZERO_HEARTABOVE
4101    !Config Desc  = maintenance respiration coefficient at 0 deg C, for heartwood above, tabulated
4102    !Config if    = OK_STOMATE
4103    !Config Def   = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
4104    !Config Help  =
4105    !Config Units = [g/g/day]
4106    CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove)
4107
4108    !Config Key   = CM_ZERO_HEARTBELOW
4109    !Config Desc  = maintenance respiration coefficient at 0 deg C,for heartwood below, tabulated
4110    !Config if    = OK_STOMATE
4111    !Config Def   = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
4112    !Config Help  =
4113    !Config Units = [g/g/day]
4114    CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow)
4115
4116    !Config Key   = CM_ZERO_ROOT
4117    !Config Desc  = maintenance respiration coefficient at 0 deg C, for roots, tabulated
4118    !Config if    = OK_STOMATE
4119    !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
4120    !Config Help  =
4121    !Config Units = [g/g/day]
4122    CALL getin_p('CM_ZERO_ROOT',cm_zero_root)
4123
4124    !Config Key   = CM_ZERO_FRUIT
4125    !Config Desc  = maintenance respiration coefficient at 0 deg C, for fruits, tabulated
4126    !Config if    = OK_STOMATE
4127    !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   
4128    !Config Help  =
4129    !Config Units = [g/g/day]
4130    CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit)
4131
4132    !Config Key   = CM_ZERO_CARBRES
4133    !Config Desc  = maintenance respiration coefficient at 0 deg C, for carbohydrate reserve, tabulated
4134    !Config if    = OK_STOMATE
4135    !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
4136    !Config Help  =
4137    !Config Units = [g/g/day]
4138    CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres)
4139
4140    !
4141    ! Fire - stomate
4142    !
4143
4144    !Config Key   = FLAM
4145    !Config Desc  = flamability: critical fraction of water holding capacity
4146    !Config if    = OK_STOMATE
4147    !Config Def   = undef, .15, .25, .25, .25, .25, .25, .25, .25, .25, .25, .35, .35
4148    !Config Help  =
4149    !Config Units = [-]
4150    CALL getin_p('FLAM',flam)
4151
4152    !Config Key   = RESIST
4153    !Config Desc  = fire resistance
4154    !Config if    = OK_STOMATE
4155    !Config Def   = undef, .95, .90, .12, .50, .12, .12, .12, .12, .0, .0, .0, .0
4156    !Config Help  =
4157    !Config Units = [-]
4158    CALL getin_p('RESIST',resist)
4159
4160    !
4161    ! Flux - LUC
4162    !
4163
4164    !Config Key   = COEFF_LCCHANGE_1
4165    !Config Desc  = Coeff of biomass export for the year
4166    !Config if    = OK_STOMATE
4167    !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
4168    !Config Help  =
4169    !Config Units = [-]
4170    CALL getin_p('COEFF_LCCHANGE_1',coeff_lcchange_1)
4171
4172    !Config Key   = COEFF_LCCHANGE_10
4173    !Config Desc  = Coeff of biomass export for the decade
4174    !Config if    = OK_STOMATE
4175    !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
4176    !Config Help  =
4177    !Config Units = [-]
4178    CALL getin_p('COEFF_LCCHANGE_10',coeff_lcchange_10)
4179
4180    !Config Key   = COEFF_LCCHANGE_100
4181    !Config Desc  = Coeff of biomass export for the century
4182    !Config if    = OK_STOMATE
4183    !Config Def   = undef, 0., 0., 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0.104, 0., 0.104, 0.
4184    !Config Help  =
4185    !Config Units = [-]
4186    CALL getin_p('COEFF_LCCHANGE_100',coeff_lcchange_100)
4187!gmjc
4188    !Config  Key  =
4189     !Config  Desc = minimum gdd to allow senescence of crops
4190     !Config  if  = OK_STOMATE
4191     !Config  Def  =  ! maximum specific leaf area (m**2/gC)
4192     !Config  Help =
4193     !Config  Units = Celsius degrees [C]
4194     CALL getin_p('SLA_MAX',sla_max)
4195     !
4196     !Config  Key  = SLA_MIN
4197     !Config  Desc = minimum specific leaf area (m**2/gC)
4198     !Config  if  = OK_STOMATE
4199     !Config  Def  =
4200     !Config  Help =
4201     !Config  Units = Celsius degrees [C]
4202     CALL getin_p('SLA_MIN',sla_min)
4203!end gmjc
4204    !
4205    ! Phenology
4206    !
4207
4208    !Config Key   = LAI_MAX_TO_HAPPY
4209    !Config Desc  = threshold of LAI below which plant uses carbohydrate reserves
4210    !Config if    = OK_STOMATE
4211    !Config Def   = undef, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
4212    !Config Help  =
4213    !Config Units = [-]
4214    CALL getin_p('LAI_MAX_TO_HAPPY',lai_max_to_happy) 
4215
4216    !Config Key   = LAI_MAX
4217    !Config Desc  = maximum LAI, PFT-specific
4218    !Config if    = OK_STOMATE
4219    !Config Def   = undef, 7., 7., 5., 5., 5., 4.5, 4.5, 3.0, 2.5, 2.5, 5.,5.
4220    !Config Help  =
4221    !Config Units = [m^2/m^2]
4222    CALL getin_p('LAI_MAX',lai_max)
4223
4224    !Config Key   = PHENO_TYPE
4225    !Config Desc  = type of phenology, 0=bare ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
4226    !Config if    = OK_STOMATE
4227    !Config Def   = 0, 1, 3, 1, 1, 2, 1, 2, 2, 4, 4, 2, 3
4228    !Config Help  =
4229    !Config Units = [-]
4230    CALL getin_p('PHENO_TYPE',pheno_type)
4231
4232    !
4233    ! Phenology : Leaf Onset
4234    !
4235
4236    !Config Key   = PHENO_GDD_CRIT_C
4237    !Config Desc  = critical gdd, tabulated (C), constant c of aT^2+bT+c
4238    !Config if    = OK_STOMATE
4239    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 270., 400., 125., 400.
4240    !Config Help  =
4241    !Config Units = [-]
4242    CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c)
4243
4244    !Config Key   = PHENO_GDD_CRIT_B
4245    !Config Desc  = critical gdd, tabulated (C), constant b of aT^2+bT+c
4246    !Config if    = OK_STOMATE
4247    !Config Def   = undef, undef, undef, undef, undef, undef, undef,undef, undef, 6.25, 0., 0., 0.
4248    !Config Help  =
4249    !Config Units = [-]
4250    CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b)
4251
4252    !Config Key   = PHENO_GDD_CRIT_A
4253    !Config Desc  = critical gdd, tabulated (C), constant a of aT^2+bT+c
4254    !Config if    = OK_STOMATE
4255    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.03125,  0., 0., 0.
4256    !Config Help  =
4257    !Config Units = [-]
4258    CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a)
4259
4260    !Config Key   = PHENO_MOIGDD_T_CRIT
4261    !Config Desc  = Average temperature threashold for C4 grass used in pheno_moigdd
4262    !Config if    = OK_STOMATE
4263    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 22.0, undef, undef
4264    !Config Help  =
4265    !Config Units = [C]
4266    CALL getin_p('PHENO_MOIGDD_T_CRIT',pheno_moigdd_t_crit)
4267
4268    !Config Key   = NGD_CRIT
4269    !Config Desc  = critical ngd, tabulated. Threshold -5 degrees
4270    !Config if    = OK_STOMATE
4271    !Config Def   = undef, undef, undef, undef, undef, undef, undef, 0., undef, undef, undef, undef, undef
4272    !Config Help  = NGD : Number of Growing Days.
4273    !Config Units = [days]
4274    CALL getin_p('NGD_CRIT',ngd_crit)
4275
4276    !Config Key   = NCDGDD_TEMP
4277    !Config Desc  = critical temperature for the ncd vs. gdd function in phenology
4278    !Config if    = OK_STOMATE
4279    !Config Def   = undef, undef, undef, undef, undef, 5., undef, 0., undef, undef, undef, undef, undef
4280    !Config Help  =
4281    !Config Units = [C]
4282    CALL getin_p('NCDGDD_TEMP',ncdgdd_temp)
4283
4284    !Config Key   = HUM_FRAC
4285    !Config Desc  = critical humidity (relative to min/max) for phenology
4286    !Config if    = OK_STOMATE
4287    !Config Def   = undef, undef, .5, undef, undef, undef, undef, undef,  undef, .5, .5, .5,.5     
4288    !Config Help  =
4289    !Config Units = [%]
4290    CALL getin_p('HUM_FRAC',hum_frac)
4291
4292    !Config Key   = HUM_MIN_TIME
4293    !Config Desc  = minimum time elapsed since moisture minimum
4294    !Config if    = OK_STOMATE
4295    !Config Def   = undef, undef, 50., undef, undef, undef, undef, undef, undef, 36., 35., 75., 75.
4296    !Config Help  =
4297    !Config Units = [days]
4298    CALL getin_p('HUM_MIN_TIME',hum_min_time)
4299
4300    !Config Key   = TAU_SAP
4301    !Config Desc  = sapwood -> heartwood conversion time
4302    !Config if    = OK_STOMATE
4303    !Config Def   = undef, 730., 730., 730., 730., 730., 730., 730., 730., undef, undef, undef, undef
4304    !Config Help  =
4305    !Config Units = [days]
4306    CALL getin_p('TAU_SAP',tau_sap)
4307
4308    !Config Key   = TAU_LEAFINIT
4309    !Config Desc  = time to attain the initial foliage using the carbohydrate reserve
4310    !Config if    = OK_STOMATE
4311    !Config Def   = undef, 10., 10., 10., 10., 10., 10., 10., 10., 10., 10., 10., 10.
4312    !Config Help  =
4313    !Config Units = [days]
4314    CALL getin_p('TAU_LEAFINIT',tau_leafinit) 
4315
4316    !Config Key   = TAU_FRUIT
4317    !Config Desc  = fruit lifetime
4318    !Config if    = OK_STOMATE
4319    !Config Def   = undef, 90., 90., 90., 90., 90., 90., 90., 90., undef, undef, undef, undef
4320    !Config Help  =
4321    !Config Units = [days]
4322    CALL getin_p('TAU_FRUIT',tau_fruit)
4323
4324    !Config Key   = ECUREUIL
4325    !Config Desc  = fraction of primary leaf and root allocation put into reserve
4326    !Config if    = OK_STOMATE
4327    !Config Def   = undef, .0, 1., .0, .0, 1., .0, 1., 1., 1., 1., 1., 1.
4328    !Config Help  =
4329    !Config Units = [-]
4330    CALL getin_p('ECUREUIL',ecureuil)
4331
4332    !Config Key   = ALLOC_MIN
4333    !Config Desc  = minimum allocation above/below = f(age) - 30/01/04 NV/JO/PF
4334    !Config if    = OK_STOMATE
4335    !Config Def   = undef, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef
4336    !Config Help  =
4337    !Config Units = [-]
4338    CALL getin_p('ALLOC_MIN',alloc_min)
4339
4340    !Config Key   = ALLOC_MAX
4341    !Config Desc  = maximum allocation above/below = f(age) - 30/01/04 NV/JO/PF
4342    !Config if    = OK_STOMATE
4343    !Config Def   = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef
4344    !Config Help  =
4345    !Config Units = [-]
4346    CALL getin_p('ALLOC_MAX',alloc_max)
4347
4348    !Config Key   = DEMI_ALLOC
4349    !Config Desc  = mean allocation above/below = f(age) - 30/01/04 NV/JO/PF
4350    !Config if    = OK_STOMATE
4351    !Config Def   = undef, 5., 5., 5., 5., 5., 5., 5., 5., undef, undef, undef, undef
4352    !Config Help  =
4353    !Config Units = [-]
4354    CALL getin_p('DEMI_ALLOC',demi_alloc)
4355
4356    !Config Key   = LEAFLIFE_TAB
4357    !Config Desc  = leaf longevity
4358    !Config if    = OK_STOMATE
4359    !Config Def   = undef, .5, 2., .33, 1., 2., .33, 2., 2., 2., 2., 2., 2.
4360    !Config Help  =
4361    !Config Units = [years]
4362    CALL getin_p('LEAFLIFE_TAB',leaflife_tab)
4363
4364    !
4365    ! Phenology : Senescence
4366    !
4367    !
4368    !Config Key   = LEAFFALL
4369    !Config Desc  = length of death of leaves, tabulated
4370    !Config if    = OK_STOMATE
4371    !Config Def   = undef, undef, 10., undef, undef, 30., undef, 5., 10., 10., 10., 10., 10.
4372    !Config Help  =
4373    !Config Units = [days]
4374    CALL getin_p('LEAFFALL',leaffall)
4375
4376    !Config Key   = LEAFAGECRIT
4377    !Config Desc  = critical leaf age, tabulated
4378    !Config if    = OK_STOMATE
4379    !Config Def   = undef, 730., 180., 910., 730., 160., 910., 220., 120., 80., 120., 90., 90. 
4380    !Config Help  =
4381    !Config Units = [days]
4382    CALL getin_p('LEAFAGECRIT',leafagecrit) 
4383
4384    !Config Key   = SENESCENCE_TYPE
4385    !Config Desc  = type of senescence, tabulated
4386    !Config if    = OK_STOMATE
4387    !Config Def   = none, none, dry, none, none, cold, none, cold, cold, mixed, mixed, mixed, mixed
4388    !Config Help  =
4389    !Config Units = [-]
4390    CALL getin_p('SENESCENCE_TYPE',senescence_type) 
4391
4392    !Config Key   = SENESCENCE_HUM
4393    !Config Desc  = critical relative moisture availability for senescence
4394    !Config if    = OK_STOMATE
4395    !Config Def   = undef, undef, .3, undef, undef, undef, undef, undef, undef, .2, .2, .3, .2
4396    !Config Help  =
4397    !Config Units = [-]
4398    CALL getin_p('SENESCENCE_HUM',senescence_hum)
4399
4400    !Config Key   = NOSENESCENCE_HUM
4401    !Config Desc  = relative moisture availability above which there is no humidity-related senescence
4402    !Config if    = OK_STOMATE
4403    !Config Def   = undef, undef, .8, undef, undef, undef, undef, undef, undef, 0.6, .3, .3, .3
4404    !Config Help  =
4405    !Config Units = [-]
4406    CALL getin_p('NOSENESCENCE_HUM',nosenescence_hum) 
4407
4408    !Config Key   = MAX_TURNOVER_TIME
4409    !Config Desc  = maximum turnover time for grasse
4410    !Config if    = OK_STOMATE
4411    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef,  80.,  80., 80., 80.
4412    !Config Help  =
4413    !Config Units = [days]
4414    CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time)
4415
4416    !Config Key   = MIN_TURNOVER_TIME
4417    !Config Desc  = minimum turnover time for grasse
4418    !Config if    = OK_STOMATE
4419    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, 10., 10., 10., 10.
4420    !Config Help  =
4421    !Config Units = [days]
4422    CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time)
4423
4424    !Config Key   = MIN_LEAF_AGE_FOR_SENESCENCE
4425    !Config Desc  = minimum leaf age to allow senescence g
4426    !Config if    = OK_STOMATE
4427    !Config Def   = undef, undef, 90., undef, undef, 90., undef, 60., 60., 30., 30., 30., 30.
4428    !Config Help  =
4429    !Config Units = [days]
4430    CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE',min_leaf_age_for_senescence)
4431
4432    !Config Key   = SENESCENCE_TEMP_C
4433    !Config Desc  = critical temperature for senescence (C), constant c of aT^2+bT+c, tabulated
4434    !Config if    = OK_STOMATE
4435    !Config Def   = undef, undef, undef, undef, undef, 16., undef, 14., 10, 5, 5., 5., 10.
4436    !Config Help  =
4437    !Config Units = [-]
4438    CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c)
4439
4440    !Config Key   = SENESCENCE_TEMP_B
4441    !Config Desc  = critical temperature for senescence (C), constant b of aT^2+bT+c ,tabulated
4442    !Config if    = OK_STOMATE
4443    !Config Def   = undef, undef, undef, undef, undef, 0., undef, 0., 0., .1, 0., 0., 0.
4444    !Config Help  =
4445    !Config Units = [-]
4446    CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b)
4447
4448    !Config Key   = SENESCENCE_TEMP_A
4449    !Config Desc  = critical temperature for senescence (C), constant a of aT^2+bT+c , tabulated
4450    !Config if    = OK_STOMATE
4451    !Config Def   = undef, undef, undef, undef, undef, 0., undef, 0., 0.,.00375, 0., 0., 0.
4452    !Config Help  =
4453    !Config Units = [-]
4454    CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a)
4455
4456    !Config Key   = GDD_SENESCENCE
4457    !Config Desc  = minimum gdd to allow senescence of crops 
4458    !Config if    = OK_STOMATE
4459    !Config Def   = undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, undef, 950., 4000.
4460    !Config Help  =
4461    !Config Units = [days]
4462    CALL getin_p("GDD_SENESCENCE", gdd_senescence)
4463
4464    !Config Key   = TCM_CRIT
4465    !Config Desc  = critical tcm, tabulated
4466    !Config if    = OK_STOMATE
4467    !Config Def   = undef, undef, undef, 5.0, 15.5, 15.5, -8.0, -8.0, -8.0, undef, undef, undef, undef
4468    !Config Help  =
4469    !Config Units = [C]
4470    CALL getin_p('TCM_CRIT',tcm_crit)
4471
4472    IF (use_age_class) THEN
4473      ! Age classes
4474      ! I want to create a temporary array that indicates which "real" PFT starts
4475      ! on which index.  This could probably be put somewhere else, but this
4476      ! routine is only called once a year and this loop is not expensive.
4477
4478      ! start_index and nagec_pft has length of nvm, only the beginning nvmap elements record
4479      ! the number of age groups for each PFT. The remaining elements will
4480      ! be -1 and when we use start_index and nagec_pft in the code, they're always looped
4481      ! over nvmap.
4482      start_index(:)=-1
4483      nagec_pft(:)=-1
4484      DO ivma=1,nvmap
4485        ! The start index is just the first place we find this real PFT.
4486        DO ivm=1,nvm
4487          IF(agec_group(ivm) .EQ. ivma)THEN
4488             start_index(ivma)=ivm
4489             j = 0
4490             DO WHILE(agec_group(ivm+j) .EQ. ivma)
4491               j = j+1
4492               ! we put this condition to handle the case that we have only one single
4493               ! age class for each PFT, but we still want to use the gross land cover
4494               ! change module.
4495               IF ((ivm+j .GT. nvmap .AND. nagec_tree .EQ. 1 .AND. nagec_herb .EQ. 1) .OR. ivm+j .GT. nvm) EXIT
4496             ENDDO
4497             nagec_pft(ivma)=j
4498             EXIT
4499          ENDIF
4500        ENDDO
4501      ENDDO
4502      ! Check to see if the calculation worked and we found indices for all of them.
4503      DO ivma=1,nvmap
4504        IF(start_index(ivma) .LT. 0)THEN
4505          WRITE(numout,*) 'Could not find a start index for one age class group!'
4506          WRITE(numout,*) 'Check the input file to make sure the following ivma appears in agec_group'
4507          WRITE(numout,*) 'ivma,nvmap',ivma,nvmap
4508          WRITE(numout,*) 'agec_group',agec_group(:)
4509          STOP
4510        ENDIF
4511      ENDDO
4512      ! Make sure input nagec_tree and nagec_herb is consistent
4513      DO ivma = 1,nvmap
4514        IF (nagec_pft(ivma) .GT.1) THEN
4515         IF (is_tree(start_index(ivma))) THEN
4516           IF (nagec_pft(ivma) .NE. nagec_tree) THEN
4517             WRITE(numout,*) 'The real number of age class for trees is not equal to nagec_tree'
4518             STOP
4519           ENDIF
4520         ELSE
4521           IF (nagec_pft(ivma) .NE. nagec_herb) THEN
4522             WRITE(numout,*) 'The real number of age class for grass/pasture is not equal to nagec_herb'
4523             STOP
4524           ENDIF
4525         ENDIF
4526        ENDIF
4527      ENDDO
4528    ENDIF
4529
4530!
4531!WETLAND CH4 methane
4532!
4533!pss+
4534  !Config Key   = sdepth_v
4535  !Config Desc  = soil depth for wetland vegetation types
4536  !Config if    = CH4_CALCUL
4537  !Config Def   = /0,129,129,129,129,129,129,129,129,79,79,162,162/
4538  !Config Help  =
4539  !Config Units = [cm]
4540  CALL getin_p('SDEPTH_V',sdepth_v)
4541
4542  !Config Key   = rdepth_v
4543  !Config Desc  = rooting depth for wetland vegetation types
4544  !Config if    = CH4_CALCUL
4545  !Config Def   = /0,64,64,64,64,64,64,64,64,39,39,81,81/
4546  !Config Help  =
4547  !Config Units = [cm]
4548  CALL getin_p('RDEPTH_V',rdepth_v)
4549
4550  !Config Key   = tveg_v
4551  !Config Desc  = Plant mediated transport efficiency
4552  !Config if    = CH4_CALCUL
4553  !Config Def   = /0,1,1,1,1,1,1,1,1,10,10,15,15/
4554  !Config Help  =
4555  !Config Units = [-]
4556  CALL getin_p('SDEPTH_V',tveg_v)
4557!pss-
4558 
4559 END SUBROUTINE config_stomate_pft_parameters
4560!
4561!=
4562!
4563
4564
4565!! ================================================================================================================================
4566!! SUBROUTINE   : pft_parameters_clear
4567!!
4568!>\BRIEF         This subroutine deallocates memory at the end of the simulation.
4569!!
4570!! DESCRIPTION  : None
4571!!
4572!! RECENT CHANGE(S): None
4573!!
4574!! MAIN OUTPUT VARIABLE(S): None
4575!!
4576!! REFERENCE(S) : None
4577!!
4578!! FLOWCHART    : None
4579!! \n
4580!_ ================================================================================================================================
4581
4582 SUBROUTINE pft_parameters_clear
4583   
4584   l_first_pft_parameters = .TRUE.
4585   
4586   IF (ALLOCATED(pft_to_mtc)) DEALLOCATE(pft_to_mtc)
4587   IF (ALLOCATED(PFT_name)) DEALLOCATE(PFT_name)
4588   IF (ALLOCATED(veget_ori_fixed_test_1)) DEALLOCATE(veget_ori_fixed_test_1)   
4589   IF (ALLOCATED(llaimax)) DEALLOCATE(llaimax)
4590   IF (ALLOCATED(llaimin)) DEALLOCATE(llaimin)
4591   IF (ALLOCATED(height_presc)) DEALLOCATE(height_presc)   
4592   IF (ALLOCATED(z0_over_height)) DEALLOCATE(z0_over_height)   
4593   IF (ALLOCATED(ratio_z0m_z0h)) DEALLOCATE(ratio_z0m_z0h)   
4594   IF (ALLOCATED(type_of_lai)) DEALLOCATE(type_of_lai)
4595   IF (ALLOCATED(is_tree)) DEALLOCATE(is_tree)
4596   IF (ALLOCATED(natural)) DEALLOCATE(natural)
4597! dgvmjc
4598    IF (ALLOCATED(pasture)) DEALLOCATE(pasture)
4599! end dgvmjc
4600   IF (ALLOCATED(is_deciduous)) DEALLOCATE(is_deciduous)
4601   IF (ALLOCATED(is_evergreen)) DEALLOCATE(is_evergreen)
4602   IF (ALLOCATED(is_needleleaf)) DEALLOCATE(is_needleleaf)
4603   IF (ALLOCATED(is_tropical)) DEALLOCATE(is_tropical)
4604   IF (ALLOCATED(humcste)) DEALLOCATE(humcste)
4605   IF (ALLOCATED(pref_soil_veg)) DEALLOCATE(pref_soil_veg)
4606   IF (ALLOCATED(agec_group)) DEALLOCATE(agec_group)
4607   IF (ALLOCATED(age_class_bound)) DEALLOCATE(age_class_bound)
4608   IF (ALLOCATED(start_index)) DEALLOCATE(start_index)
4609   IF (ALLOCATED(nagec_pft)) DEALLOCATE(nagec_pft)
4610   IF (ALLOCATED(is_c4)) DEALLOCATE(is_c4) 
4611   IF (ALLOCATED(vcmax_fix)) DEALLOCATE(vcmax_fix)
4612   IF (ALLOCATED(downregulation_co2_coeff)) DEALLOCATE(downregulation_co2_coeff) 
4613   IF (ALLOCATED(E_KmC)) DEALLOCATE(E_KmC)
4614   IF (ALLOCATED(E_KmO)) DEALLOCATE(E_KmO)
4615   IF (ALLOCATED(E_Sco)) DEALLOCATE(E_Sco)
4616   IF (ALLOCATED(E_gamma_star)) DEALLOCATE(E_gamma_star)
4617   IF (ALLOCATED(E_Vcmax)) DEALLOCATE(E_Vcmax)
4618   IF (ALLOCATED(E_Jmax)) DEALLOCATE(E_Jmax)
4619   IF (ALLOCATED(aSV)) DEALLOCATE(aSV)
4620   IF (ALLOCATED(bSV)) DEALLOCATE(bSV)
4621   IF (ALLOCATED(tphoto_min)) DEALLOCATE(tphoto_min)
4622   IF (ALLOCATED(tphoto_max)) DEALLOCATE(tphoto_max)
4623   IF (ALLOCATED(aSJ)) DEALLOCATE(aSJ)
4624   IF (ALLOCATED(bSJ)) DEALLOCATE(bSJ)
4625   IF (ALLOCATED(D_Vcmax)) DEALLOCATE(D_Vcmax)
4626   IF (ALLOCATED(D_Jmax)) DEALLOCATE(D_Jmax)
4627   IF (ALLOCATED(E_gm)) DEALLOCATE(E_gm) 
4628   IF (ALLOCATED(S_gm)) DEALLOCATE(S_gm) 
4629   IF (ALLOCATED(D_gm)) DEALLOCATE(D_gm)
4630   IF (ALLOCATED(E_Rd)) DEALLOCATE(E_Rd)
4631   IF (ALLOCATED(Vcmax25)) DEALLOCATE(Vcmax25)
4632   IF (ALLOCATED(arJV)) DEALLOCATE(arJV)
4633   IF (ALLOCATED(brJV)) DEALLOCATE(brJV)
4634   IF (ALLOCATED(KmC25)) DEALLOCATE(KmC25)
4635   IF (ALLOCATED(KmO25)) DEALLOCATE(KmO25)
4636   IF (ALLOCATED(Sco25)) DEALLOCATE(Sco25) 
4637   IF (ALLOCATED(gm25)) DEALLOCATE(gm25)
4638   IF (ALLOCATED(gamma_star25)) DEALLOCATE(gamma_star25)
4639   IF (ALLOCATED(a1)) DEALLOCATE(a1)
4640   IF (ALLOCATED(b1)) DEALLOCATE(b1)
4641   IF (ALLOCATED(g0)) DEALLOCATE(g0)
4642   IF (ALLOCATED(h_protons)) DEALLOCATE(h_protons)
4643   IF (ALLOCATED(fpsir)) DEALLOCATE(fpsir)
4644   IF (ALLOCATED(fQ)) DEALLOCATE(fQ)
4645   IF (ALLOCATED(fpseudo)) DEALLOCATE(fpseudo)
4646   IF (ALLOCATED(kp)) DEALLOCATE(kp)
4647   IF (ALLOCATED(alpha)) DEALLOCATE(alpha)
4648   IF (ALLOCATED(gbs)) DEALLOCATE(gbs)
4649   IF (ALLOCATED(theta)) DEALLOCATE(theta)
4650   IF (ALLOCATED(alpha_LL)) DEALLOCATE(alpha_LL)
4651   IF (ALLOCATED(stress_vcmax)) DEALLOCATE(stress_vcmax) 
4652   IF (ALLOCATED(stress_gs)) DEALLOCATE(stress_gs) 
4653   IF (ALLOCATED(stress_gm)) DEALLOCATE(stress_gm)
4654   IF (ALLOCATED(ext_coeff)) DEALLOCATE(ext_coeff)
4655   IF (ALLOCATED(ext_coeff_vegetfrac)) DEALLOCATE(ext_coeff_vegetfrac)
4656   IF (ALLOCATED(rveg_pft)) DEALLOCATE(rveg_pft)
4657   IF (ALLOCATED(rstruct_const)) DEALLOCATE(rstruct_const)
4658   IF (ALLOCATED(kzero)) DEALLOCATE(kzero)
4659   IF (ALLOCATED(wmax_veg)) DEALLOCATE(wmax_veg)
4660   IF (ALLOCATED(throughfall_by_pft)) DEALLOCATE(throughfall_by_pft)
4661   IF (ALLOCATED(snowa_aged_vis)) DEALLOCATE(snowa_aged_vis)
4662   IF (ALLOCATED(snowa_aged_nir)) DEALLOCATE(snowa_aged_nir)
4663   IF (ALLOCATED(snowa_dec_vis)) DEALLOCATE(snowa_dec_vis)
4664   IF (ALLOCATED(snowa_dec_nir)) DEALLOCATE(snowa_dec_nir)
4665   IF (ALLOCATED(alb_leaf_vis)) DEALLOCATE(alb_leaf_vis)
4666   IF (ALLOCATED(alb_leaf_nir)) DEALLOCATE(alb_leaf_nir)   
4667   !chaoyue+
4668   IF (ALLOCATED(permafrost_veg_exists)) DEALLOCATE(permafrost_veg_exists)   
4669   !chaoyue-
4670   IF (ALLOCATED(em_factor_isoprene)) DEALLOCATE(em_factor_isoprene)
4671   IF (ALLOCATED(em_factor_monoterpene)) DEALLOCATE(em_factor_monoterpene)
4672   IF (ALLOCATED(em_factor_apinene)) DEALLOCATE(em_factor_apinene)
4673   IF (ALLOCATED(em_factor_bpinene)) DEALLOCATE(em_factor_bpinene)
4674   IF (ALLOCATED(em_factor_limonene)) DEALLOCATE(em_factor_limonene)
4675   IF (ALLOCATED(em_factor_myrcene)) DEALLOCATE(em_factor_myrcene)
4676   IF (ALLOCATED(em_factor_sabinene)) DEALLOCATE(em_factor_sabinene)
4677   IF (ALLOCATED(em_factor_camphene)) DEALLOCATE(em_factor_camphene)
4678   IF (ALLOCATED(em_factor_3carene)) DEALLOCATE(em_factor_3carene)
4679   IF (ALLOCATED(em_factor_tbocimene)) DEALLOCATE(em_factor_tbocimene)
4680   IF (ALLOCATED(em_factor_othermonot)) DEALLOCATE(em_factor_othermonot)
4681   IF (ALLOCATED(em_factor_sesquiterp)) DEALLOCATE(em_factor_sesquiterp)
4682   IF (ALLOCATED(em_factor_ORVOC)) DEALLOCATE(em_factor_ORVOC)
4683   IF (ALLOCATED(em_factor_OVOC)) DEALLOCATE(em_factor_OVOC)
4684   IF (ALLOCATED(em_factor_MBO)) DEALLOCATE(em_factor_MBO)
4685   IF (ALLOCATED(em_factor_methanol)) DEALLOCATE(em_factor_methanol)
4686   IF (ALLOCATED(em_factor_acetone)) DEALLOCATE(em_factor_acetone)
4687   IF (ALLOCATED(em_factor_acetal)) DEALLOCATE(em_factor_acetal)
4688   IF (ALLOCATED(em_factor_formal)) DEALLOCATE(em_factor_formal)
4689   IF (ALLOCATED(em_factor_acetic)) DEALLOCATE(em_factor_acetic)
4690   IF (ALLOCATED(em_factor_formic)) DEALLOCATE(em_factor_formic)
4691   IF (ALLOCATED(em_factor_no_wet)) DEALLOCATE(em_factor_no_wet)
4692   IF (ALLOCATED(em_factor_no_dry)) DEALLOCATE(em_factor_no_dry)
4693   IF (ALLOCATED(Larch)) DEALLOCATE(Larch)
4694   IF (ALLOCATED(leaf_tab)) DEALLOCATE(leaf_tab)
4695   IF (ALLOCATED(sla)) DEALLOCATE(sla)
4696   IF (ALLOCATED(availability_fact)) DEALLOCATE(availability_fact)
4697   IF (ALLOCATED(R0)) DEALLOCATE(R0)
4698   IF (ALLOCATED(S0)) DEALLOCATE(S0)
4699   IF (ALLOCATED(L0)) DEALLOCATE(L0)
4700   IF (ALLOCATED(frac_growthresp)) DEALLOCATE(frac_growthresp)
4701   IF (ALLOCATED(maint_resp_slope)) DEALLOCATE(maint_resp_slope)
4702   IF (ALLOCATED(maint_resp_slope_c)) DEALLOCATE(maint_resp_slope_c)
4703   IF (ALLOCATED(maint_resp_slope_b)) DEALLOCATE(maint_resp_slope_b)
4704   IF (ALLOCATED(maint_resp_slope_a)) DEALLOCATE(maint_resp_slope_a)
4705   IF (ALLOCATED(coeff_maint_zero)) DEALLOCATE(coeff_maint_zero)
4706   IF (ALLOCATED(cm_zero_leaf)) DEALLOCATE(cm_zero_leaf)
4707   IF (ALLOCATED(cm_zero_sapabove)) DEALLOCATE(cm_zero_sapabove)
4708   IF (ALLOCATED(cm_zero_sapbelow)) DEALLOCATE(cm_zero_sapbelow)
4709   IF (ALLOCATED(cm_zero_heartabove)) DEALLOCATE(cm_zero_heartabove)
4710   IF (ALLOCATED(cm_zero_heartbelow)) DEALLOCATE(cm_zero_heartbelow)
4711   IF (ALLOCATED(cm_zero_root)) DEALLOCATE(cm_zero_root)
4712   IF (ALLOCATED(cm_zero_fruit)) DEALLOCATE(cm_zero_fruit)
4713   IF (ALLOCATED(cm_zero_carbres)) DEALLOCATE(cm_zero_carbres)
4714   IF (ALLOCATED(flam)) DEALLOCATE(flam)
4715   IF (ALLOCATED(resist)) DEALLOCATE(resist)
4716   !spitfire
4717   IF (ALLOCATED(dens_fuel)) DEALLOCATE(dens_fuel)
4718   IF (ALLOCATED(f_sh)) DEALLOCATE(f_sh)
4719   IF (ALLOCATED(crown_length)) DEALLOCATE(crown_length)
4720   IF (ALLOCATED(BTpar1)) DEALLOCATE(BTpar1)
4721   IF (ALLOCATED(BTpar2)) DEALLOCATE(BTpar2)
4722   IF (ALLOCATED(r_ck)) DEALLOCATE(r_ck)
4723   IF (ALLOCATED(p_ck)) DEALLOCATE(p_ck)
4724   IF (ALLOCATED(ef_CO2)) DEALLOCATE(ef_CO2)
4725   IF (ALLOCATED(ef_CO)) DEALLOCATE(ef_CO)
4726   IF (ALLOCATED(ef_CH4)) DEALLOCATE(ef_CH4)
4727   IF (ALLOCATED(ef_VOC)) DEALLOCATE(ef_VOC)
4728   IF (ALLOCATED(ef_TPM)) DEALLOCATE(ef_TPM)
4729   IF (ALLOCATED(ef_NOx)) DEALLOCATE(ef_NOx)
4730   IF (ALLOCATED(me)) DEALLOCATE(me)
4731   IF (ALLOCATED(fire_max_cf_100hr)) DEALLOCATE(fire_max_cf_100hr)
4732   IF (ALLOCATED(fire_max_cf_1000hr)) DEALLOCATE(fire_max_cf_1000hr)
4733   !endspit
4734   IF (ALLOCATED(coeff_lcchange_1)) DEALLOCATE(coeff_lcchange_1)
4735   IF (ALLOCATED(coeff_lcchange_10)) DEALLOCATE(coeff_lcchange_10)
4736   IF (ALLOCATED(coeff_lcchange_100)) DEALLOCATE(coeff_lcchange_100)
4737   IF (ALLOCATED(lai_max_to_happy)) DEALLOCATE(lai_max_to_happy)
4738   IF (ALLOCATED(lai_max)) DEALLOCATE(lai_max)
4739!gmjc
4740   IF(ALLOCATED(is_grassland_manag))DEALLOCATE(is_grassland_manag)
4741   IF(ALLOCATED(is_grassland_cut))DEALLOCATE(is_grassland_cut)
4742   IF(ALLOCATED(is_grassland_grazed))DEALLOCATE(is_grassland_grazed)
4743   IF (ALLOCATED(nb_year_management)) DEALLOCATE(nb_year_management)
4744   IF (ALLOCATED(management_intensity)) DEALLOCATE(management_intensity)
4745   IF (ALLOCATED(management_start)) DEALLOCATE(management_start)
4746   IF (ALLOCATED(deposition_start)) DEALLOCATE(deposition_start)
4747   IF(ALLOCATED(sla_max))DEALLOCATE(sla_max)
4748   IF(ALLOCATED(sla_min))DEALLOCATE(sla_min)
4749!end gmjc
4750   IF (ALLOCATED(pheno_model)) DEALLOCATE(pheno_model)
4751   IF (ALLOCATED(pheno_type)) DEALLOCATE(pheno_type)
4752   IF (ALLOCATED(pheno_gdd_crit_c)) DEALLOCATE(pheno_gdd_crit_c)
4753   IF (ALLOCATED(pheno_gdd_crit_b)) DEALLOCATE(pheno_gdd_crit_b)
4754   IF (ALLOCATED(pheno_gdd_crit_a)) DEALLOCATE(pheno_gdd_crit_a)
4755   IF (ALLOCATED(pheno_gdd_crit)) DEALLOCATE(pheno_gdd_crit)
4756   IF (ALLOCATED(pheno_moigdd_t_crit)) DEALLOCATE(pheno_moigdd_t_crit)
4757   IF (ALLOCATED(ngd_crit)) DEALLOCATE(ngd_crit)
4758   IF (ALLOCATED(ncdgdd_temp)) DEALLOCATE(ncdgdd_temp)
4759   IF (ALLOCATED(hum_frac)) DEALLOCATE(hum_frac)
4760   IF (ALLOCATED(hum_min_time)) DEALLOCATE(hum_min_time)
4761   IF (ALLOCATED(tau_sap)) DEALLOCATE(tau_sap)
4762   IF (ALLOCATED(tau_leafinit)) DEALLOCATE(tau_leafinit)
4763   IF (ALLOCATED(tau_fruit)) DEALLOCATE(tau_fruit)
4764   IF (ALLOCATED(ecureuil)) DEALLOCATE(ecureuil)
4765   IF (ALLOCATED(alloc_min)) DEALLOCATE(alloc_min)
4766   IF (ALLOCATED(alloc_max)) DEALLOCATE(alloc_max)
4767   IF (ALLOCATED(demi_alloc)) DEALLOCATE(demi_alloc)
4768   IF (ALLOCATED(leaflife_tab)) DEALLOCATE(leaflife_tab)
4769   IF (ALLOCATED(leaffall)) DEALLOCATE(leaffall)
4770   IF (ALLOCATED(leafagecrit)) DEALLOCATE(leafagecrit)
4771   IF (ALLOCATED(senescence_type)) DEALLOCATE(senescence_type)
4772   IF (ALLOCATED(senescence_hum)) DEALLOCATE(senescence_hum)
4773   IF (ALLOCATED(nosenescence_hum)) DEALLOCATE(nosenescence_hum)
4774   IF (ALLOCATED(max_turnover_time)) DEALLOCATE(max_turnover_time)
4775   IF (ALLOCATED(min_turnover_time)) DEALLOCATE(min_turnover_time)
4776   IF (ALLOCATED(min_leaf_age_for_senescence)) DEALLOCATE(min_leaf_age_for_senescence)
4777   IF (ALLOCATED(senescence_temp_c)) DEALLOCATE(senescence_temp_c)
4778   IF (ALLOCATED(senescence_temp_b)) DEALLOCATE(senescence_temp_b)
4779   IF (ALLOCATED(senescence_temp_a)) DEALLOCATE(senescence_temp_a)
4780   IF (ALLOCATED(senescence_temp)) DEALLOCATE(senescence_temp)
4781   IF (ALLOCATED(gdd_senescence)) DEALLOCATE(gdd_senescence)
4782   IF (ALLOCATED(residence_time)) DEALLOCATE(residence_time)
4783   IF (ALLOCATED(tmin_crit)) DEALLOCATE(tmin_crit)
4784   IF (ALLOCATED(tcm_crit)) DEALLOCATE(tcm_crit)
4785   IF (ALLOCATED(lai_initmin)) DEALLOCATE(lai_initmin)
4786   IF (ALLOCATED(bm_sapl)) DEALLOCATE(bm_sapl)
4787   IF (ALLOCATED(migrate)) DEALLOCATE(migrate)
4788   IF (ALLOCATED(maxdia)) DEALLOCATE(maxdia)
4789   IF (ALLOCATED(cn_sapl)) DEALLOCATE(cn_sapl)
4790   IF (ALLOCATED(leaf_timecst)) DEALLOCATE(leaf_timecst)
4791   
4792!pss+
4793   IF (ALLOCATED(rdepth_v)) DEALLOCATE(rdepth_v)
4794   IF (ALLOCATED(sdepth_v)) DEALLOCATE(sdepth_v)
4795   IF (ALLOCATED(tveg_v)) DEALLOCATE(tveg_v)
4796!pss-
4797
4798!!!!! crop parameters
4799   IF (ALLOCATED(irrig_threshold)) DEALLOCATE(irrig_threshold)
4800   IF (ALLOCATED(irrig_fulfill)) DEALLOCATE(irrig_fulfill)
4801
4802   ! DEALLOCATE FOR crop
4803
4804   IF(ALLOCATED(ok_LAIdev))DEALLOCATE(ok_LAIdev)
4805
4806   IF(ALLOCATED(SP_codeplante))DEALLOCATE(SP_codeplante)
4807   IF(ALLOCATED(SP_stade0))DEALLOCATE(SP_stade0)
4808   IF(ALLOCATED(SP_iplt0))DEALLOCATE(SP_iplt0)
4809   IF(ALLOCATED(SP_nbox))DEALLOCATE(SP_nbox)
4810   IF(ALLOCATED(SP_iwater))DEALLOCATE(SP_iwater)
4811   IF(ALLOCATED(SP_codesimul))DEALLOCATE(SP_codesimul)
4812   IF(ALLOCATED(SP_codelaitr))DEALLOCATE(SP_codelaitr)
4813   IF(ALLOCATED(SP_slamax))DEALLOCATE(SP_slamax)
4814   IF(ALLOCATED(SP_slamin))DEALLOCATE(SP_slamin)
4815   IF(ALLOCATED(SP_codeperenne))DEALLOCATE(SP_codeperenne)
4816   IF(ALLOCATED(SP_codcueille))DEALLOCATE(SP_codcueille)
4817   IF(ALLOCATED(SP_codegdh))DEALLOCATE(SP_codegdh)
4818   IF(ALLOCATED(SP_codetemp))DEALLOCATE(SP_codetemp)
4819   IF(ALLOCATED(SP_coderetflo))DEALLOCATE(SP_coderetflo)
4820   IF(ALLOCATED(SP_codeinnact))DEALLOCATE(SP_codeinnact)
4821   IF(ALLOCATED(SP_codeh2oact))DEALLOCATE(SP_codeh2oact)
4822   IF(ALLOCATED(SP_stressdev))DEALLOCATE(SP_stressdev)
4823   IF(ALLOCATED(SP_innlai))DEALLOCATE(SP_innlai)
4824   IF(ALLOCATED(SP_innsenes))DEALLOCATE(SP_innsenes)
4825   IF(ALLOCATED(SP_codebfroid))DEALLOCATE(SP_codebfroid)
4826   IF(ALLOCATED(SP_codephot))DEALLOCATE(SP_codephot)
4827   IF(ALLOCATED(SP_codedormance))DEALLOCATE(SP_codedormance)
4828   IF(ALLOCATED(SP_codefauche))DEALLOCATE(SP_codefauche)
4829   IF(ALLOCATED(SP_codetempfauche))DEALLOCATE(SP_codetempfauche)
4830   IF(ALLOCATED(SP_codlainet))DEALLOCATE(SP_codlainet)
4831   IF(ALLOCATED(SP_codeindetermin))DEALLOCATE(SP_codeindetermin)
4832   IF(ALLOCATED(SP_codeinitprec))DEALLOCATE(SP_codeinitprec)
4833   IF(ALLOCATED(SP_culturean))DEALLOCATE(SP_culturean)
4834   IF(ALLOCATED(SP_jvc))DEALLOCATE(SP_jvc)
4835   IF(ALLOCATED(SP_tfroid))DEALLOCATE(SP_tfroid)
4836   IF(ALLOCATED(SP_ampfroid))DEALLOCATE(SP_ampfroid)
4837   IF(ALLOCATED(SP_jvcmini))DEALLOCATE(SP_jvcmini)
4838   IF(ALLOCATED(SP_tgmin))DEALLOCATE(SP_tgmin)
4839   IF(ALLOCATED(SP_stpltger))DEALLOCATE(SP_stpltger)
4840   IF(ALLOCATED(SP_profsem))DEALLOCATE(SP_profsem)
4841   IF(ALLOCATED(SP_propjgermin))DEALLOCATE(SP_propjgermin)
4842   IF(ALLOCATED(SP_tdmax))DEALLOCATE(SP_tdmax)
4843   IF(ALLOCATED(SP_nbjgerlim))DEALLOCATE(SP_nbjgerlim)
4844   IF(ALLOCATED(SP_densitesem))DEALLOCATE(SP_densitesem)
4845   IF(ALLOCATED(SP_vigueurbat))DEALLOCATE(SP_vigueurbat)
4846   IF(ALLOCATED(SP_codepluiepoquet))DEALLOCATE(SP_codepluiepoquet)
4847   IF(ALLOCATED(SP_codehypo))DEALLOCATE(SP_codehypo)
4848   IF(ALLOCATED(SP_elmax))DEALLOCATE(SP_elmax)
4849   IF(ALLOCATED(SP_belong))DEALLOCATE(SP_belong)
4850   IF(ALLOCATED(SP_celong))DEALLOCATE(SP_celong)
4851   IF(ALLOCATED(SP_nlevlim1))DEALLOCATE(SP_nlevlim1)
4852   IF(ALLOCATED(SP_nlevlim2))DEALLOCATE(SP_nlevlim2)
4853   IF(ALLOCATED(SP_codrecolte))DEALLOCATE(SP_codrecolte)
4854   IF(ALLOCATED(SP_variete))DEALLOCATE(SP_variete)
4855   IF(ALLOCATED(SP_codegermin))DEALLOCATE(SP_codegermin)
4856
4857   IF(ALLOCATED(S_codeulaivernal))DEALLOCATE(S_codeulaivernal)
4858   IF(ALLOCATED(SP_swfacmin))DEALLOCATE(SP_swfacmin)
4859   IF(ALLOCATED(SP_neffmax))DEALLOCATE(SP_neffmax)
4860   IF(ALLOCATED(SP_nsatrat))DEALLOCATE(SP_nsatrat)
4861
4862   ! STICS:: LAI CALCULATION
4863   IF(ALLOCATED(SP_laiplantule))DEALLOCATE(SP_laiplantule)
4864   IF(ALLOCATED(SP_vlaimax))DEALLOCATE(SP_vlaimax)
4865   IF(ALLOCATED(SP_stlevamf))DEALLOCATE(SP_stlevamf)
4866   IF(ALLOCATED(SP_stdrpmat))DEALLOCATE(SP_stdrpmat)
4867   IF(ALLOCATED(SP_stamflax))DEALLOCATE(SP_stamflax)
4868
4869   IF(ALLOCATED(SP_udlaimax))DEALLOCATE(SP_udlaimax)
4870   IF(ALLOCATED(SP_laicomp))DEALLOCATE(SP_laicomp)
4871   IF(ALLOCATED(SP_adens))DEALLOCATE(SP_adens)
4872   IF(ALLOCATED(SP_bdens))DEALLOCATE(SP_bdens)
4873   IF(ALLOCATED(SP_tcxstop))DEALLOCATE(SP_tcxstop)
4874   IF(ALLOCATED(SP_tcmax))DEALLOCATE(SP_tcmax)
4875   IF(ALLOCATED(SP_tcmin))DEALLOCATE(SP_tcmin)
4876   IF(ALLOCATED(SP_dlaimax))DEALLOCATE(SP_dlaimax)
4877   IF(ALLOCATED(SP_dlaimin))DEALLOCATE(SP_dlaimin)
4878   IF(ALLOCATED(SP_pentlaimax))DEALLOCATE(SP_pentlaimax)
4879   IF(ALLOCATED(SP_tigefeuil))DEALLOCATE(SP_tigefeuil)
4880
4881   IF(ALLOCATED(SP_stlaxsen))DEALLOCATE(SP_stlaxsen)
4882   IF(ALLOCATED(SP_stsenlan))DEALLOCATE(SP_stsenlan)
4883   IF(ALLOCATED(SP_stlevdrp))DEALLOCATE(SP_stlevdrp)
4884   IF(ALLOCATED(SP_stflodrp))DEALLOCATE(SP_stflodrp)
4885   IF(ALLOCATED(SP_stdrpdes))DEALLOCATE(SP_stdrpdes)
4886   IF(ALLOCATED(SP_phyllotherme))DEALLOCATE(SP_phyllotherme)
4887
4888   IF(ALLOCATED(SP_lai0))DEALLOCATE(SP_lai0)
4889   IF(ALLOCATED(SP_tustressmin))DEALLOCATE(SP_tustressmin)
4890
4891
4892   ! STICS:: LAI SENESCENCE
4893   IF(ALLOCATED(SP_nbfgellev))DEALLOCATE(SP_nbfgellev)
4894   IF(ALLOCATED(SP_ratiodurvieI))DEALLOCATE(SP_ratiodurvieI)
4895   IF(ALLOCATED(SP_durvieF))DEALLOCATE(SP_durvieF)
4896   IF(ALLOCATED(SP_ratiosen))DEALLOCATE(SP_ratiosen)
4897   IF(ALLOCATED(SP_tdmin))DEALLOCATE(SP_tdmin)
4898   
4899   ! STICS:: F_humerac
4900 
4901   IF(ALLOCATED(SP_sensrsec))DEALLOCATE(SP_sensrsec)
4902   ! STICS:: gel
4903
4904   IF(ALLOCATED(SP_codgellev))DEALLOCATE(SP_codgellev)
4905   IF(ALLOCATED(SP_codgeljuv))DEALLOCATE(SP_codgeljuv)
4906   IF(ALLOCATED(SP_codgelveg))DEALLOCATE(SP_codgelveg)
4907   IF(ALLOCATED(SP_tletale))DEALLOCATE(SP_tletale)
4908   IF(ALLOCATED(SP_tdebgel))DEALLOCATE(SP_tdebgel)
4909   IF(ALLOCATED(SP_tgellev10))DEALLOCATE(SP_tgellev10)
4910   IF(ALLOCATED(SP_tgellev90))DEALLOCATE(SP_tgellev90)
4911
4912   IF(ALLOCATED(SP_tgeljuv10))DEALLOCATE(SP_tgeljuv10)
4913   IF(ALLOCATED(SP_tgeljuv90))DEALLOCATE(SP_tgeljuv90)
4914   IF(ALLOCATED(SP_tgelveg10))DEALLOCATE(SP_tgelveg10)
4915   IF(ALLOCATED(SP_tgelveg90))DEALLOCATE(SP_tgelveg90)
4916
4917
4918
4919
4920   ! STICS:: Photoperiod
4921 
4922   IF(ALLOCATED(SP_sensiphot))DEALLOCATE(SP_sensiphot)
4923   IF(ALLOCATED(SP_phosat))DEALLOCATE(SP_phosat)
4924   IF(ALLOCATED(SP_phobase))DEALLOCATE(SP_phobase)
4925   
4926   ! STICS:: CARBON ALLOCATION
4927     
4928   IF(ALLOCATED(SP_stoprac))DEALLOCATE(SP_stoprac)
4929   IF(ALLOCATED(SP_zracplantule))DEALLOCATE(SP_zracplantule)
4930   IF(ALLOCATED(SP_codtrophrac))DEALLOCATE(SP_codtrophrac)
4931   IF(ALLOCATED(SP_repracpermax))DEALLOCATE(SP_repracpermax)
4932   IF(ALLOCATED(SP_repracpermin))DEALLOCATE(SP_repracpermin)
4933   IF(ALLOCATED(SP_krepracperm))DEALLOCATE(SP_krepracperm)
4934   IF(ALLOCATED(SP_repracseumax))DEALLOCATE(SP_repracseumax)
4935   IF(ALLOCATED(SP_repracseumin))DEALLOCATE(SP_repracseumin)
4936   IF(ALLOCATED(SP_krepracseu))DEALLOCATE(SP_krepracseu)
4937   IF(ALLOCATED(SP_codetemprac))DEALLOCATE(SP_codetemprac)
4938   IF(ALLOCATED(SP_codedyntalle))DEALLOCATE(SP_codedyntalle)
4939   IF(ALLOCATED(SP_nbjgrain))DEALLOCATE(SP_nbjgrain)
4940   IF(ALLOCATED(SP_maxgs))DEALLOCATE(SP_maxgs)
4941   IF(ALLOCATED(SP_codgelflo))DEALLOCATE(SP_codgelflo)
4942   IF(ALLOCATED(SP_tgelflo10))DEALLOCATE(SP_tgelflo10)
4943   IF(ALLOCATED(SP_tgelflo90))DEALLOCATE(SP_tgelflo90)
4944   IF(ALLOCATED(SP_cgrain))DEALLOCATE(SP_cgrain)
4945   IF(ALLOCATED(SP_cgrainv0))DEALLOCATE(SP_cgrainv0)
4946   IF(ALLOCATED(SP_nbgrmax))DEALLOCATE(SP_nbgrmax)
4947   IF(ALLOCATED(SP_nbgrmin))DEALLOCATE(SP_nbgrmin)
4948   IF(ALLOCATED(SP_codazofruit))DEALLOCATE(SP_codazofruit)
4949   IF(ALLOCATED(SP_codeir))DEALLOCATE(SP_codeir)
4950   IF(ALLOCATED(SP_vitircarb))DEALLOCATE(SP_vitircarb)
4951   IF(ALLOCATED(SP_irmax))DEALLOCATE(SP_irmax)
4952   IF(ALLOCATED(SP_vitircarbT))DEALLOCATE(SP_vitircarbT)
4953   IF(ALLOCATED(SP_codetremp))DEALLOCATE(SP_codetremp)
4954   IF(ALLOCATED(SP_tminremp))DEALLOCATE(SP_tminremp)
4955   IF(ALLOCATED(SP_tmaxremp))DEALLOCATE(SP_tmaxremp)
4956   IF(ALLOCATED(SP_pgrainmaxi))DEALLOCATE(SP_pgrainmaxi)
4957 
4958   IF(ALLOCATED(SP_DY_INN))DEALLOCATE(SP_DY_INN)
4959   IF(ALLOCATED(SP_avenfert))DEALLOCATE(SP_avenfert)
4960!!!!! end crop parameters
4961
4962 END SUBROUTINE pft_parameters_clear
4963
4964END MODULE pft_parameters
Note: See TracBrowser for help on using the repository browser.