source: branches/publications/ORCHIDEE_Biochar/src_parameters/pft_parameters.f90 @ 8375

Last change on this file since 8375 was 7366, checked in by simon.bowring, 3 years ago

Biochar version

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