source: branches/publications/ORCHIDEE_gmd-2018-261/src_parameters/constantes_var.f90 @ 8794

Last change on this file since 8794 was 4998, checked in by nicolas.vuichard, 7 years ago

rev29012018

  • Property svn:keywords set to Date Revision
File size: 73.6 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_ncycle          !! activate nitrogen cycle
67!$OMP THREADPRIVATE(ok_ncycle)
68  LOGICAL :: impose_cn          !! impose the CN ratio of leaves
69!$OMP THREADPRIVATE(impose_cn)
70  LOGICAL :: ok_dgvm            !! activate dynamic vegetation
71!$OMP THREADPRIVATE(ok_dgvm)
72  LOGICAL :: ok_pheno           !! activate the calculation of lai using stomate rather than a prescription
73!$OMP THREADPRIVATE(ok_pheno)
74  LOGICAL :: ok_bvoc            !! activate biogenic volatile organic coumpounds
75!$OMP THREADPRIVATE(ok_bvoc)
76  LOGICAL :: ok_leafage         !! activate leafage
77!$OMP THREADPRIVATE(ok_leafage)
78  LOGICAL :: ok_radcanopy       !! use canopy radiative transfer model
79!$OMP THREADPRIVATE(ok_radcanopy)
80  LOGICAL :: ok_multilayer      !! use canopy radiative transfer model with multi-layers
81!$OMP THREADPRIVATE(ok_multilayer)
82  LOGICAL :: ok_pulse_NOx       !! calculate NOx emissions with pulse
83!$OMP THREADPRIVATE(ok_pulse_NOx)
84  LOGICAL :: ok_bbgfertil_NOx   !! calculate NOx emissions with bbg fertilizing effect
85!$OMP THREADPRIVATE(ok_bbgfertil_NOx)
86  LOGICAL :: ok_cropsfertil_NOx !! calculate NOx emissions with fertilizers use
87!$OMP THREADPRIVATE(ok_cropsfertil_NOx)
88
89  LOGICAL :: ok_co2bvoc_poss    !! CO2 inhibition on isoprene activated following Possell et al. (2005) model
90!$OMP THREADPRIVATE(ok_co2bvoc_poss)
91  LOGICAL :: ok_co2bvoc_wilk    !! CO2 inhibition on isoprene activated following Wilkinson et al. (2006) model
92!$OMP THREADPRIVATE(ok_co2bvoc_wilk)
93 
94  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.  !! ORCHIDEE detects if it is coupled with a GCM or
95                                            !! just use with one driver in OFF-LINE. (true/false)
96!$OMP THREADPRIVATE(OFF_LINE_MODE) 
97  LOGICAL, SAVE :: impose_param = .TRUE.    !! Flag impos_param : read all the parameters in the run.def file
98!$OMP THREADPRIVATE(impose_param)
99  CHARACTER(LEN=80), SAVE     :: restname_in       = 'NONE'                 !! Input Restart files name for Sechiba component 
100!$OMP THREADPRIVATE(restname_in)
101  CHARACTER(LEN=80), SAVE     :: restname_out      = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
102!$OMP THREADPRIVATE(restname_out)
103  CHARACTER(LEN=80), SAVE     :: stom_restname_in  = 'NONE'                 !! Input Restart files name for Stomate component
104!$OMP THREADPRIVATE(stom_restname_in)
105  CHARACTER(LEN=80), SAVE     :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
106!$OMP THREADPRIVATE(stom_restname_out)
107  INTEGER, SAVE :: printlev=1       !! Standard level for text output [0, 1, 2, 3]
108!$OMP THREADPRIVATE(printlev)
109
110  !
111  ! TIME
112  !
113  REAL(r_std), SAVE :: one_day  !! One day in seconds (s)
114!$OMP THREADPRIVATE(one_day)
115  REAL(r_std), SAVE :: one_year !! One year in days
116!$OMP THREADPRIVATE(one_year)
117  REAL(r_std), PARAMETER :: one_hour = 3600.0  !! One hour in seconds (s)
118  INTEGER(i_std), PARAMETER  :: spring_days_max = 40  !! Maximum number of days during which we watch for possible spring frost damage
119
120  ! TIME STEP
121  REAL(r_std)            :: dt_sechiba         !! Time step in sechiba
122!$OMP THREADPRIVATE(dt_sechiba)
123  REAL(r_std)            :: dt_stomate         !! Time step in stomate
124!$OMP THREADPRIVATE(dt_stomate)
125
126  !
127  ! SPECIAL VALUES
128  !
129  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
130  !-
131  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
132!$OMP THREADPRIVATE(val_exp)
133  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
134 
135  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
136  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
137 
138  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
139  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
140
141
142  !
143  !  DIMENSIONING AND INDICES PARAMETERS 
144  !
145  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
146  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
147  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
148  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
149  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
150  !-
151  !! Soil
152  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
153  !-
154  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
155  !-
156  !! litter fractions: indices (unitless)
157  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
158  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
159  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
160  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
161  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
162  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
163  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
164  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
165  INTEGER(i_std), PARAMETER :: ilabile = 9       !! Index for reserve compartment (unitless)
166  INTEGER(i_std), PARAMETER :: nparts = 9        !! Number of biomass compartments (unitless)
167  !-
168  !! indices for assimilation parameters
169  INTEGER(i_std), PARAMETER :: ivcmax = 1        !! Index for vcmax (assimilation parameters) (unitless)
170  INTEGER(i_std), PARAMETER :: inue = 2          !! Index for nue (assimilationbn parameters) (unitless)
171  INTEGER(i_std), PARAMETER :: ileafN = 3        !! Index for leaf N (assimilationbn parameters) (unitless)
172  INTEGER(i_std), PARAMETER :: npco2 = 3         !! Number of assimilation parameters (unitless)
173  !-
174  !! trees and litter: indices for the parts of heart-
175  !! and sapwood above and below the ground
176  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
177  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
178  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
179  !-
180  !! litter: indices for metabolic and structural part
181  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
182  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
183  INTEGER(i_std), PARAMETER :: iwoody = 3       !! Index for woody litter (unitless)
184  INTEGER(i_std), PARAMETER :: nlitt = 3        !! Number of levels for litter compartments (unitless)
185  !-
186  !! carbon pools: indices
187  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
188  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
189  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
190  INTEGER(i_std), PARAMETER :: isurface = 4     !! Index for passive carbon pool (unitless)
191  INTEGER(i_std), PARAMETER :: ncarb = 4        !! Number of soil carbon pools (unitless)
192  !-
193  !! For isotopes and nitrogen
194  INTEGER(i_std), PARAMETER :: nelements = 2    !! Number of isotopes considered
195  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
196  INTEGER(i_std), PARAMETER :: initrogen = 2    !! Index for nitrogen
197  !! N-cycle : indices
198  INTEGER(i_std), PARAMETER :: iammonium = 1    !! Index for Ammonium
199  INTEGER(i_std), PARAMETER :: initrate  = 2    !! Index for Nitrate
200  INTEGER(i_std), PARAMETER :: inox      = 3    !! Index for NOX
201  INTEGER(i_std), PARAMETER :: initrous  = 4    !! Index for N2O
202  INTEGER(i_std), PARAMETER :: idinitro  = 5    !! Index for N2
203  INTEGER(i_std), PARAMETER :: nionspec  = 2    !! Number of ionics form considered (ammonium, nitrate)
204  INTEGER(i_std), PARAMETER :: nnspec    = 5    !! Number of N-species considered
205
206  INTEGER(i_std), PARAMETER :: iatm_ammo = 1    !! Index for N input from Ammonium N atmospheric deposition
207  INTEGER(i_std), PARAMETER :: iatm_nitr = 2    !! Index for N input from Nitrate N atmospheric deposition
208  INTEGER(i_std), PARAMETER :: ibnf      = 3    !! Index for N input from BNF
209  INTEGER(i_std), PARAMETER :: ifert     = 4    !! Index for N input from Fertilisation
210  INTEGER(i_std), PARAMETER :: imanure   = 5    !! Index for N input from Manure
211  INTEGER(i_std), PARAMETER :: ninput    = 5    !! Number of N-input considered 
212 
213
214  INTEGER(i_std), PARAMETER :: i_nh4_to_no3 = 1 !! Index for NO3 production
215  INTEGER(i_std), PARAMETER :: i_nh4_to_no  = 2 !! Index for NO production
216  INTEGER(i_std), PARAMETER :: i_nh4_to_n2o = 3 !! Index for N2O production
217
218  INTEGER(i_std), PARAMETER :: i_no3_to_nox = 1  !! Index for NO3 consumption
219  INTEGER(i_std), PARAMETER :: i_nox_to_n2o  = 2 !! Index for NO/Nox consumption
220  INTEGER(i_std), PARAMETER :: i_n2o_to_n2 = 3   !! Index for N2O consumption
221
222
223  !
224  !! Indices used for analytical spin-up
225  INTEGER(i_std), PARAMETER :: nbpools = 10              !! Total number of carbon pools (unitless)
226  INTEGER(i_std), PARAMETER :: istructural_above = 1    !! Index for structural litter above (unitless)
227  INTEGER(i_std), PARAMETER :: istructural_below = 2    !! Index for structural litter below (unitless)
228  INTEGER(i_std), PARAMETER :: imetabolic_above = 3     !! Index for metabolic litter above (unitless)
229  INTEGER(i_std), PARAMETER :: imetabolic_below = 4     !! Index for metabolic litter below (unitless)
230  INTEGER(i_std), PARAMETER :: iwoody_above = 5         !! Index for woody litter above (unitless)
231  INTEGER(i_std), PARAMETER :: iwoody_below = 6         !! Index for woody litter below (unitless)
232  INTEGER(i_std), PARAMETER :: iactive_pool = 7         !! Index for active carbon pool (unitless)
233  INTEGER(i_std), PARAMETER :: islow_pool   = 8         !! Index for slow carbon pool (unitless)
234  INTEGER(i_std), PARAMETER :: ipassive_pool = 9        !! Index for passive carbon pool (unitless)
235  INTEGER(i_std), PARAMETER :: isurface_pool = 10       !! Index for surface carbon pool (unitless)
236
237
238  !
239  ! NUMERICAL AND PHYSICS CONSTANTS
240  !
241  !
242
243  !-
244  ! 1. Mathematical and numerical constants
245  !-
246  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
247  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
248  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
249  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
250  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
251  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
252  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
253  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
254  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
255  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
256  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
257  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
258  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
259
260  !-
261  ! 2 . Physics
262  !-
263  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
264  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
265  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
266  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
267  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
268  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
269  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
270  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
271  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
272  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
273  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
274  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
275                                                            !! of dry air (unitless)
276  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
277  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
278  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
279       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
280  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
281  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
282                                                            !! vapor minus 1(unitless) 
283  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
284                                                            !! minus 1 (unitless)
285  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
286  REAL(r_std), PARAMETER :: ct_karman = 0.41_r_std          !! Van Karmann Constant (unitless)
287  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
288  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
289  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
290  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
291
292
293  INTEGER(i_std), SAVE :: testpft = 6
294  !-
295  ! 3. Climatic constants
296  !-
297  !! Constantes of the Louis scheme
298  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
299                                                  !! reference to Louis (1979)
300!$OMP THREADPRIVATE(cb)
301  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
302                                                  !! reference to Louis (1979)
303!$OMP THREADPRIVATE(cc)
304  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
305                                                  !! reference to Louis (1979)
306!$OMP THREADPRIVATE(cd)
307  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
308!$OMP THREADPRIVATE(rayt_cste)
309  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
310!$OMP THREADPRIVATE(defc_plus)
311  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
312!$OMP THREADPRIVATE(defc_mult)
313
314  !-
315  ! 4. Soil thermodynamics constants
316  !-
317  ! Look at constantes_soil.f90
318
319
320  !
321  ! OPTIONAL PARTS OF THE MODEL
322  !
323  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
324                                                  !! we provide here a way to catch that in the calling procedure.
325                                                  !! (from Jan Polcher)(true/false)
326  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
327                                                  !! Value is read from run.def in intersurf_history
328!$OMP THREADPRIVATE(almaoutput)
329
330  !
331  ! DIVERSE
332  !
333  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
334                                                           ! Compatibility with Nicolas Viovy driver.
335!$OMP THREADPRIVATE(stomate_forcing_name)
336  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
337                                                           ! Compatibility with Nicolas Viovy driver.
338!$OMP THREADPRIVATE(stomate_Cforcing_name)
339  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
340!$OMP THREADPRIVATE(forcing_id)
341  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
342                                                     !! This variable will be set to false for teststomate.
343
344
345
346                         !------------------------!
347                         !  SECHIBA PARAMETERS    !
348                         !------------------------!
349 
350
351  !
352  ! GLOBAL PARAMETERS   
353  !
354  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
355!$OMP THREADPRIVATE(min_wind)
356  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
357!$OMP THREADPRIVATE(snowcri)
358
359
360  !
361  ! FLAGS ACTIVATING SUB-MODELS
362  !
363  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
364!$OMP THREADPRIVATE(treat_expansion)
365  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
366!$OMP THREADPRIVATE(ok_herbivores)
367  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
368!$OMP THREADPRIVATE(harvest_agri)
369  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
370!$OMP THREADPRIVATE(lpj_gap_const_mort)
371  LOGICAL, SAVE :: disable_fire = .FALSE.      !! flag that disable fire (true/false)
372!$OMP THREADPRIVATE(disable_fire)
373  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
374!$OMP THREADPRIVATE(spinup_analytic)
375  LOGICAL, SAVE :: ok_explicitsnow             !! Flag to activate explicit snow scheme instead of default snow scheme
376!$OMP THREADPRIVATE(ok_explicitsnow)
377
378  !
379  ! CONFIGURATION VEGETATION
380  !
381  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
382!$OMP THREADPRIVATE(agriculture)
383  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
384!$OMP THREADPRIVATE(impveg)
385  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
386!$OMP THREADPRIVATE(impsoilt)
387  LOGICAL, SAVE :: impose_ninput_dep = .FALSE. !! Impose N input values ? (true/false)
388!$OMP THREADPRIVATE(impose_ninput_dep)
389  LOGICAL, SAVE :: impose_ninput_fert = .FALSE. !! Impose N input values ? (true/false)       
390!$OMP THREADPRIVATE(impose_ninput_fert)   
391 LOGICAL, SAVE :: impose_ninput_manure = .FALSE. !! Impose N input values ? (true/false)       
392!$OMP THREADPRIVATE(impose_ninput_manure)                     
393  LOGICAL, SAVE :: impose_ninput_bnf = .FALSE. !! Impose N input values ? (true/false)       
394!$OMP THREADPRIVATE(impose_ninput_bnf)
395
396  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
397!$OMP THREADPRIVATE(do_now_stomate_lcchange)
398  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
399!$OMP THREADPRIVATE(done_stomate_lcchange)
400  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
401!$OMP THREADPRIVATE(read_lai)
402  LOGICAL, SAVE :: map_pft_format = .TRUE. !! Read a land use vegetation map on PFT format (true/false)
403!$OMP THREADPRIVATE(map_pft_format)
404  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
405!$OMP THREADPRIVATE(veget_reinit)
406  LOGICAL, SAVE :: ninput_reinit = .TRUE.  !! To change N INPUT file in a run. (true/false)
407!$OMP THREADPRIVATE(ninput_reinit)
408
409  !
410  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
411  !
412  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
413!$OMP THREADPRIVATE(max_snow_age)
414  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)
415!$OMP THREADPRIVATE(snow_trans)
416  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
417!$OMP THREADPRIVATE(sneige)
418  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
419!$OMP THREADPRIVATE(maxmass_snow)
420
421  !! Heat capacity
422  REAL(r_std), PARAMETER :: capa_ice = 2.228*1.E3       !! Heat capacity of ice (J/kg/K)
423  REAL(r_std), SAVE      :: so_capa_ice                 !! Heat capacity of saturated frozen soil (J/K/m3)
424!$OMP THREADPRIVATE(so_capa_ice)
425  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
426  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
427
428  !! Thermal conductivities
429  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
430  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
431  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
432
433  !! Time constant of long-term soil humidity (s)
434  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
435
436  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme   
437  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
438  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
439  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
440  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
441  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
442  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
443  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
444
445  !! The maximum snow density and water holding characterisicts
446  REAL(r_std), SAVE         :: xrhosmax = 750.  ! (kg m-3)
447  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  ! (-)
448  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  ! (-)
449  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 ! (kg/m3)
450  REAL(r_std), SAVE         :: xrhosmin = 50. 
451  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
452  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
453
454  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
455  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
456
457  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
458  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
459 
460  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
461  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
462  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
463  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
464
465  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
466 
467  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
468  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
469  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
470
471  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
472 
473  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
474  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
475  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
476  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
477 
478  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
479  ! (sig only for new snow OR high altitudes)
480  ! from Sun et al. (1999): based on data from Jordan (1991)
481  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
482  !
483  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_AVAP  = -0.06023 ! (W/m/K)
484  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_BVAP  = -2.5425  ! (W/m)
485  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_CVAP  = -289.99  ! (K)
486 
487  REAL(r_std),SAVE :: xansmax = 0.85      !! Maxmimum snow albedo
488  REAL(r_std),SAVE :: xansmin = 0.50      !! Miniumum snow albedo
489  REAL(r_std),SAVE :: xans_todry = 0.008  !! Albedo decay rate for dry snow
490  REAL(r_std),SAVE :: xans_t = 0.240      !! Albedo decay rate for wet snow
491
492  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
493  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
494  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
495
496  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
497  ! (sig only for new snow OR high altitudes)
498  ! from Sun et al. (1999): based on data from Jordan (1991)
499  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
500  !
501  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
502  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s)
503  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
504  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
505  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
506  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
507  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
508
509  !
510  ! BVOC : Biogenic activity  for each age class
511  !
512  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
513                                                                                       !! age class : isoprene (unitless)
514!$OMP THREADPRIVATE(iso_activity)
515  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
516                                                                                       !! age class : methanol (unnitless)
517!$OMP THREADPRIVATE(methanol_activity)
518
519  !
520  ! condveg.f90
521  !
522
523  ! 1. Scalar
524
525  ! 1.1 Flags used inside the module
526
527  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
528                                            !! albedo (see header of subroutine)
529                                            !! (true/false)
530!$OMP THREADPRIVATE(alb_bare_model)
531  LOGICAL, SAVE :: alb_bg_modis = .FALSE.   !! Switch for choosing values of bare soil
532                                            !! albedo read from file
533                                            !! (true/false)
534!$OMP THREADPRIVATE(alb_bg_modis)
535  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
536                                            !! (see header of subroutine). 
537                                            !! (true/false)
538!$OMP THREADPRIVATE(impaze)
539  LOGICAL, SAVE :: rough_dyn = .FALSE.      !! Chooses between two methods to calculate the
540                                            !! the roughness height : static or dynamic (varying with LAI)
541                                            !! (true/false)
542!$OMP THREADPRIVATE(rough_dyn)
543
544  LOGICAL, SAVE :: sla_dyn = .FALSE.        !! Chooses between two methods to calculate the
545                                            !! specific leaf area: static or dynamic (varying with LAI or biomass)
546                                            !! (true/false)
547!$OMP THREADPRIVATE(sla_dyn)
548
549  LOGICAL, SAVE :: new_watstress = .FALSE.
550!$OMP THREADPRIVATE(new_watstress)
551
552  REAL(r_std), SAVE :: alpha_watstress = 1.
553!$OMP THREADPRIVATE(alpha_watstress)
554
555  ! 1.2 Others
556
557  REAL(r_std), SAVE :: height_displacement = 0.66        !! Factor to calculate the zero-plane displacement
558                                                         !! height from vegetation height (m)
559!$OMP THREADPRIVATE(height_displacement)
560  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
561!$OMP THREADPRIVATE(z0_bare)
562  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
563!$OMP THREADPRIVATE(z0_ice)
564  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)
565!$OMP THREADPRIVATE(tcst_snowa)
566  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
567!$OMP THREADPRIVATE(snowcri_alb)
568  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
569!$OMP THREADPRIVATE(fixed_snow_albedo)
570  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
571!$OMP THREADPRIVATE(z0_scal)
572  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
573                                                         !! displacement height (m) (imposed)
574!$OMP THREADPRIVATE(roughheight_scal)
575  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
576!$OMP THREADPRIVATE(emis_scal)
577
578  REAL(r_std), SAVE :: c1 = 0.32                         !! Constant used in the formulation of the ratio of
579!$OMP THREADPRIVATE(c1)                                  !! friction velocity to the wind speed at the canopy top
580                                                         !! see Ershadi et al. (2015) for more info
581  REAL(r_std), SAVE :: c2 = 0.264                        !! Constant used in the formulation of the ratio of
582!$OMP THREADPRIVATE(c2)                                  !! friction velocity to the wind speed at the canopy top
583                                                         !! see Ershadi et al. (2015) for more info
584  REAL(r_std), SAVE :: c3 = 15.1                         !! Constant used in the formulation of the ratio of
585!$OMP THREADPRIVATE(c3)                                  !! friction velocity to the wind speed at the canopy top
586                                                         !! see Ershadi et al. (2015) for more info
587  REAL(r_std), SAVE :: Cdrag_foliage = 0.2               !! Drag coefficient of the foliage
588!$OMP THREADPRIVATE(Cdrag_foliage)                       !! See Ershadi et al. (2015) and Su et. al (2001) for more info
589  REAL(r_std), SAVE :: Ct = 0.01                         !! Heat transfer coefficient of the leaf
590!$OMP THREADPRIVATE(Ct)                                  !! See Ershadi et al. (2015) and Su et. al (2001) for more info
591  REAL(r_std), SAVE :: Prandtl = 0.71                    !! Prandtl number used in the calculation of Ct_star
592!$OMP THREADPRIVATE(Prandtl)                             !! See Su et. al (2001) for more info
593
594
595
596  ! 2. Arrays
597
598  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
599!$OMP THREADPRIVATE(alb_deadleaf)
600  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
601!$OMP THREADPRIVATE(alb_ice)
602  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
603                                                                     !! used imposed (unitless)
604!$OMP THREADPRIVATE(albedo_scal)
605  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
606       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
607                                                          !! dry soil albedo values in visible range
608!$OMP THREADPRIVATE(vis_dry)
609  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
610       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
611                                                          !! dry soil albedo values in near-infrared range
612!$OMP THREADPRIVATE(nir_dry)
613  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
614       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
615                                                          !! wet soil albedo values in visible range
616!$OMP THREADPRIVATE(vis_wet)
617  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
618       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
619                                                          !! wet soil albedo values in near-infrared range
620!$OMP THREADPRIVATE(nir_wet)
621  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
622       &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:
623                                                                   !! Averaged of wet and dry soil albedo values
624                                                                   !! in visible and near-infrared range
625!$OMP THREADPRIVATE(albsoil_vis)
626  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
627       &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:
628                                                                !! Averaged of wet and dry soil albedo values
629                                                                !! in visible and near-infrared range
630!$OMP THREADPRIVATE(albsoil_nir)
631
632  !
633  ! diffuco.f90
634  !
635
636  ! 0. Constants
637
638  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
639                                                     !! of dry air (unitless)
640  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
641  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
642  REAL(r_std), PARAMETER :: mol_to_m_1 = 0.0244      !!
643  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
644  REAL(r_std), PARAMETER :: W_to_mol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
645
646  ! 1. Scalar
647
648  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
649!$OMP THREADPRIVATE(nlai)
650  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
651!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
652  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
653!$OMP THREADPRIVATE(laimax)
654  LOGICAL, SAVE :: downregulation_co2 = .FALSE.            !! Set to .TRUE. if you want CO2 downregulation.
655!$OMP THREADPRIVATE(downregulation_co2)
656  REAL(r_std), SAVE :: downregulation_co2_baselevel = 280. !! CO2 base level (ppm)
657!$OMP THREADPRIVATE(downregulation_co2_baselevel)
658
659  REAL(r_std), SAVE :: gb_ref = 1./25.                     !! Leaf bulk boundary layer resistance (s m-1)
660
661  ! 3. Coefficients of equations
662
663  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
664!$OMP THREADPRIVATE(lai_level_depth)
665!
666  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
667  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
668!$OMP THREADPRIVATE(dew_veg_poly_coeff)
669!
670  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
671!$OMP THREADPRIVATE(Oi)
672  !
673  ! slowproc.f90
674  !
675
676  ! 1. Scalar
677
678  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
679!$OMP THREADPRIVATE(veget_year_orig)
680  INTEGER(i_std), SAVE :: ninput_year_orig = 0       !!  first year for N inputs (number)
681!$OMP THREADPRIVATE(ninput_year_orig)
682  LOGICAL, SAVE :: ninput_suffix_year = .FALSE.      !! Do the Ninput datasets have a 'year' suffix ? (y/n) 
683!$OMP THREADPRIVATE(ninput_suffix_year)
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 :: siltfraction_default = 0.5    !! Default value for silt fraction (0-1, unitless)
687!$OMP THREADPRIVATE(siltfraction_default)
688  REAL(r_std), SAVE :: bulk_default = 1000           !! Default value for bulk density of soil (kg/m3)
689!$OMP THREADPRIVATE(bulk_default)
690  REAL(r_std), SAVE :: ph_default = 5.5              !! Default value for pH of soil (-)
691!$OMP THREADPRIVATE(ph_default)
692  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
693!$OMP THREADPRIVATE(min_vegfrac)
694  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
695!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
696 
697  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
698!$OMP THREADPRIVATE(stempdiag_bid)
699
700
701                           !-----------------------------!
702                           !  STOMATE AND LPJ PARAMETERS !
703                           !-----------------------------!
704
705
706  !
707  ! lpj_constraints.f90
708  !
709 
710  ! 1. Scalar
711
712  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
713                                           !! regeneration (vernalization) (years)
714!$OMP THREADPRIVATE(too_long)
715
716
717  !
718  ! lpj_establish.f90
719  !
720
721  ! 1. Scalar
722
723  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (0-1, unitless)
724!$OMP THREADPRIVATE(estab_max_tree)
725  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (0-1, unitless)
726!$OMP THREADPRIVATE(estab_max_grass)
727 
728  ! 3. Coefficients of equations
729
730  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
731!$OMP THREADPRIVATE(establish_scal_fact)
732  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
733!$OMP THREADPRIVATE(max_tree_coverage)
734  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
735!$OMP THREADPRIVATE(ind_0_estab)
736
737
738  !
739  ! lpj_fire.f90
740  !
741
742  ! 1. Scalar
743
744  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
745!$OMP THREADPRIVATE(tau_fire)
746  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
747                                                !! below which iginitions extinguish
748                                                !! @tex $(gC m^{-2})$ @endtex
749!$OMP THREADPRIVATE(litter_crit)
750  REAL(r_std), SAVE :: fire_resist_lignin = 0.5 !!
751!$OMP THREADPRIVATE(fire_resist_lignin)
752  ! 2. Arrays
753
754  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
755       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95, .95 /)       !! compartments emitted to the atmosphere
756!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
757
758  ! 3. Coefficients of equations
759
760  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
761!$OMP THREADPRIVATE(bcfrac_coeff)
762  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
763!$OMP THREADPRIVATE(firefrac_coeff)
764
765  !
766  ! lpj_gap.f90
767  !
768
769  ! 1. Scalar
770
771  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
772                                                 !! @tex $(year^{-1})$ @endtex
773!$OMP THREADPRIVATE(ref_greff)
774
775  !               
776  ! lpj_light.f90
777  !             
778
779  ! 1. Scalar
780 
781  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
782                                            !! to fpc of last time step (F)? (true/false)
783!$OMP THREADPRIVATE(annual_increase)
784  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
785                                            !! (due to its branches etc.) (0-1, unitless)
786                                            !! This means that only a small fraction of its crown area
787                                            !! can be invaded by other trees.
788!$OMP THREADPRIVATE(min_cover)
789  !
790  ! lpj_pftinout.f90
791  !
792
793  ! 1. Scalar
794
795  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
796!$OMP THREADPRIVATE(min_avail)
797  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
798!$OMP THREADPRIVATE(ind_0)
799  ! 3. Coefficients of equations
800 
801  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
802!$OMP THREADPRIVATE(RIP_time_min)
803  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
804!$OMP THREADPRIVATE(npp_longterm_init)
805  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
806!$OMP THREADPRIVATE(everywhere_init)
807
808
809
810
811  !
812  ! stomate_data.f90
813  !
814
815  ! 1. Scalar
816
817  ! 1.2 climatic parameters
818
819  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
820!$OMP THREADPRIVATE(precip_crit)
821  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
822!$OMP THREADPRIVATE(gdd_crit_estab)
823  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
824!$OMP THREADPRIVATE(fpc_crit)
825
826  ! 1.3 sapling characteristics
827
828  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
829!$OMP THREADPRIVATE(alpha_grass)
830  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
831!$OMP THREADPRIVATE(alpha_tree)
832  REAL(r_std), SAVE :: struct_to_leaves = 0.05  !! Fraction of structural carbon in grass and crops as a share of the leaf
833                                                !! carbon pool. Only used for grasses and crops (thus NOT for trees)
834                                                !! (unitless)
835!$OMP THREADPRIVATE(struct_to_leaves)
836
837  REAL(r_std), SAVE :: labile_to_total = 0.01   !! Fraction of the labile pool in trees, grasses and crops as a share of the
838                                                !! total carbon pool (accounting for the N-content of the different tissues).
839                                                !! (unitless)
840!$OMP THREADPRIVATE(labile_to_total)
841
842
843
844  ! 1.4  time scales for phenology and other processes (in days)
845  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
846!$OMP THREADPRIVATE(tau_hum_month)
847  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
848!$OMP THREADPRIVATE(tau_hum_week)
849  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
850!$OMP THREADPRIVATE(tau_t2m_month)
851  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
852!$OMP THREADPRIVATE(tau_t2m_week)
853  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
854!$OMP THREADPRIVATE(tau_tsoil_month)
855  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
856!$OMP THREADPRIVATE(tau_soilhum_month)
857  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
858!$OMP THREADPRIVATE(tau_gpp_week)
859  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
860!$OMP THREADPRIVATE(tau_gdd)
861  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
862!$OMP THREADPRIVATE(tau_ngd)
863  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
864!$OMP THREADPRIVATE(coeff_tau_longterm)
865  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
866!$OMP THREADPRIVATE(tau_longterm_max)
867
868  ! 3. Coefficients of equations
869
870  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
871!$OMP THREADPRIVATE(bm_sapl_carbres)
872  REAL(r_std), SAVE :: bm_sapl_labile = 5.             !!
873!$OMP THREADPRIVATE(bm_sapl_labile)
874  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
875!$OMP THREADPRIVATE(bm_sapl_sapabove)
876  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
877!$OMP THREADPRIVATE(bm_sapl_heartabove)
878  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
879!$OMP THREADPRIVATE(bm_sapl_heartbelow)
880  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
881!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
882  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
883!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
884  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
885!$OMP THREADPRIVATE(init_sapl_mass_carbres)
886  REAL(r_std), SAVE :: init_sapl_mass_labile = 5.      !!
887!$OMP THREADPRIVATE(init_sapl_mass_labile)
888  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
889!$OMP THREADPRIVATE(init_sapl_mass_root)
890  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
891!$OMP THREADPRIVATE(init_sapl_mass_fruit)
892  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
893!$OMP THREADPRIVATE(cn_sapl_init)
894  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
895!$OMP THREADPRIVATE(migrate_tree)
896  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
897!$OMP THREADPRIVATE(migrate_grass)
898  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
899!$OMP THREADPRIVATE(lai_initmin_tree)
900  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
901!$OMP THREADPRIVATE(lai_initmin_grass)
902  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
903!$OMP THREADPRIVATE(dia_coeff)
904  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
905!$OMP THREADPRIVATE(maxdia_coeff)
906  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
907!$OMP THREADPRIVATE(bm_sapl_leaf)
908
909
910  !
911  ! stomate_litter.f90
912  !
913
914  ! 0. Constants
915
916  REAL(r_std), PARAMETER :: Q10 = 10.               !!
917
918  ! 1. Scalar
919
920  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
921!$OMP THREADPRIVATE(z_decomp)
922
923  ! 2. Arrays
924
925  REAL(r_std), SAVE :: frac_soil_struct_sua = 0.4    !! corresponding to frac_soil(istructural,isurface,iabove)
926!$OMP THREADPRIVATE(frac_soil_struct_sua)
927  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
928!$OMP THREADPRIVATE(frac_soil_struct_ab)
929  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
930!$OMP THREADPRIVATE(frac_soil_struct_sa)
931  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
932!$OMP THREADPRIVATE(frac_soil_struct_sb)
933  REAL(r_std), SAVE :: frac_soil_metab_sua = 0.4    !! corresponding to frac_soil(imetabolic,iactive,iabove)
934!$OMP THREADPRIVATE(frac_soil_metab_sua)
935  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
936!$OMP THREADPRIVATE(frac_soil_metab_ab)
937  REAL(r_std), SAVE, DIMENSION(nparts) :: CN_fix = & !! C/N ratio of each plant pool (0-100, unitless)
938       & (/ 40., 40., 40., 40., 40., 40., 40., 40., 40. /) 
939!$OMP THREADPRIVATE(CN_fix)
940
941  ! 3. Coefficients of equations
942
943  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
944!$OMP THREADPRIVATE(metabolic_ref_frac)
945  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
946!$OMP THREADPRIVATE(metabolic_LN_ratio)
947  ! Turnover rate (yr-1) - From Parton et al., 1993
948  REAL(r_std), SAVE :: turn_metabolic = 15           !!
949!$OMP THREADPRIVATE(turn_metabolic)
950  REAL(r_std), SAVE :: turn_struct = 4                !!
951!$OMP THREADPRIVATE(turn_struct)
952  REAL(r_std), SAVE :: turn_woody = 1.33              !! from DOFOCO
953!$OMP THREADPRIVATE(turn_woody)
954  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
955!$OMP THREADPRIVATE(soil_Q10)
956  REAL(r_std), SAVE :: soil_Q10_uptake = 0.69              !!= ln 2
957!$OMP THREADPRIVATE(soil_Q10_uptake)
958  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
959!$OMP THREADPRIVATE(tsoil_ref)
960  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
961!$OMP THREADPRIVATE(litter_struct_coef)
962  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
963!$OMP THREADPRIVATE(moist_coeff)
964  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
965!$OMP THREADPRIVATE(moistcont_min)
966
967
968  !
969  ! stomate_lpj.f90
970  !
971
972  ! 1. Scalar
973
974  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
975!$OMP THREADPRIVATE(frac_turnover_daily)
976
977
978  !
979  ! stomate_npp.f90
980  !
981
982  ! 1. Scalar
983
984  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
985                                     !! for maintenance respiration (0-1, unitless)
986!$OMP THREADPRIVATE(tax_max)
987
988
989  !
990  ! stomate_phenology.f90
991  !
992
993  ! 1. Scalar
994
995  LOGICAL, SAVE :: always_init = .FALSE.           !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
996!$OMP THREADPRIVATE(always_init)
997  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
998!$OMP THREADPRIVATE(min_growthinit_time)
999  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1000                                                   !!  - for trees (0-1, unitless)
1001!$OMP THREADPRIVATE(moiavail_always_tree)
1002  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1003                                                   !! - for grass (0-1, unitless)
1004!$OMP THREADPRIVATE(moiavail_always_grass)
1005  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1006!$OMP THREADPRIVATE(t_always)
1007  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1008!$OMP THREADPRIVATE(t_always_add)
1009
1010  ! 3. Coefficients of equations
1011 
1012  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
1013!$OMP THREADPRIVATE(gddncd_ref)
1014  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
1015!$OMP THREADPRIVATE(gddncd_curve)
1016  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
1017!$OMP THREADPRIVATE(gddncd_offset)
1018
1019
1020  !
1021  ! stomate_prescribe.f90
1022  !
1023
1024  ! 3. Coefficients of equations
1025
1026  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
1027!$OMP THREADPRIVATE(bm_sapl_rescale)
1028
1029
1030  !
1031  ! stomate_resp.f90
1032  !
1033
1034  ! 3. Coefficients of equations
1035
1036  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1037!$OMP THREADPRIVATE(maint_resp_min_vmax)
1038  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1039!$OMP THREADPRIVATE(maint_resp_coeff)
1040
1041
1042  !
1043  ! stomate_som_dynamics.f90 (in stomate_soilcarbon.f90)   
1044  !
1045
1046  ! 2. Arrays
1047
1048  ! 2.1 Fixed fraction from one pool to another (or to CO2 emission)
1049
1050  REAL(r_std), SAVE :: active_to_pass_ref_frac = 0.003  !! from active pool: depends on clay content  (0-1, unitless)
1051                                                        !! corresponding to frac_carb(:,iactive,ipassive)
1052  REAL(r_std), SAVE :: surf_to_slow_ref_frac = 0.4      !! from surface pool
1053                                                        !! corresponding to frac_carb(:,isurf,islow)
1054  REAL(r_std), SAVE :: active_to_CO2_ref_frac  = 0.85   !! from active pool: depends on clay content  (0-1, unitless)
1055                                                        !! corresponding to frac_resp(:,iactive)
1056!$OMP THREADPRIVATE(active_to_CO2_ref_frac)
1057  REAL(r_std), SAVE :: slow_to_pass_ref_frac   = 0.03  !! from slow pool: depends on clay content  (0-1, unitless)
1058                                                        !! corresponding to frac_carb(:,islow,ipassive)
1059!$OMP THREADPRIVATE(slow_to_pass_ref_frac)
1060  REAL(r_std), SAVE :: slow_to_CO2_ref_frac    = 0.55   !! from slow pool (0-1, unitless)
1061                                                        !! corresponding to frac_resp(:,islow)
1062!$OMP THREADPRIVATE(slow_to_CO2_ref_frac)
1063  REAL(r_std), SAVE :: pass_to_active_ref_frac = 0.45   !! from passive pool (0-1, unitless)
1064                                                        !! corresponding to frac_carb(:,ipassive,iactive)
1065!$OMP THREADPRIVATE(pass_to_active_ref_frac)
1066  REAL(r_std), SAVE :: pass_to_slow_ref_frac   = 0.0    !! from passive pool (0-1, unitless)
1067                                                        !! corresponding to frac_carb(:,ipassive,islow)
1068!$OMP THREADPRIVATE(pass_to_slow_ref_frac)
1069
1070  ! 3. Define Variable fraction from one pool to another (function of silt and clay fraction)
1071  REAL(r_std), SAVE :: active_to_pass_clay_frac     = 0.032
1072!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1073  !! residence times in carbon pools (days)
1074
1075  REAL(r_std), SAVE :: active_to_CO2_clay_silt_frac = 0.68
1076!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1077  REAL(r_std), SAVE :: slow_to_pass_clay_frac   = 0 
1078!$OMP THREADPRIVATE(slow_to_pass_clay_frac)
1079
1080  ! C to N target ratios of differnt pools
1081  REAL(r_std), SAVE ::  CN_target_iactive_ref  = 15. !! CN target ratio of active pool for soil min N = 0
1082  REAL(r_std), SAVE ::  CN_target_islow_ref    = 20. !! CN target ratio of slow pool for soil min N = 0
1083  REAL(r_std), SAVE ::  CN_target_ipassive_ref = 10. !! CN target ratio of passive pool for soil min N = 0
1084  REAL(r_std), SAVE ::  CN_target_isurface_ref = 20. !! CN target ratio of surface pool for litter nitrogen content = 0
1085
1086  REAL(r_std), SAVE ::  CN_target_iactive_Nmin  = -6.  !! CN target ratio change per mineral N unit (g m-2) for active pool
1087  REAL(r_std), SAVE ::  CN_target_islow_Nmin    = -4.  !! CN target ratio change per mineral N unit (g m-2) for slow pool
1088  REAL(r_std), SAVE ::  CN_target_ipassive_Nmin = -1.5 !! CN target ratio change per mineral N unit (g m-2) for passive pool
1089  REAL(r_std), SAVE ::  CN_target_isurface_pnc  = -5.  !! CN target ratio change per plant nitrogen content unit (%) for surface pool
1090  !! Turnover in SOM pools (year-1)
1091  REAL(r_std), SAVE :: som_turn_isurface = 6.0           !! turnover of surface pool (year-1)
1092!$OMP THREADPRIVATE(som_turn_isurface)
1093  REAL(r_std), SAVE :: som_turn_iactive  = 7.3           !! turnover of active pool (year-1)
1094!$OMP THREADPRIVATE(som_turn_iactive)
1095  REAL(r_std), SAVE :: som_turn_islow    = 0.2           !! turnover of slow pool (year-1)
1096!$OMP THREADPRIVATE(som_turn_islow)
1097  REAL(r_std), SAVE :: som_turn_ipassive = 0.0045        !! turnover of passive pool (year-1)
1098!$OMP THREADPRIVATE(som_turn_ipassive)
1099
1100
1101  REAL(r_std), SAVE :: som_turn_iactive_clay_frac = 0.75 !! clay-dependant parameter impacting on turnover rate of active pool
1102                                                         !! Tm parameter of Parton et al. 1993 (-)
1103!$OMP THREADPRIVATE(som_turn_iactive_clay_frac)
1104
1105  !
1106  ! stomate_turnover.f90
1107  !
1108
1109  ! 3. Coefficients of equations
1110
1111  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1112!$OMP THREADPRIVATE(new_turnover_time_ref)
1113  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
1114!$OMP THREADPRIVATE(leaf_age_crit_tref)
1115  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
1116!$OMP THREADPRIVATE(leaf_age_crit_coeff)
1117
1118
1119  !
1120  ! stomate_vmax.f90
1121  !
1122 
1123  ! 1. Scalar
1124
1125  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1126!$OMP THREADPRIVATE(vmax_offset)
1127  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1128                                                !! reaches 1 (unitless)
1129!$OMP THREADPRIVATE(leafage_firstmax)
1130  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1131                                                !! falls below 1 (unitless)
1132!$OMP THREADPRIVATE(leafage_lastmax)
1133  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1134                                                !! reaches its minimum (vmax_offset)
1135                                                !! (unitless)
1136!$OMP THREADPRIVATE(leafage_old)
1137
1138
1139  !
1140  ! nitrogen_dynamics (in stomate_soilcarbon.f90)
1141  !
1142
1143  ! 0. Constants
1144  REAL(r_std), PARAMETER :: D_air = 1.73664     !! Oxygen diffusion rate in the air = 0.07236 m2/h
1145                                               !! from Table 2 of Li et al, 2000
1146                                               !! (m**2/day)
1147
1148  REAL(r_std), PARAMETER :: C_molar_mass = 12  !! Carbon Molar mass (gC mol-1)
1149
1150  REAL(r_std), PARAMETER :: Pa_to_hPa    = 0.01      !! Conversion factor from Pa to hPa (-)
1151  REAL(r_std), PARAMETER :: V_O2         = 0.209476  !! Volumetric fraction of O2 in air (-)
1152
1153  REAL(r_std), PARAMETER :: pk_NH4 = 9.25      !! The negative logarithm of the acid dissociation constant K_NH4     
1154                                               !! See Table 4 of Li et al. 1992 and Appendix A of Zhang et al. 2002   
1155
1156                                     
1157  ! 1. Scalar
1158
1159  ! Coefficients for defining maximum porosity
1160  ! From Saxton, K.E., Rawls, W.J., Romberger, J.S., Papendick, R.I., 1986
1161  ! Estimationg generalized soil-water characteristics from texture.
1162  ! Soil Sci. Soc. Am. J. 50, 1031-1036
1163  ! Cited in Table 5 (page 444) of
1164  ! Y. Pachepsky, W.J. Rawls
1165  ! Development of Pedotransfer Functions in Soil Hydrology
1166  ! Elsevier, 23 nov. 2004 - 542 pages
1167  ! http://books.google.fr/books?id=ar_lPXaJ8QkC&printsec=frontcover&hl=fr#v=onepage&q&f=false
1168  REAL(r_std), SAVE :: h_saxton = 0.332          !! h coefficient
1169!$OMP THREADPRIVATE(h_saxton)
1170  REAL(r_std), SAVE :: j_saxton = -7.251*1e-4    !! j coefficient
1171!$OMP THREADPRIVATE(j_saxton)
1172  REAL(r_std), SAVE :: k_saxton = 0.1276         !! k coefficient
1173!$OMP THREADPRIVATE(k_saxton)
1174
1175  ! Values of the power used in the equation defining the diffusion of oxygen in soil
1176  ! from Table 2 of Li et al, 2000
1177  REAL(r_std), SAVE :: diffusionO2_power_1 = 3.33 !! (unitless)
1178!$OMP THREADPRIVATE(diffusionO2_power_1)
1179  REAL(r_std), SAVE :: diffusionO2_power_2 = 2.0  !! (unitless)
1180!$OMP THREADPRIVATE(diffusionO2_power_2)
1181
1182  ! Temperature-related Factors impacting on Oxygen diffusion rate
1183  ! From eq. 2 of Table 2 (Li et al, 2000)
1184  REAL(r_std), SAVE ::   F_nofrost = 1.2          !! (unitless)
1185!$OMP THREADPRIVATE(F_nofrost)
1186  REAL(r_std), SAVE ::   F_frost   = 0.8          !! (unitless)
1187!$OMP THREADPRIVATE(F_frost)
1188
1189  ! Coefficients used in the calculation of Volumetric fraction of anaerobic microsites
1190  ! a and b constants are not specified in Li et al., 2000
1191  ! S. Zaehle used a=0.85 and b=1 without mention to any publication
1192  REAL(r_std), SAVE ::   a_anvf    = 0.85 !! (-)
1193!$OMP THREADPRIVATE(a_anvf)
1194  REAL(r_std), SAVE ::   b_anvf    = 1.   !! (-)
1195!$OMP THREADPRIVATE(b_anvf)
1196
1197  ! Coefficients used in the calculation of the Fraction of adsorbed NH4+
1198  ! Li et al. 1992, JGR, Table 4
1199  REAL(r_std), SAVE ::   a_FixNH4 = 0.41  !! (-)
1200!$OMP THREADPRIVATE(a_FixNH4)
1201  REAL(r_std), SAVE ::   b_FixNH4 = -0.47 !! (-)
1202!$OMP THREADPRIVATE(b_FixNH4)
1203  REAL(r_std), SAVE ::   clay_max = 0.63  !! (-)
1204!$OMP THREADPRIVATE(clay_max)
1205
1206  ! Coefficients used in the calculation of the Response of Nitrification
1207  ! to soil moisture
1208  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1209  REAL(r_std), SAVE ::   fwnit_0 =  -0.0243  !! (-)
1210!$OMP THREADPRIVATE(fwnit_0)
1211  REAL(r_std), SAVE ::   fwnit_1 =   0.9975  !! (-)
1212!$OMP THREADPRIVATE(fwnit_1)
1213  REAL(r_std), SAVE ::   fwnit_2 =  -5.5368  !! (-)
1214!$OMP THREADPRIVATE(fwnit_2)
1215  REAL(r_std), SAVE ::   fwnit_3 =  17.651   !! (-)
1216!$OMP THREADPRIVATE(fwnit_3)
1217  REAL(r_std), SAVE ::   fwnit_4 = -12.904   !! (-)
1218!$OMP THREADPRIVATE(fwnit_4)
1219
1220  ! Coefficients used in the calculation of the Response of Nitrification
1221  ! to Temperature
1222  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1223  REAL(r_std), SAVE ::   ft_nit_0 =  -0.0233 !! (-)
1224!$OMP THREADPRIVATE(ft_nit_0)
1225  REAL(r_std), SAVE ::   ft_nit_1 =   0.3094 !! (-)
1226!$OMP THREADPRIVATE(ft_nit_1)
1227  REAL(r_std), SAVE ::   ft_nit_2 =  -0.2234 !! (-)
1228!$OMP THREADPRIVATE(ft_nit_2)
1229  REAL(r_std), SAVE ::   ft_nit_3 =   0.1566 !! (-)
1230!$OMP THREADPRIVATE(ft_nit_3)
1231  REAL(r_std), SAVE ::   ft_nit_4 =  -0.0272 !! (-)
1232!$OMP THREADPRIVATE(ft_nit_4)
1233
1234  ! Coefficients used in the calculation of the Response of Nitrification
1235  ! to pH
1236  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1237  REAL(r_std), SAVE ::   fph_0 = -1.2314  !! (-)
1238!$OMP THREADPRIVATE(fph_0)
1239  REAL(r_std), SAVE ::   fph_1 = 0.7347   !! (-)
1240!$OMP THREADPRIVATE(fph_1)
1241  REAL(r_std), SAVE ::   fph_2 = -0.0604  !! (-)
1242!$OMP THREADPRIVATE(fph_2)
1243
1244  ! Coefficients used in the calculation of the response of NO2 or NO
1245  ! production during nitrificationof to Temperature
1246  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 102
1247  REAL(r_std), SAVE ::   ftv_0 = 2.72   !! (-)
1248!$OMP THREADPRIVATE(ftv_0)
1249  REAL(r_std), SAVE ::   ftv_1 = 34.6   !! (-)
1250!$OMP THREADPRIVATE(ftv_1)
1251  REAL(r_std), SAVE ::   ftv_2 = 9615.  !! (-)
1252!$OMP THREADPRIVATE(ftv_2)
1253
1254  REAL(r_std), SAVE ::   k_nitrif = 0.2         !! Nitrification rate at 20 ◩C and field capacity (day-1)
1255                                                !! from Schmid et al., 2001
1256!$OMP THREADPRIVATE(k_nitrif)
1257
1258  REAL(r_std), SAVE ::   n2o_nitrif_p = 0.0006  !! Reference n2o production per N-NO3 produced g N-N2O  (g N-NO3)-1
1259                                                !! From Zhang et al., 2002 - Appendix A p. 102
1260!$OMP THREADPRIVATE(n2o_nitrif_p)
1261  REAL(r_std), SAVE ::   no_nitrif_p = 0.0025   !! Reference NO production per N-NO3 produced g N-NO  (g N-NO3)-1
1262                                                !! From Zhang et al., 2002 - Appendix A p. 102
1263!$OMP THREADPRIVATE(no_nitrif_p)
1264
1265  ! NO production from chemodenitrification
1266  ! based on Kesik et al., 2005, Biogeosciences
1267  ! Coefficients used in the calculation of the Response to Temperature
1268  REAL(r_std), SAVE ::   chemo_t0  = -31494. !! (-)
1269!$OMP THREADPRIVATE(chemo_t0)
1270  ! Coefficients use in the calculation of the Response to pH
1271  REAL(r_std), SAVE ::   chemo_ph0 = -1.62   !! (-)
1272!$OMP THREADPRIVATE(chemo_ph0)
1273  ! Coefficients used in the calculation of NO production from chemodenitrification
1274  REAL(r_std), SAVE ::   chemo_0   = 30.     !! (-)
1275!$OMP THREADPRIVATE(chemo_0)
1276  REAL(r_std), SAVE ::   chemo_1   = 16565.  !! (-)
1277!$OMP THREADPRIVATE(chemo_1)
1278
1279  ! Denitrification processes
1280  ! Li et al, 2000, JGR Table 4 eq 1, 2 and 4
1281  !
1282  ! Coefficients used in the Temperature response of
1283  ! relative growth rate of total denitrifiers - Eq. 2 Table 4 of Li et al., 2000
1284  REAL(r_std), SAVE ::   ft_denit_0 = 2.     !! (-)
1285!$OMP THREADPRIVATE(ft_denit_0)
1286  REAL(r_std), SAVE ::   ft_denit_1 = 22.5   !! (-)
1287!$OMP THREADPRIVATE(ft_denit_1)
1288  REAL(r_std), SAVE ::   ft_denit_2 = 10.    !! (-)
1289!$OMP THREADPRIVATE(ft_denit_2)
1290  !
1291  ! Coefficients used in the pH response of
1292  ! relative growth rate of total denitrifiers - Eq. 2 Table 4 of Li et al., 2000
1293  REAL(r_std), SAVE ::   fph_no3_0  = 4.25    !! (-)
1294!$OMP THREADPRIVATE(fph_no3_0)
1295  REAL(r_std), SAVE ::   fph_no3_1  = 0.5     !! (-)
1296!$OMP THREADPRIVATE(fph_no3_1)
1297  REAL(r_std), SAVE ::   fph_no_0  = 5.25     !! (-)
1298!$OMP THREADPRIVATE(fph_no_0)
1299  REAL(r_std), SAVE ::   fph_no_1  = 1.       !! (-)
1300!$OMP THREADPRIVATE(fph_no_1)
1301  REAL(r_std), SAVE ::   fph_n2o_0  = 6.25    !! (-)
1302!$OMP THREADPRIVATE(fph_n2o_0)
1303  REAL(r_std), SAVE ::   fph_n2o_1  = 1.5     !! (-)
1304!$OMP THREADPRIVATE(fph_n2o_1)
1305
1306  REAL(r_std), SAVE ::   Kn = 0.083           !! Half Saturation of N oxydes (kgN/m3)
1307                                              !! Table 4 of Li et al., 2000
1308!$OMP THREADPRIVATE(Kn)
1309
1310  ! Maximum Relative growth rate of Nox denitrifiers
1311  ! Eq.1 Table 4 Li et al., 2000
1312  REAL(r_std), SAVE ::   mu_no3_max = 0.67   !! (hour-1)
1313!$OMP THREADPRIVATE(mu_no3_max)
1314  REAL(r_std), SAVE ::   mu_no_max  = 0.34   !! (hour-1)
1315!$OMP THREADPRIVATE(mu_no_max)
1316  REAL(r_std), SAVE ::   mu_n2o_max = 0.34   !! (hour-1)
1317!$OMP THREADPRIVATE(mu_n2o_max)
1318
1319  ! Maximum growth yield of NOx denitrifiers on N oxydes
1320  ! Table 4 Li et al., 2000
1321  REAL(r_std), SAVE ::   Y_no3 = 0.401 !! (kgC / kgN)
1322!$OMP THREADPRIVATE(Y_no3)
1323  REAL(r_std), SAVE ::   Y_no  = 0.428 !! (kgC / kgN)
1324!$OMP THREADPRIVATE(Y_no)
1325  REAL(r_std), SAVE ::   Y_n2o = 0.151 !! (kgC / kgN)
1326!$OMP THREADPRIVATE(Y_n2o)
1327
1328  ! Maintenance coefficient on N oxyde
1329  ! Table 4 Li et al., 2000
1330  REAL(r_std), SAVE ::   M_no3 = 0.09   !! (kgN / kgC / hour)
1331!$OMP THREADPRIVATE(M_no3)
1332  REAL(r_std), SAVE ::   M_no  = 0.035  !! (kgN / kgC / hour)
1333!$OMP THREADPRIVATE(M_no)
1334  REAL(r_std), SAVE ::   M_n2o = 0.079  !! (kgN / kgC / hour)
1335!$OMP THREADPRIVATE(M_n2o)
1336
1337       
1338  REAL(r_std), SAVE ::   Maint_c = 0.0076    !! Maintenance coefficient of carbon (kgC/kgC/h)
1339                                        !! Table 4 Li et al., 2000
1340!$OMP THREADPRIVATE(Maint_c)
1341  REAL(r_std), SAVE ::   Yc = 0.503     !! Maximum growth yield on soluble carbon (kgC/kgC)
1342                                        !! Table 4 Li et al., 2000
1343!$OMP THREADPRIVATE(Yc)
1344
1345  !! Coefficients used in the eq. defining the response of N-emission to clay fraction (-)
1346  !! from  Table 4, Li et al. 2000
1347  REAL(r_std), SAVE ::   F_clay_0 = 0.13   
1348!$OMP THREADPRIVATE(F_clay_0)
1349  REAL(r_std), SAVE ::   F_clay_1 = -0.079
1350!$OMP THREADPRIVATE(F_clay_1)
1351
1352
1353  REAL(r_std), SAVE ::   ratio_nh4_fert = 0.875  !! Proportion of ammonium in the fertilizers (ammo-nitrate)
1354                                                 !! = 7./8. (-)
1355!$OMP THREADPRIVATE(ratio_nh4_fert)
1356
1357  ! 2. Arrays
1358  REAL(r_std), SAVE, DIMENSION(2)  :: vmax_uptake = (/ 3. , 3. /) !! Vmax of nitrogen uptake by plants
1359                                                                  !! for Ammonium (ind.1) and Nitrate (ind.2)
1360                                                                  !! (in umol (g DryWeight_root)-1 h-1)
1361                                                                  !! from  Kronzucker et al. (1995, 1996)
1362!$OMP THREADPRIVATE(vmax_uptake)
1363
1364  REAL(r_std), SAVE, DIMENSION(2)  :: K_N_min = (/ 30., 30. /)    !! [NH4+] (resp. [NO3-]) for which the Nuptake
1365                                                                  !! equals vmax/2.   (umol per litter)
1366                                                                  !! from Kronzucker, 1995
1367!$OMP THREADPRIVATE(K_N_min)
1368
1369  REAL(r_std), SAVE, DIMENSION(2)  :: low_K_N_min = (/ 0.0002, 0.0002 /) !! Rate of N uptake not associated with
1370                                                                         !! Michaelis- Menten Kinetics for Ammonium
1371                                                                         !! (ind.1) and Nitrate (ind.2)
1372                                                                         !! from Kronzucker, 1995 ((umol)-1)
1373!$OMP THREADPRIVATE(low_K_N_min)
1374
1375
1376  !! Other N-related parameters
1377  REAL(r_std), SAVE                                  :: Dmax = 0.25      !! Parameter te be clarified (what it is, units, ...)
1378                                                                         !! used in stomate_growth_fun_all
1379
1380  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
1381                                                   !! carbohydrate reserve may be used for
1382                                                   !! trees (days)
1383!$OMP THREADPRIVATE(reserve_time_tree)
1384  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
1385                                                   !! carbohydrate reserve may be used for
1386                                                   !! grasses (days)
1387!$OMP THREADPRIVATE(reserve_time_grass)
1388
1389  !
1390  ! stomate_season.f90
1391  !
1392
1393  ! 1. Scalar
1394
1395  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
1396!$OMP THREADPRIVATE(gppfrac_dormance)
1397  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
1398!$OMP THREADPRIVATE(tau_climatology)
1399  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
1400!$OMP THREADPRIVATE(hvc1)
1401  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
1402!$OMP THREADPRIVATE(hvc2)
1403  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
1404!$OMP THREADPRIVATE(leaf_frac_hvc)
1405  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
1406!$OMP THREADPRIVATE(tlong_ref_max)
1407  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
1408!$OMP THREADPRIVATE(tlong_ref_min)
1409
1410  ! 3. Coefficients of equations
1411
1412  REAL(r_std), SAVE :: ncd_max_year = 3.
1413!$OMP THREADPRIVATE(ncd_max_year)
1414  REAL(r_std), SAVE :: gdd_threshold = 5.
1415!$OMP THREADPRIVATE(gdd_threshold)
1416  REAL(r_std), SAVE :: green_age_ever = 2.
1417!$OMP THREADPRIVATE(green_age_ever)
1418  REAL(r_std), SAVE :: green_age_dec = 0.5
1419!$OMP THREADPRIVATE(green_age_dec)
1420
1421  INTEGER(i_std), SAVE :: ncirc = 1                  !! Number of circumference classes used to calculate C allocation
1422!$OMP THREADPRIVATE(ncirc)
1423  REAL(r_std), PARAMETER :: kilo_to_unit = 1.0E03   !! Convert Kilo to unit
1424
1425
1426LOGICAL, SAVE :: lbypass_cc = .FALSE.                      !! Set to true for a temporary patch of a known bug, though the underlying
1427!$OMP THREADPRIVATE(lbypass_cc)
1428LOGICAL, SAVE :: ld_fake_height=.TRUE.  ! a flag to turn on the statements
1429!$OMP THREADPRIVATE(ld_fake_height)
1430REAL(r_std), SAVE :: sync_threshold = 0.0001     !! The threshold above which a warning is generated when the
1431!$OMP THREADPRIVATE(sync_threshold)
1432LOGICAL,PARAMETER :: ld_biomass=.FALSE.   ! a flag to turn on debug statements
1433INTEGER(i_std), SAVE        :: test_pft = 4                              !! Number of PFT for which detailed output
1434!$OMP THREADPRIVATE(test_pft)
1435
1436INTEGER(i_std), SAVE        :: test_grid = 1                                 !! Number of the grid square for which detailed output
1437!$OMP THREADPRIVATE(test_grid)
1438
1439LOGICAL,PARAMETER                       :: ld_stop=.FALSE.      ! a flag to turn on some stop statements.
1440LOGICAL,SAVE                            :: ld_alloc=.FALSE.     ! a flag to turn on debug statements
1441LOGICAL,PARAMETER                       :: ld_warn=.FALSE.      ! a flag to turn on various warnings
1442LOGICAL,PARAMETER                       :: jr_nextstep = .FALSE.   ! set this to TRUE to activate the
1443LOGICAL,PARAMETER                       :: ld_massbal=.FALSE.   ! a flag to turn on debug statements
1444INTEGER(i_std), PARAMETER :: ipoolchange = 5           !! change in pool size i.e. change in biomass
1445
1446INTEGER(i_std), PARAMETER :: ilat2in = 4               !! incoming lateral flux i.e. N deposition for the land
1447INTEGER(i_std), PARAMETER :: ilat2out = 3              !! outgoing lateral flux i.e. DOC leaching for the litter routine
1448INTEGER(i_std), PARAMETER :: iatm2land = 1             !! atmosphere to land fluxes such as GPP and co2_2_bm
1449INTEGER(i_std), PARAMETER :: iland2atm = 2             !! land to atmosphere fluxes such as Rh, Ra and product decomposition
1450INTEGER(i_std), PARAMETER :: nmbcomp = 5               !! The total nomber of components in our mass balance check
1451
1452
1453REAL(r_std), SAVE :: max_delta_KF = 0.1          !! Maximum change in KF from one time step to another (m)
1454                                                   !! This is a bit arbitrary.
1455!$OMP THREADPRIVATE(max_delta_KF)
1456
1457 REAL(r_std), SAVE :: maint_from_gpp = 0.8        !! Some carbon needs to remain to support the growth, hence,
1458                                                   !! respiration will be limited. In this case resp_maint
1459                                                   !! (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
1460                                                   !! of the GPP (gC m-2 s-1)
1461!$OMP THREADPRIVATE(maint_from_gpp)
1462 
1463  REAL(r_std), PARAMETER :: m2_to_ha = 10000.       !! Conversion from m2 to hectares
1464  REAL(r_std), PARAMETER :: ha_to_m2 = 0.0001       !! Conversion from hectares (forestry) to m2 (rest of the code)
1465
1466END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.