source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_parameters/constantes_var.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

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