source: branches/publications/ORCHIDEE_gmd-2018-182/src_stomate/stomate_assimtemp.f90 @ 7442

Last change on this file since 7442 was 947, checked in by didier.solyga, 12 years ago

Merge Hydrology branch into ORCHIDEE trunk version.

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 6.0 KB
Line 
1! =================================================================================================================================
2! MODULE        : stomate_assimtemp
3!
4! CONTACT       : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE       : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
7!
8!>\BRIEF        Calculate the photosynthesis temperatures.
9!!     
10!!\n DESCRIPTION: None
11!!
12!! RECENT CHANGE(S): None
13!!
14!! SVN          :
15!! $HeadURL$
16!! $Date$
17!! $Revision$
18!! \n
19!_ =================================================================================================================================
20
21MODULE stomate_assimtemp
22
23  ! modules used:
24
25  USE pft_parameters
26  USE constantes 
27
28  IMPLICIT NONE
29
30  ! private & public routines
31
32  PRIVATE
33  PUBLIC assim_temp
34
35CONTAINS
36
37!! ================================================================================================================================
38!! SUBROUTINE   : assim_temp
39!!
40!>\BRIEF        This subroutine calculates the minimal, maximal and optimal
41!! temperatures for photosynthesis.
42!!
43!! \n DESCRIPTION (definitions, functional, design, flags): The temperatures are
44!! calculated as second order polynomials of the long term reference temperature tlong_ref.
45!!
46!! A climatological annual temperature is given as an input file of ORCHIDEE, at a 1.125°(lon)x1.121°(lat) spatial resolution.
47!! This temperature was derived from a IIASA database (Leemans and Cramer, 1991).
48!! This initial climatological annual temperature is first interpolated at the spatial grid of the
49!! meteorological forcing fields in stomate_io.f90::get_reftemp (\f$tlong\_ref\f$).
50!! This long term reference temperature is then updated along the ORCHIDEE run at each stomate time step in stomate_season.f90.
51!!
52!! The polynomial coefficients depend on the PFT and their values are defined in
53!! stomate_constants.f90. Coefficients for degrees 1 and 2 of the polynomials are
54!! zero, meaning the temperatures are just predefined constants (Wullschleger, 1993), except for C3
55!! grasses, which has been designed specifically for ORCHIDEE (no reference publication other than Krinner et al. (2005)).
56!!
57!! This routine is called once at the beginning by stomate_var_init and then at each stomate time step by stomateLpj.
58!!
59!! RECENT CHANGE(S): None
60!!
61!! MAIN OUTPUT VARIABLE(S): minimal (t_photo_min), maximal (t_photo_max) and
62!! optimal temperatures (t_photo_opt) for photosynthesis
63!!
64!! REFERENCE(S) :
65!! - Krinner, G., Viovy, N., Noblet-Ducoudre, N. de, Ogee, J., Polcher, J.,
66!! Friedlingstein, P., Sitch, S., and Prentice, I. C (2005). A dynamic global
67!! vegetation model for studies of the coupled atmosphere-biosphere system.
68!! Global Biogeochem. Cycles, 19, GB1015
69!! - Leemans, R. and Cramer,W. (1991). The IIASA Database for Mean Monthly Values
70!! of Temperature, Precipitation, and Cloudiness on a Global Terrestrial Grid.
71!! Research Report, INTERNATIONAL INSTITUTE FOR APPLIED SYSTEMS ANALYSIS Laxenburg, Austria.
72!! International Standard Book Number 3-7045-0113-1.
73!! - Wullschleger, S.D. (1993). Biochemical limitations to carbon assimilation in C\f$_3\f$ plants:
74!! a retrospective analysis of the A/C\f$_i\f$ curves from 109 species. Journal of Experimental Botany, 44 (262), 907-920
75!!
76!! FLOWCHART    : None
77!!
78!! REVISION(S)  : None
79!! \n
80!_ ================================================================================================================================
81
82  SUBROUTINE assim_temp (npts, tlong_ref, t2m_month, t_photo_min, t_photo_opt, t_photo_max)
83
84    !
85    !! 0. Variable and parameter declaration
86    !
87
88    !
89    !! 0.1 Input variables
90    !
91    INTEGER(i_std), INTENT(in)                                  :: npts        !! Domain size   
92    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref   !! "long term" 2 meter reference temperatures (K)   
93    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_month   !! "monthly" 2-meter temperatures (K)
94
95    !
96    !! 0.2 Output variables
97    !
98    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)               :: t_photo_min !! Minimum temperature for photosynthesis (K)   
99    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)               :: t_photo_opt !! Optimum temperature for photosynthesis (K)   
100    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)               :: t_photo_max !! Maximum temperature for photosynthesis (K)
101
102    !
103    !! 0.3 Modified variables
104    !
105
106    !
107    !! 0.4 Local variables
108    !
109    REAL(r_std), DIMENSION(npts)                                :: tl          !! "Long term" 2 meter reference temperatures
110                                                                               !! (degree C)   
111    INTEGER(i_std)                                              :: j           !! Index (unitless)
112
113!_ ================================================================================================================================
114
115    tl(:) = tlong_ref(:) - ZeroCelsius
116
117    DO j = 2,nvm        ! Loop over # PFTs
118
119       !
120       !! 1. Normal case
121       !
122
123       t_photo_min(:,j) = tphoto_min_c(j) + tphoto_min_b(j)*tl(:) + tphoto_min_a(j)*tl(:)*tl(:) + ZeroCelsius
124       t_photo_opt(:,j) = tphoto_opt_c(j) + tphoto_opt_b(j)*tl(:) + tphoto_opt_a(j)*tl(:)*tl(:) + ZeroCelsius
125       t_photo_max(:,j) = tphoto_max_c(j) + tphoto_max_b(j)*tl(:) + tphoto_max_a(j)*tl(:)*tl(:) + ZeroCelsius
126
127       !
128       !! 2. If the monthly temperature is too low, we set tmax < tmin.
129       !!    Therefore, photosynthesis will not be possible (we need tmin < t < tmax).
130       !     t2m_month is calculated at every stomate time step using a linear relaxation method, in stomate_season.f90
131       !     (see section [27] in Krinner et al. (2005)).
132       !
133
134!! min_stomate is a constant defined in stomate_constants.f90 (= 1.E-8_r_std).
135       WHERE ( t2m_month(:) .LT. t_photo_min(:,j) )
136          t_photo_max(:,j) = t_photo_min(:,j) - min_stomate
137       ENDWHERE
138
139    ENDDO       ! Loop over # PFTs
140
141  END SUBROUTINE assim_temp
142
143END MODULE stomate_assimtemp
Note: See TracBrowser for help on using the repository browser.