source: branches/ORCHIDEE_EXT/ORCHIDEE/src_parameters/pft_parameters.f90 @ 435

Last change on this file since 435 was 435, checked in by didier.solyga, 13 years ago

Add a new getin_p subroutine for vector of characters. Replace the last getin by getin_p. Use the new function of IOPSL for writing the names of the PFTs defined by the user in the history files

File size: 75.8 KB
Line 
1! Version 0:   26/06/2010
2! This is the module where we define the number of pfts and the values of the
3! parameters
4! author : D.Solyga
5
6MODULE pft_parameters
7
8USE constantes_mtc
9USE constantes
10USE ioipsl
11USE parallel
12USE defprec
13
14IMPLICIT NONE
15
16
17  !-------------------------
18  ! PFT global
19  !------------------------
20  ! Number of vegetation types
21  INTEGER(i_std), SAVE :: nvm = 13 
22  !-
23  !Table of conversion : we associate one pft to one mtc
24  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pft_to_mtc
25  !-
26  ! Description of the PFT
27  CHARACTER(len=34), ALLOCATABLE, SAVE, DIMENSION (:)  :: PFT_name
28  !
29  ! Flag l_first_define_pft
30  LOGICAL, SAVE   :: l_first_define_pft = .TRUE.
31
32  !----------------------
33  ! Vegetation structure
34  !----------------------
35  !-
36  ! 1 .Sechiba
37  !-
38  ! Value for veget_ori for tests in 0-dim simulations
39  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: veget_ori_fixed_test_1
40  ! laimax for maximum lai see also type of lai interpolation
41  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: llaimax
42  ! laimin for minimum lai see also type of lai interpolation
43  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: llaimin
44  ! prescribed height of vegetation.
45  ! Value for height_presc : one for each vegetation type
46  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: height_presc
47  ! Type of behaviour of the LAI evolution algorithm
48  ! for each vegetation type.
49  ! Value of type_of_lai, one for each vegetation type : mean or interp
50  CHARACTER(len=5),ALLOCATABLE, SAVE, DIMENSION (:) :: type_of_lai
51  ! Is the vegetation type a tree ?
52  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_tree
53  !>> DS new for merge in the trunk   ! 15/06/2011
54  ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
55  ! is PFT deciduous ?
56  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_deciduous
57  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_evergreen
58  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_c3
59  ! used in diffuco   !! Nathalie le 28 mars 2006 - sur proposition de Fred Hourdin, ajout
60  !! d'un potentiometre pour regler la resistance de la vegetation
61  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)      ::  rveg_pft
62
63  !-
64  ! 2 .Stomate
65  !-
66  ! leaf type
67  ! 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bared ground
68  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaf_tab
69  ! specif leaf area (m**2/gC)
70  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: sla
71  ! natural?
72  LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:) :: natural
73
74  !-------------------------------
75  ! Evapotranspiration -  sechiba
76  !-------------------------------
77  !-
78  ! Structural resistance.
79  ! Value for rstruct_const : one for each vegetation type
80  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: rstruct_const
81  !
82  ! A vegetation dependent constant used in the calculation
83  ! of the surface resistance.
84  ! Value for kzero one for each vegetation type
85  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: kzero 
86
87
88  !-------------------
89  ! Water - sechiba
90  !-------------------
91  !-
92  ! Maximum field capacity for each of the vegetations (Temporary).
93  ! Value of wmax_veg : max quantity of water :
94  ! one for each vegetation type en Kg/M3
95  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: wmax_veg
96  ! Root profile description for the different vegetation types.
97  ! These are the factor in the exponential which gets
98  ! the root density as a function of depth
99  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: humcste
100  ! used in hydrolc
101  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: throughfall_by_pft
102
103
104  !------------------
105  ! Albedo - sechiba
106  !------------------
107  !-
108  ! Initial snow albedo value for each vegetation type
109  ! as it will be used in condveg_snow
110  ! Values are from the Thesis of S. Chalita (1992)
111  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_ini
112  !
113  ! Decay rate of snow albedo value for each vegetation type
114  ! as it will be used in condveg_snow
115  ! Values are from the Thesis of S. Chalita (1992)
116  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: snowa_dec
117  !
118  ! leaf albedo of vegetation type, visible albedo
119  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_vis
120  ! leaf albedo of vegetation type, near infrared albedo
121  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf_nir
122  ! leaf albedo of vegetation type, VIS+NIR
123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alb_leaf
124
125
126  !------------------------
127  !   Soil - vegetation
128  !------------------------
129  !
130  ! Table which contains the correlation between the soil types
131  ! and vegetation type. Two modes exist :
132  !  1) pref_soil_veg = 0 then we have an equidistribution
133  !     of vegetation on soil types
134  !  2) Else for each pft the prefered soil type is given :
135  !     1=sand, 2=loan, 3=clay
136  ! The variable is initialized in slowproc.
137  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: pref_soil_veg
138  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_sand
139  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_loan
140  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pref_soil_veg_clay
141
142  !----------------
143  ! Photosynthesis
144  !----------------
145  !-
146  ! 1 .CO2
147  !-
148  ! flag for C4 vegetation types
149  LOGICAL, ALLOCATABLE, SAVE, DIMENSION (:) :: is_c4
150  ! Slope of the gs/A relation (Ball & al.)
151  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: gsslope
152  ! intercept of the gs/A relation (Ball & al.)
153  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: gsoffset
154  ! values used for vcmax when STOMATE is not activated
155  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  ::  vcmax_fix
156  ! values used for vjmax when STOMATE is not activated
157  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: vjmax_fix
158  ! values used for photosynthesis tmin when STOMATE is not activated
159  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: co2_tmin_fix
160  ! values used for photosynthesis topt when STOMATE is not activated
161  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: co2_topt_fix
162  ! values used for photosynthesis tmax when STOMATE is not activated
163  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: co2_tmax_fix
164  !-
165  ! 2 .Stomate
166  !-
167  ! extinction coefficient of the Monsi&Seaki relationship (1953)
168  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ext_coeff ! = ext_coef in sechiba
169  ! Maximum rate of carboxylation
170  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: vcmax_opt
171  ! Maximum rate of RUbp regeneration
172  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: vjmax_opt
173  ! minimum photosynthesis temperature,
174  ! constant a of ax^2+bx+c (deg C),tabulated
175  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tphoto_min_a
176  ! minimum photosynthesis temperature,
177  ! constant b of ax^2+bx+c (deg C),tabulated
178  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: tphoto_min_b 
179  ! minimum photosynthesis temperature,
180  ! constant c of ax^2+bx+c (deg C),tabulated
181  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: tphoto_min_c 
182  ! optimum photosynthesis temperature,
183  ! constant a of ax^2+bx+c (deg C),tabulated
184  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: tphoto_opt_a 
185  ! optimum photosynthesis temperature,
186  ! constant b of ax^2+bx+c (deg C),tabulated
187  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: tphoto_opt_b 
188  ! optimum photosynthesis temperature,
189  ! constant c of ax^2+bx+c (deg C),tabulated
190  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION (:)  :: tphoto_opt_c
191  ! maximum photosynthesis temperature,
192  ! constant a of ax^2+bx+c (deg C), tabulated
193  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: tphoto_max_a
194  ! maximum photosynthesis temperature,
195  ! constant b of ax^2+bx+c (deg C), tabulated
196  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: tphoto_max_b 
197  ! maximum photosynthesis temperature,
198  ! constant c of ax^2+bx+c (deg C), tabulated
199  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION (:)   :: tphoto_max_c 
200
201
202  !-----------------------
203  ! Respiration - stomate
204  !-----------------------
205  !
206!-! slope of maintenance respiration coefficient (1/K, 1/K^2, 1/K^3), used in the code
207  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)        :: maint_resp_slope
208  ! slope of maintenance respiration coefficient (1/K),
209  ! constant c of aT^2+bT+c , tabulated
210  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: maint_resp_slope_c
211  ! slope of maintenance respiration coefficient (1/K),
212  ! constant b of aT^2+bT+c , tabulated
213  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: maint_resp_slope_b
214  ! slope of maintenance respiration coefficient (1/K),
215  ! constant a of aT^2+bT+c , tabulated
216  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: maint_resp_slope_a
217!- ! maintenance respiration coefficient (g/g/day) at 0 deg C, used in the code
218  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: coeff_maint_zero
219  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
220  ! for leaves, tabulated
221  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_leaf
222  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
223  ! for sapwood above, tabulated
224  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_sapabove
225  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
226  ! for sapwood below, tabulated
227  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_sapbelow
228  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
229  ! for heartwood above, tabulated
230  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_heartabove
231  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
232  ! for heartwood below, tabulated
233  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_heartbelow
234  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
235  ! for roots, tabulated
236  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_root
237  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
238  ! for fruits, tabulated
239  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: cm_zero_fruit
240  ! maintenance respiration coefficient (g/g/day) at 0 deg C,
241  ! for carbohydrate reserve, tabulated
242  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::cm_zero_carbres
243
244 
245  !----------------
246  ! Fire - stomate
247  !----------------
248  !
249  ! flamability: critical fraction of water holding capacity
250  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: flam
251  ! fire resistance
252  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: resist
253
254
255  !---------------
256  ! Flux - LUC
257  !---------------
258  !
259  ! Coeff of biomass export for the year
260  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: coeff_lcchange_1
261  ! Coeff of biomass export for the decade
262  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: coeff_lcchange_10
263  ! Coeff of biomass export for the century
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: coeff_lcchange_100
265 
266
267  !-----------
268  ! Phenology
269  !-----------
270  !-
271  ! 1 .Stomate
272  !-
273  ! maximum LAI, PFT-specific
274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: lai_max 
275  ! which phenology model is used? (tabulated)
276  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_model
277  ! type of phenology
278  ! 0=bared ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
279  ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols
280  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_type
281  !-
282  ! 2. Leaf Onset
283  !-
284!-! critical gdd,tabulated (C), used in the code
285  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: pheno_gdd_crit
286  ! critical gdd,tabulated (C), constant c of aT^2+bT+c
287  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: pheno_gdd_crit_c
288  ! critical gdd,tabulated (C), constant b of aT^2+bT+c
289  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::  pheno_gdd_crit_b
290  ! critical gdd,tabulated (C), constant a of aT^2+bT+c
291  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::  pheno_gdd_crit_a
292  ! critical ngd,tabulated. Threshold -5 degrees
293  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ngd_crit
294  ! critical temperature for the ncd vs. gdd function in phenology
295  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::  ncdgdd_temp
296  ! critical humidity (relative to min/max) for phenology
297  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::  hum_frac
298  ! minimum duration of dormance (d) for phenology
299  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: lowgpp_time
300  ! minimum time elapsed since moisture minimum (d)
301  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)  :: hum_min_time
302  ! sapwood -> heartwood conversion time (d)
303  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tau_sap
304  ! fruit lifetime (d)
305  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tau_fruit
306  ! fraction of primary leaf and root allocation put into reserve
307  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: ecureuil
308  ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
309  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alloc_min
310  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: alloc_max
311  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: demi_alloc
312  !>> DS new for merge in the trunk
313  ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla
314  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaflife_tab
315  !-
316  ! 3. Senescence
317  !-
318  ! length of death of leaves,tabulated (d)
319  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leaffall 
320  ! critical leaf age,tabulated (d)
321  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: leafagecrit
322  ! type of senescence,tabulated
323  ! List of avaible types of senescence :
324  ! 'cold  ', 'dry   ', 'mixed ', 'none  '
325  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_type
326  ! critical relative moisture availability for senescence
327  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_hum
328  ! relative moisture availability above which
329  ! there is no humidity-related senescence
330  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: nosenescence_hum
331  ! maximum turnover time for grasse
332  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: max_turnover_time
333  ! minimum turnover time for grasse
334  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: min_turnover_time
335  ! minimum leaf age to allow senescence g
336  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: min_leaf_age_for_senescence
337!-! critical temperature for senescence (C), used in the code
338  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:) :: senescence_temp
339  ! critical temperature for senescence (C),
340  ! constant c of aT^2+bT+c , tabulated
341  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::  senescence_temp_c
342  ! critical temperature for senescence (C),
343  ! constant b of aT^2+bT+c , tabulated
344  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_temp_b
345  ! critical temperature for senescence (C),
346  ! constant a of aT^2+bT+c , tabulated
347  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: senescence_temp_a
348
349
350  !-----------
351  ! DGVM
352  !-----------
353  !-
354  ! residence time (y) of trees
355  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: residence_time
356  ! critical tmin, tabulated (C)
357  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) :: tmin_crit
358  ! critical tcm, tabulated (C)
359  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:) ::  tcm_crit
360
361
362  !--------------------------------------------
363  ! Internal parameters used in stomate_data
364  !-------------------------------------------
365  !
366  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:)   :: lai_initmin
367  ! is pft a tree
368  LOGICAL,   ALLOCATABLE, SAVE, DIMENSION (:)    :: tree
369  ! sapling biomass (gC/ind)
370  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION (:,:)  :: bm_sapl
371  ! migration speed (m/year)
372  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION (:)    :: migrate
373  ! maximum stem diameter from which on crown area no longer increases (m)m
374  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION (:)     :: maxdia
375  ! crown of tree when sapling (m**2)
376  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION (:)    :: cn_sapl
377  ! time constant for leaf age discretisation (d)
378  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION (:)    :: leaf_timecst
379
380
381CONTAINS
382 !
383 SUBROUTINE pft_parameters_main(ok_sechiba,ok_stomate) 
384   
385   IMPLICIT NONE
386
387   ! 0.1 input
388   
389   ! Is SECHIBA active ?
390   LOGICAL, INTENT(in) :: ok_sechiba
391   ! Is STOMATE active ?
392   LOGICAL, INTENT(in) :: ok_stomate
393   
394   ! 0.4 local 
395
396   ! Indice
397   INTEGER(i_std) :: i
398
399   !----------------------
400   ! PFT global
401   !----------------------
402
403   IF(l_first_define_pft) THEN
404
405      ! 1. First time step
406      IF(long_print) THEN
407         WRITE(numout,*) 'l_first_define_pft :we read the parameters from the def files'
408      ENDIF
409
410      ! 2. Memory allocation
411      ! Allocation of memory for the pfts-parameters
412      CALL pft_parameters_alloc(ok_sechiba,ok_stomate)
413
414      ! 3. Correspondance table
415     
416      ! 3.1 Initialisation of the correspondance table
417      ! Initialisation of the correspondance table
418      pft_to_mtc(:) = undef_int
419     
420      ! 3.2 Reading of the conrrespondance table in the .def file
421      !
422      !Config  Key  = PFT_TO_MTC
423      !Config  Desc = correspondance array linking a PFT to MTC
424      !Config  if  = ANYTIME
425      !Config  Def  = 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13
426      !Config  Help =
427      !Config  Units = NONE
428      CALL getin_p('PFT_TO_MTC',pft_to_mtc)
429     
430      ! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array
431      !     If the configuration is wrong, send a error message to the user.
432      IF(nvm .EQ. 13 ) THEN
433         IF(pft_to_mtc(1) .EQ. undef_int) THEN
434            WRITE(numout,*) 'Note to the user : we will use ORCHIDEE to its standard configuration'
435            pft_to_mtc(:) = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /)
436         ENDIF
437      ELSE   
438         IF(pft_to_mtc(1) .EQ. undef_int) THEN
439            WRITE(numout,*)' The array PFT_TO_MTC is empty : we stop'
440         ENDIF
441      ENDIF
442
443      ! 3.4 Some error messages
444
445      ! 3.4.1 What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)?
446       DO i = 1, nvm
447          IF(pft_to_mtc(i) .GT. nvmc) THEN
448             WRITE(numout,*) "the MTC you chose doesn't exist"
449             STOP 'we stop reading pft_to_mtc'
450          ENDIF
451       ENDDO   
452
453
454      ! 3.4.2 Check if pft_to_mtc(1) = 1
455       IF(pft_to_mtc(1) .NE. 1) THEN
456          WRITE(numout,*) 'the first pft has to be the bare soil'
457          STOP 'we stop reading next values of pft_to_mtc'
458       ELSE
459          DO i = 2,nvm
460             IF(pft_to_mtc(i) .EQ.1) THEN
461                WRITE(numout,*) 'only pft_to_mtc(1) has to be the bare soil'
462                STOP 'we stop reading pft_to_mtc'
463             ENDIF
464          ENDDO
465       ENDIF
466     
467   
468      ! 4.Initialisation of the pfts-parameters
469      CALL pft_parameters_init(ok_sechiba,ok_stomate)
470
471      ! 5. Useful data
472
473      ! 5.1 Read the name of the PFTs given by the user
474      !
475      !Config  Key = PFT_NAME
476      !Config  Desc = Name of a PFT
477      !Config  if = ANYTIME
478      !Config  Def = bared ground, tropical broad-leaved evergreen, tropical broad-leaved raingreen, temperate needleleaf evergreen,temperate broad-leaved evergreen
479      !              temperate broad-leaved summergreen, boreal needleleaf evergreen, boreal broad-leaved summergreen, boreal needleleaf summergreen,
480      !              C3 grass, C4 grass, C3 agriculture, C4 agriculture   
481      !Config  Help = the user can name the new PFTs he/she introducing for new species
482      !Config  Units = NONE
483      CALL getin_p('PFT_NAME',pft_name)
484
485      ! 5.2 A useful message to the user: correspondance between the number of the pft
486      ! and the name of the associated mtc
487      DO i = 1,nvm
488         WRITE(numout,*) 'the PFT',i, 'called  ', PFT_name(i),'corresponds to the MTC : ',MTC_name(pft_to_mtc(i)) 
489      ENDDO
490
491      ! 6. Initialisation of 2D arrays used in the code
492
493      !- pref_soil_veg
494      pref_soil_veg(:,:) = zero_int
495
496      IF (ok_sechiba) THEN
497         !-alb_leaf
498         alb_leaf(:) = zero
499      ENDIF
500
501      IF (ok_stomate) THEN
502         !- pheno_gdd_crit
503         pheno_gdd_crit(:,:) = zero 
504         !
505         !- senescence_temp
506         senescence_temp(:,:) = zero
507         !
508         !- maint_resp_slope
509         maint_resp_slope(:,:) = zero
510         !
511         !-coeff_maint_zero
512         coeff_maint_zero(:,:) = zero
513      ENDIF
514
515      ! 7. End message
516      IF(long_print) THEN
517         WRITE(numout,*) 'pft_parameters_done'
518      ENDIF
519
520   ELSE
521
522      l_first_define_pft = .FALSE.
523       
524      RETURN
525
526   ENDIF
527
528 END SUBROUTINE pft_parameters_main
529 !
530 !=
531 !
532 SUBROUTINE pft_parameters_init(ok_sechiba,ok_stomate)
533 
534   IMPLICIT NONE
535   
536   ! 0.1 input
537   
538   ! Is SECHIBA active ?
539   LOGICAL, INTENT(in) :: ok_sechiba
540   ! Is STOMATE active ?
541   LOGICAL, INTENT(in) :: ok_stomate
542
543   ! 0.4 local
544
545   INTEGER(i_std) :: j,k
546
547   !---------------------------------------------------------------
548
549   !
550   ! 1. Correspondance between the PFTs values and thes MTCs values
551   !
552 
553
554   ! 1.1 For parameters used anytime
555   
556   DO j= 1, nvm
557      !-
558      PFT_name(j) = MTC_name(pft_to_mtc(j))
559      !-
560      ! Vegetation structure
561      !-
562      !
563      ! 1 .Sechiba
564      !
565      veget_ori_fixed_test_1(j) = veget_ori_fixed_mtc(pft_to_mtc(j))
566      llaimax(j) = llaimax_mtc(pft_to_mtc(j))
567      llaimin(j) = llaimin_mtc(pft_to_mtc(j))
568      height_presc(j) = height_presc_mtc(pft_to_mtc(j))
569      type_of_lai(j) = type_of_lai_mtc(pft_to_mtc(j))
570      is_tree(j) = is_tree_mtc(pft_to_mtc(j))
571      natural(j) = natural_mtc(pft_to_mtc(j))
572      !
573      ! 2 .Stomate
574      !
575      !>> DS new for merge in the trunk   ! 15/06/2011
576      ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
577      is_deciduous(j) = is_deciduous_mtc(pft_to_mtc(j))
578      is_evergreen(j) = is_evergreen_mtc(pft_to_mtc(j))
579      is_c3(j) = is_c3(pft_to_mtc(j))
580      !-
581      ! Water - sechiba
582      !-
583      humcste(j) = humcste_mtc(pft_to_mtc(j))
584      !-
585      !   Soil - vegetation
586      !-
587      pref_soil_veg_sand(j) = pref_soil_veg_sand_mtc(pft_to_mtc(j))
588      pref_soil_veg_loan(j) = pref_soil_veg_loan_mtc(pft_to_mtc(j))
589      pref_soil_veg_clay(j) = pref_soil_veg_clay_mtc(pft_to_mtc(j))
590      !-
591      ! Photosynthesis
592      !-
593      is_c4(j) = is_c4_mtc(pft_to_mtc(j))
594      gsslope(j) = gsslope_mtc(pft_to_mtc(j))
595      gsoffset(j) = gsoffset_mtc(pft_to_mtc(j))
596      vcmax_fix(j) = vcmax_fix_mtc(pft_to_mtc(j))
597      vjmax_fix(j) = vjmax_fix_mtc(pft_to_mtc(j))
598      co2_tmin_fix(j) = co2_tmin_fix_mtc(pft_to_mtc(j))
599      co2_topt_fix(j) = co2_topt_fix_mtc(pft_to_mtc(j))
600      co2_tmax_fix(j) = co2_tmax_fix_mtc(pft_to_mtc(j))
601      ext_coeff(j) = ext_coeff_mtc(pft_to_mtc(j))
602      !-
603   ENDDO
604
605   ! 1.2 For sechiba parameters
606
607   IF (ok_sechiba) THEN
608      !-
609      DO j =1 ,nvm
610         !-
611         ! Vegetation structure - sechiba
612         !-
613         rveg_pft(j) = rveg_mtc(pft_to_mtc(j))
614         !-
615         ! Evapotranspiration -  sechiba
616         !-
617         rstruct_const(j) = rstruct_const_mtc(pft_to_mtc(j))
618         kzero(j) = kzero_mtc(pft_to_mtc(j))
619         !-
620         ! Water - sechiba
621         !-
622         wmax_veg(j) = wmax_veg_mtc(pft_to_mtc(j))
623         throughfall_by_pft(j) = throughfall_by_mtc(pft_to_mtc(j))
624         !-
625         ! Albedo - sechiba
626         !-
627         snowa_ini(j) = snowa_ini_mtc(pft_to_mtc(j))
628         snowa_dec(j) = snowa_dec_mtc(pft_to_mtc(j)) 
629         alb_leaf_vis(j) = alb_leaf_vis_mtc(pft_to_mtc(j)) 
630         alb_leaf_nir(j) = alb_leaf_nir_mtc(pft_to_mtc(j))
631      ENDDO
632      !-
633   ENDIF
634
635   ! 1.3 For stomate parameters
636
637   IF (ok_stomate) THEN
638      !-
639      DO j = 1,nvm
640         !-
641         ! Vegetation structure - stomate
642         !-
643         leaf_tab(j) = leaf_tab_mtc(pft_to_mtc(j))
644         sla(j) = sla_mtc(pft_to_mtc(j))
645         !-
646         ! Photosynthesis
647         !-
648         vcmax_opt(j) = vcmax_opt_mtc(pft_to_mtc(j))
649         vjmax_opt(j) = vjmax_opt_mtc(pft_to_mtc(j)) 
650         tphoto_min_a(j) = tphoto_min_a_mtc(pft_to_mtc(j)) 
651         tphoto_min_b(j) = tphoto_min_b_mtc(pft_to_mtc(j))
652         tphoto_min_c(j) = tphoto_min_c_mtc(pft_to_mtc(j))
653         tphoto_opt_a(j) = tphoto_opt_a_mtc(pft_to_mtc(j))
654         tphoto_opt_b(j) = tphoto_opt_b_mtc(pft_to_mtc(j))
655         tphoto_opt_c(j) = tphoto_opt_c_mtc(pft_to_mtc(j))
656         tphoto_max_a(j) = tphoto_max_a_mtc(pft_to_mtc(j))
657         tphoto_max_b(j) = tphoto_max_b_mtc(pft_to_mtc(j))
658         tphoto_max_c(j) = tphoto_max_c_mtc(pft_to_mtc(j))
659         !-
660         ! Respiration - stomate
661         !-
662         maint_resp_slope_c(j) = maint_resp_slope_c_mtc(pft_to_mtc(j))               
663         maint_resp_slope_b(j) = maint_resp_slope_b_mtc(pft_to_mtc(j))
664         maint_resp_slope_a(j) = maint_resp_slope_a_mtc(pft_to_mtc(j))
665         cm_zero_leaf(j)= cm_zero_leaf_mtc(pft_to_mtc(j))
666         cm_zero_sapabove(j) = cm_zero_sapabove_mtc(pft_to_mtc(j))
667         cm_zero_sapbelow(j) = cm_zero_sapbelow_mtc(pft_to_mtc(j)) 
668         cm_zero_heartabove(j) = cm_zero_heartabove_mtc(pft_to_mtc(j)) 
669         cm_zero_heartbelow(j) = cm_zero_heartbelow_mtc(pft_to_mtc(j))
670         cm_zero_root(j) = cm_zero_root_mtc(pft_to_mtc(j))
671         cm_zero_fruit(j) = cm_zero_fruit_mtc(pft_to_mtc(j))
672         cm_zero_carbres(j) = cm_zero_carbres_mtc(pft_to_mtc(j))
673         !-
674         ! Fire - stomate
675         !-
676         flam(j) = flam_mtc(pft_to_mtc(j))
677         resist(j) = resist_mtc(pft_to_mtc(j))
678         !-
679         ! Flux - LUC
680         !-
681         coeff_lcchange_1(j) = coeff_lcchange_1_mtc(pft_to_mtc(j))
682         coeff_lcchange_10(j) = coeff_lcchange_10_mtc(pft_to_mtc(j))
683         coeff_lcchange_100(j) = coeff_lcchange_100_mtc(pft_to_mtc(j))
684         !-
685         ! Phenology
686         !-
687         !
688         ! 1 .Stomate
689         !
690         lai_max(j) = lai_max_mtc(pft_to_mtc(j))
691         pheno_model(j) = pheno_model_mtc(pft_to_mtc(j))
692         pheno_type(j) = pheno_type_mtc(pft_to_mtc(j))
693         !
694         ! 2. Leaf Onset
695         !
696         pheno_gdd_crit_c(j) = pheno_gdd_crit_c_mtc(pft_to_mtc(j))
697         pheno_gdd_crit_b(j) = pheno_gdd_crit_b_mtc(pft_to_mtc(j))         
698         pheno_gdd_crit_a(j) = pheno_gdd_crit_a_mtc(pft_to_mtc(j))
699         ngd_crit(j) =  ngd_crit_mtc(pft_to_mtc(j))
700         ncdgdd_temp(j) = ncdgdd_temp_mtc(pft_to_mtc(j)) 
701         hum_frac(j) = hum_frac_mtc(pft_to_mtc(j))
702         lowgpp_time(j) = lowgpp_time_mtc(pft_to_mtc(j))
703         hum_min_time(j) = hum_min_time_mtc(pft_to_mtc(j))
704         tau_sap(j) = tau_sap_mtc(pft_to_mtc(j))
705         tau_fruit(j) = tau_fruit_mtc(pft_to_mtc(j))
706         ecureuil(j) = ecureuil_mtc(pft_to_mtc(j))
707         alloc_min(j) = alloc_min_mtc(pft_to_mtc(j))
708         alloc_max(j) = alloc_max_mtc(pft_to_mtc(j))
709         demi_alloc(j) = demi_alloc_mtc(pft_to_mtc(j))
710         !>> DS new for merge in the trunk   ! 15/06/2011
711         leaflife_tab(j) = leaflife_mtc(pft_to_mtc(j))
712         !
713         ! 3. Senescence
714         !
715         leaffall(j) = leaffall_mtc(pft_to_mtc(j))
716         leafagecrit(j) = leafagecrit_mtc(pft_to_mtc(j))
717         senescence_type(j) = senescence_type_mtc(pft_to_mtc(j)) 
718         senescence_hum(j) = senescence_hum_mtc(pft_to_mtc(j)) 
719         nosenescence_hum(j) = nosenescence_hum_mtc(pft_to_mtc(j)) 
720         max_turnover_time(j) = max_turnover_time_mtc(pft_to_mtc(j))
721         min_turnover_time(j) = min_turnover_time_mtc(pft_to_mtc(j))
722         min_leaf_age_for_senescence(j) = min_leaf_age_for_senescence_mtc(pft_to_mtc(j))
723         senescence_temp_c(j) = senescence_temp_c_mtc(pft_to_mtc(j))
724         senescence_temp_b(j) = senescence_temp_b_mtc(pft_to_mtc(j))
725         senescence_temp_a(j) = senescence_temp_a_mtc(pft_to_mtc(j))
726         !-
727         ! DGVM
728         residence_time(j) = residence_time_mtc(pft_to_mtc(j))
729         tmin_crit(j) = tmin_crit_mtc(pft_to_mtc(j))
730         tcm_crit(j) = tcm_crit_mtc(pft_to_mtc(j))
731      ENDDO
732      !-
733   ENDIF
734
735 END SUBROUTINE pft_parameters_init
736 !
737 !=
738 !
739 SUBROUTINE pft_parameters_alloc(ok_sechiba,ok_stomate)
740
741   IMPLICIT NONE
742
743   ! 0.1 input
744   
745   ! Is SECHIBA active ?
746   LOGICAL, INTENT(in) :: ok_sechiba
747   ! Is STOMATE active ?
748   LOGICAL, INTENT(in) :: ok_stomate
749
750   ! 0.4 local
751   LOGICAL ::  l_error
752   INTEGER :: ier
753
754   !---------------------------------------------
755
756   !
757   ! 1. Parameters used anytime
758   !
759   l_error = .FALSE.
760   !-
761   ALLOCATE(pft_to_mtc(nvm),stat=ier)
762   l_error = l_error .OR. (ier .NE. 0)
763   ALLOCATE(PFT_name(nvm),stat=ier)
764   l_error = l_error .OR. (ier .NE. 0)
765   ALLOCATE(height_presc(nvm),stat=ier)
766   l_error = l_error .OR. (ier .NE. 0)
767   ALLOCATE(is_tree(nvm),stat=ier)
768   l_error = l_error .OR. (ier .NE. 0) 
769   ALLOCATE(natural(nvm),stat=ier)
770   l_error = l_error .OR. (ier .NE. 0)
771   ALLOCATE(is_c4(nvm),stat=ier)
772   l_error = l_error .OR. (ier .NE. 0)
773   ALLOCATE(gsslope(nvm),stat=ier)
774   l_error = l_error .OR. (ier .NE. 0)
775   ALLOCATE(gsoffset(nvm),stat=ier)
776   l_error = l_error .OR. (ier .NE. 0)
777   ALLOCATE(humcste(nvm),stat=ier)
778   l_error = l_error .OR. (ier .NE. 0)
779   ALLOCATE(ext_coeff(nvm),stat=ier)
780   l_error = l_error .OR. (ier .NE. 0)
781   !-
782   ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier)
783   l_error = l_error .OR. (ier .NE. 0)
784   ALLOCATE(llaimax(nvm),stat=ier)
785   l_error = l_error .OR. (ier .NE. 0)
786   ALLOCATE(llaimin(nvm),stat=ier)
787   l_error = l_error .OR. (ier .NE. 0)
788   ALLOCATE(type_of_lai(nvm),stat=ier)
789   l_error = l_error .OR. (ier .NE. 0)
790   ALLOCATE(vcmax_fix(nvm),stat=ier)
791   l_error = l_error .OR. (ier .NE. 0)
792   ALLOCATE(vjmax_fix(nvm),stat=ier)
793   l_error = l_error .OR. (ier .NE. 0)
794   ALLOCATE(co2_tmin_fix(nvm),stat=ier)
795   l_error = l_error .OR. (ier .NE. 0)
796   ALLOCATE(co2_topt_fix(nvm),stat=ier)
797   l_error = l_error .OR. (ier .NE. 0)
798   ALLOCATE(co2_tmax_fix(nvm),stat=ier)
799   l_error = l_error .OR. (ier .NE. 0)
800   !-
801   ALLOCATE(pref_soil_veg_sand(nvm),stat=ier)
802   l_error = l_error .OR. (ier .NE. 0)
803   ALLOCATE(pref_soil_veg_loan(nvm),stat=ier)
804   l_error = l_error .OR. (ier .NE. 0)
805   ALLOCATE(pref_soil_veg_clay(nvm),stat=ier)
806   l_error = l_error .OR. (ier .NE. 0)
807   ALLOCATE(pref_soil_veg(nvm,nstm),stat=ier)
808   l_error = l_error .OR. (ier .NE. 0)
809
810   !-
811   !>> DS new for merge in the trunk   ! 15/06/2011
812   ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
813   ALLOCATE(is_deciduous(nvm),stat=ier)   
814   l_error = l_error .OR. (ier .NE. 0)
815   ALLOCATE(is_evergreen(nvm),stat=ier) 
816   l_error = l_error .OR. (ier .NE. 0)
817   ALLOCATE(is_c3(nvm),stat=ier) 
818   l_error = l_error .OR. (ier .NE. 0)
819   ! >> END
820   
821   IF(l_error) THEN
822      STOP 'pft _alloc : error in memory allocation of pft parameters'
823   ENDIF
824   
825   !
826   ! 2. Parameters used if ok_sechiba only
827   !
828   IF (ok_sechiba) THEN
829      l_error=.FALSE.
830      !-
831      ALLOCATE(rstruct_const(nvm),stat=ier)
832      l_error = l_error .OR. (ier .NE. 0)
833      ALLOCATE(kzero(nvm),stat=ier)
834      l_error = l_error .OR. (ier .NE. 0)
835      ALLOCATE (rveg_pft(nvm),stat=ier)
836      l_error = l_error .OR. (ier .NE. 0) 
837      ALLOCATE(wmax_veg(nvm),stat=ier)
838      l_error = l_error .OR. (ier .NE. 0)
839      ALLOCATE(throughfall_by_pft(nvm),stat=ier)
840      l_error = l_error .OR. (ier .NE. 0)
841      !-
842      ALLOCATE(snowa_ini(nvm),stat=ier)
843      l_error = l_error .OR. (ier .NE. 0) 
844      ALLOCATE(snowa_dec(nvm),stat=ier)
845      l_error = l_error .OR. (ier .NE. 0)
846      ALLOCATE(alb_leaf_vis(nvm),stat=ier)
847      l_error = l_error .OR. (ier .NE. 0)
848      ALLOCATE(alb_leaf_nir(nvm),stat=ier)
849      l_error = l_error .OR. (ier .NE. 0)
850      ALLOCATE(alb_leaf(2*nvm),stat=ier)
851      l_error = l_error .OR. (ier .NE. 0)
852   ENDIF
853
854   IF(l_error) THEN
855      WRITE(numout,*) 'Error in memory allocation for sechiba pft parameters'
856   ENDIF
857
858   !
859   ! 3. Parameters used if ok_stomate only
860   !
861   IF (ok_stomate) THEN
862      l_error=.FALSE.
863      !-
864      ALLOCATE(leaf_tab(nvm),stat=ier)
865      l_error = l_error .OR. (ier .NE. 0)
866      ALLOCATE(sla(nvm),stat=ier)
867      l_error = l_error .OR. (ier .NE. 0)   
868      ALLOCATE(vcmax_opt(nvm),stat=ier)
869      l_error = l_error .OR. (ier .NE. 0) 
870      ALLOCATE(vjmax_opt(nvm),stat=ier)
871      l_error = l_error .OR. (ier .NE. 0)
872      !-
873      ALLOCATE(tphoto_min_a(nvm),stat=ier)
874      l_error = l_error .OR. (ier .NE. 0) 
875      ALLOCATE(tphoto_min_b(nvm),stat=ier)
876      l_error = l_error .OR. (ier .NE. 0) 
877      ALLOCATE(tphoto_min_c(nvm),stat=ier)
878      l_error = l_error .OR. (ier .NE. 0) 
879      ALLOCATE(tphoto_opt_a(nvm),stat=ier)
880      l_error = l_error .OR. (ier .NE. 0) 
881      ALLOCATE(tphoto_opt_b(nvm),stat=ier)
882      l_error = l_error .OR. (ier .NE. 0) 
883      ALLOCATE(tphoto_opt_c(nvm),stat=ier)
884      l_error = l_error .OR. (ier .NE. 0) 
885      ALLOCATE(tphoto_max_a(nvm),stat=ier)
886      l_error = l_error .OR. (ier .NE. 0) 
887      ALLOCATE(tphoto_max_b(nvm),stat=ier)
888      l_error = l_error .OR. (ier .NE. 0) 
889      ALLOCATE(tphoto_max_c(nvm),stat=ier)
890      l_error = l_error .OR. (ier .NE. 0) 
891      !-
892      ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier)
893      l_error = l_error .OR. (ier .NE. 0)
894      ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier)
895      l_error = l_error .OR. (ier .NE. 0)
896      ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier)
897      l_error = l_error .OR. (ier .NE. 0)
898      ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier)
899      l_error = l_error .OR. (ier .NE. 0)
900      ALLOCATE(ngd_crit(nvm),stat=ier)
901      l_error = l_error .OR. (ier .NE. 0)
902      ALLOCATE(ncdgdd_temp(nvm),stat=ier)
903      l_error = l_error .OR. (ier .NE. 0)
904      ALLOCATE(hum_frac(nvm),stat=ier)
905      l_error = l_error .OR. (ier .NE. 0)
906      ALLOCATE(lowgpp_time(nvm),stat=ier)
907      l_error = l_error .OR. (ier .NE. 0)
908      ALLOCATE(hum_min_time(nvm),stat=ier)
909      l_error = l_error .OR. (ier .NE. 0)
910      ALLOCATE(tau_sap(nvm),stat=ier)
911      l_error = l_error .OR. (ier .NE. 0)
912      ALLOCATE(tau_fruit(nvm),stat=ier)
913      l_error = l_error .OR. (ier .NE. 0)
914      ALLOCATE(ecureuil(nvm),stat=ier)
915      l_error = l_error .OR. (ier .NE. 0)
916      ALLOCATE(alloc_min(nvm),stat=ier)
917      l_error = l_error .OR. (ier .NE. 0)
918      ALLOCATE(alloc_max(nvm),stat=ier)
919      l_error = l_error .OR. (ier .NE. 0)
920      ALLOCATE(demi_alloc(nvm),stat=ier)
921      l_error = l_error .OR. (ier .NE. 0)
922      !-
923      ALLOCATE(maint_resp_slope(nvm,3),stat=ier)
924      l_error = l_error .OR. (ier .NE. 0)
925      ALLOCATE(maint_resp_slope_c(nvm),stat=ier)
926      l_error = l_error .OR. (ier .NE. 0)
927      ALLOCATE(maint_resp_slope_b(nvm),stat=ier)
928      l_error = l_error .OR. (ier .NE. 0)
929      ALLOCATE(maint_resp_slope_a(nvm),stat=ier)
930      l_error = l_error .OR. (ier .NE. 0)
931      ALLOCATE(coeff_maint_zero(nvm,nparts),stat=ier)
932      l_error = l_error .OR. (ier .NE. 0)
933      ALLOCATE(cm_zero_leaf(nvm),stat=ier)
934      l_error = l_error .OR. (ier .NE. 0)
935      ALLOCATE(cm_zero_sapabove(nvm),stat=ier)
936      l_error = l_error .OR. (ier .NE. 0)
937      ALLOCATE(cm_zero_sapbelow(nvm),stat=ier)
938      l_error = l_error .OR. (ier .NE. 0)
939      ALLOCATE(cm_zero_heartabove(nvm),stat=ier)
940      l_error = l_error .OR. (ier .NE. 0)
941      ALLOCATE(cm_zero_heartbelow(nvm),stat=ier)
942      l_error = l_error .OR. (ier .NE. 0)
943      ALLOCATE(cm_zero_root(nvm),stat=ier)
944      l_error = l_error .OR. (ier .NE. 0)
945      ALLOCATE(cm_zero_fruit(nvm),stat=ier)
946      l_error = l_error .OR. (ier .NE. 0)
947      ALLOCATE(cm_zero_carbres(nvm),stat=ier)
948      l_error = l_error .OR. (ier .NE. 0)
949      !-
950      ALLOCATE(flam(nvm),stat=ier)
951      l_error = l_error .OR. (ier .NE. 0) 
952      ALLOCATE(resist(nvm),stat=ier)
953      l_error = l_error .OR. (ier .NE. 0) 
954      !-
955      ALLOCATE(coeff_lcchange_1(nvm),stat=ier)
956      l_error = l_error .OR. (ier .NE. 0)
957      ALLOCATE(coeff_lcchange_10(nvm),stat=ier)
958      l_error = l_error .OR. (ier .NE. 0)
959      ALLOCATE(coeff_lcchange_100(nvm),stat=ier)
960      l_error = l_error .OR. (ier .NE. 0)
961      !-
962      ALLOCATE(lai_max(nvm),stat=ier)
963      l_error = l_error .OR. (ier .NE. 0)
964      ALLOCATE(pheno_model(nvm),stat=ier)
965      l_error = l_error .OR. (ier .NE. 0) 
966      ALLOCATE(pheno_type(nvm),stat=ier)
967      l_error = l_error .OR. (ier .NE. 0) 
968      !-
969      ALLOCATE(leaffall(nvm),stat=ier)
970      l_error = l_error .OR. (ier .NE. 0)
971      ALLOCATE(leafagecrit(nvm),stat=ier)
972      l_error = l_error .OR. (ier .NE. 0)
973      ALLOCATE(senescence_type(nvm),stat=ier)
974      l_error = l_error .OR. (ier .NE. 0)
975      ALLOCATE(senescence_hum(nvm),stat=ier)
976      l_error = l_error .OR. (ier .NE. 0)
977      ALLOCATE(nosenescence_hum(nvm),stat=ier)
978      l_error = l_error .OR. (ier .NE. 0)
979      ALLOCATE(max_turnover_time(nvm),stat=ier)
980      l_error = l_error .OR. (ier .NE. 0)
981      ALLOCATE(min_turnover_time(nvm),stat=ier)
982      l_error = l_error .OR. (ier .NE. 0)
983      ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier)
984      l_error = l_error .OR. (ier .NE. 0)
985      ALLOCATE(senescence_temp_c(nvm),stat=ier)
986      l_error = l_error .OR. (ier .NE. 0)
987      ALLOCATE(senescence_temp_b(nvm),stat=ier)
988      l_error = l_error .OR. (ier .NE. 0)
989      ALLOCATE(senescence_temp_a(nvm),stat=ier)
990      l_error = l_error .OR. (ier .NE. 0)
991      ALLOCATE(senescence_temp(nvm,3),stat=ier)
992      l_error = l_error .OR. (ier .NE. 0)
993      !-
994      ALLOCATE(residence_time(nvm),stat=ier)
995      l_error = l_error .OR. (ier .NE. 0)
996      ALLOCATE(tmin_crit(nvm),stat=ier)
997      l_error = l_error .OR. (ier .NE. 0)
998      ALLOCATE(tcm_crit(nvm),stat=ier)
999      l_error = l_error .OR. (ier .NE. 0)
1000      !-
1001      ALLOCATE(lai_initmin(nvm),stat=ier)
1002      l_error = l_error .OR. (ier .NE. 0)
1003      ALLOCATE(tree(nvm),stat=ier)
1004      l_error = l_error .OR. (ier .NE. 0)
1005      ALLOCATE(bm_sapl(nvm,nparts),stat=ier)
1006      l_error = l_error .OR. (ier .NE. 0)
1007      ALLOCATE(migrate(nvm),stat=ier)
1008      l_error = l_error .OR. (ier .NE. 0)
1009      ALLOCATE(maxdia(nvm),stat=ier)
1010      l_error = l_error .OR. (ier .NE. 0)
1011      ALLOCATE(cn_sapl(nvm),stat=ier)
1012      l_error = l_error .OR. (ier .NE. 0)
1013      ALLOCATE(leaf_timecst(nvm),stat=ier)
1014      l_error = l_error .OR. (ier .NE. 0) 
1015      ALLOCATE(leaflife_tab(nvm),stat=ier)   
1016      l_error = l_error .OR. (ier .NE. 0)
1017   ENDIF
1018   !
1019   IF (l_error) THEN
1020       STOP 'pft _alloc : error in memory allocation of stomate pft parameters'
1021   ENDIF
1022
1023 END SUBROUTINE pft_parameters_alloc
1024!
1025!=
1026!
1027 SUBROUTINE getin_pft_parameters
1028   
1029   IMPLICIT NONE
1030 
1031   LOGICAL, SAVE ::  first_call = .TRUE.
1032
1033   IF (first_call) THEN
1034
1035     !-
1036     ! Vegetation structure
1037     !-
1038     !
1039     !Config  Key  = SECHIBA_LAI
1040     !Config  Desc = laimax for maximum lai see also type of lai interpolation
1041     !Config  if  =  IMPOSE_VEG
1042     !Config  Def  = 0., 8., 8., 4., 4.5, 4.5, 4., 4.5, 4., 2., 2., 2., 2.
1043     !Config  Help = Values of lai used for interpolation of the lai map
1044     !Config  Units =
1045     CALL getin_p('SECHIBA_LAI',llaimax)
1046     !
1047     !Config  Key  = LLAIMIN
1048     !Config  Desc = laimin for minimum lai see also type of lai interpolation
1049     !Config  if  = OK_SECHIBA
1050     !Config  Def  = 0., 8., 0., 4., 4.5, 0., 4., 0., 0., 0., 0., 0., 0.
1051     !Config  Help =
1052     !Config  Units =
1053     CALL getin_p('LLAIMIN',llaimin)
1054     !
1055     !Config  Key  = SLOWPROC_HEIGHT
1056     !Config  Desc = prescribed height of vegetation : one for each vegetation type
1057     !Config  if  = OK_SECHIBA
1058     !Config  Def  = 0.,30.,30.,20.,20.,20.,15.,15.,15.,.5,.6,1.,1.
1059     !Config  Help =
1060     !Config  Units = Meters [m] ?
1061     CALL getin_p('SLOWPROC_HEIGHT', height_presc)
1062     !
1063     !Config  Key  = TYPE_OF_LAI
1064     !Config  Desc = Type of behaviour of the LAI evolution algorithm for each vegetation type : mean or interp
1065     !Config  if  = OK_SECHIBA
1066     !Config  Def  = inter','inter','inter','inter','inter','inter','inter','inter','inter','inter','inter','inter','inter'
1067     !Config  Help =
1068     !Config  Units = NONE
1069     CALL getin_p('TYPE_OF_LAI',type_of_lai)
1070     !
1071     !Config  Key  = IS_TREE
1072     !Config  Desc = Is the vegetation type a tree ?
1073     !Config  if  = OK_SECHIBA
1074     !Config  Def  = n, y, y, y, y, y, y, y, y, n, n, n, n
1075     !Config  Help =
1076     !Config  Units = NONE
1077     CALL getin_p('IS_TREE',is_tree)
1078     !
1079     !Config  Key  = NATURAL
1080     !Config  Desc = natural?
1081     !Config  if  = OK_SECHIBA
1082     !Config  Def  = y, y, y, y, y, y, y, y, y, y, y, n, n
1083     !Config  Help =
1084     !Config  Units = NONE
1085     CALL getin_p('NATURAL',natural)
1086
1087     !>> DS new for merge in the trunk   ! 15/06/2011
1088     ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
1089     !
1090     !Config  Key  = IS_DECIDUOUS
1091     !Config  Desc = is PFT deciduous ?
1092     !Config  if  = OK_SECHIBA
1093     !Config  Def  = n, n, y, n, n, y, n, y, y, n, n, n, n
1094     !Config  Help =
1095     !Config  Units = NONE
1096     CALL getin_p('IS_DECIDUOUS',is_deciduous)
1097     !
1098     !Config  Key  = IS_EVERGREEN
1099     !Config  Desc = is PFT evergreen ?
1100     !Config  if  = OK_SECHIBA
1101     !Config  Def  = n, y, n, y, y, n, y, n, n, n, n, n, n
1102     !Config  Help =
1103     !Config  Units = NONE
1104     CALL getin_p('IS_EVERGREEN',is_evergreen)
1105     !
1106     !Config  Key  = IS_C3
1107     !Config  Desc = is PFT C3 ?
1108     !Config  if  = OK_SECHIBA
1109     !Config  Def  = n, n, n, n, n, n, n, n, n, n, y, n, y, n
1110     !Config  Help =
1111     !Config  Units = NONE   
1112     CALL getin_p('IS_C3',is_c3)   
1113
1114     !-
1115     ! Photosynthesis
1116     !-
1117     !
1118     !Config  Key  = IS_C4
1119     !Config  Desc = flag for C4 vegetation types
1120     !Config  if  = OK_SECHIBA
1121     !Config  Def  = n, n, n, n, n, n, n, n, n, n, n, y, n, y
1122     !Config  Help =
1123     !Config  Units = NONE
1124     CALL getin_p('IS_C4',is_c4)
1125     !
1126     !Config  Key  = GSSLOPE
1127     !Config  Desc = Slope of the gs/A relation (Ball & al.
1128     !Config  if  = OK_SECHIBA AND OK_CO2
1129     !Config  Def  = 0., 9., 9., 9., 9., 9., 9., 9., 9., 9., 3., 9., 3.
1130     !Config  Help =
1131     !Config  Units =
1132     CALL getin_p('GSSLOPE',gsslope)
1133     !
1134     !Config  Key  = GSOFFSET
1135     !Config  Desc = intercept of the gs/A relation (Ball & al.)
1136     !Config  if  = OK_SECHIBA
1137     !Config  Def  = 0.0,  0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.01, 0.03, 0.01, 0.03
1138     !Config  Help =
1139     !Config  Units =
1140     CALL getin_p('GSOFFSET',gsoffset)
1141     !
1142     !Config  Key  = VCMAX_FIX
1143     !Config  Desc = values used for vcmax when STOMATE is not activated
1144     !Config  if  =  OK_SECHIBA
1145     !Config  Def  =  0., 40., 50., 30., 35., 40.,30., 40., 35., 60., 60., 70., 70.
1146     !Config  Help =
1147     !Config  Units =
1148     CALL getin_p('VCMAX_FIX',vcmax_fix)
1149     !
1150     !Config  Key  = VJMAX_FIX
1151     !Config  Desc = values used for vjmax when STOMATE is not activated
1152     !Config  if  = OK_SECHIBA
1153     !Config  Def  =  0., 80., 100., 60., 70., 80.,  60., 80., 70., 120., 120., 140., 140.
1154     !Config  Help =
1155     !Config  Units =
1156     CALL getin_p('VJMAX_FIX',vjmax_fix)
1157     !
1158     !Config  Key  = CO2_TMIN_FIX
1159     !Config  Desc = values used for photosynthesis tmin when STOMATE is not activated
1160     !Config  if  = OK_SECHIBA
1161     !Config  Def  = 0.,  2.,  2., -4., -3., -2., -4., -4., -4., -5.,  6., -5.,  6.
1162     !Config  Help =
1163     !Config  Units =
1164     CALL getin_p('CO2_TMIN_FIX',co2_tmin_fix)
1165     !
1166     !Config  Key  = CO2_TOPT_FIX
1167     !Config  Desc = values used for photosynthesis topt when STOMATE is not activated
1168     !Config  if  = OK_SECHIBA
1169     !Config  Def  =  0., 27.5, 27.5, 17.5, 25., 20.,17.5, 17.5, 17.5, 20.,  32.5, 20.,  32.5
1170     !Config  Help =
1171     !Config  Units =
1172     CALL getin_p('CO2_TOPT_FIX',co2_topt_fix)
1173     !
1174     !Config  Key  = CO2_TMAX_FIX
1175     !Config  Desc = values used for photosynthesis tmax when STOMATE is not activated
1176     !Config  if  = OK_SECHIBA
1177     !Config  Def  = 0., 55., 55., 38., 48., 38.,38., 38., 38., 45., 55., 45., 55.
1178     !Config  Help =
1179     !Config  Units =
1180     CALL getin_p('CO2_TMAX_FIX',co2_tmax_fix)
1181     !
1182     !Config  Key  = EXT_COEFF
1183     !Config  Desc = extinction coefficient of the Monsi&Seaki relationship (1953)
1184     !Config  if  = OK_SECHIBA OR OK_STOMATE
1185     !Config  Def  = .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5
1186     !Config  Help =
1187     !Config  Units =
1188     CALL getin_p('EXT_COEFF',ext_coeff)
1189
1190     !-
1191     ! Water-hydrology - sechiba
1192     !-
1193     !
1194     !Config  Key  = HYDROL_HUMCSTE
1195     !Config  Desc = Root profile
1196     !Config  Def  = 5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4.
1197     !Config  if  = OK_SECHIBA
1198     !Config  Help = Default values were defined for 2 meters soil depth.
1199     !Config        For 4 meters soil depth, you may use those ones :
1200     !Config        5., .4, .4, 1., .8, .8, 1., 1., .8, 4., 1., 4., 1.
1201     !Config  Units =
1202     CALL getin_p('HYDROL_HUMCSTE', humcste)
1203
1204     !-
1205     ! Soil - vegetation
1206     !-
1207     !
1208     !Config  Key  = PREF_SOIL_VEG_SAND
1209     !Config  Desc = Table which contains the correlation between the soil types and vegetation type
1210     !Config  if  = OK_SECHIBA
1211     !Config  Def  = 1, 3, 3, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2
1212     !Config  Help = first layer of the soil
1213     !Config  Units =
1214     CALL getin_p('PREF_SOIL_VEG_SAND',pref_soil_veg_sand)
1215     !
1216     !Config  Key  = PREF_SOIL_VEG_LOAN
1217     !Config  Desc = Table which contains the correlation between the soil types and vegetation type
1218     !Config  if  = OK_SECHIBA
1219     !Config  Def  = 2, 2, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3, 3
1220     !Config  Help = second layer of the soil
1221     !Config  Units =
1222     CALL getin_p('PREF_SOIL_VEG_LOAN',pref_soil_veg_loan) 
1223      !
1224     !Config  Key  = PREF_SOIL_VEG_CLAY
1225     !Config  Desc = Table which contains the correlation between the soil types and vegetation type
1226     !Config  if  = OK_SECHIBA
1227     !Config  Def  = 3, 1, 1, 1, 1, 1 ,1 ,1 ,1 ,1 ,1 ,1, 1
1228     !Config  Help = third layer of the soil
1229     !Config  Units =       
1230     CALL getin_p('PREF_SOIL_VEG_CLAY',pref_soil_veg_clay)
1231
1232     first_call = .FALSE.
1233
1234   ENDIF
1235
1236 END SUBROUTINE getin_pft_parameters
1237!
1238!=
1239!
1240 SUBROUTINE getin_sechiba_pft_parameters
1241
1242   IMPLICIT NONE
1243 
1244   LOGICAL, SAVE ::  first_call = .TRUE.
1245
1246  IF (first_call) THEN
1247     !-
1248     ! Evapotranspiration -  sechiba
1249     !-
1250     !
1251     !Config  Key  = RSTRUCT_CONST
1252     !Config  Desc = Structural resistance : one for each vegetation type
1253     !Config  if  = OK_SECHIBA
1254     !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
1255     !Config  Help =
1256     !Config  Units =
1257     CALL getin_p('RSTRUCT_CONST',rstruct_const)
1258     !
1259     !Config  Key  = KZERO
1260     !Config  Desc =  A vegetation dependent constant used in the calculation of the surface resistance.
1261     !Config  if  = OK_SECHIBA
1262     !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
1263     !Config  Help =
1264     !Config  Units =
1265     CALL getin_p('KZERO',kzero)
1266     !
1267     ! Ajouts Nathalie - le 28 Mars 2006 - sur conseils Fred Hourdin
1268     !
1269     !Config  Key  = RVEG_PFT
1270     !Config  Desc = Artificial parameter to increase or decrease canopy resistance.
1271     !Config  if  = OK_SECHIBA
1272     !Config  Def  = 1.
1273     !Config  Help = This parameter is set by PFT.
1274     !Config  Units =
1275     CALL getin_p('RVEG_PFT', rveg_pft)   
1276
1277     !-
1278     ! Water-hydrology - sechiba
1279     !-
1280     !
1281     !Config  Key  = WMAX_VEG
1282     !Config  Desc = Maximum field capacity for each of the vegetations (Temporary): max quantity of water
1283     !Config  if  = OK_SECHIBA
1284     !Config  Def  =  150., 150., 150., 150., 150., 150., 150.,150., 150., 150., 150., 150., 150.
1285     !Config  Help =
1286     !Config  Units = [Kg/M3]
1287     CALL getin_p('WMAX_VEG',wmax_veg)
1288     !
1289     !Config  Key  = PERCENT_THROUGHFALL_PFT
1290     !Config  Desc = Percent by PFT of precip that is not intercepted by the canopy
1291     !Config  if  = OK_SECHIBA OR OK_CWRR
1292     !Config  Def  = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30.
1293     !Config  Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
1294     !Config         will get directly to the ground without being intercepted, for each PFT.
1295     !Config  Units = [Kg/M3]
1296     CALL getin_p('PERCENT_TROUGHFALL_PFT',throughfall_by_pft)
1297
1298     !-
1299     ! Albedo - sechiba
1300     !-
1301     !
1302     !Config  Key  = SNOWA_INI
1303     !Config  Desc = Initial snow albedo value for each vegetation type as it will be used in condveg_snow
1304     !Config  if  = OK_SECHIBA
1305     !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
1306     !Config  Help = Values are from the Thesis of S. Chalita (1992)
1307     !Config  Units =
1308     CALL getin_p('SNOWA_INI',snowa_ini)
1309     !
1310     !Config  Key  = SNOWA_DEC
1311     !Config  Desc = Decay rate of snow albedo value for each vegetation type as it will be used in condveg_snow
1312     !Config  if  =  OK_SECHIBA
1313     !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
1314     !Config  Help = Values are from the Thesis of S. Chalita (1992)
1315     !Config  Units =
1316     CALL getin_p('SNOWA_DEC',snowa_dec)
1317     !
1318     !Config  Key  = ALB_LEAF_VIS
1319     !Config  Desc = leaf albedo of vegetation type, visible albedo
1320     !Config  if  = OK_SECHIBA
1321     !Config  Def  = .00, .04, .06, .06, .06,.06, .06, .06, .06, .10, .10, .10, .10
1322     !Config  Help =
1323     !Config  Units =
1324     CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis)
1325     !
1326     !Config  Key  = ALB_LEAF_NIR
1327     !Config  Desc = leaf albedo of vegetation type, near infrared albedo
1328     !Config  if  = OK_SECHIBA
1329     !Config  Def  =.00, .20, .22, .22, .22,.22, .22, .22, .22, .30,.30, .30, .30
1330     !Config  Help =
1331     !Config  Units =
1332     CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir)
1333
1334     first_call = .FALSE.
1335
1336  ENDIF
1337
1338END SUBROUTINE getin_sechiba_pft_parameters
1339!
1340!=
1341!
1342SUBROUTINE getin_stomate_pft_parameters
1343
1344  IMPLICIT NONE
1345
1346  LOGICAL, SAVE ::  first_call = .TRUE.
1347
1348  IF (first_call) THEN
1349
1350     !-
1351     ! Vegetation structure
1352     !-
1353     !
1354     !Config  Key  = LEAF_TAB
1355     !Config  Desc =  leaf type : 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bare ground
1356     !Config  if  = OK_STOMATE
1357     !Config  Def  =  4, 1, 1, 2, 1, 1, 2, 1, 2, 3, 3, 3, 3
1358     !Config  Help =
1359     !Config  Units = NONE
1360     CALL getin_p('LEAF_TAB',leaf_tab)
1361     !
1362     !Config  Key  = SLA
1363     !Config  Desc =  specif leaf area
1364     !Config  if  = OK_STOMATE
1365     !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
1366     !Config  Help =
1367     !Config  Units = [m**2/gC]
1368     CALL getin_p('SLA',sla)
1369
1370     !-
1371     ! Photosynthesis
1372     !-
1373     !
1374     !Config  Key  = VCMAX_OPT
1375     !Config  Desc =  Maximum rate of carboxylation
1376     !Config  if  = OK_STOMATE
1377     !Config  Def  =  undef, 65., 65., 35., 45., 55., 35., 45., 35., 70., 70.,70., 70.
1378     !Config  Help =
1379     !Config  Units = [%]
1380     CALL getin_p('VCMAX_OPT',vcmax_opt)
1381     !
1382     !Config  Key  = VJMAX_OPT
1383     !Config  Desc = Maximum rate of RUbp regeneration
1384     !Config  if  =  OK_STOMATE
1385     !Config  Def  =  undef, 130., 130., 70., 80., 110., 70., 90., 70., 160.,160.,200., 200.
1386     !Config  Help =
1387     !Config  Units = [%]
1388     CALL getin_p('VJMAX_OPT',vjmax_opt)
1389     !
1390     !Config  Key  = TPHOTO_MIN_A
1391     !Config  Desc =  minimum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated
1392     !Config  if  = OK_STOMATE
1393     !Config  Def  =  undef,  0., 0., 0., 0., 0., 0.,  0., 0.,  0.0025, 0., 0., 0.
1394     !Config  Help =
1395     !Config  Units = NONE
1396     CALL getin_p('TPHOTO_MIN_A',tphoto_min_a)
1397     !
1398     !Config  Key  = TPHOTO_MIN_B
1399     !Config  Desc = minimum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated
1400     !Config  if  = OK_STOMATE
1401     !Config  Def  =  undef,  0.,  0., 0., 0., 0., 0., 0., 0., 0.1, 0.,0.,0.
1402     !Config  Help =
1403     !Config  Units = NONE
1404     CALL getin_p('TPHOTO_MIN_B',tphoto_min_b)
1405     !
1406     !Config  Key  = TPHOTO_MIN_C
1407     !Config  Desc = minimum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated
1408     !Config  if  = OK_STOMATE
1409     !Config  Def  =  undef,  2., 2., -4., -3.,-2.,-4., -4.,-4.,-3.25, 13.,-5.,13.
1410     !Config  Help =
1411     !Config  Units = NONE
1412     CALL getin_p('TPHOTO_MIN_C',tphoto_min_c)
1413     !
1414     !Config  Key  = TPHOTO_OPT_A
1415     !Config  Desc = optimum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated
1416     !Config  if  = OK_STOMATE
1417     !Config  Def  =  undef, 0., 0., 0., 0.,0.,0.,0.,0.,0.0025,0.,0.,0.
1418     !Config  Help =
1419     !Config  Units = NONE
1420     CALL getin_p('TPHOTO_OPT_A',tphoto_opt_a)
1421     !
1422     !Config  Key  = TPHOTO_OPT_B
1423     !Config  Desc = optimum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated
1424     !Config  if  = OK_STOMATE
1425     !Config  Def  =  undef, 0.,0.,0.,0.,0.,0., 0.,0.,0.25,0.,0.,0. 
1426     !Config  Help =
1427     !Config  Units = NONE
1428     CALL getin_p('TPHOTO_OPT_B',tphoto_opt_b)
1429     !
1430     !Config  Key  = TPHOTO_OPT_C
1431     !Config  Desc = optimum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated
1432     !Config  if  = OK_STOMATE
1433     !Config  Def  = undef, 37., 37., 25., 32., 26., 25., 25., 25., 27.25, 36., 30., 36.
1434     !Config  Help =
1435     !Config  Units = NONE
1436     CALL getin_p('TPHOTO_OPT_C',tphoto_opt_c)
1437     !
1438     !Config  Key  = TPHOTO_MAX_A
1439     !Config  Desc = maximum photosynthesis temperature, constant a of ax^2+bx+c (deg C), tabulated
1440     !Config  if  = OK_STOMATE
1441     !Config  Def  = undef,  0., 0., 0., 0., 0., 0., 0., 0., 0.00375, 0., 0., 0.
1442     !Config  Help =
1443     !Config  Units = NONE
1444     CALL getin_p('TPHOTO_MAX_A',tphoto_max_a)
1445     !
1446     !Config  Key  = TPHOTO_MAX_B
1447     !Config  Desc = maximum photosynthesis temperature, constant b of ax^2+bx+c (deg C), tabulated
1448     !Config  if  = OK_STOMATE
1449     !Config  Def  = undef, 0., 0., 0., 0., 0., 0., 0., 0.,0.35, 0., 0., 0.   
1450     !Config  Help =
1451     !Config  Units = NONE
1452     CALL getin_p('TPHOTO_MAX_B',tphoto_max_b)
1453     !
1454     !Config  Key  = TPHOTO_MAX_C
1455     !Config  Desc = maximum photosynthesis temperature, constant c of ax^2+bx+c (deg C), tabulated
1456     !Config  if  = OK_STOMATE
1457     !Config  Def  = undef, 55., 55.,38., 48.,38.,38., 38., 38., 41.125, 55., 45., 55. 
1458     !Config  Help =
1459     !Config  Units = NONE
1460     CALL getin_p('TPHOTO_MAX_C',tphoto_max_c)
1461
1462     !-
1463     ! Respiration - stomate
1464     !-
1465     !
1466     !Config  Key  = MAINT_RESP_SLOPE_C
1467     !Config  Desc = slope of maintenance respiration coefficient (1/K), constant c of aT^2+bT+c , tabulated
1468     !Config  if  = OK_STOMATE
1469     !Config  Def  = undef, .12, .12,.16,.16,.16,.16,.16,.16,.16,.12,.16,.12
1470     !Config  Help =
1471     !Config  Units = NONE
1472     CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) 
1473     !
1474     !Config  Key  = MAINT_RESP_SLOPE_B
1475     !Config  Desc = slope of maintenance respiration coefficient (1/K), constant b of aT^2+bT+c , tabulated
1476     !Config  if  = OK_STOMATE
1477     !Config  Def  = undef,.0,.0,.0,.0,.0,.0,.0,.0, -.00133,.0, -.00133,.0
1478     !Config  Help =
1479     !Config  Units = NONE
1480     CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b)
1481     !
1482     !Config  Key  = MAINT_RESP_SLOPE_A
1483     !Config  Desc = slope of maintenance respiration coefficient (1/K), constant a of aT^2+bT+c , tabulated
1484     !Config  if  = OK_STOMATE
1485     !Config  Def  = undef,.0,.0, .0,.0,.0,.0,.0,.0,.0,.0,.0,.0   
1486     !Config  Help =
1487     !Config  Units = NONE
1488     CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a)
1489     !
1490     !Config  Key  = CM_ZERO_LEAF
1491     !Config  Desc =  maintenance respiration coefficient at 0 deg C, for leaves, tabulated
1492     !Config  if  = OK_STOMATE
1493     !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
1494     !Config  Help =
1495     !Config  Units = [g/g/day]
1496     CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf)
1497     !
1498     !Config  Key  = CM_ZERO_SAPABOVE
1499     !Config  Desc = maintenance respiration coefficient at 0 deg C,for sapwood above, tabulated
1500     !Config  if  = OK_STOMATE
1501     !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
1502     !Config  Help =
1503     !Config  Units = [g/g/day]
1504     CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove)
1505     !
1506     !Config  Key  = CM_ZERO_SAPBELOW
1507     !Config  Desc = maintenance respiration coefficient at 0 deg C, for sapwood below, tabulated
1508     !Config  if  = OK_STOMATE
1509     !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
1510     !Config  Help =
1511     !Config  Units = [g/g/day]
1512     CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow)
1513     !
1514     !Config  Key  = CM_ZERO_HEARTABOVE
1515     !Config  Desc = maintenance respiration coefficient at 0 deg C, for heartwood above, tabulated
1516     !Config  if  = OK_STOMATE
1517     !Config  Def  =  undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
1518     !Config  Help =
1519     !Config  Units = [g/g/day]
1520     CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove)
1521     !
1522     !Config  Key  = CM_ZERO_HEARTBELOW
1523     !Config  Desc = maintenance respiration coefficient at 0 deg C,for heartwood below, tabulated
1524     !Config  if  = OK_STOMATE
1525     !Config  Def  = undef, 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0., 0.
1526     !Config  Help =
1527     !Config  Units = [g/g/day]
1528     CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow)
1529     !
1530     !Config  Key  = CM_ZERO_ROOT
1531     !Config  Desc = maintenance respiration coefficient at 0 deg C, for roots, tabulated
1532     !Config  if  = OK_STOMATE
1533     !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
1534     !Config  Help =
1535     !Config  Units = [g/g/day]
1536     CALL getin_p('CM_ZERO_ROOT',cm_zero_root)
1537     !
1538     !Config  Key  = CM_ZERO_FRUIT
1539     !Config  Desc = maintenance respiration coefficient at 0 deg C, for fruits, tabulated
1540     !Config  if  = OK_STOMATE
1541     !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   
1542     !Config  Help =
1543     !Config  Units = [g/g/day]
1544     CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit)
1545     !
1546     !Config  Key  = CM_ZERO_CARBRES
1547     !Config  Desc = maintenance respiration coefficient at 0 deg C, for carbohydrate reserve, tabulated
1548     !Config  if  = OK_STOMATE
1549     !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
1550     !Config  Help =
1551     !Config  Units = [g/g/day]
1552     CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres)
1553
1554     !-
1555     ! Fire - stomate
1556     !-
1557     !
1558     !Config  Key  = FLAM
1559     !Config  Desc = flamability: critical fraction of water holding capacity
1560     !Config  if  = OK_STOMATE
1561     !Config  Def  = undef,.15,.25,.25,.25,.25,.25,.25,.25,.25,.25,.35,.35
1562     !Config  Help =
1563     !Config  Units =
1564     CALL getin_p('FLAM',flam)
1565     !
1566     !Config  Key  = RESIST
1567     !Config  Desc = fire resistance
1568     !Config  if  = OK_STOMATE
1569     !Config  Def  = undef, .95,.90,.12,.50,.12,.12,.12,.12,.0,.0,.0,.0
1570     !Config  Help =
1571     !Config  Units =
1572     CALL getin_p('RESIST',resist)
1573
1574     !-
1575     ! Flux - LUC
1576     !-
1577     !
1578     !Config  Key  = COEFF_LCCHANGE_1
1579     !Config  Desc = Coeff of biomass export for the year
1580     !Config  if  = OK_STOMATE
1581     !Config  Def  = undef,0.597,0.597,0.597,0.597,0.597,0.597, 0.597, 0.597, 0.597, 0.597, 0.597, 0.597
1582     !Config  Help =
1583     !Config  Units =
1584     CALL getin_p('COEFF_LCCHANGE_1',coeff_lcchange_1)
1585     !
1586     !Config  Key  = COEFF_LCCHANGE_10
1587     !Config  Desc = Coeff of biomass export for the decade
1588     !Config  if  = OK_STOMATE
1589     !Config  Def  = undef,0.403,0.403,0.299,0.299,0.299,0.299,0.299,0.299,0.299,0.403,0.299,0.403
1590     !Config  Help =
1591     !Config  Units =
1592     CALL getin_p('COEFF_LCCHANGE_10',coeff_lcchange_10)
1593     !
1594     !Config  Key  = COEFF_LCCHANGE_100
1595     !Config  Desc = Coeff of biomass export for the century
1596     !Config  if  = OK_STOMATE
1597     !Config  Def  = undef, 0.,0.,0.104,0.104,0.104,0.104,0.104,0.104,0.104, 0.,0.104,0.
1598     !Config  Help =
1599     !Config  Units =
1600     CALL getin_p('COEFF_LCCHANGE_100',coeff_lcchange_100)
1601
1602     !-
1603     ! Phenology
1604     !-
1605     !
1606     !Config  Key  = LAI_MAX
1607     !Config  Desc = maximum LAI, PFT-specific
1608     !Config  if  = OK_STOMATE
1609     !Config  Def  = undef, 7., 7., 5., 5., 5.,4.5, 4.5, 3.0, 2.5, 2.5, 5.,5.
1610     !Config  Help =
1611     !Config  Units =
1612     CALL getin_p('LAI_MAX',lai_max)
1613     !
1614     !Config  Key  = PHENO_MODEL
1615     !Config  Desc = which phenology model is used? (tabulated)
1616     !Config  if  = OK_STOMATE
1617     !Config  Def  =  'none  ', 'none  ', 'moi   ', 'none  ','none  ','ncdgdd','none  ','ncdgdd','ngd   ','moigdd','moigdd','moigdd','moigdd'
1618     !Config  Help =
1619     !Config  Units = NONE
1620     CALL getin_p('PHENO_MODEL',pheno_model)
1621     !
1622     !Config  Key  = PHENO_TYPE
1623     !Config  Desc = type of phenology, 0=bare ground 1=evergreen,  2=summergreen,  3=raingreen,  4=perennial
1624     !Config  if  = OK_STOMATE
1625     !Config  Def  =  0, 1, 3, 1, 1, 2, 1, 2, 2, 4, 4, 2, 3
1626     !Config  Help =
1627     !Config  Units = NONE
1628     CALL getin_p('PHENO_TYPE',pheno_type)
1629
1630     !-
1631     ! Phenology : Leaf Onset
1632     !-
1633     !
1634     !Config  Key  = PHENO_GDD_CRIT_C
1635     !Config  Desc = critical gdd, tabulated (C), constant c of aT^2+bT+c
1636     !Config  if  = OK_STOMATE
1637     !Config  Def  = undef, undef, undef, undef, undef, undef, undef, undef, undef, 270., 400., 125., 400.
1638     !Config  Help =
1639     !Config  Units = NONE
1640     CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c)
1641     !
1642     !Config  Key  = PHENO_GDD_CRIT_B
1643     !Config  Desc = critical gdd, tabulated (C), constant b of aT^2+bT+c
1644     !Config  if  = OK_STOMATE
1645     !Config  Def  = undef, undef, undef, undef, undef, undef, undef,undef, undef, 6.25, 0., 0., 0.
1646     !Config  Help =
1647     !Config  Units = NONE
1648     CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b)
1649     !
1650     !Config  Key  = PHENO_GDD_CRIT_A
1651     !Config  Desc = critical gdd, tabulated (C), constant a of aT^2+bT+c
1652     !Config  if  = OK_STOMATE
1653     !Config  Def  = undef, undef, undef, undef, undef, undef, undef, undef, undef, 0.03125,  0., 0., 0.
1654     !Config  Help =
1655     !Config  Units = NONE
1656     CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a)
1657     !
1658     !Config  Key  = NGD_CRIT
1659     !Config  Desc =  critical ngd, tabulated. Threshold -5 degrees
1660     !Config  if  = OK_STOMATE
1661     !Config  Def  = undef, undef, undef, undef, undef, undef, undef, 0., undef, undef, undef, undef, undef
1662     !Config  Help =
1663     !Config  Units =
1664     CALL getin_p('NGD_CRIT',ngd_crit)
1665     !
1666     !Config  Key  = NCDGDD_TEMP
1667     !Config  Desc = critical temperature for the ncd vs. gdd function in phenology
1668     !Config  if  = OK_STOMATE
1669     !Config  Def  = undef, undef, undef, undef, undef, 5., undef, 0., undef, undef, undef, undef, undef
1670     !Config  Help =
1671     !Config  Units = celsius degrees (C)  ?
1672     CALL getin_p('NCDGDD_TEMP', ncdgdd_temp)
1673     !
1674     !Config  Key  = HUM_FRAC
1675     !Config  Desc = critical humidity (relative to min/max) for phenology
1676     !Config  if  = OK_STOMATE
1677     !Config  Def  = undef, undef, .5, undef, undef, undef, undef, undef,  undef, .5, .5, .5,.5     
1678     !Config  Help =
1679     !Config  Units =
1680     CALL getin_p('HUM_FRAC', hum_frac)
1681     !
1682     !Config  Key  = LOWGPP_TIME
1683     !Config  Desc = minimum duration of dormance for phenology
1684     !Config  if  = OK_STOMATE
1685     !Config  Def  =  undef, undef, 30., undef, undef, 30., undef, 30., 30., 30., 30., 30., 30. 
1686     !Config  Help =
1687     !Config  Units = days
1688     CALL getin_p('LOWGPP_TIME', lowgpp_time)
1689     !
1690     !Config  Key  = HUM_MIN_TIME
1691     !Config  Desc = minimum time elapsed since moisture minimum
1692     !Config  if  = OK_STOMATE
1693     !Config  Def  =  undef, undef, 50., undef, undef, undef, undef, undef, undef, 35., 35., 75., 75.
1694     !Config  Help =
1695     !Config  Units = days [d]
1696     CALL getin_p('HUM_MIN_TIME', hum_min_time)
1697     !
1698     !Config  Key  = TAU_SAP
1699     !Config  Desc = sapwood -> heartwood conversion time
1700     !Config  if  = OK_STOMATE
1701     !Config  Def  = undef, 730., 730., 730., 730., 730., 730., 730., 730., undef, undef, undef, undef
1702     !Config  Help =
1703     !Config  Units = days [d]
1704     CALL getin_p('TAU_SAP',tau_sap)
1705     !
1706     !Config  Key  = TAU_FRUIT
1707     !Config  Desc =  fruit lifetime
1708     !Config  if  = OK_STOMATE
1709     !Config  Def  = undef, 90., 90., 90., 90., 90., 90., 90., 90., undef, undef, undef, undef
1710     !Config  Help =
1711     !Config  Units = days [d]
1712     CALL getin_p('TAU_FRUIT',tau_fruit)
1713     !
1714     !Config  Key  = ECUREUIL
1715     !Config  Desc = fraction of primary leaf and root allocation put into reserve
1716     !Config  if  = OK_STOMATE
1717     !Config  Def  = undef, .0, 1.,.0,.0, 1., .0,1., 1., 1., 1., 1., 1.
1718     !Config  Help =
1719     !Config  Units = NONE
1720     CALL getin_p('ECUREUIL',ecureuil)
1721     !
1722     !Config  Key  = ALLOC_MIN
1723     !Config  Desc = allocation above/below = f(age) - 30/01/04 NV/JO/PF
1724     !Config  if  = OK_STOMATE
1725     !Config  Def  = undef,  0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, undef, undef, undef, undef
1726     !Config  Help =
1727     !Config  Units =
1728     CALL getin_p('ALLOC_MIN',alloc_min)
1729     !
1730     !Config  Key  = ALLOC_MAX
1731     !Config  Desc =
1732     !Config  if  = OK_STOMATE
1733     !Config  Def  = undef, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, undef, undef, undef, undef
1734     !Config  Help =
1735     !Config  Units =
1736     CALL getin_p('ALLOC_MAX',alloc_max)
1737     !
1738     !Config  Key  = DEMI_ALLOC
1739     !Config  Desc =
1740     !Config  if  = OK_STOMATE
1741     !Config  Def  = undef, 5., 5., 5., 5., 5., 5., 5., 5., undef, undef, undef, undef
1742     !Config  Help =
1743     !Config  Units =
1744     CALL getin_p('DEMI_ALLOC',demi_alloc)
1745
1746     !>> DS new for merge in the trunk
1747     ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla
1748     !
1749     !Config  Key  = LEAFLIFE_TAB
1750     !Config  Desc =
1751     !Config  if  = OK_STOMATE
1752     !Config  Def  = undef, .5, 2.,.33, 1., 2.,.33, 2., 2., 2., 2., 2., 2.
1753     !Config  Help =
1754     !Config  Units =
1755     CALL getin_p('LEAFLIFE_TAB',leaflife_tab)
1756
1757     !-
1758     ! Phenology : Senescence
1759     !-
1760     !
1761     !Config  Key  = LEAFFALL
1762     !Config  Desc = length of death of leaves, tabulated
1763     !Config  if  = OK_STOMATE
1764     !Config  Def  = undef,     undef,     10.,   undef,   undef,     10.,   undef,10.,     10.,     10.,     10.,     10.,     10.
1765     !Config  Help =
1766     !Config  Units = days [d]
1767     CALL getin_p('LEAFFALL',leaffall)
1768     !
1769     !Config  Key  = LEAFAGECRIT
1770     !Config  Desc = critical leaf age, tabulated
1771     !Config  if  = OK_STOMATE
1772     !Config  Def  = undef,     730.,    180.,    910.,    730.,    180.,    910.,180.,    180.,    120.,    120.,    90.,    90. 
1773     !Config  Help =
1774     !Config  Units = days [d]
1775     CALL getin_p('LEAFAGECRIT',leafagecrit) 
1776     !
1777     !Config  Key  = SENESCENCE_TYPE
1778     !Config  Desc = type of senescence, tabulated
1779     !Config  if  = OK_STOMATE
1780     !Config  Def  =  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ', 'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ','mixed ',  'mixed ',   'mixed '
1781     !Config  Help =
1782     !Config  Units = NONE
1783     CALL getin_p('SENESCENCE_TYPE', senescence_type) 
1784     !
1785     !Config  Key  = SENESCENCE_HUM
1786     !Config  Desc = critical relative moisture availability for senescence
1787     !Config  if  = OK_STOMATE
1788     !Config  Def  = undef, undef, .3, undef, undef, undef, undef, undef, undef, .2, .2, .3, .2
1789     !Config  Help =
1790     !Config  Units =
1791     CALL getin_p('SENESCENCE_HUM', senescence_hum)
1792     !
1793     !Config  Key  = NOSENESCENCE_HUM
1794     !Config  Desc = relative moisture availability above which there is no humidity-related senescence
1795     !Config  if  = OK_STOMATE
1796     !Config  Def  = undef, undef, .8, undef, undef, undef, undef, undef, undef, .3, .3, .3, .3
1797     !Config  Help =
1798     !Config  Units =
1799     CALL getin_p('NOSENESCENCE_HUM', nosenescence_hum) 
1800     !
1801     !Config  Key  = MAX_TURNOVER_TIME
1802     !Config  Desc = maximum turnover time for grasse
1803     !Config  if  = OK_STOMATE
1804     !Config  Def  = undef,  undef, undef, undef, undef, undef, undef, undef, undef,  80.,  80., 80., 80.
1805     !Config  Help =
1806     !Config  Units = days [d]
1807     CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time)
1808     !
1809     !Config  Key  = MIN_TURNOVER_TIME
1810     !Config  Desc = minimum turnover time for grasse
1811     !Config  if  = OK_STOMATE
1812     !Config  Def  = undef, undef, undef, undef, undef, undef, undef, undef, undef, 10., 10., 10., 10.
1813     !Config  Help =
1814     !Config  Units = days [d]
1815     CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time)
1816     !
1817     !Config  Key  = MIN_LEAF_AGE_FOR_SENESCENCE
1818     !Config  Desc =  minimum leaf age to allow senescence g
1819     !Config  if  = OK_STOMATE
1820     !Config  Def  = undef, undef, 90., undef, undef, 90., undef, 60., 60., 30., 30., 30., 30.
1821     !Config  Help =
1822     !Config  Units = days ?
1823     CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE', min_leaf_age_for_senescence)
1824     !
1825     !Config  Key  = SENESCENCE_TEMP_C
1826     !Config  Desc = critical temperature for senescence (C), constant c of aT^2+bT+c, tabulated
1827     !Config  if  = OK_STOMATE
1828     !Config  Def  = undef, undef, undef, undef, undef, 12., undef, 7., 2., -1.375, 5., 5., 10.
1829     !Config  Help =
1830     !Config  Units = NONE
1831     CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c)
1832     !
1833     !Config  Key  = SENESCENCE_TEMP_B
1834     !Config  Desc = critical temperature for senescence (C), constant b of aT^2+bT+c ,tabulated
1835     !Config  if  = OK_STOMATE
1836     !Config  Def  =  undef, undef, undef, undef, undef, 0., undef, 0., 0., .1, 0., 0., 0.
1837     !Config  Help =
1838     !Config  Units = NONE
1839     CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b)
1840     !
1841     !Config  Key  = SENESCENCE_TEMP_A
1842     !Config  Desc = critical temperature for senescence (C), constant a of aT^2+bT+c , tabulated
1843     !Config  if  = OK_STOMATE
1844     !Config  Def  = undef, undef, undef, undef, undef, 0., undef, 0., 0.,.00375, 0., 0., 0.
1845     !Config  Help =
1846     !Config  Units = NONE
1847     CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a)
1848
1849     !-
1850     ! DGVM
1851     !-
1852     !
1853     !Config  Key  = RESIDENCE_TIME
1854     !Config  Desc =  residence time of trees
1855     !Config  if  = OK_DGVM AND .NOT. LPJ_GAP_CONST_MORT
1856     !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
1857     !Config  Help =
1858     !Config  Units = years (y)
1859     CALL getin_p('RESIDENCE_TIME',residence_time)
1860     !
1861     !Config  Key  = TMIN_CRIT
1862     !Config  Desc = critical tmin, tabulated
1863     !Config  if  = OK_STOMATE
1864     !Config  Def  = undef,  0.0, 0.0, -30.0, -14.0, -30.0, -45.0, -45.0, undef, undef, undef, undef, undef
1865     !Config  Help =
1866     !Config  Units = Celsius degrees [C]
1867     CALL getin_p('TMIN_CRIT',tmin_crit)
1868     !
1869     !Config  Key  = TCM_CRIT
1870     !Config  Desc = critical tcm, tabulated
1871     !Config  if  = OK_STOMATE
1872     !Config  Def  =  undef, undef, undef, 5.0, 15.5, 15.5, -8.0, -8.0, -8.0, undef, undef,  undef, undef
1873     !Config  Help =
1874     !Config  Units = Celsius degrees [C]
1875     CALL getin_p('TCM_CRIT',tcm_crit)
1876     
1877     first_call = .FALSE.
1878       
1879  ENDIF
1880 
1881END SUBROUTINE getin_stomate_pft_parameters
1882!
1883!=
1884!
1885 SUBROUTINE pft_parameters_clear
1886   
1887   l_first_define_pft = .TRUE.
1888   
1889   IF(ALLOCATED(pft_to_mtc))DEALLOCATE(pft_to_mtc)
1890   IF(ALLOCATED(PFT_name))DEALLOCATE(PFT_name)
1891   !-
1892   IF(ALLOCATED(veget_ori_fixed_test_1))DEALLOCATE(veget_ori_fixed_test_1)   
1893   IF(ALLOCATED(llaimax))DEALLOCATE(llaimax)
1894   IF(ALLOCATED(llaimin))DEALLOCATE(llaimin)
1895   IF(ALLOCATED(height_presc))DEALLOCATE(height_presc)   
1896   IF(ALLOCATED(type_of_lai))DEALLOCATE(type_of_lai)
1897   IF(ALLOCATED(is_tree))DEALLOCATE(is_tree)
1898   IF(ALLOCATED(natural))DEALLOCATE(natural)
1899   !-
1900   !>> DS new for merge in the trunk   ! 15/06/2011
1901   ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
1902   IF(ALLOCATED(is_deciduous))DEALLOCATE(is_deciduous)
1903   IF(ALLOCATED(is_evergreen))DEALLOCATE(is_evergreen)
1904   IF(ALLOCATED(is_c3))DEALLOCATE(is_c3) 
1905   !-
1906   IF(ALLOCATED(humcste))DEALLOCATE(humcste)
1907   !-
1908   IF(ALLOCATED(pref_soil_veg_sand))DEALLOCATE(pref_soil_veg_sand)
1909   IF(ALLOCATED(pref_soil_veg_loan))DEALLOCATE(pref_soil_veg_loan)
1910   IF(ALLOCATED(pref_soil_veg_clay))DEALLOCATE(pref_soil_veg_clay)
1911   IF(ALLOCATED(pref_soil_veg))DEALLOCATE(pref_soil_veg)
1912   !-
1913   IF(ALLOCATED(is_c4))DEALLOCATE(is_c4) 
1914   IF(ALLOCATED(gsslope))DEALLOCATE(gsslope)
1915   IF(ALLOCATED(gsoffset))DEALLOCATE(gsoffset)
1916   IF(ALLOCATED(vcmax_fix))DEALLOCATE(vcmax_fix)
1917   IF(ALLOCATED(vjmax_fix))DEALLOCATE(vjmax_fix)
1918   IF(ALLOCATED(co2_tmin_fix))DEALLOCATE(co2_tmin_fix)
1919   IF(ALLOCATED(co2_topt_fix))DEALLOCATE(co2_topt_fix)
1920   IF(ALLOCATED(co2_tmax_fix))DEALLOCATE(co2_tmax_fix) 
1921   IF(ALLOCATED(ext_coeff))DEALLOCATE(ext_coeff)
1922   !-
1923   IF(ALLOCATED(rveg_pft))DEALLOCATE(rveg_pft)
1924   !-
1925   IF(ALLOCATED(rstruct_const))DEALLOCATE(rstruct_const)
1926   IF(ALLOCATED(kzero))DEALLOCATE(kzero)
1927   !-
1928   IF(ALLOCATED(wmax_veg))DEALLOCATE(wmax_veg)
1929   IF(ALLOCATED(throughfall_by_pft))DEALLOCATE(throughfall_by_pft)
1930   !-
1931   IF(ALLOCATED(snowa_ini))DEALLOCATE(snowa_ini)
1932   IF(ALLOCATED(snowa_dec))DEALLOCATE(snowa_dec)
1933   IF(ALLOCATED(alb_leaf_vis))DEALLOCATE(alb_leaf_vis)
1934   IF(ALLOCATED(alb_leaf_nir))DEALLOCATE(alb_leaf_nir)   
1935   IF(ALLOCATED(alb_leaf))DEALLOCATE(alb_leaf)
1936   !-
1937   IF(ALLOCATED(leaf_tab))DEALLOCATE(leaf_tab)
1938   IF(ALLOCATED(sla))DEALLOCATE(sla)
1939   !-
1940   IF(ALLOCATED(vcmax_opt))DEALLOCATE(vcmax_opt)
1941   IF(ALLOCATED(vjmax_opt))DEALLOCATE(vjmax_opt)
1942   IF(ALLOCATED(tphoto_min_a))DEALLOCATE(tphoto_min_a)
1943   IF(ALLOCATED(tphoto_min_b))DEALLOCATE(tphoto_min_b)
1944   IF(ALLOCATED(tphoto_min_c))DEALLOCATE(tphoto_min_c)
1945   IF(ALLOCATED(tphoto_opt_a))DEALLOCATE(tphoto_opt_a)
1946   IF(ALLOCATED(tphoto_opt_b))DEALLOCATE(tphoto_opt_b)
1947   IF(ALLOCATED(tphoto_opt_c))DEALLOCATE(tphoto_opt_c)
1948   IF(ALLOCATED(tphoto_max_a))DEALLOCATE(tphoto_max_a)
1949   IF(ALLOCATED(tphoto_max_b))DEALLOCATE(tphoto_max_b)
1950   IF(ALLOCATED(tphoto_max_c))DEALLOCATE(tphoto_max_c)
1951   !-
1952   IF(ALLOCATED(maint_resp_slope))DEALLOCATE(maint_resp_slope)
1953   IF(ALLOCATED(maint_resp_slope_c))DEALLOCATE(maint_resp_slope_c)
1954   IF(ALLOCATED(maint_resp_slope_b))DEALLOCATE(maint_resp_slope_b)
1955   IF(ALLOCATED(maint_resp_slope_a))DEALLOCATE(maint_resp_slope_a)
1956   IF(ALLOCATED(coeff_maint_zero))DEALLOCATE(coeff_maint_zero)
1957   IF(ALLOCATED(cm_zero_leaf))DEALLOCATE(cm_zero_leaf)
1958   IF(ALLOCATED(cm_zero_sapabove))DEALLOCATE(cm_zero_sapabove)
1959   IF(ALLOCATED(cm_zero_sapbelow))DEALLOCATE(cm_zero_sapbelow)
1960   IF(ALLOCATED(cm_zero_heartabove))DEALLOCATE(cm_zero_heartabove)
1961   IF(ALLOCATED(cm_zero_heartbelow))DEALLOCATE(cm_zero_heartbelow)
1962   IF(ALLOCATED(cm_zero_root))DEALLOCATE(cm_zero_root)
1963   IF(ALLOCATED(cm_zero_fruit))DEALLOCATE(cm_zero_fruit)
1964   IF(ALLOCATED(cm_zero_carbres))DEALLOCATE(cm_zero_carbres)
1965   !-
1966   IF(ALLOCATED(flam))DEALLOCATE(flam)
1967   IF(ALLOCATED(resist))DEALLOCATE(resist)
1968   !-
1969   IF(ALLOCATED(coeff_lcchange_1))DEALLOCATE(coeff_lcchange_1)
1970   IF(ALLOCATED(coeff_lcchange_10))DEALLOCATE(coeff_lcchange_10)
1971   IF(ALLOCATED(coeff_lcchange_100))DEALLOCATE(coeff_lcchange_100)
1972   !-
1973   IF(ALLOCATED(lai_max)) DEALLOCATE(lai_max)
1974   IF(ALLOCATED(pheno_model))DEALLOCATE(pheno_model)
1975   IF(ALLOCATED(pheno_type))DEALLOCATE(pheno_type)
1976   !-
1977   IF(ALLOCATED(pheno_gdd_crit_c))DEALLOCATE(pheno_gdd_crit_c)
1978   IF(ALLOCATED(pheno_gdd_crit_b))DEALLOCATE(pheno_gdd_crit_b)
1979   IF(ALLOCATED(pheno_gdd_crit_a))DEALLOCATE(pheno_gdd_crit_a)
1980   IF(ALLOCATED(pheno_gdd_crit))DEALLOCATE(pheno_gdd_crit)
1981   IF(ALLOCATED(ngd_crit))DEALLOCATE(ngd_crit)
1982   IF(ALLOCATED(ncdgdd_temp))DEALLOCATE(ncdgdd_temp)
1983   IF(ALLOCATED(hum_frac))DEALLOCATE(hum_frac)
1984   IF(ALLOCATED(lowgpp_time))DEALLOCATE(lowgpp_time)   
1985   IF(ALLOCATED(hum_min_time))DEALLOCATE(hum_min_time)
1986   IF(ALLOCATED(tau_sap))DEALLOCATE(tau_sap)
1987   IF(ALLOCATED(tau_fruit))DEALLOCATE(tau_fruit)
1988   IF(ALLOCATED(ecureuil))DEALLOCATE(ecureuil)
1989   IF(ALLOCATED(alloc_min))DEALLOCATE(alloc_min)
1990   IF(ALLOCATED(alloc_max))DEALLOCATE(alloc_max)
1991   IF(ALLOCATED(demi_alloc))DEALLOCATE(demi_alloc)
1992   !>> DS new for merge in the trunk   ! 15/06/2011
1993   IF(ALLOCATED(leaflife_tab))DEALLOCATE(leaflife_tab)
1994   !-
1995   IF(ALLOCATED(leaffall))DEALLOCATE(leaffall)
1996   IF(ALLOCATED(leafagecrit))DEALLOCATE(leafagecrit)
1997   IF(ALLOCATED(senescence_type))DEALLOCATE(senescence_type)
1998   IF(ALLOCATED(senescence_hum))DEALLOCATE(senescence_hum)
1999   IF(ALLOCATED(nosenescence_hum))DEALLOCATE(nosenescence_hum)
2000   IF(ALLOCATED(max_turnover_time))DEALLOCATE(max_turnover_time)
2001   IF(ALLOCATED(min_turnover_time))DEALLOCATE(min_turnover_time)
2002   IF(ALLOCATED(min_leaf_age_for_senescence))DEALLOCATE(min_leaf_age_for_senescence)
2003   !-
2004   IF(ALLOCATED(senescence_temp_c))DEALLOCATE(senescence_temp_c)
2005   IF(ALLOCATED(senescence_temp_b))DEALLOCATE(senescence_temp_b)
2006   IF(ALLOCATED(senescence_temp_a))DEALLOCATE(senescence_temp_a)
2007   IF(ALLOCATED(senescence_temp))DEALLOCATE(senescence_temp)
2008   !-
2009   IF(ALLOCATED(residence_time))DEALLOCATE(residence_time)
2010   IF(ALLOCATED(tmin_crit))DEALLOCATE(tmin_crit)
2011   IF(ALLOCATED(tcm_crit))DEALLOCATE(tcm_crit)
2012   !-
2013   IF(ALLOCATED(lai_initmin))DEALLOCATE(lai_initmin)
2014   IF(ALLOCATED(tree))DEALLOCATE(tree)
2015   IF(ALLOCATED(bm_sapl))DEALLOCATE(bm_sapl)
2016   IF(ALLOCATED(migrate))DEALLOCATE(migrate)
2017   IF(ALLOCATED(maxdia))DEALLOCATE(maxdia)
2018   IF(ALLOCATED(cn_sapl))DEALLOCATE(cn_sapl)
2019   IF(ALLOCATED(leaf_timecst))DEALLOCATE(leaf_timecst)
2020   
2021 END SUBROUTINE pft_parameters_clear
2022
2023END MODULE pft_parameters
Note: See TracBrowser for help on using the repository browser.