source: branches/publications/ORCHIDEE_gmd_2018_MICT-LEAK/src_parameters/pft_parameters_var.f90 @ 7442

Last change on this file since 7442 was 4977, checked in by simon.bowring, 6 years ago

Currently running (13/02/2018) version includes all necessarily changes to include DOC in MICT code... further parametrisation necessary to equate soil pools with those of normal forcesoil restarts

  • Property svn:keywords set to Date Revision
File size: 60.5 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  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: f_sh              !! scorch height parameter for crown fire
402  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: crown_length      !! crown length
403  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: BTpar1            !! Bark thickness parameter
404  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: BTpar2            !! Bark thickness parameter
405  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: r_ck              !! parameter for postfire mortality as a result of crown damage
406  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: p_ck              !! parameter for postfire mortality as a result of crown damage
407  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_CO2            !! emissions factors
408  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_CO
409  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_CH4
410  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_VOC
411  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_TPM
412  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ef_NOx
413  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: me                !! flammability threshold
414  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fire_max_cf_100hr       !! Maximum combustion fraction for 100hr and 1000hr fuel for different PFTs
415  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: fire_max_cf_1000hr       !! Maximum combustion fraction for 100hr and 1000hr fuel for different PFTs
416  !endspit
417
418  !
419  ! grassland management
420  !
421  !gmjc
422  ! Is the vegetation type a managed grassland ?
423  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_manag
424  ! Is the vegetation type a cut grassland for management adaptation ?
425  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_cut
426  ! Is the vegetation type a grazed grassland for management adaptation ?
427  LOGICAL,ALLOCATABLE, SAVE, DIMENSION (:) :: is_grassland_grazed
428  ! Management Intensity reading in MANAGEMENT_MAP
429  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: management_intensity
430  ! Start year of management reading in MANAGEMENT_MAP & GRAZING_MAP
431  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: management_start
432  ! Start year of N deposition reading in DEPOSITION_MAP
433  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: deposition_start
434  ! Number of year that management should be read
435  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nb_year_management
436  ! maximum specific leaf area (m**2/gC)
437  REAL(r_std),  ALLOCATABLE, SAVE, DIMENSION(:) :: sla_max
438  ! minimum specific leaf area (m**2/gC)
439  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)  :: sla_min
440  !end gmjc
441
442  !
443  ! FLUX - LUC (Land Use Change)
444  !
445  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_1   !! Coeff of biomass export for the year (unitless)
446!$OMP THREADPRIVATE(coeff_lcchange_1)
447
448  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_10  !! Coeff of biomass export for the decade (unitless)
449!$OMP THREADPRIVATE(coeff_lcchange_10)
450
451  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: coeff_lcchange_100 !! Coeff of biomass export for the century (unitless)
452!$OMP THREADPRIVATE(coeff_lcchange_100)
453 
454 
455  !
456  ! PHENOLOGY
457  !
458  !-
459  ! 1. Stomate
460  !-
461  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max_to_happy  !! threshold of LAI below which plant uses carbohydrate reserves
462!$OMP THREADPRIVATE(lai_max_to_happy)
463
464  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_max           !! maximum LAI, PFT-specific @tex $(m^2.m^{-2})$ @endtex
465!$OMP THREADPRIVATE(lai_max)
466
467  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_type     !! type of phenology (0-4, unitless)
468                                                                    !! 0=bare ground 1=evergreen,  2=summergreen,
469                                                                    !! 3=raingreen,  4=perennial
470                                                                    !! For the moment, the bare ground phenotype is not managed,
471                                                                    !! so it is considered as "evergreen"
472!$OMP THREADPRIVATE(pheno_type)
473
474  !-
475  ! 2. Leaf Onset
476  !-
477  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: pheno_gdd_crit   !! critical gdd,tabulated (C), used in the code
478!$OMP THREADPRIVATE(pheno_gdd_crit)
479
480  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_c   !! critical gdd,tabulated (C),
481                                                                     !! constant c of aT^2+bT+c (unitless)
482!$OMP THREADPRIVATE(pheno_gdd_crit_c)
483
484  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_b   !! critical gdd,tabulated (C),
485                                                                     !! constant b of aT^2+bT+c (unitless)
486!$OMP THREADPRIVATE(pheno_gdd_crit_b)
487
488  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_gdd_crit_a   !! critical gdd,tabulated (C),
489                                                                     !! constant a of aT^2+bT+c (unitless)
490!$OMP THREADPRIVATE(pheno_gdd_crit_a)
491
492  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: pheno_moigdd_t_crit!! Monthly avearage temperature treashold used for C4 grass (C)
493!$OMP THREADPRIVATE(pheno_moigdd_t_crit)
494
495  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ngd_crit           !! critical ngd,tabulated. Threshold -5 degrees (days)
496!$OMP THREADPRIVATE(ngd_crit)
497
498  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ncdgdd_temp        !! critical temperature for the ncd vs. gdd function
499                                                                     !! in phenology (C)
500!$OMP THREADPRIVATE(ncdgdd_temp)
501
502  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_frac           !! critical humidity (relative to min/max) for phenology
503                                                                     !! (0-1, unitless)
504!$OMP THREADPRIVATE(hum_frac)
505
506  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: hum_min_time       !! minimum time elapsed since moisture minimum (days)
507!$OMP THREADPRIVATE(hum_min_time)
508
509  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_sap            !! sapwood -> heartwood conversion time (days)
510!$OMP THREADPRIVATE(tau_sap)
511
512  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_fruit          !! fruit lifetime (days)
513!$OMP THREADPRIVATE(tau_fruit)
514
515  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tau_leafinit  !! time to attain the initial foliage using the carbohydrate reserve
516!$OMP THREADPRIVATE(tau_leafinit)
517
518  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: ecureuil           !! fraction of primary leaf and root allocation put
519                                                                     !! into reserve (0-1, unitless)
520!$OMP THREADPRIVATE(ecureuil)
521
522  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_min          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
523!$OMP THREADPRIVATE(alloc_min)
524
525  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: alloc_max          !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
526!$OMP THREADPRIVATE(alloc_max)
527
528  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: demi_alloc         !! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF
529!$OMP THREADPRIVATE(demi_alloc)
530
531  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaflife_tab       !! leaf longevity, tabulated (??units??)
532!$OMP THREADPRIVATE(leaflife_tab)
533
534  !-
535  ! 3. Senescence
536  !-
537  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaffall              !! length of death of leaves,tabulated (days)
538!$OMP THREADPRIVATE(leaffall)
539
540  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leafagecrit           !! critical leaf age,tabulated (days)
541!$OMP THREADPRIVATE(leafagecrit)
542
543  CHARACTER(len=6), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_type  !! type of senescence,tabulated (unitless)
544                                                                        !! List of avaible types of senescence :
545                                                                        !! 'cold  ', 'dry   ', 'mixed ', 'none  '
546!$OMP THREADPRIVATE(senescence_type)
547
548  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_hum        !! critical relative moisture availability for senescence
549                                                                        !! (0-1, unitless)
550!$OMP THREADPRIVATE(senescence_hum)
551
552  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nosenescence_hum      !! relative moisture availability above which there is
553                                                                        !! no humidity-related senescence (0-1, unitless)
554!$OMP THREADPRIVATE(nosenescence_hum)
555
556  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: max_turnover_time     !! maximum turnover time for grasses (days)
557!$OMP THREADPRIVATE(max_turnover_time)
558
559  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_turnover_time     !! minimum turnover time for grasses (days)
560!$OMP THREADPRIVATE(min_turnover_time)
561
562  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: min_leaf_age_for_senescence  !! minimum leaf age to allow senescence g (days)
563!$OMP THREADPRIVATE(min_leaf_age_for_senescence)
564
565  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:) :: senescence_temp     !! critical temperature for senescence (C),
566                                                                        !! used in the code
567!$OMP THREADPRIVATE(senescence_temp)
568
569  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_c     !! critical temperature for senescence (C),
570                                                                        !! constant c of aT^2+bT+c , tabulated (unitless)
571!$OMP THREADPRIVATE(senescence_temp_c)
572
573  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_b     !! critical temperature for senescence (C),
574                                                                        !! constant b of aT^2+bT+c , tabulated (unitless)
575!$OMP THREADPRIVATE(senescence_temp_b)
576
577  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: senescence_temp_a     !! critical temperature for senescence (C),
578                                                                        !! constant a of aT^2+bT+c , tabulated (unitless)
579!$OMP THREADPRIVATE(senescence_temp_a)
580
581  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: gdd_senescence        !! minimum gdd to allow senescence of crops (days)
582!$OMP THREADPRIVATE(gdd_senescence)
583
584  !
585  ! DGVM
586  !
587
588  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: residence_time        !! residence time of trees (y)
589!$OMP THREADPRIVATE(residence_time)
590
591  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tmin_crit             !! critical tmin, tabulated (C)
592!$OMP THREADPRIVATE(tmin_crit)
593
594  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tcm_crit              !! critical tcm, tabulated (C)
595!$OMP THREADPRIVATE(tcm_crit)
596
597  !
598  ! Biogenic Volatile Organic Compounds
599  !
600
601  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_isoprene       !! Isoprene emission factor
602                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
603!$OMP THREADPRIVATE(em_factor_isoprene)
604
605  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_monoterpene    !! Monoterpene emission factor
606                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
607!$OMP THREADPRIVATE(em_factor_monoterpene)
608
609  REAL(r_std), SAVE :: LDF_mono                                            !! monoterpenes fraction dependancy to light
610!$OMP THREADPRIVATE(LDF_mono)
611  REAL(r_std), SAVE :: LDF_sesq                                            !! sesquiterpenes fraction dependancy to light
612!$OMP THREADPRIVATE(LDF_sesq)
613  REAL(r_std), SAVE :: LDF_meth                                            !! methanol fraction dependancy to light
614!$OMP THREADPRIVATE(LDF_meth)
615  REAL(r_std), SAVE :: LDF_acet                                            !! acetone fraction dependancy to light
616!$OMP THREADPRIVATE(LDF_acet)
617  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_apinene        !! Alfa pinene emission factor
618                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
619!$OMP THREADPRIVATE(em_factor_apinene)
620
621  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_bpinene        !! Beta pinene emission factor
622                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
623!$OMP THREADPRIVATE(em_factor_bpinene)
624
625  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_limonene       !! Limonene emission factor
626                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
627!$OMP THREADPRIVATE(em_factor_limonene)
628
629  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_myrcene        !! Myrcene emission factor
630                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
631!$OMP THREADPRIVATE(em_factor_myrcene)
632
633  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sabinene       !! Sabinene emission factor
634                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
635!$OMP THREADPRIVATE(em_factor_sabinene)
636
637  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_camphene       !! Camphene emission factor
638                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
639!$OMP THREADPRIVATE(em_factor_camphene)
640
641  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_3carene        !! 3-carene emission factor
642                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
643!$OMP THREADPRIVATE(em_factor_3carene)
644
645  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_tbocimene      !! T-beta-ocimene emission factor
646                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
647!$OMP THREADPRIVATE(em_factor_tbocimene)
648
649  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_othermonot     !! Other monoterpenes emission factor
650                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
651!$OMP THREADPRIVATE(em_factor_othermonot)
652
653  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_sesquiterp     !! Sesquiterpene emission factor
654                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
655!$OMP THREADPRIVATE(em_factor_sesquiterp)
656
657  REAL(r_std), SAVE :: beta_mono                                           !! Monoterpenes temperature dependency coefficient
658!$OMP THREADPRIVATE(beta_mono)
659  REAL(r_std), SAVE :: beta_sesq                                           !! Sesquiterpenes temperature dependency coefficient
660!$OMP THREADPRIVATE(beta_sesq)
661  REAL(r_std), SAVE :: beta_meth                                           !! Methanol temperature dependency coefficient
662!$OMP THREADPRIVATE(beta_meth)
663  REAL(r_std), SAVE :: beta_acet                                           !! Acetone temperature dependency coefficient
664!$OMP THREADPRIVATE(beta_acet)
665  REAL(r_std), SAVE :: beta_oxyVOC                                         !! Other oxygenated BVOC temperature dependency coefficient
666!$OMP THREADPRIVATE(beta_oxyVOC)
667
668  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_ORVOC          !! ORVOC emissions factor
669                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
670!$OMP THREADPRIVATE(em_factor_ORVOC)
671
672  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_OVOC           !! OVOC emissions factor
673                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
674!$OMP THREADPRIVATE(em_factor_OVOC)
675
676  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_MBO            !! MBO emissions factor
677                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
678!$OMP THREADPRIVATE(em_factor_MBO)
679
680  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_methanol       !! Methanol emissions factor
681                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
682!$OMP THREADPRIVATE(em_factor_methanol)
683
684  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetone        !! Acetone emissions factor
685                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
686!$OMP THREADPRIVATE(em_factor_acetone)
687
688  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetal         !! Acetaldehyde emissions factor
689                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
690!$OMP THREADPRIVATE(em_factor_acetal)
691
692  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formal         !! Formaldehyde emissions factor
693                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
694!$OMP THREADPRIVATE(em_factor_formal)
695
696  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_acetic         !! Acetic Acid emissions factor
697                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
698!$OMP THREADPRIVATE(em_factor_acetic)
699
700  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_formic         !! Formic Acid emissions factor
701                                                                           !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
702!$OMP THREADPRIVATE(em_factor_formic)
703
704  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_wet         !! NOx emissions factor soil emissions and
705                                                                           !! exponential dependancy factor for wet soils
706                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
707!$OMP THREADPRIVATE(em_factor_no_wet)
708
709  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: em_factor_no_dry         !! NOx emissions factor soil emissions and
710                                                                           !! exponential dependancy factor for dry soils
711                                                                           !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
712!$OMP THREADPRIVATE(em_factor_no_dry)
713
714  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: Larch                    !! Larcher 1991 SAI/LAI ratio (unitless)
715!$OMP THREADPRIVATE(Larch)
716
717  !
718  ! INTERNAL PARAMETERS USED IN STOMATE_DATA
719  !
720
721  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: lai_initmin   !! Initial lai for trees/grass
722                                                                !! @tex $(m^2.m^{-2})$ @endtex
723!$OMP THREADPRIVATE(lai_initmin)
724
725  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: bm_sapl   !! sapling biomass @tex $(gC.ind^{-1})$ @endtex
726!$OMP THREADPRIVATE(bm_sapl)
727
728  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: migrate       !! migration speed @tex $(m.year^{-1})$ @endtex
729!$OMP THREADPRIVATE(migrate)
730
731  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: maxdia        !! maximum stem diameter from which on crown area no longer
732                                                                !! increases (m)
733!$OMP THREADPRIVATE(maxdia)
734
735  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: cn_sapl       !! crown of tree when sapling  @tex $(m^2$)$ @endtex
736!$OMP THREADPRIVATE(cn_sapl)
737
738  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: leaf_timecst  !! time constant for leaf age discretisation (days)
739!$OMP THREADPRIVATE(leaf_timecst)
740
741
742!
743! WETLAND CH4 methane
744!
745!pss+
746  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: sdepth_v  !! soil depth for wetland vegetation types
747!$OMP THREADPRIVATE(sdepth_v)
748
749  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: rdepth_v  !! rooting depth for wetland vegetation types
750!$OMP THREADPRIVATE(rdepth_v)
751
752  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: tveg_v  !! Plant mediated transport efficiency
753!$OMP THREADPRIVATE(tveg_v)
754!pss-
755
756!!!! cropland parameters
757
758
759  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: irrig_threshold   !! Value for stress threshold to start irrigation (0-1, vegstress)
760!$OMP THREADPRIVATE(irrig_threshold)
761  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: irrig_fulfill     !! Value for fulfilling irrigation demand (0-1)
762!$OMP THREADPRIVATE(irrig_fulfill)
763
764  ! 4. STICS
765  ! 4.0
766  LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: ok_LAIdev     !! flag for using the STICS-LAIdev module   
767!$OMP THREADPRIVATE(ok_LAIdev)
768  ! 4.1 LAIdev module
769  CHARACTER(len=3), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeplante
770!$OMP THREADPRIVATE(SP_codeplante)
771  CHARACTER(len=3), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stade0
772!$OMP THREADPRIVATE(SP_stade0)
773  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iplt0
774!$OMP THREADPRIVATE(SP_iplt0)
775  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iplt1
776!$OMP THREADPRIVATE(SP_iplt1)
777  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iplt2
778!$OMP THREADPRIVATE(SP_iplt2)
779  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nbox
780!$OMP THREADPRIVATE(SP_nbox)
781  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_iwater 
782!$OMP THREADPRIVATE(SP_iwater)
783  CHARACTER(len=7), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codesimul
784!$OMP THREADPRIVATE(SP_codesimul)
785  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codelaitr
786!$OMP THREADPRIVATE(SP_codelaitr)
787  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_slamax
788!$OMP THREADPRIVATE(SP_slamax)
789  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_slamin
790!$OMP THREADPRIVATE(SP_slamin)
791  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeperenne    !! annual crop (1) or perennial crop (2)
792!$OMP THREADPRIVATE(SP_codeperenne)
793  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codcueille     !! harvest option: cutting (1) or picking (2)
794!$OMP THREADPRIVATE(SP_codcueille)
795  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codegdh        !! hourly (1) or daily (2) calculation of development unit
796!$OMP THREADPRIVATE(SP_codegdh)
797  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codetemp       !!
798!$OMP THREADPRIVATE(SP_codetemp)
799  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_coderetflo
800!$OMP THREADPRIVATE(SP_coderetflo)
801  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeinnact
802!$OMP THREADPRIVATE(SP_codeinnact)
803  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeh2oact
804!$OMP THREADPRIVATE(SP_codeh2oact)
805  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stressdev
806!$OMP THREADPRIVATE(SP_stressdev)
807  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_innlai
808!$OMP THREADPRIVATE(SP_innlai)
809  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_innsenes
810!$OMP THREADPRIVATE(SP_innsenes)
811  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codebfroid
812!$OMP THREADPRIVATE(SP_codebfroid)
813  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codephot
814!$OMP THREADPRIVATE(SP_codephot)
815  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codedormance
816!$OMP THREADPRIVATE(SP_codedormance)
817  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codefauche     !! option of cut modes for forage crops: yes (1), no (2)
818!$OMP THREADPRIVATE(SP_codefauche)
819  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codetempfauche !! option of the reference temperature to compute cutting sum of temperatures : upvt (1), udevair (2)
820!$OMP THREADPRIVATE(SP_codetempfauche)
821  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codlainet
822!$OMP THREADPRIVATE(SP_codlainet)
823  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeindetermin
824!$OMP THREADPRIVATE(SP_codeindetermin)
825  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codeinitprec
826!$OMP THREADPRIVATE(SP_codeinitprec)
827  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_culturean 
828!$OMP THREADPRIVATE(SP_culturean)
829  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_jvc
830!$OMP THREADPRIVATE(SP_jvc)
831  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tfroid
832!$OMP THREADPRIVATE(SP_tfroid)
833  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_ampfroid 
834!$OMP THREADPRIVATE(SP_ampfroid)
835  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_jvcmini
836!$OMP THREADPRIVATE(SP_jvcmini)
837  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgmin
838!$OMP THREADPRIVATE(SP_tgmin)
839  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stpltger
840!$OMP THREADPRIVATE(SP_stpltger)
841  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_profsem
842!$OMP THREADPRIVATE(SP_profsem)
843  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
844!$OMP THREADPRIVATE(SP_propjgermin)
845  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tdmax
846!$OMP THREADPRIVATE(SP_tdmax)
847  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nbjgerlim              !! Threshold number of day after grain imbibition without germination lack // days
848!$OMP THREADPRIVATE(SP_nbjgerlim)
849  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_densitesem
850!$OMP THREADPRIVATE(SP_densitesem)
851  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_vigueurbat                !!  indicator of plant vigor allowing to emerge through the crust  // between 0 and 1 //
852!$OMP THREADPRIVATE(SP_vigueurbat)
853  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
854!$OMP THREADPRIVATE(SP_codepluiepoquet)
855  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codehypo
856!$OMP THREADPRIVATE(SP_codehypo)
857  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_elmax
858!$OMP THREADPRIVATE(SP_elmax)
859  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_belong
860!$OMP THREADPRIVATE(SP_belong)
861  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_celong
862!$OMP THREADPRIVATE(SP_celong)
863  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nlevlim1             !! number of days after germination decreasing the emerged plants if emergence has not occur // days
864!$OMP THREADPRIVATE(SP_nlevlim1)
865  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nlevlim2             !! number of days after germination after which the emerged plants are null // days
866!$OMP THREADPRIVATE(SP_nlevlim2)
867  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codrecolte           !! harvest mode : all the plant (1) or just the fruits (2)
868!$OMP THREADPRIVATE(SP_codrecolte)
869  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_variete              !! variety number in the technical file // SD
870!$OMP THREADPRIVATE(SP_variete)
871  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)
872!$OMP THREADPRIVATE(SP_codegermin)
873
874  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: S_codeulaivernal
875!$OMP THREADPRIVATE(S_codeulaivernal)
876  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_swfacmin
877!$OMP THREADPRIVATE(SP_swfacmin)
878  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_neffmax
879!$OMP THREADPRIVATE(SP_neffmax)
880  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nsatrat
881!$OMP THREADPRIVATE(SP_nsatrat)
882
883  ! 4.2  STICS:: LAI CALCULATION
884  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_laiplantule
885!$OMP THREADPRIVATE(SP_laiplantule)
886  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_vlaimax
887!$OMP THREADPRIVATE(SP_vlaimax)
888  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stlevamf
889!$OMP THREADPRIVATE(SP_stlevamf)
890  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stamflax
891!$OMP THREADPRIVATE(SP_stamflax)
892  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_udlaimax
893!$OMP THREADPRIVATE(SP_udlaimax)
894  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_laicomp
895!$OMP THREADPRIVATE(SP_laicomp)
896  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_adens                   !! Interplant competition parameter
897!$OMP THREADPRIVATE(SP_adens)
898  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_bdens
899!$OMP THREADPRIVATE(SP_bdens)
900  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tcxstop
901!$OMP THREADPRIVATE(SP_tcxstop)
902  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tcmax
903!$OMP THREADPRIVATE(SP_tcmax)
904  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tcmin
905!$OMP THREADPRIVATE(SP_tcmin)
906  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_dlaimax
907!$OMP THREADPRIVATE(SP_dlaimax)
908  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_dlaimin
909!$OMP THREADPRIVATE(SP_dlaimin)
910  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_pentlaimax
911!$OMP THREADPRIVATE(SP_pentlaimax)
912  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tigefeuil               !! stem (structural part)/leaf proportion // SD 
913!$OMP THREADPRIVATE(SP_tigefeuil)
914
915  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stlaxsen
916!$OMP THREADPRIVATE(SP_stlaxsen)
917  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stsenlan
918!$OMP THREADPRIVATE(SP_stsenlan)
919  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stlevdrp
920!$OMP THREADPRIVATE(SP_stlevdrp)
921  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stflodrp
922!$OMP THREADPRIVATE(SP_stflodrp)
923  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stdrpmat
924!$OMP THREADPRIVATE(SP_stdrpmat)
925  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_stdrpdes
926!$OMP THREADPRIVATE(SP_stdrpdes)
927 
928  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_phyllotherme
929!$OMP THREADPRIVATE(SP_phyllotherme)
930  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_lai0
931!$OMP THREADPRIVATE(SP_lai0)
932  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tustressmin
933!$OMP THREADPRIVATE(SP_tustressmin)
934
935
936
937  ! 4.3  STICS:: LAI SENESCENCE 
938  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_nbfgellev
939!$OMP THREADPRIVATE(SP_nbfgellev)
940  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_ratiodurvieI
941!$OMP THREADPRIVATE(SP_ratiodurvieI)
942  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_durvieF
943!$OMP THREADPRIVATE(SP_durvieF)
944  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_ratiosen
945!$OMP THREADPRIVATE(SP_ratiosen)
946  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tdmin
947!$OMP THREADPRIVATE(SP_tdmin)
948 
949  ! 4.4 STICS:: F_humerac
950
951  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_sensrsec
952!$OMP THREADPRIVATE(SP_sensrsec)
953
954  ! 4.5 STICS:: gel
955
956  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codgellev
957!$OMP THREADPRIVATE(SP_codgellev)
958  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codgeljuv
959!$OMP THREADPRIVATE(SP_codgeljuv)
960  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_codgelveg
961!$OMP THREADPRIVATE(SP_codgelveg)
962  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tletale
963!$OMP THREADPRIVATE(SP_tletale)
964  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tdebgel
965!$OMP THREADPRIVATE(SP_tdebgel)
966  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgellev10
967!$OMP THREADPRIVATE(SP_tgellev10)
968  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgellev90
969!$OMP THREADPRIVATE(SP_tgellev90)
970
971  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgeljuv10
972!$OMP THREADPRIVATE(SP_tgeljuv10)
973  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgeljuv90
974!$OMP THREADPRIVATE(SP_tgeljuv90)
975  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgelveg10
976!$OMP THREADPRIVATE(SP_tgelveg10)
977  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_tgelveg90
978!$OMP THREADPRIVATE(SP_tgelveg90)
979
980
981  ! 4.6 STICS:: Photoperiod
982 
983  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_sensiphot
984!$OMP THREADPRIVATE(SP_sensiphot)
985  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_phosat
986!$OMP THREADPRIVATE(SP_phosat)
987  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:) :: SP_phobase
988!$OMP THREADPRIVATE(SP_phobase)
989 
990  ! 4.7 STICS:: carbon allocation
991 
992  CHARACTER(len=3), ALLOCATABLE, SAVE, DIMENSION(:)   :: SP_stoprac
993!$OMP THREADPRIVATE(SP_stoprac)
994  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_zracplantule
995!$OMP THREADPRIVATE(SP_zracplantule)
996  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codtrophrac
997!$OMP THREADPRIVATE(SP_codtrophrac)
998  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracpermax
999!$OMP THREADPRIVATE(SP_repracpermax)
1000  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracpermin
1001!$OMP THREADPRIVATE(SP_repracpermin)
1002  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_krepracperm
1003!$OMP THREADPRIVATE(SP_krepracperm)
1004  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracseumax
1005!$OMP THREADPRIVATE(SP_repracseumax)
1006  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_repracseumin
1007!$OMP THREADPRIVATE(SP_repracseumin)
1008  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_krepracseu
1009!$OMP THREADPRIVATE(SP_krepracseu)
1010  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codetemprac
1011!$OMP THREADPRIVATE(SP_codetemprac)
1012  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codedyntalle
1013!$OMP THREADPRIVATE(SP_codedyntalle)
1014  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_nbjgrain
1015!$OMP THREADPRIVATE(SP_nbjgrain)
1016  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_maxgs
1017!$OMP THREADPRIVATE(SP_maxgs)
1018  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codgelflo
1019!$OMP THREADPRIVATE(SP_codgelflo)
1020  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tgelflo10
1021!$OMP THREADPRIVATE(SP_tgelflo10)
1022  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tgelflo90
1023!$OMP THREADPRIVATE(SP_tgelflo90)
1024  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_cgrain
1025!$OMP THREADPRIVATE(SP_cgrain)
1026  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_cgrainv0
1027!$OMP THREADPRIVATE(SP_cgrainv0)
1028  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_nbgrmax
1029!$OMP THREADPRIVATE(SP_nbgrmax)
1030  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_nbgrmin
1031!$OMP THREADPRIVATE(SP_nbgrmin)
1032  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codazofruit
1033!$OMP THREADPRIVATE(SP_codazofruit)
1034  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codeir
1035!$OMP THREADPRIVATE(SP_codeir)
1036  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_vitircarb
1037!$OMP THREADPRIVATE(SP_vitircarb)
1038  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_irmax
1039!$OMP THREADPRIVATE(SP_irmax)
1040  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_vitircarbT
1041!$OMP THREADPRIVATE(SP_vitircarbT)
1042  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:)     :: SP_codetremp
1043!$OMP THREADPRIVATE(SP_codetremp)
1044  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tminremp
1045!$OMP THREADPRIVATE(SP_tminremp)
1046  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_tmaxremp
1047!$OMP THREADPRIVATE(SP_tmaxremp)
1048  REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_pgrainmaxi
1049!$OMP THREADPRIVATE(SP_pgrainmaxi)
1050
1051!! for  dynamic nitrogen processes
1052
1053LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: SP_DY_INN     !! flag for activating the dynamic nitrogen processes 
1054!$OMP THREADPRIVATE(SP_DY_INN)
1055
1056REAL(r_std), ALLOCATABLE, SAVE, DIMENSION(:)        :: SP_avenfert
1057!$OMP THREADPRIVATE(SP_avenfert)
1058
1059!!!! end cropland parameters, xuhui
1060
1061
1062! STOMATE - Age classes
1063
1064  INTEGER(i_std), SAVE                            :: nvmap          !! The number of PFTs we have if we ignore age classes.
1065                                                                    !! @tex $-$ @endtex
1066!$OMP THREADPRIVATE(nvmap)
1067  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: agec_group     !! The age class group that this PFT belongs to.
1068                                                                    !! If you're not using age classes, this will just be
1069                                                                    !! set to the number of the PFT and should be ignored
1070                                                                    !! in the code.
1071                                                                    !! @tex $-$ @endtex
1072!$OMP THREADPRIVATE(agec_group)
1073  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: age_class_bound!! The age class bounds used to allow age class to move
1074                                                                    !! to next one.
1075!$OMP THREADPRIVATE(age_class_bound)
1076! I do not like the location of these next two variables.  They are computed
1077! after agec_group is read in.  Ideally, they would be passed around
1078! as arguments or in a structure, since they are not really
1079! parameters read in from the input file.
1080  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: start_index    !! Gives the index that this real PFT starts
1081                                                                    !! on, ignoring age classes
1082                                                                    !! @tex $-$ @endtex
1083!$OMP THREADPRIVATE(start_index)
1084  INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: nagec_pft      !! The number of age classes for each PFT.
1085                                                                    !! @tex $-$ @endtex
1086!$OMP THREADPRIVATE(nagec_pft)
1087END MODULE pft_parameters_var
Note: See TracBrowser for help on using the repository browser.