!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_constants.f90,v 1.21 2010/05/17 14:25:41 ssipsl Exp $ !IPSL (2006) ! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC !- MODULE stomate_constants !--------------------------------------------------------------------- USE defprec USE constantes_veg USE ioipsl USE parallel ! bare soil in Sechiba INTEGER(i_std),PARAMETER :: ibare_sechiba = 1 !- ! 0 = no, 4 = full online diagnostics INTEGER(i_std),SAVE :: bavard=1 ! write forcing file for carbon spinup? LOGICAL,SAVE :: write_carbonforce ! Horizontal indices INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: hori_index ! Horizonatal + PFT indices INTEGER(i_std),ALLOCATABLE,SAVE,DIMENSION(:) :: horipft_index !- ! Land cover change ! Horizontal + P10 indices INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip10_index ! Horizontal + P100 indices INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip100_index ! Horizontal + P11 indices INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip11_index ! Horizontal + P101 indices INTEGER(i_std), ALLOCATABLE, SAVE, DIMENSION(:) :: horip101_index !- ! time step INTEGER(i_std),SAVE :: itime ! STOMATE history file ID INTEGER(i_std),SAVE :: hist_id_stomate ! STOMATE history file ID for IPCC output INTEGER(i_std),SAVE :: hist_id_stomate_IPCC ! STOMATE restart file ID INTEGER(i_std),SAVE :: rest_id_stomate !- ! Freezing point REAL(r_std),PARAMETER :: ZeroCelsius = 273.15 ! e REAL(r_std),PARAMETER :: euler = 2.71828182846 ! Epsilon to detect a near zero floating point REAL(r_std),PARAMETER :: min_stomate = 1.E-8_r_std ! some large value REAL(r_std),PARAMETER :: large_value = 1.E33_r_std ! Special value REAL(r_std),PARAMETER :: undef = -9999. !- ! maximum reference long term temperature (K) REAL(r_std),PARAMETER :: tlong_ref_max=303.1 ! minimum reference long term temperature (K) REAL(r_std),PARAMETER :: tlong_ref_min=253.1 !- ! trees and litter: indices for the parts of heart- and sapwood above ! and below the ground INTEGER(i_std),PARAMETER :: iabove = 1 INTEGER(i_std),PARAMETER :: ibelow = 2 INTEGER(i_std),PARAMETER :: nlevs = 2 !- ! litter: indices for metabolic and structural part INTEGER(i_std),PARAMETER :: imetabolic = 1 INTEGER(i_std),PARAMETER :: istructural = 2 INTEGER(i_std),PARAMETER :: nlitt = 2 !- ! carbon pools: indices INTEGER(i_std),PARAMETER :: iactive = 1 INTEGER(i_std),PARAMETER :: islow = 2 INTEGER(i_std),PARAMETER :: ipassive = 3 INTEGER(i_std),PARAMETER :: ncarb = 3 !- ! litter fractions: indices INTEGER(i_std),PARAMETER :: ileaf = 1 INTEGER(i_std),PARAMETER :: isapabove = 2 INTEGER(i_std),PARAMETER :: isapbelow = 3 INTEGER(i_std),PARAMETER :: iheartabove = 4 INTEGER(i_std),PARAMETER :: iheartbelow = 5 INTEGER(i_std),PARAMETER :: iroot = 6 INTEGER(i_std),PARAMETER :: ifruit = 7 INTEGER(i_std),PARAMETER :: icarbres = 8 INTEGER(i_std),PARAMETER :: nparts = 8 !- ! transformation between types of surface INTEGER(i_std),PARAMETER :: ito_natagri = 1 INTEGER(i_std),PARAMETER :: ito_total = 2 !- ! leaf age discretisation ( 1 = no discretisation ) INTEGER(i_std),PARAMETER :: nleafages = 4 !- ! alpha's : ? REAL(r_std),PARAMETER :: alpha_grass = .5 REAL(r_std),PARAMETER :: alpha_tree = 1. !- ! type declaration for photosynthesis TYPE t_photo_type REAL(r_std), DIMENSION(nvm) :: t_max_a REAL(r_std), DIMENSION(nvm) :: t_max_b REAL(r_std), DIMENSION(nvm) :: t_max_c REAL(r_std), DIMENSION(nvm) :: t_opt_a REAL(r_std), DIMENSION(nvm) :: t_opt_b REAL(r_std), DIMENSION(nvm) :: t_opt_c REAL(r_std), DIMENSION(nvm) :: t_min_a REAL(r_std), DIMENSION(nvm) :: t_min_b REAL(r_std), DIMENSION(nvm) :: t_min_c END TYPE t_photo_type !- ! type declaration for phenology TYPE pheno_type REAL(r_std), DIMENSION(nvm,3) :: gdd REAL(r_std), DIMENSION(nvm) :: ngd REAL(r_std), DIMENSION(nvm) :: ncdgdd_temp REAL(r_std), DIMENSION(nvm) :: hum_frac REAL(r_std), DIMENSION(nvm) :: lowgpp_time REAL(r_std), DIMENSION(nvm) :: leaffall REAL(r_std), DIMENSION(nvm) :: leafagecrit REAL(r_std) :: tau_hum_month REAL(r_std) :: tau_hum_week REAL(r_std) :: tau_t2m_month REAL(r_std) :: tau_t2m_week REAL(r_std) :: tau_tsoil_month REAL(r_std) :: tau_soilhum_month REAL(r_std) :: tau_gpp_week REAL(r_std) :: tau_gdd REAL(r_std) :: tau_ngd REAL(r_std) :: tau_longterm REAL(r_std), DIMENSION(nvm) :: lai_initmin CHARACTER(len=6), DIMENSION(nvm) :: pheno_model CHARACTER(len=6), DIMENSION(nvm) :: senescence_type REAL(r_std), DIMENSION(nvm,3) :: senescence_temp REAL(r_std), DIMENSION(nvm) :: senescence_hum REAL(r_std), DIMENSION(nvm) :: nosenescence_hum REAL(r_std), DIMENSION(nvm) :: max_turnover_time REAL(r_std), DIMENSION(nvm) :: min_leaf_age_for_senescence REAL(r_std), DIMENSION(nvm) :: min_turnover_time !- REAL(r_std), DIMENSION(nvm) :: hum_min_time END TYPE pheno_type !- ! parameters for the pipe model !- ! crown area = pipe_tune1. stem diameter**(1.6) (Reinicke's theory) REAL(r_std),PARAMETER :: pipe_tune1 = 100.0 ! height=pipe_tune2 * diameter**pipe_tune3 REAL(r_std),PARAMETER :: pipe_tune2 = 40.0 REAL(r_std),PARAMETER :: pipe_tune3 = 0.5 ! needed for stem diameter REAL(r_std),PARAMETER :: pipe_tune4 = 0.3 ! Density REAL(r_std),PARAMETER :: pipe_density = 2.e5 ! one more parameter REAL(r_std),PARAMETER :: pipe_k1 = 8.e3 !- ! Maximum tree establishment rate REAL(r_std),PARAMETER :: estab_max_tree = 0.12 ! Maximum grass establishment rate REAL(r_std),PARAMETER :: estab_max_grass = 0.12 ! initial density of individuals REAL(r_std),PARAMETER :: ind_0 = 0.02 !- ! Do we treat PFT expansion across a grid point after introduction? ! default = .FALSE. LOGICAL,SAVE :: treat_expansion = .FALSE. !- ! herbivores? LOGICAL,SAVE :: ok_herbivores = .FALSE. !- ! harvesting ? LOGICAL,SAVE :: harvest_agri = .TRUE. !- ! For trees, minimum fraction of crown area occupied ! (due to its branches etc.) ! This means that only a small fraction of its crown area ! can be invaded by other trees. REAL(r_std),PARAMETER :: min_cover = 0.05 !- ! climatic parameters !- ! minimum precip, in mm/year REAL(r_std),PARAMETER :: precip_crit = 100. ! minimum gdd for establishment of saplings REAL(r_std),PARAMETER :: gdd_crit = 150. ! critical fpc, needed for light competition and establishment REAL(r_std),PARAMETER :: fpc_crit = 0.95 !- ! critical value for being adapted (1-1/e) REAL(r_std),PARAMETER :: adapted_crit = 1. - ( 1. / euler ) ! critical value for being regenerative (1/e) REAL(r_std),PARAMETER :: regenerate_crit = 1. / euler !- ! fraction of GPP which is lost as growth respiration REAL(r_std),PARAMETER :: frac_growthresp = 0.28 !- ! description of the PFT CHARACTER(len=34), SAVE, DIMENSION(nvm) :: PFT_name = & & (/ 'bared ground ', & ! 1 & 'tropical broad-leaved evergreen ', & ! 2 & 'tropical broad-leaved raingreen ', & ! 3 & 'temperate needleleaf evergreen ', & ! 4 & 'temperate broad-leaved evergreen ', & ! 5 & 'temperate broad-leaved summergreen', & ! 6 & 'boreal needleleaf evergreen ', & ! 7 & 'boreal broad-leaved summergreen', & ! 8 & 'boreal needleleaf summergreen', & ! 9 & ' C3 grass ', & ! 10 & ' C4 grass ', & ! 11 & ' C3 agriculture', & ! 12 & ' C4 agriculture' /) ! 13 ! extinction coefficient of the Monsi&Seaki (53) relationship REAL(r_std), SAVE, DIMENSION(nvm) :: ext_coeff ! is pft a tree LOGICAL, SAVE, DIMENSION(nvm) :: tree ! leaf type ! 1=broad leaved tree, 2=needle leaved tree, 3=grass 4=bared ground INTEGER(i_std), SAVE, DIMENSION(nvm) :: leaf_tab = & & (/ 4, 1, 1, 2, 1, 1, 2, & & 1, 2, 3, 3, 3, 3 /) ! natural? LOGICAL, SAVE, DIMENSION(nvm) :: natural = & & (/ .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., .TRUE., & & .TRUE., .TRUE., .TRUE., .TRUE., .FALSE., .FALSE. /) ! flamability: critical fraction of water holding capacity REAL(r_std), SAVE, DIMENSION(nvm) :: flam ! fire resistance REAL(r_std), SAVE, DIMENSION(nvm) :: resist ! specific leaf area (m**2/gC) REAL(r_std), SAVE, DIMENSION(nvm) :: sla ! sapling biomass (gC/ind) REAL(r_std), SAVE, DIMENSION(nvm,nparts) :: bm_sapl ! migration speed (m/year) REAL(r_std), SAVE, DIMENSION(nvm) :: migrate ! maximum stem diameter from which on crown area no longer increases (m) REAL(r_std), SAVE, DIMENSION(nvm) :: maxdia ! crown of tree when sapling (m**2) REAL(r_std), SAVE, DIMENSION(nvm) :: cn_sapl ! critical minimum temperature (K) REAL(r_std), SAVE, DIMENSION(nvm) :: tmin_crit ! critical temperature of the coldest month (K) REAL(r_std), SAVE, DIMENSION(nvm) :: tcm_crit ! critical values for phenology TYPE(pheno_type),SAVE :: pheno_crit ! time constant for leaf age discretisation (d) REAL(r_std), SAVE, DIMENSION(nvm) :: leaf_timecst ! maximum LAI, PFT-specific REAL(r_std), SAVE, DIMENSION (nvm) :: lai_max ! maintenance respiration coefficient (g/g/day) at 0 deg C REAL(r_std), SAVE, DIMENSION(nvm,nparts) :: coeff_maint_zero ! slope of maintenance respiration coefficient (1/K, 1/K^2, 1/K^3) REAL(r_std), SAVE, DIMENSION(nvm,3) :: maint_resp_slope ! residence time (y) of trees REAL(r_std), SAVE, DIMENSION(nvm) :: residence_time ! leaf lifetime, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: leaflife_tab ! type of phenology ! 0=bared ground 1=evergreen, 2=summergreen, 3=raingreen, 4=perennial ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen" INTEGER(i_std), SAVE, DIMENSION(nvm) :: pheno_type_tab ! critical tmin, tabulated (C) REAL(r_std), SAVE, DIMENSION(nvm) :: tmin_crit_tab ! critical tcm, tabulated (C) REAL(r_std), SAVE, DIMENSION(nvm) :: tcm_crit_tab ! critical gdd, tabulated (C), constant c of aT^2+bT+c REAL(r_std), SAVE, DIMENSION(nvm) :: gdd_crit1_tab ! critical gdd, tabulated (C), constant b of aT^2+bT+c REAL(r_std), SAVE, DIMENSION(nvm) :: gdd_crit2_tab ! critical gdd, tabulated (C), constant a of aT^2+bT+c REAL(r_std), SAVE, DIMENSION(nvm) :: gdd_crit3_tab ! critical ngd, tabulated. Threshold -5 degrees REAL(r_std), SAVE, DIMENSION(nvm) :: ngd_crit_tab ! critical temperature for the ncd vs. gdd function in phenology REAL(r_std), SAVE, DIMENSION(nvm) :: ncdgdd_temp_tab ! critical humidity (relative to min/max) for phenology REAL(r_std), SAVE, DIMENSION(nvm) :: hum_frac_tab ! minimum duration of dormance (d) for phenology REAL(r_std), SAVE, DIMENSION(nvm) :: lowgpp_time_tab ! minimum time elapsed since moisture minimum (d) REAL(r_std), SAVE, DIMENSION(nvm) :: hum_min_time_tab ! sapwood -> heartwood conversion time (d) REAL(r_std), SAVE, DIMENSION(nvm) :: tau_sap ! fruit lifetime (d) REAL(r_std), SAVE, DIMENSION(nvm) :: tau_fruit ! fraction of primary leaf and root allocation put into reserve REAL(r_std), SAVE, DIMENSION(nvm) :: ecureuil ! Maximum rate of carboxylation REAL(r_std), SAVE, DIMENSION(nvm) :: vcmax_opt ! Maximum rate of RUbp regeneration REAL(r_std), SAVE, DIMENSION(nvm) :: vjmax_opt !- ! constants needed for photosynthesis temperatures TYPE(t_photo_type), SAVE :: t_photo ! lenth of death of leaves, tabulated (d) REAL(r_std), SAVE, DIMENSION(nvm) :: leaffall_tab ! critical leaf age, tabulated (d) REAL(r_std), SAVE, DIMENSION(nvm) :: leafagecrit_tab ! which phenology model is used? (tabulated) CHARACTER(len=6), SAVE, DIMENSION(nvm) :: pheno_model_tab ! List of avaible phenology models : ! 'hum ', 'moi ', 'ncdgdd', 'ngd ', 'humgdd', 'moigdd', 'none ' ! type of senescence, tabulated CHARACTER(len=6), SAVE, DIMENSION(nvm) :: senescence_type_tab !- ! List of avaible types of senescence : ! 'cold ', 'dry ', 'mixed ', 'none ' ! critical temperature for senescence (C), ! constant c of aT^2+bT+c , tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: senescence_temp1_tab ! critical temperature for senescence (C), ! constant b of aT^2+bT+c , tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: senescence_temp2_tab ! critical temperature for senescence (C), ! constant a of aT^2+bT+c , tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: senescence_temp3_tab ! critical relative moisture availability for senescence REAL(r_std), SAVE, DIMENSION(nvm) :: senescence_hum_tab ! relative moisture availability above which ! there is no humidity-related senescence REAL(r_std), SAVE, DIMENSION(nvm) :: nosenescence_hum_tab ! maximum turnover time for grasse REAL(r_std), SAVE, DIMENSION(nvm) :: max_turnover_time_tab ! minimum turnover time for grasse REAL(r_std), SAVE, DIMENSION(nvm) :: min_turnover_time_tab ! minimum leaf age to allow senescence g REAL(r_std), SAVE, DIMENSION(nvm) :: min_leaf_age_for_senescence_tab !- ! slope of maintenance respiration coefficient (1/K), ! constant c of aT^2+bT+c , tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: maint_resp_slope1_tab ! slope of maintenance respiration coefficient (1/K), ! constant b of aT^2+bT+c , tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: maint_resp_slope2_tab ! slope of maintenance respiration coefficient (1/K), ! constant a of aT^2+bT+c , tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: maint_resp_slope3_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for leaves, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_leaf_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for sapwood above, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_sapabove_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for sapwood below, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_sapbelow_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for heartwood above, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_heartabove_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for heartwood below, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_heartbelow_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for roots, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_root_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for fruits, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_fruit_tab ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for carbohydrate reserve, tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: cm_zero_carbres_tab !- ! minimum photosynthesis temperature, ! constant a of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_min_a_tab ! minimum photosynthesis temperature, ! constant b of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_min_b_tab ! minimum photosynthesis temperature, ! constant c of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_min_c_tab !- ! optimum photosynthesis temperature, ! constant a of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_opt_a_tab ! optimum photosynthesis temperature, ! constant b of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_opt_b_tab ! optimum photosynthesis temperature, ! constant c of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_opt_c_tab !- ! maximum photosynthesis temperature, ! constant a of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_max_a_tab ! maximum photosynthesis temperature, ! constant b of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_max_b_tab ! maximum photosynthesis temperature, ! constant c of ax^2+bx+c (deg C), tabulated REAL(r_std), SAVE, DIMENSION(nvm) :: tphoto_max_c_tab ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF REAL(r_std), SAVE, DIMENSION(nvm) :: alloc_min REAL(r_std), SAVE, DIMENSION(nvm) :: alloc_max REAL(r_std), SAVE, DIMENSION(nvm) :: demi_alloc ! Coeff of biomass export for the year REAL(r_std), SAVE, DIMENSION(nvm) :: coeff_lcchange_1 ! Coeff of biomass export for the decade REAL(r_std), SAVE, DIMENSION(nvm) :: coeff_lcchange_10 ! Coeff of biomass export for the century REAL(r_std), SAVE, DIMENSION(nvm) :: coeff_lcchange_100 CONTAINS SUBROUTINE stomate_constants_init () ! flamability: critical fraction of water holding capacity flam(2:nvm) = & & (/ .15, .25, .25, .25, .25, .25, & .25, .25, .25, .25, .35, .35 /) !!$ flam(2:nvm) = & !!$ & (/ .25, .25, .25, .25, .25, .25, & !!$ .25, .25, .30, .30, .35, .35 /) ! flam = & ! & (/ .15, .15, .15, .15, .15, .15, & ! & .15, .15, .15, .15, .15, .15 /) ! fire resistance resist(2:nvm) = & & (/ .95, .90, .12, .50, .12, .12, & & .12, .12, .0, .0, .0, .0 /) !!$ resist(2:nvm) = & !!$ & (/ .12, .50, .12, .50, .12, .12, & !!$ & .12, .12, .0, .0, .0, .0 /) ! maximum LAI, PFT-specific lai_max(:) = & & (/ undef, & & 7., 7., 5., 5., 5., 4.5, & & 4.5, 3.0, 2.5, 2.5, 5., 5. /) ! residence time (y) of trees residence_time(2:nvm) = & & (/ 30.0, 30.0, 40.0, 40.0, 40.0, 80.0, & & 80.0, 80.0, 0.0, 0.0, 0.0, 0.0 /) ! leaf lifetime, tabulated !SZ modif to LPJ values leaflife_tab(2:nvm) = & & (/ .5, 2., .33, 1., 2., .33, & & 2., 2., 2., 2., 2., 2. /) !!$ leaflife_tab(2:nvm) = & !!$ & (/ .5, 1., .5, .5, 1., .5, & !!$ & 1., 1., 1., 1., 1., 1. /) ! type of phenology ! 0=bared ground 1=evergreen, 2=summergreen, 3=raingreen, 4=perennial ! Pour l'instant, le phénotype de sol nu n'est pas géré aussi on traitera les sols nu comme "evergreen" pheno_type_tab(2:nvm) = & & (/ 1, 3, 1, 1, 2, 1, & & 2, 2, 4, 4, 2, 3 /) ! critical tmin, tabulated (C) tmin_crit_tab(2:nvm) = & & (/ 0.0, 0.0, -45.0, -10.0, -45.0, -60.0, & & -60.0, undef, undef, undef, undef, undef /) ! critical tcm, tabulated (C) tcm_crit_tab(2:nvm) = & & (/ undef, undef, 5.0, 15.5, 15.5, -2.0, & & 5.0, -2.0, undef, undef, undef, undef /) ! critical gdd, tabulated (C), constant c of aT^2+bT+c gdd_crit1_tab(2:nvm) = & & (/ undef, undef, undef, undef, undef, undef, & & undef, undef, 270., 400., 125., 400. /) !!$ gdd_crit1_tab(2:nvm) = & !!$ & (/ undef, undef, undef, undef, undef, undef, & !!$ & undef, undef, 184.375, 400., 125., 400. /) ! critical gdd, tabulated (C), constant b of aT^2+bT+c gdd_crit2_tab(2:nvm) = & & (/ undef, undef, undef, undef, undef, undef, & & undef, undef, 6.25, 0., 0., 0. /) ! critical gdd, tabulated (C), constant a of aT^2+bT+c gdd_crit3_tab(2:nvm) = & & (/ undef, undef, undef, undef, undef, undef, & & undef, undef, 0.03125, 0., 0., 0. /) ! critical ngd, tabulated. Threshold -5 degrees ngd_crit_tab(2:nvm) = & & (/ undef, undef, undef, undef, undef, undef, & & undef, 17., undef, undef, undef, undef /) ! critical temperature for the ncd vs. gdd function in phenology ncdgdd_temp_tab(2:nvm) = & & (/ undef, undef, undef, undef, 5., undef, & & 0., undef, undef, undef, undef, undef /) ! critical humidity (relative to min/max) for phenology hum_frac_tab(2:nvm) = & & (/ undef, .5, undef, undef, undef, undef, & & undef, undef, .5, .5, .5, .5 /) ! minimum duration of dormance (d) for phenology lowgpp_time_tab(2:nvm) = & & (/ undef, 30., undef, undef, 30., undef, & & 30., 30., 30., 30., 30., 30. /) ! minimum time elapsed since moisture minimum (d) hum_min_time_tab(2:nvm) = & & (/ undef, 50., undef, undef, undef, undef, & & undef, undef, 35., 35., 75., 75. /) ! sapwood -> heartwood conversion time (d) tau_sap(2:nvm) = & & (/ 730., 730., 730., 730., 730., 730., & & 730., 730., undef, undef, undef, undef /) ! fruit lifetime (d) tau_fruit(2:nvm) = & & (/ 90., 90., 90., 90., 90., 90., & & 90., 90., undef, undef, undef, undef /) ! fraction of primary leaf and root allocation put into reserve ecureuil(2:nvm) = & & (/ .0, 1., .0, .0, 1., .0, & & 1., 1., 1., 1., 1., 1. /) ! Maximum rate of carboxylation !Shilong vcmax_opt(:) = & & (/ undef, & & 65., 65., 35., 45., 55., 35., & & 45., 35., 70., 70., 70., 70. /) CALL getin_p("vcmax_opt", vcmax_opt) ! 1.9.3 !!$ vcmax_opt(2:nvm) = & !!$ & (/ 65., 65., 35., 40., 55., 35., & !!$ & 45., 35., 70., 70., 70., 70. / ! OLD HEAD before 1.9.3 !!$ vcmax_opt(2:nvm) = & !!$ & (/ 65., 65., 35., 40., 55., 35., & !!$ & 45., 35., 80., 80., 100., 100. /) !modif jerome carbofor ! vcmax_opt = & ! & (/ 65., 65., 50., 40., 75., 35., & ! & 45., 35., 80., 80., 100., 100. /) !DATA vcmax_opt_tab / 0., 65., 65., 37.5, 45., 60., 37.5, & ! 50., 40., 100., 100., 100., 100. / !- ! Maximum rate of RUbp regeneration vjmax_opt(2:nvm) = & & (/ 130., 130., 70., 80., 110., 70., & & 90., 70., 160., 160., 200., 200. /) !- !DATA vjmax_opt_tab / 0., 130., 130., 75., 90., 120., 75., & ! 100., 80., 200., 200., 200., 200. / !- ! length of death of leaves, tabulated (d) leaffall_tab(2:nvm) = & & (/ undef, 10., undef, undef, 10., undef, & & 10., 10., 10., 10., 10., 10. /) ! critical leaf age, tabulated (d) ! Shilong modification leafagecrit_tab(2:nvm) = & & (/ 730., 180., 910., 730., 180., 910., & & 180., 180., 120., 120., 90., 90. /) ! OLD HEAD !!$ DATA leafagecrit_tab / 730., 180., 910., 730., 180., 910., & !!$ 180., 180., 120., 120., 120., 120. / !NEW SHILONG ! & (/ 730., 180., 910., 730., 180., 910., & ! & 180., 180., 120., 120., 70., 70. /) !- ! which phenology model is used? (tabulated) pheno_model_tab(1:nvm) = & & (/ 'none ', 'none ', 'moi ', 'none ', 'none ', & & 'ncdgdd', 'none ', 'ncdgdd', 'ngd ', 'moigdd', & & 'moigdd', 'moigdd', 'moigdd' /) ! List of avaible phenology models : ! 'hum ', 'moi ', 'ncdgdd', 'ngd ', 'humgdd', 'moigdd', 'none ' !- ! type of senescence, tabulated senescence_type_tab(1:nvm) = & & (/ 'none ', 'none ', 'dry ', 'none ', 'none ', & & 'cold ', 'none ', 'cold ', 'cold ', 'mixed ', & & 'mixed ', 'mixed ', 'mixed ' /) !- ! List of avaible types of senescence : ! 'cold ', 'dry ', 'mixed ', 'none ' !- ! critical temperature for senescence (C), ! constant c of aT^2+bT+c , tabulated senescence_temp1_tab(2:nvm) = & & (/ undef, undef, undef, undef, 12., undef, & & 7., 2., -1.375, 5., 5., 10. /) ! critical temperature for senescence (C), ! constant b of aT^2+bT+c , tabulated senescence_temp2_tab(2:nvm) = & & (/ undef, undef, undef, undef, 0., undef, & & 0., 0., .1, 0., 0., 0. /) ! critical temperature for senescence (C), ! constant a of aT^2+bT+c , tabulated senescence_temp3_tab(2:nvm) = & & (/ undef, undef, undef, undef, 0., undef, & & 0., 0., .00375, 0., 0., 0. /) ! critical relative moisture availability for senescence !SZ 080806, reparameterisation of TrBR: reduce criticial moisture from .6 to .3 ! to mimic a leaf dropping at -1.49 MPa, buffered to account for sechiba senescence_hum_tab(2:nvm) = & & (/ undef, .3, undef, undef, undef, undef, & & undef, undef, .2, .2, .3, .2 /) ! 1.9.3 !!$ senescence_hum_tab(2:nvm) = & !!$ & (/ undef, .6, undef, undef, undef, undef, & !!$ & undef, undef, .2, .2, .3, .2 /) ! relative moisture availability above which ! there is no humidity-related senescence !SZ 080806, reparameterisation of TrBR: reduce nosenencemoisture to avoid leaf dropping ! when phenology routine would give new flushing of leaves: 1.0 to 0.8 nosenescence_hum_tab(2:nvm) = & & (/ undef, .8, undef, undef, undef, undef, & & undef, undef, .3, .3, .3, .3 /) ! 1.9.3 !!$ nosenescence_hum_tab(2:nvm) = & !!$ & (/ undef, 1., undef, undef, undef, undef, & !!$ & undef, undef, .3, .3, .3, .3 /) ! maximum turnover time for grasse max_turnover_time_tab(2:nvm) = & & (/ undef, undef, undef, undef, undef, undef, & & undef, undef, 80., 80., 80., 80. /) ! minimum turnover time for grasse min_turnover_time_tab(2:nvm) = & & (/ undef, undef, undef, undef, undef, undef, & & undef, undef, 10., 10., 10., 10. /) ! minimum leaf age to allow senescence g min_leaf_age_for_senescence_tab(:) = & & (/ undef, & & undef, 90., undef, undef, 90., undef, & & 60., 60., 30., 30., 30., 30. /) !- ! slope of maintenance respiration coefficient (1/K), ! constant c of aT^2+bT+c , tabulated !SZ - 1.9.3 maint_resp_slope1_tab(2:nvm) = & & (/ .12, .12, .16, .16, .16, .16, & & .16, .16, .16, .12, .16, .12 /) !OLD MERGE !!$ maint_resp_slope1_tab(2:nvm) = & !!$ & (/ .16, .16, .16, .16, .16, .16, & !!$ & .16, .16, .16, .12, .16, .16 /) !Shilong !!$ maint_resp_slope1_tab(2:nvm) = & !!$ & (/ .12, .12, .16, .16, .16, .16, & !!$ & .16, .16, .16, .16, .16, .16 /) !- ! slope of maintenance respiration coefficient (1/K), ! constant b of aT^2+bT+c , tabulated maint_resp_slope2_tab(2:nvm) = & & (/ .0, .0, .0, .0, .0, .0, & & .0, .0, -.00133, .0, -.00133, .0 /) ! DATA maint_resp_slope2_tab / .0, .0, .0, .0, .0, .0, .0, & ! .0, .0, .0, .0, .0, .0 / ! slope of maintenance respiration coefficient (1/K), ! constant a of aT^2+bT+c , tabulated maint_resp_slope3_tab(2:nvm) = & & (/ .0, .0, .0, .0, .0, .0, & & .0, .0, .0, .0, .0, .0 /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for leaves, tabulated cm_zero_leaf_tab(2:nvm) = & & (/ 2.35E-3, 2.62E-3, 1.01E-3, 2.35E-3, 2.62E-3, 1.01E-3, & & 2.62E-3, 2.05E-3, 2.62E-3, 2.62E-3, 2.62E-3, 2.62E-3 /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for sapwood above, tabulated cm_zero_sapabove_tab(2:nvm) = & & (/ 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for sapwood below, tabulated cm_zero_sapbelow_tab(2:nvm) = & & (/ 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for heartwood above, tabulated cm_zero_heartabove_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0., 0., 0., 0. /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for heartwood below, tabulated cm_zero_heartbelow_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0., 0., 0., 0. /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for roots, tabulated cm_zero_root_tab(2:nvm) = & & (/ 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, & & 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3, 1.67E-3 /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for fruits, tabulated cm_zero_fruit_tab(2:nvm) = & & (/ 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !- ! maintenance respiration coefficient (g/g/day) at 0 deg C, ! for carbohydrate reserve, tabulated cm_zero_carbres_tab(2:nvm) = & & (/ 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, & & 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4, 1.19E-4 /) !- ! minimum photosynthesis temperature, ! constant a of ax^2+bx+c (deg C), tabulated tphoto_min_a_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0.0025, 0., 0., 0. /) !- ! minimum photosynthesis temperature, ! constant b of ax^2+bx+c (deg C), tabulated tphoto_min_b_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0.1, 0., 0., 0. /) !- ! minimum photosynthesis temperature, ! constant c of ax^2+bx+c (deg C), tabulated tphoto_min_c_tab(2:nvm) = & & (/ 2., 2., -4., -3., -2., -4., & & -4., -4., -3.25, 13., -5., 13. /) !- ! optimum photosynthesis temperature, ! constant a of ax^2+bx+c (deg C), tabulated tphoto_opt_a_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & 0., 0., 0.0025, 0., 0., 0. /) ! optimum photosynthesis temperature, ! constant b of ax^2+bx+c (deg C), tabulated tphoto_opt_b_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0.25, 0., 0., 0. /) !- ! optimum photosynthesis temperature, ! constant c of ax^2+bx+c (deg C), tabulated tphoto_opt_c_tab(2:nvm) = & & (/ 37., 37., 25., 32., 26., 25., & & 25., 25., 27.25, 36., 30., 36. /) !- ! maximum photosynthesis temperature, ! constant a of ax^2+bx+c (deg C), tabulated tphoto_max_a_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0.00375, 0., 0., 0. /) !- ! maximum photosynthesis temperature, ! constant b of ax^2+bx+c (deg C), tabulated tphoto_max_b_tab(2:nvm) = & & (/ 0., 0., 0., 0., 0., 0., & & 0., 0., 0.35, 0., 0., 0. /) !- ! maximum photosynthesis temperature, ! constant c of ax^2+bx+c (deg C), tabulated tphoto_max_c_tab(2:nvm) = & & (/ 55., 55., 38., 48., 38., 38., & & 38., 38., 41.125, 55., 45., 55. /) !- ! NEW - allocation above/below = f(age) - 30/01/04 NV/JO/PF alloc_min(2:nvm) = & & (/ 0.2, 0.2, 0.2, 0.2, 0.2, 0.2, & & 0.2, 0.2, undef, undef, undef, undef /) alloc_max(2:nvm) = & & (/ 0.8, 0.8, 0.8, 0.8, 0.8, 0.8, & & 0.8, 0.8, undef, undef, undef, undef /) demi_alloc(2:nvm) = & & (/ 5., 5., 5., 5., 5., 5., & & 5., 5., undef, undef, undef, undef /) ! Coeff of biomass export for the year coeff_lcchange_1(2:nvm) = & & (/ 0.597, 0.597, 0.597, 0.597, 0.597, 0.597, & & 0.597, 0.597, 0.597, 0.597, 0.597, 0.597 /) ! Coeff of biomass export for the decade coeff_lcchange_10(2:nvm) = & & (/ 0.403, 0.403, 0.299, 0.299, 0.299, 0.299, & & 0.299, 0.299, 0.299, 0.403, 0.299, 0.403 /) ! Coeff of biomass export for the century coeff_lcchange_100(2:nvm) = & & (/ 0., 0., 0.104, 0.104, 0.104, 0.104, & & 0.104, 0.104, 0.104, 0., 0.104, 0. /) END SUBROUTINE stomate_constants_init !--------------------------- END MODULE stomate_constants