source: branches/publications/ORCHIDEE-MICT-OP-r6850/src_parameters/pft_parameters_var.f90 @ 7442

Last change on this file since 7442 was 6849, checked in by yidi.xu, 4 years ago

ORCHIDEE-MICT-OP for oil palm growth modelling

  • Property svn:keywords set to Date Revision
File size: 64.2 KB
Line 
1! =================================================================================================================================
2! MODULE       : pft_parameters_var
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        This module contains the variables in function of plant funtional type (pft).
10!!
11!!\n DESCRIPTION: This module contains the declarations for the externalized variables in function of the
12!!                plant foncional type(pft). \n
13!!                The module is already USE in module pft_parameters. Therefor no need to USE it seperatly except
14!!                if the subroutines in module pft_parameters are not needed.\n
15!!
16!! RECENT CHANGE(S): None
17!!
18!! REFERENCE(S) : None
19!!
20!! SVN          :
21!! $HeadURL: $
22!! $Date$
23!! $Revision$
24!! \n
25!_ ================================================================================================================================
26
27MODULE pft_parameters_var
28
29  USE defprec
30 
31  IMPLICIT NONE
32
33
34  !
35  ! PFT GLOBAL
36  !
37  INTEGER(i_std), SAVE :: nvm = 13                              !! Number of vegetation types (2-N, unitless)
38  INTEGER(i_std), SAVE :: nphs = 40                             !! Number of phytomers (2-N, unitless)
39!$OMP THREADPRIVATE(nvm)
40
41  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pft_to_mtc  !! Table of conversion : we associate one pft to one metaclass
42                                                                 !! (1-13, unitless)
43!$OMP THREADPRIVATE(pft_to_mtc)
44
45  CHARACTER(LEN=34), ALLOCATABLE, SAVE, DIMENSION(:) :: PFT_name !! Description of the PFT (unitless)
46!$OMP THREADPRIVATE(PFT_name)
47
48  LOGICAL, SAVE   :: l_first_pft_parameters = .TRUE.             !! To keep first call trace of the module (true/false)
49!$OMP THREADPRIVATE(l_first_pft_parameters)
50
51  !
52  ! VEGETATION STRUCTURE
53  !
54  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_tab       !! leaf type (1-4, unitless)
55                                                                    !! 1=broad leaved tree, 2=needle leaved tree,
56                                                                    !! 3=grass 4=bare ground
57!$OMP THREADPRIVATE(leaf_tab)
58
59  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_model  !! which phenology model is used? (tabulated) (unitless)
60!$OMP THREADPRIVATE(pheno_model)
61
62  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tree               !! Is the vegetation type a tree ? (true/false)
63!$OMP THREADPRIVATE(is_tree)
64
65  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_deciduous          !! Is PFT deciduous ? (true/false)
66!$OMP THREADPRIVATE(is_deciduous)
67
68  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_evergreen          !! Is PFT evegreen ? (true/false)
69!$OMP THREADPRIVATE(is_evergreen)
70
71  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_needleleaf         !! Is PFT needleleaf ? (true/false)
72!$OMP THREADPRIVATE(is_needleleaf)
73 
74  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_tropical           !! Is PFT tropical ? (true/false)
75!$OMP THREADPRIVATE(is_tropical)
76
77  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: natural               !! natural? (true/false)
78!$OMP THREADPRIVATE(natural)
79! dgvmjc
80  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: pasture               !! pasture? (true/false)
81!$OMP THREADPRIVATE(pasture)
82!! yidi
83  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_oilpalm            !! oil palm? (true/false)
84!$OMP THREADPRIVATE(is_oilpalm)
85  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_oilpalm_ffbharvest !! oil palm ffb harvest? (true/false)
86!$OMP THREADPRIVATE(is_oilpalm_ffbharvest)
87!! yidi
88! end dgvmjc
89  CHARACTER(len=5), ALLOCATABLE, SAVE, DIMENSION(:) :: type_of_lai  !! Type of behaviour of the LAI evolution algorithm
90                                                                    !! for each vegetation type.
91                                                                    !! Value of type_of_lai, one for each vegetation type :
92                                                                    !! mean or interp
93!$OMP THREADPRIVATE(type_of_lai)
94
95  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: veget_ori_fixed_test_1 !! Value for veget_ori for tests in 0-dim simulations
96                                                                         !! (0-1, unitless)
97!$OMP THREADPRIVATE(veget_ori_fixed_test_1)
98
99  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimax                !! laimax for maximum lai see also type of lai
100                                                                         !! interpolation
101                                                                         !! @tex $(m^2.m^{-2})$ @endtex
102!$OMP THREADPRIVATE(llaimax)
103
104  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: llaimin                !! laimin for minimum lai see also type of lai
105                                                                         !! interpolation
106                                                                         !! @tex $(m^2.m^{-2})$ @endtex
107!$OMP THREADPRIVATE(llaimin)
108
109  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: height_presc           !! prescribed height of vegetation.(m)
110                                                                         !! Value for height_presc : one for each vegetation type
111!$OMP THREADPRIVATE(height_presc)
112
113  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: z0_over_height        !! Factor to calculate roughness height from
114                                                                        !! vegetation height (unitless)   
115!$OMP THREADPRIVATE(z0_over_height)
116
117  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ratio_z0m_z0h         !! Ratio between z0m and z0h
118!$OMP THREADPRIVATE(ratio_z0m_z0h)
119
120  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) ::  rveg_pft              !! Potentiometer to set vegetation resistance (unitless)
121                                                                         !! Nathalie on March 28th, 2006 - from Fred Hourdin,
122!$OMP THREADPRIVATE(rveg_pft)
123
124  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sla                    !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
125!$OMP THREADPRIVATE(sla)
126
127  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: availability_fact      !! calculate dynamic mortality in lpj_gap
128!$OMP THREADPRIVATE(availability_fact)
129
130  !
131  ! EVAPOTRANSPIRATION (sechiba)
132  !
133  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rstruct_const          !! Structural resistance.
134                                                                         !! Value for rstruct_const : one for each vegetation type
135                                                                         !! @tex $(s.m^{-1})$ @endtex
136!$OMP THREADPRIVATE(rstruct_const)
137
138  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kzero                  !! A vegetation dependent constant used in the calculation
139                                                                         !! of the surface resistance.
140                                                                         !! Value for kzero one for each vegetation type
141                                                                         !! @tex $(kg.m^2.s^{-1})$ @endtex
142!$OMP THREADPRIVATE(kzero)
143
144  !
145  ! WATER (sechiba)
146  !
147  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: wmax_veg  !! Volumetric available soil water capacity in each PFT
148                                                            !! @tex $(kg.m^{-3} of soil)$ @endtex
149!$OMP THREADPRIVATE(wmax_veg)
150
151  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: humcste   !! Root profile description for the different vegetation types.
152                                                            !! These are the factor in the exponential which gets
153                                                            !! the root density as a function of depth
154                                                            !! @tex $(m^{-1})$ @endtex
155!$OMP THREADPRIVATE(humcste)
156
157  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: throughfall_by_pft !! Percent by PFT of precip that is not intercepted by the canopy
158!$OMP THREADPRIVATE(throughfall_by_pft)
159
160  !
161  ! ALBEDO (sechiba)
162  !
163  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_vis !! Minimum snow albedo value for each vegetation type
164                                                                 !! after aging (dirty old snow), visible albedo (unitless)
165                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
166!$OMP THREADPRIVATE(snowa_aged_vis)
167
168  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_aged_nir !! Minimum snow albedo value for each vegetation type
169                                                                 !! after aging (dirty old snow), near infrared albedo (unitless)
170                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
171!$OMP THREADPRIVATE(snowa_aged_nir)
172
173  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_vis  !! Decay rate of snow albedo value for each vegetation type
174                                                                 !! as it will be used in condveg_snow, visible albedo (unitless)
175                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
176!$OMP THREADPRIVATE(snowa_dec_vis)
177
178  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: snowa_dec_nir  !! Decay rate of snow albedo value for each vegetation type
179                                                                 !! as it will be used in condveg_snow, near infrared albedo (unitless)
180                                                                 !! Source : Values are from the Thesis of S. Chalita (1992)
181!$OMP THREADPRIVATE(snowa_dec_nir)
182
183  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_vis  !! leaf albedo of vegetation type, visible albedo (unitless)
184!$OMP THREADPRIVATE(alb_leaf_vis)
185
186  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alb_leaf_nir  !! leaf albedo of vegetation type, near infrared albedo (unitless)
187!$OMP THREADPRIVATE(alb_leaf_nir)
188  !chaoyue+
189  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: permafrost_veg_exists!! leaf albedo of vegetation type, near infrared albedo (unitless)
190!$OMP THREADPRIVATE(permafrost_veg_exists)
191  !chaoyue-
192
193  !
194  ! SOIL - VEGETATION
195  !
196  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pref_soil_veg      !! Table which contains the correlation between the soil
197                                                                        !! types and vegetation type. Two modes exist :
198                                                                        !! 1) pref_soil_veg = 0 then we have an equidistribution
199                                                                        !!    of vegetation on soil types
200                                                                        !! 2) Else for each pft the prefered soil type is given :
201                                                                        !!    1=sand, 2=loan, 3=clay
202                                                                        !! This variable is initialized in slowproc.(1-3, unitless)
203!$OMP THREADPRIVATE(pref_soil_veg)
204
205  !
206  ! PHOTOSYNTHESIS
207  !
208  !-
209  ! 1. CO2
210  !-
211  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: is_c4             !! flag for C4 vegetation types (true/false)
212!$OMP THREADPRIVATE(is_c4)
213
214  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: vcmax_fix     !! values used for vcmax when STOMATE is not activated
215                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
216!$OMP THREADPRIVATE(vcmax_fix)
217
218  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: downregulation_co2_coeff !! Coefficient for CO2 downregulation (unitless)
219!$OMP THREADPRIVATE(downregulation_co2_coeff)
220
221  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmC         !! Energy of activation for KmC (J mol-1)
222!$OMP THREADPRIVATE(E_KmC)                                                               
223  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_KmO         !! Energy of activation for KmO (J mol-1)
224!$OMP THREADPRIVATE(E_KmO)         
225REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Sco           !! Energy of activation for Sco (J mol-1)
226!$OMP THREADPRIVATE(E_Sco)           
227  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gamma_star  !! Energy of activation for gamma_star (J mol-1)
228!$OMP THREADPRIVATE(E_gamma_star)   
229  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Vcmax       !! Energy of activation for Vcmax (J mol-1)
230!$OMP THREADPRIVATE(E_Vcmax)                                                             
231  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Jmax        !! Energy of activation for Jmax (J mol-1)
232!$OMP THREADPRIVATE(E_Jmax)
233  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: aSV           !! a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1)
234!$OMP THREADPRIVATE(aSV)   
235  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: bSV           !! b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1 °C-1)
236!$OMP THREADPRIVATE(bSV)
237  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_min   !! minimum photosynthesis temperature (deg C)
238!$OMP THREADPRIVATE(tphoto_min)
239  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tphoto_max   !! maximum photosynthesis temperature (deg C)
240!$OMP THREADPRIVATE(tphoto_max)
241  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: aSJ           !! a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1)
242!$OMP THREADPRIVATE(aSJ)   
243  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: bSJ           !! b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1 °C-1)
244!$OMP THREADPRIVATE(bSJ)   
245  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Vcmax       !! Energy of deactivation for Vcmax (J mol-1)
246!$OMP THREADPRIVATE(D_Vcmax)                     
247  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_Jmax        !! Energy of deactivation for Jmax (J mol-1)
248!$OMP THREADPRIVATE(D_Jmax)                           
249
250  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_gm          !! Energy of activation for gm (J mol-1)
251!$OMP THREADPRIVATE(E_gm)                                       
252  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S_gm          !! Entropy term for gm (J K-1 mol-1)
253!$OMP THREADPRIVATE(S_gm)                                       
254  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: D_gm          !! Energy of deactivation for gm (J mol-1)
255!$OMP THREADPRIVATE(D_gm)                                       
256         
257  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: E_Rd          !! Energy of activation for Rd (J mol-1)
258!$OMP THREADPRIVATE(E_Rd)                                     
259  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Vcmax25       !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
260                                                                !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
261!$OMP THREADPRIVATE(Vcmax25)
262  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: arJV          !! a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1)
263!$OMP THREADPRIVATE(arJV)
264  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: brJV          !! b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1)
265!$OMP THREADPRIVATE(brJV)
266  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmC25         !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
267!$OMP THREADPRIVATE(KmC25)                                     
268  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: KmO25         !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
269!$OMP THREADPRIVATE(KmO25)               
270REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Sco25           !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
271!$OMP THREADPRIVATE(Sco25)     
272  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gamma_star25  !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
273!$OMP THREADPRIVATE(gamma_star25)       
274  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gm25         !! Mesophyll diffusion conductance at 25°C (mol m−2 s−1 bar−1)
275!$OMP THREADPRIVATE(gm25)     
276  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: a1            !! Empirical factor involved in the calculation of fvpd (-)
277!$OMP THREADPRIVATE(a1)                                       
278  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: b1            !! Empirical factor involved in the calculation of fvpd (-)
279!$OMP THREADPRIVATE(b1)                                       
280  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: g0            !! Residual stomatal conductance when irradiance approaches zero (mol m−2 s−1 bar−1)
281!$OMP THREADPRIVATE(g0)                                       
282  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: h_protons     !! Number of protons required to produce one ATP (mol mol-1)
283!$OMP THREADPRIVATE(h_protons)                                 
284  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpsir         !! Fraction of PSII e− transport rate partitioned to the C4 cycle (-)
285!$OMP THREADPRIVATE(fpsir)                                         
286  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fQ            !! Fraction of electrons at reduced plastoquinone that follow the Q-cycle (-) - Values for C3 platns are not used
287!$OMP THREADPRIVATE(fQ)                                       
288  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fpseudo       !! Fraction of electrons at PSI that follow  pseudocyclic transport (-) - Values for C3 platns are not used
289!$OMP THREADPRIVATE(fpseudo)                                   
290  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: kp            !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
291!$OMP THREADPRIVATE(kp)                                       
292  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha         !! Fraction of PSII activity in the bundle sheath (-)
293!$OMP THREADPRIVATE(alpha)                                     
294  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gbs           !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
295!$OMP THREADPRIVATE(gbs)                                       
296  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: theta         !! Convexity factor for response of J to irradiance (-)
297!$OMP THREADPRIVATE(theta)                                     
298  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alpha_LL      !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
299!$OMP THREADPRIVATE(alpha_LL)
300  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_vcmax  !! Stress on vcmax
301!$OMP THREADPRIVATE(stress_vcmax)
302  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gs     !! Stress on vcmax
303!$OMP THREADPRIVATE(stress_gs)
304  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: stress_gm     !! Stress on vcmax
305!$OMP THREADPRIVATE(stress_gm)
306
307  !-
308  ! 2. Stomate
309  !-
310  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff     !! extinction coefficient of the Monsi&Saeki relationship (1953)
311                                                                !! (unitless)
312!$OMP THREADPRIVATE(ext_coeff)
313  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ext_coeff_vegetfrac     !! extinction coefficient used for the calculation of the
314                                                                !! bare soil fraction (unitless)
315!$OMP THREADPRIVATE(ext_coeff_vegetfrac)
316
317
318  !
319  ! ALLOCATION (stomate)
320  !
321  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: R0            !! Default root allocation (0-1, unitless)
322!$OMP THREADPRIVATE(R0)
323  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S0            !! Default sapwood allocation (0-1, unitless)
324!$OMP THREADPRIVATE(S0)
325  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: L0            !! Default leaf allocation (0-1, unitless)
326!$OMP THREADPRIVATE(L0)
327
328
329  !
330  ! RESPIRATION (stomate)
331  !
332  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: frac_growthresp  !! fraction of GPP which is lost as growth respiration
333
334!$OMP THREADPRIVATE(frac_growthresp)
335
336  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: maint_resp_slope  !! slope of maintenance respiration coefficient
337                                                                      !! (1/K, 1/K^2, 1/K^3), used in the code
338!$OMP THREADPRIVATE(maint_resp_slope)
339
340  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_c  !! slope of maintenance respiration coefficient (1/K),
341                                                                      !! constant c of aT^2+bT+c , tabulated
342!$OMP THREADPRIVATE(maint_resp_slope_c)
343
344  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_b  !! slope of maintenance respiration coefficient (1/K),
345                                                                      !! constant b of aT^2+bT+c , tabulated
346!$OMP THREADPRIVATE(maint_resp_slope_b)
347
348  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maint_resp_slope_a  !! slope of maintenance respiration coefficient (1/K),
349                                                                      !! constant a of aT^2+bT+c , tabulated
350!$OMP THREADPRIVATE(maint_resp_slope_a)
351
352  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: coeff_maint_zero  !! maintenance respiration coefficient at 0 deg C,
353                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
354!$OMP THREADPRIVATE(coeff_maint_zero)
355
356  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_leaf        !! maintenance respiration coefficient at 0 deg C,
357                                                                      !! for leaves, tabulated
358                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
359!$OMP THREADPRIVATE(cm_zero_leaf)
360
361  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapabove    !! maintenance respiration coefficient at 0 deg C,
362                                                                      !! for sapwood above, tabulated
363                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
364!$OMP THREADPRIVATE(cm_zero_sapabove)
365
366  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_sapbelow    !! maintenance respiration coefficient at 0 deg C,
367                                                                      !! for sapwood below, tabulated
368                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
369!$OMP THREADPRIVATE(cm_zero_sapbelow)
370
371  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartabove  !! maintenance respiration coefficient at 0 deg C
372                                                                      !! for heartwood above, tabulated
373                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
374!$OMP THREADPRIVATE(cm_zero_heartabove)
375
376  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_heartbelow  !! maintenance respiration coefficient at 0 deg C,
377                                                                      !! for heartwood below, tabulated
378                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
379!$OMP THREADPRIVATE(cm_zero_heartbelow)
380
381  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_root        !! maintenance respiration coefficient at 0 deg C,
382                                                                      !! for roots, tabulated
383                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
384!$OMP THREADPRIVATE(cm_zero_root)
385
386  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_fruit       !! maintenance respiration coefficient  at 0 deg C,
387                                                                      !! for fruits, tabulated
388                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
389!$OMP THREADPRIVATE(cm_zero_fruit)
390
391  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cm_zero_carbres     !! maintenance respiration coefficient at 0 deg C,
392                                                                      !! for carbohydrate reserve, tabulated
393                                                                      !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
394!$OMP THREADPRIVATE(cm_zero_carbres)
395
396 
397  !
398  ! FIRE (stomate)
399  !
400  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: flam              !! flamability : critical fraction of water holding
401                                                                    !! capacity (0-1, unitless)
402!$OMP THREADPRIVATE(flam)
403
404  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: resist            !! fire resistance (0-1, unitless)
405!$omp threadprivate(resist)
406  !spitfire
407  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: dens_fuel         !! fuel bulk density
408!$omp threadprivate(dens_fuel)
409  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: f_sh              !! scorch height parameter for crown fire
410!$omp threadprivate(f_sh)
411  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: crown_length      !! crown length
412!$omp threadprivate(crown_length)
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: BTpar1            !! Bark thickness parameter
414!$omp threadprivate(BTpar1)
415  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: BTpar2            !! Bark thickness parameter
416!$omp threadprivate(BTpar2)
417  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: r_ck              !! parameter for postfire mortality as a result of crown damage
418!$omp threadprivate(r_ck)
419  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: p_ck              !! parameter for postfire mortality as a result of crown damage
420!$omp threadprivate(p_ck)
421  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_CO2            !! emissions factors
422!$omp threadprivate(ef_CO2)
423  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_CO
424!$omp threadprivate(ef_CO)
425  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_CH4
426!$omp threadprivate(ef_CH4)
427  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_VOC
428!$omp threadprivate(ef_VOC)
429  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_TPM
430!$omp threadprivate(ef_TPM)
431  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_NOx
432!$omp threadprivate(ef_NOx)
433  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: me                !! flammability threshold
434!$omp threadprivate(me)
435  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fire_max_cf_100hr       !! Maximum combustion fraction for 100hr and 1000hr fuel for different PFTs
436!$omp threadprivate(fire_max_cf_100hr)
437  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fire_max_cf_1000hr       !! Maximum combustion fraction for 100hr and 1000hr fuel for different PFTs
438!$omp threadprivate(fire_max_cf_1000hr)
439  !endspit
440
441  !
442  ! grassland management
443  !
444  !gmjc
445  ! Is the vegetation type a managed grassland ?
446  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_manag
447!$omp threadprivate(is_grassland_manag)
448  ! Is the vegetation type a cut grassland for management adaptation ?
449  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_cut
450!$omp threadprivate(is_grassland_cut)
451  ! Is the vegetation type a grazed grassland for management adaptation ?
452  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_grazed
453!$omp threadprivate(is_grassland_grazed)
454  ! Management Intensity reading in MANAGEMENT_MAP
455  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: management_intensity
456!$omp threadprivate(management_intensity)
457  ! Start year of management reading in MANAGEMENT_MAP & GRAZING_MAP
458  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: management_start
459!$omp threadprivate(management_start)
460  ! Start year of N deposition reading in DEPOSITION_MAP
461  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: deposition_start
462!$omp threadprivate(deposition_start)
463  ! Number of year that management should be read
464  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nb_year_management
465!$omp threadprivate(nb_year_management)
466  ! maximum specific leaf area (m**2/gC)
467  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION(:) :: sla_max
468!$omp threadprivate(sla_max)
469  ! minimum specific leaf area (m**2/gC)
470  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)  :: sla_min
471!$omp threadprivate(sla_min)
472  !end gmjc
473
474  ! Is the vegetation type bioenergy?
475  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_bioe1
476!$OMP THREADPRIVATE(is_bioe1)
477
478  !
479  ! FLUX - LUC (Land Use Change)
480  !
481  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
482!$OMP THREADPRIVATE(coeff_lcchange_1)
483
484  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
485!$OMP THREADPRIVATE(coeff_lcchange_10)
486
487  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
488!$OMP THREADPRIVATE(coeff_lcchange_100)
489 
490  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_indwood_1   !! Coeff of biomass export for the year (unitless)
491!$OMP THREADPRIVATE(coeff_indwood_1)
492
493  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_indwood_10  !! Coeff of biomass export for the decade (unitless)
494!$OMP THREADPRIVATE(coeff_indwood_10)
495
496  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_indwood_100 !! Coeff of biomass export for the century (unitless)
497!$OMP THREADPRIVATE(coeff_indwood_100)
498 
499  !
500  ! PHENOLOGY
501  !
502  !-
503  ! 1. Stomate
504  !-
505  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
506!$OMP THREADPRIVATE(lai_max_to_happy)
507
508  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
509!$OMP THREADPRIVATE(lai_max)
510
511  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
512                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
513                                                                    !! 3=raingreen,  4=perennial
514                                                                    !! For the moment, the bare ground phenotype is not managed,
515                                                                    !! so it is considered as "evergreen"
516!$OMP THREADPRIVATE(pheno_type)
517
518  !-
519  ! 2. Leaf Onset
520  !-
521  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
522!$OMP THREADPRIVATE(pheno_gdd_crit)
523
524  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
525                                                                     !! constant c of aT^2+bT+c (unitless)
526!$OMP THREADPRIVATE(pheno_gdd_crit_c)
527
528  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
529                                                                     !! constant b of aT^2+bT+c (unitless)
530!$OMP THREADPRIVATE(pheno_gdd_crit_b)
531
532  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
533                                                                     !! constant a of aT^2+bT+c (unitless)
534!$OMP THREADPRIVATE(pheno_gdd_crit_a)
535
536  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
537!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
538
539  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
540!$OMP THREADPRIVATE(ngd_crit)
541
542  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
543                                                                     !! in phenology (C)
544!$OMP THREADPRIVATE(ncdgdd_temp)
545
546  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
547                                                                     !! (0-1, unitless)
548!$OMP THREADPRIVATE(hum_frac)
549
550  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
551!$OMP THREADPRIVATE(hum_min_time)
552
553  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! sapwood -> heartwood conversion time (days)
554!$OMP THREADPRIVATE(tau_sap)
555
556  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit lifetime (days)
557!$OMP THREADPRIVATE(tau_fruit)
558
559  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit  !! time to attain the initial foliage using the carbohydrate reserve
560!$OMP THREADPRIVATE(tau_leafinit)
561
562  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
563                                                                     !! into reserve (0-1, unitless)
564!$OMP THREADPRIVATE(ecureuil)
565
566  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
567!$OMP THREADPRIVATE(alloc_min)
568
569  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
570!$OMP THREADPRIVATE(alloc_max)
571
572  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
573!$OMP THREADPRIVATE(demi_alloc)
574!! yidi
575  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ftophy_min          !! MIN - allocation FFB/PHYTOMER = f(phytomer_age) - yidi
576!$OMP THREADPRIVATE(ftophy_min)
577
578  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ftophy_max          !! MAX - allocation FFB/PHYTOMER = f(phytomer_age) - yidi
579!$OMP THREADPRIVATE(ftophy_max)
580
581  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phyalloc_max          !! MAX allocation PHYTOMER/SAPAB = f(phytomer_age) - yidi
582!$OMP THREADPRIVATE(phyalloc_max)
583
584  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phyalloc_min          !! MIN allocation PHYTOMER/SAPAB = f(phytomer_age) - yidi
585!$OMP THREADPRIVATE(phyalloc_min)
586
587  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: turn_coeff          !! turn coefficient of old leaves when phytomer pruned - yidi
588!$OMP THREADPRIVATE(turn_coeff)
589!! yidi
590
591  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab       !! leaf longevity, tabulated (??units??)
592!$OMP THREADPRIVATE(leaflife_tab)
593
594  !-
595  ! 3. Senescence
596  !-
597  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
598!$OMP THREADPRIVATE(leaffall)
599
600  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit           !! critical leaf age,tabulated (days)
601!$OMP THREADPRIVATE(leafagecrit)
602
603!! yidi
604  !REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phytomerleafagecrit   !! critical leaf age for each phytomer,tabulated (days)
605!$OMP THREADPRIVATE(phytomerleafagecrit)
606
607  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phytomeragecrit       !! critical phytomer age,tabulated (days)
608!$OMP THREADPRIVATE(phytomeragecrit)
609
610  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ffbharvestagecrit     !! critical ffb harvest time,tabulated (days)
611!$OMP THREADPRIVATE(ffbharvestagecrit)
612
613  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ffballocmin    !! critical ffb harvest time,tabulated (days)
614!$OMP THREADPRIVATE(ffballocmin)
615
616  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ffballocmax    !! critical ffb harvest time,tabulated (days)
617!$OMP THREADPRIVATE(ffballocmax)
618!! yidi
619
620  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
621                                                                        !! List of avaible types of senescence :
622                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
623!$OMP THREADPRIVATE(senescence_type)
624
625  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
626                                                                        !! (0-1, unitless)
627!$OMP THREADPRIVATE(senescence_hum)
628
629  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
630                                                                        !! no humidity-related senescence (0-1, unitless)
631!$OMP THREADPRIVATE(nosenescence_hum)
632
633  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
634!$OMP THREADPRIVATE(max_turnover_time)
635
636  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
637!$OMP THREADPRIVATE(min_turnover_time)
638
639  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
640!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
641
642  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
643                                                                        !! used in the code
644!$OMP THREADPRIVATE(senescence_temp)
645
646  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
647                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
648!$OMP THREADPRIVATE(senescence_temp_c)
649
650  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
651                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
652!$OMP THREADPRIVATE(senescence_temp_b)
653
654  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
655                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
656!$OMP THREADPRIVATE(senescence_temp_a)
657
658  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
659!$OMP THREADPRIVATE(gdd_senescence)
660
661  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: always_init               !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
662!$OMP THREADPRIVATE(always_init)
663
664  !
665  ! DGVM
666  !
667
668  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
669!$OMP THREADPRIVATE(residence_time)
670
671  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
672!$OMP THREADPRIVATE(tmin_crit)
673
674  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
675!$OMP THREADPRIVATE(tcm_crit)
676
677  !
678  ! Biogenic Volatile Organic Compounds
679  !
680
681  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
682                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
683!$OMP THREADPRIVATE(em_factor_isoprene)
684
685  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
686                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
687!$OMP THREADPRIVATE(em_factor_monoterpene)
688
689  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
690!$OMP THREADPRIVATE(LDF_mono)
691  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
692!$OMP THREADPRIVATE(LDF_sesq)
693  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
694!$OMP THREADPRIVATE(LDF_meth)
695  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
696!$OMP THREADPRIVATE(LDF_acet)
697  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
698                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
699!$OMP THREADPRIVATE(em_factor_apinene)
700
701  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
702                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
703!$OMP THREADPRIVATE(em_factor_bpinene)
704
705  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
706                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
707!$OMP THREADPRIVATE(em_factor_limonene)
708
709  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
710                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
711!$OMP THREADPRIVATE(em_factor_myrcene)
712
713  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
714                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
715!$OMP THREADPRIVATE(em_factor_sabinene)
716
717  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
718                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
719!$OMP THREADPRIVATE(em_factor_camphene)
720
721  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
722                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
723!$OMP THREADPRIVATE(em_factor_3carene)
724
725  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
726                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
727!$OMP THREADPRIVATE(em_factor_tbocimene)
728
729  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
730                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
731!$OMP THREADPRIVATE(em_factor_othermonot)
732
733  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
734                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
735!$OMP THREADPRIVATE(em_factor_sesquiterp)
736
737  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
738!$OMP THREADPRIVATE(beta_mono)
739  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
740!$OMP THREADPRIVATE(beta_sesq)
741  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
742!$OMP THREADPRIVATE(beta_meth)
743  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
744!$OMP THREADPRIVATE(beta_acet)
745  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
746!$OMP THREADPRIVATE(beta_oxyVOC)
747
748  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
749                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
750!$OMP THREADPRIVATE(em_factor_ORVOC)
751
752  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
753                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
754!$OMP THREADPRIVATE(em_factor_OVOC)
755
756  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
757                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
758!$OMP THREADPRIVATE(em_factor_MBO)
759
760  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
761                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
762!$OMP THREADPRIVATE(em_factor_methanol)
763
764  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
765                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
766!$OMP THREADPRIVATE(em_factor_acetone)
767
768  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
769                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
770!$OMP THREADPRIVATE(em_factor_acetal)
771
772  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
773                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
774!$OMP THREADPRIVATE(em_factor_formal)
775
776  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
777                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
778!$OMP THREADPRIVATE(em_factor_acetic)
779
780  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
781                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
782!$OMP THREADPRIVATE(em_factor_formic)
783
784  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
785                                                                           !! exponential dependancy factor for wet soils
786                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
787!$OMP THREADPRIVATE(em_factor_no_wet)
788
789  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
790                                                                           !! exponential dependancy factor for dry soils
791                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
792!$OMP THREADPRIVATE(em_factor_no_dry)
793
794  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
795!$OMP THREADPRIVATE(Larch)
796
797  !
798  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
799  !
800
801  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
802                                                                !! @tex $(m^2.m^{-2})$ @endtex
803!$OMP THREADPRIVATE(lai_initmin)
804
805  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
806!$OMP THREADPRIVATE(bm_sapl)
807
808  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
809!$OMP THREADPRIVATE(migrate)
810
811  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
812                                                                !! increases (m)
813!$OMP THREADPRIVATE(maxdia)
814
815  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
816!$OMP THREADPRIVATE(cn_sapl)
817
818  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
819!$OMP THREADPRIVATE(leaf_timecst)
820!! yidi
821  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: phytomer_timecst  !! time constant for phytomer age discretisation (days)
822!$OMP THREADPRIVATE(phytomer_timecst)
823!! yidi
824
825!
826! WETLAND CH4 methane
827!
828!pss+
829  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sdepth_v  !! soil depth for wetland vegetation types
830!$OMP THREADPRIVATE(sdepth_v)
831
832  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rdepth_v  !! rooting depth for wetland vegetation types
833!$OMP THREADPRIVATE(rdepth_v)
834
835  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tveg_v  !! Plant mediated transport efficiency
836!$OMP THREADPRIVATE(tveg_v)
837!pss-
838
839!!!! cropland parameters
840
841
842  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: irrig_threshold   !! Value for stress threshold to start irrigation (0-1, vegstress)
843!$OMP THREADPRIVATE(irrig_threshold)
844  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: irrig_fulfill     !! Value for fulfilling irrigation demand (0-1)
845!$OMP THREADPRIVATE(irrig_fulfill)
846
847  ! 4. STICS
848  ! 4.0
849  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: ok_LAIdev     !! flag for using the STICS-LAIdev module   
850!$OMP THREADPRIVATE(ok_LAIdev)
851  ! 4.1 LAIdev module
852  CHARACTER(len=3), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeplante
853!$OMP THREADPRIVATE(SP_codeplante)
854  CHARACTER(len=3), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stade0
855!$OMP THREADPRIVATE(SP_stade0)
856  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iplt0
857!$OMP THREADPRIVATE(SP_iplt0)
858  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iplt1
859!$OMP THREADPRIVATE(SP_iplt1)
860  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iplt2
861!$OMP THREADPRIVATE(SP_iplt2)
862  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nbox
863!$OMP THREADPRIVATE(SP_nbox)
864  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iwater 
865!$OMP THREADPRIVATE(SP_iwater)
866  CHARACTER(len=7), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codesimul
867!$OMP THREADPRIVATE(SP_codesimul)
868  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codelaitr
869!$OMP THREADPRIVATE(SP_codelaitr)
870  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_slamax
871!$OMP THREADPRIVATE(SP_slamax)
872  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_slamin
873!$OMP THREADPRIVATE(SP_slamin)
874  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeperenne    !! annual crop (1) or perennial crop (2)
875!$OMP THREADPRIVATE(SP_codeperenne)
876  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codcueille     !! harvest option: cutting (1) or picking (2)
877!$OMP THREADPRIVATE(SP_codcueille)
878  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codegdh        !! hourly (1) or daily (2) calculation of development unit
879!$OMP THREADPRIVATE(SP_codegdh)
880  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codetemp       !!
881!$OMP THREADPRIVATE(SP_codetemp)
882  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_coderetflo
883!$OMP THREADPRIVATE(SP_coderetflo)
884  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeinnact
885!$OMP THREADPRIVATE(SP_codeinnact)
886  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeh2oact
887!$OMP THREADPRIVATE(SP_codeh2oact)
888  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stressdev
889!$OMP THREADPRIVATE(SP_stressdev)
890  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_innlai
891!$OMP THREADPRIVATE(SP_innlai)
892  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_innsenes
893!$OMP THREADPRIVATE(SP_innsenes)
894  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codebfroid
895!$OMP THREADPRIVATE(SP_codebfroid)
896  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codephot
897!$OMP THREADPRIVATE(SP_codephot)
898  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codedormance
899!$OMP THREADPRIVATE(SP_codedormance)
900  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codefauche     !! option of cut modes for forage crops: yes (1), no (2)
901!$OMP THREADPRIVATE(SP_codefauche)
902  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codetempfauche !! option of the reference temperature to compute cutting sum of temperatures : upvt (1), udevair (2)
903!$OMP THREADPRIVATE(SP_codetempfauche)
904  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codlainet
905!$OMP THREADPRIVATE(SP_codlainet)
906  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeindetermin
907!$OMP THREADPRIVATE(SP_codeindetermin)
908  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeinitprec
909!$OMP THREADPRIVATE(SP_codeinitprec)
910  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_culturean 
911!$OMP THREADPRIVATE(SP_culturean)
912  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_jvc
913!$OMP THREADPRIVATE(SP_jvc)
914  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tfroid
915!$OMP THREADPRIVATE(SP_tfroid)
916  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_ampfroid 
917!$OMP THREADPRIVATE(SP_ampfroid)
918  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_jvcmini
919!$OMP THREADPRIVATE(SP_jvcmini)
920  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgmin
921!$OMP THREADPRIVATE(SP_tgmin)
922  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stpltger
923!$OMP THREADPRIVATE(SP_stpltger)
924  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_profsem
925!$OMP THREADPRIVATE(SP_profsem)
926  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_propjgermin              !! minimal proportion of the duration P_nbjgerlim when the temperature is higher than the temperature threshold P_Tdmax
927!$OMP THREADPRIVATE(SP_propjgermin)
928  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tdmax
929!$OMP THREADPRIVATE(SP_tdmax)
930  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nbjgerlim              !! Threshold number of day after grain imbibition without germination lack // days
931!$OMP THREADPRIVATE(SP_nbjgerlim)
932  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_densitesem
933!$OMP THREADPRIVATE(SP_densitesem)
934  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_vigueurbat                !!  indicator of plant vigor allowing to emerge through the crust  // between 0 and 1 //
935!$OMP THREADPRIVATE(SP_vigueurbat)
936  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codepluiepoquet              !!  option to replace rainfall by irrigation at poquet depth in the case of poquet sowing // code 1/2
937!$OMP THREADPRIVATE(SP_codepluiepoquet)
938  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codehypo
939!$OMP THREADPRIVATE(SP_codehypo)
940  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_elmax
941!$OMP THREADPRIVATE(SP_elmax)
942  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_belong
943!$OMP THREADPRIVATE(SP_belong)
944  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_celong
945!$OMP THREADPRIVATE(SP_celong)
946  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nlevlim1             !! number of days after germination decreasing the emerged plants if emergence has not occur // days
947!$OMP THREADPRIVATE(SP_nlevlim1)
948  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nlevlim2             !! number of days after germination after which the emerged plants are null // days
949!$OMP THREADPRIVATE(SP_nlevlim2)
950  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codrecolte           !! harvest mode : all the plant (1) or just the fruits (2)
951!$OMP THREADPRIVATE(SP_codrecolte)
952  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_variete              !! variety number in the technical file // SD
953!$OMP THREADPRIVATE(SP_variete)
954  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codegermin           !! option of simulation of a germination phase or a delay at the beginning of the crop (1) or  direct starting (2)
955!$OMP THREADPRIVATE(SP_codegermin)
956
957  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S_codeulaivernal
958!$OMP THREADPRIVATE(S_codeulaivernal)
959  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_swfacmin
960!$OMP THREADPRIVATE(SP_swfacmin)
961  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_neffmax
962!$OMP THREADPRIVATE(SP_neffmax)
963  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nsatrat
964!$OMP THREADPRIVATE(SP_nsatrat)
965
966  ! 4.2  STICS:: LAI CALCULATION
967  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_laiplantule
968!$OMP THREADPRIVATE(SP_laiplantule)
969  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_vlaimax
970!$OMP THREADPRIVATE(SP_vlaimax)
971  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stlevamf
972!$OMP THREADPRIVATE(SP_stlevamf)
973  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stamflax
974!$OMP THREADPRIVATE(SP_stamflax)
975  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_udlaimax
976!$OMP THREADPRIVATE(SP_udlaimax)
977  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_laicomp
978!$OMP THREADPRIVATE(SP_laicomp)
979  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_adens                   !! Interplant competition parameter
980!$OMP THREADPRIVATE(SP_adens)
981  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_bdens
982!$OMP THREADPRIVATE(SP_bdens)
983  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tcxstop
984!$OMP THREADPRIVATE(SP_tcxstop)
985  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tcmax
986!$OMP THREADPRIVATE(SP_tcmax)
987  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tcmin
988!$OMP THREADPRIVATE(SP_tcmin)
989  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_dlaimax
990!$OMP THREADPRIVATE(SP_dlaimax)
991  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_dlaimin
992!$OMP THREADPRIVATE(SP_dlaimin)
993  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_pentlaimax
994!$OMP THREADPRIVATE(SP_pentlaimax)
995  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tigefeuil               !! stem (structural part)/leaf proportion // SD 
996!$OMP THREADPRIVATE(SP_tigefeuil)
997
998  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stlaxsen
999!$OMP THREADPRIVATE(SP_stlaxsen)
1000  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stsenlan
1001!$OMP THREADPRIVATE(SP_stsenlan)
1002  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stlevdrp
1003!$OMP THREADPRIVATE(SP_stlevdrp)
1004  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stflodrp
1005!$OMP THREADPRIVATE(SP_stflodrp)
1006  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stdrpmat
1007!$OMP THREADPRIVATE(SP_stdrpmat)
1008  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stdrpdes
1009!$OMP THREADPRIVATE(SP_stdrpdes)
1010 
1011  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_phyllotherme
1012!$OMP THREADPRIVATE(SP_phyllotherme)
1013  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_lai0
1014!$OMP THREADPRIVATE(SP_lai0)
1015  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tustressmin
1016!$OMP THREADPRIVATE(SP_tustressmin)
1017
1018
1019
1020  ! 4.3  STICS:: LAI SENESCENCE 
1021  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nbfgellev
1022!$OMP THREADPRIVATE(SP_nbfgellev)
1023  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_ratiodurvieI
1024!$OMP THREADPRIVATE(SP_ratiodurvieI)
1025  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_durvieF
1026!$OMP THREADPRIVATE(SP_durvieF)
1027  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_ratiosen
1028!$OMP THREADPRIVATE(SP_ratiosen)
1029  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tdmin
1030!$OMP THREADPRIVATE(SP_tdmin)
1031 
1032  ! 4.4 STICS:: F_humerac
1033
1034  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_sensrsec
1035!$OMP THREADPRIVATE(SP_sensrsec)
1036
1037  ! 4.5 STICS:: gel
1038
1039  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codgellev
1040!$OMP THREADPRIVATE(SP_codgellev)
1041  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codgeljuv
1042!$OMP THREADPRIVATE(SP_codgeljuv)
1043  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codgelveg
1044!$OMP THREADPRIVATE(SP_codgelveg)
1045  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tletale
1046!$OMP THREADPRIVATE(SP_tletale)
1047  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tdebgel
1048!$OMP THREADPRIVATE(SP_tdebgel)
1049  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgellev10
1050!$OMP THREADPRIVATE(SP_tgellev10)
1051  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgellev90
1052!$OMP THREADPRIVATE(SP_tgellev90)
1053
1054  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgeljuv10
1055!$OMP THREADPRIVATE(SP_tgeljuv10)
1056  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgeljuv90
1057!$OMP THREADPRIVATE(SP_tgeljuv90)
1058  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgelveg10
1059!$OMP THREADPRIVATE(SP_tgelveg10)
1060  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgelveg90
1061!$OMP THREADPRIVATE(SP_tgelveg90)
1062
1063
1064  ! 4.6 STICS:: Photoperiod
1065 
1066  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_sensiphot
1067!$OMP THREADPRIVATE(SP_sensiphot)
1068  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_phosat
1069!$OMP THREADPRIVATE(SP_phosat)
1070  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_phobase
1071!$OMP THREADPRIVATE(SP_phobase)
1072 
1073  ! 4.7 STICS:: carbon allocation
1074 
1075  CHARACTER(len=3), ALLOCATABLE, SAVE, DIMENSION(:)   :: SP_stoprac
1076!$OMP THREADPRIVATE(SP_stoprac)
1077  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_zracplantule
1078!$OMP THREADPRIVATE(SP_zracplantule)
1079  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codtrophrac
1080!$OMP THREADPRIVATE(SP_codtrophrac)
1081  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracpermax
1082!$OMP THREADPRIVATE(SP_repracpermax)
1083  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracpermin
1084!$OMP THREADPRIVATE(SP_repracpermin)
1085  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_krepracperm
1086!$OMP THREADPRIVATE(SP_krepracperm)
1087  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracseumax
1088!$OMP THREADPRIVATE(SP_repracseumax)
1089  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracseumin
1090!$OMP THREADPRIVATE(SP_repracseumin)
1091  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_krepracseu
1092!$OMP THREADPRIVATE(SP_krepracseu)
1093  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codetemprac
1094!$OMP THREADPRIVATE(SP_codetemprac)
1095  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codedyntalle
1096!$OMP THREADPRIVATE(SP_codedyntalle)
1097  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_nbjgrain
1098!$OMP THREADPRIVATE(SP_nbjgrain)
1099  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_maxgs
1100!$OMP THREADPRIVATE(SP_maxgs)
1101  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codgelflo
1102!$OMP THREADPRIVATE(SP_codgelflo)
1103  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tgelflo10
1104!$OMP THREADPRIVATE(SP_tgelflo10)
1105  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tgelflo90
1106!$OMP THREADPRIVATE(SP_tgelflo90)
1107  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_cgrain
1108!$OMP THREADPRIVATE(SP_cgrain)
1109  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_cgrainv0
1110!$OMP THREADPRIVATE(SP_cgrainv0)
1111  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_nbgrmax
1112!$OMP THREADPRIVATE(SP_nbgrmax)
1113  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_nbgrmin
1114!$OMP THREADPRIVATE(SP_nbgrmin)
1115  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codazofruit
1116!$OMP THREADPRIVATE(SP_codazofruit)
1117  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codeir
1118!$OMP THREADPRIVATE(SP_codeir)
1119  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_vitircarb
1120!$OMP THREADPRIVATE(SP_vitircarb)
1121  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_irmax
1122!$OMP THREADPRIVATE(SP_irmax)
1123  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_vitircarbT
1124!$OMP THREADPRIVATE(SP_vitircarbT)
1125  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codetremp
1126!$OMP THREADPRIVATE(SP_codetremp)
1127  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tminremp
1128!$OMP THREADPRIVATE(SP_tminremp)
1129  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tmaxremp
1130!$OMP THREADPRIVATE(SP_tmaxremp)
1131  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_pgrainmaxi
1132!$OMP THREADPRIVATE(SP_pgrainmaxi)
1133
1134!! for  dynamic nitrogen processes
1135
1136LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: SP_DY_INN     !! flag for activating the dynamic nitrogen processes 
1137!$OMP THREADPRIVATE(SP_DY_INN)
1138
1139REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_avenfert
1140!$OMP THREADPRIVATE(SP_avenfert)
1141
1142!!!! end cropland parameters, xuhui
1143
1144
1145! STOMATE - Age classes
1146
1147  INTEGER(i_std), SAVE                            :: nvmap          !! The number of PFTs we have if we ignore age classes.
1148                                                                    !! @tex $-$ @endtex
1149!$OMP THREADPRIVATE(nvmap)
1150  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: agec_group     !! The age class group that this PFT belongs to.
1151                                                                    !! If you're not using age classes, this will just be
1152                                                                    !! set to the number of the PFT and should be ignored
1153                                                                    !! in the code.
1154                                                                    !! @tex $-$ @endtex
1155!$OMP THREADPRIVATE(agec_group)
1156  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: age_class_bound!! The age class bounds used to allow age class to move
1157                                                                    !! to next one.
1158!$OMP THREADPRIVATE(age_class_bound)
1159! I do not like the location of these next two variables.  They are computed
1160! after agec_group is read in.  Ideally, they would be passed around
1161! as arguments or in a structure, since they are not really
1162! parameters read in from the input file.
1163  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: start_index    !! Gives the index that this real PFT starts
1164                                                                    !! on, ignoring age classes
1165                                                                    !! @tex $-$ @endtex
1166!$OMP THREADPRIVATE(start_index)
1167  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nagec_pft      !! The number of age classes for each PFT.
1168                                                                    !! @tex $-$ @endtex
1169!$OMP THREADPRIVATE(nagec_pft)
1170END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.