source: branches/publications/ORCHIDEE_gmd_mict_peat_ch4/src_parameters/pft_parameters_var.f90 @ 7346

Last change on this file since 7346 was 7020, checked in by elodie.salmon, 3 years ago

New: ebullition threshold vary with depth

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