source: tags/ORCHIDEE_1_9_5/ORCHIDEE/src_stomate/stomate_assimtemp.f90

Last change on this file 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: 2.4 KB
Line 
1! calculates the photosynthesis temperatures
2!
3! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_assimtemp.f90,v 1.7 2009/01/06 17:18:32 ssipsl Exp $
4! IPSL (2006)
5!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
6!
7MODULE stomate_assimtemp
8
9  ! modules used:
10
11  USE stomate_constants
12  USE constantes_veg
13
14  IMPLICIT NONE
15
16  ! private & public routines
17
18  PRIVATE
19  PUBLIC assim_temp
20
21CONTAINS
22
23  SUBROUTINE assim_temp (npts, tlong_ref, t2m_month, t_photo_min, t_photo_opt, t_photo_max)
24
25    !
26    ! 0 declarations
27    !
28
29    ! 0.1 input
30
31    ! Domain size
32    INTEGER(i_std), INTENT(in)                                        :: npts
33    ! "long term" 2 meter reference temperatures (K)
34    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
35    ! "monthly" 2-meter temperatures (K)
36    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m_month
37
38    ! 0.2 output
39    ! Minimum temperature for photosynthesis (K)
40    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: t_photo_min
41    ! Optimum temperature for photosynthesis (K)
42    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: t_photo_opt
43    ! Maximum temperature for photosynthesis (K)
44    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: t_photo_max
45
46    ! 0.3 local
47    ! "long term" 2 meter reference temperatures (deg C)
48    REAL(r_std), DIMENSION(npts)                                :: tl
49    ! Index
50    INTEGER(i_std)                                             :: j
51
52    ! =========================================================================
53
54    tl(:) = tlong_ref(:) - ZeroCelsius
55
56    DO j = 2,nvm
57
58       !
59       ! 1 normal case
60       !
61
62       t_photo_min(:,j) = t_photo%t_min_c(j) + t_photo%t_min_b(j)*tl(:) + t_photo%t_min_a(j)*tl(:)*tl(:) + ZeroCelsius
63       t_photo_opt(:,j) = t_photo%t_opt_c(j) + t_photo%t_opt_b(j)*tl(:) + t_photo%t_opt_a(j)*tl(:)*tl(:) + ZeroCelsius
64       t_photo_max(:,j) = t_photo%t_max_c(j) + t_photo%t_max_b(j)*tl(:) + t_photo%t_max_a(j)*tl(:)*tl(:) + ZeroCelsius
65
66       !
67       ! 2 If the monthly temperature is too low, we set tmax < tmin.
68       !   Therefore, photosynthesis will not be possible (we need tmin < t < tmax)
69       !
70
71       WHERE ( t2m_month(:) .LT. t_photo_min(:,j) )
72          t_photo_max(:,j) = t_photo_min(:,j) - min_stomate
73       ENDWHERE
74
75    ENDDO
76
77  END SUBROUTINE assim_temp
78
79END MODULE stomate_assimtemp
Note: See TracBrowser for help on using the repository browser.