source: branches/publications/ORCHIDEE-LEAK-r5919/src_parameters/constantes_var.f90 @ 5925

Last change on this file since 5925 was 5315, checked in by ronny.lauerwald, 6 years ago

Bug fix DOC inputs in floodplains and swamps

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