source: branches/publications/ORCHIDEE_CAN_r2290/src_stomate/stomate_growth_res_lim.f90 @ 5242

Last change on this file since 5242 was 1902, checked in by matthew.mcgrath, 10 years ago

DEV: Trunk merges up to and including r1892

  • Property svn:executable set to *
File size: 60.3 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_growth_res_lim
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7!                This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Plant growth and C-allocation among the biomass components (leaves, wood, roots, fruit, reserves)
10!!               is calculated making use of the resource limitation scheme proposed by Friedlingstein et al 1999.     
11!!
12!!\n DESCRIPTION: This module calculates three processes: (1) daily maintenance respiration based on the half-hourly
13!!               respiration calculated in stomate_resp.f90, (2) the allocation fractions to the different biomass
14!!               components based on the resource-limitation approach and (3) the allocatable biomass as the residual
15!!               of GPP-Ra. Multiplication of the allocation fractions and allocatable biomass given the changes in
16!!               biomass pools.
17!!
18!! RECENT CHANGE(S): Until 1.9.6 the calculations in this routine were distributed over stomate_alloc.f90 and
19!!               stomate_npp.f90. Given the strong dependencies of both routines they were merged in this module.
20!!               At the same time an alternative growth module (stomate_growth_fun_all.f90) was introduced.               
21!!
22!! REFERENCE(S) : - Friedlingstein, P., G. Joel, C.B. Field, and Y. Fung (1999), Towards an allocation
23!!               scheme for global terrestrial carbon models, Global Change Biology, 5, 755-770.\n
24!!
25!! SVN          :
26!! $HeadURL$
27!! $Date$
28!! $Revision$
29!! \n
30!_ ================================================================================================================================
31
32MODULE stomate_growth_res_lim
33
34  ! Modules used:
35
36  USE ioipsl_para
37  USE pft_parameters
38  USE stomate_data
39  USE constantes
40  USE constantes_soil
41
42  IMPLICIT NONE
43
44  ! Private & public routines
45
46  PRIVATE
47  PUBLIC growth_res_lim_clear, growth_res_lim
48
49  ! Variables shared by all subroutines in this module
50
51  LOGICAL, SAVE                                             :: firstcall = .TRUE.  !! Is this the first call? (true/false)
52 
53  CONTAINS
54
55
56!! ================================================================================================================================
57!! SUBROUTINE   : growth_res_lim_clear
58!!
59!>\BRIEF          Set the flag ::firstcall to .TRUE. and as such activate section
60!! 1.1 of the subroutine alloc (see below).\n
61!!
62!_ ================================================================================================================================
63
64  SUBROUTINE growth_res_lim_clear
65    firstcall = .TRUE.
66  END SUBROUTINE growth_res_lim_clear
67
68
69!! ================================================================================================================================
70!! SUBROUTINE   : growth_res_lim
71!!
72!>\BRIEF        Calculate NPP as the difference between GPP and respiration (= growth +
73!! maintenance respiration). Distribute NPP over all compartments (carbon reserves,
74!! aboveground sapwood, belowground sapwood, root, fruits and leaves following
75!! Friedlingstein et al. (1999).
76!!
77!! DESCRIPTION  : NPP is calculated from three components: Gross Primary Productivity
78!! (GPP), maintenance respiration and growth respiration
79!! (all in @tex $ gC.m^{-2}dt^{-1} $ @endtex), following the convention that positive
80!! fluxes denote fluxes from the plants to the atmosphere. GPP is the input variable from
81!! which, in the end, NPP or total allocatable biomass @tex $(gC.m^{-2})$ @endtex is
82!! calculated. Net primary production is then calculated as:\n 
83!! NPP = GPP - growth_resp - maint-resp   [eq. 1]\n   
84!!     
85!! The calculation of maintenance respiration is done in routine stomate_resp.f90.
86!! Maintenance respiration is calculated for the whole plant and is therefore removed from
87!! the total allocatable biomass. In order to prevent all allocatable biomass from being
88!! used for maintenance respiration, a limit fraction of total allocatable biomass, tax_max,
89!! is defined (in the variables declaration). If maintenance respiration exceeds tax_max
90!! (::bm_tax_max), the maximum allowed allocatable biomass will be respired and the remaining
91!! respiration, required in excess of tax_max, is taken out from tissues already present in
92!! the plant biomass.\n 
93!!
94!! After total allocatable biomass has been updated by removing maintenance respiration,
95!! total allocatable biomass is distributed to all plant compartments according to the
96!! f_alloc fractions also calculated in this routine.\n
97!!
98!! The philosophy underlying the allocation scheme is that allocation patterns
99!! result from evolved responses that adjust carbon investments to facilitate capture of
100!! most limiting resources i.e. light, water and mineral nitrogen. The implemented scheme
101!! calculates the limitation of light, water and nitrogen. However, nitrogen is not a
102!! prognostic variable of the model and therefore soil temperature and soil moisture
103!! are used as a proxy for soil nitrogen availability.\n
104!! Sharpe & Rykiel (1991) proposed a generic relationship between the allocation of
105!! carbon to a given plant compartment and the availability of a particular resource:\n
106!! \latexonly
107!!   \input{alloc1.tex}
108!! \endlatexonly
109!! \n
110!! where A is the allocation of biomass production (NPP) to a given compartment (either
111!! leaves, stem, or roots). Xi and Yj are resource availabilities (e.g. light, water,
112!! nutrient). For a given plant compartment, a resource can be of type X or Y. An increase
113!! in a X-type resource will increase the allocation to compartment A. An increase in a
114!! Y-type resource will, however, lead to a decrease in carbon allocation to that compartment.
115!! In other words, Y-type resources are those for which uptake increases with increased
116!! investment in the compartment in question. X-type resources, as a consequence of
117!! trade-offs, are the opposite. For example, water is a Y-type resource for root allocation.
118!! Water-limited conditions should promote carbon allocation to roots, which enhance water
119!! uptake and hence minimize plant water stress. Negative relationships between investment
120!! and uptake arise when increased investment in one compartment leads, as required for
121!! conservation of mass, to decreased investment in a component involved in uptake of
122!! that resource.\n
123!!
124!! The implemented scheme allocates carbon to the following components:\n
125!! - Carbon reserves;\n
126!! - Aboveground sapwood;\n
127!! - Belowground sapwood;\n
128!! - Roots;\n
129!! - Fruits/seeds and\n
130!! - Leaves.
131!! \n
132!!
133!! The allocation to fruits and seeds is simply a 10% "tax" of the total biomass
134!! production.\n
135!! Following carbohydrate use to support budburst and initial growth, the
136!! carbohydrate reserve is refilled. The daily amount of carbon allocated to the
137!! reserve pool is proportional to leaf+root allocation (::LtoLSR and ::RtoLSR).
138!! Sapwood and root allocation (respectively ::StoLSR and ::RtoLSR) are proportional
139!! to the estimated light and soil (water and nitrogen) stress (::Limit_L and
140!! ::Limit_NtoW). Further, Sapwood allocation is separated in belowground sapwood
141!! and aboveground sapwood making use of the parameter (:: alloc_sap_above_tree
142!! or ::alloc_sap_above_grass). For trees partitioning between above and
143!! belowground compartments is a function of PFT age. Leaf allocation (::LtoLSR)
144!! is calculated as the residual of root and sapwood
145!! allocation (LtoLSR(:) = 1. - RtoLSR(:) - StoLSR(:).\n
146!!
147!! Growth respiration is calculated as a fraction of allocatable biomass for each part
148!! of the plant. The fraction coefficient ::frac_growth_resp is defined in
149!! stomate_constants.f90 and is currently set to be the same for all plant compartments.
150!! Is it thus assumed that it takes as much energy to grow a leaf as it is to grow
151!! wood. Allocatable biomass of all plant compartments are updated by removing what is
152!! lost through growth respiration. Net allocatable biomass (total allocatable biomass
153!! after maintenance and growth respiration) is added to the current biomass for each
154!! plant compartment.\n
155!!
156!! Finally, leaf age and plant age are updated. Leaf age is described with the concept
157!! of "leaf age classes". A number of leaf age classes (::nleafages) is defined in
158!! stomate_constants.f90. Each leaf age class contains a fraction (::leaf_frac) of the
159!! total leaf biomass. When new biomass is added to leaves, the age of the biomass in
160!! the youngest leaf age class is decreased. The fractions of leaves in the other leaf
161!! ages classes are also updated as the total biomass has increased. Plant age is
162!! updated first by increasing the age of the previous biomass by one time step, and
163!! then by adjusting this age as the average of the ages of the previous and the new
164!! biomass.
165!!
166!! RECENT CHANGE(S): Until 1.9.6 the calculations in this routine were distributed over
167!! stomate_alloc.f90 and stomate_npp.f90. Given the strong dependencies of both routines
168!! they were merged in a single module. The underlying science and principles were not
169!! changed. This new module (stomate_growth_res_lim) exactely reproduces the results
170!! from the previous implementation (stomate_alloc and stomate_npp). At the same time an
171!! alternative growth module (stomate_growth_fun_all.f90), based on the pipe-model, was
172!! added to the code.
173!!
174!! MAIN OUTPUT VARIABLE(S): ::npp and ::biomass; fraction of NPP that is allocated to the
175!! six different biomass compartments (leaves, roots, above and belowground wood,
176!! carbohydrate reserves and fruits). DIMENSION(npts,nvm,nparts).
177!!
178!! REFERENCE(S) :
179!! - Friedlingstein, P., G. Joel, C.B. Field, and Y. Fung (1999), Towards an allocation
180!! scheme for global terrestrial carbon models, Global Change Biology, 5, 755-770.\n
181!! - Krinner G, Viovy N, de Noblet-Ducoudr N, Ogee J, Polcher J, Friedlingstein P,
182!! Ciais P, Sitch S, Prentice I C (2005) A dynamic global vegetation model for studies
183!! of the coupled atmosphere-biosphere system. Global Biogeochemical Cycles, 19, GB1015,
184!! doi: 10.1029/2003GB002199.\n
185!! - F.W.T.Penning De Vries, A.H.M. Brunsting, H.H. Van Laar. 1974. Products, requirements
186!! and efficiency of biosynthesis a quantitative approach. Journal of Theoretical Biology,
187!! Volume 45, Issue 2, June 1974, Pages 339-377.
188!! - Sharpe, P.J.H., and Rykiel, E.J. (1991), Modelling integrated response of plants
189!! to multiple stresses. In: Response of Plants to Multiple Stresses (eds Mooney, H.A.,
190!! Winner, W.E., Pell, E.J.), pp. 205-224, Academic Press, San Diego, CA.\n
191!!
192!! +++++++++++++++++++++
193!! MAKE A NEW FLOW CHART
194!! +++++++++++++++++++++
195!! FLOWCHART    :
196!! \latexonly
197!! \includegraphics[scale=0.14]{stomate_npp_flow.jpg}
198!! \endlatexonly
199!! \n
200!! \latexonly
201!!   \includegraphics[scale=0.5]{allocflow.jpg}
202!! \endlatexonly
203!! \n
204!_ ================================================================================================================================
205 
206  SUBROUTINE growth_res_lim (npts, dt, lai, veget_max, &
207       PFTpresent, senescence, when_growthinit, moiavail_week, &
208       soilhum_month, tsoil_month, gpp, resp_maint_part, &
209       resp_maint, resp_growth, npp, biomass, &
210       age, leaf_age, leaf_frac)
211!, use_reserve)                                             
212 
213
214 !! 0. Variable and parameter declaration
215
216    !! 0.1 Input variables
217
218    INTEGER(i_std), INTENT(in)                               :: npts                    !! Domain size - number of grid cells
219                                                                                        !! (unitless)
220    REAL(r_std), INTENT(in)                                  :: dt                      !! Time step of the simulations for stomate
221                                                                                        !! (days)   
222    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: lai                     !! PFT leaf area index
223                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
224    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: veget_max               !! PFT "Maximal" coverage fraction of a PFT 
225                                                                                        !! @tex $(m^2 m^{-2})$ @endtex   
226    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: when_growthinit         !! Days since beginning of growing season
227                                                                                        !! (days)
228    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: moiavail_week           !! PFT moisture availability - integrated
229                                                                                        !! over a week (0-1, unitless)
230    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)             :: gpp                     !! PFT gross primary productivity
231                                                                                        !! @tex $(gC.m^{-2}dt^{-1})$ @endtex                                       
232    REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)            :: tsoil_month             !! PFT soil temperature - integrated over
233                                                                                        !! a month (K)
234    REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)            :: soilhum_month           !! PFT soil humidity - integrated over a
235                                                                                        !! month (0-1, unitless)
236    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(in)      :: resp_maint_part         !! Maintenance respiration of different plant
237                                                                                        !! parts @tex $(gC.m^{-2}dt^{-1})$ @endtex 
238    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: senescence              !! Is the PFT senescent?  - only for
239                                                                                        !! deciduous trees (true/false)
240    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                 :: PFTpresent              !! PFT exists (true/false)
241   
242    !! 0.2 Output variables
243
244    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)            :: resp_maint              !! PFT maintenance respiration
245                                                                                        !! @tex $(gC.m^{-2}dt^{-1})$ @endtex               
246    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)            :: resp_growth             !! PFT growth respiration
247                                                                                        !! @tex $(gC.m^{-2}dt^{-1})$ @endtex                           
248    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)            :: npp                     !! PFT net primary productivity
249                                                                                        !! @tex $(gC.m^{-2}dt^{-1})$ @endtex
250
251    !! 0.3 Modified variables
252
253    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)          :: age                     !! PFT age (years)
254    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout)   :: biomass       !! PFT total biomass
255                                                                                        !! @tex $(gC m^{-2})$ @endtex
256    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout):: leaf_age                !! PFT age of different leaf classes
257                                                                                        !! (days)
258    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout):: leaf_frac               !! PFT fraction of leaves in leaf age class
259                                                                                        !! (0-1, unitless)
260
261    !! 0.4 Local variables
262                         
263    INTEGER(i_std)                                           :: i,j,k,l,m               !! Indices (unitless)
264    REAL(r_std)                                              :: reserve_time            !! Maximum number of days during which
265                                                                                        !! carbohydrate reserve may be used (days)
266    REAL(r_std), DIMENSION(nvm)                              :: lai_happy_old           !! Lai threshold below which carbohydrate
267                                                                                        !! reserve may be used
268                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
269    REAL(r_std), DIMENSION(npts)                             :: limit_L                 !! Lights stress (0-1, unitless)
270    REAL(r_std), DIMENSION(npts)                             :: limit_N                 !! Total nitrogen stress (0-1, unitless)
271    REAL(r_std), DIMENSION(npts)                             :: limit_N_temp            !! Stress from soil temperature on nitrogen
272                                                                                        !! mineralisation (0-1, unitless)
273    REAL(r_std), DIMENSION(npts)                             :: limit_N_hum             !! Stress from soil humidity on nitrogen
274                                                                                        !! mineralisation (0-1, unitless)
275    REAL(r_std), DIMENSION(npts)                             :: limit_W                 !! Soil water stress (0-1, unitless)
276    REAL(r_std), DIMENSION(npts)                             :: limit_WorN              !! Most limiting factor in the soil:
277                                                                                        !! nitrogen or water (0-1, unitless)
278    REAL(r_std), DIMENSION(npts)                             :: limit                   !! Most limiting factor: amongst limit_N,
279                                                                                        !! limit_W and limit_L (0-1, unitless)
280    REAL(r_std), DIMENSION(npts)                             :: t_nitrogen              !! Preliminairy soil temperature stress
281                                                                                        !! used as a proxy for nitrogen stress (K)
282    REAL(r_std), DIMENSION(npts)                             :: h_nitrogen              !! Preliminairy soil humidity stress used
283                                                                                        !! as a proxy for nitrogen stress
284                                                                                        !! (unitless) 
285    REAL(r_std), DIMENSION(npts)                             :: rpc                     !! Scaling factor for integrating vertical
286                                                                                        !! soil profiles (unitless)     
287    REAL(r_std), DIMENSION(npts)                             :: LtoLSR                  !! Ratio between leaf-allocation and
288                                                                                        !! (leaf+sapwood+root)-allocation
289                                                                                        !! (0-1, unitless)
290    REAL(r_std), DIMENSION(npts)                             :: StoLSR                  !! Ratio between sapwood-allocation and
291                                                                                        !! (leaf+sapwood+root)-allocation
292                                                                                        !! (0-1, unitless)
293    REAL(r_std), DIMENSION(npts)                             :: RtoLSR                  !! Ratio between root-allocation and
294                                                                                        !! (leaf+sapwood+root)-allocation
295                                                                                        !! (0-1, unitless)
296    REAL(r_std), DIMENSION(npts)                             :: carb_rescale            !! Rescaling factor for allocation factors
297                                                                                        !! if carbon is allocated to carbohydrate
298                                                                                        !! reserve (0-1, unitless)
299    REAL(r_std), DIMENSION(npts)                             :: natveg_tot              !! Total natural vegetation cover on
300                                                                                        !! natural part of the grid cell
301                                                                                        !! (0-1, unitless)
302    REAL(r_std), DIMENSION(npts)                             :: lai_nat                 !! Average LAI on natural part of the grid
303                                                                                        !! cell @tex $(m^2 m^{-2})$ @endtex
304    REAL(r_std), DIMENSION(npts)                             :: alloc_sap_above         !! Fraction of sapwood
305                                                                                        !! allocation to above ground sapwood
306                                                                                        !! (0-1, unitless)
307    REAL(r_std), DIMENSION(npts)                             :: bm_add                  !! Biomass increase @tex $(gC.m^{-2})$ @endtex         
308    REAL(r_std), DIMENSION(npts)                             :: bm_new                  !! New biomass @tex $(gC.m^{-2})$ @endtex
309    REAL(r_std), DIMENSION(npts)                             :: bm_tax_max              !! Maximum part of allocatable biomass used for
310                                                                                        !! respiration @tex $(gC.m^{-2})$ @endtex       
311    REAL(r_std), DIMENSION(npts)                             :: bm_pump                 !! Biomass that remains to be taken away
312                                                                                        !! @tex $(gC.m^{-2})$ @endtex
313    REAL(r_std), DIMENSION(npts,nvm)                         :: transloc_leaf           !! Fraction of carbohydrate reserve used
314                                                                                        !! (::use_reserve) to support leaf growth
315                                                                                        !! @tex $(gC m^{-2})$ @endtex
316    REAL(r_std), DIMENSION(npts,nvm)                         :: use_reserve             !! Mass taken from carbohydrate reserve
317                                                                                        !! @tex $(gC m^{-2})$ @endtex                           
318    REAL(r_std), DIMENSION(npts,nvm)                         :: bm_create               !! Biomass created when biomass<0 because of dark
319                                                                                        !! respiration @tex $(gC.m^{-2})$ @endtex
320    REAL(r_std), DIMENSION(npts,nvm)                         :: bm_alloc_tot            !! Allocatable biomass for the whole plant
321                                                                                        !! @tex $(gC.m^{-2})$ @endtex
322    REAL(r_std), DIMENSION(npts,nvm)                         :: dia                     !! Tree diameter (cm)
323    REAL(r_std), DIMENSION(npts,nvm)                         :: ltor                    !! Leaf to root ratio (unitless)
324    REAL(r_std), DIMENSION(npts,nvm)                         :: leaf_mass_young         !! Leaf biomass in youngest leaf age class
325                                                                                        !! @tex $(gC m^{-2})$ @endtex
326    REAL(r_std), DIMENSION(npts,nvm)                         :: lm_old                  !! Variable to store leaf biomass from
327                                                                                        !! previous time step
328                                                                                        !! @tex $(gC m^{-2})$ @endtex
329    REAL(r_std), DIMENSION(npts,nvm)                         :: lai_around              !! lai on natural part of the grid cell, or
330                                                                                        !! of agricultural PFTs
331                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
332    REAL(r_std), DIMENSION(npts,nvm)                         :: veget_max_nat           !! Vegetation cover of natural PFTs on the
333                                                                                        !! grid cell (agriculture masked)
334                                                                                        !! (0-1, unitless)
335    REAL(r_std), DIMENSION(npts,nparts)                      :: resp_growth_part        !! Growth respiration of different plant parts
336                                                                                        !! @tex $(gC.m^{-2}dt^{-1})$ @endtex
337    REAL(r_std), DIMENSION(npts,nvm,nparts)                  :: f_alloc                 !! PFT fraction of NPP that is allocated to
338                                                                                        !! the different components (0-1, unitless)
339    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements)        :: bm_alloc                !! PFT biomass increase, i.e. NPP per plant part
340                                                                                        !! @tex $(gC.m^{-2}dt^{-1})$ @endtex**2
341    REAL(r_std), SAVE, DIMENSION(0:nbdl)                     :: z_soil                  !! Variable to store depth of the different
342                                                                                        !! soil layers (m)
343!_ =================================================================================================================================
344
345
346!! 1. Initialize
347
348    IF (bavard.GE.3) WRITE(numout,*) 'Entering resource limited growth'
349
350    !! 1.1 First call only
351    IF ( firstcall ) THEN
352     
353       !! 1.1.1 Initialization
354       L0(2:nvm) = un - R0 - S0(2:nvm)
355       IF ((MINVAL(L0(2:nvm)) .LT. zero) .OR. (MAXVAL(S0(2:nvm)) .EQ. un)) THEN
356
357          CALL ipslerr_p (3,'in module stomate_alloc', &
358               &           'Something wrong happened', &
359               &           'L0 negative or division by zero if S0 = 1', &
360               &           '(Check your parameters.)')
361
362       ENDIF
363
364
365       !! 1.1.2 Copy the depth of the different soil layers (number of layers=nbdl)
366       !        previously calculated as variable diaglev in routines sechiba.f90 and slowproc.f90
367       z_soil(0) = 0.
368       z_soil(1:nbdl) = diaglev(1:nbdl)
369
370       !! 1.1.3 Print flags and parameter settings
371       WRITE(numout,*) 'allocation:'
372       WRITE(numout,'(a)',ADVANCE='NO') '    > We'
373       !IF ( .NOT. ok_minres ) WRITE(numout,'(a,$)') ' do NOT'
374       WRITE(numout,*) 'try to reach a minumum reservoir when severely stressed.'
375       WRITE(numout,*) '   > Time delay (days) to build leaf mass (::tau_leafinit): ', tau_leafinit
376       WRITE(numout,*) '   > Curvature of root mass with increasing soil depth (::z_nitrogen): ', z_nitrogen
377       WRITE(numout,*) '   > Sap allocation above the ground / total sap allocation (0-1, unitless): '
378       WRITE(numout,*) '       grasses (::alloc_sap_above_grass) :', alloc_sap_above_grass
379       WRITE(numout,*) '   > Default root alloc fraction (1; ::R0): ', R0
380       WRITE(numout,*) '   > Default sapwood alloc fraction (1; ::S0): ', S0(:)
381       WRITE(numout,*) '   > Default fruit allocation (1, ::f_fruit): ', f_fruit
382       WRITE(numout,*) '   > Minimum (min_LtoLSR)/maximum (::max_LtoLSR)leaf alloc fraction (0-1, unitless): ',&
383            min_LtoLSR,max_LtoLSR
384       WRITE(numout,*) '   > Maximum time (days) the carbon reserve can be used:'
385       WRITE(numout,*) '       trees (reserve_time_tree):',reserve_time_tree
386       WRITE(numout,*) '       grasses (reserve_time_grass):',reserve_time_grass
387 
388       firstcall = .FALSE.
389
390    ENDIF
391   
392    !! 1.2 Every call
393
394    !! 1.2.1 Reset output variable (::f_alloc)
395    f_alloc(:,:,:) = zero
396    f_alloc(:,:,icarbres) = un
397    bm_alloc(:,:,:,icarbon) = zero
398    resp_maint(:,:) = zero
399    resp_growth(:,:) = zero
400    npp(:,:) = zero
401    use_reserve(:,:) = zero
402 
403
404    !! 1.2.2 Proxy for soil nitrogen stress
405    !  Nitrogen availability and thus N-stress can not be calculated by the model. Water and
406    !  temperature stress are used as proxy under the assumption that microbial activity is
407    !  determined by soil temperature and water availability. In turn, microbial activity is
408    !  assumed to be an indicator for nitrogen mineralisation and thus its availability.
409
410    !! 1.2.2.1 Convolution of nitrogen stress with root profile
411    !  Here we calculate preliminary soil temperature and soil humidity stresses that will be used
412    !  as proxies for nitrogen stress. Their calculation follows the nitrogen-uptake capacity of roots.
413    !  The capacity of roots to take up nitrogen is assumed to decrease exponentially with
414    !  increasing soil depth. The curvature of the exponential function describing the
415    !  nitrogen-uptake capacity of roots (= root mass * uptake capacity) is given by
416    !  ::z_nitrogen. Strictly speaking its unit is meters (m). Despite its units this parameter
417    !  has no physical meaning.
418    !  Because the roots are described by an exponential function but the soil depth is limited to
419    !  ::z_soil(nbdl), the root profile is truncated at ::z_soil(nbdl). For numerical reasons,
420    !  the total capacity of the soil profile for nitrogen uptake should be 1. To this aim a scaling
421    !  factor (::rpc) is calculated as follows:\n
422    !  \latexonly
423    !  \input{alloc2.tex}
424    !  \endlatexonly
425    !  Then temperature (::t_nitrogen) and humidity (::h_nitrogen) proxies for nitrogen stress are
426    !  calculated using mean weighted (weighted by nitrogen uptake capacity) soil temperature (::tsoil_month)
427    !  or soil moisture (::soil_hum_month) (calculated in stomate_season.f90).
428    !  \latexonly
429    !  \input{alloc3.tex}
430    !  \endlatexonly
431    !  \latexonly
432    !  \input{alloc4.tex}
433    !  \endlatexonl     
434    !  \n
435    ! Scaling factor for integration
436    rpc(:) = un / ( un - EXP( -z_soil(nbdl) / z_nitrogen ) )
437
438    ! Integrate over # soil layers
439    t_nitrogen(:) = zero
440
441    DO l = 1, nbdl ! Loop over # soil layers
442
443       t_nitrogen(:) = t_nitrogen(:) + tsoil_month(:,l) * rpc(:) * &
444            ( EXP( -z_soil(l-1)/z_nitrogen ) - EXP( -z_soil(l)/z_nitrogen ) )
445
446    ENDDO ! Loop over # soil layers
447
448    !---TEMP---
449    WRITE(numout,*) 't_nitrogen, ', t_nitrogen(:)
450    !----------
451
452    !! 1.2.2.2 Convolution for soil moisture
453    !  Integrate over # soil layers
454    h_nitrogen(:) = zero
455
456    DO l = 1, nbdl ! Loop over # soil layers
457
458       h_nitrogen(:) = &
459            h_nitrogen(:) + soilhum_month(:,l) * rpc(:) * &
460            ( EXP( -z_soil(l-1)/z_nitrogen ) - EXP( -z_soil(l)/z_nitrogen ) )
461
462    ENDDO ! Loop over # soil layers
463   
464    !---TEMP---
465    WRITE(numout,*) 'h_nitrogen, ', h_nitrogen(:)
466    !----------
467
468    !! 1.2.3 Separate between natural and agrigultural LAI
469    !  The model distinguishes different natural PFTs but does not contain information
470    !  on whether these PFTs are spatially separated or mixed. In line with the DGVM the
471    !  models treats the natural PFT's as mixed. Therefore, the average LAI over the
472    !  natural PFTs is calculated to estimate light stress. Agricultural PFTs are spatially
473    !  separated.
474    natveg_tot(:) = 0.0
475    lai_nat(:) = 0.0
476
477    DO j = 2, nvm ! Loop over # PFTs
478
479       IF ( natural(j) ) THEN
480
481          ! Mask agricultural vegetation
482          veget_max_nat(:,j) = veget_max(:,j)
483
484       ELSE
485
486          ! Mask natural vegetation
487          veget_max_nat(:,j) = zero
488
489       ENDIF
490
491       ! Sum up fraction of natural space covered by vegetation
492       natveg_tot(:) = natveg_tot(:) + veget_max_nat(:,j)
493
494       ! Sum up lai
495       lai_nat(:) = lai_nat(:) + veget_max_nat(:,j) * lai(:,j)
496
497    ENDDO ! Loop over # PFTs
498
499    DO j = 2, nvm ! Loop over # PFTs
500
501       IF ( natural(j) ) THEN
502
503          ! Use the mean LAI over all natural PFTs when estimating light stress
504          ! on a specific natural PFT
505          lai_around(:,j) = lai_nat(:)
506
507       ELSE
508
509          ! Use the actual LAI (specific for that PFT) when estimating light
510          ! stress on a specific agricultural PFT
511          lai_around(:,j) = lai(:,j)
512
513       ENDIF
514
515    ENDDO ! Loop over # PFTs
516
517
518    !! 1.2.4 Calculate LAI threshold below which carbohydrate reserve is used.
519    !  Lai_max is a PFT-dependent parameter specified in stomate_constants.f90
520    lai_happy_old(:) = lai_max(:) * lai_max_to_happy
521   
522   
523    !! 1.2.5 Set allocatable biomass
524    !  Total allocatable biomass during this time step determined from GPP.
525    !  GPP was calculated as CO2 assimilation in enerbil.f90
526    !  This is ignored later in the code if control%ok_functional_allocation is true
527    bm_alloc_tot(:,:) = gpp(:,:) * dt 
528
529
530 !! 2. Use carbohydrate reserve to support growth and update leaf age
531
532    ! Save old leaf mass, biomass got last updated in stomate_phenology.f90
533    lm_old(:,:) = biomass(:,:,ileaf,icarbon)
534
535    DO j = 2, nvm ! Loop over # PFTs
536
537       !! 2.1 Calculate demand for carbohydrate reserve to support leaf and root growth.
538       !  Maximum time (days) since start of the growing season during which carbohydrate
539       !  may be used
540       IF ( is_tree(j) ) THEN
541
542          reserve_time = reserve_time_tree
543
544       ELSE
545          reserve_time = reserve_time_grass
546
547       ENDIF
548
549       ! Growth is only supported by the use of carbohydrate reserves if the following
550       ! conditions are  statisfied:\n
551       ! - PFT is not senescent;\n
552       ! - LAI must be low (i.e. below ::lai_happy_old) and\n
553       ! - Day of year of the simulation is in the beginning of the growing season.
554       WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. ( .NOT. senescence(:,j) ) .AND. &
555            ( lai(:,j) .LT. lai_happy_old(j) ) .AND. ( when_growthinit(:,j) .LT. reserve_time ) ) 
556
557            ! Determine the mass from the carbohydrate reserve that can be used @tex $(gC m^{-2})$ @endtex.
558            ! Satisfy the demand or use everything that is available
559            ! (i.e. ::biomass(:,j,icarbres,icarbon)). Distribute the demand evenly over the time
560            ! required (::tau_leafinit) to develop a minimal canopy from reserves (::lai_happy_old)
561            ! Needs to be additive, since reserves could already have been used in stomate_phenology
562            ! old use_reserve(:) = &
563            ! old     MIN( biomass(:,j,icarbres,icarbon), &
564            ! old     2._r_std * dt/tau_leafinit * lai_happy_old(j)/ sla(j) ).
565            use_reserve(:,j) = MIN( biomass(:,j,icarbres,icarbon), &
566               & deux * dt / tau_leafinit * lai_happy_old(j) / sla(j) )
567
568!           +++CHECK+++
569!$            use_reserve(:,j) = use_reserve(:,j) + MIN( biomass(:,j,icarbres,icarbon) * 0.1, &
570!$                 deux * dt / tau_leafinit * lai_happy_old(j) / sla(j) )
571!           +++++++++++
572
573            ! Distribute the reserve over leaves and fine roots.
574            ! The part of the reserve going to the leaves is the ratio of default leaf allocation to default root and leaf allocation.
575            ! The remaining of the reserve is alocated to the roots.
576            transloc_leaf(:,j) = L0(j)/(L0(j)+R0) * use_reserve(:,j)
577            biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) + transloc_leaf(:,j)
578            biomass(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) + ( use_reserve(:,j) - transloc_leaf(:,j) )
579
580            ! Adjust the carbohydrate reserve mass by accounting for the reserves allocated to leaves and roots during
581            ! this time step
582            biomass(:,j,icarbres,icarbon) = biomass(:,j,icarbres,icarbon) - use_reserve(:,j)
583
584       ELSEWHERE
585
586           transloc_leaf(:,j) = zero
587
588       ENDWHERE
589     
590       !---TEMP---
591       WRITE(numout,*) 'use_reserve, ', use_reserve(:,j)
592       WRITE(numout,*) 'biomass(icarbres), ', biomass(:,j,icarbres,icarbon)+use_reserve(:,j)
593       WRITE(numout,*) 'other part, ', deux * dt / tau_leafinit * lai_happy_old(j) / sla(j)
594       !----------
595       
596 
597 !! 3. Update leaf age
598
599       !  Leaf age is needed for calculation of turnover and vmax in stomate_turnover.f90 and stomate_vmax.f90 routines.
600       !  Leaf biomass is distributed according to its age into several "age classes" with age class=1 representing the
601       !  youngest class, and consisting of the most newly allocated leaf biomass
602   
603       !! 3.1 Update quantity and age of the leaf biomass in the youngest class
604       !  The new amount of leaf biomass in the youngest age class (leaf_mass_young) is the sum of :
605       !  - the leaf biomass that was already in the youngest age class (leaf_frac(:,j,1) * lm_old(:,j)) with the
606       !    leaf age given in leaf_age(:,j,1)
607       !  - and the new biomass allocated to leaves (bm_alloc(:,j,ileaf,icarbon)) with a leaf age of zero.
608       leaf_mass_young(:,j) = leaf_frac(:,j,1) * lm_old(:,j) + transloc_leaf(:,j)
609
610       ! The age of the updated youngest age class is the average of the ages of its 2 components: bm_alloc(leaf) of age
611       ! '0', and leaf_frac*lm_old(=leaf_mass_young-bm_alloc) of age 'leaf_age(:,:,1)'
612       WHERE ( ( transloc_leaf(:,j) .GT. min_stomate ) .AND. ( leaf_mass_young(:,j) .GT. min_stomate ) )
613         
614          leaf_age(:,j,1) = MAX ( zero, leaf_age(:,j,1) * ( leaf_mass_young(:,j) - transloc_leaf(:,j) ) / &
615               & leaf_mass_young(:,j) )
616         
617       ENDWHERE
618
619
620       !! 3.2 Update leaf fractions
621       !      Update fractions of leaf biomass in each age class (fraction in youngest class increases)
622
623       !! 3.2.1 Update age of youngest leaves
624       !        For age class 1 (youngest class), because we have added biomass to the youngest class, we need to update
625       !        the fraction of total leaf biomass that belongs to the youngest age class : updated mass in class divided
626       !        by new total leaf mass
627       WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
628
629          leaf_frac(:,j,1) = leaf_mass_young(:,j) / biomass(:,j,ileaf,icarbon)
630
631       ENDWHERE
632
633
634       !! 3.2.2 Update age of other age classes
635       !        Because the total leaf biomass has changed, we need to update the fraction of leaves in each age class:
636       !        mass in leaf age class (from previous fraction of leaves in this class and previous total leaf biomass)
637       !        divided by new total mass
638       DO m = 2, nleafages      ! Loop over # leaf age classes
639
640          WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
641
642             leaf_frac(:,j,m) = leaf_frac(:,j,m) * lm_old(:,j) / biomass(:,j,ileaf,icarbon)
643
644          ENDWHERE
645
646       ENDDO    ! Loop over # leaf age classes
647
648    ENDDO ! loop over # PFTs
649
650
651 !! 4. Calculate allocatable fractions of biomass production (NPP)
652     
653    ! Calculate fractions of biomass production (NPP) to be allocated to the different
654    ! biomass components.\n
655    ! The fractions of NPP allocated (0-1, unitless) to the different compartments depend on the
656    ! availability of light, water, and nitrogen.
657    DO j = 2, nvm ! Loop over # PFTs
658
659       ! Reset values
660       RtoLSR(:) = zero
661       LtoLSR(:) = zero
662       StoLSR(:) = zero
663       
664       !! 4.1 Age dependency of aboveground allocation
665       !  For trees, partitioning between above and belowground sapwood biomass is a function
666       !  of age. An older tree gets more allocation to the aboveground sapwoood than a younger tree.
667       !  For the other PFTs it is prescribed.
668       !  ::alloc_min, ::alloc_max and ::demi_alloc are specified in stomate_constants.f90
669       IF ( is_tree(j) ) THEN
670
671          alloc_sap_above (:) = alloc_min(j) + (alloc_max(j) - alloc_min(j)) * &
672             &   ( un - EXP( -age(:,j) / demi_alloc(j) ) )
673
674       ELSE
675
676          alloc_sap_above(:) = alloc_sap_above_grass
677
678       ENDIF  ! tree
679
680       !---TEMP---
681       WRITE(numout,*) 'age, ', age(:,j)
682       !----------
683
684       !! 4.2 Calculate light stress, water stress and proxy for nitrogen stress.
685       !  For the limiting factors a low value indicates a strong limitation
686       WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
687
688          !! 4.2.1 Light stress
689          !  Light stress is a function of the mean lai on the natural part of the grid box
690          !  and of the PFT-specific LAI for agricultural crops. In line with the DGVM, natural
691          !  PFTs in the same gridbox are treated as if they were spatially mixed whereas
692          !  agricultural PFTs are considered to be spatially separated.
693          !  The calculation of the lights stress depends on the extinction coefficient (set to 0.5)
694          !  and of a mean LAI.
695          WHERE( lai_around(:,j) < max_possible_lai )
696             
697             limit_L(:) = MAX( 0.1_r_std, EXP( -ext_coeff(j) * lai_around(:,j) ) )
698
699          ELSEWHERE
700             
701             limit_L(:) = 0.1_r_std
702         
703          ENDWHERE
704
705 
706          !! 4.2.2 Water stress
707          !  Water stress is calculated as the weekly moisture availability.
708          !  Weekly moisture availability is calculated in stomate_season.f90.
709          limit_W(:) = MAX( 0.1_r_std, MIN( un, moiavail_week(:,j) ) )
710
711
712          !! 4.2.3 Proxy for nitrogen stress
713          !  The proxy for nitrogen stress depends on monthly soil water availability
714          !  (::soilhum_month) and monthly soil temperature (::tsoil_month). See section
715          !  1.2.2 for details on how ::t_nitrogen and ::h_nitrogen were calculated.\n
716          !  Currently nitrogen-stress is calculated for both natural and agricultural PFTs.
717          !  Due to intense fertilization of agricultural PFTs this is a strong
718          !  assumption for several agricultural regions in the world (US, Europe, India, ...)
719          !  Water stress on nitrogen mineralisation
720          limit_N_hum(:) = MAX( undemi, MIN( un, h_nitrogen(:) ) )
721
722          ! Temperature stress on nitrogen mineralisation using a Q10 decomposition model
723          ! where Q10 was set to 2
724          limit_N_temp(:) = deux**( ( t_nitrogen(:) - ZeroCelsius - Nlim_tref ) / Nlim_Q10 )
725          limit_N_temp(:) = MAX( 0.1_r_std, MIN( un, limit_N_temp(:) ) )
726
727          ! Combine water and temperature factors to get total nitrogen stress
728          limit_N(:) = MAX( 0.1_r_std, MIN( un, limit_N_hum(:) * limit_N_temp(:) ) )
729
730          ! Take the most limiting factor among soil water and nitrogen
731          limit_WorN(:) = MIN( limit_W(:), limit_N(:) )
732
733          ! Take the most limiting factor among aboveground (i.e. light) and belowground
734          ! (i.e. water & nitrogen) limitations
735          limit(:) = MIN( limit_WorN(:), limit_L(:) )
736
737
738          !! 4.3 Calculate ratio between allocation to leaves, sapwood and roots
739          !  Partitioning between belowground and aboveground biomass components is assumed
740          !  to be proportional to the ratio of belowground and aboveground stresses.\n
741          !  \latexonly
742          !  \input{alloc1.tex}
743          !  \endlatexonly
744          !  Root allocation is the default root allocation corrected by a normalized ratio of aboveground
745          !  stress to total stress. The minimum root allocation is 0.15.
746          RtoLSR(:) = MAX( .15_r_std, R0 * trois * limit_L(:) / ( limit_L(:) + deux * limit_WorN(:) ) )
747
748          ! Sapwood allocation is the default sapwood allocation corrected by a normalized ratio of
749          ! belowground stress to total stress.
750          StoLSR(:) = S0(j) * trois * limit_WorN(:) / ( deux * limit_L(:) + limit_WorN(:) )
751
752          ! Leaf allocation is calculated as the remaining allocation fraction
753          ! The range of variation of leaf allocation is constrained by ::min_LtoLSR and ::max_LtoLSR.
754          LtoLSR(:) = un - RtoLSR(:) - StoLSR(:)
755          LtoLSR(:) = MAX( min_LtoLSR, MIN( max_LtoLSR, LtoLSR(:) ) )
756
757          ! Roots allocation is recalculated as the residual carbon after leaf allocation has been calculated.
758          RtoLSR(:) = un - LtoLSR(:) - StoLSR(:)
759
760       ENDWHERE
761           
762       ! Check whether allocation needs to be adjusted. If LAI exceeds maximum LAI
763       ! (::lai_max), no addition carbon should be allocated to leaf biomass. Allocation is
764       ! then partioned between root and sapwood biomass.
765       WHERE ( (biomass(:,j,ileaf,icarbon) .GT. min_stomate) .AND. (lai(:,j) .GT. lai_max(j)) )
766
767          StoLSR(:) = StoLSR(:) + LtoLSR(:)
768          LtoLSR(:) = zero
769
770       ENDWHERE
771       
772
773       !! 4.4 Calculate the allocation fractions.
774       !  The allocation fractions (::f_alloc) are an output variable (0-1, unitless). f_alloc
775       !  has three dimensions (npts,nvm,nparts). Where ::npts is the number of grid cells, ::nvm is the
776       !  number of PFTs and ::nparts the number of biomass components. Currently six biomass compartments
777       !  are distinguished: (1) Carbon reserves, (2) Aboveground sapwood, (3) Belowground
778       !  sapwood, (4) Roots, (5) fruits/seeds and (6) Leaves.@tex $(gC m^{-2})$ @endtex \n
779       DO i = 1, npts ! Loop over grid cells
780
781          IF ( biomass(i,j,ileaf,icarbon) .GT. min_stomate ) THEN
782     
783            IF ( senescence(i,j) ) THEN
784               
785               !! 4.4.1 Allocate all C to carbohydrate reserve
786               !  If the PFT is senescent allocate all C to carbohydrate reserve,
787               !  then the allocation fraction to reserves is 1.
788               f_alloc(i,j,icarbres) = un
789
790            ELSE
791
792               !! 4.4.2 Allocation during the growing season 
793               f_alloc(i,j,ifruit) = f_fruit
794
795               ! Allocation to the carbohydrate reserve is proportional to leaf and root
796               ! allocation. If carbon is allocated to the carbohydrate reserve, rescaling
797               ! of allocation factors is required to ensure carbon mass preservation.
798               ! Carbon is allocated to the carbohydrate reserve when the pool size of the
799               ! reserve is less than the carbon needed to grow a canopy twice the size of
800               ! the maximum LAI (::lai_max). Twice the size was used as a threshold because
801               ! the reserves needs to be sufficiently to grow a canopy and roots. In case
802               ! the carbohydrate pool is full, there is no need to rescale the other
803               ! allocation factors.
804               ! If there is no rescaling of the allocation factors (carbres=1, no carbon put
805               ! to reserve), then fraction remaining after fruit allocation (1-fruit_alloc)
806               ! is distributed between leaf, root and sap (sap carbon also distributed between   
807               ! sap_above and sap_below with factor alloc_sap_above).
808               ! If carbon is allocated to the carbohydrate reserve, all these factors are
809               ! rescaled through carb_rescale, and an allocation fraction for carbohydrate pool
810               ! appears. carb_rescale depends on the parameter (::ecureuil).
811               ! (::ecureuil) is the fraction of primary leaf and root allocation put into
812               ! reserve, it is specified in stomate_constants.f90 and is either 0 or 1.
813               IF ( ( biomass(i,j,icarbres,icarbon) * sla(j) ) .LT. deux * lai_max(j) ) THEN
814
815                    carb_rescale(i) = un / ( un + ecureuil(j) * ( LtoLSR(i) + RtoLSR(i) ) )
816               
817               ELSE
818                    carb_rescale(i) = un
819               
820               ENDIF
821
822               f_alloc(i,j,ileaf) = LtoLSR(i) * ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
823               f_alloc(i,j,isapabove) = StoLSR(i) * alloc_sap_above(i) * &
824                  ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
825               f_alloc(i,j,isapbelow) = StoLSR(i) * ( un - alloc_sap_above(i) ) * &
826                  ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
827               f_alloc(i,j,iroot) = RtoLSR(i) * ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
828               f_alloc(i,j,icarbres) = ( un - carb_rescale(i) ) * ( un - f_alloc(i,j,ifruit) )
829
830               ENDIF  ! Is senescent?
831
832            ENDIF  ! There are leaves
833
834         ENDDO  ! Loop over # pixels - domain size
835
836      ENDDO  ! loop over # PFTs
837
838
839 !! 5. Calculate maintenance and growth respiration
840
841    ! First, total maintenance respiration for the whole plant is calculated by summing maintenance
842    ! respiration of the different plant compartments. Then, maintenance respiration is subtracted
843    ! from whole-plant allocatable biomass (up to a maximum fraction of the total allocatable biomass).
844    ! Growth respiration is then calculated for each plant compartment as a fraction of remaining
845    ! allocatable biomass for this compartment. NPP is calculated by substracting total autotrophic
846    ! respiration from GPP i.e. NPP = GPP - maintenance resp - growth resp.
847    DO j = 2,nvm        ! Loop over # of PFTs       
848
849       !! 5.1 Maintenance respiration of the different plant parts
850       !  Maintenance respiration of the different plant parts is calculated in
851       !  stomate_resp.f90 as a function of the plant's temperature,
852       !  the long term temperature and plant coefficients
853       resp_maint(:,j) = zero
854
855       !  Following the calculation of hourly maintenance respiration, verify that
856       !  the PFT has not been killed after calcul of resp_maint_part in stomate.
857       DO k = 1, nparts
858
859          WHERE (PFTpresent(:,j))
860
861             resp_maint(:,j) = resp_maint(:,j) + resp_maint_part(:,j,k)
862
863          ENDWHERE
864
865       ENDDO
866       
867       !! 5.2 Substract maintenance respiration from allocatable biomass
868       !  The total maintenance respiration calculated in 2.2 is substracted from the newly
869       !  produced allocatable biomass (bm_alloc_tot). However, ensure that not all allocatable
870       !  biomass is removed by setting a maximum to the fraction of allocatable biomass used
871       !  for maintenance respiration: tax_max. If the maintenance respiration is larger than
872       !  tax_max,the amount tax_max is taken from allocatable biomass, and the remaining of
873       !  maintenance respiration is taken from the tissues themselves (biomass). We suppose
874       !  that respiration is not dependent on leaf age -> therefore the leaf age structure is
875       !  not changed.
876       !  The maximum fraction of allocatable biomass used for respiration is defined as tax_max.
877       !  The value of tax_max is set in the declarations section (0.4 Local variables) of this
878       !  routine
879
880       !! 5.2.1 Resource based allocatable biomass   
881       !  maximum part of allocatable biomass used for respiration
882       bm_tax_max(:) = tax_max * bm_alloc_tot(:,j)
883
884       ! If there is enough allocatable biomass to cover maintenance respiration,
885       ! then biomass associated with maintenance respiration is removed from allocatable biomass
886       WHERE ( ( bm_alloc_tot(:,j) .GT. zero ) .AND. &
887            ( ( resp_maint(:,j) * dt ) .LT. bm_tax_max(:) ) )   
888         
889          bm_alloc_tot(:,j) = bm_alloc_tot(:,j) - resp_maint(:,j) * dt
890
891       ELSEWHERE ( resp_maint(:,j) .GT. min_stomate )
892
893          ! If there is not enough allocatable biomass to cover maintenance respiration, the 
894          ! - maximum allowed allocatable biomass (bm_tax_max) is removed from allocatable biomass.   
895          bm_alloc_tot(:,j) = bm_alloc_tot(:,j) - bm_tax_max(:)
896
897          ! ::bm_pump is the amount of maintenance respiration that exceeds the maximum allocatable biomass
898          ! This amount of biomass still needs to be respired and will be removed from tissues biomass of each
899          ! plant compartment
900          bm_pump(:) = resp_maint(:,j) * dt - bm_tax_max(:)
901
902          ! The biomass is removed from each plant compartment tissues as the ratio of the maintenance         
903          ! respiration of the plant compartment to the total maintenance respiration (resp_maint_part/resp_maint)
904          biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) - &
905             bm_pump(:) * resp_maint_part(:,j,ileaf) / resp_maint(:,j)
906          biomass(:,j,isapabove,icarbon) = biomass(:,j,isapabove,icarbon) - &
907             bm_pump(:) * resp_maint_part(:,j,isapabove) / resp_maint(:,j)
908          biomass(:,j,isapbelow,icarbon) = biomass(:,j,isapbelow,icarbon) - &
909             bm_pump(:) * resp_maint_part(:,j,isapbelow) / resp_maint(:,j)
910          biomass(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) - &
911             bm_pump(:) * resp_maint_part(:,j,iroot) / resp_maint(:,j)
912          biomass(:,j,ifruit,icarbon) = biomass(:,j,ifruit,icarbon) - &
913             bm_pump(:) * resp_maint_part(:,j,ifruit) / resp_maint(:,j)
914          biomass(:,j,icarbres,icarbon) = biomass(:,j,icarbres,icarbon) - &
915             bm_pump(:) * resp_maint_part(:,j,icarbres) / resp_maint(:,j)
916          ! Resource based allocation does not uses a labile carbon pool
917          biomass(:,j,ilabile,icarbon) = zero
918
919       ENDWHERE  ! there is enough allocatable biomass to cover maintenance respiration
920
921     
922       !! 5.3 Allocate allocatable biomass to different plant compartments.
923       !      The amount of allocatable biomass to each compartment is a fraction ::f_alloc of the total
924       !      allocatable biomass. For the resource-based allocation ::f_alloc of the different plant parts
925       !      is calculated in stomate_alloc.f90
926       DO k = 1, nparts
927
928          bm_alloc(:,j,k,icarbon) = f_alloc(:,j,k) * bm_alloc_tot(:,j)
929
930       ENDDO
931     
932
933       !! 5.4 Calculate growth respiration of each plant compartment
934       !      Growth respiration of a plant compartment is a fraction of the allocatable biomass remaining after
935       !      maintenance respiration losses have been taken into account. The fraction of allocatable biomass
936       !      removed for growth respiration is the same for all plant compartments and is defined by the parameter
937       !      frac_growth_resp in stomate_constants.f90. Allocatable biomass ::bm_alloc is updated as a result of
938       !      the removal of growth resp (gC m-2 dt-1).
939       DO k = 1,nparts
940
941          resp_growth_part(:,k) = frac_growthresp(j) * bm_alloc(:,j,k,icarbon) / dt
942          bm_alloc(:,j,k,icarbon) =  ( 1. - frac_growthresp(j) ) * bm_alloc(:,j,k,icarbon)
943
944       ENDDO
945     
946
947       !! 5.5 Total growth respiration
948       !      Calculate total growth respiration of the plant as the sum of growth respiration of all plant parts       
949       resp_growth(:,j) = zero
950       DO k = 1, nparts
951         
952          ! Total growth respiration. Calculate total growth respiration of the plant as the
953          ! sum of growth respiration of all plant parts
954          resp_growth(:,j) = resp_growth(:,j) + resp_growth_part(:,k)
955
956       ENDDO ! # biomass compartments
957
958    ENDDO ! # of PFTs
959
960   
961 !! 6. Update the biomass with newly allocated biomass after respiration
962 
963    !  Save the old leaf biomass for later. "old" leaf mass is leaf mass after maintenance respiration in the case
964    !  where maintenance respiration has required taking biomass from tissues in section 3.2   
965    lm_old(:,:) = biomass(:,:,ileaf,icarbon)
966    biomass(:,:,:,icarbon) = biomass(:,:,:,icarbon) + bm_alloc(:,:,:,icarbon)
967
968   
969 !! 7. Deal with negative biomasses
970
971    !  Biomass can become negative in some rare cases, as the GPP can be negative (dark respiration). In this case,
972    !  we set biomass to some small value min_stomate. This creation of matter (carbon) is taken into account by
973    !  decreasing the autotrophic respiration by the same amount that has been added to biomass for it to become
974    !  positive. In this case, maintenance respiration can become negative !!!
975   
976    DO k = 1, nparts    ! Loop over # of plant parts
977
978       WHERE ( biomass(:,:,k,icarbon) .LT. zero )
979
980          bm_create(:,:) = min_stomate - biomass(:,:,k,icarbon)     
981          biomass(:,:,k,icarbon) = biomass(:,:,k,icarbon) + bm_create(:,:)   
982          resp_maint(:,:) = resp_maint(:,:) - bm_create(:,:) / dt
983
984       ENDWHERE
985
986    ENDDO       ! Loop over # plant parts
987   
988
989 !! 8. Calculate NPP (See Eq 1 in header)
990   
991    ! Calculate the NPP @tex $(gC.m^{-2}dt^{-1})$ @endtex as the difference between GPP
992    ! and autotrophic respiration (maintenance and growth respirations)
993    ! This is a diagnostic calculation
994    npp(:,:) = gpp(:,:) - resp_growth(:,:) - resp_maint(:,:)
995   
996
997 !! 9. Update leaf age
998
999    !  Leaf age is needed for calculation of turnover and vmax in stomate_turnover.f90 and stomate_vmax.f90 routines.
1000    !  Leaf biomass is distributed according to its age into several "age classes" with age class=1 representing the
1001    !  youngest class, and consisting of the most newly allocated leaf biomass
1002   
1003    !! 9.1 Update quantity and age of the leaf biomass in the youngest class
1004    !      The new amount of leaf biomass in the youngest age class (leaf_mass_young) is the sum of :
1005    !      - the leaf biomass that was already in the youngest age class (leaf_frac(:,j,1) * lm_old(:,j)) with the
1006    !        leaf age given in leaf_age(:,j,1)
1007    !      - and the new biomass allocated to leaves (bm_alloc(:,j,ileaf)) with a leaf age of zero.
1008    DO j = 2,nvm
1009
1010       leaf_mass_young(:,j) = leaf_frac(:,j,1) * lm_old(:,j) + bm_alloc(:,j,ileaf,icarbon)
1011
1012    ENDDO
1013
1014    ! The age of the updated youngest age class is the average of the ages of its 2 components: bm_alloc(leaf) of age
1015    ! '0', and leaf_frac*lm_old(=leaf_mass_young-bm_alloc) of age 'leaf_age(:,j,1)'
1016    DO j = 2,nvm
1017
1018       WHERE ( ( bm_alloc(:,j,ileaf,icarbon) .GT. zero ) .AND. ( leaf_mass_young(:,j) .GT. zero ) )
1019
1020          leaf_age(:,j,1) = MAX( zero, leaf_age(:,j,1) * ( leaf_mass_young(:,j) - bm_alloc(:,j,ileaf,icarbon) ) / &
1021             & leaf_mass_young(:,j) )
1022         
1023       ENDWHERE
1024
1025    ENDDO
1026
1027    !  For age class 1 (youngest class), because we have added biomass to the youngest class, we need to update
1028    !  the fraction of total leaf biomass that belongs to the youngest age class : updated mass in class divided
1029    !  by new total leaf mass
1030    DO j = 2,nvm
1031
1032       WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
1033
1034          leaf_frac(:,j,1) = leaf_mass_young(:,j) / biomass(:,j,ileaf,icarbon)
1035
1036       ENDWHERE
1037
1038    ENDDO
1039
1040    !! 9.2 Update age of other age classes
1041    !  Because the total leaf biomass has changed, we need to update the fraction of leaves in each age class:
1042    !  mass in leaf age class (from previous fraction of leaves in this class and previous total leaf biomass)
1043    !  divided by new total mass
1044    DO m = 2, nleafages 
1045
1046       DO j = 2,nvm
1047
1048          WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
1049
1050             leaf_frac(:,j,m) = leaf_frac(:,j,m) * lm_old(:,j) / biomass(:,j,ileaf,icarbon)
1051
1052          ENDWHERE
1053
1054       ENDDO
1055
1056    ENDDO
1057
1058
1059 !! 10. Update whole-plant age
1060   
1061    !! 10.1 PFT age
1062    !  At every time step, increase age of the biomass that was already present at previous time step.
1063    !  Age is expressed in years, and the time step 'dt' in days so age increase is: dt divided by number
1064    !  of days in a year.
1065    WHERE ( PFTpresent(:,:) )
1066
1067       age(:,:) = age(:,:) + dt/one_year
1068
1069    ELSEWHERE
1070
1071       age(:,:) = zero
1072
1073    ENDWHERE
1074
1075
1076    !! 10.2 Age of grasses and crops
1077    !  For grasses and crops, biomass with age 0 has been added to the whole plant with age 'age'. New biomass is the sum of
1078    !  the current total biomass in all plant parts (bm_new), bm_new(:) = SUM( biomass(:,j,:,icarbon), DIM=2 ). The biomass
1079    !  that has just been added is the sum of the allocatable biomass of all plant parts (bm_add), its age is zero. bm_add(:) =
1080    !  SUM( bm_alloc(:,j,:,icarbon), DIM=2 ). Before allocation, the plant biomass is bm_new-bm_add, its age is "age(:,j)".
1081    !  The age of the new biomass is the average of the ages of previous and added biomass.
1082    !  For trees, age is treated in "establish" if vegetation is dynamic, and in turnover routines if it is static (in this
1083    !  case, only the age of the heartwood is accounted for).
1084    DO j = 2,nvm
1085
1086       IF ( .NOT. is_tree(j) ) THEN
1087
1088          bm_new(:) = biomass(:,j,ileaf,icarbon) + biomass(:,j,isapabove,icarbon) + &
1089               biomass(:,j,iroot,icarbon) + biomass(:,j,ifruit,icarbon)
1090          bm_add(:) = bm_alloc(:,j,ileaf,icarbon) + bm_alloc(:,j,isapabove,icarbon) + &
1091               bm_alloc(:,j,iroot,icarbon) + bm_alloc(:,j,ifruit,icarbon)
1092
1093          WHERE ( ( bm_new(:) .GT. zero ) .AND. ( bm_add(:) .GT. min_stomate ) )
1094
1095             age(:,j) = age(:,j) * ( bm_new(:) - bm_add(:) ) / bm_new(:)
1096         
1097          ENDWHERE
1098
1099       ENDIF ! is .NOT. tree
1100
1101    ENDDO  ! Loop over #PFTs
1102
1103
1104 !! 11. Write history files
1105
1106    ! Save in history file the variables describing the biomass allocated to the plant parts
1107    CALL histwrite (hist_id_stomate, 'BM_ALLOC_LEAF', itime, &
1108         bm_alloc(:,:,ileaf,icarbon), npts*nvm, horipft_index)
1109    CALL histwrite (hist_id_stomate, 'BM_ALLOC_SAP_AB', itime, &
1110         bm_alloc(:,:,isapabove,icarbon), npts*nvm, horipft_index)
1111    CALL histwrite (hist_id_stomate, 'BM_ALLOC_SAP_BE', itime, &
1112         bm_alloc(:,:,isapbelow,icarbon), npts*nvm, horipft_index)
1113    CALL histwrite (hist_id_stomate, 'BM_ALLOC_ROOT', itime, &
1114         bm_alloc(:,:,iroot,icarbon), npts*nvm, horipft_index)
1115    CALL histwrite (hist_id_stomate, 'BM_ALLOC_FRUIT', itime, &
1116         bm_alloc(:,:,ifruit,icarbon), npts*nvm, horipft_index)
1117    CALL histwrite (hist_id_stomate, 'BM_ALLOC_RES', itime, &
1118         bm_alloc(:,:,icarbres,icarbon), npts*nvm, horipft_index)
1119
1120    IF (bavard.GE.4) WRITE(numout,*) 'Leaving resource limited growth'
1121
1122
1123  END SUBROUTINE growth_res_lim
1124
1125END MODULE stomate_growth_res_lim
Note: See TracBrowser for help on using the repository browser.