source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_resp.f90 @ 64

Last change on this file since 64 was 64, checked in by didier.solyga, 13 years ago

Import first version of ORCHIDEE_EXT

File size: 7.6 KB
Line 
1!$Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_resp.f90,v 1.7 2009/01/06 17:18:32 ssipsl Exp $
2!IPSL (2006)
3! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
4 
5  !  calculate maintenance respiration on an hourly time step (NV 14/5/2002)
6MODULE stomate_resp
7  ! modules used:
8  USE stomate_data
9  USE pft_parameters
10  USE constantes 
11
12  IMPLICIT NONE
13
14  ! private & public routines
15
16  PRIVATE
17  PUBLIC maint_respiration,maint_respiration_clear
18
19  ! first call
20  LOGICAL, SAVE                                              :: firstcall = .TRUE.
21
22CONTAINS
23
24  SUBROUTINE maint_respiration_clear
25    firstcall=.TRUE.
26  END SUBROUTINE maint_respiration_clear
27
28  SUBROUTINE maint_respiration ( npts,dt,lai, t2m,tlong_ref,stempdiag,height,veget_max,&
29       rprof,biomass,resp_maint_part_radia)
30
31    !
32    ! 0 declarations
33    !
34
35    ! 0.1 input
36
37    ! Domain size
38    INTEGER(i_std), INTENT(in)                                        :: npts
39    ! time step (seconds)
40    REAL(r_std), INTENT(in)                                     :: dt
41    ! 2 m air temperature (K)
42    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: t2m
43    ! 2 m air temperature (K)
44    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tlong_ref
45    ! Soil temperature
46    REAL(r_std),DIMENSION (npts,nbdl), INTENT (in)              :: stempdiag
47    ! height of vegetation (m)
48    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: height
49    ! "maximal" coverage fraction of a PFT (LAI -> infinity) on nat/agri ground
50    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_max
51    ! root depth (m)
52    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: rprof
53    ! biomass (gC/m**2)
54    REAL(r_std),DIMENSION(npts,nvm,nparts),INTENT(in)          :: biomass 
55    ! 0.2 modified fields
56
57
58    ! 0.3 output
59
60    ! maintenance respiration of different parts (gC/dt/m**2 of total ground)
61    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)             :: resp_maint_part_radia
62    ! 0.4 local
63
64    ! leaf area index
65    REAL(r_std), DIMENSION(npts,nvm)                           :: lai
66    ! soil levels (m)
67    REAL(r_std), SAVE, DIMENSION(0:nbdl)                        :: z_soil
68    ! root temperature (convolution of root and soil temperature profiles)
69    REAL(r_std), DIMENSION(npts,nvm)                           :: t_root
70    ! maintenance respiration coefficients at 0 deg C (g/g d**-1)
71    REAL(r_std), DIMENSION(npts,nvm,nparts)                    :: coeff_maint
72    ! temperature which is pertinent for maintenance respiration (K)
73    REAL(r_std), DIMENSION(npts,nparts)                         :: t_maint
74    ! integration constant for root profile
75    REAL(r_std), DIMENSION(npts)                                :: rpc
76    ! temperature which is pertinent for maintenance respiration (K)
77    REAL(r_std), DIMENSION(npts,nparts)                         :: t_maint_radia
78    ! long term annual mean temperature, C
79    REAL(r_std), DIMENSION(npts)                                :: tl
80    ! slope of maintenance respiration coefficient (1/K)
81    REAL(r_std), DIMENSION(npts)                                :: slope
82    ! Index
83    INTEGER(i_std)                                              :: i,j,k,l,m
84
85    !
86    !
87    ! 2 define maintenance respiration coefficients
88    !
89    IF (bavard.GE.3) WRITE(numout,*) 'Entering respiration'
90    !
91    ! 1 Initializations
92    !
93    IF ( firstcall ) THEN
94
95       ! 1.1.1 soil levels
96
97       z_soil(0) = 0.
98       z_soil(1:nbdl) = diaglev(1:nbdl)
99
100       ! 1.1.2 messages
101
102       WRITE(numout,*) 'respiration:'
103
104       firstcall = .FALSE.
105
106    ENDIF
107
108    !
109
110    !
111    ! 1 do initialisation
112    !
113
114
115    DO j = 2,nvm
116
117       ! 1.3.1 rpc is an integration constant such that the integral of the root profile is 1.
118       rpc(:) = 1. / ( 1. - EXP( -z_soil(nbdl) / rprof(:,j) ) )
119
120       ! 1.3.2 integrate over the nbdl levels
121
122       t_root(:,j) = 0.0
123
124       DO l = 1, nbdl
125
126          t_root(:,j) = &
127               t_root(:,j) + stempdiag(:,l) * rpc(:) * &
128               ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) )
129
130       ENDDO
131
132    ENDDO
133
134    DO j = 2,nvm
135
136       !
137       ! 2.1 temperature which is taken for the plant part we are talking about
138       !
139
140       ! 2.1.1 parts above the ground
141
142       t_maint_radia(:,ileaf) = t2m(:)
143       t_maint_radia(:,isapabove) = t2m(:)
144       t_maint_radia(:,ifruit) = t2m(:)
145
146       ! 2.1.2 parts below the ground
147
148       t_maint_radia(:,isapbelow) = t_root(:,j)
149       t_maint_radia(:,iroot) = t_root(:,j)
150
151       ! 2.1.3 heartwood: does not respire. Any temperature
152
153       t_maint_radia(:,iheartbelow) = t_root(:,j)
154       t_maint_radia(:,iheartabove) = t2m(:)
155
156       ! 2.1.4 reserve: above the ground for trees, below for grasses
157
158       IF ( tree(j) ) THEN
159          t_maint_radia(:,icarbres) = t2m(:)
160       ELSE
161          t_maint_radia(:,icarbres) = t_root(:,j)
162       ENDIF
163
164       !
165       ! 2.2 calculate coefficient
166       !
167
168       tl(:) = tlong_ref(:) - ZeroCelsius
169       slope(:) = maint_resp_slope(j,1) + tl(:) * maint_resp_slope(j,2) + &
170            tl(:)*tl(:) * maint_resp_slope(j,3)
171
172       DO k = 1, nparts
173
174          coeff_maint(:,j,k) = &
175               MAX( (coeff_maint_zero(j,k)*dt/one_day) * &
176               ( 1. + slope(:) * (t_maint_radia(:,k)-ZeroCelsius) ), zero )
177
178       ENDDO
179
180    ENDDO
181
182    !
183    ! 3 calculate maintenance respiration.
184    !
185
186
187    lai(:,ibare_sechiba) = zero
188    resp_maint_part_radia(:,ibare_sechiba,:) = zero
189    !
190    DO j = 2,nvm
191       !
192       ! 3.1 maintenance respiration of the different plant parts
193       !
194       lai(:,j) = biomass(:,j,ileaf) * sla(j)
195
196       DO k = 1, nparts
197
198          IF ( k .EQ. ileaf ) THEN
199
200             ! Leaves: respiration depends on leaf mass AND LAI.
201!!$                WHERE ( (biomass(:,j,ileaf) > min_stomate) .AND. (lai(:,j) > 0.0) .AND. (lai(:,j) < val_exp) )
202!!$                resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * biomass(:,j,k) * &
203!!$                        ( .3*lai(:,j) + 1.4*(1.-exp(-.5*lai(:,j))) ) / lai(:,j)
204!!$             ELSEWHERE
205!!$                resp_maint_part_radia(:,j,k) = 0.0
206!!$             ENDWHERE
207             DO i = 1, npts
208                IF ( (biomass(i,j,ileaf) > min_stomate) .AND. (lai(i,j) > min_stomate) ) THEN
209!!$                         IF (lai(i,j) < 100._r_std) THEN
210!!$                            resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * &
211!!$                                 ( .3*lai(i,j) + 1.4*(1.-exp(-.5*lai(i,j))) ) / lai(i,j)
212!!$                         ELSE
213!!$                            resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * &
214!!$                                 ( .3*lai(i,j) + 1.4 ) / lai(i,j)
215!!$                         ENDIF
216!!$                   resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * &
217!!$                        ( .3*lai(i,j) + 1.4*(1.-exp(-.5*lai(i,j))) ) / lai(i,j)
218
219                   resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k) * &
220                        ( maint_resp_min_vmax*lai(i,j) + maint_resp_coeff*(1.-exp(-ext_coeff(j)*lai(i,j))) ) / lai(i,j)
221                ELSE
222                   resp_maint_part_radia(i,j,k) = zero
223                ENDIF
224             ENDDO
225          ELSE
226
227             resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * biomass(:,j,k)
228
229          ENDIF
230
231       ENDDO
232
233       !
234       ! 3.2 Total maintenance respiration of the plant
235       !     VPP killer:
236       !     resp_maint(:,j) = SUM( resp_maint_part(:,:), DIM=2 )
237       !
238
239    ENDDO
240
241
242    IF (bavard.GE.4) WRITE(numout,*) 'Leaving respiration'
243
244  END SUBROUTINE maint_respiration
245
246END MODULE stomate_resp
Note: See TracBrowser for help on using the repository browser.