source: tags/ORCHIDEE_1_9_6/ORCHIDEE/src_stomate/stomate_resp.f90

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

Add svn headers for all modules. Improve documentation of the parameters. Replace two values by the corresponding parameters.

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