source: branches/publications/ORCHIDEE-GMv3.2/ORCHIDEE/src_stomate/stomate_vmax.f90 @ 5816

Last change on this file since 5816 was 5816, checked in by jinfeng.chang, 5 years ago

copy ORCHIDEE-GMv3.2 for publication

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