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

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

Biochar version

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