source: branches/publications/ORCHIDEE-PEAT_r5488/src_parameters/pft_parameters_var.f90 @ 5491

Last change on this file since 5491 was 4806, checked in by chunjing.qiu, 7 years ago

orchi-peat based on r4229

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