!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_resp.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 ! calculate maintenance respiration on an hourly time step (NV 14/5/2002) MODULE stomate_resp ! modules used: USE stomate_constants USE constantes_veg IMPLICIT NONE ! private & public routines PRIVATE PUBLIC maint_respiration,maint_respiration_clear ! first call LOGICAL, SAVE :: firstcall = .TRUE. CONTAINS SUBROUTINE maint_respiration_clear firstcall=.TRUE. END SUBROUTINE maint_respiration_clear SUBROUTINE maint_respiration ( npts,dt,lai, t2m,tlong_ref,stempdiag,height,veget_max,& rprof,biomass,resp_maint_part_radia) ! ! 0 declarations ! ! 0.1 input ! Domain size INTEGER(i_std), INTENT(in) :: npts ! time step (seconds) REAL(r_std), INTENT(in) :: dt ! 2 m air temperature (K) REAL(r_std), DIMENSION(npts), INTENT(in) :: t2m ! 2 m air temperature (K) REAL(r_std), DIMENSION(npts), INTENT(in) :: tlong_ref ! Soil temperature REAL(r_std),DIMENSION (npts,nbdl), INTENT (in) :: stempdiag ! height of vegetation (m) REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: height ! "maximal" coverage fraction of a PFT (LAI -> infinity) on nat/agri ground REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: veget_max ! root depth (m) REAL(r_std), DIMENSION(npts,nvm), INTENT(in) :: rprof ! biomass (gC/m**2) REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in) :: biomass ! 0.2 modified fields ! 0.3 output ! maintenance respiration of different parts (gC/dt/m**2 of total ground) REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out) :: resp_maint_part_radia ! 0.4 local ! leaf area index REAL(r_std), DIMENSION(npts,nvm) :: lai ! soil levels (m) REAL(r_std), SAVE, DIMENSION(0:nbdl) :: z_soil ! root temperature (convolution of root and soil temperature profiles) REAL(r_std), DIMENSION(npts,nvm) :: t_root ! maintenance respiration coefficients at 0 deg C (g/g d**-1) REAL(r_std), DIMENSION(npts,nvm,nparts) :: coeff_maint ! temperature which is pertinent for maintenance respiration (K) REAL(r_std), DIMENSION(npts,nparts) :: t_maint ! integration constant for root profile REAL(r_std), DIMENSION(npts) :: rpc ! temperature which is pertinent for maintenance respiration (K) REAL(r_std), DIMENSION(npts,nparts) :: t_maint_radia ! long term annual mean temperature, C REAL(r_std), DIMENSION(npts) :: tl ! slope of maintenance respiration coefficient (1/K) REAL(r_std), DIMENSION(npts) :: slope ! Index INTEGER(i_std) :: i,j,k,l,m ! ! ! 2 define maintenance respiration coefficients ! IF (bavard.GE.3) WRITE(numout,*) 'Entering respiration' ! ! 1 Initializations ! IF ( firstcall ) THEN ! 1.1.1 soil levels z_soil(0) = 0. z_soil(1:nbdl) = diaglev(1:nbdl) ! 1.1.2 messages WRITE(numout,*) 'respiration:' firstcall = .FALSE. ENDIF ! ! ! 1 do initialisation ! DO j = 2,nvm ! 1.3.1 rpc is an integration constant such that the integral of the root profile is 1. rpc(:) = 1. / ( 1. - EXP( -z_soil(nbdl) / rprof(:,j) ) ) ! 1.3.2 integrate over the nbdl levels t_root(:,j) = 0.0 DO l = 1, nbdl t_root(:,j) = & t_root(:,j) + stempdiag(:,l) * rpc(:) * & ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) ENDDO ENDDO DO j = 2,nvm ! ! 2.1 temperature which is taken for the plant part we are talking about ! ! 2.1.1 parts above the ground t_maint_radia(:,ileaf) = t2m(:) t_maint_radia(:,isapabove) = t2m(:) t_maint_radia(:,ifruit) = t2m(:) ! 2.1.2 parts below the ground t_maint_radia(:,isapbelow) = t_root(:,j) t_maint_radia(:,iroot) = t_root(:,j) ! 2.1.3 heartwood: does not respire. Any temperature t_maint_radia(:,iheartbelow) = t_root(:,j) t_maint_radia(:,iheartabove) = t2m(:) ! 2.1.4 reserve: above the ground for trees, below for grasses IF ( tree(j) ) THEN t_maint_radia(:,icarbres) = t2m(:) ELSE t_maint_radia(:,icarbres) = t_root(:,j) ENDIF ! ! 2.2 calculate coefficient ! tl(:) = tlong_ref(:) - ZeroCelsius slope(:) = maint_resp_slope(j,1) + tl(:) * maint_resp_slope(j,2) + & tl(:)*tl(:) * maint_resp_slope(j,3) DO k = 1, nparts coeff_maint(:,j,k) = & MAX( (coeff_maint_zero(j,k)*dt/one_day) * & ( 1. + slope(:) * (t_maint_radia(:,k)-ZeroCelsius) ), 0._r_std ) ENDDO ENDDO ! ! 3 calculate maintenance respiration. ! lai(:,ibare_sechiba) = zero resp_maint_part_radia(:,ibare_sechiba,:) = zero ! DO j = 2,nvm ! ! 3.1 maintenance respiration of the different plant parts ! lai(:,j) = biomass(:,j,ileaf) * sla(j) DO k = 1, nparts IF ( k .EQ. ileaf ) THEN ! Leaves: respiration depends on leaf mass AND LAI. !!$ WHERE ( (biomass(:,j,ileaf) > min_stomate) .AND. (lai(:,j) > 0.0) .AND. (lai(:,j) < val_exp) ) !!$ resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * biomass(:,j,k) * & !!$ ( .3*lai(:,j) + 1.4*(1.-exp(-.5*lai(:,j))) ) / lai(:,j) !!$ ELSEWHERE !!$ resp_maint_part_radia(:,j,k) = 0.0 !!$ ENDWHERE DO i = 1, npts IF ( (biomass(i,j,ileaf) > min_stomate) .AND. (lai(i,j) > min_stomate) ) THEN !!$ IF (lai(i,j) < 100._r_std) THEN !!$ resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * & !!$ ( .3*lai(i,j) + 1.4*(1.-exp(-.5*lai(i,j))) ) / lai(i,j) !!$ ELSE !!$ resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * & !!$ ( .3*lai(i,j) + 1.4 ) / lai(i,j) !!$ ENDIF resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * & ( .3*lai(i,j) + 1.4*(1.-exp(-.5*lai(i,j))) ) / lai(i,j) ELSE resp_maint_part_radia(i,j,k) = zero ENDIF ENDDO ELSE resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * biomass(:,j,k) ENDIF ENDDO ! ! 3.2 Total maintenance respiration of the plant ! VPP killer: ! resp_maint(:,j) = SUM( resp_maint_part(:,:), DIM=2 ) ! ENDDO IF (bavard.GE.4) WRITE(numout,*) 'Leaving respiration' END SUBROUTINE maint_respiration END MODULE stomate_resp