source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_stomate/stomate_alloc.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 38.4 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_alloc
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7!                This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Allocate net primary production to: carbon reserves, aboveground sapwood,
10!! belowground sapwood, root, fruits and leaves.     
11!!
12!!\n DESCRIPTION: None
13!!
14!! RECENT CHANGE(S): None
15!!
16!! REFERENCE(S) :
17!!
18!! SVN          :
19!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_alloc.f90 $
20!! $Date: 2017-10-18 11:15:06 +0200 (Wed, 18 Oct 2017) $
21!! $Revision: 4693 $
22!! \n
23!_ ================================================================================================================================
24
25MODULE stomate_alloc
26
27  ! Modules used:
28
29  USE ioipsl_para
30  USE pft_parameters
31  USE stomate_data
32  USE constantes
33  USE constantes_soil
34
35  IMPLICIT NONE
36
37  ! Private & public routines
38
39  PRIVATE
40  PUBLIC alloc,alloc_clear
41
42 ! Variables shared by all subroutines in this module
43
44  LOGICAL, SAVE                                             :: firstcall_alloc = .TRUE.  !! Is this the first call? (true/false)
45!$OMP THREADPRIVATE(firstcall_alloc)
46CONTAINS
47
48
49!! ================================================================================================================================
50!! SUBROUTINE   : alloc_clear
51!!
52!>\BRIEF          Set the flag ::firstcall_alloc to .TRUE. and as such activate section
53!! 1.1 of the subroutine alloc (see below).\n
54!!
55!_ ================================================================================================================================
56
57  SUBROUTINE alloc_clear
58    firstcall_alloc = .TRUE.
59  END SUBROUTINE alloc_clear
60
61
62
63!! ================================================================================================================================
64!! SUBROUTINE   : alloc
65!!
66!>\BRIEF         Allocate net primary production (= photosynthesis
67!! minus autothrophic respiration) to: carbon reserves, aboveground sapwood,
68!! belowground sapwood, root, fruits and leaves following Friedlingstein et al. (1999).
69!!
70!! DESCRIPTION (definitions, functional, design, flags):\n
71!! The philosophy underlying the scheme is that allocation patterns result from
72!! evolved responses that adjust carbon investments to facilitate capture of most
73!! limiting resources i.e. light, water and mineral nitrogen. The implemented scheme
74!! calculates the limitation of light, water and nitrogen. However, nitrogen is not a
75!! prognostic variable of the model and therefore soil temperature and soil moisture
76!! are used as a proxy for soil nitrogen availability.\n
77!! Sharpe & Rykiel (1991) proposed a generic relationship between the allocation of
78!! carbon to a given plant compartment and the availability of a particular resource:\n
79!! \latexonly
80!!   \input{alloc1.tex}
81!! \endlatexonly
82!! \n
83!! where A is the allocation of biomass production (NPP) to a given compartment (either
84!! leaves, stem, or roots). Xi and Yj are resource availabilities (e.g. light, water,
85!! nutrient). For a given plant compartment, a resource can be of type X or Y. An increase
86!! in a X-type resource will increase the allocation to compartment A. An increase in a
87!! Y-type resource will, however, lead to a decrease in carbon allocation to that compartment.
88!! In other words, Y-type resources are those for which uptake increases with increased
89!! investment in the compartment in question. X-type resources, as a consequence of
90!! trade-offs, are the opposite. For example, water is a Y-type resource for root allocation.
91!! Water-limited conditions should promote carbon allocation to roots, which enhance water
92!! uptake and hence minimize plant water stress. Negative relationships between investment
93!! and uptake arise when increased investment in one compartment leads, as required for
94!! conservation of mass, to decreased investment in a component involved in uptake of
95!! that resource.\n
96!!
97!! The implemented scheme allocates carbon to the following components:\n
98!! - Carbon reserves;\n
99!! - Aboveground sapwood;\n
100!! - Belowground sapwood;\n
101!! - Roots;\n
102!! - Fruits/seeds and\n
103!! - Leaves.
104!! \n
105!!
106!! The allocation to fruits and seeds is simply a 10% "tax" of the total biomass
107!! production.\n
108!! Following carbohydrate use to support budburst and initial growth, the
109!! carbohydrate reserve is refilled. The daily amount of carbon allocated to the
110!! reserve pool is proportional to leaf+root allocation (::LtoLSR and ::RtoLSR).\n
111!! Sapwood and root allocation (respectively ::StoLSR and ::RtoLSR) are proportional
112!! to the estimated light and soil (water and nitrogen) stress (::Limit_L and
113!! ::Limit_NtoW). Further, Sapwood allocation is separated in belowground sapwood
114!! and aboveground sapwood making use of the parameter (:: alloc_sap_above_tree
115!! or ::alloc_sap_above_grass). For trees partitioning between above and
116!! belowground compartments is a function of PFT age.\n
117!! Leaf allocation (::LtoLSR) is calculated as the residual of root and sapwood
118!! allocation (LtoLSR(:) = 1. - RtoLSR(:) - StoLSR(:).\n
119!!
120!! RECENT CHANGE(S): None
121!!
122!! MAIN OUTPUT VARIABLE(S): :: f_alloc; fraction of NPP that is allocated to the
123!! six different biomass compartments (leaves, roots, above and belowground wood,
124!! carbohydrate reserves and fruits). DIMENSION(npts,nvm,nparts).
125!!
126!! REFERENCE(S) :
127!! - Friedlingstein, P., G. Joel, C.B. Field, and Y. Fung (1999), Towards an allocation
128!! scheme for global terrestrial carbon models, Global Change Biology, 5, 755-770.\n
129!! - Sharpe, P.J.H., and Rykiel, E.J. (1991), Modelling integrated response of plants
130!! to multiple stresses. In: Response of Plants to Multiple Stresses (eds Mooney, H.A.,
131!! Winner, W.E., Pell, E.J.), pp. 205-224, Academic Press, San Diego, CA.\n
132!! - Krinner G, Viovy N, de Noblet-Ducoudr N, Ogee J, Polcher J, Friedlingstein P,
133!! Ciais P, Sitch S, Prentice I C (2005) A dynamic global vegetation model for studies
134!! of the coupled atmosphere-biosphere system. Global Biogeochemical Cycles, 19, GB1015,
135!! doi: 10.1029/2003GB002199.\n
136!! - Malhi, Y., Doughty, C., and Galbraith, D. (2011). The allocation of ecosystem net primary productivity in tropical forests,
137!! Philosophical Transactions of the Royal Society B-Biological Sciences, 366, 3225-3245, DOI 10.1098/rstb.2011.0062.\n
138!!
139!! FLOWCHART    :
140!! \latexonly
141!!   \includegraphics[scale=0.5]{allocflow.jpg}
142!! \endlatexonly
143!! \n
144!_ ================================================================================================================================
145
146  SUBROUTINE alloc (npts, dt, &
147       lai, veget_cov_max, senescence, when_growthinit, &
148       moiavail_week, tsoil_month, soilhum_month, &
149       biomass, age, leaf_age, leaf_frac, rprof, f_alloc)
150
151 !! 0. Variable and parameter declaration
152
153    !! 0.1 Input variables
154
155    INTEGER(i_std), INTENT(in)                                 :: npts                  !! Domain size - number of grid cells
156                                                                                        !! (unitless)
157    REAL(r_std), INTENT(in)                                    :: dt                    !! Time step of the simulations for stomate
158                                                                                        !! (days)
159    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: lai                   !! PFT leaf area index
160                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
161    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: veget_cov_max         !! PFT "Maximal" coverage fraction of a PFT
162                                                                                        !! (= ind*cn_ind)
163                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
164    LOGICAL, DIMENSION(npts,nvm), INTENT(in)                   :: senescence            !! Is the PFT senescent?  - only for
165                                                                                        !! deciduous trees (true/false)
166    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: when_growthinit       !! Days since beginning of growing season
167                                                                                        !! (days)
168    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: moiavail_week         !! PFT moisture availability - integrated
169                                                                                        !! over a week (0-1, unitless)
170    REAL(r_std), DIMENSION(npts,nslm), INTENT(in)              :: tsoil_month           !! PFT soil temperature - integrated over
171                                                                                        !! a month (K)
172    REAL(r_std), DIMENSION(npts,nslm), INTENT(in)              :: soilhum_month         !! PFT soil humidity - integrated over a
173                                                                                        !! month (0-1, unitless)
174    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)               :: age                   !! PFT age (days)
175
176    !! 0.2 Output variables
177
178    !! 0.3 Modified variables
179
180    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(inout) :: biomass         !! PFT total biomass
181                                                                                        !! @tex $(gC m^{-2})$ @endtex
182    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_age              !! PFT age of different leaf classes
183                                                                                        !! (days)
184    REAL(r_std), DIMENSION(npts,nvm,nleafages), INTENT(inout)  :: leaf_frac             !! PFT fraction of leaves in leaf age class
185                                                                                        !! (0-1, unitless)
186    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: rprof                 !! [DISPENSABLE] PFT rooting depth - not
187                                                                                        !! calculated in the current version of
188                                                                                        !! the model (m)
189    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out)       :: f_alloc               !! PFT fraction of NPP that is allocated to
190                                                                                        !! the different components (0-1, unitless)
191
192    !! 0.4 Local variables
193
194    REAL(r_std), DIMENSION(nvm)                                :: lai_happy             !! Lai threshold below which carbohydrate
195                                                                                        !! reserve may be used
196                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
197    REAL(r_std), DIMENSION(npts)                               :: limit_L               !! Lights stress (0-1, unitless)
198    REAL(r_std), DIMENSION(npts)                               :: limit_N               !! Total nitrogen stress (0-1, unitless)
199    REAL(r_std), DIMENSION(npts)                               :: limit_N_temp          !! Stress from soil temperature on nitrogen
200                                                                                        !! mineralisation (0-1, unitless)
201    REAL(r_std), DIMENSION(npts)                               :: limit_N_hum           !! Stress from soil humidity on nitrogen
202                                                                                        !! mineralisation (0-1, unitless)
203    REAL(r_std), DIMENSION(npts)                               :: limit_W               !! Soil water stress (0-1, unitless)
204    REAL(r_std), DIMENSION(npts)                               :: limit_WorN            !! Most limiting factor in the soil:
205                                                                                        !! nitrogen or water (0-1, unitless)
206    REAL(r_std), DIMENSION(npts)                               :: limit                 !! Most limiting factor: amongst limit_N,
207                                                                                        !! limit_W and limit_L (0-1, unitless)
208    REAL(r_std), DIMENSION(npts)                               :: t_nitrogen            !! Preliminairy soil temperature stress
209                                                                                        !! used as a proxy for nitrogen stress (K)
210    REAL(r_std), DIMENSION(npts)                               :: h_nitrogen            !! Preliminairy soil humidity stress used
211                                                                                        !! as a proxy for nitrogen stress
212                                                                                        !! (unitless) 
213    REAL(r_std), DIMENSION(npts)                               :: rpc                   !! Scaling factor for integrating vertical
214                                                                                        !!  soil profiles (unitless)   
215    REAL(r_std), DIMENSION(npts)                               :: LtoLSR                !! Ratio between leaf-allocation and
216                                                                                        !! (leaf+sapwood+root)-allocation
217                                                                                        !! (0-1, unitless)
218    REAL(r_std), DIMENSION(npts)                               :: StoLSR                !! Ratio between sapwood-allocation and
219                                                                                        !! (leaf+sapwood+root)-allocation
220                                                                                        !! (0-1, unitless)
221    REAL(r_std), DIMENSION(npts)                               :: RtoLSR                !! Ratio between root-allocation and
222                                                                                        !! (leaf+sapwood+root)-allocation
223                                                                                        !! (0-1, unitless)
224    REAL(r_std), DIMENSION(npts)                               :: carb_rescale          !! Rescaling factor for allocation factors
225                                                                                        !! if carbon is allocated to carbohydrate
226                                                                                        !! reserve (0-1, unitless)
227    REAL(r_std), DIMENSION(npts)                               :: use_reserve           !! Mass of carbohydrate reserve used to
228                                                                                        !! support growth
229                                                                                        !! @tex $(gC m^{-2})$ @endtex
230    REAL(r_std), DIMENSION(npts)                               :: transloc_leaf         !! Fraction of carbohydrate reserve used
231                                                                                        !! (::use_reserve) to support leaf growth
232                                                                                        !! @tex $(gC m^{-2})$ @endtex
233    REAL(r_std), DIMENSION(npts)                               :: leaf_mass_young       !! Leaf biomass in youngest leaf age class
234                                                                                        !! @tex $(gC m^{-2})$ @endtex
235    REAL(r_std), DIMENSION(npts,nvm)                           :: lm_old                !! Variable to store leaf biomass from
236                                                                                        !! previous time step
237                                                                                        !! @tex $(gC m^{-2})$ @endtex
238    REAL(r_std)                                                :: reserve_time          !! Maximum number of days during which
239                                                                                        !! carbohydrate reserve may be used (days)
240    REAL(r_std), DIMENSION(npts,nvm)                           :: lai_around            !! lai on natural part of the grid cell, or
241                                                                                        !! of agricultural PFTs
242                                                                                        !! @tex $(m^2 m^{-2})$ @endtex
243    REAL(r_std), DIMENSION(npts,nvm)                           :: veget_cov_max_nat     !! Vegetation cover of natural PFTs on the
244                                                                                        !! grid cell (agriculture masked)
245                                                                                        !! (0-1, unitless)
246    REAL(r_std), DIMENSION(npts)                               :: natveg_tot            !! Total natural vegetation cover on
247                                                                                        !! natural part of the grid cell
248                                                                                        !! (0-1, unitless)
249    REAL(r_std), DIMENSION(npts)                               :: lai_nat               !! Average LAI on natural part of the grid
250                                                                                        !! cell @tex $(m^2 m^{-2})$ @endtex
251    REAL(r_std), DIMENSION(npts)                               :: zdiff_min             !! [DISPENSABLE] intermediate array for
252                                                                                        !! looking for minimum
253    REAL(r_std), DIMENSION(npts)                               :: alloc_sap_above       !! Prescribed fraction of sapwood
254                                                                                        !! allocation to above ground sapwood
255                                                                                        !! (0-1, unitless)
256    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)               :: z_soil                !! Variable to store depth of the different
257                                                                                        !! soil layers (m)
258!$OMP THREADPRIVATE(z_soil)
259    INTEGER(i_std)                                             :: i,j,l,m               !! Indices (unitless)
260    INTEGER(i_std)                                             :: ier                   !! Error handling
261
262!_ ================================================================================================================================
263
264    IF (printlev>=3) WRITE(numout,*) 'Entering alloc'
265
266!! 1. Initialize
267
268    !! 1.1 First call only
269    IF ( firstcall_alloc ) THEN
270
271       !
272       ! 1.1.0 Initialization
273       !
274       L0(2:nvm) = un - R0(2:nvm) - S0(2:nvm) 
275       IF ((MINVAL(L0(2:nvm)) .LT. zero) .OR. (MAXVAL(S0(2:nvm)) .EQ. un)) THEN
276          CALL ipslerr_p (3,'in module stomate_alloc', &
277               &           'Something wrong happened', &
278               &           'L0 negative or division by zero if S0 = 1', &
279               &           '(Check your parameters.)')
280       ENDIF
281
282       
283       !! 1.1.1 Copy the depth of the different soil layers (number of layers=nslm)
284       !        previously calculated as variable diaglev in routines sechiba.f90 and slowproc.f90 
285       ALLOCATE(z_soil(0:nslm), stat=ier)
286       IF ( ier /= 0 ) CALL ipslerr_p(3,'stomate_alloc','Pb in allocate of z_soil','','')
287       z_soil(0) = zero
288       z_soil(1:nslm) = diaglev(1:nslm)
289
290       !! 1.1.2 Print flags and parameter settings
291       IF (printlev >= 2) THEN
292          WRITE(numout,*) 'alloc:'
293          WRITE(numout,'(a,$)') '    > We'
294          IF ( .NOT. ok_minres ) WRITE(numout,'(a,$)') ' do NOT'
295          WRITE(numout,*) 'try to reach a minumum reservoir when severely stressed.'
296          WRITE(numout,*) '   > Time delay (days) to build leaf mass (::tau_leafinit): ', &
297               tau_leafinit(:)
298          WRITE(numout,*) '   > Curvature of root mass with increasing soil depth (::z_nitrogen): ', &
299               z_nitrogen
300          WRITE(numout,*) '   > Sap allocation above the ground / total sap allocation (0-1, unitless): '
301          WRITE(numout,*) '       grasses (::alloc_sap_above_grass) :', alloc_sap_above_grass
302          WRITE(numout,*) '   > Default root alloc fraction (1; ::R0): ', R0(:)
303          WRITE(numout,*) '   > Default sapwood alloc fraction (1; ::S0): ', S0(:)
304          WRITE(numout,*) '   > Default fruit allocation (1, ::f_fruit): ', f_fruit
305          WRITE(numout,*) '   > Minimum (min_LtoLSR)/maximum (::max_LtoLSR)leaf alloc fraction (0-1, unitless): ',&
306               min_LtoLSR,max_LtoLSR
307          WRITE(numout,*) '   > Maximum time (days) the carbon reserve can be used:'
308          WRITE(numout,*) '       trees (reserve_time_tree):',reserve_time_tree
309          WRITE(numout,*) '       grasses (reserve_time_grass):',reserve_time_grass
310       END IF
311       firstcall_alloc = .FALSE.
312
313    ENDIF
314
315
316    !! 1.2 Every call
317    !! 1.2.1 Reset output variable (::f_alloc)
318    f_alloc(:,:,:) = zero
319    f_alloc(:,:,icarbres) = un
320
321 
322    !! 1.2.2 Proxy for soil nitrogen stress
323    !        Nitrogen availability and thus N-stress can not be calculated by the model. Water and
324    !        temperature stress are used as proxy under the assumption that microbial activity is
325    !        determined by soil temperature and water availability. In turn, microbial activity is
326    !         assumed to be an indicator for nitrogen mineralisation and thus its availability.
327
328    !! 1.2.2.1 Convolution of nitrogen stress with root profile
329    !          Here we calculate preliminary soil temperature and soil humidity stresses that will be used
330    !          as proxies for nitrogen stress. Their calculation follows the nitrogen-uptake capacity of roots.
331    !          The capacity of roots to take up nitrogen is assumed to decrease exponentially with
332    !          increasing soil depth. The curvature of the exponential function describing the
333    !          nitrogen-uptake capacity of roots (= root mass * uptake capacity) is given by
334    !          ::z_nitrogen. Strictly speaking its unit is meters (m). Despite its units this parameter
335    !          has no physical meaning.
336    !          Because the roots are described by an exponential function but the soil depth is limited to
337    !          ::z_soil(nslm), the root profile is truncated at ::z_soil(nslm). For numerical reasons,
338    !          the total capacity of the soil profile for nitrogen uptake should be 1. To this aim a scaling
339    !          factor (::rpc) is calculated as follows:\n
340    !          \latexonly
341    !            \input{alloc2.tex}
342    !          \endlatexonly
343    !          Then temperature (::t_nitrogen) and humidity (::h_nitrogen) proxies for nitrogen stress are
344    !          calculated using mean weighted (weighted by nitrogen uptake capacity) soil temperature (::tsoil_month)
345    !          or soil moisture (::soil_hum_month) (calculated in stomate_season.f90).
346    !          \latexonly
347    !            \input{alloc3.tex}
348    !          \endlatexonly
349    !          \latexonly
350    !            \input{alloc4.tex}
351    !          \endlatexonly   
352    !          \n
353                 
354    ! Scaling factor for integration
355    rpc(:) = un / ( un - EXP( -z_soil(nslm) / z_nitrogen ) )
356
357    ! Integrate over # soil layers
358    t_nitrogen(:) = zero
359
360    DO l = 1, nslm ! Loop over # soil layers
361
362       t_nitrogen(:) = &
363            t_nitrogen(:) + tsoil_month(:,l) * rpc(:) * &
364            ( EXP( -z_soil(l-1)/z_nitrogen ) - EXP( -z_soil(l)/z_nitrogen ) )
365
366    ENDDO ! Loop over # soil layers
367
368 
369!!$    !! 1.2.2.2 Convolution for soil moisture
370!!$    !          Scaling factor for integration
371!!$    rpc(:) = 1. / ( 1. - EXP( -z_soil(nslm) / z_nitrogen ) )
372
373    ! Integrate over # soil layers
374    h_nitrogen(:) = zero
375
376    DO l = 1, nslm ! Loop over # soil layers
377
378       h_nitrogen(:) = &
379            h_nitrogen(:) + soilhum_month(:,l) * rpc(:) * &
380            ( EXP( -z_soil(l-1)/z_nitrogen ) - EXP( -z_soil(l)/z_nitrogen ) )
381
382    ENDDO ! Loop over # soil layers
383
384
385    !! 1.2.3 Separate between natural and agrigultural LAI
386    !        The model distinguishes different natural PFTs but does not contain information
387    !        on whether these PFTs are spatially separated or mixed. In line with the DGVM the
388    !        models treats the natural PFT's as mixed. Therefore, the average LAI over the
389    !        natural PFTs is calculated to estimate light stress. Agricultural PFTs are spatially
390    !        separated.
391    natveg_tot(:) = zero
392    lai_nat(:) = zero
393
394    DO j = 2, nvm ! Loop over # PFTs
395
396       IF ( natural(j) ) THEN
397          ! Mask agricultural vegetation
398          veget_cov_max_nat(:,j) = veget_cov_max(:,j)
399       ELSE
400          ! Mask natural vegetation
401          veget_cov_max_nat(:,j) = zero
402       ENDIF
403
404       ! Sum up fraction of natural space covered by vegetation
405       natveg_tot(:) = natveg_tot(:) + veget_cov_max_nat(:,j)
406
407       ! Sum up lai
408       lai_nat(:) = lai_nat(:) + veget_cov_max_nat(:,j) * lai(:,j)
409
410    ENDDO ! Loop over # PFTs
411
412    DO j = 2, nvm ! Loop over # PFTs
413
414       IF ( natural(j) ) THEN
415
416          ! Use the mean LAI over all natural PFTs when estimating light stress
417          ! on a specific natural PFT
418          lai_around(:,j) = lai_nat(:)
419       ELSE
420
421          ! Use the actual LAI (specific for that PFT) when estimating light
422          ! stress on a specific agricultural PFT
423          lai_around(:,j) = lai(:,j)
424       ENDIF
425
426    ENDDO ! Loop over # PFTs
427
428
429    !! 1.2.4 Calculate LAI threshold below which carbohydrate reserve is used.
430    !        Lai_max is a PFT-dependent parameter specified in stomate_constants.f90
431    lai_happy(:) = lai_max(:) * lai_max_to_happy(:)
432
433 !! 2. Use carbohydrate reserve to support growth and update leaf age
434
435    ! Save old leaf mass, biomass got last updated in stomate_phenology.f90
436    lm_old(:,:) = biomass(:,:,ileaf,icarbon)
437
438    DO j = 2, nvm ! Loop over # PFTs
439
440       !! 2.1 Calculate demand for carbohydrate reserve to support leaf and root growth.
441       !      Maximum time (days) since start of the growing season during which carbohydrate
442       !      may be used
443       IF ( is_tree(j) ) THEN
444          reserve_time = reserve_time_tree
445       ELSE
446          reserve_time = reserve_time_grass
447       ENDIF
448
449       ! Growth is only supported by the use of carbohydrate reserves if the following
450       ! conditions are  statisfied:\n
451       ! - PFT is not senescent;\n
452       ! - LAI must be low (i.e. below ::lai_happy) and\n
453       ! - Day of year of the simulation is in the beginning of the growing season.
454       WHERE ( ( biomass(:,j,ileaf,icarbon) .GT. zero ) .AND. & 
455            ( .NOT. senescence(:,j) ) .AND. &
456            ( lai(:,j) .LT. lai_happy(j) ) .AND. &
457            ( when_growthinit(:,j) .LT. reserve_time ) ) 
458
459          ! Determine the mass from the carbohydrate reserve that can be used @tex $(gC m^{-2})$ @endtex.
460          ! Satisfy the demand or use everything that is available
461          ! (i.e. ::biomass(:,j,icarbres)). Distribute the demand evenly over the time
462          ! required (::tau_leafinit) to develop a minimal canopy from reserves (::lai_happy).
463          use_reserve(:) = &
464               MIN( biomass(:,j,icarbres,icarbon), &
465               deux * dt/tau_leafinit(j) * lai_happy(j)/ sla(j) )
466
467          ! Distribute the reserve over leaves and fine roots.
468          ! The part of the reserve going to the leaves is the ratio of default leaf allocation to default root and leaf allocation.
469          ! The remaining of the reserve is alocated to the roots.
470          transloc_leaf(:) = L0(j)/(L0(j)+R0(j)) * use_reserve(:)
471          biomass(:,j,ileaf,icarbon) = biomass(:,j,ileaf,icarbon) + transloc_leaf(:)
472          biomass(:,j,iroot,icarbon) = biomass(:,j,iroot,icarbon) + ( use_reserve(:) - transloc_leaf(:) )
473
474          ! Adjust the carbohydrate reserve mass by accounting for the reserves allocated to leaves and roots during
475          ! this time step
476          biomass(:,j,icarbres,icarbon) = biomass(:,j,icarbres,icarbon) - use_reserve(:)
477
478       ELSEWHERE
479
480          transloc_leaf(:) = zero
481
482       ENDWHERE
483   
484       !! 2.2 Update leaf age
485       !! 2.2.1 Decrease leaf age in youngest class
486       !        Adjust the mass of the youngest leaves by the newly grown leaves
487       leaf_mass_young(:) = leaf_frac(:,j,1) * lm_old(:,j) + transloc_leaf(:)
488
489       WHERE ( ( transloc_leaf(:) .GT. min_stomate ) .AND. ( leaf_mass_young(:) .GT. min_stomate ) )
490         
491          ! Adjust leaf age by the ratio of leaf_mass_young (t-1)/leaf_mass_young (t)
492          leaf_age(:,j,1) = MAX( zero, leaf_age(:,j,1) * ( leaf_mass_young(:) - transloc_leaf(:) ) / &
493               leaf_mass_young(:) )
494
495       ENDWHERE
496
497       !! 2.2.2 Update leaf mass fraction for the different age classes
498       !        Mass fraction in the youngest age class is calculated as the ratio between
499       !        the new mass in the youngest class and the total leaf biomass
500       !        (inc. the new leaves)
501       WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
502         
503          leaf_frac(:,j,1) = leaf_mass_young(:) / biomass(:,j,ileaf,icarbon)
504
505       ENDWHERE
506
507
508       ! Mass fraction in the other classes is calculated as the ratio bewteen
509       ! the current mass in that age and the total leaf biomass
510       ! (inc. the new leaves)\n
511       DO m = 2, nleafages ! Loop over # leaf age classes
512
513          WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
514
515             leaf_frac(:,j,m) = leaf_frac(:,j,m) * lm_old(:,j) / biomass(:,j,ileaf,icarbon)
516
517          ENDWHERE
518
519       ENDDO ! Loop over # leaf age classes
520
521    ENDDO ! loop over # PFTs
522
523 !! 3. Calculate allocatable fractions of biomass production (NPP)
524     
525    ! Calculate fractions of biomass production (NPP) to be allocated to the different
526    ! biomass components.\n
527    ! The fractions of NPP allocated (0-1, unitless) to the different compartments depend on the
528    ! availability of light, water, and nitrogen.
529    DO j = 2, nvm ! Loop over # PFTs
530
531       ! Reset values
532       RtoLSR(:) = zero
533       LtoLSR(:) = zero
534       StoLSR(:) = zero
535
536       ! For trees, partitioning between above and belowground sapwood biomass is a function
537       ! of age. An older tree gets more allocation to the aboveground sapwoood than a younger tree.
538       ! For the other PFTs it is prescribed.
539       ! ::alloc_min, ::alloc_max and ::demi_alloc are specified in stomate_constants.f90
540       IF ( is_tree(j) ) THEN
541
542          alloc_sap_above(:) = alloc_min(j)+(alloc_max(j)-alloc_min(j))*(un-EXP(-age(:,j)/demi_alloc(j)))
543       
544       ELSE
545         
546          alloc_sap_above(:) = alloc_sap_above_grass
547       
548       ENDIF
549
550
551       !! 3.1 Calculate light stress, water stress and proxy for nitrogen stress.\n
552       !      For the limiting factors a low value indicates a strong limitation
553       WHERE ( biomass(:,j,ileaf,icarbon) .GT. min_stomate )
554
555          !! 3.1.1 Light stress
556          !        Light stress is a function of the mean lai on the natural part of the grid box
557          !        and of the PFT-specific LAI for agricultural crops. In line with the DGVM, natural
558          !        PFTs in the same gridbox are treated as if they were spatially mixed whereas
559          !        agricultural PFTs are considered to be spatially separated.
560          !        The calculation of the lights stress depends on the extinction coefficient (set to 0.5)
561          !        and of a mean LAI.
562          WHERE( lai_around(:,j) < max_possible_lai )
563
564             limit_L(:) = MAX( 0.1_r_std, EXP( -ext_coeff(j) * lai_around(:,j) ) )
565         
566          ELSEWHERE
567             
568             limit_L(:) = 0.1_r_std
569         
570          ENDWHERE
571
572          !! 3.1.2 Water stress
573          !        Water stress is calculated as the weekly moisture availability.
574          !        Weekly moisture availability is calculated in stomate_season.f90.
575          limit_W(:) = MAX( 0.1_r_std, MIN( un, moiavail_week(:,j) ) )
576
577
578          !! 3.1.3 Proxy for nitrogen stress
579          !         The proxy for nitrogen stress depends on monthly soil water availability
580          !         (::soilhum_month) and monthly soil temperature (::tsoil_month). See section
581          !         1.2.2 for details on how ::t_nitrogen and ::h_nitrogen were calculated.\n
582          !         Currently nitrogen-stress is calculated for both natural and agricultural PFTs.
583          !         Due to intense fertilization of agricultural PFTs this is a strong
584          !         assumption for several agricultural regions in the world (US, Europe, India, ...)
585          !         Water stress on nitrogen mineralisation
586          limit_N_hum(:) = MAX( undemi, MIN( un, h_nitrogen(:) ) )
587
588          ! Temperature stress on nitrogen mineralisation using a Q10 decomposition model
589          ! where Q10 was set to 2
590          limit_N_temp(:) = 2.**((t_nitrogen(:) - ZeroCelsius - Nlim_tref )/Nlim_Q10)
591          limit_N_temp(:) = MAX( 0.1_r_std, MIN( un, limit_N_temp(:) ) )
592
593          ! Combine water and temperature factors to get total nitrogen stress
594          limit_N(:) = MAX( 0.1_r_std, MIN( un, limit_N_hum(:) * limit_N_temp(:) ) )
595
596          ! Take the most limiting factor among soil water and nitrogen
597          limit_WorN(:) = MIN( limit_W(:), limit_N(:) )
598
599          ! Take the most limiting factor among aboveground (i.e. light) and belowground
600          ! (i.e. water & nitrogen) limitations
601          limit(:) = MIN( limit_WorN(:), limit_L(:) )
602
603          !! 3.2 Calculate ratio between allocation to leaves, sapwood and roots
604          !      Partitioning between belowground and aboveground biomass components is assumed
605          !      to be proportional to the ratio of belowground and aboveground stresses.\n
606          !      \latexonly
607          !        \input{alloc1.tex}
608          !      \endlatexonly
609          !      Root allocation is the default root allocation corrected by a normalized ratio of aboveground stress to total stress.
610          !      The minimum root allocation is 0.15.
611          RtoLSR(:) = &
612               MAX( .15_r_std, &
613               R0(j) * trois * limit_L(:) / ( limit_L(:) + deux * limit_WorN(:) ) )
614
615          ! Sapwood allocation is the default sapwood allocation corrected by a normalized ratio of belowground stress to total stress.
616          StoLSR(:) = S0(j) * 3. * limit_WorN(:) / ( 2._r_std * limit_L(:) + limit_WorN(:) )
617
618          ! Leaf allocation is calculated as the remaining allocation fraction
619          ! The range of variation of leaf allocation is constrained by ::min_LtoLSR and ::max_LtoLSR.
620          LtoLSR(:) = un - RtoLSR(:) - StoLSR(:)
621          LtoLSR(:) = MAX( min_LtoLSR, MIN( max_LtoLSR, LtoLSR(:) ) )
622
623          ! Roots allocation is recalculated as the residual carbon after leaf allocation has been calculated.
624          RtoLSR(:) = un - LtoLSR(:) - StoLSR(:)
625
626       ENDWHERE
627           
628       ! Check whether allocation needs to be adjusted. If LAI exceeds maximum LAI
629       ! (::lai_max), no addition carbon should be allocated to leaf biomass. Allocation is
630       ! then partioned between root and sapwood biomass.
631       WHERE ( (biomass(:,j,ileaf,icarbon) .GT. min_stomate) .AND. (lai(:,j) .GT. lai_max(j)) )
632
633          StoLSR(:) = StoLSR(:) + LtoLSR(:)
634          LtoLSR(:) = zero
635
636       ENDWHERE
637
638       !! 3.3 Calculate the allocation fractions.
639       !      The allocation fractions (::f_alloc) are an output variable (0-1, unitless). f_alloc
640       !      has three dimensions (npts,nvm,nparts). Where ::npts is the number of grid cells, ::nvm is the
641       !      number of PFTs and ::nparts the number of biomass components. Currently six biomass compartments
642       !      are distinguished: (1) Carbon reserves, (2) Aboveground sapwood, (3) Belowground
643       !      sapwood, (4) Roots, (5) fruits/seeds and (6) Leaves.@tex $(gC m^{-2})$ @endtex \n
644       DO i = 1, npts ! Loop over grid cells
645
646          IF ( biomass(i,j,ileaf,icarbon) .GT. min_stomate ) THEN
647     
648             IF ( senescence(i,j) ) THEN
649               
650                !! 3.3.1 Allocate all C to carbohydrate reserve
651                !        If the PFT is senescent allocate all C to carbohydrate reserve,
652                !        then the allocation fraction to reserves is 1.
653                f_alloc(i,j,icarbres) = un
654
655             ELSE
656
657                !! 3.3.2 Allocation during the growing season 
658                f_alloc(i,j,ifruit) = f_fruit
659
660
661                ! Allocation to the carbohydrate reserve is proportional to leaf and root
662                ! allocation. If carbon is allocated to the carbohydrate reserve, rescaling
663                ! of allocation factors is required to ensure carbon mass preservation.\n
664                ! Carbon is allocated to the carbohydrate reserve when the pool size of the
665                ! reserve is less than the carbon needed to grow a canopy twice the size of
666                ! the maximum LAI (::lai_max). Twice the size was used as a threshold because
667                ! the reserves needs to be sufficiently to grow a canopy and roots. In case
668                ! the carbohydrate pool is full, there is no need to rescale the other
669                ! allocation factors.
670                ! If there is no rescaling of the allocation factors (carbres=1, no carbon put
671                ! to reserve), then fraction remaining after fruit allocation (1-fruit_alloc)
672                ! is distributed between leaf, root and sap (sap carbon also distributed between   
673                ! sap_above and sap_below with factor alloc_sap_above).
674                ! If carbon is allocated to the carbohydrate reserve, all these factors are
675                ! rescaled through carb_rescale, and an allocation fraction for carbohydrate pool
676                ! appears. carb_rescale depends on the parameter (::ecureuil).
677                ! (::ecureuil) is the fraction of primary leaf and root allocation put into
678                ! reserve, it is specified in stomate_constants.f90 and is either 0 or 1.
679                IF ( ( biomass(i,j,icarbres,icarbon)*sla(j) ) .LT. 2*lai_max(j) ) THEN
680                   carb_rescale(i) = un / ( un + ecureuil(j) * ( LtoLSR(i) + RtoLSR(i) ) )
681                ELSE
682                   carb_rescale(i) = un
683                ENDIF
684
685                f_alloc(i,j,ileaf) = LtoLSR(i) * ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
686                f_alloc(i,j,isapabove) = StoLSR(i) * alloc_sap_above(i) * &
687                     ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
688                f_alloc(i,j,isapbelow) = StoLSR(i) * ( un - alloc_sap_above(i) ) * &
689                     ( un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
690                f_alloc(i,j,iroot) = RtoLSR(i) * (un - f_alloc(i,j,ifruit) ) * carb_rescale(i)
691                f_alloc(i,j,icarbres) = ( un - carb_rescale(i) ) * ( un - f_alloc(i,j,ifruit) )
692
693             ENDIF  ! Is senescent?
694
695          ENDIF  ! There are leaves
696
697       ENDDO  ! Loop over # pixels - domain size
698
699    ENDDO  ! loop over # PFTs
700
701    IF (printlev>=3) WRITE(numout,*) 'Leaving alloc'
702
703  END SUBROUTINE alloc
704
705END MODULE stomate_alloc
Note: See TracBrowser for help on using the repository browser.