source: branches/publications/ORCHIDEE-LEAK-r5919/src_parameters/pft_parameters.f90 @ 5925

Last change on this file since 5925 was 3221, checked in by josefine.ghattas, 8 years ago

Ticket #230 : modifications related to BVOC
J Lathiere, P Messina, A Cozic

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