source: tags/ORCHIDEE/src_stomate/stomate_vmax.f90 @ 6

Last change on this file since 6 was 6, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

File size: 7.9 KB
Line 
1! calculates the leaf efficiency
2!
3! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_vmax.f90,v 1.11 2010/04/06 15:44:01 ssipsl Exp $
4! IPSL (2006)
5!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
6!
7MODULE stomate_vmax
8
9  ! modules used:
10
11  USE ioipsl
12  USE stomate_constants
13  USE constantes_veg
14
15  IMPLICIT NONE
16
17  ! private & public routines
18
19  PRIVATE
20  PUBLIC vmax, vmax_clear
21
22  ! first call
23  LOGICAL, SAVE                                              :: firstcall = .TRUE.
24
25CONTAINS
26
27  SUBROUTINE vmax_clear
28    firstcall=.TRUE.
29  END SUBROUTINE vmax_clear
30
31  SUBROUTINE vmax (npts, dt, &
32       leaf_age, leaf_frac, &
33       vcmax, vjmax)
34
35    !
36    ! 0 declarations
37    !
38
39    ! 0.1 input
40
41    ! Domain size
42    INTEGER(i_std), INTENT(in)                                        :: npts
43    ! time step of Stomate in days
44    REAL(r_std), INTENT(in)                                     :: dt
45
46    ! 0.2 modified fields
47
48    ! leaf age (days)
49    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age
50    ! fraction of leaves in leaf age class
51    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac
52
53    ! 0.3 output
54
55    ! Maximum rate of carboxylation
56    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: vcmax
57    ! Maximum rate of RUbp regeneration
58    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)              :: vjmax
59
60    ! 0.4 local
61
62    ! offset (minimum relative vcmax)
63    REAL(r_std), PARAMETER                                      :: vmax_offset = 0.3
64    ! leaf age at which vmax attains vcmax_opt (in fraction of critical leaf age)
65    REAL(r_std), PARAMETER                                      :: leafage_firstmax = 0.03
66    ! leaf age at which vmax falls below vcmax_opt (in fraction of critical leaf age)
67    REAL(r_std), PARAMETER                                      :: leafage_lastmax = 0.5
68    ! leaf age at which vmax attains its minimum (in fraction of critical leaf age)
69    REAL(r_std), PARAMETER                                      :: leafage_old = 1.
70    ! leaf efficiency (vcmax/vcmax_opt)
71    REAL(r_std), DIMENSION(npts)                                :: leaf_efficiency
72    ! change of fraction of leaves in age class
73    REAL(r_std), DIMENSION(npts,nvm,nleafages)                 :: d_leaf_frac
74    ! new leaf age (d)
75    REAL(r_std), DIMENSION(npts,nleafages)                      :: leaf_age_new
76    ! sum of leaf age fractions, for normalization
77    REAL(r_std), DIMENSION(npts)                                :: sumfrac
78    ! relative leaf age (age/critical age)
79    REAL(r_std), DIMENSION(npts)                                :: rel_age
80    ! Index
81    INTEGER(i_std)                                              :: j,m
82
83    ! =========================================================================
84
85    IF (bavard.GE.3) WRITE(numout,*) 'Entering vmax'
86
87    !
88    ! 1 Initialization
89    !
90
91    !
92    ! 1.1 first call: info about flags and parameters.
93    !
94
95    IF ( firstcall ) THEN
96
97       WRITE(numout,*) 'vmax:'
98
99       WRITE(numout,*) '   > offset (minimum vcmax/vmax_opt):' , vmax_offset
100       WRITE(numout,*) '   > relative leaf age at which vmax attains vcmax_opt:', leafage_firstmax
101       WRITE(numout,*) '   > relative leaf age at which vmax falls below vcmax_opt:', leafage_lastmax
102       WRITE(numout,*) '   > relative leaf age at which vmax attains its minimum:', leafage_old
103
104       firstcall = .FALSE.
105
106    ENDIF
107
108    !
109    ! 1.2 initialize output
110    !
111
112    vcmax(:,:) = zero
113    vjmax(:,:) = zero
114
115    !
116    ! 2 leaf age: general increase and turnover between age classes.
117    !
118
119    !
120    ! 2.1 increase leaf age
121    !
122
123    DO m = 1, nleafages
124
125       DO j = 2,nvm
126          WHERE ( leaf_frac(:,j,m) .GT. min_stomate )
127
128             leaf_age(:,j,m) = leaf_age(:,j,m) + dt
129             
130          ENDWHERE
131       ENDDO
132
133    ENDDO
134
135    !
136    ! 2.2 turnover between leaf age classes
137    !     d_leaf_frac(:,:,m) = what leaves m-1 and goes into m
138    !
139
140    DO j = 2,nvm
141
142       ! 2.2.1 fluxes
143
144       ! nothing goes into first age class
145       d_leaf_frac(:,j,1) = zero
146
147       ! from m-1 to m
148       DO m = 2, nleafages 
149
150          d_leaf_frac(:,j,m) = leaf_frac(:,j,m-1) * dt/leaf_timecst(j)
151
152       ENDDO
153
154       ! 2.2.2 new leaf age in class
155       !       new age = ( old age * old fraction + fractional increase * age of source ) /
156       !                 new fraction
157
158       leaf_age_new(:,:) = zero
159
160       DO m = 2, nleafages-1
161          !      DO m=2, nleafages
162
163          WHERE ( d_leaf_frac(:,j,m) .GT. min_stomate )
164
165             leaf_age_new(:,m) = ( ( (leaf_frac(:,j,m)- d_leaf_frac(:,j,m+1)) * leaf_age(:,j,m) )  + &
166                  ( d_leaf_frac(:,j,m) * leaf_age(:,j,m-1) ) ) / &
167                  ( leaf_frac(:,j,m) + d_leaf_frac(:,j,m)- d_leaf_frac(:,j,m+1) )
168
169             !           leaf_age_new(:,m) = ( ( leaf_frac(:,j,m) * leaf_age(:,j,m) )  + &
170             !                                ( d_leaf_frac(:,j,m) * leaf_age(:,j,m-1) ) ) / &
171             !                              ( leaf_frac(:,j,m) + d_leaf_frac(:,j,m) )
172
173          ENDWHERE
174
175       ENDDO       ! Loop over age classes
176
177       WHERE ( d_leaf_frac(:,j,nleafages) .GT. min_stomate )
178
179          leaf_age_new(:,nleafages) = ( ( leaf_frac(:,j,nleafages) * leaf_age(:,j,nleafages) )  + &
180               ( d_leaf_frac(:,j,nleafages) * leaf_age(:,j,nleafages-1) ) ) / &
181               ( leaf_frac(:,j,nleafages) + d_leaf_frac(:,j,nleafages) )
182
183       ENDWHERE
184
185       DO m = 2, nleafages
186
187          WHERE ( d_leaf_frac(:,j,m) .GT. min_stomate )
188
189             leaf_age(:,j,m) = leaf_age_new(:,m)
190
191          ENDWHERE
192
193       ENDDO       ! Loop over age classes
194
195       ! 2.2.3 calculate new fraction
196
197       DO m = 2, nleafages
198
199          ! where the change comes from
200          leaf_frac(:,j,m-1) = leaf_frac(:,j,m-1) - d_leaf_frac(:,j,m)
201
202          ! where it goes to
203          leaf_frac(:,j,m) = leaf_frac(:,j,m) + d_leaf_frac(:,j,m)
204
205       ENDDO
206
207       ! 2.2.4 renormalize fractions in order to prevent accumulation
208       !       of numerical errors
209
210       ! correct small negative values
211
212       DO m = 1, nleafages
213          leaf_frac(:,j,m) = MAX( zero, leaf_frac(:,j,m) )
214       ENDDO
215
216       ! total of fractions, should be very close to one where there is leaf mass
217
218       sumfrac(:) = zero
219
220       DO m = 1, nleafages
221
222          sumfrac(:) = sumfrac(:) + leaf_frac(:,j,m)
223
224       ENDDO
225
226       ! normalize
227
228       DO m = 1, nleafages
229
230          WHERE ( sumfrac(:) .GT. min_stomate )
231
232             leaf_frac(:,j,m) = leaf_frac(:,j,m) / sumfrac(:) 
233
234          ELSEWHERE
235
236             leaf_frac(:,j,m) = zero
237
238          ENDWHERE
239
240       ENDDO
241
242    ENDDO         ! Loop over PFTs
243
244    !
245    ! 3 calculate vmax as a function of the age
246    !
247
248    DO j = 2,nvm
249
250       vcmax(:,j) = zero
251       vjmax(:,j) = zero
252
253       ! sum up over the different age classes
254
255       DO m = 1, nleafages
256
257          !
258          ! 3.1 efficiency in each of the age classes
259          !     increases from 0 to 1 at the beginning (rel_age < leafage_firstmax), stays 1
260          !     until rel_age = leafage_lastmax, then decreases to vmax_offset at
261          !     rel_age = leafage_old, then stays at vmax_offset.
262          !
263
264          rel_age(:) = leaf_age(:,j,m) / pheno_crit%leafagecrit(j)
265
266          leaf_efficiency(:) = MAX( vmax_offset, MIN( 1._r_std, &
267               vmax_offset + (1._r_std-vmax_offset) * rel_age(:) / leafage_firstmax, &
268               1._r_std - (1._r_std-vmax_offset) * ( rel_age(:) - leafage_lastmax ) / &
269               ( leafage_old - leafage_lastmax ) ) )
270
271          !
272          ! 3.2 add to mean vmax
273          !
274
275          vcmax(:,j) = vcmax(:,j) + vcmax_opt(j) * leaf_efficiency(:) * leaf_frac(:,j,m)
276          vjmax(:,j) = vjmax(:,j) + vjmax_opt(j) * leaf_efficiency(:) * leaf_frac(:,j,m)
277
278       ENDDO     ! loop over age classes
279
280    ENDDO       ! loop over PFTs
281
282    IF (bavard.GE.4) WRITE(numout,*) 'Leaving vmax'
283
284  END SUBROUTINE vmax
285
286END MODULE stomate_vmax
Note: See TracBrowser for help on using the repository browser.