source: branches/publications/ORCHIDEE-MUSLE-r6129/src_parameters/constantes_var.f90 @ 7346

Last change on this file since 7346 was 6128, checked in by haicheng.zhang, 5 years ago

New: ORCHIDEE_MUSLE modified on 20190722 by Haicheng Zhang

  • Property svn:keywords set to Date Revision
File size: 83.9 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_var
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF        constantes_var module contains most constantes like pi, Earth radius, etc...
10!!              and all externalized parameters except pft-dependent constants.
11!!
12!!\n DESCRIPTION: This module contains most constantes and the externalized parameters of ORCHIDEE which
13!!                are not pft-dependent.\n
14!!                In this module, you can set the flag diag_qsat in order to detect the pixel where the
15!!                temperature is out of range (look qsatcalc and dev_qsatcalc in qsat_moisture.f90).\n
16!!                The Earth radius is approximated by the Equatorial radius.The Earth's equatorial radius a,
17!!                or semi-major axis, is the distance from its center to the equator and equals 6,378.1370 km.
18!!                The equatorial radius is often used to compare Earth with other planets.\n
19!!                The meridional mean is well approximated by the semicubic mean of the two axe yielding
20!!                6367.4491 km or less accurately by the quadratic mean of the two axes about 6,367.454 km
21!!                or even just the mean of the two axes about 6,367.445 km.\n
22!!                This module is already USE in module constantes. Therefor no need to USE it seperatly except
23!!                if the subroutines in module constantes are not needed.\n
24!!               
25!! RECENT CHANGE(S):
26!!
27!! REFERENCE(S) :
28!! - Louis, Jean-Francois (1979), A parametric model of vertical eddy fluxes in the atmosphere.
29!! Boundary Layer Meteorology, 187-202.\n
30!!
31!! SVN          :
32!! $HeadURL: $
33!! $Date$
34!! $Revision$
35!! \n
36!_ ================================================================================================================================
37
38MODULE constantes_var
39
40  USE defprec
41  IMPLICIT NONE
42!-
43
44                         !-----------------------!
45                         !  ORCHIDEE CONSTANTS   !
46                         !-----------------------!
47
48  !
49  ! FLAGS
50  !
51  LOGICAL :: river_routing      !! activate river routing
52  LOGICAL :: erosion_module      !! activate river routing
53  LOGICAL :: erosion_cdiffusion   !! activate river routing
54!$OMP THREADPRIVATE(river_routing)
55  LOGICAL :: hydrol_cwrr        !! activate 11 layers hydrolgy model
56!$OMP THREADPRIVATE(hydrol_cwrr)
57  LOGICAL :: do_floodplains     !! activate flood plains
58!$OMP THREADPRIVATE(do_floodplains)
59  LOGICAL :: do_irrigation      !! activate computation of irrigation flux
60!$OMP THREADPRIVATE(do_irrigation)
61  LOGICAL :: ok_sechiba         !! activate physic of the model
62!$OMP THREADPRIVATE(ok_sechiba)
63  LOGICAL :: ok_co2             !! activate photosynthesis
64!$OMP THREADPRIVATE(ok_co2)
65  LOGICAL :: ok_stomate         !! activate carbon cycle
66!$OMP THREADPRIVATE(ok_stomate)
67  LOGICAL :: ok_dgvm            !! activate dynamic vegetation
68!$OMP THREADPRIVATE(ok_dgvm)
69  LOGICAL :: ok_pheno           !! activate the calculation of lai using stomate rather than a prescription
70!$OMP THREADPRIVATE(ok_pheno)
71  LOGICAL :: ok_bvoc            !! activate biogenic volatile organic coumpounds
72!$OMP THREADPRIVATE(ok_bvoc)
73  LOGICAL :: ok_leafage         !! activate leafage
74!$OMP THREADPRIVATE(ok_leafage)
75  LOGICAL :: ok_radcanopy       !! use canopy radiative transfer model
76!$OMP THREADPRIVATE(ok_radcanopy)
77  LOGICAL :: ok_multilayer      !! use canopy radiative transfer model with multi-layers
78!$OMP THREADPRIVATE(ok_multilayer)
79  LOGICAL :: ok_pulse_NOx       !! calculate NOx emissions with pulse
80!$OMP THREADPRIVATE(ok_pulse_NOx)
81  LOGICAL :: ok_bbgfertil_NOx   !! calculate NOx emissions with bbg fertilizing effect
82!$OMP THREADPRIVATE(ok_bbgfertil_NOx)
83  LOGICAL :: ok_cropsfertil_NOx !! calculate NOx emissions with fertilizers use
84!$OMP THREADPRIVATE(ok_cropsfertil_NOx)
85
86  LOGICAL :: ok_co2bvoc_poss    !! CO2 inhibition on isoprene activated following Possell et al. (2005) model
87!$OMP THREADPRIVATE(ok_co2bvoc_poss)
88  LOGICAL :: ok_co2bvoc_wilk    !! CO2 inhibition on isoprene activated following Wilkinson et al. (2006) model
89!$OMP THREADPRIVATE(ok_co2bvoc_wilk)
90  LOGICAL :: ld_doc             !! activate the debug comments for the DOC module (true/false) 
91!$OMP THREADPRIVATE(ld_doc)
92  LOGICAL, SAVE :: OFF_LINE_MODE = .FALSE.  !! ORCHIDEE detects if it is coupled with a GCM or
93                                            !! just use with one driver in OFF-LINE. (true/false)
94!$OMP THREADPRIVATE(OFF_LINE_MODE) 
95  LOGICAL, SAVE :: impose_param = .TRUE.    !! Flag impos_param : read all the parameters in the run.def file
96!$OMP THREADPRIVATE(impose_param)
97  CHARACTER(LEN=80), SAVE     :: restname_in       = 'NONE'                 !! Input Restart files name for Sechiba component 
98!$OMP THREADPRIVATE(restname_in)
99  CHARACTER(LEN=80), SAVE     :: restname_out      = 'sechiba_rest_out.nc'  !! Output Restart files name for Sechiba component
100!$OMP THREADPRIVATE(restname_out)
101  CHARACTER(LEN=80), SAVE     :: stom_restname_in  = 'NONE'                 !! Input Restart files name for Stomate component
102!$OMP THREADPRIVATE(stom_restname_in)
103  CHARACTER(LEN=80), SAVE     :: stom_restname_out = 'stomate_rest_out.nc'  !! Output Restart files name for Stomate component
104!$OMP THREADPRIVATE(stom_restname_out)
105  INTEGER, SAVE :: printlev=1       !! Standard level for text output [0, 1, 2, 3]
106!$OMP THREADPRIVATE(printlev)
107
108  !
109  ! TIME
110  !
111  REAL(r_std), SAVE :: one_day  !! One day in seconds (s)
112!$OMP THREADPRIVATE(one_day)
113  REAL(r_std), SAVE :: one_year !! One year in days
114!$OMP THREADPRIVATE(one_year)
115  REAL(r_std), PARAMETER :: one_hour = 3600.0  !! One hour in seconds (s)
116  INTEGER(i_std), PARAMETER  :: spring_days_max = 40  !! Maximum number of days during which we watch for possible spring frost damage
117
118  ! TIME STEP
119  REAL(r_std)            :: dt_sechiba         !! Time step in sechiba
120!$OMP THREADPRIVATE(dt_sechiba)
121  REAL(r_std)            :: dt_stomate         !! Time step in stomate
122!$OMP THREADPRIVATE(dt_stomate)
123
124  !
125  ! SPECIAL VALUES
126  !
127  INTEGER(i_std), PARAMETER :: undef_int = 999999999     !! undef integer for integer arrays (unitless)
128  !-
129  REAL(r_std), SAVE :: val_exp = 999999.                 !! Specific value if no restart value  (unitless)
130!$OMP THREADPRIVATE(val_exp)
131  REAL(r_std), PARAMETER :: undef = -9999.               !! Special value for stomate (unitless)
132 
133  REAL(r_std), PARAMETER :: min_sechiba = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
134  REAL(r_std), PARAMETER :: undef_sechiba = 1.E+20_r_std !! The undef value used in SECHIBA (unitless)
135 
136  REAL(r_std), PARAMETER :: min_stomate = 1.E-8_r_std    !! Epsilon to detect a near zero floating point (unitless)
137  REAL(r_std), PARAMETER :: large_value = 1.E33_r_std    !! some large value (for stomate) (unitless)
138
139
140  !
141  !  DIMENSIONING AND INDICES PARAMETERS 
142  !
143  INTEGER(i_std), PARAMETER :: ibare_sechiba = 1 !! Index for bare soil in Sechiba (unitless)
144  INTEGER(i_std), PARAMETER :: ivis = 1          !! index for albedo in visible range (unitless)
145  INTEGER(i_std), PARAMETER :: inir = 2          !! index for albeod i near-infrared range (unitless)
146  INTEGER(i_std), PARAMETER :: nnobio = 1        !! Number of other surface types: land ice (lakes,cities, ...) (unitless)
147  INTEGER(i_std), PARAMETER :: iice = 1          !! Index for land ice (see nnobio) (unitless)
148  !-
149  !! Soil
150  INTEGER(i_std), PARAMETER :: classnb = 9       !! Levels of soil colour classification (unitless)
151  !-
152  INTEGER(i_std), PARAMETER :: nleafages = 4     !! leaf age discretisation ( 1 = no discretisation )(unitless)
153!  INTEGER(i_std), PARAMETER :: nsubgrid = 1238728  !! maximum number of subgrids for each orchidee grid
154  !-
155  !! litter fractions: indices (unitless)
156  INTEGER(i_std), PARAMETER :: ileaf = 1         !! Index for leaf compartment (unitless)
157  INTEGER(i_std), PARAMETER :: isapabove = 2     !! Index for sapwood above compartment (unitless)
158  INTEGER(i_std), PARAMETER :: isapbelow = 3     !! Index for sapwood below compartment (unitless)
159  INTEGER(i_std), PARAMETER :: iheartabove = 4   !! Index for heartwood above compartment (unitless)
160  INTEGER(i_std), PARAMETER :: iheartbelow = 5   !! Index for heartwood below compartment (unitless)
161  INTEGER(i_std), PARAMETER :: iroot = 6         !! Index for roots compartment (unitless)
162  INTEGER(i_std), PARAMETER :: ifruit = 7        !! Index for fruits compartment (unitless)
163  INTEGER(i_std), PARAMETER :: icarbres = 8      !! Index for reserve compartment (unitless)
164  INTEGER(i_std), PARAMETER :: nparts = 8        !! Number of biomass compartments (unitless)
165  !-
166  !! indices for assimilation parameters
167  INTEGER(i_std), PARAMETER :: ivcmax = 1        !! Index for vcmax (assimilation parameters) (unitless)
168  INTEGER(i_std), PARAMETER :: npco2 = 1         !! Number of assimilation parameters (unitless)
169  !-
170  !! trees and litter: indices for the parts of heart-
171  !! and sapwood above and below the ground
172  INTEGER(i_std), PARAMETER :: iabove = 1       !! Index for above part (unitless)
173  INTEGER(i_std), PARAMETER :: ibelow = 2       !! Index for below part (unitless)
174  INTEGER(i_std), PARAMETER :: nlevs = 2        !! Number of levels for trees and litter (unitless)
175  !-
176  !! litter: indices for metabolic and structural part
177  INTEGER(i_std), PARAMETER :: imetabolic = 1   !! Index for metabolic litter (unitless)
178  INTEGER(i_std), PARAMETER :: istructural = 2  !! Index for structural litter (unitless)
179  INTEGER(i_std), PARAMETER :: nlitt = 2        !! Number of levels for litter compartments (unitless)
180  !-
181  !! carbon pools: indices
182  INTEGER(i_std), PARAMETER :: iactive = 1      !! Index for active carbon pool (unitless)
183  INTEGER(i_std), PARAMETER :: islow = 2        !! Index for slow carbon pool (unitless)
184  INTEGER(i_std), PARAMETER :: ipassive = 3     !! Index for passive carbon pool (unitless)
185  INTEGER(i_std), PARAMETER :: ncarb = 3        !! Number of soil carbon pools (unitless)
186  !-
187  !! DOC pools: indices
188  INTEGER(i_std), PARAMETER :: ifree = 1        !! Index for free soil dissolved organic carbon (unitless)
189  INTEGER(i_std), PARAMETER :: iadsorbed = 2    !! Index for adsorbed soil dissolved organic carbon (unitless)
190  INTEGER(i_std), PARAMETER :: ndoc = 2         !! Number of soil dissolved organic carbon pools (unitless)
191  !-
192  !! DOC exportation pathways indices
193  INTEGER(i_std), PARAMETER :: irunoff = 1      !! Index for runoff (unitless)
194  INTEGER(i_std), PARAMETER :: iflooded = 2     !! Index for flooding (unitless)
195  INTEGER(i_std), PARAMETER :: idrainage = 3    !! Index for drainage (unitless)
196  INTEGER(i_std), PARAMETER :: nexp = 3         !! Number of DOC export pathways (unitless)
197  !-
198  !! carbon pools: indices
199  INTEGER(i_std), PARAMETER :: imetabo = 1      !! Index for aboveground metabolic litter pool(unitless)
200  INTEGER(i_std), PARAMETER :: istrabo = 2      !! Index for aboveground structural litter pool(unitless)
201  INTEGER(i_std), PARAMETER :: imetbel = 3      !! Index for belowground metabolic litter pool(unitless)
202  INTEGER(i_std), PARAMETER :: istrbel = 4      !! Index for belowground structural litter  pool(unitless)
203  INTEGER(i_std), PARAMETER :: iact = 5         !! Index for active carbon pool (unitless)
204  INTEGER(i_std), PARAMETER :: islo = 6         !! Index for slow carbon pool (unitless)
205  INTEGER(i_std), PARAMETER :: ipas = 7         !! Index for passive carbon pool (unitless)
206  INTEGER(i_std), PARAMETER :: npool = 7        !! Number of soil carbon pools (unitless)
207  !
208  !! carbon pools: indices
209  INTEGER(i_std), PARAMETER :: ico2 = 1         !! Index for CO2 (unitless)
210  INTEGER(i_std), PARAMETER :: io2 = 2          !! Index for O2 (unitless)
211  INTEGER(i_std), PARAMETER :: ich4 = 3         !! Index for CH4 (unitless)
212  INTEGER(i_std), PARAMETER :: ngaz = 3         !! Number of gaz in soil (unitless)
213  !-
214  !! For isotopes and nitrogen
215  INTEGER(i_std), PARAMETER :: nelements = 1    !! Number of isotopes considered
216  INTEGER(i_std), PARAMETER :: icarbon = 1      !! Index for carbon
217  !
218  !! Indices for check mass balance
219  INTEGER(i_std), PARAMETER :: nmbcomp=5
220  INTEGER(i_std), PARAMETER :: iatm2land=1
221  INTEGER(i_std), PARAMETER :: iland2atm=2
222  INTEGER(i_std), PARAMETER :: ilat2out=3
223  INTEGER(i_std), PARAMETER :: ilat2in=4
224  INTEGER(i_std), PARAMETER :: ipoolchange=5
225  !
226  !! Indices used for analytical spin-up
227  INTEGER(i_std), PARAMETER :: nbpools = 211                     !! Total number of carbon pools (unitless)
228  INTEGER(i_std), PARAMETER :: istructural_above = 1            !! Index for structural litter above (unitless)
229  INTEGER(i_std), PARAMETER :: istructural_below_z1 = 2         !! Index for structural litter below at 1st layer (unitless)
230  INTEGER(i_std), PARAMETER :: istructural_below_z2 = 3         !! Index for structural litter below at 2nd layer (unitless)
231  INTEGER(i_std), PARAMETER :: istructural_below_z3 = 4         !! Index for structural litter below at 3rd layer (unitless)
232  INTEGER(i_std), PARAMETER :: istructural_below_z4 = 5         !! Index for structural litter below at 4th layer (unitless)
233  INTEGER(i_std), PARAMETER :: istructural_below_z5 = 6         !! Index for structural litter below at 5th layer (unitless)
234  INTEGER(i_std), PARAMETER :: istructural_below_z6 = 7         !! Index for structural litter below at 6th layer (unitless)
235  INTEGER(i_std), PARAMETER :: istructural_below_z7 = 8         !! Index for structural litter below at 7th layer (unitless)
236  INTEGER(i_std), PARAMETER :: istructural_below_z8 = 9         !! Index for structural litter below at 8th layer (unitless)
237  INTEGER(i_std), PARAMETER :: istructural_below_z9 = 10        !! Index for structural litter below at 9th layer (unitless)
238  INTEGER(i_std), PARAMETER :: istructural_below_z10 = 11       !! Index for structural litter below at 10th layer (unitless)
239  INTEGER(i_std), PARAMETER :: istructural_below_z11 = 12       !! Index for structural litter below at 11th layer (unitless)
240  INTEGER(i_std), PARAMETER :: imetabolic_above = 13            !! Index for metabolic litter above (unitless)
241  INTEGER(i_std), PARAMETER :: imetabolic_below_z1 = 14         !! Index for metabolic litter below at 1st layer (unitless)
242  INTEGER(i_std), PARAMETER :: imetabolic_below_z2 = 15         !! Index for metabolic litter below at 2nd layer (unitless)
243  INTEGER(i_std), PARAMETER :: imetabolic_below_z3 = 16         !! Index for metabolic litter below at 3rd layer (unitless)
244  INTEGER(i_std), PARAMETER :: imetabolic_below_z4 = 17         !! Index for metabolic litter below at 4th layer (unitless)
245  INTEGER(i_std), PARAMETER :: imetabolic_below_z5 = 18         !! Index for metabolic litter below at 5th layer (unitless)
246  INTEGER(i_std), PARAMETER :: imetabolic_below_z6 = 19         !! Index for metabolic litter below at 6th layer (unitless)
247  INTEGER(i_std), PARAMETER :: imetabolic_below_z7 = 20         !! Index for metabolic litter below at 7th layer (unitless)
248  INTEGER(i_std), PARAMETER :: imetabolic_below_z8 = 21         !! Index for metabolic litter below at 8th layer (unitless)
249  INTEGER(i_std), PARAMETER :: imetabolic_below_z9 = 22         !! Index for metabolic litter below at 9th layer (unitless)
250  INTEGER(i_std), PARAMETER :: imetabolic_below_z10 = 23        !! Index for metabolic litter below at 10th layer (unitless)
251  INTEGER(i_std), PARAMETER :: imetabolic_below_z11 = 24        !! Index for metabolic litter below at 11th layer (unitless)
252  INTEGER(i_std), PARAMETER :: iactive_pool_z1 = 25             !! Index for active carbon pool at 1st layer (unitless)
253  INTEGER(i_std), PARAMETER :: iactive_pool_z2 = 26             !! Index for active carbon pool at 2nd layer (unitless)
254  INTEGER(i_std), PARAMETER :: iactive_pool_z3 = 27             !! Index for active carbon pool at 3rd layer (unitless)
255  INTEGER(i_std), PARAMETER :: iactive_pool_z4 = 28             !! Index for active carbon pool at 4th layer (unitless)
256  INTEGER(i_std), PARAMETER :: iactive_pool_z5 = 29             !! Index for active carbon pool at 5th layer (unitless)
257  INTEGER(i_std), PARAMETER :: iactive_pool_z6 = 30             !! Index for active carbon pool at 6th layer (unitless)
258  INTEGER(i_std), PARAMETER :: iactive_pool_z7 = 31             !! Index for active carbon pool at 7th layer (unitless)
259  INTEGER(i_std), PARAMETER :: iactive_pool_z8 = 32             !! Index for active carbon pool at 8th layer (unitless)
260  INTEGER(i_std), PARAMETER :: iactive_pool_z9 = 33             !! Index for active carbon pool at 9th layer (unitless)
261  INTEGER(i_std), PARAMETER :: iactive_pool_z10 = 34            !! Index for active carbon pool at 10th layer (unitless)
262  INTEGER(i_std), PARAMETER :: iactive_pool_z11 = 35            !! Index for active carbon pool at 11th layer (unitless)
263  INTEGER(i_std), PARAMETER :: islow_pool_z1   = 36             !! Index for slow carbon pool at 1st layer (unitless)
264  INTEGER(i_std), PARAMETER :: islow_pool_z2   = 37             !! Index for slow carbon pool at 2nd layer (unitless)
265  INTEGER(i_std), PARAMETER :: islow_pool_z3   = 38             !! Index for slow carbon pool at 3rd layer (unitless)
266  INTEGER(i_std), PARAMETER :: islow_pool_z4   = 39             !! Index for slow carbon pool at 4th layer (unitless)
267  INTEGER(i_std), PARAMETER :: islow_pool_z5   = 40             !! Index for slow carbon pool at 5th layer (unitless)
268  INTEGER(i_std), PARAMETER :: islow_pool_z6   = 41             !! Index for slow carbon pool at 6th layer (unitless)
269  INTEGER(i_std), PARAMETER :: islow_pool_z7   = 42             !! Index for slow carbon pool at 7th layer (unitless)
270  INTEGER(i_std), PARAMETER :: islow_pool_z8   = 43             !! Index for slow carbon pool at 8th layer (unitless)
271  INTEGER(i_std), PARAMETER :: islow_pool_z9   = 44             !! Index for slow carbon pool at 9th layer (unitless)
272  INTEGER(i_std), PARAMETER :: islow_pool_z10   = 45            !! Index for slow carbon pool at 10th layer (unitless)
273  INTEGER(i_std), PARAMETER :: islow_pool_z11   = 46            !! Index for slow carbon pool at 11th layer (unitless)
274  INTEGER(i_std), PARAMETER :: ipassive_pool_z1 = 47            !! Index for passive carbon pool at 1st layer (unitless)
275  INTEGER(i_std), PARAMETER :: ipassive_pool_z2 = 48            !! Index for passive carbon pool at 2nd layer (unitless)
276  INTEGER(i_std), PARAMETER :: ipassive_pool_z3 = 49            !! Index for passive carbon pool at 3rd layer (unitless)
277  INTEGER(i_std), PARAMETER :: ipassive_pool_z4 = 50            !! Index for passive carbon pool at 4th layer (unitless)
278  INTEGER(i_std), PARAMETER :: ipassive_pool_z5 = 51            !! Index for passive carbon pool at 5th layer (unitless)
279  INTEGER(i_std), PARAMETER :: ipassive_pool_z6 = 52            !! Index for passive carbon pool at 6th layer (unitless)
280  INTEGER(i_std), PARAMETER :: ipassive_pool_z7 = 53            !! Index for passive carbon pool at 7th layer (unitless)
281  INTEGER(i_std), PARAMETER :: ipassive_pool_z8 = 54            !! Index for passive carbon pool at 8th layer (unitless)
282  INTEGER(i_std), PARAMETER :: ipassive_pool_z9 = 55            !! Index for passive carbon pool at 9th layer (unitless)
283  INTEGER(i_std), PARAMETER :: ipassive_pool_z10 = 56           !! Index for passive carbon pool at 10th layer (unitless)
284  INTEGER(i_std), PARAMETER :: ipassive_pool_z11 = 57           !! Index for passive carbon pool at 11th layer (unitless)
285  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_metabo = 58            !! Index for free DOC at 1st layer (unitless)
286  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_metabo = 59            !! Index for free DOC at 2nd layer (unitless)
287  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_metabo = 60            !! Index for free DOC at 3rd layer (unitless)
288  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_metabo = 61            !! Index for free DOC at 4th layer (unitless)
289  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_metabo = 62            !! Index for free DOC at 5th layer (unitless)
290  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_metabo = 63            !! Index for free DOC at 6th layer (unitless)
291  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_metabo = 64            !! Index for free DOC at 7th layer (unitless)
292  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_metabo = 65            !! Index for free DOC at 8th layer (unitless)
293  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_metabo = 66            !! Index for free DOC at 9th layer (unitless)
294  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_metabo = 67           !! Index for free DOC at 10th layer (unitless)
295  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_metabo = 68           !! Index for free DOC at 11th layer (unitless)
296  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_metabo = 69             !! Index for adsorbed DOC at 1st layer (unitless)
297  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_metabo = 70             !! Index for adsorbed DOC at 2nd layer (unitless)
298  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_metabo = 71             !! Index for adsorbed DOC at 3rd layer (unitless)
299  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_metabo = 72             !! Index for adsorbed DOC at 4th layer (unitless)
300  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_metabo = 73             !! Index for adsorbed DOC at 5th layer (unitless)
301  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_metabo = 74             !! Index for adsorbed DOC at 6th layer (unitless)
302  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_metabo = 75             !! Index for adsorbed DOC at 7th layer (unitless)
303  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_metabo = 76             !! Index for adsorbed DOC at 8th layer (unitless)
304  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_metabo = 77             !! Index for adsorbed DOC at 9th layer (unitless)
305  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_metabo = 78            !! Index for adsorbed DOC at 10th layer (unitless)
306  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_metabo = 79            !! Index for adsorbed DOC at 11th layer (unitless)
307  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_strabo = 80            !! Index for free DOC at 1st layer (unitless)
308  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_strabo = 81            !! Index for free DOC at 2nd layer (unitless)
309  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_strabo = 82            !! Index for free DOC at 3rd layer (unitless)
310  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_strabo = 83            !! Index for free DOC at 4th layer (unitless)
311  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_strabo = 84            !! Index for free DOC at 5th layer (unitless)
312  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_strabo = 85            !! Index for free DOC at 6th layer (unitless)
313  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_strabo = 86            !! Index for free DOC at 7th layer (unitless)
314  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_strabo = 87            !! Index for free DOC at 8th layer (unitless)
315  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_strabo = 88            !! Index for free DOC at 9th layer (unitless)
316  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_strabo = 89           !! Index for free DOC at 10th layer (unitless)
317  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_strabo = 90           !! Index for free DOC at 11th layer (unitless)
318  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_strabo = 91             !! Index for adsorbed DOC at 1st layer (unitless)
319  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_strabo = 92             !! Index for adsorbed DOC at 2nd layer (unitless)
320  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_strabo = 93             !! Index for adsorbed DOC at 3rd layer (unitless)
321  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_strabo = 94             !! Index for adsorbed DOC at 4th layer (unitless)
322  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_strabo = 95             !! Index for adsorbed DOC at 5th layer (unitless)
323  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_strabo = 96             !! Index for adsorbed DOC at 6th layer (unitless)
324  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_strabo = 97             !! Index for adsorbed DOC at 7th layer (unitless)
325  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_strabo = 98             !! Index for adsorbed DOC at 8th layer (unitless)
326  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_strabo = 99             !! Index for adsorbed DOC at 9th layer (unitless)
327  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_strabo = 100           !! Index for adsorbed DOC at 10th layer (unitless)
328  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_strabo = 101           !! Index for adsorbed DOC at 11th layer (unitless)
329  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_metbel = 102            !! Index for free DOC at 1st layer (unitless)
330  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_metbel = 103            !! Index for free DOC at 2nd layer (unitless)
331  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_metbel = 104            !! Index for free DOC at 3rd layer (unitless)
332  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_metbel = 105            !! Index for free DOC at 4th layer (unitless)
333  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_metbel = 106            !! Index for free DOC at 5th layer (unitless)
334  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_metbel = 107            !! Index for free DOC at 6th layer (unitless)
335  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_metbel = 108            !! Index for free DOC at 7th layer (unitless)
336  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_metbel = 109            !! Index for free DOC at 8th layer (unitless)
337  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_metbel = 110            !! Index for free DOC at 9th layer (unitless)
338  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_metbel = 111           !! Index for free DOC at 10th layer (unitless)
339  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_metbel = 112           !! Index for free DOC at 11th layer (unitless)
340  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_metbel = 113             !! Index for adsorbed DOC at 1st layer (unitless)
341  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_metbel = 114             !! Index for adsorbed DOC at 2nd layer (unitless)
342  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_metbel = 115             !! Index for adsorbed DOC at 3rd layer (unitless)
343  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_metbel = 116             !! Index for adsorbed DOC at 4th layer (unitless)
344  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_metbel = 117             !! Index for adsorbed DOC at 5th layer (unitless)
345  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_metbel = 118             !! Index for adsorbed DOC at 6th layer (unitless)
346  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_metbel = 119             !! Index for adsorbed DOC at 7th layer (unitless)
347  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_metbel = 120             !! Index for adsorbed DOC at 8th layer (unitless)
348  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_metbel = 121             !! Index for adsorbed DOC at 9th layer (unitless)
349  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_metbel = 122           !! Index for adsorbed DOC at 10th layer (unitless)
350  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_metbel = 123           !! Index for adsorbed DOC at 11th layer (unitless)
351  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_strbel = 124            !! Index for free DOC at 1st layer (unitless)
352  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_strbel = 125            !! Index for free DOC at 2nd layer (unitless)
353  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_strbel = 126            !! Index for free DOC at 3rd layer (unitless)
354  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_strbel = 127            !! Index for free DOC at 4th layer (unitless)
355  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_strbel = 128            !! Index for free DOC at 5th layer (unitless)
356  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_strbel = 129            !! Index for free DOC at 6th layer (unitless)
357  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_strbel = 130            !! Index for free DOC at 7th layer (unitless)
358  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_strbel = 131            !! Index for free DOC at 8th layer (unitless)
359  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_strbel = 132            !! Index for free DOC at 9th layer (unitless)
360  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_strbel = 133           !! Index for free DOC at 10th layer (unitless)
361  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_strbel = 134           !! Index for free DOC at 11th layer (unitless)
362  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_strbel = 135             !! Index for adsorbed DOC at 1st layer (unitless)
363  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_strbel = 136             !! Index for adsorbed DOC at 2nd layer (unitless)
364  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_strbel = 137             !! Index for adsorbed DOC at 3rd layer (unitless)
365  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_strbel = 138             !! Index for adsorbed DOC at 4th layer (unitless)
366  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_strbel = 139             !! Index for adsorbed DOC at 5th layer (unitless)
367  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_strbel = 140             !! Index for adsorbed DOC at 6th layer (unitless)
368  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_strbel = 141             !! Index for adsorbed DOC at 7th layer (unitless)
369  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_strbel = 142             !! Index for adsorbed DOC at 8th layer (unitless)
370  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_strbel = 143             !! Index for adsorbed DOC at 9th layer (unitless)
371  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_strbel = 144           !! Index for adsorbed DOC at 10th layer (unitless)
372  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_strbel = 145           !! Index for adsorbed DOC at 11th layer (unitless)
373  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_act = 146            !! Index for free DOC at 1st layer (unitless)
374  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_act = 147            !! Index for free DOC at 2nd layer (unitless)
375  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_act = 148            !! Index for free DOC at 3rd layer (unitless)
376  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_act = 149            !! Index for free DOC at 4th layer (unitless)
377  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_act = 150            !! Index for free DOC at 5th layer (unitless)
378  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_act = 151            !! Index for free DOC at 6th layer (unitless)
379  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_act = 152            !! Index for free DOC at 7th layer (unitless)
380  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_act = 153            !! Index for free DOC at 8th layer (unitless)
381  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_act = 154            !! Index for free DOC at 9th layer (unitless)
382  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_act = 155           !! Index for free DOC at 10th layer (unitless)
383  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_act = 156           !! Index for free DOC at 11th layer (unitless)
384  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_act = 157             !! Index for adsorbed DOC at 1st layer (unitless)
385  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_act = 158             !! Index for adsorbed DOC at 2nd layer (unitless)
386  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_act = 159             !! Index for adsorbed DOC at 3rd layer (unitless)
387  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_act = 160             !! Index for adsorbed DOC at 4th layer (unitless)
388  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_act = 161             !! Index for adsorbed DOC at 5th layer (unitless)
389  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_act = 162             !! Index for adsorbed DOC at 6th layer (unitless)
390  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_act = 163             !! Index for adsorbed DOC at 7th layer (unitless)
391  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_act = 164             !! Index for adsorbed DOC at 8th layer (unitless)
392  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_act = 165             !! Index for adsorbed DOC at 9th layer (unitless)
393  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_act = 166           !! Index for adsorbed DOC at 10th layer (unitless)
394  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_act = 167           !! Index for adsorbed DOC at 11th layer (unitless)
395  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_slo = 168            !! Index for free DOC at 1st layer (unitless)
396  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_slo = 169            !! Index for free DOC at 2nd layer (unitless)
397  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_slo = 170            !! Index for free DOC at 3rd layer (unitless)
398  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_slo = 171            !! Index for free DOC at 4th layer (unitless)
399  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_slo = 172            !! Index for free DOC at 5th layer (unitless)
400  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_slo = 173            !! Index for free DOC at 6th layer (unitless)
401  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_slo = 174            !! Index for free DOC at 7th layer (unitless)
402  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_slo = 175            !! Index for free DOC at 8th layer (unitless)
403  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_slo = 176            !! Index for free DOC at 9th layer (unitless)
404  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_slo = 177           !! Index for free DOC at 10th layer (unitless)
405  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_slo = 178           !! Index for free DOC at 11th layer (unitless)
406  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_slo = 179             !! Index for adsorbed DOC at 1st layer (unitless)
407  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_slo = 180             !! Index for adsorbed DOC at 2nd layer (unitless)
408  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_slo = 181             !! Index for adsorbed DOC at 3rd layer (unitless)
409  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_slo = 182             !! Index for adsorbed DOC at 4th layer (unitless)
410  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_slo = 183             !! Index for adsorbed DOC at 5th layer (unitless)
411  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_slo = 184             !! Index for adsorbed DOC at 6th layer (unitless)
412  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_slo = 185             !! Index for adsorbed DOC at 7th layer (unitless)
413  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_slo = 186             !! Index for adsorbed DOC at 8th layer (unitless)
414  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_slo = 187             !! Index for adsorbed DOC at 9th layer (unitless)
415  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_slo = 188           !! Index for adsorbed DOC at 10th layer (unitless)
416  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_slo = 189           !! Index for adsorbed DOC at 11th layer (unitless)
417  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z1_pas = 190            !! Index for free DOC at 1st layer (unitless)
418  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z2_pas = 191            !! Index for free DOC at 2nd layer (unitless)
419  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z3_pas = 192            !! Index for free DOC at 3rd layer (unitless)
420  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z4_pas = 193            !! Index for free DOC at 4th layer (unitless)
421  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z5_pas = 194            !! Index for free DOC at 5th layer (unitless)
422  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z6_pas = 195            !! Index for free DOC at 6th layer (unitless)
423  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z7_pas = 196            !! Index for free DOC at 7th layer (unitless)
424  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z8_pas = 197            !! Index for free DOC at 8th layer (unitless)
425  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z9_pas = 198            !! Index for free DOC at 9th layer (unitless)
426  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z10_pas = 199           !! Index for free DOC at 10th layer (unitless)
427  INTEGER(i_std), PARAMETER :: ifreedoc_pool_z11_pas = 200           !! Index for free DOC at 11th layer (unitless)
428  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z1_pas = 201             !! Index for adsorbed DOC at 1st layer (unitless)
429  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z2_pas = 202             !! Index for adsorbed DOC at 2nd layer (unitless)
430  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z3_pas = 203             !! Index for adsorbed DOC at 3rd layer (unitless)
431  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z4_pas = 204             !! Index for adsorbed DOC at 4th layer (unitless)
432  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z5_pas = 205             !! Index for adsorbed DOC at 5th layer (unitless)
433  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z6_pas = 206             !! Index for adsorbed DOC at 6th layer (unitless)
434  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z7_pas = 207             !! Index for adsorbed DOC at 7th layer (unitless)
435  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z8_pas = 208             !! Index for adsorbed DOC at 8th layer (unitless)
436  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z9_pas = 209             !! Index for adsorbed DOC at 9th layer (unitless)
437  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z10_pas = 210           !! Index for adsorbed DOC at 10th layer (unitless)
438  INTEGER(i_std), PARAMETER :: iadsdoc_pool_z11_pas = 211           !! Index for adsorbed DOC at 11th layer (unitless)
439
440  INTEGER(i_std), SAVE      :: sro_bottom = 5                        !! Layer down to which DOC for surface runoff is taken (max=10)
441  !! For the routing of C and CO2 outgassing
442  !! Indices used for matter transport with water flows
443  INTEGER(i_std), PARAMETER :: ih2o = 1        !! index for water (unitless)
444  INTEGER(i_std), PARAMETER :: idoc = 2        !! index for dissolved organic carbon (unitless)
445  INTEGER(i_std), PARAMETER :: ico2aq = 3      !! index for free dissolved carbon dioxide (unitless)
446  INTEGER(i_std), PARAMETER :: ico2ev = 4      !! index for evaded carbon dioxide (unitless) 
447  INTEGER(i_std), PARAMETER :: nflow = 4       !! number of compounds transported with water flows (unitless)
448  !! Indices used to distinguish different aquatic systems
449  INTEGER(i_std), PARAMETER :: ifastr = 1       !! index for fast reservoir (unitless)
450  INTEGER(i_std), PARAMETER :: islowr = 2       !! index for slow reservoir (unitless) 
451  INTEGER(i_std), PARAMETER :: istreamr = 3     !! index for stream reservoir (unitless) 
452  INTEGER(i_std), PARAMETER :: ifloodr = 4      !! index for flood reservoir (unitless)
453  INTEGER(i_std), PARAMETER :: ipondr = 5       !! index for pond reservoir (unitless) 
454  INTEGER(i_std), PARAMETER :: naqsys = 5      !! number of aquatic systems considered (unitless)
455
456  !
457  ! NUMERICAL AND PHYSICS CONSTANTS
458  !
459  !
460
461  !-
462  ! 1. Mathematical and numerical constants
463  !-
464  REAL(r_std), PARAMETER :: pi = 3.141592653589793238   !! pi souce : http://mathworld.wolfram.com/Pi.html (unitless)
465  REAL(r_std), PARAMETER :: euler = 2.71828182845904523 !! e source : http://mathworld.wolfram.com/e.html (unitless)
466  REAL(r_std), PARAMETER :: zero = 0._r_std             !! Numerical constant set to 0 (unitless)
467  REAL(r_std), PARAMETER :: undemi = 0.5_r_std          !! Numerical constant set to 1/2 (unitless)
468  REAL(r_std), PARAMETER :: un = 1._r_std               !! Numerical constant set to 1 (unitless)
469  REAL(r_std), PARAMETER :: moins_un = -1._r_std        !! Numerical constant set to -1 (unitless)
470  REAL(r_std), PARAMETER :: deux = 2._r_std             !! Numerical constant set to 2 (unitless)
471  REAL(r_std), PARAMETER :: trois = 3._r_std            !! Numerical constant set to 3 (unitless)
472  REAL(r_std), PARAMETER :: quatre = 4._r_std           !! Numerical constant set to 4 (unitless)
473  REAL(r_std), PARAMETER :: cinq = 5._r_std             !![DISPENSABLE] Numerical constant set to 5 (unitless)
474  REAL(r_std), PARAMETER :: six = 6._r_std              !![DISPENSABLE] Numerical constant set to 6 (unitless)
475  REAL(r_std), PARAMETER :: huit = 8._r_std             !! Numerical constant set to 8 (unitless)
476  REAL(r_std), PARAMETER :: dix = 10._r_std             !! Numerical constant set to 100 (unitless)
477  REAL(r_std), PARAMETER :: cent = 100._r_std           !! Numerical constant set to 100 (unitless)
478  REAL(r_std), PARAMETER :: mille = 1000._r_std         !! Numerical constant set to 1000 (unitless)
479
480  !-
481  ! 2 . Physics
482  !-
483  REAL(r_std), PARAMETER :: R_Earth = 6378000.              !! radius of the Earth : Earth radius ~= Equatorial radius (m)
484  REAL(r_std), PARAMETER :: mincos  = 0.0001                !! Minimum cosine value used for interpolation (unitless)
485  REAL(r_std), PARAMETER :: pb_std = 1013.                  !! standard pressure (hPa)
486  REAL(r_std), PARAMETER :: ZeroCelsius = 273.15            !! 0 degre Celsius in degre Kelvin (K)
487  REAL(r_std), PARAMETER :: tp_00 = 273.15                  !! 0 degre Celsius in degre Kelvin (K)
488  REAL(r_std), PARAMETER :: chalsu0 = 2.8345E06             !! Latent heat of sublimation (J.kg^{-1})
489  REAL(r_std), PARAMETER :: chalev0 = 2.5008E06             !! Latent heat of evaporation (J.kg^{-1})
490  REAL(r_std), PARAMETER :: chalfu0 = chalsu0-chalev0       !! Latent heat of fusion (J.kg^{-1})
491  REAL(r_std), PARAMETER :: c_stefan = 5.6697E-8            !! Stefan-Boltzman constant (W.m^{-2}.K^{-4})
492  REAL(r_std), PARAMETER :: cp_air = 1004.675               !! Specific heat of dry air (J.kg^{-1}.K^{-1})
493  REAL(r_std), PARAMETER :: cte_molr = 287.05               !! Specific constant of dry air (kg.mol^{-1})
494  REAL(r_std), PARAMETER :: kappa = cte_molr/cp_air         !! Kappa : ratio between specific constant and specific heat
495                                                            !! of dry air (unitless)
496  REAL(r_std), PARAMETER :: msmlr_air = 28.964E-03          !! Molecular weight of dry air (kg.mol^{-1})
497  REAL(r_std), PARAMETER :: msmlr_h2o = 18.02E-03           !! Molecular weight of water vapor (kg.mol^{-1})
498  REAL(r_std), PARAMETER :: cp_h2o = &                      !! Specific heat of water vapor (J.kg^{-1}.K^{-1})
499       & cp_air*(quatre*msmlr_air)/( 3.5_r_std*msmlr_h2o) 
500  REAL(r_std), PARAMETER :: cte_molr_h2o = cte_molr/quatre  !! Specific constant of water vapor (J.kg^{-1}.K^{-1})
501  REAL(r_std), PARAMETER :: retv = msmlr_air/msmlr_h2o-un   !! Ratio between molecular weight of dry air and water
502                                                            !! vapor minus 1(unitless) 
503  REAL(r_std), PARAMETER :: rvtmp2 = cp_h2o/cp_air-un       !! Ratio between specific heat of water vapor and dry air
504                                                            !! minus 1 (unitless)
505  REAL(r_std), PARAMETER :: cepdu2 = (0.1_r_std)**2         !! Squared wind shear (m^2.s^{-2})
506  REAL(r_std), PARAMETER :: ct_karman = 0.35_r_std          !! Van Karmann Constant (unitless)
507  REAL(r_std), PARAMETER :: cte_grav = 9.80665_r_std        !! Acceleration of the gravity (m.s^{-2})
508  REAL(r_std), PARAMETER :: pa_par_hpa = 100._r_std         !! Transform pascal into hectopascal (unitless)
509  REAL(r_std), PARAMETER :: RR = 8.314                      !! Ideal gas constant (J.mol^{-1}.K^{-1})
510  REAL(r_std), PARAMETER :: Sct = 1370.                     !! Solar constant (W.m^{-2})
511
512
513  !-
514  ! 3. Climatic constants
515  !-
516  !! Constantes of the Louis scheme
517  REAL(r_std), SAVE :: cb = 5._r_std              !! Constant of the Louis scheme (unitless);
518                                                  !! reference to Louis (1979)
519!$OMP THREADPRIVATE(cb)
520  REAL(r_std), SAVE :: cc = 5._r_std              !! Constant of the Louis scheme (unitless);
521                                                  !! reference to Louis (1979)
522!$OMP THREADPRIVATE(cc)
523  REAL(r_std), SAVE :: cd = 5._r_std              !! Constant of the Louis scheme (unitless);
524                                                  !! reference to Louis (1979)
525!$OMP THREADPRIVATE(cd)
526  REAL(r_std), SAVE :: rayt_cste = 125.           !! Constant in the computation of surface resistance (W.m^{-2})
527!$OMP THREADPRIVATE(rayt_cste)
528  REAL(r_std), SAVE :: defc_plus = 23.E-3         !! Constant in the computation of surface resistance (K.W^{-1})
529!$OMP THREADPRIVATE(defc_plus)
530  REAL(r_std), SAVE :: defc_mult = 1.5            !! Constant in the computation of surface resistance (K.W^{-1})
531!$OMP THREADPRIVATE(defc_mult)
532
533  !-
534  ! 4. Soil thermodynamics constants
535  !-
536  ! Look at constantes_soil.f90
537
538
539  !
540  ! OPTIONAL PARTS OF THE MODEL
541  !
542  LOGICAL,PARAMETER :: diag_qsat = .TRUE.         !! One of the most frequent problems is a temperature out of range
543                                                  !! we provide here a way to catch that in the calling procedure.
544                                                  !! (from Jan Polcher)(true/false)
545  LOGICAL, SAVE     :: almaoutput =.FALSE.        !! Selects the type of output for the model.(true/false)
546                                                  !! Value is read from run.def in intersurf_history
547!$OMP THREADPRIVATE(almaoutput)
548
549  !
550  ! DIVERSE
551  !
552  CHARACTER(LEN=100), SAVE :: stomate_forcing_name='NONE'  !! NV080800 Name of STOMATE forcing file (unitless)
553                                                           ! Compatibility with Nicolas Viovy driver.
554!$OMP THREADPRIVATE(stomate_forcing_name)
555  CHARACTER(LEN=100), SAVE :: stomate_Cforcing_name='NONE' !! NV080800 Name of soil forcing file (unitless)
556                                                           ! Compatibility with Nicolas Viovy driver.
557!$OMP THREADPRIVATE(stomate_Cforcing_name)
558  INTEGER(i_std), SAVE :: forcing_id                 !! Index of the forcing file (unitless)
559!$OMP THREADPRIVATE(forcing_id)
560  LOGICAL, SAVE :: allow_forcing_write=.TRUE.        !! Allow writing of stomate_forcing file.
561                                                     !! This variable will be set to false for teststomate.
562
563
564
565                         !------------------------!
566                         !  SECHIBA PARAMETERS    !
567                         !------------------------!
568 
569
570  !
571  ! GLOBAL PARAMETERS   
572  !
573  REAL(r_std), SAVE :: min_wind = 0.1      !! The minimum wind (m.s^{-1})
574!$OMP THREADPRIVATE(min_wind)
575  REAL(r_std), SAVE :: snowcri = 1.5       !! Sets the amount above which only sublimation occures (kg.m^{-2})
576!$OMP THREADPRIVATE(snowcri)
577
578
579  !
580  ! FLAGS ACTIVATING SUB-MODELS
581  !
582  LOGICAL, SAVE :: treat_expansion = .FALSE.   !! Do we treat PFT expansion across a grid point after introduction? (true/false)
583!$OMP THREADPRIVATE(treat_expansion)
584  LOGICAL, SAVE :: ok_herbivores = .FALSE.     !! flag to activate herbivores (true/false)
585!$OMP THREADPRIVATE(ok_herbivores)
586  LOGICAL, SAVE :: harvest_agri = .TRUE.       !! flag to harvest aboveground biomass from agricultural PFTs)(true/false)
587!$OMP THREADPRIVATE(harvest_agri)
588  LOGICAL, SAVE :: lpj_gap_const_mort          !! constant moratlity (true/false). Default value depend on OK_DGVM.
589!$OMP THREADPRIVATE(lpj_gap_const_mort)
590  LOGICAL, SAVE :: disable_fire = .FALSE.      !! flag that disable fire (true/false)
591!$OMP THREADPRIVATE(disable_fire)
592  LOGICAL, SAVE :: spinup_analytic = .FALSE.   !! Flag to activate analytical resolution for spinup (true/false)
593!$OMP THREADPRIVATE(spinup_analytic)
594  LOGICAL, SAVE :: ok_explicitsnow             !! Flag to activate explicit snow scheme instead of default snow scheme
595!$OMP THREADPRIVATE(ok_explicitsnow)
596  LOGICAL, SAVE :: moist_func_Moyano = .FALSE. !! Flag to activate the calculation of moisture control function on soil C decomposition based on Moyano et al., 2012 BG (true/false)
597!$OMP THREADPRIVATE(moist_func_Moyano)
598
599  !
600  ! CONFIGURATION VEGETATION
601  !
602  LOGICAL, SAVE :: agriculture = .TRUE.    !! allow agricultural PFTs (true/false)
603!$OMP THREADPRIVATE(agriculture)
604  LOGICAL, SAVE :: impveg = .FALSE.        !! Impose vegetation ? (true/false)
605!$OMP THREADPRIVATE(impveg)
606  LOGICAL, SAVE :: impsoilt = .FALSE.      !! Impose soil ? (true/false)
607!$OMP THREADPRIVATE(impsoilt)
608  LOGICAL, SAVE :: do_now_stomate_lcchange = .FALSE.  !! Time to call lcchange in stomate_lpj
609!$OMP THREADPRIVATE(do_now_stomate_lcchange)
610  LOGICAL, SAVE :: done_stomate_lcchange = .FALSE.    !! If true, call lcchange in stomate_lpj has just been done.
611!$OMP THREADPRIVATE(done_stomate_lcchange)
612  LOGICAL, SAVE :: read_lai = .FALSE.      !! Flag to read a map of LAI if STOMATE is not activated (true/false)
613!$OMP THREADPRIVATE(read_lai)
614  LOGICAL, SAVE :: map_pft_format = .TRUE. !! Read a land use vegetation map on PFT format (true/false)
615!$OMP THREADPRIVATE(map_pft_format)
616  LOGICAL, SAVE :: veget_reinit = .TRUE.   !! To change LAND USE file in a run. (true/false)
617!$OMP THREADPRIVATE(veget_reinit)
618
619  !
620  ! PARAMETERS USED BY BOTH HYDROLOGY MODELS
621  !
622  REAL(r_std), SAVE :: max_snow_age = 50._r_std !! Maximum period of snow aging (days)
623!$OMP THREADPRIVATE(max_snow_age)
624  REAL(r_std), SAVE :: snow_trans = 0.3_r_std   !! Transformation time constant for snow (m)
625!$OMP THREADPRIVATE(snow_trans)
626  REAL(r_std), SAVE :: sneige                   !! Lower limit of snow amount (kg.m^{-2})
627!$OMP THREADPRIVATE(sneige)
628  REAL(r_std), SAVE :: maxmass_snow = 3000.     !! The maximum mass of snow (kg.m^{-2})
629!$OMP THREADPRIVATE(maxmass_snow)
630
631  !! Heat capacity
632  REAL(r_std), PARAMETER :: capa_ice = 2.228*1.E3       !! Heat capacity of ice (J/kg/K)
633  REAL(r_std), SAVE      :: so_capa_ice                 !! Heat capacity of saturated frozen soil (J/K/m3)
634!$OMP THREADPRIVATE(so_capa_ice)
635  REAL(r_std), PARAMETER :: rho_water = 1000.           !! Density of water (kg/m3)
636  REAL(r_std), PARAMETER :: rho_ice = 920.              !! Density of ice (kg/m3)
637
638  !! Thermal conductivities
639  REAL(r_std), PARAMETER :: cond_water = 0.6            !! Thermal conductivity of liquid water (W/m/K)
640  REAL(r_std), PARAMETER :: cond_ice = 2.2              !! Thermal conductivity of ice (W/m/K)
641  REAL(r_std), PARAMETER :: cond_solid = 2.32           !! Thermal conductivity of mineral soil particles (W/m/K)
642
643  !! Time constant of long-term soil humidity (s)
644  REAL(r_std), PARAMETER :: lhf = 0.3336*1.E6           !! Latent heat of fusion (J/kg)
645
646  INTEGER(i_std), PARAMETER :: nsnow=3                  !! Number of levels in the snow for explicit snow scheme   
647  REAL(r_std), PARAMETER    :: XMD    = 28.9644E-3 
648  REAL(r_std), PARAMETER    :: XBOLTZ      = 1.380658E-23 
649  REAL(r_std), PARAMETER    :: XAVOGADRO   = 6.0221367E+23 
650  REAL(r_std), PARAMETER    :: XRD    = XAVOGADRO * XBOLTZ / XMD 
651  REAL(r_std), PARAMETER    :: XCPD   = 7.* XRD /2. 
652  REAL(r_std), PARAMETER    :: phigeoth = 0.057 ! 0. DKtest
653  REAL(r_std), PARAMETER    :: thick_min_snow = .01 
654
655  !! The maximum snow density and water holding characterisicts
656  REAL(r_std), SAVE         :: xrhosmax = 750.  ! (kg m-3)
657  REAL(r_std), SAVE         :: xwsnowholdmax1   = 0.03  ! (-)
658  REAL(r_std), SAVE         :: xwsnowholdmax2   = 0.10  ! (-)
659  REAL(r_std), SAVE         :: xsnowrhohold     = 200.0 ! (kg/m3)
660  REAL(r_std), SAVE         :: xrhosmin = 50. 
661  REAL(r_std), PARAMETER    :: xci = 2.106e+3 
662  REAL(r_std), PARAMETER    :: xrv = 6.0221367e+23 * 1.380658e-23 /18.0153e-3 
663
664  !! ISBA-ES Critical snow depth at which snow grid thicknesses constant
665  REAL(r_std), PARAMETER    :: xsnowcritd = 0.03  ! (m)
666
667  !! The threshold of snow depth used for preventing numerical problem in thermal calculations
668  REAL(r_std), PARAMETER    :: snowcritd_thermal = 0.01  ! (m) 
669 
670  !! ISBA-ES CROCUS (Pahaut 1976): snowfall density coefficients:
671  REAL(r_std), PARAMETER       :: snowfall_a_sn = 109.0  !! (kg/m3)
672  REAL(r_std), PARAMETER       :: snowfall_b_sn =   6.0  !! (kg/m3/K)
673  REAL(r_std), PARAMETER       :: snowfall_c_sn =  26.0  !! [kg/(m7/2 s1/2)]
674
675  REAL(r_std), PARAMETER       :: dgrain_new_max=  2.0e-4!! (m) : Maximum grain size of new snowfall
676 
677  !! Used in explicitsnow to prevent numerical problems as snow becomes vanishingly thin.
678  REAL(r_std), PARAMETER                :: psnowdzmin = .0001   ! m
679  REAL(r_std), PARAMETER                :: xsnowdmin = .000001  ! m
680
681  REAL(r_std), PARAMETER                :: ph2o = 1000.         !! Water density [kg/m3]
682 
683  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
684  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
685  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND1 = 0.02    ! [W/m/K]
686  REAL(r_std), SAVE                     :: ZSNOWTHRMCOND2 = 2.5E-6  ! [W m5/(kg2 K)]
687 
688  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
689  ! (sig only for new snow OR high altitudes)
690  ! from Sun et al. (1999): based on data from Jordan (1991)
691  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
692  !
693  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_AVAP  = -0.06023 ! (W/m/K)
694  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_BVAP  = -2.5425  ! (W/m)
695  REAL(r_std), SAVE                       :: ZSNOWTHRMCOND_CVAP  = -289.99  ! (K)
696 
697  REAL(r_std),SAVE :: xansmax = 0.85      !! Maxmimum snow albedo
698  REAL(r_std),SAVE :: xansmin = 0.50      !! Miniumum snow albedo
699  REAL(r_std),SAVE :: xans_todry = 0.008  !! Albedo decay rate for dry snow
700  REAL(r_std),SAVE :: xans_t = 0.240      !! Albedo decay rate for wet snow
701
702  ! ISBA-ES Thermal conductivity coefficients from Anderson (1976):
703  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
704  REAL(r_std), PARAMETER                  :: XP00 = 1.E5
705
706  ! ISBA-ES Thermal conductivity: Implicit vapor diffn effects
707  ! (sig only for new snow OR high altitudes)
708  ! from Sun et al. (1999): based on data from Jordan (1991)
709  ! see Boone, Meteo-France/CNRM Note de Centre No. 70 (2002)
710  !
711  REAL(r_std), SAVE          :: ZSNOWCMPCT_RHOD  = 150.0        !! (kg/m3)
712  REAL(r_std), SAVE          :: ZSNOWCMPCT_ACM   = 2.8e-6       !! (1/s)
713  REAL(r_std), SAVE          :: ZSNOWCMPCT_BCM   = 0.04         !! (1/K)
714  REAL(r_std), SAVE          :: ZSNOWCMPCT_CCM   = 460.         !! (m3/kg)
715  REAL(r_std), SAVE          :: ZSNOWCMPCT_V0    = 3.7e7        !! (Pa/s)
716  REAL(r_std), SAVE          :: ZSNOWCMPCT_VT    = 0.081        !! (1/K)
717  REAL(r_std), SAVE          :: ZSNOWCMPCT_VR    = 0.018        !! (m3/kg)
718
719  !
720  ! BVOC : Biogenic activity  for each age class
721  !
722  REAL(r_std), SAVE, DIMENSION(nleafages) :: iso_activity = (/0.5, 1.5, 1.5, 0.5/)     !! Biogenic activity for each
723                                                                                       !! age class : isoprene (unitless)
724!$OMP THREADPRIVATE(iso_activity)
725  REAL(r_std), SAVE, DIMENSION(nleafages) :: methanol_activity = (/1., 1., 0.5, 0.5/)  !! Biogenic activity for each
726                                                                                       !! age class : methanol (unnitless)
727!$OMP THREADPRIVATE(methanol_activity)
728
729  !
730  ! condveg.f90
731  !
732
733  ! 1. Scalar
734
735  ! 1.1 Flags used inside the module
736
737  LOGICAL, SAVE :: alb_bare_model = .FALSE. !! Switch for choosing values of bare soil
738                                            !! albedo (see header of subroutine)
739                                            !! (true/false)
740!$OMP THREADPRIVATE(alb_bare_model)
741  LOGICAL, SAVE :: alb_bg_modis = .FALSE.   !! Switch for choosing values of bare soil
742                                            !! albedo read from file
743                                            !! (true/false)
744!$OMP THREADPRIVATE(alb_bg_modis)
745  LOGICAL, SAVE :: impaze = .FALSE.         !! Switch for choosing surface parameters
746                                            !! (see header of subroutine). 
747                                            !! (true/false)
748!$OMP THREADPRIVATE(impaze)
749  LOGICAL, SAVE :: z0cdrag_ave = .TRUE.     !! Chooses between two methods to calculate the
750                                            !! grid average of the roughness (see header of subroutine)   
751                                            !! (true/false)
752!$OMP THREADPRIVATE(z0cdrag_ave)
753  ! 1.2 Others
754
755  REAL(r_std), SAVE :: z0_over_height = un/16.           !! Factor to calculate roughness height from
756                                                         !! vegetation height (unitless)   
757!$OMP THREADPRIVATE(z0_over_height)
758  REAL(r_std), SAVE :: height_displacement = 0.75        !! Factor to calculate the zero-plane displacement
759                                                         !! height from vegetation height (m)
760!$OMP THREADPRIVATE(height_displacement)
761  REAL(r_std), SAVE :: z0_bare = 0.01                    !! bare soil roughness length (m)
762!$OMP THREADPRIVATE(z0_bare)
763  REAL(r_std), SAVE :: z0_ice = 0.001                    !! ice roughness length (m)
764!$OMP THREADPRIVATE(z0_ice)
765  REAL(r_std), SAVE :: tcst_snowa = 5.0                  !! Time constant of the albedo decay of snow (days)
766!$OMP THREADPRIVATE(tcst_snowa)
767  REAL(r_std), SAVE :: snowcri_alb = 10.                 !! Critical value for computation of snow albedo (cm)
768!$OMP THREADPRIVATE(snowcri_alb)
769  REAL(r_std), SAVE :: fixed_snow_albedo = undef_sechiba !! To choose a fixed snow albedo value (unitless)
770!$OMP THREADPRIVATE(fixed_snow_albedo)
771  REAL(r_std), SAVE :: z0_scal = 0.15                    !! Surface roughness height imposed (m)
772!$OMP THREADPRIVATE(z0_scal)
773  REAL(r_std), SAVE :: roughheight_scal = zero           !! Effective roughness Height depending on zero-plane
774                                                         !! displacement height (m) (imposed)
775!$OMP THREADPRIVATE(roughheight_scal)
776  REAL(r_std), SAVE :: emis_scal = 1.0                   !! Surface emissivity imposed (unitless)
777!$OMP THREADPRIVATE(emis_scal)
778  ! 2. Arrays
779
780  REAL(r_std), SAVE, DIMENSION(2) :: alb_deadleaf = (/ .12, .35/)    !! albedo of dead leaves, VIS+NIR (unitless)
781!$OMP THREADPRIVATE(alb_deadleaf)
782  REAL(r_std), SAVE, DIMENSION(2) :: alb_ice = (/ .60, .20/)         !! albedo of ice, VIS+NIR (unitless)
783!$OMP THREADPRIVATE(alb_ice)
784  REAL(r_std), SAVE, DIMENSION(2) :: albedo_scal = (/ 0.25, 0.25 /)  !! Albedo values for visible and near-infrared
785                                                                     !! used imposed (unitless)
786!$OMP THREADPRIVATE(albedo_scal)
787  REAL(r_std) , SAVE, DIMENSION(classnb) :: vis_dry = (/0.24,&
788       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.27/)  !! Soil albedo values to soil colour classification:
789                                                          !! dry soil albedo values in visible range
790!$OMP THREADPRIVATE(vis_dry)
791  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_dry = (/0.48,&
792       &0.44, 0.40, 0.36, 0.32, 0.28, 0.24, 0.20, 0.55/)  !! Soil albedo values to soil colour classification:
793                                                          !! dry soil albedo values in near-infrared range
794!$OMP THREADPRIVATE(nir_dry)
795  REAL(r_std), SAVE, DIMENSION(classnb) :: vis_wet = (/0.12,&
796       &0.11, 0.10, 0.09, 0.08, 0.07, 0.06, 0.05, 0.15/)  !! Soil albedo values to soil colour classification:
797                                                          !! wet soil albedo values in visible range
798!$OMP THREADPRIVATE(vis_wet)
799  REAL(r_std), SAVE, DIMENSION(classnb) :: nir_wet = (/0.24,&
800       &0.22, 0.20, 0.18, 0.16, 0.14, 0.12, 0.10, 0.31/)  !! Soil albedo values to soil colour classification:
801                                                          !! wet soil albedo values in near-infrared range
802!$OMP THREADPRIVATE(nir_wet)
803  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_vis = (/ &
804       &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:
805                                                                   !! Averaged of wet and dry soil albedo values
806                                                                   !! in visible and near-infrared range
807!$OMP THREADPRIVATE(albsoil_vis)
808  REAL(r_std), SAVE, DIMENSION(classnb) :: albsoil_nir = (/ &
809       &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:
810                                                                !! Averaged of wet and dry soil albedo values
811                                                                !! in visible and near-infrared range
812!$OMP THREADPRIVATE(albsoil_nir)
813
814  !
815  ! diffuco.f90
816  !
817
818  ! 0. Constants
819
820  REAL(r_std), PARAMETER :: Tetens_1 = 0.622         !! Ratio between molecular weight of water vapor and molecular weight 
821                                                     !! of dry air (unitless)
822  REAL(r_std), PARAMETER :: Tetens_2 = 0.378         !!
823  REAL(r_std), PARAMETER :: ratio_H2O_to_CO2 = 1.6   !! Ratio of water vapor diffusivity to the CO2 diffusivity (unitless)
824  REAL(r_std), PARAMETER :: mmol_to_m_1 = 0.0244     !!
825  REAL(r_std), PARAMETER :: RG_to_PAR = 0.5          !!
826  REAL(r_std), PARAMETER :: W_to_mmol = 4.6          !! W_to_mmol * RG_to_PAR = 2.3
827
828  ! 1. Scalar
829
830  INTEGER(i_std), SAVE :: nlai = 20             !! Number of LAI levels (unitless)
831!$OMP THREADPRIVATE(nlai)
832  LOGICAL, SAVE :: ldq_cdrag_from_gcm = .FALSE. !! Set to .TRUE. if you want q_cdrag coming from GCM
833!$OMP THREADPRIVATE(ldq_cdrag_from_gcm)
834  REAL(r_std), SAVE :: laimax = 12.             !! Maximal LAI used for splitting LAI into N layers (m^2.m^{-2})
835!$OMP THREADPRIVATE(laimax)
836  LOGICAL, SAVE :: downregulation_co2 = .FALSE.            !! Set to .TRUE. if you want CO2 downregulation.
837!$OMP THREADPRIVATE(downregulation_co2)
838  REAL(r_std), SAVE :: downregulation_co2_baselevel = 280. !! CO2 base level (ppm)
839!$OMP THREADPRIVATE(downregulation_co2_baselevel)
840
841  ! 3. Coefficients of equations
842
843  REAL(r_std), SAVE :: lai_level_depth = 0.15  !!
844!$OMP THREADPRIVATE(lai_level_depth)
845!
846  REAL(r_std), SAVE, DIMENSION(6) :: dew_veg_poly_coeff = &            !! coefficients of the 5 degree polynomomial used
847  & (/ 0.887773, 0.205673, 0.110112, 0.014843,  0.000824,  0.000017 /) !! in the equation of coeff_dew_veg
848!$OMP THREADPRIVATE(dew_veg_poly_coeff)
849!
850  REAL(r_std), SAVE               :: Oi=210000.    !! Intercellular oxygen partial pressure (ubar)
851!$OMP THREADPRIVATE(Oi)
852  !
853  ! slowproc.f90
854  !
855
856  ! 1. Scalar
857
858  INTEGER(i_std), SAVE :: veget_year_orig = 0        !!  first year for landuse (number)
859!$OMP THREADPRIVATE(veget_year_orig)
860  REAL(r_std), SAVE :: clayfraction_default = 0.2    !! Default value for clay fraction (0-1, unitless)
861!$OMP THREADPRIVATE(clayfraction_default)
862  REAL(r_std), SAVE :: siltfraction_default = 0.4    !! Default value for silt fraction (0-1, unitless)
863!$OMP THREADPRIVATE(siltfraction_default)
864  REAL(r_std), SAVE :: sandfraction_default = 0.4    !! Default value for sand fraction (0-1, unitless)
865!$OMP THREADPRIVATE(sandfraction_default)
866  REAL(r_std), SAVE :: min_vegfrac = 0.001           !! Minimal fraction of mesh a vegetation type can occupy (0-1, unitless)
867!$OMP THREADPRIVATE(min_vegfrac)
868  REAL(r_std), SAVE :: frac_nobio_fixed_test_1 = 0.0 !! Value for frac_nobio for tests in 0-dim simulations (0-1, unitless)
869!$OMP THREADPRIVATE(frac_nobio_fixed_test_1)
870 
871  REAL(r_std), SAVE :: stempdiag_bid = 280.          !! only needed for an initial LAI if there is no restart file
872!$OMP THREADPRIVATE(stempdiag_bid)
873
874  ! routing.f90
875  !
876
877  ! 1. Constants
878  REAL(r_std), PARAMETER :: msmlr_C = 12.011E-03     !! Molecular weight of C (kg.mol^{-1})
879
880                           !-----------------------------!
881                           !  STOMATE AND LPJ PARAMETERS !
882                           !-----------------------------!
883
884
885  !
886  ! lpj_constraints.f90
887  !
888 
889  ! 1. Scalar
890
891  REAL(r_std), SAVE  :: too_long = 5.      !! longest sustainable time without
892                                           !! regeneration (vernalization) (years)
893!$OMP THREADPRIVATE(too_long)
894
895
896  !
897  ! lpj_establish.f90
898  !
899
900  ! 1. Scalar
901
902  REAL(r_std), SAVE :: estab_max_tree = 0.12   !! Maximum tree establishment rate (0-1, unitless)
903!$OMP THREADPRIVATE(estab_max_tree)
904  REAL(r_std), SAVE :: estab_max_grass = 0.12  !! Maximum grass establishment rate (0-1, unitless)
905!$OMP THREADPRIVATE(estab_max_grass)
906 
907  ! 3. Coefficients of equations
908
909  REAL(r_std), SAVE :: establish_scal_fact = 5.  !!
910!$OMP THREADPRIVATE(establish_scal_fact)
911  REAL(r_std), SAVE :: max_tree_coverage = 0.98  !! (0-1, unitless)
912!$OMP THREADPRIVATE(max_tree_coverage)
913  REAL(r_std), SAVE :: ind_0_estab = 0.2         !! = ind_0 * 10.
914!$OMP THREADPRIVATE(ind_0_estab)
915
916
917  !
918  ! lpj_fire.f90
919  !
920
921  ! 1. Scalar
922
923  REAL(r_std), SAVE :: tau_fire = 30.           !! Time scale for memory of the fire index (days).
924!$OMP THREADPRIVATE(tau_fire)
925  REAL(r_std), SAVE :: litter_crit = 200.       !! Critical litter quantity for fire
926                                                !! below which iginitions extinguish
927                                                !! @tex $(gC m^{-2})$ @endtex
928!$OMP THREADPRIVATE(litter_crit)
929  REAL(r_std), SAVE :: fire_resist_struct = 0.5 !!
930!$OMP THREADPRIVATE(fire_resist_struct)
931  ! 2. Arrays
932
933  REAL(r_std), SAVE, DIMENSION(nparts) :: co2frac = &    !! The fraction of the different biomass
934       & (/ .95, .95, 0., 0.3, 0., 0., .95, .95 /)       !! compartments emitted to the atmosphere
935!$OMP THREADPRIVATE(co2frac)                                                         !! when burned (unitless, 0-1) 
936
937  ! 3. Coefficients of equations
938
939  REAL(r_std), SAVE, DIMENSION(3) :: bcfrac_coeff = (/ .3,  1.3,  88.2 /)         !! (unitless)
940!$OMP THREADPRIVATE(bcfrac_coeff)
941  REAL(r_std), SAVE, DIMENSION(4) :: firefrac_coeff = (/ 0.45, 0.8, 0.6, 0.13 /)  !! (unitless)
942!$OMP THREADPRIVATE(firefrac_coeff)
943
944  !
945  ! lpj_gap.f90
946  !
947
948  ! 1. Scalar
949
950  REAL(r_std), SAVE :: ref_greff = 0.035         !! Asymptotic maximum mortality rate
951                                                 !! @tex $(year^{-1})$ @endtex
952!$OMP THREADPRIVATE(ref_greff)
953
954  !               
955  ! lpj_light.f90
956  !             
957
958  ! 1. Scalar
959 
960  LOGICAL, SAVE :: annual_increase = .TRUE. !! for diagnosis of fpc increase, compare today's fpc to last year's maximum (T) or
961                                            !! to fpc of last time step (F)? (true/false)
962!$OMP THREADPRIVATE(annual_increase)
963  REAL(r_std), SAVE :: min_cover = 0.05     !! For trees, minimum fraction of crown area occupied
964                                            !! (due to its branches etc.) (0-1, unitless)
965                                            !! This means that only a small fraction of its crown area
966                                            !! can be invaded by other trees.
967!$OMP THREADPRIVATE(min_cover)
968  !
969  ! lpj_pftinout.f90
970  !
971
972  ! 1. Scalar
973
974  REAL(r_std), SAVE :: min_avail = 0.01         !! minimum availability
975!$OMP THREADPRIVATE(min_avail)
976  REAL(r_std), SAVE :: ind_0 = 0.02             !! initial density of individuals
977!$OMP THREADPRIVATE(ind_0)
978  ! 3. Coefficients of equations
979 
980  REAL(r_std), SAVE :: RIP_time_min = 1.25      !! test whether the PFT has been eliminated lately (years)
981!$OMP THREADPRIVATE(RIP_time_min)
982  REAL(r_std), SAVE :: npp_longterm_init = 10.  !! Initialisation value for npp_longterm (gC.m^{-2}.year^{-1})
983!$OMP THREADPRIVATE(npp_longterm_init)
984  REAL(r_std), SAVE :: everywhere_init = 0.05   !!
985!$OMP THREADPRIVATE(everywhere_init)
986
987
988  !
989  ! stomate_alloc.f90
990  !
991
992  ! 0. Constants
993
994  REAL(r_std), PARAMETER :: max_possible_lai = 10. !! (m^2.m^{-2})
995  REAL(r_std), PARAMETER :: Nlim_Q10 = 10.         !!
996
997  ! 1. Scalar
998
999  LOGICAL, SAVE :: ok_minres = .TRUE.              !! [DISPENSABLE] Do we try to reach a minimum reservoir even if
1000                                                   !! we are severely stressed? (true/false)
1001!$OMP THREADPRIVATE(ok_minres)
1002  REAL(r_std), SAVE :: reserve_time_tree = 30.     !! Maximum number of days during which
1003                                                   !! carbohydrate reserve may be used for
1004                                                   !! trees (days)
1005!$OMP THREADPRIVATE(reserve_time_tree)
1006  REAL(r_std), SAVE :: reserve_time_grass = 20.    !! Maximum number of days during which
1007                                                   !! carbohydrate reserve may be used for
1008                                                   !! grasses (days)
1009!$OMP THREADPRIVATE(reserve_time_grass)
1010
1011  REAL(r_std), SAVE :: f_fruit = 0.1               !! Default fruit allocation (0-1, unitless)
1012!$OMP THREADPRIVATE(f_fruit)
1013  REAL(r_std), SAVE :: alloc_sap_above_grass = 1.0 !! fraction of sapwood allocation above ground
1014                                                   !! for grass (0-1, unitless)
1015!$OMP THREADPRIVATE(alloc_sap_above_grass)
1016  REAL(r_std), SAVE :: min_LtoLSR = 0.2            !! Prescribed lower bounds for leaf
1017                                                   !! allocation (0-1, unitless)
1018!$OMP THREADPRIVATE(min_LtoLSR)
1019  REAL(r_std), SAVE :: max_LtoLSR = 0.5            !! Prescribed upper bounds for leaf
1020                                                   !! allocation (0-1, unitless)
1021!$OMP THREADPRIVATE(max_LtoLSR)
1022  REAL(r_std), SAVE :: z_nitrogen = 0.2            !! Curvature of the root profile (m)
1023!$OMP THREADPRIVATE(z_nitrogen)
1024
1025  ! 3. Coefficients of equations
1026
1027  REAL(r_std), SAVE :: Nlim_tref = 25.             !! (C)
1028!$OMP THREADPRIVATE(Nlim_tref)
1029
1030
1031  !
1032  ! stomate_data.f90
1033  !
1034
1035  ! 1. Scalar
1036
1037  ! 1.1 Parameters for the pipe model
1038
1039  REAL(r_std), SAVE :: pipe_tune1 = 100.0        !! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) (unitless)
1040!$OMP THREADPRIVATE(pipe_tune1)
1041  REAL(r_std), SAVE :: pipe_tune2 = 40.0         !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
1042!$OMP THREADPRIVATE(pipe_tune2)
1043  REAL(r_std), SAVE :: pipe_tune3 = 0.5          !! height=pipe_tune2 * diameter**pipe_tune3 (unitless)
1044!$OMP THREADPRIVATE(pipe_tune3)
1045  REAL(r_std), SAVE :: pipe_tune4 = 0.3          !! needed for stem diameter (unitless)
1046!$OMP THREADPRIVATE(pipe_tune4)
1047  REAL(r_std), SAVE :: pipe_density = 2.e5       !! Density
1048!$OMP THREADPRIVATE(pipe_density)
1049  REAL(r_std), SAVE :: pipe_k1 = 8.e3            !! one more SAVE
1050!$OMP THREADPRIVATE(pipe_k1)
1051  REAL(r_std), SAVE :: pipe_tune_exp_coeff = 1.6 !! pipe tune exponential coeff (unitless)
1052!$OMP THREADPRIVATE(pipe_tune_exp_coeff)
1053
1054  ! 1.2 climatic parameters
1055
1056  REAL(r_std), SAVE :: precip_crit = 100.        !! minimum precip, in (mm/year)
1057!$OMP THREADPRIVATE(precip_crit)
1058  REAL(r_std), SAVE :: gdd_crit_estab = 150.     !! minimum gdd for establishment of saplings
1059!$OMP THREADPRIVATE(gdd_crit_estab)
1060  REAL(r_std), SAVE :: fpc_crit = 0.95           !! critical fpc, needed for light competition and establishment (0-1, unitless)
1061!$OMP THREADPRIVATE(fpc_crit)
1062
1063  ! 1.3 sapling characteristics
1064
1065  REAL(r_std), SAVE :: alpha_grass = 0.5         !! alpha coefficient for grasses (unitless)
1066!$OMP THREADPRIVATE(alpha_grass)
1067  REAL(r_std), SAVE :: alpha_tree = 1.           !! alpha coefficient for trees (unitless)
1068!$OMP THREADPRIVATE(alpha_tree)
1069  REAL(r_std), SAVE :: mass_ratio_heart_sap = 3. !! mass ratio (heartwood+sapwood)/sapwood (unitless)
1070!$OMP THREADPRIVATE(mass_ratio_heart_sap)
1071
1072  ! 1.4  time scales for phenology and other processes (in days)
1073
1074  REAL(r_std), SAVE :: tau_hum_month = 20.        !! (days)       
1075!$OMP THREADPRIVATE(tau_hum_month)
1076  REAL(r_std), SAVE :: tau_hum_week = 7.          !! (days) 
1077!$OMP THREADPRIVATE(tau_hum_week)
1078  REAL(r_std), SAVE :: tau_t2m_month = 20.        !! (days)     
1079!$OMP THREADPRIVATE(tau_t2m_month)
1080  REAL(r_std), SAVE :: tau_t2m_week = 7.          !! (days) 
1081!$OMP THREADPRIVATE(tau_t2m_week)
1082  REAL(r_std), SAVE :: tau_tsoil_month = 20.      !! (days)     
1083!$OMP THREADPRIVATE(tau_tsoil_month)
1084  REAL(r_std), SAVE :: tau_soilhum_month = 20.    !! (days)     
1085!$OMP THREADPRIVATE(tau_soilhum_month)
1086  REAL(r_std), SAVE :: tau_gpp_week = 7.          !! (days) 
1087!$OMP THREADPRIVATE(tau_gpp_week)
1088  REAL(r_std), SAVE :: tau_gdd = 40.              !! (days) 
1089!$OMP THREADPRIVATE(tau_gdd)
1090  REAL(r_std), SAVE :: tau_ngd = 50.              !! (days) 
1091!$OMP THREADPRIVATE(tau_ngd)
1092  REAL(r_std), SAVE :: coeff_tau_longterm = 3.    !! (unitless)
1093!$OMP THREADPRIVATE(coeff_tau_longterm)
1094  REAL(r_std), SAVE :: tau_longterm_max           !! (days) 
1095!$OMP THREADPRIVATE(tau_longterm_max)
1096
1097  ! 3. Coefficients of equations
1098
1099  REAL(r_std), SAVE :: bm_sapl_carbres = 5.             !!
1100!$OMP THREADPRIVATE(bm_sapl_carbres)
1101  REAL(r_std), SAVE :: bm_sapl_sapabove = 0.5           !!
1102!$OMP THREADPRIVATE(bm_sapl_sapabove)
1103  REAL(r_std), SAVE :: bm_sapl_heartabove = 2.          !!
1104!$OMP THREADPRIVATE(bm_sapl_heartabove)
1105  REAL(r_std), SAVE :: bm_sapl_heartbelow = 2.          !!
1106!$OMP THREADPRIVATE(bm_sapl_heartbelow)
1107  REAL(r_std), SAVE :: init_sapl_mass_leaf_nat = 0.1    !!
1108!$OMP THREADPRIVATE(init_sapl_mass_leaf_nat)
1109  REAL(r_std), SAVE :: init_sapl_mass_leaf_agri = 1.    !!
1110!$OMP THREADPRIVATE(init_sapl_mass_leaf_agri)
1111  REAL(r_std), SAVE :: init_sapl_mass_carbres = 5.      !!
1112!$OMP THREADPRIVATE(init_sapl_mass_carbres)
1113  REAL(r_std), SAVE :: init_sapl_mass_root = 0.1        !!
1114!$OMP THREADPRIVATE(init_sapl_mass_root)
1115  REAL(r_std), SAVE :: init_sapl_mass_fruit = 0.3       !! 
1116!$OMP THREADPRIVATE(init_sapl_mass_fruit)
1117  REAL(r_std), SAVE :: cn_sapl_init = 0.5               !!
1118!$OMP THREADPRIVATE(cn_sapl_init)
1119  REAL(r_std), SAVE :: migrate_tree = 10.*1.E3          !!
1120!$OMP THREADPRIVATE(migrate_tree)
1121  REAL(r_std), SAVE :: migrate_grass = 10.*1.E3         !!
1122!$OMP THREADPRIVATE(migrate_grass)
1123  REAL(r_std), SAVE :: lai_initmin_tree = 0.3           !!
1124!$OMP THREADPRIVATE(lai_initmin_tree)
1125  REAL(r_std), SAVE :: lai_initmin_grass = 0.1          !!
1126!$OMP THREADPRIVATE(lai_initmin_grass)
1127  REAL(r_std), SAVE, DIMENSION(2) :: dia_coeff = (/ 4., 0.5 /)            !!
1128!$OMP THREADPRIVATE(dia_coeff)
1129  REAL(r_std), SAVE, DIMENSION(2) :: maxdia_coeff =(/ 100., 0.01/)        !!
1130!$OMP THREADPRIVATE(maxdia_coeff)
1131  REAL(r_std), SAVE, DIMENSION(4) :: bm_sapl_leaf = (/ 4., 4., 0.8, 5./)  !!
1132!$OMP THREADPRIVATE(bm_sapl_leaf)
1133
1134
1135
1136  !
1137  ! stomate_litter.f90
1138  !
1139
1140  ! 0. Constants
1141
1142  REAL(r_std), PARAMETER :: Q10 = 10.               !!
1143
1144  ! 1. Scalar
1145
1146  REAL(r_std), SAVE :: z_decomp = 0.2               !!  Maximum depth for soil decomposer's activity (m)
1147!$OMP THREADPRIVATE(z_decomp)
1148
1149  ! 2. Arrays
1150
1151  REAL(r_std), SAVE :: frac_soil_struct_aa = 0.45   !! corresponding to frac_soil(istructural,iactive,iabove)
1152!$OMP THREADPRIVATE(frac_soil_struct_aa)
1153  REAL(r_std), SAVE :: frac_soil_struct_ab = 0.45   !! corresponding to frac_soil(istructural,iactive,ibelow)
1154!$OMP THREADPRIVATE(frac_soil_struct_ab)
1155  REAL(r_std), SAVE :: frac_soil_struct_sa = 0.7    !! corresponding to frac_soil(istructural,islow,iabove)
1156!$OMP THREADPRIVATE(frac_soil_struct_sa)
1157  REAL(r_std), SAVE :: frac_soil_struct_sb = 0.7    !! corresponding to frac_soil(istructural,islow,ibelow)
1158!$OMP THREADPRIVATE(frac_soil_struct_sb)
1159  REAL(r_std), SAVE :: frac_soil_metab_aa = 0.45    !! corresponding to frac_soil(imetabolic,iactive,iabove)
1160!$OMP THREADPRIVATE(frac_soil_metab_aa)
1161  REAL(r_std), SAVE :: frac_soil_metab_ab = 0.45    !! corresponding to frac_soil(imetabolic,iactive,ibelow)
1162!$OMP THREADPRIVATE(frac_soil_metab_ab)
1163  REAL(r_std), SAVE, DIMENSION(nparts) :: CN = &    !! C/N ratio of each plant pool (0-100, unitless)
1164       & (/ 40., 40., 40., 40., 40., 40., 40., 40. /) 
1165!$OMP THREADPRIVATE(CN)
1166  REAL(r_std), SAVE, DIMENSION(nparts) :: LC = &    !! Lignin/C ratio of different plant parts (0,22-0,35, unitless)
1167       & (/ 0.22, 0.35, 0.35, 0.35, 0.35, 0.22, 0.22, 0.22 /)
1168!$OMP THREADPRIVATE(LC)
1169
1170  ! 3. Coefficients of equations
1171
1172  REAL(r_std), SAVE :: metabolic_ref_frac = 0.85    !! used by litter and soilcarbon (0-1, unitless)
1173!$OMP THREADPRIVATE(metabolic_ref_frac)
1174  REAL(r_std), SAVE :: metabolic_LN_ratio = 0.018   !! (0-1, unitless)   
1175!$OMP THREADPRIVATE(metabolic_LN_ratio)
1176  REAL(r_std), SAVE :: tau_metabolic = 0.066        !!
1177!$OMP THREADPRIVATE(tau_metabolic)
1178  REAL(r_std), SAVE :: tau_struct = 0.245           !!
1179!$OMP THREADPRIVATE(tau_struct)
1180  REAL(r_std), SAVE :: soil_Q10 = 0.69              !!= ln 2
1181!$OMP THREADPRIVATE(soil_Q10)
1182  REAL(r_std), SAVE :: a_term_Q10_soil = 1.1756     !! used for Q10 calculation in soils
1183!$OMP THREADPRIVATE(a_term_Q10_soil)
1184  REAL(r_std), SAVE :: b_term_Q10_soil = 55.33     !! used for Q10 calculation in soils
1185!$OMP THREADPRIVATE(b_term_Q10_soil)
1186  REAL(r_std), SAVE :: tsoil_ref = 30.              !!
1187!$OMP THREADPRIVATE(tsoil_ref)
1188  REAL(r_std), SAVE :: litter_struct_coef = 3.      !!
1189!$OMP THREADPRIVATE(litter_struct_coef)
1190  REAL(r_std), SAVE, DIMENSION(3) :: moist_coeff = (/ 1.1,  2.4,  0.29 /) !!
1191!$OMP THREADPRIVATE(moist_coeff)
1192  REAL(r_std), SAVE :: moistcont_min = 0.25  !! minimum soil wetness to limit the heterotrophic respiration
1193!$OMP THREADPRIVATE(moistcont_min)
1194  REAL(r_std), SAVE :: Dif = 1.E-4   !! diffusion coeficient for POC (m2 year-1) coming from Koven et al., 2013 BG.
1195!$OMP THREADPRIVATE(Dif)
1196 REAL(r_std), SAVE :: z_litter = 10.   !! Thickness of the above ground litter layer
1197!$OMP THREADPRIVATE(z_litter)
1198
1199
1200  !
1201  ! stomate_lpj.f90
1202  !
1203
1204  ! 1. Scalar
1205
1206  REAL(r_std), SAVE :: frac_turnover_daily = 0.55  !! (0-1, unitless)
1207!$OMP THREADPRIVATE(frac_turnover_daily)
1208
1209
1210  !
1211  ! stomate_npp.f90
1212  !
1213
1214  ! 1. Scalar
1215
1216  REAL(r_std), SAVE :: tax_max = 0.8 !! Maximum fraction of allocatable biomass used
1217                                     !! for maintenance respiration (0-1, unitless)
1218!$OMP THREADPRIVATE(tax_max)
1219
1220
1221  !
1222  ! stomate_phenology.f90
1223  !
1224
1225  ! 1. Scalar
1226
1227  LOGICAL, SAVE :: always_init = .FALSE.           !! take carbon from atmosphere if carbohydrate reserve too small? (true/false)
1228!$OMP THREADPRIVATE(always_init)
1229  REAL(r_std), SAVE :: min_growthinit_time = 300.  !! minimum time since last beginning of a growing season (days)
1230!$OMP THREADPRIVATE(min_growthinit_time)
1231  REAL(r_std), SAVE :: moiavail_always_tree = 1.0  !! moisture monthly availability above which moisture tendency doesn't matter
1232                                                   !!  - for trees (0-1, unitless)
1233!$OMP THREADPRIVATE(moiavail_always_tree)
1234  REAL(r_std), SAVE :: moiavail_always_grass = 0.6 !! moisture monthly availability above which moisture tendency doesn't matter
1235                                                   !! - for grass (0-1, unitless)
1236!$OMP THREADPRIVATE(moiavail_always_grass)
1237  REAL(r_std), SAVE :: t_always                    !! monthly temp. above which temp. tendency doesn't matter
1238!$OMP THREADPRIVATE(t_always)
1239  REAL(r_std), SAVE :: t_always_add = 10.          !! monthly temp. above which temp. tendency doesn't matter (C)
1240!$OMP THREADPRIVATE(t_always_add)
1241
1242  ! 3. Coefficients of equations
1243 
1244  REAL(r_std), SAVE :: gddncd_ref = 603.           !!
1245!$OMP THREADPRIVATE(gddncd_ref)
1246  REAL(r_std), SAVE :: gddncd_curve = 0.0091       !!
1247!$OMP THREADPRIVATE(gddncd_curve)
1248  REAL(r_std), SAVE :: gddncd_offset = 64.         !!
1249!$OMP THREADPRIVATE(gddncd_offset)
1250
1251
1252  !
1253  ! stomate_prescribe.f90
1254  !
1255
1256  ! 3. Coefficients of equations
1257
1258  REAL(r_std), SAVE :: bm_sapl_rescale = 40.       !!
1259!$OMP THREADPRIVATE(bm_sapl_rescale)
1260
1261
1262  !
1263  ! stomate_resp.f90
1264  !
1265
1266  ! 3. Coefficients of equations
1267
1268  REAL(r_std), SAVE :: maint_resp_min_vmax = 0.3   !!
1269!$OMP THREADPRIVATE(maint_resp_min_vmax)
1270  REAL(r_std), SAVE :: maint_resp_coeff = 1.4      !!
1271!$OMP THREADPRIVATE(maint_resp_coeff)
1272
1273
1274  !
1275  ! stomate_soilcarbon.f90
1276  !
1277
1278  ! 2. Arrays
1279
1280  ! 2.1 frac_carb_coefficients
1281
1282  REAL(r_std), SAVE :: frac_carb_ap = 0.004  !! from active pool: depends on clay content  (0-1, unitless)
1283                                             !! corresponding to frac_carb(:,iactive,ipassive)
1284!$OMP THREADPRIVATE(frac_carb_ap)
1285  REAL(r_std), SAVE :: frac_carb_sa = 0.93   !! from slow pool (0-1, unitless)
1286                                             !! corresponding to frac_carb(:,islow,iactive)
1287!$OMP THREADPRIVATE(frac_carb_sa)
1288  REAL(r_std), SAVE :: frac_carb_pa = 1.0   !! from passive pool (0-1, unitless)
1289                                             !! corresponding to frac_carb(:,ipassive,iactive)
1290!$OMP THREADPRIVATE(frac_carb_pa)
1291
1292  ! 3. Coefficients of equations
1293
1294  REAL(r_std), SAVE :: active_to_pass_clay_frac = 0.68  !! (0-1, unitless)
1295!$OMP THREADPRIVATE(active_to_pass_clay_frac)
1296  !! residence times in carbon pools (days)
1297  REAL(r_std), SAVE :: carbon_tau_iactive = 1.0   !! residence times in active pool (days)
1298!$OMP THREADPRIVATE(carbon_tau_iactive)
1299  REAL(r_std), SAVE :: carbon_tau_islow = 6.0      !! residence times in slow pool (days)
1300!$OMP THREADPRIVATE(carbon_tau_islow)
1301  REAL(r_std), SAVE :: carbon_tau_ipassive = 462.0   !! residence times in passive pool (days)
1302!$OMP THREADPRIVATE(carbon_tau_ipassive)
1303  !! priming parameter (-)
1304  REAL(r_std), SAVE :: priming_param_iactive = 493.66   !! priming parameter for the active pool (-)
1305!$OMP THREADPRIVATE(priming_param_iactive)
1306  REAL(r_std), SAVE :: priming_param_islow = 194.03   !! priming parameter for the slow pool (-)
1307!$OMP THREADPRIVATE(priming_param_islow)
1308  REAL(r_std), SAVE :: priming_param_ipassive = 136.54   !! priming parameter for the passive pool (-)
1309!$OMP THREADPRIVATE(priming_param_ipassvie)
1310  REAL(r_std), SAVE, DIMENSION(15) :: DOC_tau_labile = (/1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3,1.3/)   !! residence times of labile DOC (days) tuning
1311!$OMP THREADPRIVATE(DOC_tau_labile)
1312  REAL(r_std), SAVE, DIMENSION(15) :: DOC_tau_stable = (/60.4,1.3,1.3,60.4,1.3,1.3,60.4,1.3,60.4,1.3,1.3,1.3,1.3,1.3,1.3/)   !! residence times of labile DOC (days) tuning
1313!$OMP THREADPRIVATE(DOC_tau_stable)
1314 REAL(r_std), SAVE :: D_DOC = 1.06272e-05 !! diffusion coeficient for DOC (m2 d-1) coming from Burdige et al., 1999 in Ota et al., 2013
1315!$OMP THREADPRIVATE(D_DOC)
1316 REAL(r_std), SAVE :: red_factor = 1.  !! A parameter to reduce the DOC flux due to water flux in the soil column. Pure tunning set to 1 so no
1317                                       !! effect by default.
1318!$OMP THREADPRIVATE(red_factor)
1319 REAL(r_std), SAVE :: m_ads = 0.3   !! partition coeficient for adsorption of DOC (-) from Neff and Asner, 2001
1320!$OMP THREADPRIVATE(m_ads)
1321 REAL(r_std), SAVE :: b_ads = 0.15    !! desorption coeficient for adsorption of DOC (mg C g soil-1) from Neff and Asner, 2001
1322!$OMP THREADPRIVATE(b_ads)
1323REAL(r_std), SAVE :: kd_ads = 0.00805    !! distribution coefficient for adsorption of DOC (m3 water kg soil-1) from Moore et al., 1992
1324!$OMP THREADPRIVATE(kd_ads)
1325 REAL(r_std), SAVE, DIMENSION(15) :: CUE = (/0.5,0.35,0.35,0.5,0.35,0.35,0.5,0.35,0.5,0.5,0.5,0.5,0.5,0.5,0.5/)   !! Microbial carbon use efficiency(unitless, 0-1) from Camino-Serrano In prep 
1326!$OMP THREADPRIVATE(CUE)
1327  REAL(r_std), SAVE :: bulk_density_default = 1.65   !! soil bulk density (kg m-3)
1328!$OMP THREADPRIVATE(bulk_density)
1329  REAL(r_std), SAVE, DIMENSION(3) :: flux_tot_coeff = (/ 1.2, 1.4, .75/)
1330!$OMP THREADPRIVATE(flux_tot_coeff)
1331  REAL(r_std), SAVE :: soil_ph_default = 7.0   !! soil pH (pH units)
1332!$OMP THREADPRIVATE(soil_ph)
1333
1334  !
1335  ! stomate_turnover.f90
1336  !
1337
1338  ! 3. Coefficients of equations
1339
1340  REAL(r_std), SAVE :: new_turnover_time_ref = 20. !!(days)
1341!$OMP THREADPRIVATE(new_turnover_time_ref)
1342  REAL(r_std), SAVE :: leaf_age_crit_tref = 20.    !! (C)
1343!$OMP THREADPRIVATE(leaf_age_crit_tref)
1344  REAL(r_std), SAVE, DIMENSION(3) :: leaf_age_crit_coeff = (/ 1.5, 0.75, 10./) !! (unitless)
1345!$OMP THREADPRIVATE(leaf_age_crit_coeff)
1346
1347
1348  !
1349  ! stomate_vmax.f90
1350  !
1351 
1352  ! 1. Scalar
1353
1354  REAL(r_std), SAVE :: vmax_offset = 0.3        !! minimum leaf efficiency (unitless)
1355!$OMP THREADPRIVATE(vmax_offset)
1356  REAL(r_std), SAVE :: leafage_firstmax = 0.03  !! relative leaf age at which efficiency
1357                                                !! reaches 1 (unitless)
1358!$OMP THREADPRIVATE(leafage_firstmax)
1359  REAL(r_std), SAVE :: leafage_lastmax = 0.5    !! relative leaf age at which efficiency
1360                                                !! falls below 1 (unitless)
1361!$OMP THREADPRIVATE(leafage_lastmax)
1362  REAL(r_std), SAVE :: leafage_old = 1.         !! relative leaf age at which efficiency
1363                                                !! reaches its minimum (vmax_offset)
1364                                                !! (unitless)
1365!$OMP THREADPRIVATE(leafage_old)
1366  !
1367  ! stomate_season.f90
1368  !
1369
1370  ! 1. Scalar
1371
1372  REAL(r_std), SAVE :: gppfrac_dormance = 0.2  !! report maximal GPP/GGP_max for dormance (0-1, unitless)
1373!$OMP THREADPRIVATE(gppfrac_dormance)
1374  REAL(r_std), SAVE :: tau_climatology = 20.   !! tau for "climatologic variables (years)
1375!$OMP THREADPRIVATE(tau_climatology)
1376  REAL(r_std), SAVE :: hvc1 = 0.019            !! parameters for herbivore activity (unitless)
1377!$OMP THREADPRIVATE(hvc1)
1378  REAL(r_std), SAVE :: hvc2 = 1.38             !! parameters for herbivore activity (unitless)
1379!$OMP THREADPRIVATE(hvc2)
1380  REAL(r_std), SAVE :: leaf_frac_hvc = 0.33    !! leaf fraction (0-1, unitless)
1381!$OMP THREADPRIVATE(leaf_frac_hvc)
1382  REAL(r_std), SAVE :: tlong_ref_max = 303.1   !! maximum reference long term temperature (K)
1383!$OMP THREADPRIVATE(tlong_ref_max)
1384  REAL(r_std), SAVE :: tlong_ref_min = 253.1   !! minimum reference long term temperature (K)
1385!$OMP THREADPRIVATE(tlong_ref_min)
1386
1387  ! 3. Coefficients of equations
1388
1389  REAL(r_std), SAVE :: ncd_max_year = 3.
1390!$OMP THREADPRIVATE(ncd_max_year)
1391  REAL(r_std), SAVE :: gdd_threshold = 5.
1392!$OMP THREADPRIVATE(gdd_threshold)
1393  REAL(r_std), SAVE :: green_age_ever = 2.
1394!$OMP THREADPRIVATE(green_age_ever)
1395  REAL(r_std), SAVE :: green_age_dec = 0.5
1396!$OMP THREADPRIVATE(green_age_dec)
1397
1398END MODULE constantes_var
Note: See TracBrowser for help on using the repository browser.