source: branches/publications/ORCHIDEE-ICE_SurfaceMassBalance/src_parameters/constantes_var.f90 @ 8398

Last change on this file since 8398 was 7591, checked in by christophe.dumas, 2 years ago

thermosoil_main : fixed a bug in the calculation of temp_sol_new : add the case of ice sheet point totreat correctly the snow free ice case. | explicitsnow_levels : code compliant to compile with both version 12 and 3 layers of snow. | constantes_var.f90 : nice=8 levels of ice

  • Property svn:keywords set to Date Revision
File size: 58.5 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_var
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        constantes_var module contains most constantes like pi, Earth radius, etc...
10!!              and all externalized parameters except pft-dependent constants.
11!!
12!!\n DESCRIPTION: This module contains most constantes and the externalized parameters of ORCHIDEE which
13!!                are not pft-dependent.\n
14!!                In this module, you can set the flag diag_qsat in order to detect the pixel where the
15!!                temperature is out of range (look qsatcalc and dev_qsatcalc in qsat_moisture.f90).\n
16!!                The Earth radius is approximated by the Equatorial radius.The Earth's equatorial radius a,
17!!                or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km.
18!!                The equatorial radius is often used to compare Earth with other planets.\n
19!!                The meridional mean is well approximated by the semicubic mean of the two axe yielding
20!!                6367.4491 km or less accurately by the quadratic mean of the two axes about 6,367.454 km
21!!                or even just the mean of the two axes about 6,367.445 km.\n
22!!                This module is already USE in module constantes. Therefor no need to USE it seperatly except
23!!                if the subroutines in module constantes are not needed.\n
24!!               
25!! RECENT CHANGE(S):
26!!
27!! REFERENCE(S) :
28!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
29!! Boundary Layer Meteorology, 187-202.\n
30!!
31!! SVN          :
32!! $HeadURL: $
33!! $Date$
34!! $Revision$
35!! \n
36!_ ================================================================================================================================
37
38MODULE constantes_var
39
40  USE defprec
41
42  IMPLICIT NONE
43!-
44
45                         !-----------------------!
46                         !  ORCHIDEE CONSTANTS   !
47                         !-----------------------!
48
49  !
50  ! FLAGS
51  !
52  LOGICAL :: river_routing      !! activate river routing
53!$OMP THREADPRIVATE(river_routing)
54  LOGICAL :: hydrol_cwrr        !! activate 11 layers hydrolgy model
55!$OMP THREADPRIVATE(hydrol_cwrr)
56  LOGICAL :: do_floodplains     !! activate flood plains
57!$OMP THREADPRIVATE(do_floodplains)
58  LOGICAL :: do_irrigation      !! activate computation of irrigation flux
59!$OMP THREADPRIVATE(do_irrigation)
60  LOGICAL :: ok_sechiba         !! activate physic of the model
61!$OMP THREADPRIVATE(ok_sechiba)
62  LOGICAL :: ok_co2             !! activate photosynthesis
63!$OMP THREADPRIVATE(ok_co2)
64  LOGICAL :: ok_stomate         !! activate carbon cycle
65!$OMP THREADPRIVATE(ok_stomate)
66  LOGICAL :: ok_dgvm            !! activate dynamic vegetation
67!$OMP THREADPRIVATE(ok_dgvm)
68  LOGICAL :: ok_pheno           !! activate the calculation of lai using stomate rather than a prescription
69!$OMP THREADPRIVATE(ok_pheno)
70  LOGICAL :: ok_bvoc            !! activate biogenic volatile organic coumpounds
71!$OMP THREADPRIVATE(ok_bvoc)
72  LOGICAL :: ok_leafage         !! activate leafage
73!$OMP THREADPRIVATE(ok_leafage)
74  LOGICAL :: ok_radcanopy       !! use canopy radiative transfer model
75!$OMP THREADPRIVATE(ok_radcanopy)
76  LOGICAL :: ok_multilayer      !! use canopy radiative transfer model with multi-layers
77!$OMP THREADPRIVATE(ok_multilayer)
78  LOGICAL :: ok_pulse_NOx       !! calculate NOx emissions with pulse
79!$OMP THREADPRIVATE(ok_pulse_NOx)
80  LOGICAL :: ok_bbgfertil_NOx   !! calculate NOx emissions with bbg fertilizing effect
81!$OMP THREADPRIVATE(ok_bbgfertil_NOx)
82  LOGICAL :: ok_cropsfertil_NOx !! calculate NOx emissions with fertilizers use
83!$OMP THREADPRIVATE(ok_cropsfertil_NOx)
84
85  LOGICAL :: ok_co2bvoc_poss    !! CO2 inhibition on isoprene activated following Possell et al. (2005) model
86!$OMP THREADPRIVATE(ok_co2bvoc_poss)
87  LOGICAL :: ok_co2bvoc_wilk    !! CO2 inhibition on isoprene activated following Wilkinson et al. (2006) model
88!$OMP THREADPRIVATE(ok_co2bvoc_wilk)
89 
90  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.  !! ORCHIDEE detects if it is coupled with a GCM or
91                                            !! just use with one driver in OFF-LINE. (true/false)
92!$OMP THREADPRIVATE(OFF_LINE_MODE) 
93  LOGICAL, SAVE :: impose_param = .TRUE.    !! Flag impos_param : read all the parameters in the run.def file
94!$OMP THREADPRIVATE(impose_param)
95  CHARACTER(LEN=80), SAVE     :: restname_in       = 'NONE'                 !! Input Restart files name for Sechiba component 
96!$OMP THREADPRIVATE(restname_in)
97  CHARACTER(LEN=80), SAVE     :: restname_out      = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
98!$OMP THREADPRIVATE(restname_out)
99  CHARACTER(LEN=80), SAVE     :: stom_restname_in  = 'NONE'                 !! Input Restart files name for Stomate component
100!$OMP THREADPRIVATE(stom_restname_in)
101  CHARACTER(LEN=80), SAVE     :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
102!$OMP THREADPRIVATE(stom_restname_out)
103  INTEGER, SAVE :: printlev=2       !! Standard level for text output [0, 1, 2, 3]
104!$OMP THREADPRIVATE(printlev)
105
106  !
107  ! TIME
108  !
109  REAL(r_std), SAVE :: one_day  !! One day in seconds (s)
110!$OMP THREADPRIVATE(one_day)
111  REAL(r_std), SAVE :: one_year !! One year in days
112!$OMP THREADPRIVATE(one_year)
113  REAL(r_std), PARAMETER :: one_hour = 3600.0  !! One hour in seconds (s)
114  INTEGER(i_std), PARAMETER  :: spring_days_max = 40  !! Maximum number of days during which we watch for possible spring frost damage
115
116  ! TIME STEP
117  REAL(r_std)            :: dt_sechiba         !! Time step in sechiba
118!$OMP THREADPRIVATE(dt_sechiba)
119  REAL(r_std)            :: dt_stomate         !! Time step in stomate
120!$OMP THREADPRIVATE(dt_stomate)
121
122  !
123  ! SPECIAL VALUES
124  !
125  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
126  !-
127  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
128!$OMP THREADPRIVATE(val_exp)
129  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
130 
131  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
132  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
133 
134  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
135  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
136
137
138  !
139  !  DIMENSIONING AND INDICES PARAMETERS 
140  !
141  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
142  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
143  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
144  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
145  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
146  !-
147  !! Soil
148  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
149  !-
150  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
151  !-
152  !! litter fractions: indices (unitless)
153  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
154  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
155  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
156  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
157  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
158  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
159  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
160  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
161  INTEGER(i_std), PARAMETER :: nparts = 8        !! Number of biomass compartments (unitless)
162  !-
163  !! indices for assimilation parameters
164  INTEGER(i_std), PARAMETER :: ivcmax = 1        !! Index for vcmax (assimilation parameters) (unitless)
165  INTEGER(i_std), PARAMETER :: npco2 = 1         !! Number of assimilation parameters (unitless)
166  !-
167  !! trees and litter: indices for the parts of heart-
168  !! and sapwood above and below the ground
169  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
170  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
171  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
172  !-
173  !! litter: indices for metabolic and structural part
174  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
175  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
176  INTEGER(i_std), PARAMETER :: nlitt = 2        !! Number of levels for litter compartments (unitless)
177  !-
178  !! carbon pools: indices
179  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
180  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
181  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
182  INTEGER(i_std), PARAMETER :: ncarb = 3        !! Number of soil carbon pools (unitless)
183  !-
184  !! For isotopes and nitrogen
185  INTEGER(i_std), PARAMETER :: nelements = 1    !! Number of isotopes considered
186  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
187  !
188  !! Indices used for analytical spin-up
189  INTEGER(i_std), PARAMETER :: nbpools = 7              !! Total number of carbon pools (unitless)
190  INTEGER(i_std), PARAMETER :: istructural_above = 1    !! Index for structural litter above (unitless)
191  INTEGER(i_std), PARAMETER :: istructural_below = 2    !! Index for structural litter below (unitless)
192  INTEGER(i_std), PARAMETER :: imetabolic_above = 3     !! Index for metabolic litter above (unitless)
193  INTEGER(i_std), PARAMETER :: imetabolic_below = 4     !! Index for metabolic litter below (unitless)
194  INTEGER(i_std), PARAMETER :: iactive_pool = 5         !! Index for active carbon pool (unitless)
195  INTEGER(i_std), PARAMETER :: islow_pool   = 6         !! Index for slow carbon pool (unitless)
196  INTEGER(i_std), PARAMETER :: ipassive_pool = 7        !! Index for passive carbon pool (unitless)
197
198
199  !
200  ! NUMERICAL AND PHYSICS CONSTANTS
201  !
202  !
203
204  !-
205  ! 1. Mathematical and numerical constants
206  !-
207  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
208  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
209  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
210  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
211  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
212  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
213  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
214  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
215  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
216  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
217  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
218  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
219  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
220
221  !-
222  ! 2 . Physics
223  !-
224  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
225  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
226  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
227  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
228  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
229  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
230  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
231  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
232  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
233  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
234  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
235  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
236                                                            !! of dry air (unitless)
237  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
238  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
239  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
240       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
241  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
242  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
243                                                            !! vapor minus 1(unitless) 
244  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
245                                                            !! minus 1 (unitless)
246  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
247  REAL(r_std), PARAMETER :: ct_karman = 0.41_r_std          !! Van Karmann Constant (unitless)
248  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
249  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
250  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
251  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
252
253
254  INTEGER(i_std), SAVE :: testpft = 6
255  !-
256  ! 3. Climatic constants
257  !-
258  !! Constantes of the Louis scheme
259  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
260                                                  !! reference to Louis (1979)
261!$OMP THREADPRIVATE(cb)
262  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
263                                                  !! reference to Louis (1979)
264!$OMP THREADPRIVATE(cc)
265  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
266                                                  !! reference to Louis (1979)
267!$OMP THREADPRIVATE(cd)
268  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
269!$OMP THREADPRIVATE(rayt_cste)
270  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
271!$OMP THREADPRIVATE(defc_plus)
272  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
273!$OMP THREADPRIVATE(defc_mult)
274
275  !-
276  ! 4. Soil thermodynamics constants
277  !-
278  ! Look at constantes_soil.f90
279
280
281  !
282  ! OPTIONAL PARTS OF THE MODEL
283  !
284  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
285                                                  !! we provide here a way to catch that in the calling procedure.
286                                                  !! (from Jan Polcher)(true/false)
287  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
288                                                  !! Value is read from run.def in intersurf_history
289!$OMP THREADPRIVATE(almaoutput)
290
291  !
292  ! DIVERSE
293  !
294  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
295                                                           ! Compatibility with Nicolas Viovy driver.
296!$OMP THREADPRIVATE(stomate_forcing_name)
297  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
298                                                           ! Compatibility with Nicolas Viovy driver.
299!$OMP THREADPRIVATE(stomate_Cforcing_name)
300  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
301!$OMP THREADPRIVATE(forcing_id)
302  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
303                                                     !! This variable will be set to false for teststomate.
304
305
306
307                         !------------------------!
308                         !  SECHIBA PARAMETERS    !
309                         !------------------------!
310 
311
312  !
313  ! GLOBAL PARAMETERS   
314  !
315  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
316!$OMP THREADPRIVATE(min_wind)
317  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
318!$OMP THREADPRIVATE(snowcri)
319
320
321  !
322  ! FLAGS ACTIVATING SUB-MODELS
323  !
324  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
325!$OMP THREADPRIVATE(treat_expansion)
326  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
327!$OMP THREADPRIVATE(ok_herbivores)
328  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
329!$OMP THREADPRIVATE(harvest_agri)
330  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
331!$OMP THREADPRIVATE(lpj_gap_const_mort)
332  LOGICAL, SAVE :: disable_fire = .FALSE.      !! flag that disable fire (true/false)
333!$OMP THREADPRIVATE(disable_fire)
334  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
335!$OMP THREADPRIVATE(spinup_analytic)
336  LOGICAL, SAVE :: ok_explicitsnow             !! Flag to activate explicit snow scheme instead of default snow scheme
337!$OMP THREADPRIVATE(ok_explicitsnow)
338  LOGICAL, SAVE :: ok_ice_sheet                !! Flag to activate ice scheme on ice-sheet area
339!$OMP THREADPRIVATE(ok_ice_sheet)
340
341  !
342  ! CONFIGURATION VEGETATION
343  !
344  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
345!$OMP THREADPRIVATE(agriculture)
346  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
347!$OMP THREADPRIVATE(impveg)
348  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
349!$OMP THREADPRIVATE(impsoilt)
350  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
351!$OMP THREADPRIVATE(do_now_stomate_lcchange)
352  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
353!$OMP THREADPRIVATE(done_stomate_lcchange)
354  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
355!$OMP THREADPRIVATE(read_lai)
356  LOGICAL, SAVE :: map_pft_format = .TRUE. !! Read a land use vegetation map on PFT format (true/false)
357!$OMP THREADPRIVATE(map_pft_format)
358  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
359!$OMP THREADPRIVATE(veget_reinit)
360
361  !
362  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
363  !
364  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
365!$OMP THREADPRIVATE(max_snow_age)
366  REAL(r_std), SAVE :: snow_trans = 0.2_r_std   !! Transformation time constant for snow (m), reduced from the value 0.3 (04/07/2016)
367!$OMP THREADPRIVATE(snow_trans)
368  REAL(r_std), SAVE :: snow_trans_nobio = 1.0_r_std   !! Transformation time constant for snow on nobio (m), (18/02/2019)
369!$OMP THREADPRIVATE(snow_trans_nobio)
370  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
371!$OMP THREADPRIVATE(sneige)
372  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
373!$OMP THREADPRIVATE(maxmass_snow)
374
375  !! Heat capacity
376  REAL(r_std), PARAMETER :: capa_ice = 2.228*1.E3       !! Heat capacity of ice (J/kg/K)
377  REAL(r_std), SAVE      :: so_capa_ice                 !! Heat capacity of saturated frozen soil (J/K/m3)
378!$OMP THREADPRIVATE(so_capa_ice)
379  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
380  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
381
382  !! Thermal conductivities
383  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
384  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
385  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
386
387  !! Time constant of long-term soil humidity (s)
388  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
389
390!cdc26-06-2021  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme
391!  INTEGER(i_std), PARAMETER :: nsnow=3                   !! Number of levels in the snow for explicit snow scheme
392  INTEGER(i_std), PARAMETER :: nsnow=12                  !! Number of levels in the snow for explicit snow scheme
393  INTEGER(i_std), PARAMETER :: nice=8
394!  INTEGER(i_std), PARAMETER :: nice=4                    !! Number of levels in ice (for ice-sheet area)
395  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
396  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
397  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
398  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
399  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
400  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
401  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
402
403  !! The maximum snow density and water holding characterisicts
404  REAL(r_std), SAVE         :: xrhosmax = 750.  ! (kg m-3)
405  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  ! (-)
406  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  ! (-)
407  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 ! (kg/m3)
408  REAL(r_std), SAVE         :: xrhosmin = 50. 
409  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
410  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
411
412  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
413  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
414
415  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
416  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
417 
418  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
419  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
420  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
421  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
422
423  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
424 
425  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
426  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
427  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
428
429  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
430 
431  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
432  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
433  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
434  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
435 
436  ! Thermal ice conductivity coefficients Yin CHao Yen 1981 (Temp > 195K):
437  REAL(r_std), SAVE                     :: ZICETHRMCOND1 = 6.727   ! [W/m/K]
438  REAL(r_std), SAVE                     :: ZICETHRMCOND2 = -0.0041 !
439  ! Thermal ice heat capacity coefficients :
440  REAL(r_std), SAVE                     :: ZICETHRMHEAT1 = 2115.3  !
441  REAL(r_std), SAVE                     :: ZICETHRMHEAT2 = 7.79293 !
442 
443  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
444  ! (sig only for new snow OR high altitudes)
445  ! from Sun et al. (1999): based on data from Jordan (1991)
446  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
447  !
448  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_AVAP  = -0.06023 ! (W/m/K)
449  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_BVAP  = -2.5425  ! (W/m)
450  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_CVAP  = -289.99  ! (K)
451 
452  REAL(r_std),SAVE :: xansmax = 0.85      !! Maxmimum snow albedo
453  REAL(r_std),SAVE :: xansmin = 0.50      !! Miniumum snow albedo
454  REAL(r_std),SAVE :: xans_todry = 0.008  !! Albedo decay rate for dry snow
455  REAL(r_std),SAVE :: xans_t = 0.240      !! Albedo decay rate for wet snow
456
457  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
458  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
459  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
460
461  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
462  ! (sig only for new snow OR high altitudes)
463  ! from Sun et al. (1999): based on data from Jordan (1991)
464  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
465  !
466  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
467  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s)
468  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
469  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
470  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
471  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
472  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
473
474!!-SC- Ajout de nouveaux paramÚtres pour la viscosité si T > 264 K
475
476  REAL(r_std), SAVE          :: ZSNOWCMPCT_W0    = 2.0e7        !! (Pa/s)
477  REAL(r_std), SAVE          :: ZSNOWCMPCT_WT    = 0.35         !! (1/K)
478  REAL(r_std), SAVE          :: ZSNOWCMPCT_WR    = 0.01         !! (m3/kg)
479
480!!-SC- New constants for use of the compaction scheme from Decharme et al.(2016)
481
482  REAL(r_std), SAVE          :: xrhosref         = 250.          !!  (kg/m3)
483  REAL(r_std), SAVE          :: xrhosmob         = 295.          !!  (kg/m3)
484  REAL(r_std), SAVE          :: xrhoswind        = 350.          !!  (kg/m3)
485
486  REAL(r_std), SAVE          :: ZSNOWCMPCT_X0    = 7.62237e6     ! 7.82237e6     !! (Pa/s)
487
488  REAL(r_std), SAVE          :: ZSNOWCMPCT_XT    = 0.1           !! (1/K)
489  REAL(r_std), SAVE          :: ZSNOWCMPCT_XR    = 0.023         !! (m3/kg)
490  REAL(r_std), SAVE          :: DTref            = 5.            !! (K)
491
492  REAL(r_std), SAVE          :: ACMPCT           = 2.868
493  REAL(r_std), SAVE          :: BCMPCT           = 0.085         !! (s/m)
494  REAL(r_std), SAVE          :: KCMPCT            = 1.25         !! (unitless)
495
496  REAL(r_std), SAVE          :: a_tau            = 10            !!
497  REAL(r_std), SAVE          :: b_tau            = 3.25          !!
498
499  REAL(r_std), SAVE          :: Amob             = 1.25          !! (unitless)
500
501!!-SC-
502
503  !
504  ! BVOC : Biogenic activity  for each age class
505  !
506  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
507                                                                                       !! age class : isoprene (unitless)
508!$OMP THREADPRIVATE(iso_activity)
509  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
510                                                                                       !! age class : methanol (unnitless)
511!$OMP THREADPRIVATE(methanol_activity)
512
513  !
514  ! condveg.f90
515  !
516
517  ! 1. Scalar
518
519  ! 1.1 Flags used inside the module
520
521  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
522                                            !! albedo (see header of subroutine)
523                                            !! (true/false)
524!$OMP THREADPRIVATE(alb_bare_model)
525  LOGICAL, SAVE :: alb_bg_modis = .FALSE.   !! Switch for choosing values of bare soil
526                                            !! albedo read from file
527                                            !! (true/false)
528!$OMP THREADPRIVATE(alb_bg_modis)
529  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
530                                            !! (see header of subroutine). 
531                                            !! (true/false)
532!$OMP THREADPRIVATE(impaze)
533  LOGICAL, SAVE :: rough_dyn = .FALSE.      !! Chooses between two methods to calculate the
534                                            !! the roughness height : static or dynamic (varying with LAI)
535                                            !! (true/false)
536!$OMP THREADPRIVATE(rough_dyn)
537
538  LOGICAL, SAVE :: new_watstress = .FALSE.
539!$OMP THREADPRIVATE(new_watstress)
540
541  REAL(r_std), SAVE :: alpha_watstress = 1.
542!$OMP THREADPRIVATE(alpha_watstress)
543
544  ! 1.2 Others
545
546
547  REAL(r_std), SAVE :: height_displacement = 0.66        !! Factor to calculate the zero-plane displacement
548                                                         !! height from vegetation height (m)
549!$OMP THREADPRIVATE(height_displacement)
550  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
551!$OMP THREADPRIVATE(z0_bare)
552  REAL(r_std), SAVE :: z0_ice = 0.001                !! ice roughness length (m) --> Standard value
553!!-SC REAL(r_std), SAVE :: z0_ice = 0.0001                     !! ice roughness length (m) --> Modified (Z0_ice/10)
554!!-SC REAL(r_std), SAVE :: z0_ice = 4E-05                    !! ice roughness length (m) --> Modified (Z0ice/25)
555!$OMP THREADPRIVATE(z0_ice)
556  REAL(r_std), SAVE :: tcst_snowa = 10.0                !! Time constant of the albedo decay of snow (days), increased from the value 5.0 (04/07/2016)
557!$OMP THREADPRIVATE(tcst_snowa)
558  REAL(r_std), SAVE :: tcst_snowa_nobio = 2.0            !! Time constant of the albedo decay of snow on nobio (days) (18/02/2018)
559!$OMP THREADPRIVATE(tcst_snowa_nobio)
560REAL(r_std), SAVE :: omg1 = 7.0                          !! First tuning constant for snow ageing on nobio areas (14/10/2020)
561!$OMP THREADPRIVATE(omg1)
562REAL(r_std), SAVE :: omg2 = 4.0                          !! Second tuning constant for snow ageing on nobio areas (14/10/2020)
563!$OMP THREADPRIVATE(omg2)
564  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
565!$OMP THREADPRIVATE(snowcri_alb)
566  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
567!$OMP THREADPRIVATE(fixed_snow_albedo)
568  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
569!$OMP THREADPRIVATE(z0_scal)
570  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
571                                                         !! displacement height (m) (imposed)
572!$OMP THREADPRIVATE(roughheight_scal)
573  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
574!$OMP THREADPRIVATE(emis_scal)
575
576  REAL(r_std), SAVE :: c1 = 0.32                         !! Constant used in the formulation of the ratio of
577!$OMP THREADPRIVATE(c1)                                  !! friction velocity to the wind speed at the canopy top
578                                                         !! see Ershadi et al. (2015) for more info
579  REAL(r_std), SAVE :: c2 = 0.264                        !! Constant used in the formulation of the ratio of
580!$OMP THREADPRIVATE(c2)                                  !! friction velocity to the wind speed at the canopy top
581                                                         !! see Ershadi et al. (2015) for more info
582  REAL(r_std), SAVE :: c3 = 15.1                         !! Constant used in the formulation of the ratio of
583!$OMP THREADPRIVATE(c3)                                  !! friction velocity to the wind speed at the canopy top
584                                                         !! see Ershadi et al. (2015) for more info
585  REAL(r_std), SAVE :: Cdrag_foliage = 0.2               !! Drag coefficient of the foliage
586!$OMP THREADPRIVATE(Cdrag_foliage)                       !! See Ershadi et al. (2015) and Su et. al (2001) for more info
587  REAL(r_std), SAVE :: Ct = 0.01                         !! Heat transfer coefficient of the leaf
588!$OMP THREADPRIVATE(Ct)                                  !! See Ershadi et al. (2015) and Su et. al (2001) for more info
589  REAL(r_std), SAVE :: Prandtl = 0.71                    !! Prandtl number used in the calculation of Ct_star
590!$OMP THREADPRIVATE(Prandtl)                             !! See Su et. al (2001) for more info
591
592
593
594  ! 2. Arrays
595
596  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
597!$OMP THREADPRIVATE(alb_deadleaf)
598  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
599!$OMP THREADPRIVATE(alb_ice)
600  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
601                                                                     !! used imposed (unitless)
602!$OMP THREADPRIVATE(albedo_scal)
603  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
604       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
605                                                          !! dry soil albedo values in visible range
606!$OMP THREADPRIVATE(vis_dry)
607  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
608       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
609                                                          !! dry soil albedo values in near-infrared range
610!$OMP THREADPRIVATE(nir_dry)
611  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
612       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
613                                                          !! wet soil albedo values in visible range
614!$OMP THREADPRIVATE(vis_wet)
615  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
616       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
617                                                          !! wet soil albedo values in near-infrared range
618!$OMP THREADPRIVATE(nir_wet)
619  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
620       &0.18, 0.16, 0.16, 0.15, 0.12, 0.105, 0.09, 0.075, 0.25/)   !! Soil albedo values to soil colour classification:
621                                                                   !! Averaged of wet and dry soil albedo values
622                                                                   !! in visible and near-infrared range
623!$OMP THREADPRIVATE(albsoil_vis)
624  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
625       &0.36, 0.34, 0.34, 0.33, 0.30, 0.25, 0.20, 0.15, 0.45/)  !! Soil albedo values to soil colour classification:
626                                                                !! Averaged of wet and dry soil albedo values
627                                                                !! in visible and near-infrared range
628!$OMP THREADPRIVATE(albsoil_nir)
629
630!  REAL(r_std), SAVE, DIMENSION(3) :: ZSICOEF1  = (/0.05, 0.35, 49.6/)    !! Ice grid parameters 3 layers : thickness of ice levels
631!  REAL(r_std), SAVE, DIMENSION(4) :: ZSICOEF1  = (/0.02, 0.12, 5., 50./)    !! Ice grid parameters 4 layers : thickness of ice levels
632  REAL(r_std), SAVE, DIMENSION(8) :: ZSICOEF1  = (/0.01, 0.05, 0.15, 0.5, 1., 5., 10., 50./)    !! Ice grid parameters 8 layers : thickness of ice levels
633
634!$OMP THREADPRIVATE(zsicoef1)
635
636  !
637  ! diffuco.f90
638  !
639
640  ! 0. Constants
641
642  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
643                                                     !! of dry air (unitless)
644  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
645  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
646  REAL(r_std), PARAMETER :: mol_to_m_1 = 0.0244      !!
647  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
648  REAL(r_std), PARAMETER :: W_to_mol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
649
650  ! 1. Scalar
651
652  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
653!$OMP THREADPRIVATE(nlai)
654  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
655!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
656  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
657!$OMP THREADPRIVATE(laimax)
658  LOGICAL, SAVE :: downregulation_co2 = .FALSE.            !! Set to .TRUE. if you want CO2 downregulation.
659!$OMP THREADPRIVATE(downregulation_co2)
660  REAL(r_std), SAVE :: downregulation_co2_baselevel = 280. !! CO2 base level (ppm)
661!$OMP THREADPRIVATE(downregulation_co2_baselevel)
662
663  REAL(r_std), SAVE :: gb_ref = 1./25.                     !! Leaf bulk boundary layer resistance (s m-1)
664
665  ! 3. Coefficients of equations
666
667  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
668!$OMP THREADPRIVATE(lai_level_depth)
669!
670  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
671  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
672!$OMP THREADPRIVATE(dew_veg_poly_coeff)
673!
674  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
675!$OMP THREADPRIVATE(Oi)
676  !
677  ! slowproc.f90
678  !
679
680  ! 1. Scalar
681
682  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
683!$OMP THREADPRIVATE(veget_year_orig)
684  REAL(r_std), SAVE :: clayfraction_default = 0.2    !! Default value for clay fraction (0-1, unitless)
685!$OMP THREADPRIVATE(clayfraction_default)
686  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
687!$OMP THREADPRIVATE(min_vegfrac)
688  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
689!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
690 
691  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
692!$OMP THREADPRIVATE(stempdiag_bid)
693
694
695                           !-----------------------------!
696                           !  STOMATE AND LPJ PARAMETERS !
697                           !-----------------------------!
698
699
700  !
701  ! lpj_constraints.f90
702  !
703 
704  ! 1. Scalar
705
706  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
707                                           !! regeneration (vernalization) (years)
708!$OMP THREADPRIVATE(too_long)
709
710
711  !
712  ! lpj_establish.f90
713  !
714
715  ! 1. Scalar
716
717  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (ind/m2/dt_stomate)
718!$OMP THREADPRIVATE(estab_max_tree)
719  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (ind/m2/dt_stomate)
720!$OMP THREADPRIVATE(estab_max_grass)
721 
722  ! 3. Coefficients of equations
723
724  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
725!$OMP THREADPRIVATE(establish_scal_fact)
726  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
727!$OMP THREADPRIVATE(max_tree_coverage)
728  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
729!$OMP THREADPRIVATE(ind_0_estab)
730
731
732  !
733  ! lpj_fire.f90
734  !
735
736  ! 1. Scalar
737
738  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
739!$OMP THREADPRIVATE(tau_fire)
740  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
741                                                !! below which iginitions extinguish
742                                                !! @tex $(gC m^{-2})$ @endtex
743!$OMP THREADPRIVATE(litter_crit)
744  REAL(r_std), SAVE :: fire_resist_struct = 0.5 !!
745!$OMP THREADPRIVATE(fire_resist_struct)
746  ! 2. Arrays
747
748  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
749       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)       !! compartments emitted to the atmosphere
750!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
751
752  ! 3. Coefficients of equations
753
754  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
755!$OMP THREADPRIVATE(bcfrac_coeff)
756  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
757!$OMP THREADPRIVATE(firefrac_coeff)
758
759  !
760  ! lpj_gap.f90
761  !
762
763  ! 1. Scalar
764
765  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
766                                                 !! @tex $(year^{-1})$ @endtex
767!$OMP THREADPRIVATE(ref_greff)
768
769  !               
770  ! lpj_light.f90
771  !             
772
773  ! 1. Scalar
774 
775  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
776                                            !! to fpc of last time step (F)? (true/false)
777!$OMP THREADPRIVATE(annual_increase)
778  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
779                                            !! (due to its branches etc.) (0-1, unitless)
780                                            !! This means that only a small fraction of its crown area
781                                            !! can be invaded by other trees.
782!$OMP THREADPRIVATE(min_cover)
783  !
784  ! lpj_pftinout.f90
785  !
786
787  ! 1. Scalar
788
789  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
790!$OMP THREADPRIVATE(min_avail)
791  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
792!$OMP THREADPRIVATE(ind_0)
793  ! 3. Coefficients of equations
794 
795  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
796!$OMP THREADPRIVATE(RIP_time_min)
797  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
798!$OMP THREADPRIVATE(npp_longterm_init)
799  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
800!$OMP THREADPRIVATE(everywhere_init)
801
802
803  !
804  ! stomate_alloc.f90
805  !
806
807  ! 0. Constants
808
809  REAL(r_std), PARAMETER :: max_possible_lai = 10. !! (m^2.m^{-2})
810  REAL(r_std), PARAMETER :: Nlim_Q10 = 10.         !!
811
812  ! 1. Scalar
813
814  LOGICAL, SAVE :: ok_minres = .TRUE.              !! [DISPENSABLE] Do we try to reach a minimum reservoir even if
815                                                   !! we are severely stressed? (true/false)
816!$OMP THREADPRIVATE(ok_minres)
817  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
818                                                   !! carbohydrate reserve may be used for
819                                                   !! trees (days)
820!$OMP THREADPRIVATE(reserve_time_tree)
821  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
822                                                   !! carbohydrate reserve may be used for
823                                                   !! grasses (days)
824!$OMP THREADPRIVATE(reserve_time_grass)
825
826  REAL(r_std), SAVE :: f_fruit = 0.1               !! Default fruit allocation (0-1, unitless)
827!$OMP THREADPRIVATE(f_fruit)
828  REAL(r_std), SAVE :: alloc_sap_above_grass = 1.0 !! fraction of sapwood allocation above ground
829                                                   !! for grass (0-1, unitless)
830!$OMP THREADPRIVATE(alloc_sap_above_grass)
831  REAL(r_std), SAVE :: min_LtoLSR = 0.2            !! Prescribed lower bounds for leaf
832                                                   !! allocation (0-1, unitless)
833!$OMP THREADPRIVATE(min_LtoLSR)
834  REAL(r_std), SAVE :: max_LtoLSR = 0.5            !! Prescribed upper bounds for leaf
835                                                   !! allocation (0-1, unitless)
836!$OMP THREADPRIVATE(max_LtoLSR)
837  REAL(r_std), SAVE :: z_nitrogen = 0.2            !! Curvature of the root profile (m)
838!$OMP THREADPRIVATE(z_nitrogen)
839
840  ! 3. Coefficients of equations
841
842  REAL(r_std), SAVE :: Nlim_tref = 25.             !! (C)
843!$OMP THREADPRIVATE(Nlim_tref)
844
845
846  !
847  ! stomate_data.f90
848  !
849
850  ! 1. Scalar
851
852  ! 1.1 Parameters for the pipe model
853
854  REAL(r_std), SAVE :: pipe_tune1 = 100.0        !! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) (unitless)
855!$OMP THREADPRIVATE(pipe_tune1)
856  REAL(r_std), SAVE :: pipe_tune2 = 40.0         !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
857!$OMP THREADPRIVATE(pipe_tune2)
858  REAL(r_std), SAVE :: pipe_tune3 = 0.5          !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
859!$OMP THREADPRIVATE(pipe_tune3)
860  REAL(r_std), SAVE :: pipe_tune4 = 0.3          !! needed for stem diameter (unitless)
861!$OMP THREADPRIVATE(pipe_tune4)
862  REAL(r_std), SAVE :: pipe_density = 2.e5       !! Density
863!$OMP THREADPRIVATE(pipe_density)
864  REAL(r_std), SAVE :: pipe_k1 = 8.e3            !! one more SAVE
865!$OMP THREADPRIVATE(pipe_k1)
866  REAL(r_std), SAVE :: pipe_tune_exp_coeff = 1.6 !! pipe tune exponential coeff (unitless)
867!$OMP THREADPRIVATE(pipe_tune_exp_coeff)
868
869  ! 1.2 climatic parameters
870
871  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
872!$OMP THREADPRIVATE(precip_crit)
873  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
874!$OMP THREADPRIVATE(gdd_crit_estab)
875  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
876!$OMP THREADPRIVATE(fpc_crit)
877
878  ! 1.3 sapling characteristics
879
880  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
881!$OMP THREADPRIVATE(alpha_grass)
882  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
883!$OMP THREADPRIVATE(alpha_tree)
884  REAL(r_std), SAVE :: mass_ratio_heart_sap = 3. !! mass ratio (heartwood+sapwood)/sapwood (unitless)
885!$OMP THREADPRIVATE(mass_ratio_heart_sap)
886
887  ! 1.4  time scales for phenology and other processes (in days)
888
889  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
890!$OMP THREADPRIVATE(tau_hum_month)
891  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
892!$OMP THREADPRIVATE(tau_hum_week)
893  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
894!$OMP THREADPRIVATE(tau_t2m_month)
895  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
896!$OMP THREADPRIVATE(tau_t2m_week)
897  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
898!$OMP THREADPRIVATE(tau_tsoil_month)
899  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
900!$OMP THREADPRIVATE(tau_soilhum_month)
901  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
902!$OMP THREADPRIVATE(tau_gpp_week)
903  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
904!$OMP THREADPRIVATE(tau_gdd)
905  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
906!$OMP THREADPRIVATE(tau_ngd)
907  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
908!$OMP THREADPRIVATE(coeff_tau_longterm)
909  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
910!$OMP THREADPRIVATE(tau_longterm_max)
911
912  ! 3. Coefficients of equations
913
914  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
915!$OMP THREADPRIVATE(bm_sapl_carbres)
916  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
917!$OMP THREADPRIVATE(bm_sapl_sapabove)
918  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
919!$OMP THREADPRIVATE(bm_sapl_heartabove)
920  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
921!$OMP THREADPRIVATE(bm_sapl_heartbelow)
922  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
923!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
924  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
925!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
926  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
927!$OMP THREADPRIVATE(init_sapl_mass_carbres)
928  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
929!$OMP THREADPRIVATE(init_sapl_mass_root)
930  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
931!$OMP THREADPRIVATE(init_sapl_mass_fruit)
932  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
933!$OMP THREADPRIVATE(cn_sapl_init)
934  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
935!$OMP THREADPRIVATE(migrate_tree)
936  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
937!$OMP THREADPRIVATE(migrate_grass)
938  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
939!$OMP THREADPRIVATE(lai_initmin_tree)
940  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
941!$OMP THREADPRIVATE(lai_initmin_grass)
942  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
943!$OMP THREADPRIVATE(dia_coeff)
944  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
945!$OMP THREADPRIVATE(maxdia_coeff)
946  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
947!$OMP THREADPRIVATE(bm_sapl_leaf)
948
949
950
951  !
952  ! stomate_litter.f90
953  !
954
955  ! 0. Constants
956
957  REAL(r_std), PARAMETER :: Q10 = 10.               !!
958
959  ! 1. Scalar
960
961  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
962!$OMP THREADPRIVATE(z_decomp)
963
964  ! 2. Arrays
965
966  REAL(r_std), SAVE :: frac_soil_struct_aa = 0.55   !! corresponding to frac_soil(istructural,iactive,iabove)
967!$OMP THREADPRIVATE(frac_soil_struct_aa)
968  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
969!$OMP THREADPRIVATE(frac_soil_struct_ab)
970  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
971!$OMP THREADPRIVATE(frac_soil_struct_sa)
972  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
973!$OMP THREADPRIVATE(frac_soil_struct_sb)
974  REAL(r_std), SAVE :: frac_soil_metab_aa = 0.45    !! corresponding to frac_soil(imetabolic,iactive,iabove)
975!$OMP THREADPRIVATE(frac_soil_metab_aa)
976  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
977!$OMP THREADPRIVATE(frac_soil_metab_ab)
978  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = &    !! C/N ratio of each plant pool (0-100, unitless)
979       & (/ 40., 40., 40., 40., 40., 40., 40., 40. /) 
980!$OMP THREADPRIVATE(CN)
981  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = &    !! Lignin/C ratio of different plant parts (0,22-0,35, unitless)
982       & (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
983!$OMP THREADPRIVATE(LC)
984
985  ! 3. Coefficients of equations
986
987  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
988!$OMP THREADPRIVATE(metabolic_ref_frac)
989  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
990!$OMP THREADPRIVATE(metabolic_LN_ratio)
991  REAL(r_std), SAVE :: tau_metabolic = 0.066        !!
992!$OMP THREADPRIVATE(tau_metabolic)
993  REAL(r_std), SAVE :: tau_struct = 0.245           !!
994!$OMP THREADPRIVATE(tau_struct)
995  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
996!$OMP THREADPRIVATE(soil_Q10)
997  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
998!$OMP THREADPRIVATE(tsoil_ref)
999  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
1000!$OMP THREADPRIVATE(litter_struct_coef)
1001  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
1002!$OMP THREADPRIVATE(moist_coeff)
1003  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
1004!$OMP THREADPRIVATE(moistcont_min)
1005
1006
1007  !
1008  ! stomate_lpj.f90
1009  !
1010
1011  ! 1. Scalar
1012
1013  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
1014!$OMP THREADPRIVATE(frac_turnover_daily)
1015
1016
1017  !
1018  ! stomate_npp.f90
1019  !
1020
1021  ! 1. Scalar
1022
1023  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
1024                                     !! for maintenance respiration (0-1, unitless)
1025!$OMP THREADPRIVATE(tax_max)
1026
1027
1028  !
1029  ! stomate_phenology.f90
1030  !
1031
1032  ! 1. Scalar
1033
1034  LOGICAL, SAVE :: always_init = .FALSE.           !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
1035!$OMP THREADPRIVATE(always_init)
1036  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
1037!$OMP THREADPRIVATE(min_growthinit_time)
1038  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1039                                                   !!  - for trees (0-1, unitless)
1040!$OMP THREADPRIVATE(moiavail_always_tree)
1041  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1042                                                   !! - for grass (0-1, unitless)
1043!$OMP THREADPRIVATE(moiavail_always_grass)
1044  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1045!$OMP THREADPRIVATE(t_always)
1046  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1047!$OMP THREADPRIVATE(t_always_add)
1048
1049  ! 3. Coefficients of equations
1050 
1051  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
1052!$OMP THREADPRIVATE(gddncd_ref)
1053  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
1054!$OMP THREADPRIVATE(gddncd_curve)
1055  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
1056!$OMP THREADPRIVATE(gddncd_offset)
1057
1058
1059  !
1060  ! stomate_prescribe.f90
1061  !
1062
1063  ! 3. Coefficients of equations
1064
1065  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
1066!$OMP THREADPRIVATE(bm_sapl_rescale)
1067
1068
1069  !
1070  ! stomate_resp.f90
1071  !
1072
1073  ! 3. Coefficients of equations
1074
1075  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1076!$OMP THREADPRIVATE(maint_resp_min_vmax)
1077  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1078!$OMP THREADPRIVATE(maint_resp_coeff)
1079
1080
1081  !
1082  ! stomate_soilcarbon.f90
1083  !
1084
1085  ! 2. Arrays
1086
1087  ! 2.1 frac_carb_coefficients
1088
1089  REAL(r_std), SAVE :: frac_carb_ap = 0.004  !! from active pool: depends on clay content  (0-1, unitless)
1090                                             !! corresponding to frac_carb(:,iactive,ipassive)
1091!$OMP THREADPRIVATE(frac_carb_ap)
1092  REAL(r_std), SAVE :: frac_carb_sa = 0.42   !! from slow pool (0-1, unitless)
1093                                             !! corresponding to frac_carb(:,islow,iactive)
1094!$OMP THREADPRIVATE(frac_carb_sa)
1095  REAL(r_std), SAVE :: frac_carb_sp = 0.03   !! from slow pool (0-1, unitless)
1096                                             !! corresponding to frac_carb(:,islow,ipassive)
1097!$OMP THREADPRIVATE(frac_carb_sp)
1098  REAL(r_std), SAVE :: frac_carb_pa = 0.45   !! from passive pool (0-1, unitless)
1099                                             !! corresponding to frac_carb(:,ipassive,iactive)
1100!$OMP THREADPRIVATE(frac_carb_pa)
1101  REAL(r_std), SAVE :: frac_carb_ps = 0.0    !! from passive pool (0-1, unitless)
1102                                             !! corresponding to frac_carb(:,ipassive,islow)
1103!$OMP THREADPRIVATE(frac_carb_ps)
1104
1105  ! 3. Coefficients of equations
1106
1107  REAL(r_std), SAVE :: active_to_pass_clay_frac = 0.68  !! (0-1, unitless)
1108!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1109  !! residence times in carbon pools (days)
1110  REAL(r_std), SAVE :: carbon_tau_iactive = 0.149   !! residence times in active pool (days)
1111!$OMP THREADPRIVATE(carbon_tau_iactive)
1112  REAL(r_std), SAVE :: carbon_tau_islow = 5.48      !! residence times in slow pool (days)
1113!$OMP THREADPRIVATE(carbon_tau_islow)
1114  REAL(r_std), SAVE :: carbon_tau_ipassive = 241.   !! residence times in passive pool (days)
1115!$OMP THREADPRIVATE(carbon_tau_ipassive)
1116  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
1117!$OMP THREADPRIVATE(flux_tot_coeff)
1118
1119  !
1120  ! stomate_turnover.f90
1121  !
1122
1123  ! 3. Coefficients of equations
1124
1125  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1126!$OMP THREADPRIVATE(new_turnover_time_ref)
1127  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
1128!$OMP THREADPRIVATE(leaf_age_crit_tref)
1129  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
1130!$OMP THREADPRIVATE(leaf_age_crit_coeff)
1131
1132
1133  !
1134  ! stomate_vmax.f90
1135  !
1136 
1137  ! 1. Scalar
1138
1139  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1140!$OMP THREADPRIVATE(vmax_offset)
1141  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1142                                                !! reaches 1 (unitless)
1143!$OMP THREADPRIVATE(leafage_firstmax)
1144  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1145                                                !! falls below 1 (unitless)
1146!$OMP THREADPRIVATE(leafage_lastmax)
1147  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1148                                                !! reaches its minimum (vmax_offset)
1149                                                !! (unitless)
1150!$OMP THREADPRIVATE(leafage_old)
1151  !
1152  ! stomate_season.f90
1153  !
1154
1155  ! 1. Scalar
1156
1157  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
1158!$OMP THREADPRIVATE(gppfrac_dormance)
1159  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
1160!$OMP THREADPRIVATE(tau_climatology)
1161  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
1162!$OMP THREADPRIVATE(hvc1)
1163  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
1164!$OMP THREADPRIVATE(hvc2)
1165  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
1166!$OMP THREADPRIVATE(leaf_frac_hvc)
1167  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
1168!$OMP THREADPRIVATE(tlong_ref_max)
1169  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
1170!$OMP THREADPRIVATE(tlong_ref_min)
1171
1172  ! 3. Coefficients of equations
1173
1174  REAL(r_std), SAVE :: ncd_max_year = 3.
1175!$OMP THREADPRIVATE(ncd_max_year)
1176  REAL(r_std), SAVE :: gdd_threshold = 5.
1177!$OMP THREADPRIVATE(gdd_threshold)
1178  REAL(r_std), SAVE :: green_age_ever = 2.
1179!$OMP THREADPRIVATE(green_age_ever)
1180  REAL(r_std), SAVE :: green_age_dec = 0.5
1181!$OMP THREADPRIVATE(green_age_dec)
1182
1183END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.