! calculates the photosynthesis temperatures ! ! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_assimtemp.f90,v 1.7 2009/01/06 17:18:32 ssipsl Exp $ ! IPSL (2006) ! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC ! MODULE stomate_assimtemp ! modules used: USE pft_parameters USE constantes IMPLICIT NONE ! private & public routines PRIVATE PUBLIC assim_temp CONTAINS SUBROUTINE assim_temp (npts, tlong_ref, t2m_month, t_photo_min, t_photo_opt, t_photo_max) ! ! 0 declarations ! ! 0.1 input ! Domain size INTEGER(i_std), INTENT(in) :: npts ! "long term" 2 meter reference temperatures (K) REAL(r_std), DIMENSION(npts), INTENT(in) :: tlong_ref ! "monthly" 2-meter temperatures (K) REAL(r_std), DIMENSION(npts), INTENT(in) :: t2m_month ! 0.2 output ! Minimum temperature for photosynthesis (K) REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: t_photo_min ! Optimum temperature for photosynthesis (K) REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: t_photo_opt ! Maximum temperature for photosynthesis (K) REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: t_photo_max ! 0.3 local ! "long term" 2 meter reference temperatures (deg C) REAL(r_std), DIMENSION(npts) :: tl ! Index INTEGER(i_std) :: j ! ========================================================================= tl(:) = tlong_ref(:) - ZeroCelsius DO j = 2,nvm ! ! 1 normal case ! t_photo_min(:,j) = tphoto_min_c(j) + tphoto_min_b(j)*tl(:) + tphoto_min_a(j)*tl(:)*tl(:) + ZeroCelsius t_photo_opt(:,j) = tphoto_opt_c(j) + tphoto_opt_b(j)*tl(:) + tphoto_opt_a(j)*tl(:)*tl(:) + ZeroCelsius t_photo_max(:,j) = tphoto_max_c(j) + tphoto_max_b(j)*tl(:) + tphoto_max_a(j)*tl(:)*tl(:) + ZeroCelsius ! ! 2 If the monthly temperature is too low, we set tmax < tmin. ! Therefore, photosynthesis will not be possible (we need tmin < t < tmax) ! WHERE ( t2m_month(:) .LT. t_photo_min(:,j) ) t_photo_max(:,j) = t_photo_min(:,j) - min_stomate ENDWHERE ENDDO END SUBROUTINE assim_temp END MODULE stomate_assimtemp