source: tags/ORCHIDEE_4_1/ORCHIDEE/src_stomate/stomate_vmax.f90 @ 7852

Last change on this file since 7852 was 7219, checked in by sebastiaan.luyssaert, 3 years ago

Changes to insect outbreaks proposed by Guillaume. Changes to vcmax documentation proposed by Chao. Attempt to stabilize autotrophic respiration proposed by Sebastiaan

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 15.1 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, leaf_age, leaf_frac, assim_param, &
107       circ_class_biomass, circ_class_n, sugar_load, leaf_age_crit, &
108       leaf_classes)
109
110    !! 0. Variable and parameter declaration
111 
112    !! 0.1 Input variables
113    INTEGER(i_std), INTENT(in)                                 :: npts                    !! Domain size (unitless)
114    REAL(r_std), INTENT(in)                                    :: dt                      !! time step of stomate (days)
115    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)              :: circ_class_biomass      !! @tex $(gC m^{-2})$ @endtex
116    REAL(r_std), DIMENSION(:,:,:),INTENT(in)                   :: circ_class_n            !! @tex $(gC m^{-2})$ @endtex
117    REAL(r_std), DIMENSION(:,:), INTENT(in)                    :: sugar_load              !! Function reflecting how
118                                                                                          !! reserve+labile pools are filled
119   
120    !! 0.2 Output variables
121    REAL(r_std), DIMENSION(:,:,:), INTENT(out)                 :: assim_param             !! vmax, nue and leaf N for photosynthesis
122                                                                                          !! @tex $(\mu mol m^{-2}s^{-1})$ @endtex
123   
124    !! 0.3 Modified variables
125    REAL(r_std), DIMENSION(:,:,:), INTENT(inout)               :: leaf_age                !! Leaf age (days)
126    REAL(r_std), DIMENSION(:,:,:), INTENT(inout)               :: leaf_frac               !! fraction of leaves in leaf age
127                                                                                          !! classes
128                                                                                          !! (unitless)
129    REAL(r_std), DIMENSION(:,:), INTENT(inout)                 :: leaf_classes            !! width of each leaf age class (days)
130    REAL(r_std), DIMENSION(:,:), INTENT(inout)                 :: leaf_age_crit           !! critical leaf age (days)
131   
132    !! 0.4 Local variables
133    REAL(r_std), DIMENSION(npts)                               :: leaf_efficiency         !! leaf efficiency (vcmax/vcmax25)
134                                                                                          !! (unitless)
135    REAL(r_std), DIMENSION(npts,nvm,nleafages)                 :: d_leaf_frac             !! turnover between age classes
136                                                                                          !! (unitless)
137    REAL(r_std), DIMENSION(npts,nleafages)                     :: leaf_age_new            !! new leaf age (days)
138    REAL(r_std), DIMENSION(npts)                               :: sumfrac                 !! sum of leaf age fractions,
139                                                                                          !! for normalization
140                                                                                          !! (unitless)
141    REAL(r_std), DIMENSION(npts)                               :: rel_age                 !! relative leaf age (age/critical age)
142                                                                                          !! (unitless)
143    INTEGER(i_std)                                             :: j,m                     !! indices (unitless)
144    REAL(r_std), DIMENSION(npts,nvm)                           :: vcmax                   !! Maximum rate of carboxylation
145                                                                                          !! @tex ($\mu mol m^{-2} s^{-1}$) @endtex
146    REAL(r_std),DIMENSION (npts,nvm)                           :: nue                     !! Nitrogen use Efficiency with impact of leaf age (umol CO2 (gN)-1 s-1)
147!_ ================================================================================================================================
148
149    IF (printlev>=2) WRITE(numout,*) 'Entering vmax'
150
151    !! 1 Initialization
152
153    !! 1.1 first call: info about flags and parameters.
154    IF ( firstcall_vmax ) THEN
155       
156       IF (printlev >= 2) THEN
157          WRITE(numout,*) 'vmax:'
158          WRITE(numout,*) '   > offset (minimum vcmax/vmax_opt):' , vmax_offset
159          WRITE(numout,*) '   > relative leaf age at which vmax reaches vcmax_opt:', leafage_firstmax 
160          WRITE(numout,*) '   > relative leaf age at which vmax falls below vcmax_opt:', leafage_lastmax
161          WRITE(numout,*) '   > relative leaf age at which vmax reaches its minimum:', leafage_old
162       END IF
163
164      firstcall_vmax = .FALSE.
165
166    ENDIF
167
168    ! Calculation how many days each leaf age class contains
169    leaf_classes(:,1) = zero
170    DO j = 2,nvm 
171       leaf_classes(:,j) = leaf_age_crit(:,j) / REAL(nleafages,r_std)
172    END DO
173
174    !! 2 leaf age: general increase and turnover between age classes.
175   
176    !! 2.1 increase leaf age
177    !  The age of the leaves in each leaf-age-class increases by 1 time step.
178    DO m = 1, nleafages ! Loop over # leaf age classes
179       DO j = 2,nvm ! Loop over # PFTs
180          WHERE ( leaf_frac(:,j,m) .GT. min_stomate )
181
182             leaf_age(:,j,m) = leaf_age(:,j,m) + dt
183             
184          ENDWHERE
185       ENDDO ! Loop over # PFTs
186
187    ENDDO ! Loop over # leaf age classes
188
189    !! 2.2 turnover between leaf age classes
190    !     d_leaf_frac(:,:,m) = what leaves m-1 and goes into m
191    DO j = 2,nvm ! Loop over # PFTs
192
193       !! 2.2.1 fluxes
194
195       !! nothing goes into first age class
196       d_leaf_frac(:,j,1) = zero
197
198       !! for others age classes (what goes from m-1 to m)
199       DO m = 2, nleafages 
200
201          ! leaf_classes is calculated in stomate_season.f90 as the quotient of the critical leaf age per the number of age classes.
202          ! The critical leaf age is a PFT-dependent and calculated in stomate_season as a function of leaf_longevity and t2m_longterm,
203          ! representing the leaf life span.
204          ! leaf_classes determines the turnover between the nleafages different leaf age classes
205          ! (see section [118] in Krinner et al. (2005)).
206          d_leaf_frac(:,j,m) = leaf_frac(:,j,m-1) * dt/leaf_classes(:,j)
207
208       ENDDO       
209
210       !! 2.2.2 new leaf age in class
211       !       new age = ( old age * (old fraction - fractional loss) + fractional increase * age of the source class ) / new fraction
212       !       The leaf age of the youngest class (m=1) is updated into stomate_alloc         
213       leaf_age_new(:,:) = zero
214
215       DO m = 2, nleafages-1       ! Loop over age classes
216          ! For all age classes except first and last
217          WHERE ( d_leaf_frac(:,j,m) .GT. min_stomate )
218
219             leaf_age_new(:,m) = ( ( (leaf_frac(:,j,m)- d_leaf_frac(:,j,m+1)) * leaf_age(:,j,m) )  + &
220                  ( d_leaf_frac(:,j,m) * leaf_age(:,j,m-1) ) ) / &
221                  ( leaf_frac(:,j,m) + d_leaf_frac(:,j,m)- d_leaf_frac(:,j,m+1) )
222
223          ENDWHERE
224
225       ENDDO       ! Loop over age classes
226
227       ! For last age class, there is no leaf fraction leaving the class.
228       WHERE ( d_leaf_frac(:,j,nleafages) .GT. min_stomate )
229
230          leaf_age_new(:,nleafages) = ( ( leaf_frac(:,j,nleafages) * leaf_age(:,j,nleafages) )  + &
231               ( d_leaf_frac(:,j,nleafages) * leaf_age(:,j,nleafages-1) ) ) / &
232               ( leaf_frac(:,j,nleafages) + d_leaf_frac(:,j,nleafages) )
233
234       ENDWHERE
235
236       DO m = 2, nleafages       ! Loop over age classes
237
238          WHERE ( d_leaf_frac(:,j,m) .GT. min_stomate )
239
240             leaf_age(:,j,m) = leaf_age_new(:,m)
241
242          ENDWHERE
243
244       ENDDO       ! Loop over age classes
245
246       !! 2.2.3 calculate new fraction
247       DO m = 2, nleafages       ! Loop over age classes
248
249          ! where the change comes from
250          leaf_frac(:,j,m-1) = leaf_frac(:,j,m-1) - d_leaf_frac(:,j,m)
251
252          ! where it goes to
253          leaf_frac(:,j,m) = leaf_frac(:,j,m) + d_leaf_frac(:,j,m)
254
255       ENDDO       ! Loop over age classes
256
257       !! 2.2.4 renormalize fractions in order to prevent accumulation
258       !       of numerical errors
259
260       ! correct small negative values
261       DO m = 1, nleafages
262          leaf_frac(:,j,m) = MAX( zero, leaf_frac(:,j,m) )
263       ENDDO
264
265       ! total of fractions, should be very close to one where there is leaf mass
266       sumfrac(:) = zero
267
268       DO m = 1, nleafages ! Loop over age classes
269
270          sumfrac(:) = sumfrac(:) + leaf_frac(:,j,m)
271
272       ENDDO ! Loop over age classes
273
274       ! normalize
275       DO m = 1, nleafages       ! Loop over age classes
276
277          WHERE ( sumfrac(:) .GT. min_stomate )
278
279             leaf_frac(:,j,m) = leaf_frac(:,j,m) / sumfrac(:) 
280
281          ELSEWHERE
282
283             leaf_frac(:,j,m) = zero
284
285          ENDWHERE
286
287       ENDDO       ! Loop over age classes
288
289    ENDDO         ! Loop over PFTs
290
291    !
292    !! 3 calculate vmax as a function of the age
293    !
294   
295    ! Define parameters for sugar-loading
296    vcmax(:,:) = zero
297    nue(:,:) = zero
298
299    DO j = 2,nvm 
300
301       ! sum up over the different age classes
302       IF (ok_dgvm .AND. pheno_type(j)==1 .AND. leaf_tab(j)==2) THEN
303          ! pheno_typ=evergreen and leaf_tab=needleleaf
304          vcmax(:,j) = Vcmax25(j)
305
306       ELSE
307         
308          DO m = 1, nleafages
309
310             !! 3.1 efficiency in each of the age classes
311             !     it varies from vmax_offset to 1
312             !     linearly increases from vmax_offset to 1 for 0 < rel_age < leafage_firstmax
313             !     is 1 when leafage_firstmax < rel_age < leafage_lastmax
314             !     linearly decreases from 1 to vmax_offset for leafage_lastmax < rel_age < leafage_firstmax
315             !     vmax_offset for rel_age >= leafage_old
316             !     (Ishida et al., 1999)
317             rel_age(:) = leaf_age(:,j,m) / leaf_age_crit(:,j)
318             leaf_efficiency(:) = MAX( vmax_offset, MIN( un, &
319                  vmax_offset + (un - vmax_offset) * rel_age(:) / leafage_firstmax, &
320                  un - (un - vmax_offset) * ( rel_age(:) - leafage_lastmax ) / &
321                  ( leafage_old - leafage_lastmax ) ) )
322
323
324             !
325             !! 3.2 add to mean vmax
326             !
327             ! vcmax calculated here is no longer used
328             vcmax(:,j) = vcmax(:,j) + Vcmax25(j) * leaf_efficiency(:) * leaf_frac(:,j,m)
329
330             ! Calculate nue. Nue is used in diffuco_trans_co2 to calculate vcmax
331             ! from nue and Nleaf. So nue is the varaibable of interest
332             nue(:,j) = nue(:,j) + nue_opt(j) * sugar_load(:,j) * &
333                  leaf_efficiency(:) * leaf_frac(:,j,m)
334               
335          ENDDO     ! loop over age classes
336
337       ENDIF
338
339    ENDDO       ! loop over PFTs
340
341    !! 4. Photosynthesis parameters
342    assim_param(:,:,ivcmax) = zero
343    assim_param(:,:,inue)   = zero
344    assim_param(:,:,ileafN) = zero
345 
346    ! CNP approach
347    DO j = 2,nvm
348       assim_param(:,j,ivcmax) = vcmax(:,j)
349       assim_param(:,j,inue)   = nue(:,j)
350       ! This approach distinguished between the structural N (0.4%) and the active
351       ! nitrogen in the leaves. Note here leaf nitrogen per ground area is used.
352       ! As our photosynthesis is calculated over different layers of LAI, we will
353       ! need vcmax per leaf area per layer, thus requiring leaf nitrogen per leaf
354       ! area per layer as well. This is done in the module where we calculate
355       ! photosynthesis.
356       assim_param(:,j,ileafn) = SUM(circ_class_biomass(:,j,:,ileaf,initrogen) * &
357            circ_class_n(:,j,:),2) - snc * SUM(circ_class_biomass(:,j,:,ileaf,icarbon) * &
358            circ_class_n(:,j,:),2)
359    ENDDO
360
361    CALL xios_orchidee_send_field("SUGAR_LOAD",sugar_load(:,:))
362    CALL xios_orchidee_send_field("NUE",nue(:,:))
363
364    IF (printlev>=4) WRITE(numout,*) 'Leaving vmax'
365
366  END SUBROUTINE vmax
367
368END MODULE stomate_vmax
Note: See TracBrowser for help on using the repository browser.