source: branches/publications/ORCHIDEE_gmd-2018-261/src_parameters/constantes_mtc.f90

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

rev29012018

  • Property svn:keywords set to Date Revision
File size: 66.5 KB
Line 
1! =================================================================================================================================
2! MODULE       : constantes_mtc
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF         This module contains the standard values of the parameters for the 13 metaclasses of vegetation used by ORCHIDEE.
10!!
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S):
14!!
15!! REFERENCE(S) :
16!! - Kuppel, S. (2012): Doctoral Thesis, Assimilation de mesures de flux turbulents d'eau et de carbone dans un modÚle de la biosphÚre
17!! continentale
18!! - Kuppel, S., Peylin, P., Chevallier, F., Bacour, C., Maignan, F., and Richardson, A. D. (2012). Constraining a global ecosystem
19!! model with multi-site eddy-covariance data, Biogeosciences, 9, 3757-3776, DOI 10.5194/bg-9-3757-2012.
20!! - Wohlfahrt, G., M. Bahn, E. Haubner, I. Horak, W. Michaeler, K.Rottmar, U. Tappeiner, and A. Cemusca, 1999: Inter-specific
21!! variation of the biochemical limitation to photosynthesis and related leaf traits of 30 species from mountain grassland
22!! ecosystems under different land use. Plant Cell Environ., 22, 12811296.
23!! - Malhi, Y., Doughty, C., and Galbraith, D. (2011). The allocation of ecosystem net primary productivity in tropical forests,
24!! Philosophical Transactions of the Royal Society B-Biological Sciences, 366, 3225-3245, DOI 10.1098/rstb.2011.0062.
25!! - Earles, J. M., Yeh, S., and Skog, K. E. (2012). Timing of carbon emissions from global forest clearance, Nature Climate Change, 2,
26!! 682-685, Doi 10.1038/Nclimate1535.
27!! - Piao, S. L., Luyssaert, S., Ciais, P., Janssens, I. A., Chen, A. P., Cao, C., Fang, J. Y., Friedlingstein, P., Luo, Y. Q., and
28!! Wang, S. P. (2010). Forest annual carbon cost: A global-scale analysis of autotrophic respiration, Ecology, 91, 652-661,
29!! Doi 10.1890/08-2176.1.
30!! - Verbeeck, H., Peylin, P., Bacour, C., Bonal, D., Steppe, K., and Ciais, P. (2011). Seasonal patterns of co2 fluxes in amazon
31!! forests: Fusion of eddy covariance data and the orchidee model, Journal of Geophysical Research-Biogeosciences, 116,
32!! Artn G02018, Doi 10.1029/2010jg001544.
33!!
34!! SVN          :
35!! $HeadURL: $
36!! $Date$
37!! $Revision$
38!! \n
39!_ ================================================================================================================================
40
41MODULE constantes_mtc
42
43  USE defprec
44  USE constantes
45
46  IMPLICIT NONE
47
48  !
49  ! METACLASSES CHARACTERISTICS
50  !
51
52  INTEGER(i_std), PARAMETER :: nvmc = 13                         !! Number of MTCS fixed in the code (unitless)
53
54  CHARACTER(len=34), PARAMETER, DIMENSION(nvmc) :: MTC_name = &  !! description of the MTC (unitless)
55  & (/ 'bare ground                       ', &          !  1
56  &    'tropical  broad-leaved evergreen  ', &          !  2
57  &    'tropical  broad-leaved raingreen  ', &          !  3
58  &    'temperate needleleaf   evergreen  ', &          !  4
59  &    'temperate broad-leaved evergreen  ', &          !  5
60  &    'temperate broad-leaved summergreen', &          !  6
61  &    'boreal    needleleaf   evergreen  ', &          !  7
62  &    'boreal    broad-leaved summergreen', &          !  8
63  &    'boreal    needleleaf   summergreen', &          !  9
64  &    '          C3           grass      ', &          ! 10
65  &    '          C4           grass      ', &          ! 11
66  &    '          C3           agriculture', &          ! 12
67  &    '          C4           agriculture'  /)         ! 13
68
69
70  !
71  ! VEGETATION STRUCTURE
72  !
73  INTEGER(i_std),PARAMETER, DIMENSION(nvmc) :: leaf_tab_mtc  =  &                 !! leaf type (1-4, unitless)
74  & (/  4,   1,   1,   2,   1,   1,   2,   &                                      !! 1=broad leaved tree, 2=needle leaved tree
75  &     1,   2,   3,   3,   3,   3   /)                                           !! 3=grass 4=bare ground
76
77  CHARACTER(len=6), PARAMETER, DIMENSION(nvmc) :: pheno_model_mtc  =  &  !! which phenology model is used? (tabulated)
78  & (/  'none  ',   'none  ',   'moi   ',   'none  ',   'none  ',  &
79  &     'ncdgdd',   'none  ',   'ncdgdd',   'ngd   ',   'moigdd',  &
80  &     'moigdd',   'moigdd',   'moigdd'  /) 
81
82  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_tropical_mtc  =  &                       !! Is PFT tropical ? (true/false)
83  & (/ .FALSE.,   .TRUE.,    .TRUE.,    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
84  &    .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE. /)   
85
86  CHARACTER(LEN=5), PARAMETER, DIMENSION(nvmc) :: type_of_lai_mtc  =  &  !! Type of behaviour of the LAI evolution algorithm
87  & (/ 'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! for each vegetation type. (unitless)
88  &    'inter', 'inter', 'inter', 'inter', 'inter',  &                   !! Value of type_of_lai : mean or interp
89  &    'inter', 'inter', 'inter' /)
90
91  LOGICAL, PARAMETER, DIMENSION(nvmc) :: natural_mtc =  &                         !! natural?  (true/false)
92  & (/ .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,    .TRUE.,   .TRUE.,  &
93  &    .TRUE.,   .TRUE.,   .TRUE.,   .TRUE.,   .FALSE.,   .FALSE.  /)
94
95  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: veget_ori_fixed_mtc  =  &  !! Value for veget_ori for tests in
96  & (/ 0.2,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! 0-dim simulations (0-1, unitless)
97  &    0.0,   0.0,   0.8,   0.0,   0.0,   0.0  /)
98
99  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimax_mtc  =  &          !! laimax for maximum
100  & (/ 0.0,   8.0,   8.0,   4.0,   4.5,   4.5,   4.0,  &                !! See also type of lai interpolation
101  &    4.5,   4.0,   2.0,   2.0,   2.0,   2.0  /)                       !! @tex $(m^2.m^{-2})$ @endtex
102
103  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: llaimin_mtc  = &           !! laimin for minimum lai
104  & (/ 0.0,   8.0,   0.0,   4.0,   4.5,   0.0,   4.0,  &                !! See also type of lai interpolation (m^2.m^{-2})
105  &    0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                       !! @tex $(m^2.m^{-2})$ @endtex
106
107  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_presc_mtc  =  &     !! prescribed height of vegetation (m)
108  & (/  0.0,   30.0,   30.0,   20.0,   20.0,   20.0,   15.0,  &         !! Value for height_presc : one for each vegetation type
109  &    15.0,   15.0,    0.5,    0.6,    1.0,    1.0  /)
110
111  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: z0_over_height_mtc = &         !! Factor to calculate roughness height from
112  & (/  0.0, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625,  &         !! vegetation height (unitless)   
113  &  0.0625, 0.0625, 0.0625, 0.0625, 0.0625, 0.0625  /)
114
115  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ratio_z0m_z0h_mtc = &      !! Ratio between z0m and z0h values (roughness height for momentum and for heat)
116  & (/  1.0,    1.0,    1.0,    1.0,    1.0,    1.0,    1.0,  &         
117  &     1.0,    1.0,    1.0,    1.0,    1.0,    1.0  /)
118
119
120  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rveg_mtc  =  &             !! Potentiometer to set vegetation resistance (unitless)
121  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                !! Nathalie on March 28th, 2006 - from Fred Hourdin,
122  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0   /)
123
124  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: sla_mtc  =  &                       !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
125  & (/ 1.5E-2,   1.53E-2,   2.6E-2,   9.26E-3,     2E-2,   2.6E-2,   9.26E-3,  &
126  &    2.6E-2,    1.9E-2,   2.6E-2,    2.6E-2,   2.6E-2,   2.6E-2  /) 
127
128  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: slainit_mtc  =  &                       !! specif leaf area @tex $(m^2.gC^{-1})$ @endtex
129  & (/ 2.6E-2,    2.6E-2,   4.4E-2,    1.4E-2,   3.0E-2,   3.9E-2,   1.3E-2,  &
130  &    3.7E-2,    2.4E-2,   3.1E-2,    3.1E-2,   3.9E-2,   3.9E-2  /) 
131
132
133  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: availability_fact_mtc  =  &     !! calculate mortality in lpj_gap
134  & (/ undef,   0.14,  0.14,   0.10,   0.10,   0.10,   0.05,  &
135  &     0.05,   0.05,  undef,  undef,  undef,  undef  /)
136
137  !
138  ! EVAPOTRANSPIRATION (sechiba)
139  !
140  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc  =  &  !! Structural resistance.
141  & (/ 0.0,   25.0,   25.0,   25.0,   25.0,   25.0,   25.0,  &        !! @tex $(s.m^{-1})$ @endtex
142  &   25.0,   25.0,    2.5,    2.0,    2.0,    2.0   /)
143
144  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc  =  &                  !! A vegetation dependent constant used in the
145  & (/    0.0,   12.E-5,   12.E-5,   12.E-5,   12.E-5,   25.E-5,   12.E-5,  & !! calculation  of the surface resistance.
146  &    25.E-5,   25.E-5,   30.E-5,   30.E-5,   30.E-5,   30.E-5  /)           !! @tex $(kg.m^2.s^{-1})$ @endtex
147
148
149  !
150  ! WATER (sechiba)
151  !
152  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc  =  &        !! Volumetric available soil water capacity in each PFT
153  & (/ 150.0,   150.0,   150.0,   150.0,   150.0,   150.0,   150.0,  & !! @tex $(kg.m^{-3} of soil)$ @endtex
154  &    150.0,   150.0,   150.0,   150.0,   150.0,   150.0  /)         
155                                                                     
156
157  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref4m  =  &       !! Root profile description for the different
158  & (/ 5.0,   0.4,   0.4,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types. @tex $(m^{-1})$ @endtex
159  &    1.0,   0.8,   4.0,   1.0,   4.0,   1.0  /)                      !! These are the factor in the exponential which gets       
160                                                                       !! the root density as a function of depth
161                                                                       !! Values for zmaxh = 4.0 
162 
163  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref2m  =  &       !! Root profile description for the different
164  & (/ 5.0,   0.8,   0.8,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types.  @tex $(m^{-1})$ @endtex
165  &    1.0,   0.8,   4.0,   4.0,   4.0,   4.0  /)                      !! These are the factor in the exponential which gets       
166                                                                       !! the root density as a function of depth
167                                                                       !! Values for zmaxh = 2.0
168
169  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc  =  &  !! Fraction of rain intercepted by the canopy
170  & (/ 30.0,   30.0,   30.0,   30.0,   30.0,   30.0,   30.0,  &        !! (0-100, unitless)
171  &    30.0,   30.0,   30.0,   30.0,   30.0,   30.0  /)
172
173
174  !
175  ! ALBEDO (sechiba)
176  !
177  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_vis_mtc  =  &  !! Minimum snow albedo value for each vegetation type
178  & (/ 0.50,    0.0,    0.0,   0.15,   0.14,   0.14,   0.15,  &        !! after aging (dirty old snow) (unitless), visible albedo
179  &    0.14,   0.22,   0.35,   0.35,   0.35,   0.35  /)                !! Source : Values are from the Thesis of S. Chalita (1992), optimized on 04/07/2016
180
181  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_nir_mtc  =  &  !! Minimum snow albedo value for each vegetation type
182  & (/ 0.35,    0.0,    0.0,   0.14,   0.14,   0.14,   0.14,  &        !! after aging (dirty old snow) (unitless), near infrared albedo
183  &    0.14,   0.14,   0.18,   0.18,   0.18,   0.18  /)                !! Source : Values are from the Thesis of S. Chalita (1992)
184
185  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_vis_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
186  & (/ 0.45,    0.0,    0.0,   0.10,   0.06,   0.11,   0.10,  &        !! as it will be used in condveg_snow (unitless), visible albedo
187  &    0.11,   0.18,   0.60,   0.60,   0.60,   0.60  /)                !! Source : Values are from the Thesis of S. Chalita (1992), optimized on 04/07/2016
188
189  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_nir_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
190  & (/ 0.45,    0.0,    0.0,   0.06,   0.06,   0.11,   0.06,  &        !! as it will be used in condveg_snow (unitless), near infrared albedo
191  &    0.11,   0.11,   0.52,   0.52,   0.52,   0.52  /)                !! Source : Values are from the Thesis of S. Chalita (1992)
192
193  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc  =  &    !! leaf albedo of vegetation type, visible albedo, optimized on 04/07/2016
194  & (/ 0.00,   0.0397, 0.0474, 0.0386, 0.0484, 0.0411, 0.041,  &       !! (unitless)
195  &    0.0541, 0.0435, 0.0524, 0.0508, 0.0509, 0.0606  /)
196
197  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc  =  &    !! leaf albedo of vegetation type, near infrared albedo, optimized on 04/07/2016
198  & (/ 0.00,   0.227,  0.214,  0.193,  0.208,  0.244,  0.177,  &       !! (unitless)
199  &    0.218,  0.213,  0.252,  0.265,  0.272,  0.244  /)
200
201  !
202  ! SOIL - VEGETATION
203  !
204  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_mtc  =  &       !! The soil tile number for each vegetation
205  & (/ 1,   2,   2,   2,   2,   2,   2,  &                                   
206  &    2,   2,   3,   3,   3,   3  /)                                         
207
208
209  !
210  ! PHOTOSYNTHESIS
211  !
212  !-
213  ! 1 .CO2
214  !-
215  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c4_mtc  =  &                            !! flag for C4 vegetation types (true/false)
216  & (/ .FALSE.,  .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
217  &    .FALSE.,  .FALSE.,   .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.  /)
218
219  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc  =  &     !! values used for vcmax when STOMATE is not
220  & (/  0.0,   40.0,   50.0,   30.0,   35.0,   40.0,   30.0,  &      !! activated @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
221  &    40.0,   35.0,   60.0,   60.0,   70.0,   70.0  /)
222
223  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: downregulation_co2_coeff_mtc  =  &  !! coefficient for CO2 downregulation
224  & (/  0.0,   0.38,   0.38,   0.28,   0.28,   0.28,   0.22,  &
225  &     0.22,  0.22,   0.26,   0.26,   0.26,   0.26 /)
226
227  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmC_mtc  = &            !! Energy of activation for KmC (J mol-1)
228  & (/undef,  79430.,  79430.,  79430.,  79430.,  79430.,  79430.,  &  !! See Medlyn et al. (2002)
229  &  79430.,  79430.,  79430.,  79430.,  79430.,  79430.  /)           !! from Bernacchi al. (2001)
230
231  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmO_mtc  = &            !! Energy of activation for KmO (J mol-1)
232  & (/undef,  36380.,  36380.,  36380.,  36380.,  36380.,  36380.,  &  !! See Medlyn et al. (2002)
233  &  36380.,  36380.,  36380.,  36380.,  36380.,  36380.  /)           !! from Bernacchi al. (2001)
234
235REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Sco_mtc  = &            !! Energy of activation for Sco (J mol-1)
236  & (/undef, -24460., -24460., -24460., -24460., -24460., -24460.,  &  !! See Table 2 of Yin et al. (2009)
237  & -24460., -24460., -24460., -24460., -24460., -24460.  /)           !! Value for C4 plants is not mentioned - We use C3 for all plants
238
239
240  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gamma_star_mtc  = &     !! Energy of activation for gamma_star (J mol-1)
241  & (/undef,  37830.,  37830.,  37830.,  37830.,  37830.,  37830.,  &  !! See Medlyn et al. (2002) from Bernacchi al. (2001)
242  &  37830.,  37830.,  37830.,  37830.,  37830.,  37830.  /)           !! for C3 plants - We use the same values for C4 plants
243
244  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Vcmax_mtc  = &          !! Energy of activation for Vcmax (J mol-1)
245  & (/undef,  71513.,  71513.,  71513.,  71513.,  71513.,  71513.,  &  !! See Table 2 of Yin et al. (2009) for C4 plants
246  &  71513.,  71513.,  71513.,  67300.,  71513.,  67300.  /)           !! and Kattge & Knorr (2007) for C3 plants (table 3)
247
248  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Jmax_mtc  = &            !! Energy of activation for Jmax (J mol-1)
249  & (/undef,  49884.,  49884.,  49884.,  49884.,  49884.,  49884.,  &   !! See Table 2 of Yin et al. (2009) for C4 plants
250  &  49884.,  49884.,  49884.,  77900.,  49884.,  77900.  /)            !! and Kattge & Knorr (2007) for C3 plants (table 3)
251
252  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: aSV_mtc     = &            !! a coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1)
253  & (/undef,  668.39,  668.39,  668.39,  668.39,  668.39,  668.39,  &   !! See Table 3 of Kattge & Knorr (2007)
254  &  668.39,  668.39,  668.39,  641.64,  668.39,  641.64  /)            !! For C4 plants, we assume that there is no
255                                                                        !! acclimation and that at for a temperature of 25°C, aSV is the same for both C4 and C3 plants (no strong jusitification - need further parametrization)
256
257  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bSV_mtc     = &            !! b coefficient of the linear regression (a+bT) defining the Entropy term for Vcmax (J K-1 mol-1 °C-1)
258  & (/undef,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,  &   !! See Table 3 of Kattge & Knorr (2007)
259  &   -1.07,   -1.07,   -1.07,      0.,   -1.07,      0.  /)            !! We assume No acclimation term for C4 plants
260
261  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_mtc  =  &  !! minimum photosynthesis temperature (deg C)
262  & (/  undef,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0,   -4.0,  & 
263  &      -4.0,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0  /)
264
265  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_mtc  =  &  !! maximum photosynthesis temperature (deg C)
266  & (/  undef,   55.0,    55.0,   55.0,   55.0,   55.0,   55.0,  & 
267  &      55.0,   55.0,    55.0,   55.0,   55.0,   55.0  /)
268
269  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: aSJ_mtc     = &            !! a coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1)
270  & (/undef,  659.70,  659.70,  659.70,  659.70,  659.70,  659.70,  &   !! See Table 3 of Kattge & Knorr (2007)
271  &  659.70,  659.70,  659.70,    630.,  659.70,    630.  /)            !! and Table 2 of Yin et al. (2009) for C4 plants
272
273  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: bSJ_mtc     = &            !! b coefficient of the linear regression (a+bT) defining the Entropy term for Jmax (J K-1 mol-1 °C-1)
274  & (/undef,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,  &   !! See Table 3 of Kattge & Knorr (2007)
275  &   -0.75,   -0.75,   -0.75,      0.,   -0.75,      0.  /)            !! We assume no acclimation term for C4 plants
276
277  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Vcmax_mtc  = &           !! Energy of deactivation for Vcmax (J mol-1)
278  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! Medlyn et al. (2002) also uses 200000. for C3 plants (same value than D_Jmax)
279  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! 'Consequently', we use the value of D_Jmax for C4 plants
280
281  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Jmax_mtc  = &            !! Energy of deactivation for Jmax (J mol-1)
282  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! See Table 2 of Yin et al. (2009)
283  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! Medlyn et al. (2002) also uses 200000. for C3 plants
284
285  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gm_mtc  = &              !! Energy of activation for gm (J mol-1)
286  & (/undef,  49600.,  49600.,  49600.,  49600.,  49600.,  49600.,  &   !! See Table 2 of Yin et al. (2009)
287  &  49600.,  49600.,  49600.,   undef,  49600.,   undef  /)           
288                 
289  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S_gm_mtc  = &              !! Entropy term for gm (J K-1 mol-1)
290  & (/undef,   1400.,   1400.,   1400.,   1400.,   1400.,   1400.,  &   !! See Table 2 of Yin et al. (2009)
291  &   1400.,   1400.,   1400.,   undef,   1400.,   undef  /) 
292                 
293  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_gm_mtc  = &              !! Energy of deactivation for gm (J mol-1)
294  & (/undef, 437400., 437400., 437400., 437400., 437400., 437400.,  &   !! See Table 2 of Yin et al. (2009)
295  & 437400., 437400., 437400.,   undef, 437400.,   undef  /)           
296
297  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Rd_mtc  = &              !! Energy of activation for Rd (J mol-1)
298  & (/undef,  46390.,  46390.,  46390.,  46390.,  46390.,  46390.,  &   !! See Table 2 of Yin et al. (2009)
299  &  46390.,  46390.,  46390.,  46390.,  46390.,  46390.  /)           
300
301  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Vcmax25_mtc  =  &          !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
302  & (/ undef,   50.0,    65.0,    45.0,   45.0,   55.0,   45.0,  &      !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
303  &     45.0,   35.0,    70.0,    70.0,   70.0,   70.0  /)
304
305  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: arJV_mtc    = &            !! a coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio (mu mol e- (mu mol CO2)-1)
306  & (/undef,    2.59,    2.59,    2.59,    2.59,    2.59,    2.59,  &   !! See Table 3 of Kattge & Knorr (2007)
307  &    2.59,    2.59,    2.59,   1.715,    2.59,   1.715  /)            !! For C4 plants, we assume that there is no
308                                                                        !! acclimation and that for a temperature of 25°C, aSV is the same for both C4 and C3 plants (no strong jusitification - need further parametrization)
309
310  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: brJV_mtc    = &            !! b coefficient of the linear regression (a+bT) defining the Jmax25/Vcmax25 ratio ((mu mol e- (mu mol CO2)-1) (°C)-1)
311  & (/undef,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  &   !! See Table 3 of Kattge & Knorr (2007)
312  &  -0.035,  -0.035,  -0.035,      0.,  -0.035,      0.  /)            !! We assume No acclimation term for C4 plants
313
314  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmC25_mtc  = &             !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
315  & (/undef,   404.9,   404.9,   404.9,   404.9,  404.9,   404.9,  &    !! See Table 2 of Yin et al. (2009) for C4
316  &   404.9,   404.9,   404.9,    650.,   404.9,   650.  /)             !! and Medlyn et al (2002) for C3
317
318  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmO25_mtc  = &             !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
319  & (/undef, 278400., 278400., 278400., 278400., 278400., 278400.,  &   !! See Table 2 of Yin et al. (2009) for C4 plants and Medlyn et al. (2002) for C3
320  & 278400., 278400., 278400., 450000., 278400., 450000.  /)           
321
322REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Sco25_mtc  = &             !! Relative CO2 /O2 specificity factor for Rubisco at 25°C (bar bar-1)
323  & (/undef,   2800.,   2800.,   2800.,   2800.,   2800.,   2800.,  &   !! See Table 2 of Yin et al. (2009)
324  &   2800.,   2800.,   2800.,   2590.,   2800.,   2590.  /)           
325
326  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gm25_mtc  = &              !! Mesophyll diffusion conductance at 25°C (mol m-2 s-1 bar-1)
327  & (/undef,     0.4,     0.4,     0.4,     0.4,    0.4,      0.4,  &   !! See legend of Figure 6 of Yin et al. (2009)
328  &     0.4,     0.4,     0.4,   undef,     0.4,  undef  /)             !! and review by Flexas et al. (2008) - gm is not used for C4 plants
329
330  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gamma_star25_mtc  = &      !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
331  & (/undef,   42.75,   42.75,   42.75,   42.75,   42.75,   42.75,  &   !! See Medlyn et al. (2002) for C3 plants - For C4 plants, we use the same value (probably uncorrect)
332  &   42.75,   42.75,   42.75,   42.75,   42.75,   42.75  /)   
333
334  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
335  & (/undef,    0.85,    0.85,    0.85,    0.85,    0.85,  0.85,  &     !! See Table 2 of Yin et al. (2009)
336  &    0.85,    0.85,    0.85,    0.72,    0.85,    0.72  /)           
337
338  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
339  & (/undef,    0.14,    0.14,    0.14,    0.14,    0.14,  0.14,  &     !! See Table 2 of Yin et al. (2009)
340  &    0.14,    0.14,    0.14,    0.20,    0.14,    0.20  /)           
341
342  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: g0_mtc  = &                !! Residual stomatal conductance when irradiance approaches zero (mol CO2 m−2 s−1 bar−1)
343  & (/undef, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625,  &   !! Value from ORCHIDEE - No other reference.
344  & 0.00625, 0.00625, 0.00625, 0.01875, 0.00625, 0.01875  /)            !! modofy to account for the conversion for conductance to H2O to CO2
345
346  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: h_protons_mtc  = &         !! Number of protons required to produce one ATP (mol mol-1)
347  & (/undef,      4.,      4.,      4.,      4.,      4.,    4.,  &     !! See Table 2 of Yin et al. (2009) - h parameter
348  &      4.,      4.,      4.,      4.,      4.,      4.  /)           
349
350  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpsir_mtc = &              !! Fraction of PSII e− transport rate
351  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! partitioned to the C4 cycle (-)
352  &   undef,   undef,   undef,     0.4,   undef,    0.4  /)             !! See Table 2 of Yin et al. (2009) - x parameter       
353 
354  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fQ_mtc = &                 !! Fraction of electrons at reduced plastoquinone
355  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! that follow the Q-cycle (-) - Values for C3 platns are not used
356  &   undef,   undef,   undef,      1.,   undef,     1.  /)             !! See Table 2 of Yin et al. (2009)         
357
358  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpseudo_mtc = &            !! Fraction of electrons at PSI that follow
359  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! pseudocyclic transport (-) - Values for C3 platns are not used
360  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)             !! See Table 2 of Yin et al. (2009)   
361
362  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kp_mtc = &                 !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
363  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See Table 2 of Yin et al. (2009)
364  &   undef,   undef,   undef,     0.7,   undef,    0.7  /)                 
365
366  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_mtc = &              !! Fraction of PSII activity in the bundle sheath (-)
367  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
368  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)                 
369
370  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gbs_mtc = &                !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
371  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
372  &   undef,   undef,   undef,   0.003,   undef,  0.003  /)   
373
374  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: theta_mtc = &              !! Convexity factor for response of J to irradiance (-)
375  & (/undef,     0.7,     0.7,     0.7,     0.7,    0.7,    0.7,  &     !! See Table 2 of Yin et al. (2009)
376  &     0.7,     0.7,     0.7,     0.7,     0.7,    0.7  /)
377
378  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_LL_mtc = &           !! Conversion efficiency of absorbed light into J at strictly limiting light (mol e− (mol photon)−1)
379  & (/undef,     0.3,     0.3,     0.3,     0.3,    0.3,    0.3,  &     !! See comment from Yin et al. (2009) after eq. 4
380  &     0.3,     0.3,     0.3,     0.3,     0.3,    0.3  /)             !! alpha value from Medlyn et al. (2002)   
381                                                                        !! 0.093 mol CO2 fixed per mol absorbed photons
382                                                                        !! times 4 mol e- per mol CO2 produced
383
384  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_vcmax_mtc = &       !! Water stress on vcmax
385  & (/    1.,     1.,     1.,       1.,      1.,     1.,      1., &
386  &      1.,     1.,     1.,       1.,      1.,     1.  /)
387
388  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_gs_mtc = &          !! Water stress on gs
389  & (/    0.,     0.,     0.,       0.,      0.,     0.,      0., &
390  &      0.,     0.,     0.,       0.,      0.,     0.  /)
391
392  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: stress_gm_mtc = &          !! Water stress on gm
393  & (/    0.,     0.,     0.,       0.,      0.,     0.,      0., &
394  &      0.,     0.,     0.,       0.,      0.,     0.  /)
395   
396  !-
397  ! 2 .Stomate
398  !-
399  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc  =  &     !! extinction coefficient of the Monsi&Saeki
400  & (/ 0.5,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &             !! relationship (1953) ((m2[ground]) (m-2[leaf]))
401  &    0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
402  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_vegetfrac_mtc  =  &     !! extinction coefficient used for defining the fraction
403  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                       !!  of bare soil (unitless)
404  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
405  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_N_mtc  =  &    !! extinction coefficient of the leaf N content profile within the canopy
406  & (/ 0.15,  0.15,  0.15,  0.15,  0.15,  0.15,  0.15,  &             !! ((m2[ground]) (m-2[leaf]))
407  &    0.15,  0.15,  0.15,  0.15,  0.15,  0.15  /)                    !! based on Dewar et al. (2012, value of 0.18), on Carswell et al. (2000, value of 0.11 used in OCN)
408  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nue_opt_mtc = &           !! Nitrogen use efficiency of Vcmax
409  & (/ undef,   22.,    22.,    20.,    33.,    33.,    20., &         !! ((mumol[CO2] s-1) (gN[leaf])-1)
410  &      33.,   22.,    45.,    45.,    60.,    60.     /)             !! based on the work of Kattge et al. (2009, GCB)
411     
412  !
413  ! ALLOCATION (stomate)
414  !
415  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: R0_mtc = &              !! Default root allocation (0-1, unitless)
416  & (/ undef,   0.30,   0.30,   0.30,   0.30,  0.30,    0.30, &
417  &     0.30,   0.30,   0.30,   0.30,   0.30,  0.30 /)                   
418
419  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S0_mtc = &              !! Default sapwood allocation (0-1, unitless)
420  & (/ undef,   0.25,   0.25,   0.30,   0.30,  0.30,    0.30, &
421  &     0.30,   0.30,   0.30,   0.30,   0.30,  0.30 /)                   
422
423  !
424  ! RESPIRATION (stomate)
425  !
426  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_mtc  =  &  !! fraction of GPP which is lost as growth respiration
427  & (/  undef,   0.28,   0.28,   0.28,   0.28,   0.28,   0.28,  &
428  &      0.28,   0.28,   0.28,   0.28,   0.28,   0.28  /)
429
430  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_maint_init_mtc  =   &              !! maintenance respiration coefficient
431  & (/   undef,   3.06E-2,   3.06E-2,   6.46E-2,   6.46E-2,   6.46E-2,   6.46E-2,  &  !! at 10 deg C - from Sitch et al. 2003 and Zaehle (OCN)
432  &    6.46E-2,   6.46E-2,   6.46E-2,   6.46E-2,   6.46E-2,   6.46E-2  /)             !! @tex $(gC.gN^{-1}.day^{-1})$ @endtex
433
434  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tref_maint_resp_mtc  =   &              !! maintenance respiration Temperature coefficient (deg C)
435  & (/   undef,     10.02,     10.02,     10.02,     10.02,     10.02,     10.02,  & 
436  &      10.02,     10.02,     10.02,     10.02,     10.02,     10.02  /)             
437  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_maint_resp_mtc  =   &              !! maintenance respiration Temperature coefficient (deg C)
438  & (/   undef,    -46.02,    -46.02,    -46.02,    -46.02,    -46.02,    -46.02,  & 
439  &     -46.02,    -46.02,    -46.02,    -46.02,    -46.02,    -46.02  /)             
440  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: e0_maint_resp_mtc  =   &              !! maintenance respiration Temperature coefficient (unitless)
441  & (/   undef,   308.56,     308.56,   308.56,     308.56,   308.56,     308.56,  & 
442  &     308.56,   308.56,     308.56,   308.56,     308.56,   308.56  /)             
443
444  !
445  ! SOM decomposition (stomate)
446  !
447  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_leaf_mtc = &        !! Lignin/C ratio of leaf pool (unitless)
448  & (/  undef,   0.18,   0.18,   0.24,   0.18,   0.18,   0.24,  &   !! based on CN from White et al. (2000)       
449  &      0.18,   0.24,   0.09,   0.09,   0.09,   0.09  /)
450
451  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_sapabove_mtc = &    !! Lignin/C ratio of sapabove pool (unitless)
452  & (/  undef,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
453  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
454
455  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_sapbelow_mtc = &    !! Lignin/C ratio of sapbelow pool (unitless)
456  & (/  undef,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
457  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
458
459  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_heartabove_mtc = &  !! Lignin/C ratio of heartabove pool (unitless)
460  & (/  undef,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
461  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
462
463  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_heartbelow_mtc = &  !! Lignin/C ratio of heartbelow pool (unitless)
464  & (/  undef,   0.23,   0.23,   0.29,   0.23,   0.23,   0.29,  &   !! based on CN from White et al. (2000)       
465  &      0.23,   0.29,   0.09,   0.09,   0.09,   0.09  /)
466
467  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_fruit_mtc = &       !! Lignin/C ratio of fruit pool (unitless)
468  & (/  undef,   0.09,   0.09,   0.09,   0.09,   0.09,   0.09,  &   !! based on CN from White et al. (2000)       
469  &      0.09,   0.09,   0.09,   0.09,   0.09,   0.09  /)
470
471  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_root_mtc = &        !! Lignin/C ratio of root pool (unitless)
472  & (/  undef,   0.22,   0.22,   0.22,   0.22,   0.22,   0.22,  &   !! based on CN from White et al. (2000)       
473  &      0.22,   0.22,   0.22,   0.22,   0.22,   0.22  /)
474
475  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_carbres_mtc = &     !! Lignin/C ratio of carbres pool (unitless)
476  & (/  undef,   0.18,   0.18,   0.24,   0.18,   0.18,   0.24,  &   !! based on CN from White et al. (2000)       
477  &      0.18,   0.24,   0.09,   0.09,   0.09,   0.09  /)
478
479  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: LC_labile_mtc = &      !! Lignin/C ratio of labile pool (unitless)
480  & (/  undef,   0.18,   0.18,   0.24,   0.18,   0.18,   0.24,  &   !! based on CN from White et al. (2000)       
481  &      0.18,   0.24,   0.09,   0.09,   0.09,   0.09  /)
482
483  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: decomp_factor_mtc  =  &  !! Multpliactive factor modifying the standard decomposition factor for each SOM pool
484  & (/  undef,     1.,     1.,     1.,     1.,     1.,     1.,  &         
485  &        1.,     1.,     1.,     1.,    1.2,    1.4  /)
486  !
487  ! STAND STRUCTURE
488  !
489  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tree_ff_mtc = &                          !! Tree form factor to reduce
490          &(/ undef,  0.6,    0.6,   0.6,   0.6,   0.6,   0.8, &                              !! the volume of a cylinder
491          &     0.8,  0.8,  undef, undef, undef, undef /)                                     !! to the volume of the real tree shape
492
493  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_density_mtc = &                     !! Wood density @tex $(gC.m^{-3})$ @endtex
494  &(/   0.0,   2.e5,   2.e5,   2.e5,   2.e5,   2.e5,   2.e5,  &                       !! Current values are taken from the trunk.
495  &    2.e5,  2.e5,    2.e5,   2.e5,   2.e5,   2.e5  /)                               !! forestry-branch has more realistic values
496                                                                                      !! in it. Source: AFOCEL 2006
497
498  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune1_mtc = &                       !! cn_area = pipe_tune1*...
499  &(/ undef,  100.,  100.,  100.,  100.,  100.,  100., &                              !!    stem diameter**pipe_tune_exp_coeff
500  &    100.,  100., undef, undef, undef, undef /) 
501       
502  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune2_mtc = &                       !! height=pipe_tune2 * diameter**pipe_tune3
503  &(/ undef,   40.,   40.,   40.,   40.,   40.,   40., &
504  &     40.,   40., undef, undef, undef, undef /) 
505
506  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune3_mtc = &                       !! height=pipe_tune2 * diameter**pipe_tune3
507  &(/ undef,   0.5,   0.5,   0.5,   0.5,   0.5,  0.5, &
508  &     0.5,   0.5, undef, undef, undef, undef /)   
509     
510  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune4_mtc = &                       !! CHECK - needed for stem diameter
511  &(/ undef,   0.3,   0.3,   0.3,   0.3,   0.3,   0.3, &
512        0.3,   0.3, undef, undef, undef, undef /)
513
514  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_k1_mtc = &                          !! CHECK
515  &(/ undef,  8.e3,  8.e3,  8.e3,  8.e3,  8.e3,  8.e3, &
516  &    8.e3,  8.e3, undef, undef, undef, undef /) 
517
518  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pipe_tune_exp_coeff_mtc = &              !! cn_area = pipe_tune1*... 
519  &(/ undef,   1.6,   1.6,   1.6,   1.6,   1.6,   1.6, &                              !!    stem diameter**pipe_tune_exp_coeff
520  &     1.6,   1.6, undef, undef, undef, undef /) 
521     
522  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: mass_ratio_heart_sap_mtc = &             !! mass ratio (heartwood+sapwood)/heartwood
523  &(/ undef,    3.,    3.,    3.,    3.,    3.,    3., &
524  &      3.,    3., undef, undef, undef, undef /)
525
526  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: canopy_cover_mtc = &                     !! Prescribed canopy cover (1-gap fraction)
527  & (/ undef,    0.9,   0.9,   0.7,   0.7,   0.7,   0.6, &                            !! of a canopy (unitless)
528  &      0.5,    0.5,   0.9,   0.9,   0.9,   0.9 /) 
529
530  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: nmaxtrees_mtc = &                     !! Initial number of trees per ha. This parameter is
531  & (/  -9999,   2000,   2000,   7333,   8000,  15000, 15000,  &                      !! used at .firstcall. and after clearcuts
532  &     15000,  15000,  10000,  10000,  10000,  10000 /)                              !! the value is used by the allometric allocation
533                                                                                      !! and forestry subroutines.
534                                                                                      !! Values from DOFOCO run.def
535
536  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_init_min_mtc = &                  !! The minimum height (m) of a tree sapling when a forest
537  &(/ undef,    2.,    2.,    2.,    2.,    2.,    3., &                              !! stand is established. Owing to the allometric
538  &      3.,    3.,   0.1,   0.1,   0.1,   0.1 /)                                     !! relationship this setting determines all
539                                                                                      !! biomass components of a newly establised stand
540
541  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: height_init_max_mtc = &                  !! The maximum height (m) of a tree sapling when a forest
542  &(/ undef,    3.,    3.,    3.,    3.,    3.,    4., &                              !! stand is established.
543  &      4.,    4.,   0.2,   0.2,   0.2,   0.2 /)                                     
544                                                                                     
545
546  !
547  ! FIRE (stomate)
548  !
549  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc  =  &         !! flamability: critical fraction of water
550  & (/  undef,   0.15,   0.25,   0.25,   0.25,   0.25,   0.25,  &  !! holding capacity (0-1, unitless)
551  &      0.25,   0.25,   0.25,   0.25,   0.35,   0.35  /)
552
553  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc  =  &       !! fire resistance (0-1, unitless)
554  & (/ undef,   0.95,   0.90,   0.90,   0.90,   0.90,   0.90,  &
555  &    0.90,    0.90,    0.0,    0.0,    0.0,    0.0 /) 
556
557
558  !
559  ! FLUX - LUC
560  !
561  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_1_mtc  =  &   !! Coeff of biomass export for the year
562  & (/  undef,   0.897,   0.897,   0.597,   0.597,   0.597,   0.597,  &   !! (0-1, unitless)
563  &     0.597,   0.597,   0.597,   0.597,   0.597,   0.597  /)
564
565  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_10_mtc  =  &  !! Coeff of biomass export for the decade
566  & (/  undef,   0.103,   0.103,   0.299,   0.299,   0.299,   0.299,  &   !! (0-1, unitless)
567  &     0.299,   0.299,   0.299,   0.403,   0.299,   0.403  /) 
568
569  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_100_mtc  =  & !! Coeff of biomass export for the century
570  & (/  undef,     0.0,     0.0,   0.104,   0.104,   0.104,   0.104,  &   !! (0-1, unitless)
571  &     0.104,   0.104,   0.104,     0.0,   0.104,     0.0  /)
572
573
574  !
575  ! PHENOLOGY
576  !
577  !-
578  ! 1. Stomate
579  !-
580  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_max_to_happy_mtc  =  &  !! threshold of LAI below which plant uses carbohydrate reserves
581  & (/  undef,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &
582  &       0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
583
584  REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc  =  &          !! maximum LAI, PFT-specific
585  & (/ undef,   7.0,   7.0,   5.0,   5.0,   5.0,   4.5,  &               !! @tex $(m^2.m^{-2})$ @endtex
586  &      4.5,   3.0,   2.5,   2.5,   5.0,   5.0  /)
587
588  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc  =  &     !! type of phenology (0-4, unitless)
589  & (/  0,   1,   3,   1,   1,   2,   1,  &                              !! 0=bare ground 1=evergreen,  2=summergreen,
590  &     2,   2,   4,   4,   2,   3  /)                                   !! 3=raingreen,  4=perennial
591  !-
592  ! 2. Leaf Onset
593  !-
594  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc  =  &    !! critical gdd, tabulated (C),
595  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant c of aT^2+bT+c
596  &     undef,   undef,   320.0,   400.0,   320.0,   700.0  /)
597
598  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc  =  &    !! critical gdd, tabulated (C),
599  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant b of aT^2+bT+c
600  &     undef,   undef,    6.25,     0.0,    6.25,     0.0  /)
601
602  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc  =  &    !! critical gdd, tabulated (C),
603  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  &  !! constant a of aT^2+bT+c
604  &     undef,   undef,   0.03125,     0.0,  0.0315,   0.0  /)
605
606  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_moigdd_t_crit_mtc  = &  !! temperature threshold for C4 grass(C)
607  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  & 
608  &     undef,   undef,     undef,    22.0,   undef,   undef  /)
609
610  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc  =  &            !! critical ngd, tabulated.
611  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! Threshold -5 degrees (days)
612  &     undef,    17.0,   undef,   undef,   undef,   undef  /)
613
614  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc  =  &         !! critical temperature for the ncd vs. gdd
615  & (/  undef,   undef,   undef,   undef,   undef,     5.0,   undef,  &    !! function in phenology (C)
616  &       0.0,   undef,   undef,   undef,   undef,   undef  /)
617
618  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc  =  &            !! critical humidity (relative to min/max)
619  & (/  undef,   undef,   0.5,   undef,   undef,   undef,   undef, &       !! for phenology (unitless)
620  &     undef,   undef,   0.5,     0.5,     0.5,     0.5  /)
621
622  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_min_time_mtc  =  &        !! minimum time elapsed since
623  & (/  undef,   undef,   50.0,   undef,   undef,   undef,   undef,  &     !! moisture minimum (days)
624  &     undef,   undef,   36.0,    35.0,    75.0,    75.0  /) 
625
626  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_root_mtc  =  &            !! roots longevity (days)
627  & (/  undef,  365.,   365.,    365.,    365.,   365.,   365.,  &
628  &      365.,  365.,   365.,    365.,    365.,   365.  /)
629
630
631  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_sap_mtc  =  &             !! time (days) 
632  & (/  undef,   730.0,   730.0,   730.0,   730.0,   730.0,   730.0,  &
633  &     730.0,   730.0,   730.0,   730.0,   730.0,   730.0  /)
634
635  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_leafinit_mtc  =  &  !! time to attain the initial foliage using the carbohydrate reserve
636  & (/  undef,   10.,   10.,   10.,   10.,   10.,   10.,  &
637  &       10.,   10.,   10.,   10.,   10.,   10.  /)
638
639  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_fruit_mtc  =  &           !! fruit lifetime (days)
640  & (/  undef,  90.0,    90.0,    90.0,    90.0,   90.0,   90.0,  &
641  &      90.0,  90.0,   undef,   undef,   undef,   undef  /)
642
643  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ecureuil_mtc  =  &            !! fraction of primary leaf and root allocation
644  & (/  undef,   0.0,   1.0,   0.0,   0.0,   1.0,   0.0,  &                !! put into reserve (0-1, unitless)
645  &       1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
646
647  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_min_mtc  =  &           !! NEW - allocation above/below = f(age)
648  & (/  undef,   0.2,     0.2,     0.2,     0.2,    0.2,   0.2,  &         !! - 30/01/04 NV/JO/PF
649  &       0.2,   0.2,   undef,   undef,   undef,   undef  /)
650
651  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_max_mtc  =  &           !! NEW - allocation above/below = f(age)
652  & (/  undef,   0.8,     0.8,     0.8,     0.8,    0.8,   0.8,  &         !! - 30/01/04 NV/JO/PF
653  &       0.8,   0.8,   undef,   undef,   undef,   undef  /)
654
655  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: demi_alloc_mtc  =  &          !! NEW - allocation above/below = f(age)
656  & (/  undef,   5.0,     5.0,     5.0,     5.0,    5.0,   5.0,  &         !! - 30/01/04 NV/JO/PF
657  &       5.0,   5.0,   undef,   undef,   undef,   undef  /)
658
659  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaflife_mtc  =  &            !! leaf longevity, tabulated (??units??)
660  & (/  undef,   0.5,   2.0,   0.33,   1.0,   2.0,   0.33,  &
661  &       2.0,   2.0,   2.0,   2.0,    2.0,   2.0  /)
662  !-
663  ! 3. Senescence
664  !-
665  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc  =  &             !! length of death of leaves, tabulated (days)
666  & (/  undef,   undef,   10.0,   undef,   undef,   30.0,   undef,  &
667  &       5.0,    10.0,   10.0,    10.0,    10.0,   10.0  /)
668
669  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leafagecrit_mtc  =  &          !! critical leaf age, tabulated (days)
670  & (/  undef,   730.0,   180.0,   910.0,   730.0,   160.0,   910.0,  &
671  &     220.0,   120.0,    80.0,   120.0,    90.0,    90.0  /)
672
673  CHARACTER(LEN=6), PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc  =  & !! type of senescence, tabulated (unitless)
674  & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',  &
675  &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',  &
676  &     'mixed ',  'mixed ',   'mixed '            /)
677
678  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc  =  &       !! critical relative moisture availability
679  & (/  undef,   undef,   0.3,   undef,   undef,   undef,   undef,  &       !! for senescence (0-1, unitless)
680  &     undef,   undef,   0.2,     0.2,     0.3,     0.2  /)
681
682  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc  =  &     !! relative moisture availability above which
683  & (/  undef,   undef,   0.8,   undef,   undef,   undef,   undef,  &       !! there is no humidity-related senescence
684  &     undef,   undef,   0.6,     0.3,     0.3,     0.3  /)                !! (0-1, unitless)
685
686  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc  =  &    !! maximum turnover time for grasses (days)
687  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
688  &     undef,   undef,    80.0,    80.0,    80.0,    80.0  /)
689
690  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc  =  &    !! minimum turnover time for grasses (days)
691  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
692  &     undef,   undef,    10.0,    10.0,    10.0,    10.0  /)
693 
694  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recycle_leaf_mtc = &           !! Fraction of N leaf that is recycled when leaves are senescent
695  & (/  undef,     0.5,     0.5,     0.5,     0.5,     0.5,     0.5,  &
696  &       0.5,     0.5,     0.5,     0.5,     0.5,     0.5  /)
697
698  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: recycle_root_mtc = &           !! Fraction of N leaf that is recycled when leaves are senescent
699  & (/  undef,     0.2,     0.2,     0.2,     0.2,     0.2,     0.2,  &
700  &       0.2,     0.2,     0.2,     0.2,     0.2,     0.2  /)
701
702  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc  =  &  !! minimum leaf age to allow
703  & (/  undef,   undef,   90.0,   undef,   undef,   90.0,   undef,  &               !! senescence g (days)
704  &      60.0,    60.0,   30.0,    30.0,    30.0,   30.0  /)
705
706  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc  =  &    !! critical temperature for senescence (C)
707  & (/  undef,   undef,    undef,   undef,   undef,   16.0,   undef,  &     !! constant c of aT^2+bT+c, tabulated
708  &      14.0,    10.0,      5.0,     5.0,     5.0,    10.0  /)             !! (unitless)
709
710  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc  =  &    !! critical temperature for senescence (C),
711  & (/  undef,   undef,   undef,   undef,   undef,   0.0,   undef,  &       !! constant b of aT^2+bT+c, tabulated
712  &       0.0,     0.0,     0.1,     0.0,     0.0,   0.0  /)                !! (unitless)
713
714  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc  =  &    !! critical temperature for senescence (C),
715  & (/  undef,   undef,     undef,   undef,   undef,   0.0,   undef,  &     !! constant a of aT^2+bT+c, tabulated
716  &       0.0,     0.0,   0.00375,     0.0,     0.0,   0.0  /)              !! (unitless)
717
718  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gdd_senescence_mtc  =  &       !! minimum gdd to allow senescence of crops (days)
719  & (/  undef,   undef,    undef,   undef,     undef,    undef,    undef,  &
720  &     undef,   undef,    undef,   undef,      950.,    4000.  /)
721
722  !-
723  ! 4. N cycle
724  !-
725  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_min_mtc  = &            !! minimum CN ratio of leaves
726  & (/  undef,     16.,      16.,     28.,       16.,      16.,      28., &  !! (gC/gN)
727  &       16.,     16.,      16.,     16.,       16.,      16.   /)
728
729  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_max_mtc  = &            !! maximum CN ratio of leaves
730 & (/   undef,     45.,      45.,     75.,       45.,      45.,      75.,  & !! (gC/gN)
731 &        45.,     45.,      45.,     45.,       45.,      45.   /)
732
733  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_soil_n_bnf_mtc   = &        !! Value of total N (NH4+NO3)
734 & (/     0.0,     1.5,      1.5,     1.5,       1.5,      1.5,      1.5,  & 
735 &        1.5,     1.5,       2.,      2.,        2.,       2.   /)          !! above which we stop adding N via BNF
736                                                                             !! (gN/m**2)
737
738  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: manure_pftweight_mtc = &        !! Weight of the distribution of manure over the PFT surface
739 & (/   0.,     0.,      0.,     0.,       0.,      0.,      0.,  &          !! (to a same number correspond the same concentration)
740 &        0.,     0.,      1.,     1.,       1.,      1.   /)
741
742
743
744  !
745  ! DGVM
746  !
747  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc  =  &    !! residence time of trees (years)
748  & (/  undef,   30.0,   30.0,   40.0,   40.0,   40.0,   80.0,  &
749  &      80.0,   80.0,    0.0,    0.0,    0.0,    0.0  /) 
750
751  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc  =  &
752  & (/  undef,     0.0,     0.0,   -30.0,   -14.0,   -30.0,   -45.0,  &  !! critical tmin, tabulated (C)
753  &     -45.0,   undef,   undef,   undef,   undef,   undef  /)
754
755  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc  =  &
756  & (/  undef,   undef,   undef,     5.0,    15.5,    15.5,   -8.0,  &   !! critical tcm, tabulated (C)
757  &      -8.0,    -8.0,   undef,   undef,   undef,   undef  /)
758
759
760
761  !
762  ! Biogenic Volatile Organic Compounds
763  !
764  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_isoprene_mtc = &     !! Isoprene emission factor
765  & (/  0.,    24.,   24.,    8.,   16.,   45.,   8.,  &                    !!
766  &    18.,    0.5,   12.,   18.,    5.,    5.  /)
767
768  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_monoterpene_mtc = &  !! Monoterpene emission factor
769  & (/   0.,   2.0,    2.0,   1.8,    1.4,    1.6,    1.8,  &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
770  &    1.4,    1.8,    0.8,   0.8,    0.22,     0.22  /)
771
772  REAL(r_std), PARAMETER :: LDF_mono_mtc = 0.6                                  !! monoterpenes fraction dependancy to light
773  REAL(r_std), PARAMETER :: LDF_sesq_mtc = 0.5                                  !! sesquiterpenes fraction dependancy to light
774  REAL(r_std), PARAMETER :: LDF_meth_mtc = 0.8                                  !! methanol fraction dependancy to light
775  REAL(r_std), PARAMETER :: LDF_acet_mtc = 0.2                                  !! acetone fraction dependancy to light
776
777  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_apinene_mtc = &      !! Alfa pinene emission factor percentage
778  & (/   0.,   0.395,   0.395,   0.354,   0.463,   0.326,   0.354, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
779  &   0.316,   0.662,   0.231,   0.200,   0.277,   0.277 /)
780
781  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_bpinene_mtc = &      !! Beta pinene emission factor  percentage     
782  & (/   0.,   0.110,   0.110,   0.146,   0.122,   0.087,   0.146, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
783  &   0.063,   0.150,   0.123,   0.080,   0.154,   0.154  /)
784
785  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_limonene_mtc = &     !! Limonene emission factor percentage
786  & (/   0.,   0.092,   0.092,   0.083,   0.122,   0.061,   0.083, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
787  &   0.071,   0.037,   0.146,   0.280,   0.092,   0.092  /)
788
789  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_myrcene_mtc = &      !! Myrcene emission factor percentage
790  & (/   0.,   0.073,   0.073,   0.050,   0.054,   0.028,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
791  &   0.019,   0.025,   0.062,   0.057,   0.046,   0.046  /)
792
793  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sabinene_mtc = &     !! Sabinene emission factor percentage
794  & (/   0.,   0.073,   0.073,   0.050,   0.083,   0.304,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
795  &   0.263,   0.030,   0.065,   0.050,   0.062,   0.062  /)
796
797  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_camphene_mtc = &     !! Camphene emission factor percentage
798  & (/   0.,   0.055,   0.055,   0.042,   0.049,   0.004,   0.042, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
799  &   0.005,   0.023,   0.054,   0.053,   0.031,   0.031  /)
800
801  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_3carene_mtc = &      !! 3-carene emission factor percentage
802  & (/   0.,   0.048,   0.048,   0.175,   0.010,   0.024,   0.175, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
803  &   0.013,   0.042,   0.065,   0.057,   0.200,   0.200  /)
804
805  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_tbocimene_mtc = &    !! T-beta-ocimene emission factor percentage
806  & (/   0.,   0.092,   0.092,   0.054,   0.044,   0.113,   0.054, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
807  &   0.105,   0.028,   0.138,   0.120,   0.031,   0.031  /)
808
809  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_othermonot_mtc = &   !! Other monoterpenes emission factor percentage
810  & (/   0.,   0.062,   0.062,   0.046,   0.054,   0.052,   0.046, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
811  &   0.144,   0.003,   0.115,   0.103,   0.108,   0.108  /)
812
813  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sesquiterp_mtc = &   !! Sesquiterpene emission factor
814  & (/   0.,  0.45,   0.45,   0.13,   0.30,   0.36,   0.15, &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
815  &    0.30,  0.25,   0.60,   0.60,   0.08,   0.08  /)
816
817  REAL(r_std), PARAMETER :: beta_mono_mtc = 0.10                            !! Monoterpenes temperature dependency coefficient
818  REAL(r_std), PARAMETER :: beta_sesq_mtc = 0.17                            !! Sesquiterpenes temperature dependency coefficient
819  REAL(r_std), PARAMETER :: beta_meth_mtc = 0.08                            !! Methanol temperature dependency coefficient
820  REAL(r_std), PARAMETER :: beta_acet_mtc = 0.10                            !! Acetone temperature dependency coefficient
821  REAL(r_std), PARAMETER :: beta_oxyVOC_mtc = 0.13                          !! Other oxygenated BVOC temperature dependency coefficient
822
823
824  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_ORVOC_mtc = &        !! ORVOC emissions factor
825  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
826  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /) 
827
828  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_OVOC_mtc = &         !! OVOC emissions factor
829  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
830  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /)
831 
832  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_MBO_mtc = &          !! MBO emissions factor
833  & (/     0., 2.e-5, 2.e-5,   1.4, 2.e-5, 2.e-5, 0.14,  &                  !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
834  &     2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5  /) 
835 
836  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_methanol_mtc = &     !! Methanol emissions factor
837  & (/  0.,    0.8,   0.8,   1.8,   0.9,   1.9,   1.8,  &                   !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
838  &    1.8,    1.8,   0.7,   0.9,    2.,     2.  /) 
839 
840  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetone_mtc = &      !! Acetone emissions factor
841  & (/  0.,   0.25,   0.25,   0.30,   0.20,   0.33,   0.30,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
842  &   0.25,   0.25,   0.20,   0.20,   0.08,   0.08  /)
843 
844  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetal_mtc = &       !! Acetaldehyde emissions factor
845  & (/  0.,   0.2,    0.2,     0.2,   0.2,   0.25,   0.25,   0.16,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
846  &   0.16,   0.12,   0.12,   0.035,   0.020  /) 
847 
848  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formal_mtc = &       !! Formaldehyde emissions factor
849  & (/  0.,   0.04,   0.04,  0.08,    0.04,    0.04,  0.04,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
850  &   0.04,   0.04,  0.025, 0.025,   0.013,   0.013  /) 
851
852  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetic_mtc = &       !! Acetic Acid emissions factor
853  & (/   0.,   0.025,   0.025,   0.025,   0.022,   0.08,   0.025,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
854  &   0.022,   0.013,   0.012,   0.012,   0.008,   0.008  /) 
855
856  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formic_mtc = &       !! Formic Acid emissions factor
857  & (/  0.,  0.015,  0.015,   0.02,    0.02,   0.025,  0.025,  &            !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
858  &  0.015,  0.015,  0.010,  0.010,   0.008,   0.008  /) 
859
860  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_wet_mtc = &        !! NOx emissions factor soil emissions and exponential
861  & (/  0.,   2.6,   0.06,   0.03,   0.03,   0.03,   0.03,  &               !! dependancy factor for wet soils
862  &  0.03,   0.03,   0.36,   0.36,   0.36,   0.36  /)                       !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
863
864  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_dry_mtc = &        !! NOx emissions factor soil emissions and exponential
865  & (/  0.,   8.60,   0.40,   0.22,   0.22,   0.22,   0.22,  &              !! dependancy factor for dry soils
866  &   0.22,   0.22,   2.65,   2.65,   2.65,   2.65  /)                      !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
867
868  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Larch_mtc = &                  !! Larcher 1991 SAI/LAI ratio (unitless)
869  & (/   0.,   0.015,   0.015,   0.003,   0.005,   0.005,   0.003,  &
870  &   0.005,   0.003,   0.005,   0.005,   0.008,   0.008  /) 
871
872  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_latosa_max_mtc = &  !! Maximum leaf-to-sapwood area ratio as defined in McDowell et al
873  & (/ undef,  5000.,  5000.,  5000.,  3000.,  5000.,  5000.,  &   !! 2002, Oecologia and compiled in Hickler et al 2006, Appendix S2
874  &    5000.,  5000.,  0.833,  0.833,  0.833,  0.833 /)                      !! The values for grasses and crops are tuned. More work is needed
875                                                                   !! to fully justify this approach for the herbacuous PFTs (unitless)
876
877  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_latosa_min_mtc = &  !! Minimum leaf-to-sapwood area ratio as defined in McDowell et al
878  & (/ undef,  5000.,  5000.,  5000.,  3000.,  5000.,  5000.,  &   !! 2002, Oecologia and compiled in Hickler et al 2006, Appendix S2
879  &    5000.,  5000.,  0.833,  0.833,  0.833,  0.833  /)           !! The values for grasses and crops are tuned. More work is needed
880                                                                   !! to fully justify this approach for the herbacuous PFTs (unitless)
881
882  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_root_mtc = &        !! Fine root specific conductivity. Values compiled in T. Hickler     
883  & (/ undef,    4.,    4.,   4.,   4.,   4.,   4.,       &        !! et al. 2006. @tex $(m^{3} kg^{-1} s^{-1} MPa^{-1})$ @endtex   
884  &       4.,    4.,   50.,  50.,  50.,  50.   /)*1.e-7         
885                                                                       
886  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: k_sap_mtc = &         !! Maximal sapwood specific conductivity. Values compiled in T. Hickler
887  & (/-9999., 1.E-3, 1.E-3, 5.34E-4, 1.08E-4, 3.E-3, 6.25E-4,&     !! et al. 2006. @tex $(m^{2} s^{-1} MPa^{-1})$ @endtex
888  &    3.E-3, 5.82E-4, 3.E-4, 3.E-4, 3.E-4, 3.E-4    /)            !! Values from DOFOCO run.def
889
890  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_to_height_mtc = &                    !! Convertion from lai to height for grasses
891  &(/ undef, undef, undef, undef, undef, undef, undef, &                              !! and cropland. Convert lai because that way a dynamic
892  &   undef, undef,   0.1,   0.2,   0.1,   0.2 /)                                     !! sla is accounted for 
893
894  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_a_mtc = &                          !! intercept of the intra-tree competition within a stand
895  & (/ undef,  0.23,  0.23,  0.23,  0.23,  0.23,  0.23, &                               !! based on the competion rule of Deleuze and Dhote 2004
896  &     0.23,  0.23, undef, undef, undef, undef /)                                      !! Used when n_circ > 6
897
898  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_b_mtc = &                          !! slope of the intra-tree competition within a stand
899  & (/ undef,  0.58,  0.58,  0.58,  0.58,  0.58,  0.58, &                               !! based on the competion rule of Deleuze and Dhote 2004
900  &     0.58,  0.58, undef, undef, undef, undef /)                                      !! Used when n_circ > 6
901
902  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deleuze_p_all_mtc = &                      !! Percentile of the circumferences that receives photosynthates
903  & (/ undef,  0.50,  0.50,  0.99,  0.99,  0.99,  0.99, &                               !! based on the competion rule of Deleuze and Dhote 2004
904  &     0.99,  0.99, undef, undef, undef, undef /)                                      !! Used when n_circ > 6 for FM1, FM2 and FM4
905
906  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: m_dv_mtc = &                               !! Parameter in the Deleuze & Dhote allocation
907  & (/ undef,  1.05,  1.05,  1.05,  1.05,  1.05,  1.05, &                               !! rule that relaxes the cut-off imposed by
908  &     1.05,  1.05,    0.,    0.,    0.,    0. /)                                      !! ::sigma. Owing to m_relax trees still grow
909                                                                                        !! a little when their ::circ is below ::sigma
910 
911  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fruit_alloc_mtc = &   !! Fraction of biomass allocated to fruit production (0-1)
912  & (/ undef,   0.1,    0.1,    0.1,     0.1,     0.1,    0.1, &   !! currently only parameterized for forest PFTs
913  &      0.1,   0.1,     0.,     0.,      0.,      0. /) 
914
915  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: labile_reserve_mtc = &                   !! The lab_fac is divided by this value to obtain
916  &(/  0.,  60.,  30.,  60.,  60.,  30.,  60., &                                      !! a new parameter. This new parameter is a fraction
917  &    30.,  30.,  30.,  30.,  30.,  30.  /)                                          !! that is multiplied with the plant biomass to obatin
918                                                                                      !! the optimal size of the labile pool. The dependency
919                                                                                      !! on lab_fac is a nice feature but the whole
920                                                                                      !! parameterization is arbitrary
921
922  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: evergreen_reserve_mtc = &                !! Fraction of sapwood mass stored in the reserve pool of evergreen
923  &(/ undef, 0.05, 0.05, 0.05, 0.05, 0.05, 0.05, &                                    !! trees (unitless, 0-1)
924  &    0.05,  0.05, 0.05, 0.05, 0.05, 0.05 /)
925
926  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescense_reserve_mtc = &               !! Fraction of sapwood mass stored in the reserve pool of deciduous
927  &(/ undef, 0.15, 0.15, 0.15, 0.15, 0.15, 0.15, &                                    !! trees during senescense(unitless, 0-1)
928  &    0.15,  0.15, 0.15, 0.15, 0.15, 0.15 /)
929
930  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: deciduous_reserve_mtc = &                !! Fraction of sapwood mass stored in the reserve pool of deciduous
931  &(/ undef, 0.12, 0.12, 0.12, 0.12, 0.12, 0.12, &                                    !! trees during the growing season (unitless, 0-1)
932  &    0.12,  0.12, 0.3, 0.3, 0.3, 0.3 /)
933
934  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fcn_root_mtc = &      !! N/C of "root" for allocation relative to leaf N/C  according
935  & (/ undef,   .86,    .86,    .86,    .86,    .86,   .86,   &    !! to stich et al 2003
936  &      .86,   .86,    .86,    .86,    .86,    .86   /)
937
938  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fcn_wood_mtc = &      !! N/C of "wood" for allocation relative to leaf N/C  according
939  & (/ undef,    .087,   .087,   .087,   .087,   .087,  .087,  &   !! to stich et al 2003
940  &     .087,    .087,     1.,     1.,     1.,     1.   /)
941
942  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: branch_ratio_mtc =  &                      !! Ratio of branches to total woody biomass (unitless)
943  & (/  0.0,   0.38,   0.38,   0.25,   0.38,   0.38,   0.25,  &
944  &    0.38,   0.25,    0.0,    0.0,    0.0,    0.0 /)
945
946  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cn_leaf_init_mtc = &  !! C/N of leaves according to stich et al 2003
947  & (/ undef,  29.,  29.,  29.,  29.,  29.,  29.,  &
948  &      29.,  29.,  29.,  29.,  29.,  29.   /)
949
950
951             
952END MODULE constantes_mtc
Note: See TracBrowser for help on using the repository browser.