source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_parameters/constantes_mtc.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

  • Property svn:keywords set to Date Revision
File size: 51.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) :: availability_fact_mtc  =  &     !! calculate mortality in lpj_gap
129  & (/ undef,   0.14,  0.14,   0.10,   0.10,   0.10,   0.05,  &
130  &     0.05,   0.05,  undef,  undef,  undef,  undef  /)
131
132  !
133  ! EVAPOTRANSPIRATION (sechiba)
134  !
135  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: rstruct_const_mtc  =  &  !! Structural resistance.
136  & (/ 0.0,   25.0,   25.0,   25.0,   25.0,   25.0,   25.0,  &        !! @tex $(s.m^{-1})$ @endtex
137  &   25.0,   25.0,    2.5,    2.0,    2.0,    2.0   /)
138
139  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kzero_mtc  =  &                  !! A vegetation dependent constant used in the
140  & (/    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.
141  &    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
142
143
144  !
145  ! WATER (sechiba)
146  !
147  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: wmax_veg_mtc  =  &        !! Volumetric available soil water capacity in each PFT
148  & (/ 150.0,   150.0,   150.0,   150.0,   150.0,   150.0,   150.0,  & !! @tex $(kg.m^{-3} of soil)$ @endtex
149  &    150.0,   150.0,   150.0,   150.0,   150.0,   150.0  /)         
150                                                                     
151
152  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref4m  =  &       !! Root profile description for the different
153  & (/ 5.0,   0.4,   0.4,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types. @tex $(m^{-1})$ @endtex
154  &    1.0,   0.8,   4.0,   1.0,   4.0,   1.0  /)                      !! These are the factor in the exponential which gets       
155                                                                       !! the root density as a function of depth
156                                                                       !! Values for zmaxh = 4.0 
157 
158  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: humcste_ref2m  =  &       !! Root profile description for the different
159  & (/ 5.0,   0.8,   0.8,   1.0,   0.8,   0.8,   1.0,  &               !! vegetations types.  @tex $(m^{-1})$ @endtex
160  &    1.0,   0.8,   4.0,   4.0,   4.0,   4.0  /)                      !! These are the factor in the exponential which gets       
161                                                                       !! the root density as a function of depth
162                                                                       !! Values for zmaxh = 2.0
163
164  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: throughfall_by_mtc  =  &  !! Fraction of rain intercepted by the canopy
165  & (/ 30.0,   30.0,   30.0,   30.0,   30.0,   30.0,   30.0,  &        !! (0-100, unitless)
166  &    30.0,   30.0,   30.0,   30.0,   30.0,   30.0  /)
167
168
169  !
170  ! ALBEDO (sechiba)
171  !
172  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_vis_mtc  =  &  !! Minimum snow albedo value for each vegetation type
173  & (/ 0.50,    0.0,    0.0,   0.15,   0.14,   0.14,   0.15,  &        !! after aging (dirty old snow) (unitless), visible albedo
174  &    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
175
176  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_aged_nir_mtc  =  &  !! Minimum snow albedo value for each vegetation type
177  & (/ 0.35,    0.0,    0.0,   0.14,   0.14,   0.14,   0.14,  &        !! after aging (dirty old snow) (unitless), near infrared albedo
178  &    0.14,   0.14,   0.18,   0.18,   0.18,   0.18  /)                !! Source : Values are from the Thesis of S. Chalita (1992)
179
180  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_vis_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
181  & (/ 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
182  &    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
183
184  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: snowa_dec_nir_mtc  =  &   !! Decay rate of snow albedo value for each vegetation type
185  & (/ 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
186  &    0.11,   0.11,   0.52,   0.52,   0.52,   0.52  /)                !! Source : Values are from the Thesis of S. Chalita (1992)
187
188  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_vis_mtc  =  &    !! leaf albedo of vegetation type, visible albedo, optimized on 04/07/2016
189  & (/ 0.00,   0.0397, 0.0474, 0.0386, 0.0484, 0.0411, 0.041,  &       !! (unitless)
190  &    0.0541, 0.0435, 0.0524, 0.0508, 0.0509, 0.0606  /)
191
192  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alb_leaf_nir_mtc  =  &    !! leaf albedo of vegetation type, near infrared albedo, optimized on 04/07/2016
193  & (/ 0.00,   0.227,  0.214,  0.193,  0.208,  0.244,  0.177,  &       !! (unitless)
194  &    0.218,  0.213,  0.252,  0.265,  0.272,  0.244  /)
195
196  !
197  ! SOIL - VEGETATION
198  !
199  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pref_soil_veg_mtc  =  &       !! The soil tile number for each vegetation
200  & (/ 1,   2,   2,   2,   2,   2,   2,  &                                   
201  &    2,   2,   3,   3,   3,   3  /)                                         
202
203
204  !
205  ! PHOTOSYNTHESIS
206  !
207  !-
208  ! 1 .CO2
209  !-
210  LOGICAL, PARAMETER, DIMENSION(nvmc) :: is_c4_mtc  =  &                            !! flag for C4 vegetation types (true/false)
211  & (/ .FALSE.,  .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,   .FALSE.,  &
212  &    .FALSE.,  .FALSE.,   .FALSE.,   .TRUE.,    .FALSE.,   .TRUE.  /)
213
214  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: vcmax_fix_mtc  =  &     !! values used for vcmax when STOMATE is not
215  & (/  0.0,   40.0,   50.0,   30.0,   35.0,   40.0,   30.0,  &      !! activated @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
216  &    40.0,   35.0,   60.0,   60.0,   70.0,   70.0  /)
217
218  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: downregulation_co2_coeff_mtc  =  &  !! coefficient for CO2 downregulation
219  & (/  0.0,   0.38,   0.38,   0.28,   0.28,   0.28,   0.22,  &
220  &     0.22,  0.22,   0.26,   0.26,   0.26,   0.26 /)
221
222  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmC_mtc  = &            !! Energy of activation for KmC (J mol-1)
223  & (/undef,  79430.,  79430.,  79430.,  79430.,  79430.,  79430.,  &  !! See Medlyn et al. (2002)
224  &  79430.,  79430.,  79430.,  79430.,  79430.,  79430.  /)           !! from Bernacchi al. (2001)
225
226  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_KmO_mtc  = &            !! Energy of activation for KmO (J mol-1)
227  & (/undef,  36380.,  36380.,  36380.,  36380.,  36380.,  36380.,  &  !! See Medlyn et al. (2002)
228  &  36380.,  36380.,  36380.,  36380.,  36380.,  36380.  /)           !! from Bernacchi al. (2001)
229
230  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_gamma_star_mtc  = &     !! Energy of activation for gamma_star (J mol-1)
231  & (/undef,  37830.,  37830.,  37830.,  37830.,  37830.,  37830.,  &  !! See Medlyn et al. (2002) from Bernacchi al. (2001)
232  &  37830.,  37830.,  37830.,  37830.,  37830.,  37830.  /)           !! for C3 plants - We use the same values for C4 plants
233
234  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Vcmax_mtc  = &          !! Energy of activation for Vcmax (J mol-1)
235  & (/undef,  71513.,  71513.,  71513.,  71513.,  71513.,  71513.,  &  !! See Table 2 of Yin et al. (2009) for C4 plants
236  &  71513.,  71513.,  71513.,  67300.,  71513.,  67300.  /)           !! and Kattge & Knorr (2007) for C3 plants (table 3)
237
238  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Jmax_mtc  = &            !! Energy of activation for Jmax (J mol-1)
239  & (/undef,  49884.,  49884.,  49884.,  49884.,  49884.,  49884.,  &   !! See Table 2 of Yin et al. (2009) for C4 plants
240  &  49884.,  49884.,  49884.,  77900.,  49884.,  77900.  /)            !! and Kattge & Knorr (2007) for C3 plants (table 3)
241
242  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)
243  & (/undef,  668.39,  668.39,  668.39,  668.39,  668.39,  668.39,  &   !! See Table 3 of Kattge & Knorr (2007)
244  &  668.39,  668.39,  668.39,  641.64,  668.39,  641.64  /)            !! For C4 plants, we assume that there is no
245                                                                        !! 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)
246
247  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)
248  & (/undef,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,   -1.07,  &   !! See Table 3 of Kattge & Knorr (2007)
249  &   -1.07,   -1.07,   -1.07,      0.,   -1.07,      0.  /)            !! We assume No acclimation term for C4 plants
250
251  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_min_mtc  =  &  !! minimum photosynthesis temperature (deg C)
252  & (/  undef,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0,   -4.0,  & 
253  &      -4.0,   -4.0,    -4.0,   -4.0,   -4.0,   -4.0  /)
254
255  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tphoto_max_mtc  =  &  !! maximum photosynthesis temperature (deg C)
256  & (/  undef,   55.0,    55.0,   55.0,   55.0,   55.0,   55.0,  & 
257  &      55.0,   55.0,    55.0,   55.0,   55.0,   55.0  /)
258
259  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)
260  & (/undef,  659.70,  659.70,  659.70,  659.70,  659.70,  659.70,  &   !! See Table 3 of Kattge & Knorr (2007)
261  &  659.70,  659.70,  659.70,    630.,  659.70,    630.  /)            !! and Table 2 of Yin et al. (2009) for C4 plants
262
263  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)
264  & (/undef,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,   -0.75,  &   !! See Table 3 of Kattge & Knorr (2007)
265  &   -0.75,   -0.75,   -0.75,      0.,   -0.75,      0.  /)            !! We assume no acclimation term for C4 plants
266
267  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Vcmax_mtc  = &           !! Energy of deactivation for Vcmax (J mol-1)
268  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! Medlyn et al. (2002) also uses 200000. for C3 plants (same value than D_Jmax)
269  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! 'Consequently', we use the value of D_Jmax for C4 plants
270
271  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: D_Jmax_mtc  = &            !! Energy of deactivation for Jmax (J mol-1)
272  & (/undef, 200000., 200000., 200000., 200000., 200000., 200000.,  &   !! See Table 2 of Yin et al. (2009)
273  & 200000., 200000., 200000., 192000., 200000., 192000.  /)            !! Medlyn et al. (2002) also uses 200000. for C3 plants
274
275  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: E_Rd_mtc  = &              !! Energy of activation for Rd (J mol-1)
276  & (/undef,  46390.,  46390.,  46390.,  46390.,  46390.,  46390.,  &   !! See Table 2 of Yin et al. (2009)
277  &  46390.,  46390.,  46390.,  46390.,  46390.,  46390.  /)           
278
279  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Vcmax25_mtc  =  &          !! Maximum rate of Rubisco activity-limited carboxylation at 25°C
280  & (/ undef,   65.0,    65.0,    45.0,   45.0,   55.0,   45.0,  &      !! @tex $(\mu mol.m^{-2}.s^{-1})$ @endtex
281  &     45.0,   35.0,    70.0,    70.0,   70.0,   70.0  /)
282
283  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)
284  & (/undef,    2.59,    2.59,    2.59,    2.59,    2.59,    2.59,  &   !! See Table 3 of Kattge & Knorr (2007)
285  &    2.59,    2.59,    2.59,   1.715,    2.59,   1.715  /)            !! For C4 plants, we assume that there is no
286                                                                        !! 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)
287
288  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)
289  & (/undef,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  -0.035,  &   !! See Table 3 of Kattge & Knorr (2007)
290  &  -0.035,  -0.035,  -0.035,      0.,  -0.035,      0.  /)            !! We assume No acclimation term for C4 plants
291
292  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmC25_mtc  = &             !! Michaelis–Menten constant of Rubisco for CO2 at 25°C (ubar)
293  & (/undef,   404.9,   404.9,   404.9,   404.9,  404.9,   404.9,  &    !! See Table 2 of Yin et al. (2009) for C4
294  &   404.9,   404.9,   404.9,    650.,   404.9,   650.  /)             !! and Medlyn et al (2002) for C3
295
296  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: KmO25_mtc  = &             !! Michaelis–Menten constant of Rubisco for O2 at 25°C (ubar)
297  & (/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
298  & 278400., 278400., 278400., 450000., 278400., 450000.  /)           
299
300  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gamma_star25_mtc  = &      !! Ci-based CO2 compensation point in the absence of Rd at 25°C (ubar)
301  & (/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)
302  &   42.75,   42.75,   42.75,   42.75,   42.75,   42.75  /)   
303
304  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: a1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
305  & (/undef,    0.85,    0.85,    0.85,    0.85,    0.85,  0.85,  &     !! See Table 2 of Yin et al. (2009)
306  &    0.85,    0.85,    0.85,    0.85,    0.85,    0.85  /)           
307
308  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: b1_mtc  = &                !! Empirical factor involved in the calculation of fvpd (-)
309  & (/undef,    0.14,    0.14,    0.14,    0.14,    0.14,  0.14,  &     !! See Table 2 of Yin et al. (2009)
310  &    0.14,    0.14,    0.14,    0.20,    0.14,    0.20  /)           
311
312  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: g0_mtc  = &                !! Residual stomatal conductance when irradiance approaches zero (mol CO2 m−2 s−1 bar−1)
313  & (/undef, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625, 0.00625,  &   !! Value from ORCHIDEE - No other reference.
314  & 0.00625, 0.00625, 0.00625, 0.01875, 0.00625, 0.01875  /)            !! modofy to account for the conversion for conductance to H2O to CO2
315
316  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: h_protons_mtc  = &         !! Number of protons required to produce one ATP (mol mol-1)
317  & (/undef,      4.,      4.,      4.,      4.,      4.,    4.,  &     !! See Table 2 of Yin et al. (2009) - h parameter
318  &      4.,      4.,      4.,      4.,      4.,      4.  /)           
319
320  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpsir_mtc = &              !! Fraction of PSII e− transport rate
321  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! partitioned to the C4 cycle (-)
322  &   undef,   undef,   undef,     0.4,   undef,    0.4  /)             !! See Table 2 of Yin et al. (2009) - x parameter       
323 
324  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fQ_mtc = &                 !! Fraction of electrons at reduced plastoquinone
325  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! that follow the Q-cycle (-) - Values for C3 platns are not used
326  &   undef,   undef,   undef,      1.,   undef,     1.  /)             !! See Table 2 of Yin et al. (2009)         
327
328  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: fpseudo_mtc = &            !! Fraction of electrons at PSI that follow
329  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! pseudocyclic transport (-) - Values for C3 platns are not used
330  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)             !! See Table 2 of Yin et al. (2009)   
331
332  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: kp_mtc = &                 !! Initial carboxylation efficiency of the PEP carboxylase (mol m−2 s−1 bar−1)
333  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See Table 2 of Yin et al. (2009)
334  &   undef,   undef,   undef,     0.7,   undef,    0.7  /)                 
335
336  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alpha_mtc = &              !! Fraction of PSII activity in the bundle sheath (-)
337  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
338  &   undef,   undef,   undef,     0.1,   undef,    0.1  /)                 
339
340  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gbs_mtc = &                !! Bundle-sheath conductance (mol m−2 s−1 bar−1)
341  & (/undef,   undef,   undef,   undef,   undef,  undef,  undef,  &     !! See legend of Figure 6 of Yin et al. (2009)
342  &   undef,   undef,   undef,   0.003,   undef,  0.003  /)   
343
344  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: theta_mtc = &              !! Convexity factor for response of J to irradiance (-)
345  & (/undef,     0.7,     0.7,     0.7,     0.7,    0.7,    0.7,  &     !! See Table 2 of Yin et al. (2009)
346  &     0.7,     0.7,     0.7,     0.7,     0.7,    0.7  /)
347
348  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)
349  & (/undef,     0.3,     0.3,     0.3,     0.3,    0.3,    0.3,  &     !! See comment from Yin et al. (2009) after eq. 4
350  &     0.3,     0.3,     0.3,     0.3,     0.3,    0.3  /)             !! alpha value from Medlyn et al. (2002)   
351                                                                        !! 0.093 mol CO2 fixed per mol absorbed photons
352                                                                        !! times 4 mol e- per mol CO2 produced
353   
354  !-
355  ! 2 .Stomate
356  !-
357  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_mtc  =  &     !! extinction coefficient of the Monsi&Saeki
358  & (/ 0.5,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &             !! relationship (1953) (unitless)
359  &    0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
360  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ext_coeff_vegetfrac_mtc  =  &     !! extinction coefficient used for defining the fraction
361  & (/ 1.0,   1.0,   1.0,   1.0,   1.0,   1.0,   1.0,  &                       !!  of bare soil (unitless)
362  &    1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
363
364  !
365  ! ALLOCATION (stomate)
366  !
367  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: R0_mtc = &              !! Default root allocation (0-1, unitless)
368  & (/ undef,   0.30,   0.30,   0.30,   0.30,  0.30,    0.30, &
369  &     0.30,   0.30,   0.30,   0.30,   0.30,  0.30 /)                   
370
371  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: S0_mtc = &              !! Default sapwood allocation (0-1, unitless)
372  & (/ undef,   0.25,   0.25,   0.30,   0.30,  0.30,    0.30, &
373  &     0.30,   0.30,   0.30,   0.30,   0.30,  0.30 /)                   
374
375  !
376  ! RESPIRATION (stomate)
377  !
378  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: frac_growthresp_mtc  =  &  !! fraction of GPP which is lost as growth respiration
379  & (/  undef,   0.28,   0.28,   0.28,   0.28,   0.28,   0.28,  &
380  &      0.28,   0.28,   0.28,   0.28,   0.28,   0.28  /)
381
382  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_c_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
383  & (/  undef,   0.20,   0.20,   0.16,   0.16,   0.16,   0.16,  &          !! constant c of aT^2+bT+c, tabulated
384  &      0.16,   0.16,   0.16,   0.12,   0.16,   0.12  /)
385
386  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_b_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
387  & (/  undef,   0.0,        0.0,   0.0,        0.0,   0.0,   0.0,  &      !! constant b of aT^2+bT+c, tabulated
388  &       0.0,   0.0,   -0.00133,   0.0,   -0.00133,   0.0  /)
389
390  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: maint_resp_slope_a_mtc  =  &  !! slope of maintenance respiration coefficient (1/K),
391  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                !! constant a of aT^2+bT+c, tabulated
392  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)
393
394  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_leaf_mtc  =   &                  !! maintenance respiration coefficient
395  & (/   undef,   2.35E-3,   2.62E-3,   1.01E-3,   2.35E-3,   2.62E-3,   1.01E-3,  &  !! at 0 deg C,for leaves, tabulated,
396  &    2.62E-3,   2.05E-3,   2.62E-3,   2.62E-3,   2.62E-3,   2.62E-3  /)             !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
397
398  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapabove_mtc =  &                !! maintenance respiration coefficient
399  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for sapwood above,
400  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
401
402  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_sapbelow_mtc  =  &               !! maintenance respiration coefficient
403  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for sapwood below,
404  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
405
406  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartabove_mtc  =  &             !! maintenance respiration coefficient
407  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                           !! at 0 deg C, for heartwood above,
408  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                                  !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
409
410  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_heartbelow_mtc  =  &             !! maintenance respiration coefficient
411  & (/  undef,   0.0,   0.0,   0.0,   0.0,   0.0,   0.0,  &                           !! at 0 deg C, for heartwood below,
412  &       0.0,   0.0,   0.0,   0.0,   0.0,   0.0  /)                                  !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
413
414  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_root_mtc  =  &                   !! maintenance respiration coefficient
415  & (/   undef,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,  &  !! at 0 deg C, for roots, tabulated,
416  &    1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3,   1.67E-3  /)             !! @tex $(gC.gC^{-1}.day^{-1})$ @endtex
417
418  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_fruit_mtc  =  &                  !! maintenance respiration coefficient
419  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for fruits, tabulated,
420  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !!  @tex $(gC.gC^{-1}.day^{-1})$ @endtex
421
422  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: cm_zero_carbres_mtc  =  &                !! maintenance respiration coefficient
423  & (/   undef,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,  &  !! at 0 deg C, for carbohydrate reserve,
424  &    1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4,   1.19E-4  /)             !! tabulated, @tex $(gC.gC^{-1}.day^{-1})$ @endtex
425
426
427  !
428  ! FIRE (stomate)
429  !
430  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: flam_mtc  =  &         !! flamability: critical fraction of water
431  & (/  undef,   0.15,   0.25,   0.25,   0.25,   0.25,   0.25,  &  !! holding capacity (0-1, unitless)
432  &      0.25,   0.25,   0.25,   0.25,   0.35,   0.35  /)
433
434  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: resist_mtc  =  &       !! fire resistance (0-1, unitless)
435  & (/ undef,   0.95,   0.90,   0.90,   0.90,   0.90,   0.90,  &
436  &    0.90,    0.90,    0.0,    0.0,    0.0,    0.0 /) 
437
438
439  !
440  ! FLUX - LUC
441  !
442  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_1_mtc  =  &   !! Coeff of biomass export for the year
443  & (/  undef,   0.897,   0.897,   0.597,   0.597,   0.597,   0.597,  &   !! (0-1, unitless)
444  &     0.597,   0.597,   0.597,   0.597,   0.597,   0.597  /)
445
446  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_10_mtc  =  &  !! Coeff of biomass export for the decade
447  & (/  undef,   0.103,   0.103,   0.299,   0.299,   0.299,   0.299,  &   !! (0-1, unitless)
448  &     0.299,   0.299,   0.299,   0.403,   0.299,   0.403  /) 
449
450  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: coeff_lcchange_100_mtc  =  & !! Coeff of biomass export for the century
451  & (/  undef,     0.0,     0.0,   0.104,   0.104,   0.104,   0.104,  &   !! (0-1, unitless)
452  &     0.104,   0.104,   0.104,     0.0,   0.104,     0.0  /)
453
454
455  !
456  ! PHENOLOGY
457  !
458  !-
459  ! 1. Stomate
460  !-
461  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: lai_max_to_happy_mtc  =  &  !! threshold of LAI below which plant uses carbohydrate reserves
462  & (/  undef,   0.5,   0.5,   0.5,   0.5,   0.5,   0.5,  &
463  &       0.5,   0.5,   0.5,   0.5,   0.5,   0.5  /)
464
465  REAL(r_std), PARAMETER, DIMENSION (nvmc) :: lai_max_mtc  =  &          !! maximum LAI, PFT-specific
466  & (/ undef,   7.0,   7.0,   5.0,   5.0,   5.0,   4.5,  &               !! @tex $(m^2.m^{-2})$ @endtex
467  &      4.5,   3.0,   2.5,   2.5,   5.0,   5.0  /)
468
469  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: pheno_type_mtc  =  &     !! type of phenology (0-4, unitless)
470  & (/  0,   1,   3,   1,   1,   2,   1,  &                              !! 0=bare ground 1=evergreen,  2=summergreen,
471  &     2,   2,   4,   4,   2,   3  /)                                   !! 3=raingreen,  4=perennial
472  !-
473  ! 2. Leaf Onset
474  !-
475  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_c_mtc  =  &    !! critical gdd, tabulated (C),
476  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant c of aT^2+bT+c
477  &     undef,   undef,   320.0,   400.0,   320.0,   700.0  /)
478
479  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_b_mtc  =  &    !! critical gdd, tabulated (C),
480  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! constant b of aT^2+bT+c
481  &     undef,   undef,    6.25,     0.0,    6.25,     0.0  /)
482
483  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_gdd_crit_a_mtc  =  &    !! critical gdd, tabulated (C),
484  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  &  !! constant a of aT^2+bT+c
485  &     undef,   undef,   0.03125,     0.0,  0.0315,   0.0  /)
486
487  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: pheno_moigdd_t_crit_mtc  = &  !! temperature threshold for C4 grass(C)
488  & (/  undef,   undef,     undef,   undef,   undef,   undef,   undef,  & 
489  &     undef,   undef,     undef,    22.0,   undef,   undef  /)
490
491  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ngd_crit_mtc  =  &            !! critical ngd, tabulated.
492  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &    !! Threshold -5 degrees (days)
493  &     undef,    17.0,   undef,   undef,   undef,   undef  /)
494
495  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ncdgdd_temp_mtc  =  &         !! critical temperature for the ncd vs. gdd
496  & (/  undef,   undef,   undef,   undef,   undef,     5.0,   undef,  &    !! function in phenology (C)
497  &       0.0,   undef,   undef,   undef,   undef,   undef  /)
498
499  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_frac_mtc  =  &            !! critical humidity (relative to min/max)
500  & (/  undef,   undef,   0.5,   undef,   undef,   undef,   undef, &       !! for phenology (unitless)
501  &     undef,   undef,   0.5,     0.5,     0.5,     0.5  /)
502
503  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: hum_min_time_mtc  =  &        !! minimum time elapsed since
504  & (/  undef,   undef,   50.0,   undef,   undef,   undef,   undef,  &     !! moisture minimum (days)
505  &     undef,   undef,   35.0,    35.0,    75.0,    75.0  /) 
506
507  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_sap_mtc  =  &             !! time (days) 
508  & (/  undef,   730.0,   730.0,   730.0,   730.0,   730.0,   730.0,  &
509  &     730.0,   730.0,   undef,   undef,   undef,   undef  /)
510
511  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_leafinit_mtc  =  &  !! time to attain the initial foliage using the carbohydrate reserve
512  & (/  undef,   10.,   10.,   10.,   10.,   10.,   10.,  &
513  &       10.,   10.,   10.,   10.,   10.,   10.  /)
514
515  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tau_fruit_mtc  =  &           !! fruit lifetime (days)
516  & (/  undef,  90.0,    90.0,    90.0,    90.0,   90.0,   90.0,  &
517  &      90.0,  90.0,   undef,   undef,   undef,   undef  /)
518
519  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: ecureuil_mtc  =  &            !! fraction of primary leaf and root allocation
520  & (/  undef,   0.0,   1.0,   0.0,   0.0,   1.0,   0.0,  &                !! put into reserve (0-1, unitless)
521  &       1.0,   1.0,   1.0,   1.0,   1.0,   1.0  /)
522
523  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_min_mtc  =  &           !! NEW - allocation above/below = f(age)
524  & (/  undef,   0.2,     0.2,     0.2,     0.2,    0.2,   0.2,  &         !! - 30/01/04 NV/JO/PF
525  &       0.2,   0.2,   undef,   undef,   undef,   undef  /)
526
527  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: alloc_max_mtc  =  &           !! NEW - allocation above/below = f(age)
528  & (/  undef,   0.8,     0.8,     0.8,     0.8,    0.8,   0.8,  &         !! - 30/01/04 NV/JO/PF
529  &       0.8,   0.8,   undef,   undef,   undef,   undef  /)
530
531  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: demi_alloc_mtc  =  &          !! NEW - allocation above/below = f(age)
532  & (/  undef,   5.0,     5.0,     5.0,     5.0,    5.0,   5.0,  &         !! - 30/01/04 NV/JO/PF
533  &       5.0,   5.0,   undef,   undef,   undef,   undef  /)
534
535  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaflife_mtc  =  &            !! leaf longevity, tabulated (??units??)
536  & (/  undef,   0.5,   2.0,   0.33,   1.0,   2.0,   0.33,  &
537  &       2.0,   2.0,   2.0,   2.0,    2.0,   2.0  /)
538  !-
539  ! 3. Senescence
540  !-
541  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leaffall_mtc  =  &             !! length of death of leaves, tabulated (days)
542  & (/  undef,   undef,   10.0,   undef,   undef,   10.0,   undef,  &
543  &      10.0,    10.0,   10.0,    10.0,    10.0,   10.0  /)
544
545  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: leafagecrit_mtc  =  &          !! critical leaf age, tabulated (days)
546  & (/  undef,   730.0,   180.0,   910.0,   730.0,   180.0,   910.0,  &
547  &     180.0,   180.0,   120.0,   120.0,    90.0,    90.0  /)
548
549  CHARACTER(LEN=6), PARAMETER, DIMENSION(nvmc) :: senescence_type_mtc  =  & !! type of senescence, tabulated (unitless)
550  & (/  'none  ',  'none  ',   'dry   ',  'none  ',  'none  ',  &
551  &     'cold  ',  'none  ',   'cold  ',  'cold  ',  'mixed ',  &
552  &     'mixed ',  'mixed ',   'mixed '            /)
553
554  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_hum_mtc  =  &       !! critical relative moisture availability
555  & (/  undef,   undef,   0.3,   undef,   undef,   undef,   undef,  &       !! for senescence (0-1, unitless)
556  &     undef,   undef,   0.2,     0.2,     0.3,     0.2  /)
557
558  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: nosenescence_hum_mtc  =  &     !! relative moisture availability above which
559  & (/  undef,   undef,   0.8,   undef,   undef,   undef,   undef,  &       !! there is no humidity-related senescence
560  &     undef,   undef,   0.3,     0.3,     0.3,     0.3  /)                !! (0-1, unitless)
561
562  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: max_turnover_time_mtc  =  &    !! maximum turnover time for grasses (days)
563  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
564  &     undef,   undef,    80.0,    80.0,    80.0,    80.0  /)
565
566  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_turnover_time_mtc  =  &    !! minimum turnover time for grasses (days)
567  & (/  undef,   undef,   undef,   undef,   undef,   undef,   undef,  &
568  &     undef,   undef,    10.0,    10.0,    10.0,    10.0  /)
569 
570  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: min_leaf_age_for_senescence_mtc  =  &  !! minimum leaf age to allow
571  & (/  undef,   undef,   90.0,   undef,   undef,   90.0,   undef,  &               !! senescence g (days)
572  &      60.0,    60.0,   30.0,    30.0,    30.0,   30.0  /)
573
574  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_c_mtc  =  &    !! critical temperature for senescence (C)
575  & (/  undef,   undef,    undef,   undef,   undef,   12.0,   undef,  &     !! constant c of aT^2+bT+c, tabulated
576  &       7.0,     2.0,   -1.375,     5.0,    5.0,    10.0  /)              !! (unitless)
577
578  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_b_mtc  =  &    !! critical temperature for senescence (C),
579  & (/  undef,   undef,   undef,   undef,   undef,   0.0,   undef,  &       !! constant b of aT^2+bT+c, tabulated
580  &       0.0,     0.0,     0.1,     0.0,     0.0,   0.0  /)                !! (unitless)
581
582  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: senescence_temp_a_mtc  =  &    !! critical temperature for senescence (C),
583  & (/  undef,   undef,     undef,   undef,   undef,   0.0,   undef,  &     !! constant a of aT^2+bT+c, tabulated
584  &       0.0,     0.0,   0.00375,     0.0,     0.0,   0.0  /)              !! (unitless)
585
586  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: gdd_senescence_mtc  =  &       !! minimum gdd to allow senescence of crops (days)
587  & (/  undef,   undef,    undef,   undef,     undef,    undef,    undef,  &
588  &     undef,   undef,    undef,   undef,      950.,    4000.  /)
589
590
591  !
592  ! DGVM
593  !
594  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: residence_time_mtc  =  &    !! residence time of trees (years)
595  & (/  undef,   30.0,   30.0,   40.0,   40.0,   40.0,   80.0,  &
596  &      80.0,   80.0,    0.0,    0.0,    0.0,    0.0  /) 
597
598  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tmin_crit_mtc  =  &
599  & (/  undef,     0.0,     0.0,   -30.0,   -14.0,   -30.0,   -45.0,  &  !! critical tmin, tabulated (C)
600  &     -45.0,   undef,   undef,   undef,   undef,   undef  /)
601
602  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: tcm_crit_mtc  =  &
603  & (/  undef,   undef,   undef,     5.0,    15.5,    15.5,   -8.0,  &   !! critical tcm, tabulated (C)
604  &      -8.0,    -8.0,   undef,   undef,   undef,   undef  /)
605
606
607
608  !
609  ! Biogenic Volatile Organic Compounds
610  !
611  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_isoprene_mtc = &     !! Isoprene emission factor
612  & (/  0.,    24.,   24.,    8.,   16.,   45.,   8.,  &                    !!
613  &    18.,    0.5,   12.,   18.,    5.,    5.  /)
614
615  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_monoterpene_mtc = &  !! Monoterpene emission factor
616  & (/   0.,   2.0,    2.0,   1.8,    1.4,    1.6,    1.8,  &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
617  &    1.4,    1.8,    0.8,   0.8,    0.22,     0.22  /)
618
619  REAL(r_std), PARAMETER :: LDF_mono_mtc = 0.6                                  !! monoterpenes fraction dependancy to light
620  REAL(r_std), PARAMETER :: LDF_sesq_mtc = 0.5                                  !! sesquiterpenes fraction dependancy to light
621  REAL(r_std), PARAMETER :: LDF_meth_mtc = 0.8                                  !! methanol fraction dependancy to light
622  REAL(r_std), PARAMETER :: LDF_acet_mtc = 0.2                                  !! acetone fraction dependancy to light
623
624  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_apinene_mtc = &      !! Alfa pinene emission factor percentage
625  & (/   0.,   0.395,   0.395,   0.354,   0.463,   0.326,   0.354, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
626  &   0.316,   0.662,   0.231,   0.200,   0.277,   0.277 /)
627
628  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_bpinene_mtc = &      !! Beta pinene emission factor  percentage     
629  & (/   0.,   0.110,   0.110,   0.146,   0.122,   0.087,   0.146, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
630  &   0.063,   0.150,   0.123,   0.080,   0.154,   0.154  /)
631
632  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_limonene_mtc = &     !! Limonene emission factor percentage
633  & (/   0.,   0.092,   0.092,   0.083,   0.122,   0.061,   0.083, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
634  &   0.071,   0.037,   0.146,   0.280,   0.092,   0.092  /)
635
636  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_myrcene_mtc = &      !! Myrcene emission factor percentage
637  & (/   0.,   0.073,   0.073,   0.050,   0.054,   0.028,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
638  &   0.019,   0.025,   0.062,   0.057,   0.046,   0.046  /)
639
640  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sabinene_mtc = &     !! Sabinene emission factor percentage
641  & (/   0.,   0.073,   0.073,   0.050,   0.083,   0.304,   0.050, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
642  &   0.263,   0.030,   0.065,   0.050,   0.062,   0.062  /)
643
644  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_camphene_mtc = &     !! Camphene emission factor percentage
645  & (/   0.,   0.055,   0.055,   0.042,   0.049,   0.004,   0.042, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
646  &   0.005,   0.023,   0.054,   0.053,   0.031,   0.031  /)
647
648  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_3carene_mtc = &      !! 3-carene emission factor percentage
649  & (/   0.,   0.048,   0.048,   0.175,   0.010,   0.024,   0.175, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
650  &   0.013,   0.042,   0.065,   0.057,   0.200,   0.200  /)
651
652  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_tbocimene_mtc = &    !! T-beta-ocimene emission factor percentage
653  & (/   0.,   0.092,   0.092,   0.054,   0.044,   0.113,   0.054, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
654  &   0.105,   0.028,   0.138,   0.120,   0.031,   0.031  /)
655
656  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_othermonot_mtc = &   !! Other monoterpenes emission factor percentage
657  & (/   0.,   0.062,   0.062,   0.046,   0.054,   0.052,   0.046, &        !! ATTENTION: for each PFT they are PERCENTAGE of monoterpene EF
658  &   0.144,   0.003,   0.115,   0.103,   0.108,   0.108  /)
659
660  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_sesquiterp_mtc = &   !! Sesquiterpene emission factor
661  & (/   0.,  0.45,   0.45,   0.13,   0.30,   0.36,   0.15, &               !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
662  &    0.30,  0.25,   0.60,   0.60,   0.08,   0.08  /)
663
664  REAL(r_std), PARAMETER :: beta_mono_mtc = 0.10                            !! Monoterpenes temperature dependency coefficient
665  REAL(r_std), PARAMETER :: beta_sesq_mtc = 0.17                            !! Sesquiterpenes temperature dependency coefficient
666  REAL(r_std), PARAMETER :: beta_meth_mtc = 0.08                            !! Methanol temperature dependency coefficient
667  REAL(r_std), PARAMETER :: beta_acet_mtc = 0.10                            !! Acetone temperature dependency coefficient
668  REAL(r_std), PARAMETER :: beta_oxyVOC_mtc = 0.13                          !! Other oxygenated BVOC temperature dependency coefficient
669
670
671  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_ORVOC_mtc = &        !! ORVOC emissions factor
672  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
673  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /) 
674
675  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_OVOC_mtc = &         !! OVOC emissions factor
676  &  (/  0.,    1.5,    1.5,    1.5,    1.5,   1.5,    1.5,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
677  &     1.5,    1.5,    1.5,    1.5,    1.5,   1.5  /)
678 
679  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_MBO_mtc = &          !! MBO emissions factor
680  & (/     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
681  &     2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5, 2.e-5  /) 
682 
683  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_methanol_mtc = &     !! Methanol emissions factor
684  & (/  0.,    0.8,   0.8,   1.8,   0.9,   1.9,   1.8,  &                   !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
685  &    1.8,    1.8,   0.7,   0.9,    2.,     2.  /) 
686 
687  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetone_mtc = &      !! Acetone emissions factor
688  & (/  0.,   0.25,   0.25,   0.30,   0.20,   0.33,   0.30,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
689  &   0.25,   0.25,   0.20,   0.20,   0.08,   0.08  /)
690 
691  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetal_mtc = &       !! Acetaldehyde emissions factor
692  & (/  0.,   0.2,    0.2,     0.2,   0.2,   0.25,   0.25,   0.16,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
693  &   0.16,   0.12,   0.12,   0.035,   0.020  /) 
694 
695  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formal_mtc = &       !! Formaldehyde emissions factor
696  & (/  0.,   0.04,   0.04,  0.08,    0.04,    0.04,  0.04,  &              !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
697  &   0.04,   0.04,  0.025, 0.025,   0.013,   0.013  /) 
698
699  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_acetic_mtc = &       !! Acetic Acid emissions factor
700  & (/   0.,   0.025,   0.025,   0.025,   0.022,   0.08,   0.025,   &      !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
701  &   0.022,   0.013,   0.012,   0.012,   0.008,   0.008  /) 
702
703  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: em_factor_formic_mtc = &       !! Formic Acid emissions factor
704  & (/  0.,  0.015,  0.015,   0.02,    0.02,   0.025,  0.025,  &            !! @tex $(\mu gC.g^{-1}.h^{-1})$ @endtex
705  &  0.015,  0.015,  0.010,  0.010,   0.008,   0.008  /) 
706
707  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_wet_mtc = &        !! NOx emissions factor soil emissions and exponential
708  & (/  0.,   2.6,   0.06,   0.03,   0.03,   0.03,   0.03,  &               !! dependancy factor for wet soils
709  &  0.03,   0.03,   0.36,   0.36,   0.36,   0.36  /)                       !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
710
711  REAL(r_std),PARAMETER, DIMENSION(nvmc) :: em_factor_no_dry_mtc = &        !! NOx emissions factor soil emissions and exponential
712  & (/  0.,   8.60,   0.40,   0.22,   0.22,   0.22,   0.22,  &              !! dependancy factor for dry soils
713  &   0.22,   0.22,   2.65,   2.65,   2.65,   2.65  /)                      !! @tex $(ngN.m^{-2}.s^{-1})$ @endtex
714
715  REAL(r_std), PARAMETER, DIMENSION(nvmc) :: Larch_mtc = &                  !! Larcher 1991 SAI/LAI ratio (unitless)
716  & (/   0.,   0.015,   0.015,   0.003,   0.005,   0.005,   0.003,  &
717  &   0.005,   0.003,   0.005,   0.005,   0.008,   0.008  /) 
718
719  !gmjc
720  ! grassland management
721  ! Is the vegetation a grassland that can be managed ?
722  LOGICAL,PARAMETER, DIMENSION(nvmc) :: is_grassland_manag_mtc   =  &
723  & (/ .FALSE., .FALSE.,  .FALSE., .FALSE., .FALSE.,  &
724  &    .FALSE.,  .FALSE.,  .FALSE., .FALSE., .FALSE., &
725  &    .FALSE., .FALSE., .FALSE. /)
726  ! Is the vegetation a grassland that can be cut ?
727  LOGICAL,PARAMETER, DIMENSION(nvmc) :: is_grassland_cut_mtc   =  &
728  & (/ .FALSE., .FALSE.,  .FALSE., .FALSE., .FALSE.,  &
729  &    .FALSE.,  .FALSE.,  .FALSE., .FALSE., .FALSE., &
730  &    .FALSE., .FALSE., .FALSE. /)
731  ! Is the vegetation a grassland that can be grazed ?
732  LOGICAL,PARAMETER, DIMENSION(nvmc) :: is_grassland_grazed_mtc   =  &
733  & (/ .FALSE., .FALSE.,  .FALSE., .FALSE., .FALSE.,  &
734  &    .FALSE.,  .FALSE.,  .FALSE., .FALSE., .FALSE., &
735  &    .FALSE., .FALSE., .FALSE. /)
736  ! Is the vegetation a grassland that can be grazed by wild grazer?
737  LOGICAL,PARAMETER, DIMENSION(nvmc) :: is_grassland_wild_mtc   =  &
738  & (/ .FALSE., .FALSE.,  .FALSE., .FALSE., .FALSE.,  &
739  &    .FALSE.,  .FALSE.,  .FALSE., .FALSE., .FALSE., &
740  &    .FALSE., .FALSE., .FALSE. /)
741  ! Management Intensity reading in MANAGEMENT_MAP
742  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: management_intensity_mtc  =  &
743  & (/ 0,   0,   0,   0,   0,   0,   0,  &
744  &    0,   0,   0,   0,   0,   0  /)
745  ! Start year of management reading in MANAGEMENT_MAP & GRAZING_MAP
746  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: management_start_mtc  =  &
747  & (/ 0,   0,   0,   0,   0,   0,   0,  &
748  &    0,   0,   0,   0,   0,   0  /)
749  ! Start year of N deposition reading in DEPOSITION_MAP
750  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: deposition_start_mtc  =  &
751  & (/ 0,   0,   0,   0,   0,   0,   0,  &
752  &    0,   0,   0,   0,   0,   0  /)
753  ! Number of year that management should be read
754  INTEGER(i_std), PARAMETER, DIMENSION(nvmc) :: nb_year_management_mtc  =  &
755  & (/ 1,   1,   1,   1,   1,   1,   1,  &
756  &    1,   1,   1,   1,   1,   1  /)
757  ! maximum specific leaf area (m**2/gC)
758   REAL(r_std), PARAMETER, DIMENSION(nvmc)     ::    sla_max_mtc = &
759  & (/1.5E-2,1.53E-2, 2.6E-2,9.26E-3, 2E-2, 2.6E-2, 9.26E-3, &
760 &    2.6E-2, 1.9E-2, 2.6E-2,2.6E-2,2.6E-2,2.6E-2 /)
761  ! miniimum specific leaf area (m**2/gC)
762   REAL(r_std), PARAMETER, DIMENSION(nvmc)     ::    sla_min_mtc  = &
763  & (/1.5E-2,1.53E-2, 2.6E-2,9.26E-3, 2E-2, 2.6E-2, 9.26E-3, &
764  &   2.6E-2, 1.9E-2, 2.6E-2,2.6E-2,2.6E-2,2.6E-2 /)
765  !end gmjc
766 
767END MODULE constantes_mtc
Note: See TracBrowser for help on using the repository browser.