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

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

Move some labels associated to externalized parameters in sechiba to pft_parameters.f90

File size: 49.7 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 (see constantes_veg)
21  INTEGER(i_std) :: 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
381
382CONTAINS
383 !
384 SUBROUTINE pft_parameters_main 
385 
386   IMPLICIT NONE
387
388   ! Local 
389    INTEGER(i_std) :: i
390
391   !----------------------
392   ! PFT global
393   !----------------------
394
395   IF(l_first_define_pft) THEN
396
397      ! 1. First time step
398      IF(long_print) THEN
399         WRITE(numout,*) 'l_first_define_pft :we read the parameters from the def files'
400      ENDIF
401
402      ! 2. Memory allocation
403      ! Allocation of memory for the pfts-parameters
404      CALL pft_parameters_alloc
405
406      ! 3. Correspondance table
407     
408      ! 3.1 Initialisation of the correspondance table
409      ! Initialisation of the correspondance table
410      pft_to_mtc (:) = undef_integer
411     
412      ! 3.2 Reading of the conrrespondance table in the .def file
413      CALL getin_p('PFT_TO_MTC',pft_to_mtc)
414
415      ! 3.3 If the user want to use the standard configuration, he needn't to fill the correspondance array
416      !     If the configuration is wrong, send a error message to the user.
417      IF(nvm .EQ. 13 ) THEN
418         IF(pft_to_mtc(1) .EQ. undef_integer) THEN
419            WRITE(numout,*) 'Note to the user : we will use ORCHIDEE to its standard configuration'
420            pft_to_mtc(:) = (/ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 /)
421         ENDIF
422      ELSE   
423         IF(pft_to_mtc(1) .EQ. undef_integer) THEN
424            WRITE(numout,*)' The array PFT_TO_MTC is empty : we stop'
425         ENDIF
426      ENDIF
427
428      ! 3.4 Some error messages
429
430      ! 3.4.1 What happened if pft_to_mtc(j) > nvmc (if the mtc doesn't exist)?
431       DO i = 1, nvm
432          IF(pft_to_mtc(i) .GT. nvmc) THEN
433             WRITE(numout,*) "the MTC you chose doesn't exist"
434             STOP 'we stop reading pft_to_mtc'
435          ENDIF
436       ENDDO   
437
438
439      ! 3.4.2 Check if pft_to_mtc(1) = 1
440       IF(pft_to_mtc(1) .NE. 1) THEN
441          WRITE(numout,*) 'the first pft has to be the bare soil'
442          STOP 'we stop reading next values of pft_to_mtc'
443       ELSE
444          DO i = 2,nvm
445             IF(pft_to_mtc(i) .EQ.1) THEN
446                WRITE(numout,*) 'only pft_to_mtc(1) has to be the bare soil'
447                STOP 'we stop reading pft_to_mtc'
448             ENDIF
449          ENDDO
450       ENDIF
451     
452   
453      ! 4.Initialisation of the pfts-parameters
454      CALL pft_parameters_init
455
456      ! 5. A useful message to the user: correspondance between the number of the pft
457      ! and the name of the associated mtc
458      DO i = 1,nvm
459         WRITE(numout,*) 'the PFT',i,'corresponds to the MTC : ',PFT_name(i) 
460      ENDDO
461
462      ! 6. Initialisation of 2D arrays used in the code
463
464      !-alb_leaf
465      alb_leaf(:) = zero
466
467      !- pref_soil_veg
468      pref_soil_veg(:,:) = zero_int
469
470      !- pheno_gdd_crit
471      pheno_gdd_crit(:,:) = zero 
472      !
473      !- senescence_temp
474      senescence_temp(:,:) = zero
475      !
476      !- maint_resp_slope
477      maint_resp_slope(:,:) = zero
478      !
479      !-coeff_maint_zero
480      coeff_maint_zero(:,:) = zero
481
482      ! 7. End message
483      IF(long_print) THEN
484         WRITE(numout,*) 'pft_parameters_done'
485      ENDIF
486
487   ELSE
488
489      l_first_define_pft = .FALSE.
490       
491      RETURN
492
493   ENDIF
494
495 END SUBROUTINE pft_parameters_main
496 !
497 !=
498 !
499 SUBROUTINE pft_parameters_init
500 
501   IMPLICIT NONE
502   
503   !------------
504   ! local
505   INTEGER(i_std) :: j,k
506   !------------
507
508   !
509   ! 1. Initialisation !! not all the parameters are initialized
510   !
511
512   !-
513   ! Vegetation structure
514   !-
515   !
516   ! 1 .Sechiba
517   !
518   veget_ori_fixed_test_1(:) = zero
519   llaimax(:) = zero
520   llaimin(:) = zero
521   height_presc(:) = zero
522   rveg_pft(:) = zero
523   !
524   ! 2 .Stomate
525   !
526   leaf_tab(:) = zero_int
527   sla(:) = zero   
528   !-
529   ! Evapotranspiration -  sechiba
530   !-
531   rstruct_const(:) = zero
532   kzero(:) = zero
533   !-
534   ! Water - sechiba
535   !-
536   wmax_veg(:) = zero
537   humcste(:) = zero
538   throughfall_by_pft(:) = zero
539   !-
540   ! Albedo - sechiba
541   !-
542   snowa_ini(:) = zero
543   snowa_dec(:) = zero
544   alb_leaf_vis(:) = zero
545   alb_leaf_nir(:) = zero
546   !-
547   ! Soil - vegetation
548   !-
549   pref_soil_veg_sand(:) = zero_int
550   pref_soil_veg_loan(:) = zero_int
551   pref_soil_veg_clay(:) = zero_int
552   !-
553   ! Photosynthesis
554   !-
555   !
556   ! 1 .CO2
557   !
558   gsslope(:) = zero
559   gsoffset(:) = zero
560   vcmax_fix(:) = zero
561   vjmax_fix(:) = zero
562   co2_tmin_fix(:) = zero
563   co2_topt_fix(:) = zero
564   co2_tmax_fix(:) = zero
565   ext_coeff(:) = zero
566   !
567   ! 2 .Stomate
568   !
569   vcmax_opt(:) = zero
570   vjmax_opt(:) = zero
571   tphoto_min_a(:) = zero
572   tphoto_min_b(:) = zero
573   tphoto_min_c(:) = zero
574   tphoto_opt_a(:) = zero
575   tphoto_opt_b(:) = zero
576   tphoto_opt_c(:) = zero
577   tphoto_max_a(:) = zero
578   tphoto_max_b(:) = zero
579   tphoto_max_c(:) = zero
580   !-
581   ! Respiration - stomate
582   !-
583   maint_resp_slope_c(:) = zero
584   maint_resp_slope_b(:) = zero
585   maint_resp_slope_a(:) = zero
586   cm_zero_leaf(:) = zero
587   cm_zero_sapabove(:) = zero
588   cm_zero_sapbelow(:) = zero
589   cm_zero_heartabove(:) = zero
590   cm_zero_heartbelow(:) = zero
591   cm_zero_root(:) = zero
592   cm_zero_fruit(:) = zero
593   cm_zero_carbres(:) = zero
594   !-
595   ! Fire - stomate
596   !-
597   !
598   flam(:) = zero
599   resist(:) = zero
600   !-
601   ! Flux - LUC
602   !-
603   coeff_lcchange_1(:) = zero
604   coeff_lcchange_10(:) = zero
605   coeff_lcchange_100(:) = zero
606   !-
607   ! Phenology
608   !-
609   !
610   ! 1 .Stomate
611   !
612   lai_max(:) = zero
613   pheno_type(:) = zero_int
614   !
615   ! 2. Leaf Onset
616   !
617   pheno_gdd_crit_c(:) = zero
618   pheno_gdd_crit_b(:) = zero
619   pheno_gdd_crit_a(:) = zero
620   ngd_crit(:) = zero
621   ncdgdd_temp(:) = zero
622   hum_frac(:) = zero
623   lowgpp_time(:) = zero
624   hum_min_time(:) = zero
625   tau_sap(:) = zero
626   tau_fruit(:) = zero
627   ecureuil(:) = zero
628   alloc_min(:) = zero
629   alloc_max(:) = zero
630   demi_alloc(:) = zero 
631  !>> DS new for merge in the trunk 15/06/2011
632   leaflife_tab(:) = zero
633   !
634   ! 3. Senescence
635   !
636   leaffall(:) = zero
637   leafagecrit(:) = zero
638   senescence_hum(:) = zero
639   nosenescence_hum(:) = zero
640   max_turnover_time(:) = zero   
641   min_turnover_time(:) = zero 
642   min_leaf_age_for_senescence(:) = zero 
643   senescence_temp_c(:) = zero 
644   senescence_temp_b(:) = zero 
645   senescence_temp_a(:) = zero 
646   !-
647   ! DGVM
648   !-
649   residence_time(:) = zero
650   tmin_crit(:) = zero
651   tcm_crit(:) = zero
652   !-
653   !  Internal_parameters
654   !-
655   lai_initmin(:) = zero
656   bm_sapl(:,:) = zero
657   migrate(:) = zero
658   maxdia(:) = zero
659   cn_sapl(:) = zero
660   leaf_timecst(:) = zero 
661
662
663   !
664   ! 2. Correspondance between the PFTs values and thes MTCs values
665   !
666 
667   DO j= 1, nvm
668
669
670      PFT_name(j) = MTC_name(pft_to_mtc(j))
671
672      !-
673      ! Vegetation structure
674      !-
675      !
676      ! 1 .Sechiba
677      !
678      veget_ori_fixed_test_1(j) = veget_ori_fixed_mtc(pft_to_mtc(j))
679      llaimax(j) = llaimax_mtc(pft_to_mtc(j))
680      llaimin(j) = llaimin_mtc(pft_to_mtc(j))
681      height_presc(j) = height_presc_mtc(pft_to_mtc(j))
682      type_of_lai(j) = type_of_lai_mtc(pft_to_mtc(j))
683      is_tree(j) = is_tree_mtc(pft_to_mtc(j))
684      rveg_pft(j) = rveg_mtc(pft_to_mtc(j))
685
686      !>> DS new for merge in the trunk   ! 15/06/2011
687      ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
688      is_deciduous(j) = is_deciduous_mtc(pft_to_mtc(j))
689      is_evergreen(j) = is_evergreen_mtc(pft_to_mtc(j))
690      is_c3(j) = is_c3(pft_to_mtc(j))
691
692      !
693      ! 2 .Stomate
694      !
695      leaf_tab(j) = leaf_tab_mtc(pft_to_mtc(j))
696      sla(j) = sla_mtc(pft_to_mtc(j))
697      natural(j) = natural_mtc(pft_to_mtc(j))
698
699      !-
700      ! Evapotranspiration -  sechiba
701      !-
702      rstruct_const(j) = rstruct_const_mtc(pft_to_mtc(j))
703      kzero(j) = kzero_mtc(pft_to_mtc(j))
704      !-
705      ! Water - sechiba
706      !-
707      wmax_veg(j) = wmax_veg_mtc(pft_to_mtc(j))
708      humcste(j) = humcste_mtc(pft_to_mtc(j))
709      throughfall_by_pft(j) = throughfall_by_mtc(pft_to_mtc(j))
710      !-
711      ! Albedo - sechiba
712      !-
713      snowa_ini(j) = snowa_ini_mtc(pft_to_mtc(j))
714      snowa_dec(j) = snowa_dec_mtc(pft_to_mtc(j)) 
715      alb_leaf_vis(j) = alb_leaf_vis_mtc(pft_to_mtc(j)) 
716      alb_leaf_nir(j) = alb_leaf_nir_mtc(pft_to_mtc(j))
717      !-
718      !   Soil - vegetation
719      !-
720      pref_soil_veg_sand(j) = pref_soil_veg_sand_mtc(pft_to_mtc(j))
721      pref_soil_veg_loan(j) = pref_soil_veg_loan_mtc(pft_to_mtc(j))
722      pref_soil_veg_clay(j) = pref_soil_veg_clay_mtc(pft_to_mtc(j))
723
724      !-
725      ! Photosynthesis
726      !-
727      !
728      ! 1 .CO2
729      !
730      is_c4(j) = is_c4_mtc(pft_to_mtc(j))
731      gsslope(j) = gsslope_mtc(pft_to_mtc(j))
732      gsoffset(j) = gsoffset_mtc(pft_to_mtc(j))
733      vcmax_fix(j) = vcmax_fix_mtc(pft_to_mtc(j))
734      vjmax_fix(j) = vjmax_fix_mtc(pft_to_mtc(j))
735      co2_tmin_fix(j) = co2_tmin_fix_mtc(pft_to_mtc(j))
736      co2_topt_fix(j) = co2_topt_fix_mtc(pft_to_mtc(j))
737      co2_tmax_fix(j) = co2_tmax_fix_mtc(pft_to_mtc(j))
738      !
739      ! 2 .Stomate
740      !
741      ext_coeff(j) = ext_coeff_mtc(pft_to_mtc(j))
742      vcmax_opt(j) = vcmax_opt_mtc(pft_to_mtc(j))
743      vjmax_opt(j) = vjmax_opt_mtc(pft_to_mtc(j)) 
744      tphoto_min_a(j) = tphoto_min_a_mtc(pft_to_mtc(j)) 
745      tphoto_min_b(j) = tphoto_min_b_mtc(pft_to_mtc(j))
746      tphoto_min_c(j) = tphoto_min_c_mtc(pft_to_mtc(j))
747      tphoto_opt_a(j) = tphoto_opt_a_mtc(pft_to_mtc(j))
748      tphoto_opt_b(j) = tphoto_opt_b_mtc(pft_to_mtc(j))
749      tphoto_opt_c(j) = tphoto_opt_c_mtc(pft_to_mtc(j))
750      tphoto_max_a(j) = tphoto_max_a_mtc(pft_to_mtc(j))
751      tphoto_max_b(j) = tphoto_max_b_mtc(pft_to_mtc(j))
752      tphoto_max_c(j) = tphoto_max_c_mtc(pft_to_mtc(j))
753      !-
754      ! Respiration - stomate
755      !-
756      maint_resp_slope_c(j) = maint_resp_slope_c_mtc(pft_to_mtc(j))               
757      maint_resp_slope_b(j) = maint_resp_slope_b_mtc(pft_to_mtc(j))
758      maint_resp_slope_a(j) = maint_resp_slope_a_mtc(pft_to_mtc(j))
759      cm_zero_leaf(j)= cm_zero_leaf_mtc(pft_to_mtc(j))
760      cm_zero_sapabove(j) = cm_zero_sapabove_mtc(pft_to_mtc(j))
761      cm_zero_sapbelow(j) = cm_zero_sapbelow_mtc(pft_to_mtc(j)) 
762      cm_zero_heartabove(j) = cm_zero_heartabove_mtc(pft_to_mtc(j)) 
763      cm_zero_heartbelow(j) = cm_zero_heartbelow_mtc(pft_to_mtc(j))
764      cm_zero_root(j) = cm_zero_root_mtc(pft_to_mtc(j))
765      cm_zero_fruit(j) = cm_zero_fruit_mtc(pft_to_mtc(j))
766      cm_zero_carbres(j) = cm_zero_carbres_mtc(pft_to_mtc(j))
767      !-
768      ! Fire - stomate
769      !-
770      flam(j) = flam_mtc(pft_to_mtc(j))
771      resist(j) = resist_mtc(pft_to_mtc(j))
772      !-
773      ! Flux - LUC
774      !-
775      coeff_lcchange_1(j) = coeff_lcchange_1_mtc(pft_to_mtc(j))
776      coeff_lcchange_10(j) = coeff_lcchange_10_mtc(pft_to_mtc(j))
777      coeff_lcchange_100(j) = coeff_lcchange_100_mtc(pft_to_mtc(j))
778      !-
779      ! Phenology
780      !-
781      !
782      ! 1 .Stomate
783      !
784      lai_max(j) = lai_max_mtc(pft_to_mtc(j))
785      pheno_model(j) = pheno_model_mtc(pft_to_mtc(j))
786      pheno_type(j) = pheno_type_mtc(pft_to_mtc(j))
787      !
788      ! 2. Leaf Onset
789      !
790      pheno_gdd_crit_c(j) = pheno_gdd_crit_c_mtc(pft_to_mtc(j))
791      pheno_gdd_crit_b(j) = pheno_gdd_crit_b_mtc(pft_to_mtc(j))         
792      pheno_gdd_crit_a(j) = pheno_gdd_crit_a_mtc(pft_to_mtc(j))
793      ngd_crit(j) =  ngd_crit_mtc(pft_to_mtc(j))
794      ncdgdd_temp(j) = ncdgdd_temp_mtc(pft_to_mtc(j)) 
795      hum_frac(j) = hum_frac_mtc(pft_to_mtc(j))
796      lowgpp_time(j) = lowgpp_time_mtc(pft_to_mtc(j))
797      hum_min_time(j) = hum_min_time_mtc(pft_to_mtc(j))
798      tau_sap(j) =tau_sap_mtc(pft_to_mtc(j))
799      tau_fruit(j) =tau_fruit_mtc(pft_to_mtc(j))
800      ecureuil(j) = ecureuil_mtc(pft_to_mtc(j))
801      alloc_min(j) = alloc_min_mtc(pft_to_mtc(j))
802      alloc_max(j) = alloc_max_mtc(pft_to_mtc(j))
803      demi_alloc(j) = demi_alloc_mtc(pft_to_mtc(j))
804  !>> DS new for merge in the trunk   ! 15/06/2011
805      leaflife_tab(j) = leaflife_mtc(pft_to_mtc(j))
806      !
807      ! 3. Senescence
808      !
809      leaffall(j) = leaffall_mtc(pft_to_mtc(j))
810      leafagecrit(j) = leafagecrit_mtc(pft_to_mtc(j))
811      senescence_type(j) = senescence_type_mtc(pft_to_mtc(j)) 
812      senescence_hum(j) = senescence_hum_mtc(pft_to_mtc(j)) 
813      nosenescence_hum(j) = nosenescence_hum_mtc(pft_to_mtc(j)) 
814      max_turnover_time(j) = max_turnover_time_mtc(pft_to_mtc(j))
815      min_turnover_time(j) = min_turnover_time_mtc(pft_to_mtc(j))
816      min_leaf_age_for_senescence(j) = min_leaf_age_for_senescence_mtc(pft_to_mtc(j))
817      senescence_temp_c(j) = senescence_temp_c_mtc(pft_to_mtc(j))
818      senescence_temp_b(j) = senescence_temp_b_mtc(pft_to_mtc(j))
819      senescence_temp_a(j) = senescence_temp_a_mtc(pft_to_mtc(j))
820      !-
821      ! DGVM
822      residence_time(j) = residence_time_mtc(pft_to_mtc(j))
823      tmin_crit(j) = tmin_crit_mtc(pft_to_mtc(j))
824      tcm_crit(j) =  tcm_crit_mtc(pft_to_mtc(j))
825     
826   ENDDO ! end loop over nvm
827
828 END SUBROUTINE pft_parameters_init
829 !
830 !=
831 !
832 SUBROUTINE pft_parameters_alloc
833
834   IMPLICIT NONE
835   !------------------
836   ! local
837    LOGICAL ::  l_error
838    INTEGER :: ier
839   !-----------------
840
841   l_error = .FALSE.
842   ALLOCATE(pft_to_mtc(nvm),stat=ier)
843   l_error = l_error .OR. (ier .NE. 0)
844   ALLOCATE(PFT_name(nvm),stat=ier)
845   l_error = l_error .OR. (ier .NE. 0)
846   !-
847   !>> DS new for merge in the trunk   ! 15/06/2011
848   ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
849   ALLOCATE(is_deciduous(nvm),stat=ier)   
850   l_error = l_error .OR. (ier .NE. 0)
851   ALLOCATE(is_evergreen(nvm),stat=ier) 
852   l_error = l_error .OR. (ier .NE. 0)
853   ALLOCATE(is_c3(nvm),stat=ier) 
854   l_error = l_error .OR. (ier .NE. 0)
855   ALLOCATE(leaflife_tab(nvm),stat=ier)   
856   l_error = l_error .OR. (ier .NE. 0)
857   ! >> END
858
859   ALLOCATE(veget_ori_fixed_test_1(nvm),stat=ier)
860   l_error = l_error .OR. (ier .NE. 0)
861   ALLOCATE(llaimax(nvm),stat=ier)
862   l_error = l_error .OR. (ier .NE. 0)
863   ALLOCATE(llaimin(nvm),stat=ier)
864   l_error = l_error .OR. (ier .NE. 0)
865   ALLOCATE(height_presc(nvm),stat=ier)
866   l_error = l_error .OR. (ier .NE. 0)
867   ALLOCATE(type_of_lai(nvm),stat=ier)
868   l_error = l_error .OR. (ier .NE. 0)   
869   ALLOCATE(is_tree(nvm),stat=ier)
870   l_error = l_error .OR. (ier .NE. 0)   
871   !-
872   ALLOCATE(leaf_tab(nvm),stat=ier)
873   l_error = l_error .OR. (ier .NE. 0)
874   ALLOCATE(sla(nvm),stat=ier)
875   l_error = l_error .OR. (ier .NE. 0)   
876   ALLOCATE(natural(nvm),stat=ier)
877   l_error = l_error .OR. (ier .NE. 0)
878   !-
879   ALLOCATE(is_c4(nvm),stat=ier)
880   l_error = l_error .OR. (ier .NE. 0)
881   ALLOCATE(gsslope(nvm),stat=ier)
882   l_error = l_error .OR. (ier .NE. 0)
883   ALLOCATE(gsoffset(nvm),stat=ier)
884   l_error = l_error .OR. (ier .NE. 0)
885   ALLOCATE(vcmax_fix(nvm),stat=ier)
886   l_error = l_error .OR. (ier .NE. 0)
887   ALLOCATE(vjmax_fix(nvm),stat=ier)
888   l_error = l_error .OR. (ier .NE. 0)
889   ALLOCATE(co2_tmin_fix(nvm),stat=ier)
890   l_error = l_error .OR. (ier .NE. 0)
891   ALLOCATE(co2_topt_fix(nvm),stat=ier)
892   l_error = l_error .OR. (ier .NE. 0)
893   ALLOCATE(co2_tmax_fix(nvm),stat=ier)
894   l_error = l_error .OR. (ier .NE. 0)
895   !-
896   ALLOCATE(ext_coeff(nvm),stat=ier)
897   l_error = l_error .OR. (ier .NE. 0) 
898   ALLOCATE(vcmax_opt(nvm),stat=ier)
899   l_error = l_error .OR. (ier .NE. 0) 
900   ALLOCATE(vjmax_opt(nvm),stat=ier)
901   l_error = l_error .OR. (ier .NE. 0)
902   ALLOCATE(tphoto_min_a(nvm),stat=ier)
903   l_error = l_error .OR. (ier .NE. 0) 
904   ALLOCATE(tphoto_min_b(nvm),stat=ier)
905   l_error = l_error .OR. (ier .NE. 0) 
906   ALLOCATE(tphoto_min_c(nvm),stat=ier)
907   l_error = l_error .OR. (ier .NE. 0) 
908   ALLOCATE(tphoto_opt_a(nvm),stat=ier)
909   l_error = l_error .OR. (ier .NE. 0) 
910   ALLOCATE(tphoto_opt_b(nvm),stat=ier)
911   l_error = l_error .OR. (ier .NE. 0) 
912   ALLOCATE(tphoto_opt_c(nvm),stat=ier)
913   l_error = l_error .OR. (ier .NE. 0) 
914   ALLOCATE(tphoto_max_a(nvm),stat=ier)
915   l_error = l_error .OR. (ier .NE. 0) 
916   ALLOCATE(tphoto_max_b(nvm),stat=ier)
917   l_error = l_error .OR. (ier .NE. 0) 
918   ALLOCATE(tphoto_max_c(nvm),stat=ier)
919   l_error = l_error .OR. (ier .NE. 0) 
920   !-
921   ALLOCATE(pheno_gdd_crit_c(nvm),stat=ier)
922   l_error = l_error .OR. (ier .NE. 0)
923   ALLOCATE(pheno_gdd_crit_b(nvm),stat=ier)
924   l_error = l_error .OR. (ier .NE. 0)
925   ALLOCATE(pheno_gdd_crit_a(nvm),stat=ier)
926   l_error = l_error .OR. (ier .NE. 0)
927   ALLOCATE(pheno_gdd_crit(nvm,3),stat=ier)
928   l_error = l_error .OR. (ier .NE. 0)
929   ALLOCATE(ngd_crit(nvm),stat=ier)
930   l_error = l_error .OR. (ier .NE. 0)
931   ALLOCATE(ncdgdd_temp(nvm),stat=ier)
932   l_error = l_error .OR. (ier .NE. 0)
933   ALLOCATE(hum_frac(nvm),stat=ier)
934   l_error = l_error .OR. (ier .NE. 0)
935   ALLOCATE(lowgpp_time(nvm),stat=ier)
936   l_error = l_error .OR. (ier .NE. 0)
937   ALLOCATE(hum_min_time(nvm),stat=ier)
938   l_error = l_error .OR. (ier .NE. 0)
939   ALLOCATE(tau_sap(nvm),stat=ier)
940   l_error = l_error .OR. (ier .NE. 0)
941   ALLOCATE(tau_fruit(nvm),stat=ier)
942   l_error = l_error .OR. (ier .NE. 0)
943   ALLOCATE(ecureuil(nvm),stat=ier)
944   l_error = l_error .OR. (ier .NE. 0)
945   ALLOCATE(alloc_min(nvm),stat=ier)
946   l_error = l_error .OR. (ier .NE. 0)
947   ALLOCATE(alloc_max(nvm),stat=ier)
948   l_error = l_error .OR. (ier .NE. 0)
949   ALLOCATE(demi_alloc(nvm),stat=ier)
950   l_error = l_error .OR. (ier .NE. 0)
951   !-
952   ALLOCATE(maint_resp_slope(nvm,3),stat=ier)
953   l_error = l_error .OR. (ier .NE. 0)
954   ALLOCATE(maint_resp_slope_c(nvm),stat=ier)
955   l_error = l_error .OR. (ier .NE. 0)
956   ALLOCATE(maint_resp_slope_b(nvm),stat=ier)
957   l_error = l_error .OR. (ier .NE. 0)
958   ALLOCATE(maint_resp_slope_a(nvm),stat=ier)
959   l_error = l_error .OR. (ier .NE. 0)
960   ALLOCATE(coeff_maint_zero(nvm,nparts),stat=ier)
961   l_error = l_error .OR. (ier .NE. 0)
962   ALLOCATE(cm_zero_leaf(nvm),stat=ier)
963   l_error = l_error .OR. (ier .NE. 0)
964   ALLOCATE(cm_zero_sapabove(nvm),stat=ier)
965   l_error = l_error .OR. (ier .NE. 0)
966   ALLOCATE(cm_zero_sapbelow(nvm),stat=ier)
967   l_error = l_error .OR. (ier .NE. 0)
968   ALLOCATE(cm_zero_heartabove(nvm),stat=ier)
969   l_error = l_error .OR. (ier .NE. 0)
970   ALLOCATE(cm_zero_heartbelow(nvm),stat=ier)
971   l_error = l_error .OR. (ier .NE. 0)
972   ALLOCATE(cm_zero_root(nvm),stat=ier)
973   l_error = l_error .OR. (ier .NE. 0)
974   ALLOCATE(cm_zero_fruit(nvm),stat=ier)
975   l_error = l_error .OR. (ier .NE. 0)
976   ALLOCATE(cm_zero_carbres(nvm),stat=ier)
977   l_error = l_error .OR. (ier .NE. 0)
978   !-
979   ALLOCATE(flam(nvm),stat=ier)
980   l_error = l_error .OR. (ier .NE. 0) 
981   ALLOCATE(resist(nvm),stat=ier)
982   l_error = l_error .OR. (ier .NE. 0) 
983   !-
984   ALLOCATE(coeff_lcchange_1(nvm),stat=ier)
985   l_error = l_error .OR. (ier .NE. 0)
986   ALLOCATE(coeff_lcchange_10(nvm),stat=ier)
987   l_error = l_error .OR. (ier .NE. 0)
988   ALLOCATE(coeff_lcchange_100(nvm),stat=ier)
989   l_error = l_error .OR. (ier .NE. 0)
990   !-
991   ALLOCATE(lai_max(nvm),stat=ier)
992   l_error = l_error .OR. (ier .NE. 0)
993   ALLOCATE(pheno_model(nvm),stat=ier)
994   l_error = l_error .OR. (ier .NE. 0) 
995   ALLOCATE(pheno_type(nvm),stat=ier)
996   l_error = l_error .OR. (ier .NE. 0) 
997   !-
998   ALLOCATE(leaffall(nvm),stat=ier)
999   l_error = l_error .OR. (ier .NE. 0)
1000   ALLOCATE(leafagecrit(nvm),stat=ier)
1001   l_error = l_error .OR. (ier .NE. 0)
1002   ALLOCATE(senescence_type(nvm),stat=ier)
1003   l_error = l_error .OR. (ier .NE. 0)
1004   ALLOCATE(senescence_hum(nvm),stat=ier)
1005   l_error = l_error .OR. (ier .NE. 0)
1006   ALLOCATE(nosenescence_hum(nvm),stat=ier)
1007   l_error = l_error .OR. (ier .NE. 0)
1008   ALLOCATE(max_turnover_time(nvm),stat=ier)
1009   l_error = l_error .OR. (ier .NE. 0)
1010   ALLOCATE(min_turnover_time(nvm),stat=ier)
1011   l_error = l_error .OR. (ier .NE. 0)
1012   ALLOCATE(min_leaf_age_for_senescence(nvm),stat=ier)
1013   l_error = l_error .OR. (ier .NE. 0)
1014   ALLOCATE(senescence_temp_c(nvm),stat=ier)
1015   l_error = l_error .OR. (ier .NE. 0)
1016   ALLOCATE(senescence_temp_b(nvm),stat=ier)
1017   l_error = l_error .OR. (ier .NE. 0)
1018   ALLOCATE(senescence_temp_a(nvm),stat=ier)
1019   l_error = l_error .OR. (ier .NE. 0)
1020   ALLOCATE(senescence_temp(nvm,3),stat=ier)
1021   l_error = l_error .OR. (ier .NE. 0)
1022   !-
1023   ALLOCATE(residence_time(nvm),stat=ier)
1024   l_error = l_error .OR. (ier .NE. 0)
1025   ALLOCATE(tmin_crit(nvm),stat=ier)
1026   l_error = l_error .OR. (ier .NE. 0)
1027   ALLOCATE(tcm_crit(nvm),stat=ier)
1028   l_error = l_error .OR. (ier .NE. 0)
1029   !-
1030   ALLOCATE(rstruct_const(nvm),stat=ier)
1031   l_error = l_error .OR. (ier .NE. 0)
1032   ALLOCATE(kzero(nvm),stat=ier)
1033   l_error = l_error .OR. (ier .NE. 0)
1034   !-
1035   ALLOCATE(wmax_veg(nvm),stat=ier)
1036   l_error = l_error .OR. (ier .NE. 0)
1037   ALLOCATE(humcste(nvm),stat=ier)
1038   l_error = l_error .OR. (ier .NE. 0)
1039   !-
1040   ALLOCATE(snowa_ini(nvm),stat=ier)
1041   l_error = l_error .OR. (ier .NE. 0)   
1042   ALLOCATE(snowa_dec(nvm),stat=ier)
1043   l_error = l_error .OR. (ier .NE. 0)
1044   ALLOCATE(alb_leaf_vis(nvm),stat=ier)
1045   l_error = l_error .OR. (ier .NE. 0)
1046   ALLOCATE(alb_leaf_nir(nvm),stat=ier)
1047   l_error = l_error .OR. (ier .NE. 0)
1048   ALLOCATE(alb_leaf(2*nvm),stat=ier)
1049   l_error = l_error .OR. (ier .NE. 0)
1050   !-
1051   ALLOCATE(pref_soil_veg_sand(nvm),stat=ier)
1052   l_error = l_error .OR. (ier .NE. 0)
1053   ALLOCATE(pref_soil_veg_loan(nvm),stat=ier)
1054   l_error = l_error .OR. (ier .NE. 0)
1055   ALLOCATE(pref_soil_veg_clay(nvm),stat=ier)
1056   l_error = l_error .OR. (ier .NE. 0)
1057   ALLOCATE(pref_soil_veg(nvm,nstm),stat=ier)
1058   l_error = l_error .OR. (ier .NE. 0)
1059   !-
1060   ALLOCATE(lai_initmin(nvm),stat=ier)
1061   l_error = l_error .OR. (ier .NE. 0)
1062   ALLOCATE(tree(nvm),stat=ier)
1063   l_error = l_error .OR. (ier .NE. 0)
1064   ALLOCATE(bm_sapl(nvm,nparts),stat=ier)
1065   l_error = l_error .OR. (ier .NE. 0)
1066   ALLOCATE(migrate(nvm),stat=ier)
1067   l_error = l_error .OR. (ier .NE. 0)
1068   ALLOCATE(maxdia(nvm),stat=ier)
1069   l_error = l_error .OR. (ier .NE. 0)
1070   ALLOCATE(cn_sapl(nvm),stat=ier)
1071   l_error = l_error .OR. (ier .NE. 0)
1072   ALLOCATE(leaf_timecst(nvm),stat=ier)
1073   l_error = l_error .OR. (ier .NE. 0) 
1074   !-
1075   ALLOCATE(throughfall_by_pft(nvm),stat=ier)
1076   l_error = l_error .OR. (ier .NE. 0)   
1077   ALLOCATE (rveg_pft(nvm),stat=ier)
1078   l_error = l_error .OR. (ier .NE. 0) 
1079   !
1080   IF (l_error) THEN
1081       STOP 'pft _alloc : error in memory allocation'
1082   ENDIF
1083
1084 END SUBROUTINE pft_parameters_alloc
1085!
1086!=
1087!
1088 SUBROUTINE getin_sechiba_pft_parameters
1089
1090   IMPLICIT NONE
1091 
1092   LOGICAL, SAVE ::  first_call = .TRUE.
1093
1094  IF(first_call) THEN
1095
1096     ! No calling to getin for veget_ori_fixed_test_1, llaimax and height_presc
1097     ! use of setvar in slowproc.f90
1098
1099     !-
1100     ! Vegetation structure
1101     !-
1102     CALL getin_p('LLAIMIN',llaimin)
1103     CALL getin('TYPE_OF_LAI',type_of_lai)
1104     CALL getin_p('IS_TREE',is_tree)
1105     CALL getin_p('NATURAL',natural)
1106
1107     !>> DS new for merge in the trunk   ! 15/06/2011
1108     ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
1109     CALL getin('IS_DECIDUOUS',is_deciduous)
1110     CALL getin('IS_EVERGREEN',is_evergreen) 
1111     CALL getin_p('IS_C3',is_c3)   
1112
1113     !-
1114     ! Photosynthesis
1115     !-
1116     CALL getin_p('IS_C4',is_c4)
1117     CALL getin_p('GSSLOPE',gsslope)
1118     CALL getin_p('GSOFFSET',gsoffset)
1119     CALL getin_p('VCMAX_FIX',vcmax_fix)
1120     CALL getin_p('VJMAX_FIX',vjmax_fix)
1121     CALL getin_p('CO2_TMIN_FIX',co2_tmin_fix)
1122     CALL getin_p('CO2_TOPT_FIX',co2_topt_fix)
1123     CALL getin_p('CO2_TMAX_FIX',co2_tmax_fix)
1124     CALL getin_p('EXT_COEFF',ext_coeff)
1125     !-
1126     ! Evapotranspiration -  sechiba
1127     !-
1128     CALL getin_p('RSTRUCT_CONST',rstruct_const)
1129     CALL getin_p('KZERO',kzero)
1130     !
1131     ! Ajouts Nathalie - le 28 Mars 2006 - sur conseils Fred Hourdin
1132     !
1133     !Config Key  = RVEG_PFT
1134     !Config Desc = Artificial parameter to increase or decrease canopy resistance.
1135     !Config Def  = 1.
1136     !Config Help = This parameter is set by PFT.
1137     CALL getin_p('RVEG_PFT', rveg_pft)   
1138     !-
1139     ! Water-hydrology - sechiba
1140     !-
1141     CALL getin_p('WMAX_VEG',wmax_veg)
1142     !Config Key  = HYDROL_HUMCSTE
1143     !Config Desc = Root profile
1144     !Config Def  = 5., .8, .8, 1., .8, .8, 1., 1., .8, 4., 4., 4., 4.
1145     !Config Help = Default values were defined for 2 meters soil depth.
1146     !Config        For 4 meters soil depth, you may use those ones :
1147     !Config        5., .4, .4, 1., .8, .8, 1., 1., .8, 4., 1., 4., 1.
1148     CALL getin_p('HYDROL_HUMCSTE', humcste)
1149     !Config  Key  = PERCENT_THROUGHFALL_PFT
1150     !Config  Desc = Percent by PFT of precip that is not intercepted by the canopy
1151     !Config  Def  = 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30. 30.
1152     !Config  Help = During one rainfall event, PERCENT_THROUGHFALL_PFT% of the incident rainfall
1153     !Config         will get directly to the ground without being intercepted, for each PFT.
1154     CALL getin_p('PERCENT_TROUGHFALL_PFT',throughfall_by_pft)
1155     !-
1156     ! Albedo - sechiba
1157     !-
1158     CALL getin_p('SNOWA_INI',snowa_ini)
1159     CALL getin_p('SNOWA_DEC',snowa_dec)
1160     CALL getin_p('ALB_LEAF_VIS',alb_leaf_vis)
1161     CALL getin_p('ALB_LEAF_NIR',alb_leaf_nir)
1162     !-
1163     ! Soil - vegetation
1164     !-
1165     CALL getin_p('PREF_SOIL_VEG_SAND',pref_soil_veg_sand)
1166     CALL getin_p('PREF_SOIL_VEG_LOAN',pref_soil_veg_loan)         
1167     CALL getin_p('PREF_SOIL_VEG_CLAY',pref_soil_veg_clay)
1168
1169     first_call = .FALSE.
1170
1171  ENDIF
1172
1173END SUBROUTINE getin_sechiba_pft_parameters
1174!
1175!=
1176!
1177SUBROUTINE getin_stomate_pft_parameters
1178
1179  IMPLICIT NONE
1180
1181  LOGICAL, SAVE ::  first_call = .TRUE.
1182
1183  IF(first_call) THEN
1184
1185      !-
1186      ! Vegetation structure
1187      !-
1188      CALL getin_p('LEAF_TAB',leaf_tab)
1189      CALL getin_p('SLA',sla)
1190      !-
1191      ! Photosynthesis
1192      !-
1193      CALL getin_p('VCMAX_OPT',vcmax_opt)
1194      CALL getin_p('VJMAX_OPT',vjmax_opt)
1195      CALL getin_p('TPHOTO_MIN_A',tphoto_min_a)
1196      CALL getin_p('TPHOTO_MIN_B',tphoto_min_b)
1197      CALL getin_p('TPHOTO_MIN_C',tphoto_min_c)
1198      CALL getin_p('TPHOTO_OPT_A',tphoto_opt_a)
1199      CALL getin_p('TPHOTO_OPT_B',tphoto_opt_b)
1200      CALL getin_p('TPHOTO_OPT_C',tphoto_opt_c)
1201      CALL getin_p('TPHOTO_MAX_A',tphoto_max_a)
1202      CALL getin_p('TPHOTO_MAX_B',tphoto_max_b)
1203      CALL getin_p('TPHOTO_MAX_C',tphoto_max_c)
1204      !-
1205      ! Respiration - stomate
1206      !-
1207      CALL getin_p('MAINT_RESP_SLOPE_C',maint_resp_slope_c) 
1208      CALL getin_p('MAINT_RESP_SLOPE_B',maint_resp_slope_b)
1209      CALL getin_p('MAINT_RESP_SLOPE_A',maint_resp_slope_a)
1210      CALL getin_p('CM_ZERO_LEAF',cm_zero_leaf)
1211      CALL getin_p('CM_ZERO_SAPABOVE',cm_zero_sapabove)
1212      CALL getin_p('CM_ZERO_SAPBELOW',cm_zero_sapbelow)
1213      CALL getin_p('CM_ZERO_HEARTABOVE',cm_zero_heartabove)
1214      CALL getin_p('CM_ZERO_HEARTBELOW',cm_zero_heartbelow)
1215      CALL getin_p('CM_ZERO_ROOT',cm_zero_root)
1216      CALL getin_p('CM_ZERO_FRUIT',cm_zero_fruit)
1217      CALL getin_p('CM_ZERO_CARBRES',cm_zero_carbres)
1218      !-
1219      ! Fire - stomate
1220      !-
1221      CALL getin_p('FLAM',flam)
1222      CALL getin_p('RESIST',resist)
1223      !-
1224      ! Flux - LUC
1225      !-
1226      CALL getin_p('COEFF_LCCHANGE_1',coeff_lcchange_1)
1227      CALL getin_p('COEFF_LCCHANGE_10',coeff_lcchange_10)
1228      CALL getin_p('COEFF_LCCHANGE_100',coeff_lcchange_100)
1229      !-
1230      ! Phenology
1231      !-
1232      CALL getin_p('LAI_MAX',lai_max)
1233      CALL getin('PHENO_MODEL',pheno_model)
1234      CALL getin_p('PHENO_TYPE',pheno_type)
1235      !-
1236      ! Phenology : Leaf Onset
1237      !-
1238      CALL getin_p('PHENO_GDD_CRIT_C',pheno_gdd_crit_c)
1239      CALL getin_p('PHENO_GDD_CRIT_B',pheno_gdd_crit_b)
1240      CALL getin_p('PHENO_GDD_CRIT_A',pheno_gdd_crit_a)
1241      CALL getin_p('NGD_CRIT',ngd_crit)
1242      CALL getin_p('NCDGDD_TEMP', ncdgdd_temp)
1243      CALL getin_p('HUM_FRAC', hum_frac)
1244      CALL getin_p('LOWGPP_TIME', lowgpp_time)
1245      CALL getin_p('HUM_MIN_TIME', hum_min_time)
1246      CALL getin_p('TAU_SAP',tau_sap)
1247      CALL getin_p('TAU_FRUIT',tau_fruit)
1248      CALL getin_p('ECUREUIL',ecureuil)
1249      CALL getin_p('ALLOC_MIN',alloc_min)
1250      CALL getin_p('ALLOC_MAX',alloc_max)
1251      CALL getin_p('DEMI_ALLOC',demi_alloc)
1252
1253      !>> DS new for merge in the trunk
1254      ! 15/06/2011 : add leaflife_mtc for the new formalism used for calculate sla
1255      CALL getin_p('LEAFLIFE_TAB',leaflife_tab)
1256
1257      !-
1258      ! Phenology : Senescence
1259      !-
1260      CALL getin_p('LEAFFALL',leaffall)
1261      CALL getin_p('LEAFAGECRIT',leafagecrit) 
1262      CALL getin('SENESCENCE_TYPE', senescence_type) 
1263      CALL getin_p('SENESCENCE_HUM', senescence_hum)
1264      CALL getin_p('NOSENESCENCE_HUM', nosenescence_hum) 
1265      CALL getin_p('MAX_TURNOVER_TIME',max_turnover_time)
1266      CALL getin_p('MIN_TURNOVER_TIME',min_turnover_time)
1267      CALL getin_p('MIN_LEAF_AGE_FOR_SENESCENCE', min_leaf_age_for_senescence)
1268      CALL getin_p('SENESCENCE_TEMP_C',senescence_temp_c)
1269      CALL getin_p('SENESCENCE_TEMP_B',senescence_temp_b)
1270      CALL getin_p('SENESCENCE_TEMP_A',senescence_temp_a)
1271      !-
1272      ! DGVM
1273      !-
1274      CALL getin_p('RESIDENCE_TIME',residence_time)
1275      CALL getin_p('TMIN_CRIT',tmin_crit)
1276      CALL getin_p('TCM_CRIT',tcm_crit)
1277     
1278     first_call = .FALSE.
1279       
1280  ENDIF
1281 
1282END SUBROUTINE getin_stomate_pft_parameters
1283 !
1284 !=
1285 !
1286 SUBROUTINE pft_parameters_clear
1287   
1288   l_first_define_pft = .TRUE.
1289   
1290   IF(ALLOCATED(pft_to_mtc))DEALLOCATE(pft_to_mtc)
1291   IF(ALLOCATED(PFT_name))DEALLOCATE(PFT_name)
1292   !-
1293   !>> DS new for merge in the trunk   ! 15/06/2011
1294   ! Add for writing history files in stomate_lpj.f90 'treeFracPrimDec' and 'treeFracPrimEver'
1295   IF(ALLOCATED(is_deciduous))DEALLOCATE(is_deciduous)
1296   IF(ALLOCATED(is_evergreen))DEALLOCATE(is_evergreen)
1297   IF(ALLOCATED(leaflife_tab))DEALLOCATE(leaflife_tab)
1298   IF(ALLOCATED(is_c3))DEALLOCATE(is_c3) 
1299   !-
1300   IF(ALLOCATED(veget_ori_fixed_test_1))DEALLOCATE(veget_ori_fixed_test_1)   
1301   IF(ALLOCATED(llaimax))DEALLOCATE(llaimax)
1302   IF(ALLOCATED(llaimin))DEALLOCATE(llaimin)
1303   IF(ALLOCATED(height_presc))DEALLOCATE(height_presc)   
1304   IF(ALLOCATED(type_of_lai))DEALLOCATE(type_of_lai)
1305   IF(ALLOCATED(is_tree))DEALLOCATE(is_tree)
1306   !-
1307   IF(ALLOCATED(leaf_tab))DEALLOCATE(leaf_tab)
1308   IF(ALLOCATED(sla))DEALLOCATE(sla)
1309   IF(ALLOCATED(natural))DEALLOCATE(natural)
1310   !-
1311   IF(ALLOCATED(is_c4))DEALLOCATE(is_c4) 
1312   IF(ALLOCATED(gsslope))DEALLOCATE(gsslope)
1313   IF(ALLOCATED(gsoffset))DEALLOCATE(gsoffset)
1314   IF(ALLOCATED(vcmax_fix))DEALLOCATE(vcmax_fix)
1315   IF(ALLOCATED(vjmax_fix))DEALLOCATE(vjmax_fix)
1316   IF(ALLOCATED(co2_tmin_fix))DEALLOCATE(co2_tmin_fix)
1317   IF(ALLOCATED(co2_topt_fix))DEALLOCATE(co2_topt_fix)
1318   IF(ALLOCATED(co2_tmax_fix))DEALLOCATE(co2_tmax_fix) 
1319   !-
1320   IF(ALLOCATED(ext_coeff))DEALLOCATE(ext_coeff)
1321   IF(ALLOCATED(vcmax_opt))DEALLOCATE(vcmax_opt)
1322   IF(ALLOCATED(vjmax_opt))DEALLOCATE(vjmax_opt)
1323   IF(ALLOCATED(tphoto_min_a))DEALLOCATE(tphoto_min_a)
1324   IF(ALLOCATED(tphoto_min_b))DEALLOCATE(tphoto_min_b)
1325   IF(ALLOCATED(tphoto_min_c))DEALLOCATE(tphoto_min_c)
1326   IF(ALLOCATED(tphoto_opt_a))DEALLOCATE(tphoto_opt_a)
1327   IF(ALLOCATED(tphoto_opt_b))DEALLOCATE(tphoto_opt_b)
1328   IF(ALLOCATED(tphoto_opt_c))DEALLOCATE(tphoto_opt_c)
1329   IF(ALLOCATED(tphoto_max_a))DEALLOCATE(tphoto_max_a)
1330   IF(ALLOCATED(tphoto_max_b))DEALLOCATE(tphoto_max_b)
1331   IF(ALLOCATED(tphoto_max_c))DEALLOCATE(tphoto_max_c)
1332   !-
1333   IF(ALLOCATED(maint_resp_slope))DEALLOCATE(maint_resp_slope)
1334   IF(ALLOCATED(maint_resp_slope_c))DEALLOCATE(maint_resp_slope_c)
1335   IF(ALLOCATED(maint_resp_slope_b))DEALLOCATE(maint_resp_slope_b)
1336   IF(ALLOCATED(maint_resp_slope_a))DEALLOCATE(maint_resp_slope_a)
1337   IF(ALLOCATED(coeff_maint_zero))DEALLOCATE(coeff_maint_zero)
1338   IF(ALLOCATED(cm_zero_leaf))DEALLOCATE(cm_zero_leaf)
1339   IF(ALLOCATED(cm_zero_sapabove))DEALLOCATE(cm_zero_sapabove)
1340   IF(ALLOCATED(cm_zero_sapbelow))DEALLOCATE(cm_zero_sapbelow)
1341   IF(ALLOCATED(cm_zero_heartabove))DEALLOCATE(cm_zero_heartabove)
1342   IF(ALLOCATED(cm_zero_heartbelow))DEALLOCATE(cm_zero_heartbelow)
1343   IF(ALLOCATED(cm_zero_root))DEALLOCATE(cm_zero_root)
1344   IF(ALLOCATED(cm_zero_fruit))DEALLOCATE(cm_zero_fruit)
1345   IF(ALLOCATED(cm_zero_carbres))DEALLOCATE(cm_zero_carbres)
1346   !-
1347   IF(ALLOCATED(flam))DEALLOCATE(flam)
1348   IF(ALLOCATED(resist))DEALLOCATE(resist)
1349   !-
1350   IF(ALLOCATED(coeff_lcchange_1))DEALLOCATE(coeff_lcchange_1)
1351   IF(ALLOCATED(coeff_lcchange_10))DEALLOCATE(coeff_lcchange_10)
1352   IF(ALLOCATED(coeff_lcchange_100))DEALLOCATE(coeff_lcchange_100)
1353   !-
1354   IF(ALLOCATED(lai_max)) DEALLOCATE(lai_max)
1355   IF(ALLOCATED(pheno_model))DEALLOCATE(pheno_model)
1356   IF(ALLOCATED(pheno_type))DEALLOCATE(pheno_type)
1357   !-
1358   IF(ALLOCATED(pheno_gdd_crit_c))DEALLOCATE(pheno_gdd_crit_c)
1359   IF(ALLOCATED(pheno_gdd_crit_b))DEALLOCATE(pheno_gdd_crit_b)
1360   IF(ALLOCATED(pheno_gdd_crit_a))DEALLOCATE(pheno_gdd_crit_a)
1361   IF(ALLOCATED(pheno_gdd_crit))DEALLOCATE(pheno_gdd_crit)
1362   IF(ALLOCATED(ngd_crit))DEALLOCATE(ngd_crit)
1363   IF(ALLOCATED(ncdgdd_temp))DEALLOCATE(ncdgdd_temp)
1364   IF(ALLOCATED(hum_frac))DEALLOCATE(hum_frac)
1365   IF(ALLOCATED(lowgpp_time))DEALLOCATE(lowgpp_time)   
1366   IF(ALLOCATED(hum_min_time))DEALLOCATE(hum_min_time)
1367   IF(ALLOCATED(tau_sap))DEALLOCATE(tau_sap)
1368   IF(ALLOCATED(tau_fruit))DEALLOCATE(tau_fruit)
1369   IF(ALLOCATED(ecureuil))DEALLOCATE(ecureuil)
1370   IF(ALLOCATED(alloc_min))DEALLOCATE(alloc_min)
1371   IF(ALLOCATED(alloc_max))DEALLOCATE(alloc_max)
1372   IF(ALLOCATED(demi_alloc))DEALLOCATE(demi_alloc)
1373   !-
1374   IF(ALLOCATED(leaffall))DEALLOCATE(leaffall)
1375   IF(ALLOCATED(leafagecrit))DEALLOCATE(leafagecrit)
1376   IF(ALLOCATED(senescence_type))DEALLOCATE(senescence_type)
1377   IF(ALLOCATED(senescence_hum))DEALLOCATE(senescence_hum)
1378   IF(ALLOCATED(nosenescence_hum))DEALLOCATE(nosenescence_hum)
1379   IF(ALLOCATED(max_turnover_time))DEALLOCATE(max_turnover_time)
1380   IF(ALLOCATED(min_turnover_time))DEALLOCATE(min_turnover_time)
1381   IF(ALLOCATED(min_leaf_age_for_senescence))DEALLOCATE(min_leaf_age_for_senescence)
1382   !-
1383   IF(ALLOCATED(senescence_temp_c))DEALLOCATE(senescence_temp_c)
1384   IF(ALLOCATED(senescence_temp_b))DEALLOCATE(senescence_temp_b)
1385   IF(ALLOCATED(senescence_temp_a))DEALLOCATE(senescence_temp_a)
1386   IF(ALLOCATED(senescence_temp))DEALLOCATE(senescence_temp)
1387   !-
1388   IF(ALLOCATED(residence_time))DEALLOCATE(residence_time)
1389   IF(ALLOCATED(tmin_crit))DEALLOCATE(tmin_crit)
1390   IF(ALLOCATED(tcm_crit))DEALLOCATE(tcm_crit)
1391   !-
1392   IF(ALLOCATED(rstruct_const))DEALLOCATE(rstruct_const)
1393   IF(ALLOCATED(kzero))DEALLOCATE(kzero)
1394   !-
1395   IF(ALLOCATED(wmax_veg))DEALLOCATE(wmax_veg)
1396   IF(ALLOCATED(humcste))DEALLOCATE(humcste)
1397   !-
1398   IF(ALLOCATED(snowa_ini))DEALLOCATE(snowa_ini)
1399   IF(ALLOCATED(snowa_dec))DEALLOCATE(snowa_dec)
1400   IF(ALLOCATED(alb_leaf_vis))DEALLOCATE(alb_leaf_vis)
1401   IF(ALLOCATED(alb_leaf_nir))DEALLOCATE(alb_leaf_nir)   
1402   IF(ALLOCATED(alb_leaf))DEALLOCATE(alb_leaf)
1403   !-
1404   IF(ALLOCATED(pref_soil_veg_sand))DEALLOCATE(pref_soil_veg_sand)
1405   IF(ALLOCATED(pref_soil_veg_loan))DEALLOCATE(pref_soil_veg_loan)
1406   IF(ALLOCATED(pref_soil_veg_clay))DEALLOCATE(pref_soil_veg_clay)
1407   IF(ALLOCATED(pref_soil_veg))DEALLOCATE(pref_soil_veg)
1408   !-
1409   IF(ALLOCATED(lai_initmin))DEALLOCATE(lai_initmin)
1410   IF(ALLOCATED(tree))DEALLOCATE(tree)
1411   IF(ALLOCATED(bm_sapl))DEALLOCATE(bm_sapl)
1412   IF(ALLOCATED(migrate))DEALLOCATE(migrate)
1413   IF(ALLOCATED(maxdia))DEALLOCATE(maxdia)
1414   IF(ALLOCATED(cn_sapl))DEALLOCATE(cn_sapl)
1415   IF(ALLOCATED(leaf_timecst))DEALLOCATE(leaf_timecst)
1416   !-
1417   IF(ALLOCATED(throughfall_by_pft))DEALLOCATE(throughfall_by_pft)
1418   IF(ALLOCATED(rveg_pft))DEALLOCATE(rveg_pft)
1419   
1420 END SUBROUTINE pft_parameters_clear
1421
1422END MODULE pft_parameters
Note: See TracBrowser for help on using the repository browser.