source: tags/ORCHIDEE_1_9_5/ORCHIDEE/src_parameters/constantes_co2.f90 @ 8

Last change on this file since 8 was 8, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

File size: 3.4 KB
Line 
1!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_parameters/constantes_co2.f90,v 1.10 2007/05/28 15:28:05 ssipsl Exp $
2!IPSL (2006)
3! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
4!-
5MODULE constantes_co2
6!!--------------------------------------------------------------------
7!! "constantes_co2" module contains some public technical constants
8!!--------------------------------------------------------------------
9  USE constantes_veg
10!-
11  IMPLICIT NONE
12!-
13! indices for assimilation parameters
14!-
15  INTEGER(i_std),PARAMETER :: itmin = 1
16  INTEGER(i_std),PARAMETER :: itopt = 2
17  INTEGER(i_std),PARAMETER :: itmax = 3
18  INTEGER(i_std),PARAMETER :: ivcmax = 4
19  INTEGER(i_std),PARAMETER :: ivjmax = 5
20  INTEGER(i_std),PARAMETER :: npco2 = 5
21!-
22!!
23!! The following tables of parameters for SECHIBA
24!! are in the following order :
25!!
26!!    1 - Bare soil
27!!    2 - tropical  broad-leaved evergreen
28!!    3 - tropical  broad-leaved raingreen
29!!    4 - temperate needleleaf   evergreen
30!!    5 - temperate broad-leaved evergreen
31!!    6 - temperate broad-leaved summergreen
32!!    7 - boreal    needleleaf   evergreen
33!!    8 - boreal    broad-leaved summergreen
34!!    9 - boreal    needleleaf   summergreen
35!!   10 -           C3           grass
36!!   11 -           C4           grass
37!!   12 -           C3           agriculture
38!!   13 -           C4           agriculture
39!!
40! flag for C4 vegetation types
41  LOGICAL,DIMENSION(nvm),SAVE :: &
42 &  is_c4 = (/.false.,.false.,.false.,.false.,.false.,.false., &
43 &            .false.,.false.,.false.,.false.,.true.,.false.,.true. /)
44! Slope of the gs/A relation (Ball & al.)
45  REAL(r_std),DIMENSION(nvm),SAVE :: &
46 &  gsslope = (/0., 9., 9., 9., 9., 9., 9., 9., 9., 9., 3., 9., 3./)
47! intercept of the gs/A relation (Ball & al.)
48  REAL(r_std),DIMENSION(nvm),SAVE :: &
49 &  gsoffset = (/0.0,  0.01, 0.01, 0.01, 0.01, 0.01, &
50 &               0.01, 0.01, 0.01, 0.01, 0.03, 0.01, 0.03/)
51! values used for vcmax when STOMATE is not activated
52  REAL(r_std),DIMENSION(nvm),SAVE :: &
53 &  vcmax_fix = (/  0., 40., 50., 30., 35., 40., &
54 &                 30., 40., 35., 60., 60., 70., 70. /)
55! values used for vjmax when STOMATE is not activated
56  REAL(r_std),DIMENSION(nvm),SAVE :: &
57 &  vjmax_fix = (/ 0., 80., 100., 60., 70., 80., &
58 &                 60., 80., 70., 120., 120., 140., 140. /)
59! values used for photosynthesis tmin when STOMATE is not activated
60  REAL(r_std),DIMENSION(nvm),SAVE :: &
61 &  co2_tmin_fix = (/ 0.,  2.,  2., -4., -3., -2., &
62 &                   -4., -4., -4., -5.,  6., -5.,  6. /)
63! values used for photosynthesis topt when STOMATE is not activated
64  REAL(r_std),DIMENSION(nvm),SAVE :: &
65 &  co2_topt_fix = (/  0.,  27.5, 27.5, 17.5, 25.,  20.,  &
66 &                    17.5, 17.5, 17.5, 20.,  32.5, 20.,  32.5 /)
67! values used for photosynthesis tmax when STOMATE is not activated
68  REAL(r_std),DIMENSION(nvm),SAVE :: &
69 &  co2_tmax_fix = (/ 0., 55., 55., 38., 48., 38., &
70 &                   38., 38., 38., 45., 55., 45., 55. /)
71! extinction coefficient of the Monsi&Seaki relationship (1953)
72  REAL(r_std),DIMENSION(nvm),SAVE :: &
73 &  ext_coef = (/.5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5, .5/)
74! NV080800 Name of STOMATE forcing file
75  CHARACTER(LEN=100) :: stomate_forcing_name='NONE'
76! NV080800 Name of soil forcing file
77  CHARACTER(LEN=100) :: stomate_Cforcing_name='NONE'
78!-
79  INTEGER(i_std),SAVE :: forcing_id
80!------------------------
81END MODULE constantes_co2
Note: See TracBrowser for help on using the repository browser.