source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_parameters/constantes_mtc.f90 @ 8367

Last change on this file since 8367 was 7245, checked in by nicolas.vuichard, 3 years ago

improve Carbon mass balance closure. See ticket #785

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