1 | ! ================================================================================================================================= |
---|
2 | ! MODULE : stomate_vmax |
---|
3 | ! |
---|
4 | ! CONTACT : orchidee-help _at_ ipsl.jussieu.fr |
---|
5 | ! |
---|
6 | ! LICENCE : IPSL (2006). This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC |
---|
7 | ! |
---|
8 | !>\BRIEF calculates the leaf efficiency. |
---|
9 | !! |
---|
10 | !!\n DESCRIPTION: None |
---|
11 | !! |
---|
12 | !! RECENT CHANGE(S): None |
---|
13 | !! |
---|
14 | !! SVN : |
---|
15 | !! $HeadURL$ |
---|
16 | !! $Date$ |
---|
17 | !! $Revision$ |
---|
18 | !! \n |
---|
19 | !_ ================================================================================================================================= |
---|
20 | |
---|
21 | MODULE stomate_vmax |
---|
22 | |
---|
23 | ! modules used: |
---|
24 | |
---|
25 | USE ioipsl_para |
---|
26 | USE stomate_data |
---|
27 | USE constantes |
---|
28 | USE pft_parameters |
---|
29 | |
---|
30 | IMPLICIT NONE |
---|
31 | |
---|
32 | ! private & public routines |
---|
33 | |
---|
34 | PRIVATE |
---|
35 | PUBLIC vmax, vmax_clear |
---|
36 | |
---|
37 | ! first call |
---|
38 | LOGICAL, SAVE :: firstcall_vmax = .TRUE. |
---|
39 | !$OMP THREADPRIVATE(firstcall_vmax) |
---|
40 | |
---|
41 | CONTAINS |
---|
42 | |
---|
43 | !! ================================================================================================================================ |
---|
44 | !! SUBROUTINE : vmax_clear |
---|
45 | !! |
---|
46 | !>\BRIEF Flag setting |
---|
47 | !! |
---|
48 | !!\n DESCRIPTION: This subroutine sets flags ::firstcall_vmax, to .TRUE., and therefore activates |
---|
49 | !! section 1.1 of the ::vmax subroutine which writes messages to the output. \n |
---|
50 | !! This subroutine is called at the end of the subroutine ::stomate_clear, in the |
---|
51 | !! module ::stomate. |
---|
52 | !! |
---|
53 | !! RECENT CHANGE(S):None |
---|
54 | !! |
---|
55 | !! MAIN OUTPUT VARIABLE(S): ::firstcall_vmax |
---|
56 | !! |
---|
57 | !! REFERENCE(S) : None |
---|
58 | !! |
---|
59 | !! FLOWCHART : None |
---|
60 | !! \n |
---|
61 | !_ ================================================================================================================================= |
---|
62 | |
---|
63 | SUBROUTINE vmax_clear |
---|
64 | firstcall_vmax=.TRUE. |
---|
65 | END SUBROUTINE vmax_clear |
---|
66 | |
---|
67 | |
---|
68 | |
---|
69 | !! ================================================================================================================================ |
---|
70 | !! SUBROUTINE : vmax |
---|
71 | !! |
---|
72 | !>\BRIEF This subroutine computes vcmax photosynthesis parameters |
---|
73 | !! given optimal vcmax parameter values and a leaf age-related efficiency. |
---|
74 | !! |
---|
75 | !! DESCRIPTION (functional, design, flags): |
---|
76 | !! Leaf age classes are introduced to take into account the fact that photosynthetic activity depends on leaf age |
---|
77 | !! (Ishida et al., 1999). There are \f$nleafages\f$ classes (constant defined in stomate_constants.f90). |
---|
78 | !! This subroutine first calculates the new age of each leaf age-class based on fraction of leaf |
---|
79 | !! that goes from one to another class. |
---|
80 | !! Then calculation of the new fraction of leaf in each class is performed. |
---|
81 | !! Last, leaf efficiency is calculated for each PFT and for each leaf age class. |
---|
82 | !! vcmax is defined as vcmax25 and vjmax_opt weighted by a mean leaf |
---|
83 | !! efficiency. vcmax25 is PFT-dependent constants defined in constants_mtc.f90. |
---|
84 | !! |
---|
85 | !! This routine is called once at the beginning by stomate_var_init and then at each stomate time step by stomateLpj. |
---|
86 | !! |
---|
87 | !! RECENT CHANGE(S): None |
---|
88 | !! |
---|
89 | !! MAIN OUTPUT VARIABLE(S): vcmax |
---|
90 | !! |
---|
91 | !! REFERENCE(S) : |
---|
92 | !! - Ishida, A., A. Uemura, N. Koike, Y. Matsumoto, and A. Lai Hoe (1999), |
---|
93 | !! Interactive effects of leaf age and self-shading on leaf structure, photosynthetic |
---|
94 | !! capacity and chlorophyll fluorescence in the rain forest tree, |
---|
95 | !! dryobalanops aromatica, Tree Physiol., 19, 741-747 |
---|
96 | !! |
---|
97 | !! FLOWCHART : None |
---|
98 | !! |
---|
99 | !! REVISION(S) : None |
---|
100 | !! \n |
---|
101 | !_ ================================================================================================================================ |
---|
102 | |
---|
103 | SUBROUTINE vmax (npts, dt, & |
---|
104 | leaf_age, leaf_frac, & |
---|
105 | vcmax, nue) |
---|
106 | |
---|
107 | ! |
---|
108 | !! 0. Variable and parameter declaration |
---|
109 | ! |
---|
110 | |
---|
111 | ! |
---|
112 | !! 0.1 Input variables |
---|
113 | ! |
---|
114 | INTEGER(i_std), INTENT(in) :: npts !! Domain size (unitless) |
---|
115 | REAL(r_std), INTENT(in) :: dt !! time step of stomate (days) |
---|
116 | |
---|
117 | ! |
---|
118 | !! 0.2 Output variables |
---|
119 | ! |
---|
120 | REAL(r_std), DIMENSION(npts,nvm), INTENT(out) :: vcmax !! Maximum rate of carboxylation |
---|
121 | !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex |
---|
122 | REAL(r_std),DIMENSION (npts,nvm), INTENT(out) :: nue !! Nitrogen use Efficiency with impact of leaf age (umol CO2 (gN)-1 s-1) |
---|
123 | ! |
---|
124 | !! 0.3 Modified variables |
---|
125 | ! |
---|
126 | REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_age !! Leaf age (days) |
---|
127 | REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout) :: leaf_frac !! fraction of leaves in leaf age |
---|
128 | !! classes |
---|
129 | !! (unitless) |
---|
130 | |
---|
131 | ! |
---|
132 | !! 0.4 Local variables |
---|
133 | ! |
---|
134 | REAL(r_std), DIMENSION(npts) :: leaf_efficiency !! leaf efficiency (vcmax/vcmax25) |
---|
135 | !! (unitless) |
---|
136 | REAL(r_std), DIMENSION(npts,nvm,nleafages) :: d_leaf_frac !! turnover between age classes |
---|
137 | !! (unitless) |
---|
138 | REAL(r_std), DIMENSION(npts,nleafages) :: leaf_age_new !! new leaf age (days) |
---|
139 | REAL(r_std), DIMENSION(npts) :: sumfrac !! sum of leaf age fractions, |
---|
140 | !! for normalization |
---|
141 | !! (unitless) |
---|
142 | REAL(r_std), DIMENSION(npts) :: rel_age !! relative leaf age (age/critical age) |
---|
143 | !! (unitless) |
---|
144 | INTEGER(i_std) :: j,m !! indices (unitless) |
---|
145 | |
---|
146 | !_ ================================================================================================================================ |
---|
147 | |
---|
148 | IF (printlev>=3) WRITE(numout,*) 'Entering vmax' |
---|
149 | |
---|
150 | ! |
---|
151 | !! 1 Initialization |
---|
152 | ! |
---|
153 | |
---|
154 | ! |
---|
155 | !! 1.1 first call: info about flags and parameters. |
---|
156 | ! |
---|
157 | |
---|
158 | IF ( firstcall_vmax ) THEN |
---|
159 | |
---|
160 | WRITE(numout,*) 'vmax:' |
---|
161 | |
---|
162 | WRITE(numout,*) ' > offset (minimum vcmax/vmax_opt):' , vmax_offset |
---|
163 | WRITE(numout,*) ' > relative leaf age at which vmax reaches vcmax_opt:', leafage_firstmax |
---|
164 | WRITE(numout,*) ' > relative leaf age at which vmax falls below vcmax_opt:', leafage_lastmax |
---|
165 | WRITE(numout,*) ' > relative leaf age at which vmax reaches its minimum:', leafage_old |
---|
166 | |
---|
167 | firstcall_vmax = .FALSE. |
---|
168 | |
---|
169 | ENDIF |
---|
170 | |
---|
171 | ! |
---|
172 | !! 1.2 initialize output |
---|
173 | ! |
---|
174 | |
---|
175 | vcmax(:,:) = zero |
---|
176 | nue(:,:) = zero |
---|
177 | ! |
---|
178 | !! 2 leaf age: general increase and turnover between age classes. |
---|
179 | ! |
---|
180 | |
---|
181 | ! |
---|
182 | !! 2.1 increase leaf age |
---|
183 | ! |
---|
184 | ! |
---|
185 | !! The age of the leaves in each leaf-age-class increases by 1 time step. |
---|
186 | DO m = 1, nleafages ! Loop over # leaf age classes |
---|
187 | DO j = 2,nvm ! Loop over # PFTs |
---|
188 | WHERE ( leaf_frac(:,j,m) .GT. min_stomate ) |
---|
189 | |
---|
190 | leaf_age(:,j,m) = leaf_age(:,j,m) + dt |
---|
191 | |
---|
192 | ENDWHERE |
---|
193 | ENDDO ! Loop over # PFTs |
---|
194 | |
---|
195 | ENDDO ! Loop over # leaf age classes |
---|
196 | |
---|
197 | ! |
---|
198 | !! 2.2 turnover between leaf age classes |
---|
199 | ! d_leaf_frac(:,:,m) = what leaves m-1 and goes into m |
---|
200 | ! |
---|
201 | |
---|
202 | DO j = 2,nvm ! Loop over # PFTs |
---|
203 | |
---|
204 | !! 2.2.1 fluxes |
---|
205 | |
---|
206 | !! nothing goes into first age class |
---|
207 | d_leaf_frac(:,j,1) = zero |
---|
208 | |
---|
209 | !! for others age classes (what goes from m-1 to m) |
---|
210 | DO m = 2, nleafages |
---|
211 | !! leaf_timecst is defined in stomate_constants.f90 as the quotient of the critical leaf age per the number of age classes. |
---|
212 | !! The critical leaf age is a PFT-dependent constant defined in stomate_constants.f90, that represents the leaf life span. |
---|
213 | !! This time constant (leaf_timecst) determines the turnover between the nleafages different leaf age classes |
---|
214 | !! (see section [118] in Krinner et al. (2005)). |
---|
215 | d_leaf_frac(:,j,m) = leaf_frac(:,j,m-1) * dt/leaf_timecst(j) |
---|
216 | |
---|
217 | ENDDO |
---|
218 | |
---|
219 | !! 2.2.2 new leaf age in class |
---|
220 | !! new age = ( old age * (old fraction - fractional loss) + fractional increase * age of the source class ) / new fraction |
---|
221 | !! The leaf age of the youngest class (m=1) is updated into stomate_alloc |
---|
222 | leaf_age_new(:,:) = zero |
---|
223 | |
---|
224 | DO m = 2, nleafages-1 ! Loop over age classes |
---|
225 | !! For all age classes except first and last |
---|
226 | WHERE ( d_leaf_frac(:,j,m) .GT. min_stomate ) |
---|
227 | |
---|
228 | leaf_age_new(:,m) = ( ( (leaf_frac(:,j,m)- d_leaf_frac(:,j,m+1)) * leaf_age(:,j,m) ) + & |
---|
229 | ( d_leaf_frac(:,j,m) * leaf_age(:,j,m-1) ) ) / & |
---|
230 | ( leaf_frac(:,j,m) + d_leaf_frac(:,j,m)- d_leaf_frac(:,j,m+1) ) |
---|
231 | |
---|
232 | ENDWHERE |
---|
233 | |
---|
234 | ENDDO ! Loop over age classes |
---|
235 | |
---|
236 | !! For last age class, there is no leaf fraction leaving the class. |
---|
237 | |
---|
238 | WHERE ( d_leaf_frac(:,j,nleafages) .GT. min_stomate ) |
---|
239 | |
---|
240 | leaf_age_new(:,nleafages) = ( ( leaf_frac(:,j,nleafages) * leaf_age(:,j,nleafages) ) + & |
---|
241 | ( d_leaf_frac(:,j,nleafages) * leaf_age(:,j,nleafages-1) ) ) / & |
---|
242 | ( leaf_frac(:,j,nleafages) + d_leaf_frac(:,j,nleafages) ) |
---|
243 | |
---|
244 | ENDWHERE |
---|
245 | |
---|
246 | DO m = 2, nleafages ! Loop over age classes |
---|
247 | |
---|
248 | WHERE ( d_leaf_frac(:,j,m) .GT. min_stomate ) |
---|
249 | |
---|
250 | leaf_age(:,j,m) = leaf_age_new(:,m) |
---|
251 | |
---|
252 | ENDWHERE |
---|
253 | |
---|
254 | ENDDO ! Loop over age classes |
---|
255 | |
---|
256 | !! 2.2.3 calculate new fraction |
---|
257 | |
---|
258 | DO m = 2, nleafages ! Loop over age classes |
---|
259 | |
---|
260 | ! where the change comes from |
---|
261 | leaf_frac(:,j,m-1) = leaf_frac(:,j,m-1) - d_leaf_frac(:,j,m) |
---|
262 | |
---|
263 | ! where it goes to |
---|
264 | leaf_frac(:,j,m) = leaf_frac(:,j,m) + d_leaf_frac(:,j,m) |
---|
265 | |
---|
266 | ENDDO ! Loop over age classes |
---|
267 | |
---|
268 | !! 2.2.4 renormalize fractions in order to prevent accumulation |
---|
269 | ! of numerical errors |
---|
270 | |
---|
271 | ! correct small negative values |
---|
272 | |
---|
273 | DO m = 1, nleafages |
---|
274 | leaf_frac(:,j,m) = MAX( zero, leaf_frac(:,j,m) ) |
---|
275 | ENDDO |
---|
276 | |
---|
277 | ! total of fractions, should be very close to one where there is leaf mass |
---|
278 | |
---|
279 | sumfrac(:) = zero |
---|
280 | |
---|
281 | DO m = 1, nleafages ! Loop over age classes |
---|
282 | |
---|
283 | sumfrac(:) = sumfrac(:) + leaf_frac(:,j,m) |
---|
284 | |
---|
285 | ENDDO ! Loop over age classes |
---|
286 | |
---|
287 | ! normalize |
---|
288 | |
---|
289 | DO m = 1, nleafages ! Loop over age classes |
---|
290 | |
---|
291 | WHERE ( sumfrac(:) .GT. min_stomate ) |
---|
292 | |
---|
293 | leaf_frac(:,j,m) = leaf_frac(:,j,m) / sumfrac(:) |
---|
294 | |
---|
295 | ELSEWHERE |
---|
296 | |
---|
297 | leaf_frac(:,j,m) = zero |
---|
298 | |
---|
299 | ENDWHERE |
---|
300 | |
---|
301 | ENDDO ! Loop over age classes |
---|
302 | |
---|
303 | ENDDO ! Loop over PFTs |
---|
304 | |
---|
305 | ! |
---|
306 | !! 3 calculate vmax as a function of the age |
---|
307 | ! |
---|
308 | |
---|
309 | DO j = 2,nvm |
---|
310 | |
---|
311 | vcmax(:,j) = zero |
---|
312 | nue(:,j) = zero |
---|
313 | |
---|
314 | ! sum up over the different age classes |
---|
315 | IF (ok_dgvm .AND. pheno_type(j)==1 .AND. leaf_tab(j)==2) THEN |
---|
316 | ! pheno_typ=evergreen and leaf_tab=needleleaf |
---|
317 | vcmax(:,j) = Vcmax25(j) |
---|
318 | |
---|
319 | ELSE |
---|
320 | ! for deciduous tree |
---|
321 | DO m = 1, nleafages ! Loop over age classes |
---|
322 | |
---|
323 | ! |
---|
324 | !! 3.1 efficiency in each of the age classes |
---|
325 | !! it varies from vmax_offset to 1 |
---|
326 | !! linearly increases from vmax_offset to 1 for 0 < rel_age < leafage_firstmax |
---|
327 | !! is 1 when leafage_firstmax < rel_age < leafage_lastmax |
---|
328 | !! linearly decreases from 1 to vmax_offset for leafage_lastmax < rel_age < leafage_firstmax |
---|
329 | !! vmax_offset for rel_age >= leafage_old |
---|
330 | !! (Ishida et al., 1999) |
---|
331 | rel_age(:) = leaf_age(:,j,m) / leafagecrit(j) |
---|
332 | |
---|
333 | leaf_efficiency(:) = MAX( vmax_offset, MIN( un, & |
---|
334 | vmax_offset + (un - vmax_offset) * rel_age(:) / leafage_firstmax, & |
---|
335 | un - (un - vmax_offset) * ( rel_age(:) - leafage_lastmax ) / & |
---|
336 | ( leafage_old - leafage_lastmax ) ) ) |
---|
337 | |
---|
338 | ! |
---|
339 | !! 3.2 add to mean vmax |
---|
340 | ! |
---|
341 | vcmax(:,j) = vcmax(:,j) + Vcmax25(j) * leaf_efficiency(:) * leaf_frac(:,j,m) |
---|
342 | |
---|
343 | |
---|
344 | nue(:,j) = nue(:,j) + nue_opt(j) * leaf_efficiency(:) * leaf_frac(:,j,m) |
---|
345 | ENDDO ! loop over age classes |
---|
346 | ENDIF |
---|
347 | |
---|
348 | ENDDO ! loop over PFTs |
---|
349 | |
---|
350 | IF (printlev>=4) WRITE(numout,*) 'Leaving vmax' |
---|
351 | |
---|
352 | END SUBROUTINE vmax |
---|
353 | |
---|
354 | END MODULE stomate_vmax |
---|