source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_stomate/stomate_vmax.f90 @ 7660

Last change on this file since 7660 was 6482, checked in by josefine.ghattas, 5 years ago

Make sugar loading the only option to deal with excess labile and reserve pools. Flag OK_SUGAR_LOADING has been removed. No change in results. Decision taken by N. Vuichard and S. Luyssaert

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