source: tags/ORCHIDEE_4_1/ORCHIDEE/src_parameters/constantes_var.f90 @ 7852

Last change on this file since 7852 was 7686, checked in by sebastiaan.luyssaert, 2 years ago

Contributes to #814. This commit has not been tested for the two test cases with interacting disturbances.

  • Property svn:keywords set to Date Revision
File size: 128.3 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
53  INTEGER, SAVE       :: energy_control                       !! Flag that automatically controls several other flags related to
54                                                              !! multi-layering (1/2/3).
55                                                              !! 1 - DEFAULT used the enerbil module in combination with the
56                                                              !! hydraulic architecture ((ok_hydrol_arch and ok_gs_feedback
57                                                              !! true, while ok_mleb and ok_impose_canopy_structure are set
58                                                              !! to false
59                                                              !! 2 - option to use enerbil module and original water stress
60                                                              !! (not hydraulic architecture)
61                                                              !! 3 - single layer: ok_hydrol_arch, ok_gs_feedback, ok_impose_canopy_structure
62                                                              !! and ok_mleb all true, but the energy budget is only calculated for a single layer
63                                                              !! (jnlvls=1,jnlvls_under=0,jnlvls_canopy=1,jnlvls_over=0).
64                                                              !! 4 - multi-layer: ok_hydrol_arch, ok_gs_feedback,  ok_impose_canopy_structure,
65                                                              !! ok_mleb all true, and the energy budget is calculated for multiple layers
66                                                              !! (jnlvls=29,jnlvls_under=10,jnlvls_canopy=10,jnlvls_over=9).   
67                                                              !! 5 - user specific: user specific settings for these controls
68                                                              !! and layers as defined in the run.def by the user.
69!$OMP THREADPRIVATE(energy_control)
70  LOGICAL, SAVE       :: ok_hydrol_arch                       !! Flag that activates the hydraulic architecture routine (true/false)
71                                                              !! The trunk version of ORCHIDEE (false) uses soil water as a
72                                                              !! proxy for water stress and applies the stress to Vcmax.
73                                                              !! When set to true the hydraulic architecture of the vegetation
74                                                              !! is accounted for to calculate the amount of water that
75                                                              !! can be transported through the plant given the soil and leaf
76                                                              !! potential and the conductivities of the roots, wood and
77                                                              !! leaves. Water supply through the plant is compared against
78                                                              !! the atmospheric demand for water. If the supply is smaller
79                                                              !! then the demand, the plant experiences water stress and the
80                                                              !! stomata will be closed (water stress is now on gs rather
81                                                              !! than Vcmax). Note that whether stomatal regulation is used or
82                                                              !! not is controled by a separate flag: ok_gs_feedback.
83!$OMP THREADPRIVATE(ok_hydrol_arch)
84
85  LOGICAL, SAVE       :: ok_gs_feedback                       !! Flag that activates water stress on stomata (true/false)
86                                                              !! This flag is for debugging only! It allows developers
87                                                              !! to calculate GPP without any water stress. If the model is
88                                                              !! used in production mode and ok_hydrol_arch is true this
89                                                              !! flag should be true as well.
90!$OMP THREADPRIVATE(ok_gs_feedback)   
91  LOGICAL, SAVE       :: ok_mleb                              !! Flag that activates the multilayer energy budget (true/false)
92                                                              !! The model uses 10 (default) canopy layers to calculate
93                                                              !! the albedo, transmittance, absorbance and GPP. These canopy
94                                                              !! layers can be combined with 10 (default) layers below and
95                                                              !! 10 layers above the canopy to calculate the energy budget
96                                                              !! (ok_mleb=y). If set to no, this flag will make the model
97                                                              !! use 10 layers for the canopy albedo, transmittance,
98                                                              !! absorbance and GPP and just a single layer for the energy
99                                                              !! budget. Be aware that if you wish to run with hydraulic
100                                                              !! architechture ok_mleb needs to be se to true as well. Furthermore
101                                                              !! if you  wish to run with the original energy scheme (enerbil),
102                                                              !! set the layers for mleb to 1.
103!$OMP THREADPRIVATE(ok_mleb)
104  LOGICAL, SAVE       :: ok_impose_can_structure              !! This flag is for debugging only! It allows developers
105                                                              !! to use a prescribed canopy structure rather then the
106                                                              !! structure calculate by ORCHIDEE. The flag activates the
107                                                              !! sections of code which directly link the energy budget
108                                                              !! scheme to the the size and LAI profile of the canopy for the
109                                                              !! respective PFT and age class that is calculated in stomate,
110                                                              !! for the albedo. If set to TRUE and the multi-layer budget
111                                                              !! is activated the model takes LAI profile information and
112                                                              !! canopy level heights from the run.def. If set to FALSE, and
113                                                              !! the multi-layer energy budget is used the profile
114                                                              !! information and canopy levels heights comes from the
115                                                              !! PGap-based processes for calculation of stand profile
116                                                              !! information in stomate.
117!$OMP THREADPRIVATE(ok_impose_can_structure)
118  LOGICAL, SAVE       :: ok_mleb_history_file                 !! Flag that controls the writing of an output file with the
119                                                              !! multi-layer energy simulations (true/false). Note that this
120                                                              !! is a large file and writing it slows down the code.
121!$OMP THREADPRIVATE(ok_mleb_history_file)
122  LOGICAL, SAVE :: ok_read_fm_map = .FALSE.                   !! A logical flag determining if we read
123                                                              !! in the forest management strategy from a map.
124                                                              !! This should be .TRUE. for all applications
125                                                              !! except for debugging and pixel-level simulations.
126!$OMP THREADPRIVATE(ok_read_fm_map)
127  LOGICAL, SAVE :: ok_read_sp_clearcut_map = .FALSE.          !! A logical flag determining if we read
128                                                              !! in a map determining for each pixel and PFT,
129                                                              !! whether a clearcut during spinup will happen.
130!$OMP THREADPRIVATE(ok_read_sp_clearcut_map)
131  LOGICAL, SAVE :: ok_change_species = .FALSE.                !! A logical flag determining if we change
132                                                              !! species after a clearcut
133!$OMP THREADPRIVATE(ok_change_species)
134  LOGICAL, SAVE :: ok_read_species_change_map = .FALSE.       !! A logical flag determining if we read
135                                                              !! in a map which changes species after a clearcut
136                                                              !! To be used with ok_change_species = .TRUE. or
137                                                              !! set species_change_force (see below)
138!$OMP THREADPRIVATE(ok_read_species_change_map)
139  LOGICAL, SAVE :: ok_read_desired_fm_map = .FALSE.           !! A logical flag determining if we read
140                                                              !! in the desired forest management strategy from a map.
141                                                              !! To be used with ok_change_species = .TRUE. or set
142                                                              !! fm_change_force (see below)
143!$OMP THREADPRIVATE(ok_read_desired_fm_map)
144  LOGICAL, SAVE :: ok_litter_raking = .FALSE.                 !! If TRUE, this flag will simulate litter raking in
145                                                              !! in grid squares.  This has the effect of moving litter
146                                                              !! once a year from forest PFTs to agricultural PFTs, if they
147                                                              !! are present on this pixel.  If TRUE, you must also provide
148                                                              !! a map with the litter demand so we know how much litter
149                                                              !! to remove for each pixel. Litter raking is a historical
150                                                              !! land use so you reconstrauctions to use this option.
151!$OMP THREADPRIVATE(ok_litter_raking)
152 
153  LOGICAL       :: ok_dimensional_product_use = .TRUE.        !! Once the wood is harvested it ends up in wood product pools
154                                                              !! Two options were coded: (1) the product use and thus
155                                                              !! its on longevity depends on the dimensions of the harvest
156                                                              !! (2) the dimensions are ignored and the wood is used according
157                                                              !! to fixed ratios.
158 
159!$OMP THREADPRIVATE(ok_dimensional_product_use)
160
161  LOGICAL       :: ok_constant_mortality                      !! Use constant mortality or calculate mortality
162                                                              !! as a function of last yearsÂŽs NPP
163!$OMP THREADPRIVATE(ok_constant_mortality)
164
165  LOGICAL, SAVE :: ok_c13                                     !! Activate carbon isotope concetration of biomass
166!$OMP THREADPRIVATE(ok_c13)
167
168  LOGICAL, SAVE :: ok_windthrow = .FALSE.                     !! Activate the wind throw module. Trees will be killed
169                                                              !! if the wind speed exceeds the critical wind speed of
170                                                              !! of the forest (PFT).                             
171!$OMP THREADPRIVATE(ok_windthrow)
172
173  LOGICAL, SAVE :: ok_pest = .FALSE.                          !! Activate pest  module. Trees will be killed by bark beetle
174 !$OMP THREADPRIVATE(ok_pest)
175
176  LOGICAL, SAVE :: ok_bare_soil_new                           !! Choose between the two options to calculate the bare soil.
177                                                              !! False = classic view: gaps within a canopy should be treated
178                                                              !! as bare soil. True = ecological view: gaps within a canopy are
179                                                              !! part of the ecosystem and should be treated as such.
180                                                              !! The parameter is set in control.f90 as part of the ENERGY_CONTROL
181                                                              !! flag.
182!$OMP THREADPRIVATE(ok_bare_soil_new)
183
184  LOGICAL, SAVE :: ok_snow_albedo_clm3 = .TRUE.               !! Choose between two options to calculate the snow albedo. If
185                                                              !! set to .TRUE. the snow albedo is calculated for the diffuse
186                                                              !! and direct light separately and decays with age. If set to
187                                                              !! a slightly simpler calculations, the default in the trunk,
188                                                              !! is used.
189!$OMP THREADPRIVATE(ok_snow_albedo_clm3)
190
191  CHARACTER(LEN=30), SAVE :: maint_resp_control               !! Choose between two options to calculate the maint respiration. If
192                                                              !! set to 'nitrogen' the plant nitrogen pools and temperature will
193                                                              !! drive maint_resp. If set to 'c/n', maint_resp will be adjusted for
194                                                              !! the expected c/n ratio of the plant biomass. Also the temperature
195                                                              !! control itself is calculated according to Krinner et al 2005 instead
196                                                              !! of Sitch et al 2003.
197
198!$OMP THREADPRIVATE(maint_resp_control)
199
200  LOGICAL, SAVE :: ok_force_pheno = .TRUE.                    !! Temperature phenology is very predictable and happens every year but
201                                                              !! moisture-driven phenology is less stable because the conditions
202                                                              !! may not be satisfied during 12 months resulting in a year without
203                                                              !! a canopy. If the model has passed the average budbreak day by a
204                                                              !! prescribed PFT-specific offset (::force_pheno), budbreak will be forced
205                                                              !! (given the condition that buds are avaialble)
206!$OMP THREADPRIVATE(ok_force_pheno)
207
208  LOGICAL, SAVE :: nc_restart_compression !! activate netcdf restart compression
209!$OMP THREADPRIVATE(nc_restart_compression)
210  LOGICAL :: river_routing      !! activate river routing
211!$OMP THREADPRIVATE(river_routing)
212  LOGICAL, SAVE :: ok_nudge_mc  !! Activate nudging of soil moisture
213!$OMP THREADPRIVATE(ok_nudge_mc)
214  LOGICAL, SAVE :: ok_nudge_snow!! Activate nudging of snow variables
215!$OMP THREADPRIVATE(ok_nudge_snow)
216  LOGICAL, SAVE :: nudge_interpol_with_xios  !! Activate reading and interpolation with XIOS for nudging fields
217!$OMP THREADPRIVATE(nudge_interpol_with_xios)
218  LOGICAL :: do_floodplains     !! activate flood plains
219!$OMP THREADPRIVATE(do_floodplains)
220  LOGICAL :: do_irrigation      !! activate computation of irrigation flux
221!$OMP THREADPRIVATE(do_irrigation)
222  LOGICAL :: ok_sechiba         !! activate physic of the model
223!$OMP THREADPRIVATE(ok_sechiba)
224  LOGICAL :: ok_stomate         !! activate carbon cycle
225!$OMP THREADPRIVATE(ok_stomate)
226  LOGICAL :: ok_ncycle          !! activate nitrogen cycle
227!$OMP THREADPRIVATE(ok_ncycle)
228  LOGICAL :: impose_cn          !! impose the CN ratio of leaves
229!$OMP THREADPRIVATE(impose_cn)
230  LOGICAL :: reset_impose_cn    !! reset the CN ratio of leaves
231!$OMP THREADPRIVATE(reset_impose_cn)
232  LOGICAL :: read_cn          !! read the CN ratio of leaves
233!$OMP THREADPRIVATE(read_cn)
234  LOGICAL :: ok_dgvm            !! activate dynamic vegetation
235!$OMP THREADPRIVATE(ok_dgvm)
236  LOGICAL :: do_wood_harvest    !! activate wood harvest
237!$OMP THREADPRIVATE(do_wood_harvest)
238  LOGICAL :: ok_pheno           !! activate the calculation of lai using stomate rather than a prescription
239!$OMP THREADPRIVATE(ok_pheno)
240  LOGICAL :: ok_bvoc            !! activate biogenic volatile organic coumpounds
241!$OMP THREADPRIVATE(ok_bvoc)
242  LOGICAL :: ok_leafage         !! activate leafage
243!$OMP THREADPRIVATE(ok_leafage)
244  LOGICAL :: ok_radcanopy       !! use canopy radiative transfer model
245!$OMP THREADPRIVATE(ok_radcanopy)
246  LOGICAL :: ok_multilayer      !! use canopy radiative transfer model with multi-layers
247!$OMP THREADPRIVATE(ok_multilayer)
248  LOGICAL :: ok_pulse_NOx       !! calculate NOx emissions with pulse
249!$OMP THREADPRIVATE(ok_pulse_NOx)
250  LOGICAL :: ok_bbgfertil_NOx   !! calculate NOx emissions with bbg fertilizing effect
251!$OMP THREADPRIVATE(ok_bbgfertil_NOx)
252  LOGICAL :: ok_cropsfertil_NOx !! calculate NOx emissions with fertilizers use
253!$OMP THREADPRIVATE(ok_cropsfertil_NOx)
254
255  LOGICAL :: ok_co2bvoc_poss    !! CO2 inhibition on isoprene activated following Possell et al. (2005) model
256!$OMP THREADPRIVATE(ok_co2bvoc_poss)
257  LOGICAL :: ok_co2bvoc_wilk    !! CO2 inhibition on isoprene activated following Wilkinson et al. (2006) model
258!$OMP THREADPRIVATE(ok_co2bvoc_wilk)
259  LOGICAL :: ok_wlsk
260!$OMP THREADPRIVATE(ok_wlsk)
261  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.  !! ORCHIDEE detects if it is coupled with a GCM or
262                                            !! just use with one driver in OFF-LINE. (true/false)
263!$OMP THREADPRIVATE(OFF_LINE_MODE) 
264  LOGICAL, SAVE :: impose_param = .TRUE.    !! Flag impos_param : read all the parameters in the run.def file
265!$OMP THREADPRIVATE(impose_param)
266  CHARACTER(LEN=80), SAVE     :: restname_in       = 'NONE'                 !! Input Restart files name for Sechiba component 
267!$OMP THREADPRIVATE(restname_in)
268  CHARACTER(LEN=80), SAVE :: restname_out = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
269!$OMP THREADPRIVATE(restname_out)
270  CHARACTER(LEN=80), SAVE :: stom_restname_in = 'NONE'        !! Input Restart files name for Stomate component
271!$OMP THREADPRIVATE(stom_restname_in)
272  CHARACTER(LEN=80), SAVE :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
273!$OMP THREADPRIVATE(stom_restname_out)
274  INTEGER, SAVE :: printlev=2       !! Standard level for text output [0, 1, 2, 3]
275!$OMP THREADPRIVATE(printlev)
276
277  !
278  ! HACKS
279  !
280  LOGICAL, SAVE :: hack_enerbil_hydrol = .FALSE.!! For debugging only! Flag to skip a particular block of code in enerbil.f90 which results in
281                                                !! incorrect results for large scale simulations.
282!$OMP THREADPRIVATE(hack_enerbil_hydrol)
283  LOGICAL, SAVE :: hack_pgap = .FALSE.          !! For debugging only! If =.TRUE. the model uses Lambert Beer to calculate veget instead of Pgap.
284!$OMP THREADPRIVATE(hack_pgap)
285  REAL(r_std), SAVE :: hack_vessel_loss = -9999 !! Impose a constant vessel_loss in hydraulic_rachitecture when ok_vessel_mortality is TRUE. When set outside the range from 0 to 1 it will not be used.
286!$OMP THREADPRIVATE(hack_vessel_loss)
287  LOGICAL, SAVE :: hack_e_frac = .FALSE.        !! By pass the use of root length in the calculation of psi_soilroot.
288!$OMP THREADPRIVATE(hack_e_frac)
289  LOGICAL, SAVE :: hack_veget_max_new = .FALSE. !! Prescribe veget_max from run.def rather than a PFT map. Useful feature to debug simplified LCCs.
290                                                !! See slowproc.f90 for details on this feature.
291
292  !
293  ! PARAMETERS
294  !
295  REAL(r_std), SAVE :: min_n = 0.0001          !! Minimum allowable n_mineralisation when truncating som_input_total(:,initrogen) in stomate_litter.
296!$OMP THREADPRIVATE(min_n)
297  REAL(r_std), SAVE :: max_cn = 250            !! Maximum allowable ratio of som_input_total(:,icarbon) to som_input_total(:,initrogen).
298!$OMP THREADPRIVATE(max_cn)
299  REAL(r_std), SAVE :: snc = 0.004             !! Structural nitrogen  [gN g-1C] based on C:N of dead wood (White et al., 2000)
300                                               !! assuming carbon dry matter ratio of 0.5 
301!$OMP THREADPRIVATE(snc)
302  REAL(r_std), SAVE :: slope_ra = 40           !! Reduction factor to make resp_maint less temperature sensitive
303!$OMP THREADPRIVATE(slope_ra)
304
305  !
306  ! TIME
307  !
308  INTEGER(i_std), PARAMETER  :: spring_days_max = 40  !! Maximum number of days during which we watch for possible spring frost damage
309
310  !
311  ! SPECIAL VALUES
312  !
313  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
314  !-
315  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
316!$OMP THREADPRIVATE(val_exp)
317  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
318 
319  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
320  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
321 
322  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
323  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
324
325
326  REAL(r_std), SAVE :: alpha_nudge_mc                    !! Nudging constant for soil moisture
327!$OMP THREADPRIVATE(alpha_nudge_mc)
328  REAL(r_std), SAVE :: alpha_nudge_snow                  !! Nudging constant for snow variables
329!$OMP THREADPRIVATE(alpha_nudge_snow)
330
331  !
332  !  DIMENSIONING AND INDICES PARAMETERS 
333  !
334  INTEGER(i_std), PARAMETER :: istart = 1        !! Index to store values at the start
335  INTEGER(i_std), PARAMETER :: iend = 2          !! Index to store values at the end
336  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
337  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
338  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
339  INTEGER(i_std), PARAMETER :: n_spectralbands=2 !! number of spectral bands
340  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
341  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
342  !-
343  !! Soil
344  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
345  !-
346  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
347  !-
348  !! litter fractions: indices (unitless)
349  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
350  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
351  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
352  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
353  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
354  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
355  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
356  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
357  INTEGER(i_std), PARAMETER :: ilabile = 9       !! Index for reserve compartment (unitless)
358  INTEGER(i_std), PARAMETER :: nparts = 9        !! Number of biomass compartments (unitless)
359  !-
360  !! indices for assimilation parameters
361  INTEGER(i_std), PARAMETER :: ivcmax = 1        !! Index for vcmax (assimilation parameters) (unitless)
362  INTEGER(i_std), PARAMETER :: inue = 2          !! Index for nue (assimilation parameters) (unitless)
363  INTEGER(i_std), PARAMETER :: ileafN = 3        !! Index for leaf N (assimilation parameters) (unitless)
364  INTEGER(i_std), PARAMETER :: npco2 = 3         !! Number of assimilation parameters (unitless)
365
366  !-
367  !! trees and litter: indices for the parts of heart-
368  !! and sapwood above and below the ground
369  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
370  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
371  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
372  !-
373  !! litter: indices for metabolic and structural part
374  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
375  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
376  INTEGER(i_std), PARAMETER :: iwoody = 3       !! Index for woody litter (unitless)
377  INTEGER(i_std), PARAMETER :: nlitt = 3        !! Number of levels for litter compartments (unitless)
378  !-
379  !! carbon pools: indices
380  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
381  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
382  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
383  INTEGER(i_std), PARAMETER :: isurface = 4     !! Index for passive carbon pool (unitless)
384  INTEGER(i_std), PARAMETER :: ncarb = 4        !! Number of soil carbon pools (unitless)
385  !-
386  !! For isotopes and nitrogen
387  INTEGER(i_std), PARAMETER :: nelements = 2    !! Number of isotopes considered
388  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
389  INTEGER(i_std), PARAMETER :: initrogen = 2    !! Index for nitrogen
390  !! N-cycle : indices
391  INTEGER(i_std), PARAMETER :: iammonium = 1    !! Index for Ammonium
392  INTEGER(i_std), PARAMETER :: initrate  = 2    !! Index for Nitrate
393  INTEGER(i_std), PARAMETER :: inox      = 3    !! Index for NOX
394  INTEGER(i_std), PARAMETER :: initrous  = 4    !! Index for N2O
395  INTEGER(i_std), PARAMETER :: idinitro  = 5    !! Index for N2
396  INTEGER(i_std), PARAMETER :: nnspec    = 5    !! Number of N-species considered
397  INTEGER(i_std), PARAMETER :: nionspec  = 2    !! Number of ions form considered (ammonium, nitrate)
398  !! For N-deposition
399  INTEGER(i_std), PARAMETER :: iatm_ammo = 1    !! Index for N input from Ammonium N atmospheric deposition
400  INTEGER(i_std), PARAMETER :: iatm_nitr = 2    !! Index for N input from Nitrate N atmospheric deposition
401  INTEGER(i_std), PARAMETER :: ibnf      = 3    !! Index for N input from BNF
402  INTEGER(i_std), PARAMETER :: ifert     = 4    !! Index for N input from Fertilisation
403  INTEGER(i_std), PARAMETER :: imanure   = 5    !! Index for N input from Manure
404  INTEGER(i_std), PARAMETER :: ninput    = 5    !! Number of N-input considered 
405 
406
407  INTEGER(i_std), PARAMETER :: i_nh4_to_no3 = 1 !! Index for NO3 production
408  INTEGER(i_std), PARAMETER :: i_nh4_to_no  = 2 !! Index for NO production
409  INTEGER(i_std), PARAMETER :: i_nh4_to_n2o = 3 !! Index for N2O production
410  INTEGER(i_std), PARAMETER :: n_nh4_to_x = 3   !! Number of NH4 pathways
411
412  INTEGER(i_std), PARAMETER :: i_no3_to_nox = 1  !! Index for NO3 consumption
413  INTEGER(i_std), PARAMETER :: i_nox_to_n2o  = 2 !! Index for NO/Nox consumption
414  INTEGER(i_std), PARAMETER :: i_n2o_to_n2 = 3   !! Index for N2O consumption
415  INTEGER(i_std), PARAMETER :: n_n_to_x = 3      !! Number of N pathways
416
417  INTEGER(i_std), PARAMETER :: nmonth = 12       !! Months in a year; used for input .nc files with monthly arrays
418 
419  !! Updates for the mass balance closure in stomate_lpj
420  INTEGER(i_std), PARAMETER :: ibeg      = 1    !! At the begining of the routine
421  INTEGER(i_std), PARAMETER :: ipre      = 2    !! After precribe
422  INTEGER(i_std), PARAMETER :: iphe      = 3    !! After phenology
423  INTEGER(i_std), PARAMETER :: igro      = 4    !! After growth functional allocation
424  INTEGER(i_std), PARAMETER :: iage      = 5    !! After Age class distribution
425  INTEGER(i_std), PARAMETER :: iluc      = 6    !! After land cover change
426  INTEGER(i_std), PARAMETER :: imor      = 7    !! After mortality_clean
427  INTEGER(i_std), PARAMETER :: irec      = 8    !! After recruitment
428  INTEGER(i_std), PARAMETER :: ispc      = 9    !! After Species Change
429  INTEGER(i_std), PARAMETER :: nupdates  = 9    !! Number of step in stomate_lpj where veget_max and atm_to_bm is update
430
431
432  ! These next sets of parameters are now used for both circ_class_kill and
433  ! for the harvest_pool.  One source of confusion is what to do with trees that
434  ! die from self-thinning or forest dieoffs.  These happen in all forests, regardless
435  ! of management strategy.  I decided to put death of this kind into ifm_none, since
436  ! it is the only type of mortality found in an unmanaged forest.  If the mortality
437  ! does not kill the whole forest (e.g. self thinning), it goes into icut_thin.  If it
438  ! does (forest dieoff), it goes into icut_clear.  The biomass is killed in lpj_gap.
439
440  !! Indices used for forest management strategies
441  INTEGER(i_std), PARAMETER :: nfm_types = 6             !! The total number of forest management
442                                                         !! strategies we can use
443  INTEGER(i_std), PARAMETER :: ifm_none = 1              !! No human intervention in the forests.
444  INTEGER(i_std), PARAMETER :: ifm_thin = 2              !! Regular thinning and harvesting of
445                                                         !! wood based on RDI.
446  INTEGER(i_std), PARAMETER :: ifm_cop = 3               !! Coppicing for fuelwood.
447  INTEGER(i_std), PARAMETER :: ifm_src = 4               !! Short rotation coppices for biomass
448                                                         !! production.
449  INTEGER(i_std), PARAMETER :: ifm_crop = 5              !! Crop harvest
450  INTEGER(i_std), PARAMETER :: ifm_grass = 6             !! Grazing or cutting
451
452  !! flag to trigger clearcut during spinup
453  INTEGER(i_std), PARAMETER :: flag_spinup_clearcut = 1  !!
454
455  !! Indices used for harvest pools
456  INTEGER(i_std), PARAMETER :: ncut_times = 12           !! The total number of times when trees
457                                                         !! are cut and wood harvested.
458  INTEGER(i_std), PARAMETER :: icut_clear = 1            !! A clearcut where all biomass is removed.
459  INTEGER(i_std), PARAMETER :: icut_thin = 2             !! Thinning of biomass to reduce the
460                                                         !! number of trees.
461  INTEGER(i_std), PARAMETER :: icut_lcc_wood = 3         !! Wood harvest following land cover
462                                                         !! change (LCC)
463  INTEGER(i_std), PARAMETER :: icut_lcc_res = 4          !! Site clearing, removal of the stumps
464                                                         !! and branches following LCC
465  INTEGER(i_std), PARAMETER :: icut_crop = 5             !! Crop harvest
466  INTEGER(i_std), PARAMETER :: icut_grass = 6            !! Grazing or cutting
467  INTEGER(i_std), PARAMETER :: icut_cop1 = 7             !! The first coppice cut
468  INTEGER(i_std), PARAMETER :: icut_cop2 = 8             !! The second (and subsequent) coppice cut
469  INTEGER(i_std), PARAMETER :: icut_cop3 = 9             !! The last coppice cut (only for SRC)
470  INTEGER(i_std), PARAMETER :: icut_storm_break = 10     !! Stem breakage due to storm
471  INTEGER(i_std), PARAMETER :: icut_storm_uproot = 11    !! Tee uprooting due to storm
472  INTEGER(i_std), PARAMETER :: icut_beetle = 12          !! Tree killed due to bark beetle attacks
473
474  !! Indices used to define the product pools
475  !! Numbers based on Eggers 2008 - EFI report
476  INTEGER(i_std), PARAMETER :: nshort = 1                !! Length in years of the short-lived product pool (GE 1)
477  INTEGER(i_std), PARAMETER :: nmedium =17               !! Length in years of the medium-lived product pool (GT 4)
478  INTEGER(i_std), PARAMETER :: nlong = 50                !! Length in years of the long-lived product pool (GT 4)
479
480  !! Indices used for land use output variables
481  INTEGER(i_std), PARAMETER :: nlanduse = 2              !! Total number of different land uses
482  INTEGER(i_std), PARAMETER :: iharvest = 1              !! Biomass removals due to all sorts of harvest
483  INTEGER(i_std), PARAMETER :: ilcc = 2                  !! Biomass removals due to all sorts of land cover changes
484
485  !! Indices used to check the mass balance closure
486  INTEGER(i_std), PARAMETER :: nmbcomp = 5               !! The total number of components in
487                                                         !! our mass balance check
488  INTEGER(i_std), PARAMETER :: iatm2land = 1             !! atmosphere to land fluxes such as GPP
489                                                         !! and co2_2_bm
490  INTEGER(i_std), PARAMETER :: iland2atm = 2             !! land to atmosphere fluxes such as Rh,
491                                                         !! Ra and product decomposition
492  INTEGER(i_std), PARAMETER :: ilat2out = 3              !! outgoing lateral flux i.e. DOC leaching
493                                                         !! for the litter routine
494  INTEGER(i_std), PARAMETER :: ilat2in = 4               !! incoming lateral flux i.e. N deposition
495                                                         !! for the land
496  INTEGER(i_std), PARAMETER :: ipoolchange = 5           !! change in pool size i.e. change in biomass
497
498  !! Indices used for warning tracking
499  INTEGER(i_std), PARAMETER :: nwarns = 1                !! The total number of warnings we track
500  INTEGER(i_std), PARAMETER :: iwphoto = 1               !! A warning about division by zero in photosynthesis
501
502  !! Indices used for wind damage 
503  INTEGER(i_std), PARAMETER :: ibreakage = 1             !! The index for stem breakage dur to wind damage
504  INTEGER(i_std), PARAMETER :: ioverturning = 2          !! The index for the tree overtuning due to wind damage
505
506  !! Indices for orphan fluxes
507  INTEGER(i_std), PARAMETER :: norphans = 8              !! Total number of orphan fluxes (unitless)
508  INTEGER(i_std), PARAMETER :: ivegold = 1               !! Index for veget_max before LCC
509  INTEGER(i_std), PARAMETER :: ivegnew = 2               !! Index for veget_max before LCC (includes veget_max of orphan fluxes)
510  INTEGER(i_std), PARAMETER :: igpp = 3                  !! Index for gpp_daily
511  INTEGER(i_std), PARAMETER :: ico2bm = 4                !! Index for co2_to_bm
512  INTEGER(i_std), PARAMETER :: irmain = 5                !! Index for maintenance respiration
513  INTEGER(i_std), PARAMETER :: irgrow = 6                !! Index for growth respiration
514  INTEGER(i_std), PARAMETER :: inpp = 7                  !! Index for npp_daily
515  INTEGER(i_std), PARAMETER :: irhet = 8                 !! Index for total heterotrophic respiration
516  !
517
518  !! Indices for phenology
519  ! The variable ::plant_status replaces several variables (senescence,
520  ! begin_leaves and allow_phenoinit) that describe the phenological status of the plant
521  ! by storing these different aspects of phenology in a single variable, inconsistencies
522  ! become impossible or at least easier to check.
523  ! When the model starts from scratch the status is set to iprescribe this allows us
524  ! to grow leaves from the first year onwards. The plant should then go through the
525  ! different growth phases: ibudsavail, ibudbreak, icanopy, isenescent, idormant and
526  ! finally idead. Following idormant the status should return ibudsavail to initiate
527  ! another cycle in the subsequent growing season. Following idead new vegetation
528  ! should be prescribed.
529  INTEGER(i_std), PARAMETER :: inone = 0                 !! No plants thus no status
530  INTEGER(i_std), PARAMETER :: iprescribe = 1            !! Prescribe a PFT
531  INTEGER(i_std), PARAMETER :: ibudsavail = 2            !! Buds are present
532  INTEGER(i_std), PARAMETER :: ibudbreak = 3             !! Day that the buds break and leaf
533                                                         !! on-set begins
534  INTEGER(i_std), PARAMETER :: icanopy = 4               !! Canopy is present
535  INTEGER(i_std), PARAMETER :: ipresenescence = 5        !! Wood growth cessation
536  INTEGER(i_std), PARAMETER :: isenescent = 6            !! The plant is senescent
537  INTEGER(i_std), PARAMETER :: idormant = 7              !! The plant is dormant
538  INTEGER(i_std), PARAMETER :: idead = 8                 !! The plant was killed
539
540  !
541  !! Indices used for analytical spin-up
542  INTEGER(i_std), PARAMETER :: nbpools = 10              !! Total number of carbon pools (unitless)
543  INTEGER(i_std), PARAMETER :: istructural_above = 1    !! Index for structural litter above (unitless)
544  INTEGER(i_std), PARAMETER :: istructural_below = 2    !! Index for structural litter below (unitless)
545  INTEGER(i_std), PARAMETER :: imetabolic_above = 3     !! Index for metabolic litter above (unitless)
546  INTEGER(i_std), PARAMETER :: imetabolic_below = 4     !! Index for metabolic litter below (unitless)
547  INTEGER(i_std), PARAMETER :: iwoody_above = 5         !! Index for woody litter above (unitless)
548  INTEGER(i_std), PARAMETER :: iwoody_below = 6         !! Index for woody litter below (unitless)
549  INTEGER(i_std), PARAMETER :: iactive_pool = 7         !! Index for active carbon pool (unitless)
550  INTEGER(i_std), PARAMETER :: islow_pool   = 8         !! Index for slow carbon pool (unitless)
551  INTEGER(i_std), PARAMETER :: ipassive_pool = 9        !! Index for passive carbon pool (unitless)
552  INTEGER(i_std), PARAMETER :: isurface_pool = 10       !! Index for surface carbon pool (unitless)
553
554  !
555  !! Indices for the burried carbon and nitrogen following LUC
556  INTEGER(i_std), PARAMETER :: nbury=6                  !! Total number of buried pools
557  INTEGER(i_std), PARAMETER :: ilitter=1                 !! Index for litter
558  INTEGER(i_std), PARAMETER :: ifreshlitter=2           !! Index for fresh litter
559  INTEGER(i_std), PARAMETER :: ifreshsom=3              !! Index for fresh som
560  INTEGER(i_std), PARAMETER :: ibact=4                  !! Index for bacteria
561  INTEGER(i_std), PARAMETER :: isom=5                   !! Index for som
562  INTEGER(i_std), PARAMETER :: iminnitrogen=6           !! Index for mineral soil nitrogen
563
564  !
565  !! Indicies used for output variables on Landuse tiles defined according to LUMIP project
566  !! Note that ORCHIDEE do not represent pasture and urban land. Therefor the variables will have
567  !! val_exp as missing value for these tiles.
568  INTEGER(i_std), PARAMETER :: nlut=4                   !! Total number of landuse tiles according to LUMIP
569  INTEGER(i_std), PARAMETER :: id_psl=1                 !! Index for primary and secondary land
570  INTEGER(i_std), PARAMETER :: id_crp=2                 !! Index for crop land
571  INTEGER(i_std), PARAMETER :: id_pst=3                 !! Index for pasture land
572  INTEGER(i_std), PARAMETER :: id_urb=4                 !! Index for urban land
573
574  !! Indices used for canopy structure (Pgap & eff lai)
575  INTEGER(i_std),PARAMETER   :: ndist_types=6           !! the number of distributions we need in the LAI effective routines
576  INTEGER(i_std),PARAMETER   :: iheight=1               !! the tree height distribution
577  INTEGER(i_std),PARAMETER   :: idiameter=2             !! the trunk diameter distribution
578  INTEGER(i_std),PARAMETER   :: icnvol=3                !! the crown volume distribution
579  INTEGER(i_std),PARAMETER   :: icnarea=4               !! the crown area distribution
580  INTEGER(i_std),PARAMETER   :: icndiaver=5             !! the verticle crown diameter distribution
581  INTEGER(i_std),PARAMETER   :: icndiahor=6             !! the horizontal crown diameter distribution
582
583  !! indices used in AR5 output
584  INTEGER(i_std),PARAMETER   :: nlctypes=3              !! Number of land cover types
585  INTEGER(i_std),PARAMETER   :: iforest=1               !! forest
586  INTEGER(i_std),PARAMETER   :: igrass=2                !! grass
587  INTEGER(i_std),PARAMETER   :: icrop=3                 !! crops
588
589  !! Indices used in the root profile
590  INTEGER(i_std),PARAMETER   :: nroot_prof=2            !! Number of different root profiles
591  INTEGER(i_std),PARAMETER   :: istruc=1                !! Structural root profile
592  INTEGER(i_std),PARAMETER   :: ifunc=2                 !! Functional root profile for water uptake
593
594  !! Indices used to defile the vertical root rofile
595  INTEGER(i_std),PARAMETER   :: ndepths=2               !! Number of components in the definition of a vertical soil profile
596  INTEGER(i_std),PARAMETER   :: inode=1                 !! Node
597  INTEGER(i_std),PARAMETER   :: iinterface=2            !! Interface
598
599
600  !
601  ! NUMERICAL AND PHYSICS CONSTANTS
602  !
603  !-
604  ! 1. Mathematical and numerical constants
605  !-
606  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
607  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
608  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
609  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
610  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
611  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
612  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
613  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
614  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
615  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
616  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
617  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
618  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
619
620  !-
621  ! 2 . Physics
622  !-
623  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
624  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
625  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
626  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
627  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
628  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
629  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
630  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
631  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
632  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
633  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
634  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
635                                                            !! of dry air (unitless)
636  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
637  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
638  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
639       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
640  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
641  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
642                                                            !! vapor minus 1(unitless) 
643  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
644 
645  REAL(r_std), PARAMETER :: rho_h2o= 0.9991_r_std           !! Density of water at 15°C (g cm-3)                                                          !! minus 1 (unitless)
646  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
647  REAL(r_std), PARAMETER :: ct_karman = 0.41_r_std          !! Van Karmann Constant (unitless)
648  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
649  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
650  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
651  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
652
653  REAL(r_std), PARAMETER :: mm_m = 1000._r_std              !! conversion from milimeters to meters
654
655  INTEGER(i_std), SAVE :: testpft = 6
656!$OMP THREADPRIVATE(testpft)
657
658  !-
659  ! 3. Climatic constants
660  !-
661  !! Constantes of the Louis scheme
662  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
663                                                  !! reference to Louis (1979)
664!$OMP THREADPRIVATE(cb)
665  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
666                                                  !! reference to Louis (1979)
667!$OMP THREADPRIVATE(cc)
668  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
669                                                  !! reference to Louis (1979)
670!$OMP THREADPRIVATE(cd)
671  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
672!$OMP THREADPRIVATE(rayt_cste)
673  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
674!$OMP THREADPRIVATE(defc_plus)
675  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
676!$OMP THREADPRIVATE(defc_mult)
677
678  !-
679  ! 4. Soil thermodynamics constants
680  !-
681  ! Look at constantes_soil.f90
682
683
684  !
685  ! OPTIONAL PARTS OF THE MODEL
686  !
687  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
688                                                  !! we provide here a way to catch that in the calling procedure.
689                                                  !! (from Jan Polcher)(true/false)
690  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
691                                                  !! Value is read from run.def in intersurf_history
692!$OMP THREADPRIVATE(almaoutput)
693
694  !
695  ! DIVERSE
696  !
697  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
698                                                           ! Compatibility with Nicolas Viovy driver.
699!$OMP THREADPRIVATE(stomate_forcing_name)
700  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
701                                                           ! Compatibility with Nicolas Viovy driver.
702!$OMP THREADPRIVATE(stomate_Cforcing_name)
703  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_discretization_name='NONE' !! Name of soil carbon discretization forcing file (unitless)
704!$OMP THREADPRIVATE(stomate_Cforcing_discretization_name)
705  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
706!$OMP THREADPRIVATE(forcing_id)
707  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
708                                                     !! This variable will be set to false for teststomate.
709!$OMP THREADPRIVATE(allow_forcing_write)
710
711
712                         !------------------------!
713                         !  SECHIBA PARAMETERS    !
714                         !------------------------!
715 
716
717  !
718  ! GLOBAL PARAMETERS   
719  !
720  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
721!$OMP THREADPRIVATE(min_wind)
722  REAL(r_std), PARAMETER :: min_qc = 1.e-4 !! The minimum value for qc (qc=drag*wind) used in coupled(enerbil) and forced mode (enerbil and diffuco)
723  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occurs (kg.m^{-2})
724!$OMP THREADPRIVATE(snowcri)
725
726
727  !
728  ! FLAGS ACTIVATING SUB-MODELS
729  !
730  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
731!$OMP THREADPRIVATE(treat_expansion)
732  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
733!$OMP THREADPRIVATE(ok_herbivores)
734  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
735!$OMP THREADPRIVATE(harvest_agri)
736  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
737!$OMP THREADPRIVATE(lpj_gap_const_mort)
738  LOGICAL, SAVE :: disable_fire = .TRUE.       !! flag that disable fire (true/false)
739!$OMP THREADPRIVATE(disable_fire)
740  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
741!$OMP THREADPRIVATE(spinup_analytic)
742  LOGICAL, SAVE :: ok_soil_carbon_discretization !! Flag to activate soil carbon discretization (vertical carbon and soil carbon thermal insulation)
743!$OMP THREADPRIVATE(ok_soil_carbon_discretization)
744  LOGICAL, SAVE :: ok_soil_carbon_discretization_write !! Flag to activate soil carbon discretization output file
745!$OMP THREADPRIVATE(ok_soil_carbon_discretization_write)
746  LOGICAL, SAVE :: ok_vessel_mortality         !! Flag to activate death and recovery of vegetation following hydraulic failure.
747!$OMP THREADPRIVATE(ok_vessel_mortality)
748
749  !
750  ! CONFIGURATION VEGETATION
751  !
752  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
753!$OMP THREADPRIVATE(agriculture)
754  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
755!$OMP THREADPRIVATE(impveg)
756  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
757!$OMP THREADPRIVATE(impsoilt)
758  LOGICAL, SAVE :: impslope = .FALSE.      !! Impose reinf_slope ? (true/false)
759!$OMP THREADPRIVATE(impslope)
760  LOGICAL, SAVE :: impose_ninput_dep = .FALSE. !! Impose N input values from the atmosphere ? (true/false)
761!$OMP THREADPRIVATE(impose_ninput_dep)
762  LOGICAL, SAVE :: impose_ninput_fert = .FALSE. !! Impose N input values from fertilizer ? (true/false)       
763!$OMP THREADPRIVATE(impose_ninput_fert)   
764 LOGICAL, SAVE :: impose_ninput_manure = .FALSE. !! Impose N input values from manure? (true/false)       
765!$OMP THREADPRIVATE(impose_ninput_manure)                     
766  LOGICAL, SAVE :: impose_ninput_bnf = .FALSE. !! Impose N input values from biological nitrogen fixation (BNF) ? (true/false)       
767!$OMP THREADPRIVATE(impose_ninput_bnf)
768
769  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
770!$OMP THREADPRIVATE(do_now_stomate_lcchange)
771  LOGICAL, SAVE :: do_now_stomate_woodharvest = .FALSE.  !! Time to call woodharvest in stomate_lpj
772!$OMP THREADPRIVATE(do_now_stomate_woodharvest)
773  LOGICAL, SAVE :: do_now_stomate_product_use = .FALSE.  !! Time to call wood product use and decomposition
774!$OMP THREADPRIVATE(do_now_stomate_product_use)
775  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
776!$OMP THREADPRIVATE(done_stomate_lcchange)
777  LOGICAL, SAVE :: do_now_recruit = .FALSE.  !! Time to call prescribe to calculate recruits in stomate_lpj
778!$OMP THREADPRIVATE(do_now_recruit)
779  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
780!$OMP THREADPRIVATE(read_lai)
781  LOGICAL, SAVE :: vegetmap_reset = .FALSE.!! Reset the vegetation map and reset carbon related variables
782!$OMP THREADPRIVATE(vegetmap_reset)
783  INTEGER(i_std) , SAVE :: veget_update    !! Update frequency in years for landuse (nb of years)
784!$OMP THREADPRIVATE(veget_update)
785  LOGICAL, SAVE :: ninput_reinit = .TRUE.  !! To change N INPUT file in a run. (true/false)
786!$OMP THREADPRIVATE(ninput_reinit)
787
788
789  !
790  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
791  !
792  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
793!$OMP THREADPRIVATE(max_snow_age)
794  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)
795!$OMP THREADPRIVATE(snow_trans)
796  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
797!$OMP THREADPRIVATE(sneige)
798  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
799!$OMP THREADPRIVATE(maxmass_snow)
800
801  !! Heat capacity
802  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
803  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
804  REAL(r_std), PARAMETER :: rho_soil = 2700.            !! Density of soil particles (kg/m3), value from Peters-Lidard et al. 1998
805
806  !! Thermal conductivities
807  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
808  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
809  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
810
811  !! Time constant of long-term soil humidity (s)
812  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
813
814  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme   
815  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
816  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
817  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
818  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
819  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
820  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
821  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
822
823  !! The maximum snow density and water holding characterisicts
824  REAL(r_std), SAVE         :: xrhosmax = 750.  ! (kg m-3)
825!$OMP THREADPRIVATE(xrhosmax)
826  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  ! (-)
827!$OMP THREADPRIVATE(xwsnowholdmax1)
828  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  ! (-)
829!$OMP THREADPRIVATE(xwsnowholdmax2)
830  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 ! (kg/m3)
831!$OMP THREADPRIVATE(xsnowrhohold)
832  REAL(r_std), SAVE         :: xrhosmin = 50. 
833!$OMP THREADPRIVATE(xrhosmin)
834  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
835  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
836
837  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
838  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
839
840  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
841  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
842 
843  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
844  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
845  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
846  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
847
848  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
849 
850  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
851  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
852  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
853
854  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
855 
856  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
857  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
858  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
859!$OMP THREADPRIVATE(ZSNOWTHRMCOND1)
860  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
861!$OMP THREADPRIVATE(ZSNOWTHRMCOND2)
862 
863  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
864  ! (sig only for new snow OR high altitudes)
865  ! from Sun et al. (1999): based on data from Jordan (1991)
866  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
867  !
868  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_AVAP  = -0.06023 ! (W/m/K)
869!$OMP THREADPRIVATE(ZSNOWTHRMCOND_AVAP)
870  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_BVAP  = -2.5425  ! (W/m)
871!$OMP THREADPRIVATE(ZSNOWTHRMCOND_BVAP)
872  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_CVAP  = -289.99  ! (K)
873!$OMP THREADPRIVATE(ZSNOWTHRMCOND_CVAP)
874  REAL(r_std),SAVE :: xansmax = 0.85      !! Maxmimum snow albedo
875!$OMP THREADPRIVATE(xansmax)
876  REAL(r_std),SAVE :: xansmin = 0.50      !! Miniumum snow albedo
877!$OMP THREADPRIVATE(xansmin)
878  REAL(r_std),SAVE :: xans_todry = 0.008  !! Albedo decay rate for dry snow
879!$OMP THREADPRIVATE(xans_todry)
880  REAL(r_std),SAVE :: xans_t = 0.240      !! Albedo decay rate for wet snow
881!$OMP THREADPRIVATE(xans_t)
882
883  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
884  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
885  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
886
887  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
888  ! (sig only for new snow OR high altitudes)
889  ! from Sun et al. (1999): based on data from Jordan (1991)
890  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
891  !
892  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
893!$OMP THREADPRIVATE(ZSNOWCMPCT_RHOD)
894  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s)
895!$OMP THREADPRIVATE(ZSNOWCMPCT_ACM)
896  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
897!$OMP THREADPRIVATE(ZSNOWCMPCT_BCM)
898  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
899!$OMP THREADPRIVATE(ZSNOWCMPCT_CCM)
900  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
901!$OMP THREADPRIVATE(ZSNOWCMPCT_V0)
902  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
903!$OMP THREADPRIVATE(ZSNOWCMPCT_VT)
904  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
905!$OMP THREADPRIVATE(ZSNOWCMPCT_VR)
906
907    !
908  ! PARAMETERS USED FOR CANOPY LAYERS (Albedo, photosynthesis, energy budget)
909  !
910
911  INTEGER(i_std), PARAMETER   :: nlevels = 1                  !! Originally the number of levels in the canopy used in 
912                                                              !! calculation of the energy budget. After the
913                                                              !! mleb calculations have been implemented in enerbil,
914                                                              !! the jnlvls levels are determining the levels used
915                                                              !! within the multi-layer energy budget calculations. However,
916                                                              !! nlevels are still used in calculate_z_level_photo. Cannot
917                                                              !! be deleted before any decision regarding the vertical
918                                                              !! layering has been made.
919  INTEGER(i_std), SAVE        :: nlai = 10                    !! Number of levels in the canopy used in the photosynthesis
920                                                              !! routine per level dictacted by nlevels. For example, if
921                                                              !! if nlevels = 2 and nlai = 3, the photosynthesis
922                                                              !! will be calculated for nlevels_tot=2*3=6 total levels.
923!$OMP THREADPRIVATE(nlai)
924  INTEGER(i_std), SAVE        :: nlevels_tot                  !! Total number of levels, nlevels*nlai. Currently,
925                                                              !! nlevels=1 is used, thus nlevels_tot=nlai.
926                                                              !! Note that when using the multi-layer budget nlai
927                                                              !! needs to be nlai=jnlvls_canopy+1
928
929!$OMP THREADPRIVATE(nlevels_tot)
930  INTEGER(i_std), SAVE        :: jnlvls=29                    !! Number of levels in the multilayer energy budget scheme
931!$OMP THREADPRIVATE(jnlvls)
932  INTEGER(i_std), SAVE        :: jnlvls_under=10              !! Number of levels in the understorey of the multilayer energy budget scheme
933!$OMP THREADPRIVATE(jnlvls_under)
934  INTEGER(i_std), SAVE        :: jnlvls_canopy=10             !! Number of levels in the canopy of the multilayer energy budget scheme
935!$OMP THREADPRIVATE(jnlvls_canopy)
936  INTEGER(i_std), SAVE        :: jnlvls_over=9                !! Number of levels in the overstorey of the multilayer energy budget scheme
937!$OMP THREADPRIVATE(jnlvls_over)
938
939
940  INTEGER(i_std), SAVE        :: nlev_top                     !! Maximum number of canopy levels that are used to construct the "top"
941                                                              !! layer of the canopy. The top layer is used in the calculation
942                                                              !! transpiration.
943!$OMP THREADPRIVATE(nlev_top)
944  REAL(r_std), PARAMETER, &
945         DIMENSION (nlevels) :: z_level = (/ 0.0 /)           !! The height of the bottom of each canopy layer                                             
946                                                              !! @tex $(m)$ @endtex
947!$OMP THREADPRIVATE(z_level)
948
949
950
951  !
952  ! Parameters for determining the effective LAI for use in Pinty's albedo scheme
953  !
954  REAL(r_std), SAVE          ::  laieff_solar_angle           !! the zenith angle of the sun which determines our effective LAI
955                                                              !! Pinty et al recommend a value of 60 degrees for this regadless of the true
956                                                              !! solar zenith angle
957!$OMP THREADPRIVATE(laieff_solar_angle)
958  REAL(r_std), SAVE          ::  laieff_zero_cutoff           !! an arbitrary cutoff to prevent too low of values from being passed to
959                                                              !! routines in the calculation of the effective LAI
960!$OMP THREADPRIVATE(laieff_zero_cutoff)
961  REAL(r_std), SAVE          ::  direct_light_weight          !! an arbitrary weight (between 0 and 1) used when calculating the albedo and
962                                                              !! absorbed light in the canopy.  The amounts are first calculated using one unit of
963                                                              !! incoming light from either source, and then combined afterwards with this fraction.
964                                                              !! This fraction represents the light coming from
965                                                              !! the sun directory, while (1.0-this fraction) gives the amount coming
966                                                              !! from light first reflected off clouds and albedo.
967!$OMP THREADPRIVATE(direct_light_weight)
968
969  !
970  ! PARAMETERS FOR HYDRAULIC ARCHITECTURE
971  !
972
973  REAL(r_std), SAVE, DIMENSION(2)         :: a_viscosity = (/0.556,0.022/) !! Empirical parameters to adjust the resistance of fine
974                                                                           !! root and sapwood to the temperature dependency of the
975                                                                           !! viscosity of water Cochard et al 2000
976!$OMP THREADPRIVATE(a_viscosity)
977
978  !
979  ! BVOC : Biogenic activity  for each age class
980  !
981  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
982                                                                                       !! age class : isoprene (unitless)
983!$OMP THREADPRIVATE(iso_activity)
984  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
985                                                                                       !! age class : methanol (unnitless)
986!$OMP THREADPRIVATE(methanol_activity)
987
988  !
989  ! condveg.f90
990  !
991
992  ! 1. Scalar
993
994  ! 1.1 Flags used inside the module
995
996  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
997                                            !! albedo (see header of subroutine)
998                                            !! (true/false)
999!$OMP THREADPRIVATE(alb_bare_model)
1000  LOGICAL, SAVE :: alb_bg_modis = .FALSE.   !! Switch for choosing values of bare soil
1001                                            !! albedo read from file
1002                                            !! (true/false)
1003!$OMP THREADPRIVATE(alb_bg_modis)
1004  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
1005                                            !! (see header of subroutine). 
1006                                            !! (true/false)
1007!$OMP THREADPRIVATE(impaze)
1008  LOGICAL, SAVE :: rough_dyn = .TRUE.       !! Chooses between two methods to calculate the
1009                                            !! the roughness height : static or dynamic (varying with LAI)
1010                                            !! (true/false)
1011!$OMP THREADPRIVATE(rough_dyn)
1012
1013  LOGICAL, SAVE :: sla_dyn = .TRUE.        !! Chooses between two methods to calculate the
1014                                            !! specific leaf area: static or dynamic (varying with LAI or biomass)
1015                                            !! (true/false)
1016!$OMP THREADPRIVATE(sla_dyn)
1017
1018  LOGICAL, SAVE :: new_watstress = .FALSE.
1019!$OMP THREADPRIVATE(new_watstress)
1020
1021  REAL(r_std), SAVE :: alpha_watstress = 1.
1022!$OMP THREADPRIVATE(alpha_watstress)
1023  LOGICAL, SAVE :: use_height_dom = .FALSE.       !! A logical flag determining if we use
1024                                                  !! the dominant height of the vegetation (.TRUE.)
1025                                                  !! or the quadratic mean height (.FALSE.) when
1026                                                  !! the roughness height is calculated
1027!$OMP THREADPRIVATE(use_height_dom)
1028
1029  ! 1.2 Others
1030
1031  REAL(r_std), SAVE :: height_displacement = 0.66        !! Factor to calculate the zero-plane displacement
1032                                                         !! height from vegetation height (m)
1033!$OMP THREADPRIVATE(height_displacement)
1034  REAL(r_std), SAVE :: crown_packing = 1.0               !! Parameter to describe how much of the canopy space could
1035                                                         !! be filled with crowns (think: close packing of equal spheres)
1036!$OMP THREADPRIVATE(crown_packing)
1037  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
1038!$OMP THREADPRIVATE(z0_bare)
1039  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
1040!$OMP THREADPRIVATE(z0_ice)
1041  REAL(r_std), SAVE :: tcst_snowa = 3.                   !! Time constant of the albedo decay of snow (days)
1042!$OMP THREADPRIVATE(tcst_snowa)
1043  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
1044!$OMP THREADPRIVATE(snowcri_alb)
1045  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
1046!$OMP THREADPRIVATE(fixed_snow_albedo)
1047  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
1048!$OMP THREADPRIVATE(z0_scal)
1049  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
1050                                                         !! displacement height (m) (imposed)
1051!$OMP THREADPRIVATE(roughheight_scal)
1052  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
1053!$OMP THREADPRIVATE(emis_scal)
1054
1055  REAL(r_std), SAVE :: c1 = 0.32                         !! Constant used in the formulation of the ratio of
1056!$OMP THREADPRIVATE(c1)                                  !! friction velocity to the wind speed at the canopy top
1057                                                         !! see Ershadi et al. (2015) for more info
1058  REAL(r_std), SAVE :: c2 = 0.264                        !! Constant used in the formulation of the ratio of
1059!$OMP THREADPRIVATE(c2)                                  !! friction velocity to the wind speed at the canopy top
1060                                                         !! see Ershadi et al. (2015) for more info
1061  REAL(r_std), SAVE :: c3 = 15.1                         !! Constant used in the formulation of the ratio of
1062!$OMP THREADPRIVATE(c3)                                  !! friction velocity to the wind speed at the canopy top
1063                                                         !! see Ershadi et al. (2015) for more info
1064  REAL(r_std), SAVE :: Cdrag_foliage = 0.2               !! Drag coefficient of the foliage
1065!$OMP THREADPRIVATE(Cdrag_foliage)                       !! See Ershadi et al. (2015) and Su et. al (2001) for more info
1066  REAL(r_std), SAVE :: Ct = 0.01                         !! Heat transfer coefficient of the leaf
1067!$OMP THREADPRIVATE(Ct)                                  !! See Ershadi et al. (2015) and Su et. al (2001) for more info
1068  REAL(r_std), SAVE :: Prandtl = 0.71                    !! Prandtl number used in the calculation of Ct_star
1069!$OMP THREADPRIVATE(Prandtl)                             !! See Su et. al (2001) for more info
1070
1071
1072
1073  ! 2. Arrays
1074
1075 
1076! 2. Arrays
1077 
1078  REAL(r_std), SAVE, DIMENSION(n_spectralbands) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
1079!$OMP THREADPRIVATE(alb_deadleaf)
1080  REAL(r_std), SAVE, DIMENSION(n_spectralbands) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
1081!$OMP THREADPRIVATE(alb_ice)
1082  REAL(r_std), SAVE, DIMENSION(n_spectralbands) :: albedo_scal = (/ 0.25, 0.25 /)                !! Albedo values for visible and near-infrared
1083                                                                                   !! used imposed (unitless)
1084!$OMP THREADPRIVATE(albedo_scal)
1085  REAL(r_std), DIMENSION(n_spectralbands), SAVE :: alb_snow_0 = (/.95, .65/)       !! VIS and NIR albedo of fresh snow according to CLM3
1086!$OMP THREADPRIVATE(alb_snow_0)
1087  REAL(r_std), DIMENSION(n_spectralbands), SAVE :: c_albedo = (/0.2, 0.5/)         !! VIS and NIR albedo constant according to CLM3
1088!$OMP THREADPRIVATE(c_albedo)
1089  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
1090       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
1091                                                          !! dry soil albedo values in visible range
1092!$OMP THREADPRIVATE(vis_dry)
1093  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
1094       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
1095                                                          !! dry soil albedo values in near-infrared range
1096!$OMP THREADPRIVATE(nir_dry)
1097  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
1098       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
1099                                                          !! wet soil albedo values in visible range
1100!$OMP THREADPRIVATE(vis_wet)
1101  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
1102       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
1103                                                          !! wet soil albedo values in near-infrared range
1104!$OMP THREADPRIVATE(nir_wet)
1105  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
1106       &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:
1107                                                                   !! Averaged of wet and dry soil albedo values
1108                                                                   !! in visible and near-infrared range
1109!$OMP THREADPRIVATE(albsoil_vis)
1110  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
1111       &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:
1112                                                                !! Averaged of wet and dry soil albedo values
1113                                                                !! in visible and near-infrared range
1114!$OMP THREADPRIVATE(albsoil_nir)
1115  REAL(r_std) :: alb_threshold = 0.0000000001_r_std       !! A threshold for the iteration of the
1116                                                          !! multilevel albedo.  Could be externalised.
1117                                                          !! Fairly arbitrary, although if a level has
1118                                                          !! no LAI the absorption often ends up being
1119                                                          !! equal to this value, so it should not
1120                                                          !! be high.
1121!$OMP THREADPRIVATE(alb_threshold)
1122
1123
1124
1125  !
1126  ! diffuco.f90
1127  !
1128
1129  ! 0. Constants
1130
1131  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
1132                                                     !! of dry air (unitless)
1133  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
1134  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
1135  REAL(r_std), PARAMETER :: mol_to_m_1 = 0.0244      !!
1136  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
1137  REAL(r_std), PARAMETER :: W_to_mol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
1138
1139  ! 1. Scalar
1140
1141  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
1142!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
1143  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
1144!$OMP THREADPRIVATE(laimax)
1145  LOGICAL, SAVE :: downregulation_co2 = .TRUE.             !! Set to .TRUE. if you want CO2 downregulation.
1146!$OMP THREADPRIVATE(downregulation_co2)
1147  REAL(r_std), SAVE :: downregulation_co2_baselevel = 380. !! CO2 base level (ppm)
1148!$OMP THREADPRIVATE(downregulation_co2_baselevel)
1149  REAL(r_std), SAVE :: gb_ref = 1./25.                     !! Leaf bulk boundary layer resistance (s m-1)
1150!$OMP THREADPRIVATE(gb_ref)
1151
1152  ! 3. Coefficients of equations
1153
1154  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
1155!$OMP THREADPRIVATE(lai_level_depth)
1156!
1157  REAL(r_std), SAVE :: x1_coef =  0.177        !! Multiplicative factor for calculating the pseudo first order rate constant
1158                                               !! of assimilation response to
1159                                               !co2 kt (unitless)
1160!$OMP THREADPRIVATE(x1_coef)
1161  REAL(r_std), SAVE :: x1_Q10 =  0.069         !! Exponential factor in the equation defining kt (unitless)
1162!$OMP THREADPRIVATE(x1_Q10)
1163  REAL(r_std), SAVE :: quantum_yield =  0.092  !!
1164!$OMP THREADPRIVATE(quantum_yield)
1165  REAL(r_std), SAVE :: kt_coef = 0.7           !! Multiplicative factor in the equation defining kt (unitless)
1166!$OMP THREADPRIVATE(kt_coef)
1167  REAL(r_std), SAVE :: kc_coef = 39.09         !! Multiplicative factor for calculating the Michaelis-Menten
1168                                               !! coefficient Kc (unitless)
1169!$OMP THREADPRIVATE(kc_coef)
1170  REAL(r_std), SAVE :: Ko_Q10 = 0.085          !! Exponential factor for calculating the Michaelis-Menten coefficients
1171                                               !! Kc and Ko (unitless)
1172!$OMP THREADPRIVATE(Ko_Q10)
1173  REAL(r_std), SAVE :: Oa = 210000.            !! Intercellular concentration of O2 (ppm)
1174!$OMP THREADPRIVATE(Oa)
1175  REAL(r_std), SAVE :: Ko_coef =  2.412        !! Multiplicative factor for calculating the Michaelis-Menten
1176                                               !! coefficient Ko (unitless)
1177!$OMP THREADPRIVATE(Ko_coef)
1178  REAL(r_std), SAVE :: CP_0 = 42.              !! Multiplicative factor for calculating the CO2 compensation
1179                                               !! point CP (unitless)
1180!$OMP THREADPRIVATE(CP_0)
1181  REAL(r_std), SAVE :: CP_temp_coef = 9.46     !! Exponential factor for calculating the CO2 compensation point CP (unitless)
1182!$OMP THREADPRIVATE(CP_temp_coef)
1183  REAL(r_std), SAVE :: CP_temp_ref = 25.       !! Reference temperature for the CO2 compensation point CP (C)
1184!$OMP THREADPRIVATE(CP_temp_ref)
1185  !
1186  REAL(r_std), SAVE, DIMENSION(2) :: rt_coef = (/ 0.8, 1.3 /)    !!
1187!$OMP THREADPRIVATE(rt_coef)
1188  REAL(r_std), SAVE, DIMENSION(2) :: vc_coef = (/ 0.39, 0.3 /)   !!
1189!$OMP THREADPRIVATE(vc_coef)
1190  REAL(r_std), SAVE               :: c13_a = 4.4      !! fractionation against during diffusion
1191!$OMP THREADPRIVATE(c13_a)
1192  REAL(r_std), SAVE               :: c13_b = 27.      !! fractionation against during carboxylation
1193!$OMP THREADPRIVATE(c13_b)
1194  REAL(r_std), SAVE               :: threshold_c13_assim = 0.01 !! If assimilation falls below this threshold
1195                                                                !! the delta_c13
1196                                                                !is set to zero
1197!$OMP THREADPRIVATE(threshold_c13_assim)
1198  !
1199  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
1200  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
1201!$OMP THREADPRIVATE(dew_veg_poly_coeff)
1202!
1203  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
1204!$OMP THREADPRIVATE(Oi)
1205  !
1206  ! slowproc.f90
1207  !
1208
1209  ! 1. Scalar
1210
1211  INTEGER(i_std), SAVE :: ninput_year_orig = 0       !!  first year for N inputs (number)
1212!$OMP THREADPRIVATE(ninput_year_orig)
1213  LOGICAL, SAVE :: ninput_suffix_year = .FALSE.      !! Do the Ninput datasets have a 'year' suffix ? (y/n) 
1214!$OMP THREADPRIVATE(ninput_suffix_year)
1215  REAL(r_std), SAVE :: bulk_default = 1000.0           !! Default value for bulk density of soil (kg/m3)
1216!$OMP THREADPRIVATE(bulk_default)
1217  REAL(r_std), SAVE :: ph_default = 5.5              !! Default value for pH of soil (-)
1218!$OMP THREADPRIVATE(ph_default)
1219
1220  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
1221!$OMP THREADPRIVATE(min_vegfrac)
1222  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
1223!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
1224 
1225  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
1226!$OMP THREADPRIVATE(stempdiag_bid)
1227
1228
1229                           !-----------------------------!
1230                           !  STOMATE AND LPJ PARAMETERS !
1231                           !-----------------------------!
1232
1233
1234  ! Allometric relationships
1235  REAL(r_std), SAVE :: exp_kf = 3.0              !! Tuning parameter for the relationship between tree height and k_latosas
1236!$OMP THREADPRIVATE(exp_kf)
1237  !
1238  ! lpj_constraints.f90
1239  !
1240 
1241  ! 1. Scalar
1242
1243  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
1244                                           !! regeneration (vernalization) (years)
1245!$OMP THREADPRIVATE(too_long)
1246
1247
1248  !
1249  ! lpj_establish.f90
1250  !
1251
1252  ! 1. Scalar
1253
1254  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (ind/m2/dt_stomate)
1255!$OMP THREADPRIVATE(estab_max_tree)
1256  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (ind/m2/dt_stomate)
1257!$OMP THREADPRIVATE(estab_max_grass)
1258 
1259  ! 3. Coefficients of equations
1260
1261  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
1262!$OMP THREADPRIVATE(establish_scal_fact)
1263  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
1264!$OMP THREADPRIVATE(max_tree_coverage)
1265  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
1266!$OMP THREADPRIVATE(ind_0_estab)
1267
1268
1269  !
1270  ! lpj_fire.f90
1271  !
1272
1273  ! 1. Scalar
1274
1275  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
1276!$OMP THREADPRIVATE(tau_fire)
1277  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
1278                                                !! below which iginitions extinguish
1279                                                !! @tex $(gC m^{-2})$ @endtex
1280!$OMP THREADPRIVATE(litter_crit)
1281  REAL(r_std), SAVE :: fire_resist_lignin = 0.5 !!
1282!$OMP THREADPRIVATE(fire_resist_lignin)
1283  ! 2. Arrays
1284
1285  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
1286       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95, .95 /)       !! compartments emitted to the atmosphere
1287!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
1288
1289  ! 3. Coefficients of equations
1290
1291  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
1292!$OMP THREADPRIVATE(bcfrac_coeff)
1293  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
1294!$OMP THREADPRIVATE(firefrac_coeff)
1295
1296  !
1297  ! lpj_gap.f90
1298  !
1299
1300  ! 1. Scalar
1301
1302  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
1303                                                 !! @tex $(year^{-1})$ @endtex
1304!$OMP THREADPRIVATE(ref_greff)
1305
1306  !               
1307  ! lpj_light.f90
1308  !             
1309
1310  ! 1. Scalar
1311 
1312  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
1313                                            !! to fpc of last time step (F)? (true/false)
1314!$OMP THREADPRIVATE(annual_increase)
1315  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
1316                                            !! (due to its branches etc.) (0-1, unitless)
1317                                            !! This means that only a small fraction of its crown area
1318                                            !! can be invaded by other trees.
1319!$OMP THREADPRIVATE(min_cover)
1320  !
1321  ! lpj_pftinout.f90
1322  !
1323
1324  ! 1. Scalar
1325
1326  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
1327!$OMP THREADPRIVATE(min_avail)
1328  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
1329!$OMP THREADPRIVATE(ind_0)
1330  ! 3. Coefficients of equations
1331 
1332  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
1333!$OMP THREADPRIVATE(RIP_time_min)
1334  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
1335!$OMP THREADPRIVATE(npp_longterm_init)
1336  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
1337!$OMP THREADPRIVATE(everywhere_init)
1338
1339
1340
1341
1342  !
1343  ! stomate_data.f90
1344  !
1345
1346  ! 1. Scalar
1347
1348  ! 1.2 climatic parameters
1349
1350  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
1351!$OMP THREADPRIVATE(precip_crit)
1352  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
1353!$OMP THREADPRIVATE(gdd_crit_estab)
1354  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
1355!$OMP THREADPRIVATE(fpc_crit)
1356
1357  ! 1.3 sapling characteristics
1358
1359  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
1360!$OMP THREADPRIVATE(alpha_grass)
1361  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
1362!$OMP THREADPRIVATE(alpha_tree)
1363  REAL(r_std), SAVE :: struct_to_leaves = 0.05  !! Fraction of structural carbon in grass and crops as a share of the leaf
1364                                                !! carbon pool. Only used for grasses and crops (thus NOT for trees)
1365                                                !! (unitless)
1366!$OMP THREADPRIVATE(struct_to_leaves)
1367
1368  REAL(r_std), SAVE :: labile_to_total = 0.01   !! Fraction of the labile pool in trees, grasses and crops as a share of the
1369                                                !! total carbon pool (accounting for the N-content of the different tissues).
1370                                                !! (unitless)
1371!$OMP THREADPRIVATE(labile_to_total)
1372
1373
1374
1375  ! 1.4  time scales for phenology and other processes (in days)
1376REAL(r_std), SAVE :: tau_month = 20.              !! (days)       
1377!$OMP THREADPRIVATE(tau_month)
1378  REAL(r_std), SAVE :: tau_week = 7.              !! (days) 
1379!$OMP THREADPRIVATE(tau_week)
1380  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
1381!$OMP THREADPRIVATE(tau_hum_month)
1382  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
1383!$OMP THREADPRIVATE(tau_hum_week)
1384  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
1385!$OMP THREADPRIVATE(tau_t2m_month)
1386  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
1387!$OMP THREADPRIVATE(tau_t2m_week)
1388  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
1389!$OMP THREADPRIVATE(tau_tsoil_month)
1390  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
1391!$OMP THREADPRIVATE(tau_gpp_week)
1392  REAL(r_std), SAVE :: tau_sugarload_week = 7.    !! (days)
1393!$OMP THREADPRIVATE(tau_sugarload_week)
1394  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
1395!$OMP THREADPRIVATE(tau_gdd)
1396  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
1397!$OMP THREADPRIVATE(tau_ngd)
1398  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
1399!$OMP THREADPRIVATE(coeff_tau_longterm)
1400  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
1401!$OMP THREADPRIVATE(tau_longterm_max)
1402
1403  ! 3. Coefficients of equations
1404
1405  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
1406!$OMP THREADPRIVATE(bm_sapl_carbres)
1407  REAL(r_std), SAVE :: bm_sapl_labile = 5.             !!
1408!$OMP THREADPRIVATE(bm_sapl_labile)
1409  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
1410!$OMP THREADPRIVATE(bm_sapl_sapabove)
1411  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
1412!$OMP THREADPRIVATE(bm_sapl_heartabove)
1413  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
1414!$OMP THREADPRIVATE(bm_sapl_heartbelow)
1415  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
1416!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
1417  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
1418!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
1419  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
1420!$OMP THREADPRIVATE(init_sapl_mass_carbres)
1421  REAL(r_std), SAVE :: init_sapl_mass_labile = 5.      !!
1422!$OMP THREADPRIVATE(init_sapl_mass_labile)
1423  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
1424!$OMP THREADPRIVATE(init_sapl_mass_root)
1425  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
1426!$OMP THREADPRIVATE(init_sapl_mass_fruit)
1427  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
1428!$OMP THREADPRIVATE(cn_sapl_init)
1429  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
1430!$OMP THREADPRIVATE(migrate_tree)
1431  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
1432!$OMP THREADPRIVATE(migrate_grass)
1433  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
1434!$OMP THREADPRIVATE(lai_initmin_tree)
1435  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
1436!$OMP THREADPRIVATE(lai_initmin_grass)
1437  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
1438!$OMP THREADPRIVATE(dia_coeff)
1439  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
1440!$OMP THREADPRIVATE(maxdia_coeff)
1441  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
1442!$OMP THREADPRIVATE(bm_sapl_leaf)
1443
1444
1445  !
1446  ! stomate_litter.f90
1447  !
1448
1449  ! 0. Constants
1450
1451  REAL(r_std), PARAMETER :: Q10 = 10.               !!
1452
1453  ! 1. Scalar
1454
1455  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
1456!$OMP THREADPRIVATE(z_decomp)
1457
1458  ! 2. Arrays
1459
1460  REAL(r_std), SAVE :: frac_soil_struct_sua = 0.4    !! corresponding to frac_soil(istructural,isurface,iabove)
1461!$OMP THREADPRIVATE(frac_soil_struct_sua)
1462  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
1463!$OMP THREADPRIVATE(frac_soil_struct_ab)
1464  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
1465!$OMP THREADPRIVATE(frac_soil_struct_sa)
1466  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
1467!$OMP THREADPRIVATE(frac_soil_struct_sb)
1468  REAL(r_std), SAVE :: frac_soil_metab_sua = 0.4    !! corresponding to frac_soil(imetabolic,iactive,iabove)
1469!$OMP THREADPRIVATE(frac_soil_metab_sua)
1470  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
1471!$OMP THREADPRIVATE(frac_soil_metab_ab)
1472  REAL(r_std), SAVE :: fungivores = 0.3    !! Fraction of decomposed litter consumed by fungivores   
1473!$OMP THREADPRIVATE(fungivores)
1474  REAL(r_std), SAVE :: frac_woody = 0.65   !! Coefficient for determining the lignin fraction of woody litter
1475!$OMP THREADPRIVATE(frac_woody)
1476  REAL(r_std), SAVE, DIMENSION(nparts) :: CN_fix = & !! C/N ratio of each plant pool (0-100, unitless)
1477       & (/ 40., 40., 40., 40., 40., 40., 40., 40., 40. /) 
1478!$OMP THREADPRIVATE(CN_fix)
1479
1480  ! 3. Coefficients of equations
1481
1482  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
1483!$OMP THREADPRIVATE(metabolic_ref_frac)
1484  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
1485!$OMP THREADPRIVATE(metabolic_LN_ratio)
1486  ! Turnover rate (yr-1) - From Parton et al., 1993
1487  REAL(r_std), SAVE :: turn_metabolic = 15           !!
1488!$OMP THREADPRIVATE(turn_metabolic)
1489  REAL(r_std), SAVE :: turn_struct = 4                !!
1490!$OMP THREADPRIVATE(turn_struct)
1491  REAL(r_std), SAVE :: turn_woody = 1.33              !! from DOFOCO
1492!$OMP THREADPRIVATE(turn_woody)
1493  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
1494!$OMP THREADPRIVATE(soil_Q10)
1495  REAL(r_std), SAVE :: soil_Q10_uptake = 0.45         
1496!$OMP THREADPRIVATE(soil_Q10_uptake)
1497  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
1498!$OMP THREADPRIVATE(tsoil_ref)
1499  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
1500!$OMP THREADPRIVATE(litter_struct_coef)
1501  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
1502!$OMP THREADPRIVATE(moist_coeff)
1503  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
1504!$OMP THREADPRIVATE(moistcont_min)
1505
1506
1507  !
1508  ! stomate_lpj.f90
1509  !
1510
1511  ! 1. Scalar
1512
1513  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
1514!$OMP THREADPRIVATE(frac_turnover_daily)
1515
1516
1517  !
1518  ! stomate_npp.f90
1519  !
1520
1521  ! 1. Scalar
1522
1523  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
1524                                     !! for maintenance respiration (0-1, unitless)
1525!$OMP THREADPRIVATE(tax_max)
1526
1527
1528  !
1529  ! stomate_phenology.f90
1530  !
1531
1532  ! 1. Scalar
1533
1534  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
1535!$OMP THREADPRIVATE(min_growthinit_time)
1536  REAL(r_std), SAVE :: relsoilmoist_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1537                                                   !!  - for trees (0-1, unitless)
1538!$OMP THREADPRIVATE(relsoilmoist_always_tree)
1539  REAL(r_std), SAVE :: relsoilmoist_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1540                                                   !! - for grass (0-1, unitless)
1541!$OMP THREADPRIVATE(relsoilmoist_always_grass)
1542  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1543!$OMP THREADPRIVATE(t_always)
1544  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1545!$OMP THREADPRIVATE(t_always_add)
1546
1547  ! 3. Coefficients of equations
1548 
1549  REAL(r_std), SAVE :: gddncd_ref = 414.           !! Empirical parameter to determine budbreak for ncdgdd phenology type. Reprensents gdd.
1550!$OMP THREADPRIVATE(gddncd_ref)
1551  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !! Empirical parameter to determine budbreak for ncdgdd phenology type
1552!$OMP THREADPRIVATE(gddncd_curve)
1553  REAL(r_std), SAVE :: gddncd_offset = 150         !! Empirical parameter to determine budbreak for ncdgdd phenology type
1554!$OMP THREADPRIVATE(gddncd_offset)
1555
1556
1557  !
1558  ! stomate_resp.f90
1559  !
1560
1561  ! 3. Coefficients of equations
1562
1563  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1564!$OMP THREADPRIVATE(maint_resp_min_vmax)
1565  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1566!$OMP THREADPRIVATE(maint_resp_coeff)
1567
1568
1569  !
1570  ! stomate_som_dynamics.f90 (in stomate_soilcarbon.f90 or
1571  ! stomate_soil_carbon_discretization.f90)   
1572  !
1573
1574  ! 2. Arrays
1575
1576  ! 2.1 Fixed fraction from one pool to another (or to CO2 emission)
1577
1578  REAL(r_std), SAVE :: active_to_pass_ref_frac = 0.003  !! from active pool: depends on clay content  (0-1, unitless)
1579                                                        !! corresponding to frac_carb(:,iactive,ipassive)
1580!$OMP THREADPRIVATE(active_to_pass_ref_frac)
1581  REAL(r_std), SAVE :: surf_to_slow_ref_frac = 0.4      !! from surface pool
1582                                                        !! corresponding to frac_carb(:,isurf,islow)
1583!$OMP THREADPRIVATE(surf_to_slow_ref_frac)
1584
1585  REAL(r_std), SAVE :: active_to_CO2_ref_frac  = 0.85   !! from active pool: depends on clay content  (0-1, unitless)
1586                                                        !! corresponding to frac_resp(:,iactive)
1587!$OMP THREADPRIVATE(active_to_CO2_ref_frac)
1588  REAL(r_std), SAVE :: slow_to_pass_ref_frac   = 0.03  !! from slow pool: depends on clay content  (0-1, unitless)
1589                                                        !! corresponding to frac_carb(:,islow,ipassive)
1590!$OMP THREADPRIVATE(slow_to_pass_ref_frac)
1591  REAL(r_std), SAVE :: slow_to_CO2_ref_frac    = 0.55   !! from slow pool (0-1, unitless)
1592                                                        !! corresponding to frac_resp(:,islow)
1593!$OMP THREADPRIVATE(slow_to_CO2_ref_frac)
1594  REAL(r_std), SAVE :: pass_to_active_ref_frac = 0.45   !! from passive pool (0-1, unitless)
1595                                                        !! corresponding to frac_carb(:,ipassive,iactive)
1596!$OMP THREADPRIVATE(pass_to_active_ref_frac)
1597  REAL(r_std), SAVE :: pass_to_slow_ref_frac   = 0.0    !! from passive pool (0-1, unitless)
1598                                                        !! corresponding to frac_carb(:,ipassive,islow)
1599!$OMP THREADPRIVATE(pass_to_slow_ref_frac)
1600
1601  ! 2.2 som carbon pools
1602
1603  REAL(r_std), SAVE :: som_init_active = 1000           !! Initial active SOM carbon (g m-2)
1604!$OMP THREADPRIVATE(som_init_active)
1605  REAL(r_std), SAVE :: som_init_slow = 3000             !! Initial slow SOM carbon (g m-2)
1606!$OMP THREADPRIVATE(som_init_slow)
1607  REAL(r_std), SAVE :: som_init_passive = 5000          !! Initial passive SOM carbon (g m-2)
1608!$OMP THREADPRIVATE(som_init_passive)
1609  REAL(r_std), SAVE :: som_init_surface = 1000          !! Initial surface SOM carbon (g m-2)
1610!$OMP THREADPRIVATE(som_init_surface)
1611
1612  ! 3. Define Variable fraction from one pool to another (function of silt and clay fraction)
1613  REAL(r_std), SAVE :: active_to_pass_clay_frac     = 0.032
1614!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1615  REAL(r_std), SAVE :: active_to_CO2_clay_silt_frac = 0.68
1616!$OMP THREADPRIVATE(active_to_CO2_clay_silt_frac)
1617  REAL(r_std), SAVE :: slow_to_pass_clay_frac   = 0 
1618!$OMP THREADPRIVATE(slow_to_pass_clay_frac)
1619
1620  ! C to N target ratios of differnt pools
1621  REAL(r_std), SAVE ::  CN_target_iactive_ref  = 15. !! CN target ratio of active pool for soil min N = 0
1622!$OMP THREADPRIVATE(CN_target_iactive_ref)
1623  REAL(r_std), SAVE ::  CN_target_islow_ref    = 20. !! CN target ratio of slow pool for soil min N = 0
1624!$OMP THREADPRIVATE(CN_target_islow_ref)
1625  REAL(r_std), SAVE ::  CN_target_ipassive_ref = 10. !! CN target ratio of passive pool for soil min N = 0
1626!$OMP THREADPRIVATE(CN_target_ipassive_ref)
1627  REAL(r_std), SAVE ::  CN_target_isurface_ref = 20. !! CN target ratio of surface pool for litter nitrogen content = 0
1628!$OMP THREADPRIVATE(CN_target_isurface_ref)
1629  REAL(r_std), SAVE ::  CN_target_iactive_Nmin  = -6.  !! CN target ratio change per mineral N unit (g m-2) for active pool
1630!$OMP THREADPRIVATE(CN_target_iactive_Nmin)
1631  REAL(r_std), SAVE ::  CN_target_islow_Nmin    = -4.  !! CN target ratio change per mineral N unit (g m-2) for slow pool
1632!$OMP THREADPRIVATE(CN_target_islow_Nmin)
1633  REAL(r_std), SAVE ::  CN_target_ipassive_Nmin = -1.5 !! CN target ratio change per mineral N unit (g m-2) for passive pool
1634!$OMP THREADPRIVATE(CN_target_ipassive_Nmin)
1635  REAL(r_std), SAVE ::  CN_target_isurface_pnc  = -5.  !! CN target ratio change per plant nitrogen content unit (%) for surface pool
1636  !! Turnover in SOM pools (year-1)
1637!$OMP THREADPRIVATE(CN_target_isurface_pnc)
1638  REAL(r_std), SAVE :: som_turn_isurface = 6.0           !! turnover of surface pool (year-1)
1639!$OMP THREADPRIVATE(som_turn_isurface)
1640  REAL(r_std), SAVE :: som_turn_iactive     = 7.3        !! turnover of active pool (year-1)
1641!$OMP THREADPRIVATE(som_turn_iactive)
1642  REAL(r_std), SAVE :: som_turn_islow       = 0.1        !! turnover of slow pool (year-1)
1643!$OMP THREADPRIVATE(som_turn_islow)
1644  REAL(r_std), SAVE :: som_turn_ipassive    = 0.0025     !! turnover of passive pool (year-1)
1645!$OMP THREADPRIVATE(som_turn_ipassive)
1646  REAL(r_std), SAVE :: fslow = 37.0                      !! convertiing factor to go from active pool turnover to slow pool turnover from Guimberteau et al 2018 GMD
1647!$OMP THREADPRIVATE(fslow)
1648  REAL(r_std), SAVE :: fpassive = 1617.45                !! convertiing factor to go from active pool turnover to passive pool turnover from Guimberteau et al 2018 GMD
1649!$OMP THREADPRIVATE(fpassive)
1650  REAL(r_std), SAVE :: stomate_tau = 4.699E6 
1651!$OMP THREADPRIVATE(stomate_tau)
1652  REAL(r_std), SAVE :: depth_modifier = 1.E6             !! e-folding depth of turnover rates,following Koven et al.,2013,Biogeosciences. A very large value means no depth modification
1653!$OMP THREADPRIVATE(depth_modifier)
1654  REAL(r_std), SAVE :: som_turn_iactive_clay_frac = 0.75 !! clay-dependant parameter impacting on turnover rate of active pool
1655                                                         !! Tm parameter of Parton et al. 1993 (-)
1656!$OMP THREADPRIVATE(som_turn_iactive_clay_frac)
1657
1658  !
1659  ! stomate_turnover.f90
1660  !
1661
1662  ! 3. Coefficients of equations
1663
1664  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1665!$OMP THREADPRIVATE(new_turnover_time_ref)
1666
1667
1668  !
1669  ! stomate_vmax.f90
1670  !
1671 
1672  ! 1. Scalar
1673
1674  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1675!$OMP THREADPRIVATE(vmax_offset)
1676  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1677                                                !! reaches 1 (unitless)
1678!$OMP THREADPRIVATE(leafage_firstmax)
1679  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1680                                                !! falls below 1 (unitless)
1681!$OMP THREADPRIVATE(leafage_lastmax)
1682  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1683                                                !! reaches its minimum (vmax_offset)
1684                                                !! (unitless)
1685!$OMP THREADPRIVATE(leafage_old)
1686  REAL(r_std), SAVE :: sugar_load_min = 0.05    !! Lower bound for sugar loading when used to regulate NUE.
1687                                                !! Sugar loafding results in a strong reduction of GPP. By
1688                                                !! taking a rather high lower limit the impact of sugar loading
1689                                                !! is limited. This will result in high C-reserves unless
1690                                                !! leaching is implemented.
1691!$OMP THREADPRIVATE(sugar_load_min)
1692  REAL(r_std), SAVE :: sugar_load_max = 1.0     !! Upper bound for sugar loading when used to regulate NUE
1693!$OMP THREADPRIVATE(sugar_load_max)
1694
1695  !
1696  ! nitrogen_dynamics (in stomate_soilcarbon.f90)
1697  !
1698
1699  ! 0. Constants
1700  REAL(r_std), PARAMETER :: D_air = 1.73664     !! Oxygen diffusion rate in the air = 0.07236 m2/h
1701                                               !! from Table 2 of Li et al, 2000
1702                                               !! (m**2/day)
1703
1704  REAL(r_std), PARAMETER :: C_molar_mass = 12  !! Carbon Molar mass (gC mol-1)
1705
1706  REAL(r_std), PARAMETER :: Pa_to_hPa    = 0.01      !! Conversion factor from Pa to hPa (-)
1707  REAL(r_std), PARAMETER :: V_O2         = 0.209476  !! Volumetric fraction of O2 in air (-)
1708
1709  REAL(r_std), PARAMETER :: pk_NH4 = 9.25      !! The negative logarithm of the acid dissociation constant K_NH4     
1710                                               !! See Table 4 of Li et al. 1992 and Appendix A of Zhang et al. 2002   
1711
1712                                     
1713  ! 1. Scalar
1714
1715  ! Coefficients for defining maximum porosity
1716  ! From Saxton, K.E., Rawls, W.J., Romberger, J.S., Papendick, R.I., 1986
1717  ! Estimationg generalized soil-water characteristics from texture.
1718  ! Soil Sci. Soc. Am. J. 50, 1031-1036
1719  ! Cited in Table 5 (page 444) of
1720  ! Y. Pachepsky, W.J. Rawls
1721  ! Development of Pedotransfer Functions in Soil Hydrology
1722  ! Elsevier, 23 nov. 2004 - 542 pages
1723  ! http://books.google.fr/books?id=ar_lPXaJ8QkC&printsec=frontcover&hl=fr#v=onepage&q&f=false
1724  REAL(r_std), SAVE :: h_saxton = 0.332          !! h coefficient
1725!$OMP THREADPRIVATE(h_saxton)
1726  REAL(r_std), SAVE :: j_saxton = -7.251*1e-4    !! j coefficient
1727!$OMP THREADPRIVATE(j_saxton)
1728  REAL(r_std), SAVE :: k_saxton = 0.1276         !! k coefficient
1729!$OMP THREADPRIVATE(k_saxton)
1730
1731  ! Values of the power used in the equation defining the diffusion of oxygen in soil
1732  ! from Table 2 of Li et al, 2000
1733  REAL(r_std), SAVE :: diffusionO2_power_1 = 3.33 !! (unitless)
1734!$OMP THREADPRIVATE(diffusionO2_power_1)
1735  REAL(r_std), SAVE :: diffusionO2_power_2 = 2.0  !! (unitless)
1736!$OMP THREADPRIVATE(diffusionO2_power_2)
1737
1738  ! Temperature-related Factors impacting on Oxygen diffusion rate
1739  ! From eq. 2 of Table 2 (Li et al, 2000)
1740  REAL(r_std), SAVE ::   F_nofrost = 1.2          !! (unitless)
1741!$OMP THREADPRIVATE(F_nofrost)
1742  REAL(r_std), SAVE ::   F_frost   = 0.8          !! (unitless)
1743!$OMP THREADPRIVATE(F_frost)
1744
1745  ! Coefficients used in the calculation of Volumetric fraction of anaerobic microsites
1746  ! a and b constants are not specified in Li et al., 2000
1747  ! S. Zaehle used a=0.85 and b=1 without mention to any publication
1748  REAL(r_std), SAVE ::   a_anvf    = 0.85 !! (-)
1749!$OMP THREADPRIVATE(a_anvf)
1750  REAL(r_std), SAVE ::   b_anvf    = 1.   !! (-)
1751!$OMP THREADPRIVATE(b_anvf)
1752
1753  ! Coefficients used in the calculation of the Fraction of adsorbed NH4+
1754  ! Li et al. 1992, JGR, Table 4
1755  REAL(r_std), SAVE ::   a_FixNH4 = 0.41  !! (-)
1756!$OMP THREADPRIVATE(a_FixNH4)
1757  REAL(r_std), SAVE ::   b_FixNH4 = -0.47 !! (-)
1758!$OMP THREADPRIVATE(b_FixNH4)
1759  REAL(r_std), SAVE ::   clay_max = 0.63  !! (-)
1760!$OMP THREADPRIVATE(clay_max)
1761
1762  ! Coefficients used in the calculation of the Response of Nitrification
1763  ! to soil moisture
1764  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1765  REAL(r_std), SAVE ::   fw_nit_0 =  -0.0243  !! (-)
1766!$OMP THREADPRIVATE(fw_nit_0)
1767  REAL(r_std), SAVE ::   fw_nit_1 =   0.9975  !! (-)
1768!$OMP THREADPRIVATE(fw_nit_1)
1769  REAL(r_std), SAVE ::   fw_nit_2 =  -5.5368  !! (-)
1770!$OMP THREADPRIVATE(fw_nit_2)
1771  REAL(r_std), SAVE ::   fw_nit_3 =  17.651   !! (-)
1772!$OMP THREADPRIVATE(fw_nit_3)
1773  REAL(r_std), SAVE ::   fw_nit_4 = -12.904   !! (-)
1774!$OMP THREADPRIVATE(fw_nit_4)
1775
1776  ! Coefficients used in the calculation of the Response of Nitrification
1777  ! to Temperature
1778  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1779  REAL(r_std), SAVE ::   ft_nit_0 =  -0.0233 !! (-)
1780!$OMP THREADPRIVATE(ft_nit_0)
1781  REAL(r_std), SAVE ::   ft_nit_1 =   0.3094 !! (-)
1782!$OMP THREADPRIVATE(ft_nit_1)
1783  REAL(r_std), SAVE ::   ft_nit_2 =  -0.2234 !! (-)
1784!$OMP THREADPRIVATE(ft_nit_2)
1785  REAL(r_std), SAVE ::   ft_nit_3 =   0.1566 !! (-)
1786!$OMP THREADPRIVATE(ft_nit_3)
1787  REAL(r_std), SAVE ::   ft_nit_4 =  -0.0272 !! (-)
1788!$OMP THREADPRIVATE(ft_nit_4)
1789
1790  ! Coefficients used in the calculation of the Response of Nitrification
1791  ! to pH
1792  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 101
1793  REAL(r_std), SAVE ::   fph_0 = -1.2314  !! (-)
1794!$OMP THREADPRIVATE(fph_0)
1795  REAL(r_std), SAVE ::   fph_1 = 0.7347   !! (-)
1796!$OMP THREADPRIVATE(fph_1)
1797  REAL(r_std), SAVE ::   fph_2 = -0.0604  !! (-)
1798!$OMP THREADPRIVATE(fph_2)
1799
1800  ! Coefficients used in the calculation of the response of NO2 or NO
1801  ! production during nitrificationof to Temperature
1802  ! Zhang et al. 2002, Ecological Modelling, appendix A, page 102
1803  REAL(r_std), SAVE ::   ftv_0 = 2.72   !! (-)
1804!$OMP THREADPRIVATE(ftv_0)
1805  REAL(r_std), SAVE ::   ftv_1 = 34.6   !! (-)
1806!$OMP THREADPRIVATE(ftv_1)
1807  REAL(r_std), SAVE ::   ftv_2 = 9615.  !! (-)
1808!$OMP THREADPRIVATE(ftv_2)
1809
1810  REAL(r_std), SAVE ::   k_nitrif = 2.0         !! Nitrification rate at 20 ◩C and field capacity (day-1)
1811                                                !! Schmid et al., 2001 give a value of 0.2 per day.
1812                                                !! (https://doi.org/10.1023/A:1012694218748)
1813                                                !! OCN used a value of 2.0.  We keep the OCN value.
1814!$OMP THREADPRIVATE(k_nitrif)
1815
1816  REAL(r_std), SAVE ::   n2o_nitrif_p = 0.0006  !! Reference n2o production per N-NO3 produced g N-N2O  (g N-NO3)-1
1817                                                !! From Zhang et al., 2002 - Appendix A p. 102
1818!$OMP THREADPRIVATE(n2o_nitrif_p)
1819  REAL(r_std), SAVE ::   no_nitrif_p = 0.0025   !! Reference NO production per N-NO3 produced g N-NO  (g N-NO3)-1
1820                                                !! From Zhang et al., 2002 - Appendix A p. 102
1821!$OMP THREADPRIVATE(no_nitrif_p)
1822
1823  ! NO production from chemodenitrification
1824  ! based on Kesik et al., 2005, Biogeosciences
1825  ! Coefficients used in the calculation of the Response to Temperature
1826  REAL(r_std), SAVE ::   chemo_t0  = -31494. !! (-)
1827!$OMP THREADPRIVATE(chemo_t0)
1828  ! Coefficients use in the calculation of the Response to pH
1829  REAL(r_std), SAVE ::   chemo_ph0 = -1.62   !! (-)
1830!$OMP THREADPRIVATE(chemo_ph0)
1831  ! Coefficients used in the calculation of NO production from chemodenitrification
1832  REAL(r_std), SAVE ::   chemo_0   = 30.     !! (-)
1833!$OMP THREADPRIVATE(chemo_0)
1834  REAL(r_std), SAVE ::   chemo_1   = 16565.  !! (-)
1835!$OMP THREADPRIVATE(chemo_1)
1836
1837  ! Denitrification processes
1838  ! Li et al, 2000, JGR Table 4 eq 1, 2 and 4
1839  !
1840  ! Coefficients used in the Temperature response of
1841  ! relative growth rate of total denitrifiers - Eq. 2 Table 4 of Li et al., 2000
1842  REAL(r_std), SAVE ::   ft_denit_0 = 2.     !! (-)
1843!$OMP THREADPRIVATE(ft_denit_0)
1844  REAL(r_std), SAVE ::   ft_denit_1 = 22.5   !! (-)
1845!$OMP THREADPRIVATE(ft_denit_1)
1846  REAL(r_std), SAVE ::   ft_denit_2 = 10.    !! (-)
1847!$OMP THREADPRIVATE(ft_denit_2)
1848  !
1849  ! Coefficients used in the pH response of
1850  ! relative growth rate of total denitrifiers - Eq. 2 Table 4 of Li et al., 2000
1851  REAL(r_std), SAVE ::   fph_no3_0  = 4.25    !! (-)
1852!$OMP THREADPRIVATE(fph_no3_0)
1853  REAL(r_std), SAVE ::   fph_no3_1  = 0.5     !! (-)
1854!$OMP THREADPRIVATE(fph_no3_1)
1855  REAL(r_std), SAVE ::   fph_no_0  = 5.25     !! (-)
1856!$OMP THREADPRIVATE(fph_no_0)
1857  REAL(r_std), SAVE ::   fph_no_1  = 1.       !! (-)
1858!$OMP THREADPRIVATE(fph_no_1)
1859  REAL(r_std), SAVE ::   fph_n2o_0  = 6.25    !! (-)
1860!$OMP THREADPRIVATE(fph_n2o_0)
1861  REAL(r_std), SAVE ::   fph_n2o_1  = 1.5     !! (-)
1862!$OMP THREADPRIVATE(fph_n2o_1)
1863
1864  REAL(r_std), SAVE ::   Kn = 0.083           !! Half Saturation of N oxydes (kgN/m3)
1865                                              !! Table 4 of Li et al., 2000
1866!$OMP THREADPRIVATE(Kn)
1867
1868  REAL(r_std), SAVE ::   cte_bact = 0.00015
1869!$OMP THREADPRIVATE(cte_bact)
1870
1871  ! Maximum Relative growth rate of Nox denitrifiers
1872  ! Eq.1 Table 4 Li et al., 2000
1873  REAL(r_std), SAVE ::   mu_no3_max = 0.67   !! (hour-1)
1874!$OMP THREADPRIVATE(mu_no3_max)
1875  REAL(r_std), SAVE ::   mu_no_max  = 0.67   !! (hour-1)
1876!$OMP THREADPRIVATE(mu_no_max)
1877  REAL(r_std), SAVE ::   mu_n2o_max = 0.67   !! (hour-1)
1878!$OMP THREADPRIVATE(mu_n2o_max)
1879
1880  ! Maximum growth yield of NOx denitrifiers on N oxydes
1881  ! Table 4 Li et al., 2000
1882  REAL(r_std), SAVE ::   Y_no3 = 0.401 !! (kgC / kgN)
1883!$OMP THREADPRIVATE(Y_no3)
1884  REAL(r_std), SAVE ::   Y_no  = 0.428 !! (kgC / kgN)
1885!$OMP THREADPRIVATE(Y_no)
1886  REAL(r_std), SAVE ::   Y_n2o = 0.151 !! (kgC / kgN)
1887!$OMP THREADPRIVATE(Y_n2o)
1888
1889  ! Maintenance coefficient on N oxyde
1890  ! Table 4 Li et al., 2000
1891  REAL(r_std), SAVE ::   M_no3 = 0.09   !! (kgN / kgC / hour)
1892!$OMP THREADPRIVATE(M_no3)
1893  REAL(r_std), SAVE ::   M_no  = 0.035  !! (kgN / kgC / hour)
1894!$OMP THREADPRIVATE(M_no)
1895  REAL(r_std), SAVE ::   M_n2o = 0.079  !! (kgN / kgC / hour)
1896!$OMP THREADPRIVATE(M_n2o)
1897
1898       
1899  REAL(r_std), SAVE ::   Maint_c = 0.0076    !! Maintenance coefficient of carbon (kgC/kgC/h)
1900                                        !! Table 4 Li et al., 2000
1901!$OMP THREADPRIVATE(Maint_c)
1902  REAL(r_std), SAVE ::   Yc = 0.503     !! Maximum growth yield on soluble carbon (kgC/kgC)
1903                                        !! Table 4 Li et al., 2000
1904!$OMP THREADPRIVATE(Yc)
1905
1906  !! Coefficients used in the eq. defining the response of N-emission to clay fraction (-)
1907  !! from  Table 4, Li et al. 2000
1908  REAL(r_std), SAVE ::   F_clay_0 = 0.13   
1909!$OMP THREADPRIVATE(F_clay_0)
1910  REAL(r_std), SAVE ::   F_clay_1 = -0.079
1911!$OMP THREADPRIVATE(F_clay_1)
1912
1913
1914  REAL(r_std), SAVE ::   ratio_nh4_fert = 0.5  !! Proportion of ammonium in the fertilizers (ammo-nitrate)
1915                                           
1916!$OMP THREADPRIVATE(ratio_nh4_fert)
1917
1918  REAL(r_std), SAVE ::   cn_ratio_manure = 13.7  !! C:N ratio of organic fertilizer (average over table 3-1-1 from Fuchs et al. 2014)
1919 
1920!$OMP THREADPRIVATE(cn_ratio_manure)
1921
1922  ! 2. Arrays
1923  REAL(r_std), SAVE, DIMENSION(2)  :: K_N_min = (/ 30., 30. /)           !! [NH4+] (resp. [NO3-]) for which the Nuptake
1924                                                                         !! equals vmax/2.   (umol per litter)
1925                                                                         !! from Kronzucker, 1995
1926!$OMP THREADPRIVATE(K_N_min)
1927
1928  REAL(r_std), SAVE, DIMENSION(2)  :: low_K_N_min = (/ 0.0002, 0.0002 /) !! Rate of N uptake not associated with
1929                                                                         !! Michaelis- Menten Kinetics for Ammonium
1930                                                                         !! (ind.1) and Nitrate (ind.2)
1931                                                                         !! from Kronzucker, 1995 ((umol)-1)
1932!$OMP THREADPRIVATE(low_K_N_min)
1933
1934  REAL(r_std), SAVE      :: emm_fac = 0.2         !! Factor for reducing NH3 emission 
1935!$OMP THREADPRIVATE(emm_fac)
1936  REAL(r_std), SAVE      :: fact_kn_no = 0.012    !! Factor for adusting kn constant for NOx production
1937!$OMP THREADPRIVATE(fact_kn_no)
1938  REAL(r_std), SAVE      :: fact_kn_n2o = 0.04    !! Factor for adusting kn constant for N2O production
1939!$OMP THREADPRIVATE(fact_kn_n2o)
1940  REAL(r_std), SAVE      :: kfwdenit = -5.        !! Factor for adjusting sensitivity of denitrification to water content                     
1941!$OMP THREADPRIVATE(kfwdenit) 
1942 REAL(r_std), SAVE      :: fwdenitfc = 0.05       !! Value at field capacity of the sensitivity function of denitrification to water content                     
1943!$OMP THREADPRIVATE(fwdenitfc)         
1944  REAL(r_std), SAVE      :: fracn_drainage = 1.0  !! Fraction of NH3/NO3 loss by drainage
1945!$OMP THREADPRIVATE(fracn_drainage)
1946  REAL(r_std), SAVE      :: fracn_runoff = 1.0    !! Fraction of NH3/NO3 loss by runoff
1947!$OMP THREADPRIVATE(fracn_runoff)
1948
1949
1950  !! Other N-related parameters
1951  REAL(r_std), SAVE      :: Dmax = 0.25           !! Maximal elasticity of foliage N concentrations (Zaehle et al 2010, SI2, Table 1)
1952!$OMP THREADPRIVATE(Dmax)
1953
1954  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
1955                                                   !! carbohydrate reserve may be used for
1956                                                   !! trees (days)
1957!$OMP THREADPRIVATE(reserve_time_tree)
1958 
1959  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
1960                                                   !! carbohydrate reserve may be used for
1961                                                   !! grasses (days)
1962!$OMP THREADPRIVATE(reserve_time_grass)
1963  REAL(r_std), SAVE :: p_n_uptake = 0.6            !! The minimum correction factor for nitrogen uptake in case of
1964                                                   !! enough nitrogen in the reserve
1965!$OMP THREADPRIVATE(p_n_uptake)
1966
1967  !
1968  ! stomate_windthrow.f90
1969  !
1970
1971  ! 0. Constants
1972
1973  REAL(r_std), SAVE :: one_third = 0.333              !! This value is used on multiple occasions in
1974                                                      !! stomate_windthrow.f90
1975                                                      !!(unitless)
1976!$OMP THREADPRIVATE(one_third)
1977  REAL(r_std), SAVE :: dbh_height_standard = 1.3      !! The height where the diameter of the tree stem is
1978                                                      !! measured by default.
1979                                                      !@tex $(m)$ @endtex
1980!$OMP THREADPRIVATE(dbh_height_standard)
1981  REAL(r_std), SAVE :: dbh_height_stump = zero        !! The height where the diameter of the tree stem is
1982                                                      !! measured if the middle of the canopy is below 1.3 m.
1983                                                      !! @tex $(m)$ @endtex
1984!$OMP THREADPRIVATE(dbh_height_stump)
1985  REAL(r_std), SAVE :: snow_density = 150.0           !! Density of snow (kg/m3). It should be considered
1986                                                      !! to calculate this value for simulations during
1987                                                      !  future development.
1988!$OMP THREADPRIVATE(snow_density)
1989  REAL(r_std), SAVE :: clear_cut_max = 20000.0        !! The maximum contiguous area allowed to be clearfelled
1990                                                      !! @tex $(m^{2})$ @endtex
1991!$OMP THREADPRIVATE(clear_cut_max)
1992  REAL(r_std), SAVE :: c_surface = 0.003              !! Surface Drag Coefficient (Raupach 1994) (unitless)
1993!$OMP THREADPRIVATE(c_surface)
1994  REAL(r_std), SAVE :: c_drag = 0.3                   !! Element Drag Coefficient (Raupach 1994) (unitless)
1995!$OMP THREADPRIVATE(c_drag)
1996  REAL(r_std), SAVE :: c_displacement = 7.5           !! Used by Raupach to calculate the zero-plane displacement (Raupach 1994) (unitless)
1997!$OMP THREADPRIVATE(c_displacement)
1998  REAL(r_std), SAVE :: c_roughness = 2.0              !! Used by Raupach to calculate the surface roughness length (Raupach 1994) (unitless)
1999!$OMP THREADPRIVATE(c_roughness)
2000  REAL(r_std), SAVE :: air_density = 1.2226           !! The value of air density (kg*m-3). If needed, this can be derived dynamically from
2001                                                      !! other modules of ORCHIDEE, but considering the range of values it can hold, it is probably
2002                                                      !! not worth additional calculations for being used in WINDTHROW.
2003!$OMP THREADPRIVATE(air_density)
2004  REAL(r_std), SAVE :: f_crown_weight = 1.136         !! This factor represents the weight of the overhanging crown when the tree stem is bent.
2005                                                      !! The origin of 1.136 is described in the supplementary material of Hale et al. 2015.
2006!$OMP THREADPRIVATE(f_crown_weight)
2007
2008  INTEGER(i_std), SAVE :: wind_years = 5              !! The years used to calculate the total harvest area with in wind_years and the default is 5 years.
2009!$OMP THREADPRIVATE(wind_years)
2010  REAL(r_std), SAVE :: gap_threshold = 0.3            !! The threshold for the basal area loss to be considered to create the gap with edges
2011!$OMP THREADPRIVATE(gap_threshold)
2012  INTEGER(i_std), SAVE :: legacy_years = 3            !! The years used to calculate the total damage from disturbances with in legacy_years and the default is 3 years.
2013!$OMP THREADPRIVATE(legacy_years)
2014  INTEGER(i_std), SAVE :: beetle_legacy = 6           !! The years used to calculate wood leftover.
2015!$OMP THREADPRIVATE(beetle_legacy)
2016
2017! 1. Scalar
2018  REAL(r_std), SAVE :: wind_speed_storm_thr=20.0          !! the wind speed threshold above which is_storm flag is set to TRUE
2019!$OMP THREADPRIVATE(wind_speed_storm_thr)
2020
2021  REAL(r_std), SAVE :: daily_max_tune=0.1155          !! This is a linear tunning factor to adjust the calculated daily maximum wind speed from forcing dataset.
2022!$OMP THREADPRIVATE(daily_max_tune)
2023
2024
2025  INTEGER(i_std), SAVE :: nb_days_storm=5              !! the number of days at which the max wind speed is less than wind_speed_storm_thr
2026!$OMP THREADPRIVATE(nb_days_storm)
2027
2028
2029  INTEGER(i_std), SAVE :: nb_years_bgi=3              !! the number of years needed to average the bark beetle generation index
2030!$OMP THREADPRIVATE(nb_years_bgi)
2031  ! stomate_season.f90
2032  !
2033
2034  ! 1. Scalar
2035
2036  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
2037!$OMP THREADPRIVATE(gppfrac_dormance)
2038  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
2039!$OMP THREADPRIVATE(tau_climatology)
2040  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
2041!$OMP THREADPRIVATE(hvc1)
2042  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
2043!$OMP THREADPRIVATE(hvc2)
2044  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
2045!$OMP THREADPRIVATE(leaf_frac_hvc)
2046  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
2047!$OMP THREADPRIVATE(tlong_ref_max)
2048  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
2049!$OMP THREADPRIVATE(tlong_ref_min)
2050
2051  ! 3. Coefficients of equations
2052
2053  REAL(r_std), SAVE :: ncd_max_year = 3.
2054!$OMP THREADPRIVATE(ncd_max_year)
2055  REAL(r_std), SAVE :: gdd_threshold = 5.
2056!$OMP THREADPRIVATE(gdd_threshold)
2057  REAL(r_std), SAVE :: green_age_ever = 2.
2058!$OMP THREADPRIVATE(green_age_ever)
2059  REAL(r_std), SAVE :: green_age_dec = 0.5
2060!$OMP THREADPRIVATE(green_age_dec)
2061 
2062  REAL(r_std), SAVE :: ngd_min_dormance = 55.
2063!$OMP THREADPRIVATE(ngd_min_dormance)
2064
2065  !
2066  ! sapiens_forestry.f90
2067  !
2068
2069  INTEGER(i_std), SAVE      :: ncirc = 1                  !! Number of circumference classes used to calculate C allocation. This creates within stand heterogeneity (i.e., structured canopies).
2070!$OMP THREADPRIVATE(ncirc)
2071  INTEGER(i_std), SAVE      :: nagec = 1                  !! Number of age classes. This creates landscape-level heterogeneity (i.e. the effects of deforestation and harvesting are longer seen in the energy budget)
2072!$OMP THREADPRIVATE(nagec)
2073  REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:) :: age_class_bound !! Boundaries of the age classes defined as threshold diameters (m)
2074!$OMP THREADPRIVATE(age_class_bound)
2075  LOGICAL, SAVE             :: forced_clear_cut = .FALSE. !! flag at wich the stand is force to clear-cut
2076!$OMP THREADPRIVATE(forced_clear_cut)
2077
2078  LOGICAL, SAVE             :: ld_fake_height=.FALSE.     !! a flag to turn on the statements
2079!$OMP THREADPRIVATE(ld_fake_height)
2080  INTEGER(i_std), SAVE      :: test_pft = 2               !! Number of PFT for which detailed output
2081!$OMP THREADPRIVATE(test_pft)
2082  INTEGER(i_std), SAVE      :: test_grid = 1              !! Number of the grid square for which detailed output
2083                                                          !! If the default value is not one, this can cause crashes in debugging for small regions.
2084!$OMP THREADPRIVATE(test_grid)
2085
2086 !+++++++++ DEBUG +++++++
2087  LOGICAL, SAVE             :: lnvgrasspatch=.FALSE.    !! a patch for grasslands
2088!$OMP THREADPRIVATE(lnvgrasspatch)
2089!++++++++++++++++++++++++
2090 
2091  LOGICAL,PARAMETER                       :: jr_nextstep = .FALSE.!! set this to TRUE to activate the
2092 
2093  INTEGER(i_std), SAVE      :: ndia_harvest             !! The number of diameter classes used for
2094                                                        !! the wood harvest pools.
2095!$OMP THREADPRIVATE(ndia_harvest)
2096
2097  REAL(r_std), SAVE         :: max_harvest_dia = 0.7    !! The largest diameter for the harvest pools to
2098                                                        !! keep track of harvested wood from forests.
2099!$OMP THREADPRIVATE(max_harvest_dia)
2100
2101  INTEGER(i_std), SAVE      :: n_pai = 1000             !! The number of years used for the cumulative
2102                                                        !! averages of the periodic annual increment. By
2103                                                        !! setting this value to 1000, this functionality is not used.
2104                                                        !! This way of management is extremly rational. Owners are
2105                                                        !! to follow yield tables than to monitor stand growth every 5 years.                     
2106!$OMP THREADPRIVATE(n_pai)
2107
2108  INTEGER(i_std), SAVE      :: ntrees_profit            !! The number of trees over which the average
2109                                                        !! height is calculated to determine if the
2110                                                        !! stand will be profitable to thin.
2111!$OMP THREADPRIVATE(ntrees_profit)
2112
2113INTEGER, SAVE             :: species_change_force      !! This is the PFT number which is replanted after a
2114                                                       !! clearcut, if such a thing is being done.
2115                                                       !! To be used with lchange_species = .TRUE. and
2116                                                       !! lread_species_change_map = .FALSE. The
2117                                                       !! forced value is mainly useful for debugging
2118!$OMP THREADPRIVATE(species_change_force)
2119
2120INTEGER, SAVE             :: fm_change_force           !! This is the FM strategy which is used for the replant
2121                                                       !! after a clearcut, if such a thing is being done.
2122                                                       !! To be used with lchange_species = .TRUE. and
2123                                                       !! lread_desired_fm_map = .FALSE. The forced value is
2124                                                       !! mainly useful for debugging
2125!$OMP THREADPRIVATE(fm_change_force)
2126
2127 REAL(r_std), SAVE        :: min_water_stress = 0.1    !! Minimal value for wstress_fac (unitless, 0-1)
2128!$OMP THREADPRIVATE(min_water_stress)
2129
2130REAL(r_std), SAVE         :: max_delta_KF = 0.1        !! Maximum change in KF from one time step to another (m)
2131                                                       !! This is a bit arbitrary.
2132!$OMP THREADPRIVATE(max_delta_KF)
2133
2134REAL(r_std), SAVE         :: maint_from_gpp = 0.8      !! Some carbon needs to remain to support the growth, hence,
2135                                                       !! respiration will be limited. In this case resp_maint
2136                                                       !! (gC m-2 dt-1) should not be more than 80% (::maint_from_gpp)
2137                                                       !! of the GPP (gC m-2 s-1)
2138!$OMP THREADPRIVATE(maint_from_gpp)
2139 
2140  REAL(r_std), PARAMETER :: m2_to_ha = 10000.          !! Conversion from m2 to hectares
2141  REAL(r_std), PARAMETER :: ha_to_m2 = 0.0001          !! Conversion from hectares (forestry) to m2 (rest of the code)
2142  REAL(r_std), PARAMETER :: m_to_cm = 100.             !! Conversion from m to cm
2143  REAL(r_std), PARAMETER :: cm_to_m = 0.01             !! Conversion from cm to m
2144  REAL(r_std), PARAMETER :: peta_to_unit = 1.0E15      !! Convert Peta to unit
2145  REAL(r_std), PARAMETER :: tera_to_unit = 1.0E12      !! Convert Tera to unit
2146  REAL(r_std), PARAMETER :: giga_to_unit = 1.0E09      !! Convert Giga to unit
2147  REAL(r_std), PARAMETER :: mega_to_unit = 1.0E06      !! Convert Mega to unit
2148  REAL(r_std), PARAMETER :: kilo_to_unit = 1.0E03      !! Convert Kilo to unit
2149  REAL(r_std), PARAMETER :: centi_to_unit = 1.0E02     !! Convert centi to unit
2150  REAL(r_std), PARAMETER :: milli_to_unit = 1.0E-03    !! Convert milli to unit
2151  REAL(r_std), PARAMETER :: carbon_to_kilo = 2.0E-03   !! Convert g carbon to kilo biomass
2152
2153  !
2154  ! Debugging
2155  !
2156  INTEGER(i_std), SAVE :: err_act = 1                  !! There are three levels of error checking
2157                                                       !! see constantes.f90 for more details
2158!$OMP THREADPRIVATE(err_act)
2159  INTEGER(i_std), SAVE :: plev = 0                     !! print level of the subroutine ipslerr_p
2160                                                       !! (1:note, 2: warn and 3:stop)
2161!$OMP THREADPRIVATE(plev)
2162  REAL(r_std), SAVE    :: sync_threshold = 0.0001      !! The threshold above which a warning is generated when the
2163!$OMP THREADPRIVATE(sync_threshold)
2164
2165  ! Soil carbon related variables
2166  LOGICAL, SAVE                   :: soilc_isspinup = .FALSE.            !! Activate soil carbon spinup
2167!$OMP THREADPRIVATE(soilc_isspinup)
2168  REAL(r_std), PARAMETER          :: O2_init_conc = 298.3                !! gO2/m**3 mean for Cherskii
2169  REAL(r_std), PARAMETER          :: CH4_init_conc = 0.001267            !! gCH4/m**3 mean for Cherskii
2170  REAL(r_std), PARAMETER          :: z_root_max = 0.5                    !! Depth at which litter carbon input decays e-fold (root depth); 0.5 for compar w/WH
2171  REAL(r_std), PARAMETER          :: diffO2_air = 1.596E-5               !! oxygen diffusivity in air (m**2/s)
2172  REAL(r_std), PARAMETER          :: diffO2_w = 1.596E-9                 !! oxygen diffusivity in water (m**2/s)
2173  REAL(r_std), PARAMETER          :: O2_surf = 0.209                     !! oxygen concentration in surface air (molar fraction)
2174  REAL(r_std), PARAMETER          :: diffCH4_air = 1.702E-5              !! methane diffusivity in air (m**2/s)
2175  REAL(r_std), PARAMETER          :: diffCH4_w = 2.0E-9                  !! methane diffusivity in water (m**2/s)
2176  REAL(r_std), PARAMETER          :: CH4_surf = 1700.E-9                 !! methane concentration in surface air (molar fraction)
2177  REAL(r_std), SAVE               :: tetasat =  .5                       !! volumetric water content at saturation (porosity)
2178!$OMP THREADPRIVATE(tetasat)
2179  REAL(r_std), SAVE               :: tetamoss =  0.92                    !! porosity of moss
2180!$OMP THREADPRIVATE(tetamoss)
2181  REAL(r_std), SAVE               :: rho_moss                            !! density of moss
2182!$OMP THREADPRIVATE(rho_moss)
2183  REAL(r_std), PARAMETER          :: zmoss = 0.2                         !! thickness of moss layer (in permafrost regions,m) 0. ! 0.001 DKtest for compar w/WH
2184  REAL(r_std), PARAMETER          :: h_snowmoss = 0.2                    !! snow height above which we consider the moss layer to be to compressed to be effective (m)
2185  REAL(r_std), PARAMETER          :: BunsenO2 = 0.038                    !! Bunsen coefficient for O2 (10C, 1bar)
2186  REAL(r_std), PARAMETER          :: BunsenCH4 = 0.043                   !! Bunsen coefficient for CH4 (10C, Wiesenburg et Guinasso, Jr., 1979)
2187  REAL(r_std), PARAMETER          :: ebuthr = 0.9                        !! Soil humidity threshold for ebullition
2188  REAL(r_std), PARAMETER          :: wCH4 = 16.                          !! molar weight of CH4 (g/mol)
2189  REAL(r_std), PARAMETER          :: wO2 = 32.                           !! molar weight of O2 (g/mol)
2190  REAL(r_std), PARAMETER          :: wC = 12.                            !! molar weight of C (g/mol)
2191  REAL(r_std), PARAMETER          :: avm = .01                           !! minimum air volume (m**3 air/m**3 soil)
2192  REAL(r_std), PARAMETER          :: hmin_tcalc = .001                   !! minimum total snow layer thickness below which we ignore diffusion across the snow layer
2193
2194 
2195
2196END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.