source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_vmax.f90 @ 107

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

Import first version of ORCHIDEE_EXT

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