source: branches/publications/ORCHIDEE_CN-P_v1.2_r5986/ORCHIDEE/src_parameters/constantes_var.f90

Last change on this file was 5984, checked in by daniel.goll, 6 years ago

dsg

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