source: branches/publications/ORCHIDEE_CAN_r3069/src_stomate/stomate_resp.f90 @ 7475

Last change on this file since 7475 was 2609, checked in by josefine.ghattas, 9 years ago

Correction for compiling with OpenMP:

  • !$OMP THREADPRIVATE should not be set on a variable declared PARAMETER
  • Lines beginning with !$ are interpreted as OMP directive. Change to !
  • Some variables were not correcte in OMP THREADPRIVATE statement

Update src_xml directory with trunk version rev 2605

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 28.8 KB
Line 
1! =================================================================================================================================
2! MODULE           : stomate_resp
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           Calculates maintenance respiration for different plant components
10!!
11!!\n DESCRIPTION   : None
12!!
13!! RECENT CHANGE(S): None
14!!
15!! REFERENCE(S)    :
16!!- McCree KJ. An equation for the respiration of white clover plants grown under controlled conditions.
17!! In: Setlik I, editor. Prediction and measurement of photosynthetic productivity. Wageningen, The Netherlands:
18!! Pudoc; 1970. p. 221-229.
19!! - Krinner G, Viovy N, de Noblet-Ducoudre N, Ogee J, Polcher J, Friedlingstein P,
20!! Ciais P, Sitch S, Prentice I C (2005) A dynamic global vegetation model for studies
21!! of the coupled atmosphere-biosphere system. Global Biogeochemical Cycles, 19, GB1015,
22!! doi: 10.1029/2003GB002199.\n
23!! Ruimy A., Dedieu G., Saugier B. (1996), TURC: A diagnostic model
24!! of continental gross primary productivity and net primary productivity,
25!! Global Biogeochemical Cycles, 10, 269-285.\n
26
27!! SVN :
28!! $HeadURL$
29!! $Date$
30!! $Revision$
31!! \n
32!_ ================================================================================================================================
33 
34MODULE stomate_resp
35
36  ! modules used:
37  USE stomate_data
38  USE pft_parameters
39  USE constantes 
40  USE constantes_soil
41  USE function_library, ONLY : biomass_to_lai
42
43  IMPLICIT NONE
44
45  ! private & public routines
46  PRIVATE
47  PUBLIC maint_respiration,maint_respiration_clear
48
49  LOGICAL, SAVE                                              :: firstcall = .TRUE.                 !! first call
50!$OMP THREADPRIVATE(firstcall)
51
52  CONTAINS
53
54
55!! ================================================================================================================================
56!! SUBROUTINE   : maint_respiration_clear
57!!
58!>\BRIEF        : Set the flag ::firstcall to .TRUE. and as such activate section
59!!                1.1 of the subroutine maint_respiration (see below).
60!_ ================================================================================================================================
61
62  SUBROUTINE maint_respiration_clear
63    firstcall=.TRUE.
64  END SUBROUTINE maint_respiration_clear
65
66
67!! ================================================================================================================================
68!! SUBROUTINE   : maint_respiration
69!!
70!>\BRIEF         Calculate PFT maintenance respiration of each living plant part by
71!! multiplying the biomass of plant part by maintenance respiration coefficient which
72!! depends on long term mean annual temperature. PFT maintenance respiration is carbon flux
73!! with the units @tex $(gC.m^{-2}dt^{-1})$ @endtex, and the convention is from plants to the
74!! atmosphere.
75!!
76!! DESCRIPTION : The maintenance respiration of each plant part for each PFT is the biomass of the plant
77!! part multiplied by maintenance respiration coefficient. The biomass allocation to different
78!! plant parts is done in routine stomate_alloc.f90. The maintenance respiration coefficient is
79!! calculated in this routine.\n
80!!
81!! The maintenance respiration coefficient is the fraction of biomass that is lost during
82!! each time step, which increases linearly with temperature (2-meter air temperature for aboveground plant
83!! tissues; root-zone temperature for below-ground tissues). Air temperature is an input forcing variable.
84!! Root-zone temperature is a convolution of root and soil temperature profiles and also calculated
85!! in this routine.\n
86!!
87!! The calculation of maintenance respiration coefficient (fraction of biomass respired) depends linearly
88!! on temperature:
89!! - the relevant temperature for different plant parts (air temperature or root-zone temperature)\n
90!! - intercept: prescribed maintenance respiration coefficients at 0 Degree Celsius for
91!!   different plant parts for each PFT in routine stomate_constants.f90\n
92!! - slope: calculated with a quadratic polynomial with the multi-annual mean air temperature
93!! (the constants are in routine stomate_constants.f90) as follows\n
94!!    \latexonly
95!!      \input{resp3.tex}
96!!    \endlatexonly
97!!   Where, maint_resp_slope1, maint_resp_slope2, maint_resp_slope3 are constant in stomate_constants.f90.
98!!   Then coeff_maint is calculated as follows:\n
99!!    \latexonly
100!!      \input{resp4.tex}
101!!    \endlatexonly 
102!! If the calculation result is negative, maintenance respiration coefficient will take the value 0.
103!! Therefore the maintenance respiration will also be 0.\n
104!!
105!! RECENT CHANGE(S): None
106!!
107!! MAIN OUTPUT VARIABLE(S): PFT maintenance respiration of different plant parts (::resp_maint_part_radia)
108!!
109!! REFERENCE(S) :
110!! McCree KJ. An equation for the respiration of white clover plants grown under controlled conditions. In:
111!! Setlik I, editor. Prediction and measurement of photosynthetic productivity. Wageningen,
112!! The Netherlands: Pudoc; 1970. p. 221-229.
113!! Krinner G, Viovy N, de Noblet-Ducoudre N, Ogee J, Polcher J, Friedlingstein P,
114!! Ciais P, Sitch S, Prentice I C (2005) A dynamic global vegetation model for studies
115!! of the coupled atmosphere-biosphere system. Global Biogeochemical Cycles, 19, GB1015,
116!! doi: 10.1029/2003GB002199.\n
117!! Ruimy A., Dedieu G., Saugier B. (1996), TURC: A diagnostic model
118!! of continental gross primary productivity and net primary productivity,
119!! Global Biogeochemical Cycles, 10, 269-285.\n
120!! FLOWCHART    : None
121!! \n
122!_ ================================================================================================================================
123
124  SUBROUTINE maint_respiration (npts, dt, t2m, tlong_ref, &
125       stempdiag, gpp, gpp_week, lab_fac, &
126       veget_max, rprof, biomass, resp_maint_part_radia, &
127       circ_class_n, circ_class_biomass)
128
129!! 0. Variable and parameter declaration
130
131    !! 0.1 Input variables
132
133    INTEGER(i_std), INTENT(in)                      :: npts         !! Domain size - number of grid cells (unitless)
134    REAL(r_std), INTENT(in)                         :: dt           !! Time step of the simulations (seconds)
135    REAL(r_std), DIMENSION(:), INTENT(in)           :: t2m          !! 2 meter air temperature - forcing variable (K)
136    REAL(r_std), DIMENSION(:), INTENT(in)           :: tlong_ref    !! Long term annual mean 2 meter reference air temperatures
137                                                                    !! calculated in stomate_season.f90 (K)
138    REAL(r_std), DIMENSION(:,:), INTENT (in)        :: stempdiag    !! Soil temperature of each soil layer (K)
139    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: gpp          !! Gross primary production per day per unit PFT
140                                                                    !! @tex $ (gC m^{-2} dt^{-1})$ @endtex
141    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: gpp_week     !! Weekly mean gross primary production per day per unit PFT
142                                                                    !! @tex $ (gC m^{-2} dt^{-1})$ @endtex
143    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: veget_max    !! PFT "maximal" coverage fraction of a PFT (unitless)
144    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: rprof        !! PFT root depth as calculated in stomate.f90 from parameter
145                                                                    !! humcste which is root profile for different PFTs
146                                                                    !! in slowproc.f90 (m)
147    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: lab_fac      !! Activity of labile pool (??UNITS??)
148    REAL(r_std), DIMENSION(:,:,:), INTENT(in)       :: circ_class_n !! Number of individuals in each circ class
149                                                                    !! @tex $(ind m^{-2})$ @endtex
150
151    !! 0.2 Output variables
152
153    REAL(r_std), DIMENSION(:,:,:), INTENT(out)      :: resp_maint_part_radia !! PFT maintenance respiration of different
154                                                                    !! plant parts @tex $(gC.m^{-2}dt^{-1} )$ @endtex
155
156    !! 0.3 Modified variables
157   
158    REAL(r_std), DIMENSION(:,:,:,:),  INTENT(inout) :: biomass      !! PFT total biomass calculated in stomate_alloc.f90
159                                                                    !! @tex $(gC.m^{-2})$ @endtex
160    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(inout):: circ_class_biomass !! Biomass components of the model tree 
161                                                                    !! within a circumference class
162                                                                    !! class @tex $(g C ind^{-1})$ @endtex
163    !! 0.4 Local variables
164
165    REAL(r_std), DIMENSION(npts,nvm)        :: lai                  !! PFT leaf area index @tex $(m^2 m^{-2})$ @endtex
166    INTEGER(i_std)                          :: ipts,ivm,ipar,ibdl   !! Indeces (unitless)
167    REAL(r_std), SAVE, DIMENSION(0:nbdl)    :: z_soil               !! Variable to store depth of the different soil layers (m)
168!$OMP THREADPRIVATE(z_soil)
169    REAL(r_std), DIMENSION(npts,nvm)        :: t_root               !! PFT root temperature (convolution of root and soil
170                                                                    !! temperature profiles) (K)
171    REAL(r_std), DIMENSION(npts,nvm,nparts) :: coeff_maint          !! PFT maintenance respiration coefficients of different
172                                                                    !! plant compartments at 0 deg C
173                                                                    !! @tex $(g.g^{-1}dt^{-1})$ @endtex
174    REAL(r_std), DIMENSION(npts,nparts)     :: t_maint_radia        !! Temperature which is pertinent for maintenance respiration,
175                                                                    !! which is air/root temperature for above/below-ground
176                                                                    !! compartments (K)
177    REAL(r_std), DIMENSION(nvm,nparts)      :: fcn                  !! C/N ratio in tissue (unitless)
178    REAL(r_std), DIMENSION(npts,nvm)        :: resp_maint_demand    !! Rate of maintanance respiration
179                                                                    !! @tex $(gC.dt^{-1})$ @endtex
180    REAL(r_std), DIMENSION(npts,nvm)        :: resp_maint_supply    !! Rate of growth respiration
181                                                                    !! @tex $(gC.dt^{-1})$ @endtex                                 
182    REAL(r_std), DIMENSION(npts,nvm)        :: resp_maint           !! Effective rate of maintanance respiration
183                                                                    !! @tex $(gC.dt^{-1})$ @endtex   
184    REAL(r_std), DIMENSION(npts)            :: gtemp                !! Temperature response of respiration in the
185                                                                    !! Lloyd-Taylor Model (K)
186    REAL(r_std), DIMENSION(npts)            :: tl                   !! Long term reference temperature in degrees Celcius
187                                                                    !! (= tlong_ref - 273.15) (C)
188    REAL(r_std), DIMENSION(npts)            :: slope                !! slope of the temperature dependence of maintenance
189                                                                    !! respiration coefficient (1/K)
190    REAL(r_std), DIMENSION(npts)            :: rpc                  !! Scaling factor for integrating vertical soil
191                                                                    !! profiles (unitless)
192    REAL(r_std), DIMENSION(nvm)             :: coeff_maint_temp     !! PFT maintenance respiration coefficients of different
193                                                                    !! plant compartments at 0 deg C
194                                                                    !! @tex $(g.g^{-1}dt^{-1})$ @endtex
195    REAL(r_std)                             :: deficit              !! Calculate maintenance respiration based on
196                                                                    !! tissue pools (or labile pool size) (??UNIT??)
197    REAL(r_std)                             :: limit_cn             !! Calculate maintenance respiration based on
198                                                                    !! tissue pools (or labile pool size) (??UNIT??)
199    REAL(r_std)                             :: temp_share           !! Temporary variable to store the share
200                                                                    !! of biomass of each circumference class
201                                                                    !! to the total biomass           
202    REAL(r_std)                             :: temp_class_biomass   !! Biomass across parts for a single circ
203                                                                    !! class @tex $(gC m^{-2})$ @endtex
204    REAL(r_std)                             :: temp_total_biomass   !! Biomass across parts and circ classes
205                                                                    !! @tex $(gC m^{-2})$ @endtex
206    REAL(r_std)                             :: temp                 !! generic temporary variable
207
208   !! 0.5 Externalize
209   REAL(r_std), PARAMETER                   :: gtemp_ref=1.6        !! Correction factor for respiration calculation,
210                                                                    !! since ORCHIDEE maintenance respiration rates
211                                                                    !! refer to zero degrees but Lloyd and Taylor assumes
212                                                                    !! base temperature of 10 degrees (unitless)
213       
214!_ ================================================================================================================================
215   
216   
217    IF (bavard.GE.4) WRITE(numout,*) 'Entering maintenance respiration'
218   
219 !! 1. Initializations
220   
221    IF ( firstcall ) THEN
222
223       !! 1.1. Soil levels (first call only)
224       !       Set the depth of the different soil layers (number of layers: nbdl)
225       !       previously calculated as variable diaglev in routines sechiba.f90 and slowproc.f90
226       z_soil(0) = zero
227       z_soil(1:nbdl) = diaglev(1:nbdl)
228
229       ! Set first call to false for all subsequent calls
230       firstcall = .FALSE.
231
232    ENDIF
233
234   
235    !! 1.2. Calculate root temperature
236    !       Calculate root temperature as the convolution of root and soil temperature profiles
237    DO ivm = 2,nvm ! Loop over # PFTs
238
239       !! 1.2.1 Calculate rpc
240       !  - rpc is an integration constant to make the integral over the root profile is equal 'one',
241       !    calculated as follows:\n
242       !  \latexonly
243       !    \input{resp1.tex}
244       !  \endlatexonly
245       rpc(:) = un / ( un - EXP( -z_soil(nbdl) / rprof(:,ivm) ) )
246
247       !! 1.2.2 Calculate root temperature
248       !        - Integrate root profile temperature (K) over soil layers (number of layers = nbdl)
249       !          with rpc and soil temperature (K) of each soil layer as follows:\n
250       !        \latexonly
251       !          \input{resp2.tex}
252       !        \endlatexonly
253       !        Where, stempdiag is diagnostic temperature profile of soil (K)\n
254       t_root(:,ivm) = zero
255
256       DO ibdl = 1, nbdl ! Loop over # soil layers
257
258          t_root(:,ivm) = &
259               t_root(:,ivm) + stempdiag(:,ibdl) * rpc(:) * &
260               ( EXP( -z_soil(ibdl-1)/rprof(:,ivm) ) - EXP( -z_soil(ibdl)/rprof(:,ivm) ) )
261
262       ENDDO ! Loop over # soil layers
263
264    ENDDO ! Loop over # PFTs
265
266 !! 2. Define maintenance respiration coefficients
267
268    DO ivm = 2,nvm ! Loop over # PFTs
269
270       !! 2.1 Temperature for maintenanace respiration
271       !      Temperature which is used to calculate maintenance respiration for different plant compartments
272       !      (above- and belowground)\n
273       !      - for aboveground parts, we use 2-meter air temperature, t2m\n
274       !      - for belowground parts, we use root temperature calculated in section 1.2 of this subroutine\n
275       
276       ! 2.1.1 Aboveground biomass
277       t_maint_radia(:,ileaf) = t2m(:)
278       t_maint_radia(:,isapabove) = t2m(:)
279       t_maint_radia(:,ifruit) = t2m(:)
280
281       ! 2.1.2 Belowground biomass
282       t_maint_radia(:,isapbelow) = t_root(:,ivm)
283       t_maint_radia(:,iroot) = t_root(:,ivm)
284
285       !! 2.1.3 Heartwood biomass
286       !  Heartwood does does not respire (coeff_maint_zero is set to zero).
287       !  Any temperature could have been set 
288       !  [code cleaning: set t(heartwood) to undef to 'undef']
289
290       t_maint_radia(:,iheartbelow) = t_root(:,ivm)
291       t_maint_radia(:,iheartabove) = t2m(:)
292
293       !! 2.1.4 Reserve biomass
294       !  Use aboveground temperature for trees and belowground temeperature for grasses
295       IF ( is_tree(ivm) ) THEN
296
297          t_maint_radia(:,icarbres) = t2m(:)
298
299       ELSE
300
301          t_maint_radia(:,icarbres) = t_root(:,ivm)
302
303       ENDIF
304
305       !! 2.1.5 Labile biomass pool
306       !  Use aboveground temperature for the labile biomass pool
307       t_maint_radia(:,ilabile) = t2m(:)
308       
309       !! 2.2 Calculate maintenance respiration coefficients (coeff_maint)
310       !  Maintenance respiration is a fraction of biomass defined by the coefficient
311       !  coeff_maint [Mc Cree, 1969]. Coeff_maint is defined through a linear relationship of temperature [Ruimy et al, 1996]
312       !  which slope is the coefficient 'slope' and which intercept is 'coeff_maint_zero'.
313       !  - Coeff_maint_zero is defined in stomate_data to cm_zero_plantpartname
314       !  - Slope is calculated here through a second-degree polynomial [Krinner et al, 2005]
315       !  equation that makes it dependent on the long term temperature (to represent adaptation
316       !  of the ecosystem to long term temperature).
317       !   \latexonly
318       !    \input{resp3.tex}
319       !   \endlatexonly
320       !  Where, maint_resp_slope1, maint_resp_slope2, maint_resp_slope3 are constant in stomate_constants.f90.
321       !  Then coeff_maint is calculated as follows:\n
322       !   \latexonly
323       !    \input{resp4.tex}
324       !   \endlatexonly
325       !  If the calculation result is negative, coeff_maint will take the value 0.\n   
326       tl(:) = tlong_ref(:) - ZeroCelsius
327       slope(:) = maint_resp_slope(ivm,1) + tl(:) * maint_resp_slope(ivm,2) + &
328            tl(:)*tl(:) * maint_resp_slope(ivm,3)
329
330       DO ipar = 1, nparts ! Loop over # plant parts
331
332          ! Resource-based allocation       
333          IF ( .NOT.control%ok_functional_allocation ) THEN
334
335            coeff_maint(:,ivm,ipar) = MAX( (coeff_maint_zero(ivm,ipar)*dt/one_day) * &
336                 ( un + slope(:) * (t_maint_radia(:,ipar)-ZeroCelsius) ), zero ) 
337
338         ! Allometric-based allocation   
339         ELSE
340
341            !+++CHECK+++
342            ! The original code refers to the Sitch et al 2003 as the source of the equations and parameters
343            ! for modelling maintenance respiration. The equations below are consistent with the paper. The
344            ! parameter setting for coeff_maint is in the range of 0.066 to 0.011 as reported in the paper but
345            ! exact values are not given. Although, the principle of a climate correction for coeff_maint is
346            ! mentioned in Sitch et al 2003, the reduction factors themselves were not given. As it appears
347            ! now this block of code pretends much more knowledge then we actually have. Rather than using a
348            ! baseline coeff_maint that is later corrected for the climate region, the parameter values for
349            ! coeff_maint could be simply prescribed and made pft-specific.
350            ! Further down in the code C/N ratios are used to constrain respiration. The C/N ratios were reset
351            ! to the values presented in Sitch et al 2003 but still seem on the low side. If pft-specific
352            ! values are to be used, changes in respiration could be compensated for by changing
353            ! coeff_maint_init. Given Vicca et al 2012 (Ecology Letters) an NPP/GPP ratio of 0.5 is 'universal'
354            ! for forests given a sufficient nutrient supply and strictly defining NPP as solely its biomass
355            ! components (thus excluding VOC, exudation and subsidies to myccorrhizae as is the case in ORCHIDEE).
356            ! Unless observation based values are available for coeff_maint_init, these values could be adjusted
357            ! within the range of 0.066 to 0.011 to obtain an NPP/GPP of 0.5 in the absence of nutrient
358            ! limitations.
359               
360            ! LPJ respiration factors based on Sitch et al. 2003 - first part of the calculation
361            IF ( ipar.EQ.ileaf .OR. ipar.EQ.iroot .OR. ipar.EQ.ifruit .OR. &
362                 ipar.EQ.isapabove .OR. ipar.EQ.isapbelow .OR. ipar.EQ.ilabile) THEN
363               
364               ! Sonke uses
365               !coeff_maint(:,ivm,ipar) = 0.0548
366
367               ! The Sitch et al 2003 paper gives a value of 0.066 (Table 3) and 0.011 for tropical systems
368               !coeff_maint(:,ivm,ipar) = 0.066
369 
370               ! Use an effective PFT-specific value - this value has been optimized
371               ! to reproduce observed NPP/GPP ratios
372               coeff_maint(:,ivm,ipar) = coeff_maint_init(ivm)
373
374            ! heartwood and reserves pool   
375            ELSE
376
377               coeff_maint(:,ivm,ipar) = zero
378
379            ENDIF
380
381            !+++BEGIN+DELETE+++
382            ! Correction for climate region.
383            ! [remove hard coding]
384            ! Respiration rates for tropical forests
385            !IF ( ivm.LE.3 ) THEN
386               
387               ! Sonke uses
388               ! coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar)*0.33
389     
390               ! The Sitch et al 2003 paper
391               !coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar)/6.
392
393            ! Respiration rates for tropical grass and crops
394            !ELSEIF ( ivm.EQ.11 .OR. ivm.EQ.13 ) THEN
395               
396               ! Sonke uses
397               !coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar)*0.5
398               
399               ! The Sitch et al 2003 paper
400               !coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar) / 6.
401 
402            ! Respiration rates for boreal and temperate PFTs
403            !ELSE
404
405               ! Sonke uses
406               ! coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar)*0.7
407               
408               ! The Sitch et al 2003 paper - value should not be adjusted
409               !coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar)
410               !coeff_maint(:,ivm,ipar) = coeff_maint(:,ivm,ipar)*0.5
411
412            !ENDIF
413            !+++END+DELETE+++
414
415         ENDIF ! .NOT.control%ok_functional_allocation
416
417       ENDDO ! Loop over # plant parts
418     
419       
420       !+++OCN-code+++
421!       ! Calculate lai
422!       lai(:,ivm) = biomass(:,ivm,ileaf,icarbon) * sla(ivm)
423
424!       ! Leaf respiration for photosynthesis according to Friend et al. as in Zaehle et al.
425!       ! Leaf respiration is calculated in diffuco.f90
426!       IF ( control%ok_cexchange ) THEN
427!          coeff_maint_leaf(:,ivm,:) = zero
428       
429!       ! Leaf respiration for the standard ORCHIDEE photosynthesis
430!       ELSE
431!          WHERE ( (biomass(:,ivm,ileaf,icarbon) .GT. min_stomate) .AND. (lai(:,ivm) .GT. min_stomate) )
432!           
433!             coeff_maint_leaf(:,ivm,1) = coeff_maint_zero(ivm,ileaf) * biomass(:,ivm,ileaf,icarbon) * &
434!                  ( maint_resp_min_vmax*lai(:,ivm) + maint_resp_coeff*(un-exp(-ext_coeff(ivm)*lai(:,ivm))) ) &
435!                  / lai(:,ivm) / one_day
436!           
437!             coeff_maint_leaf(:,ivm,2) = slope(:)
438!           
439!          ELSEWHERE
440             
441!              coeff_maint_leaf(:,ivm,1) = zero
442!              coeff_maint_leaf(:,ivm,2) = zero
443             
444!          ENDWHERE
445         
446!       ENDIF ! control%ok_cexchange
447       !++++++++++
448
449    ENDDO ! Loop over # PFTs
450       
451
452 !! 3. Calculate maintenance respiration
453
454    ! Resource-based allocation
455    IF ( .NOT.control%ok_functional_allocation ) THEN
456
457       ! The maintenance respiration @tex $(gC.m^{-2}dt^{-1})$ @endtex of each plant compartment for each PFT is
458       ! the biomass @tex $(gC.m^{-2})$ @endtex of the plant part multiplied by maintenance respiration
459       ! coefficient @tex $(g.g^{-1}dt^{-1})$ @endtex, except that the maintenance respiration of leaves is
460       ! corrected by leaf area index (LAI) as follows:\n
461       ! \latexonly     
462       !   \input{resp5.tex}
463       ! \endlatexonly
464   
465       ! ibare_sechiba = 1, which means the there is only bare soil but not any PFT, consequently no LAI and
466       ! no  maintenance respiration
467       lai(:,ibare_sechiba) = zero
468       resp_maint_part_radia(:,ibare_sechiba,:) = zero
469   
470       ! 3.1 Maintenance respiration of the different plant parts
471       DO ivm = 2,nvm ! Loop over # PFTs
472         
473          ! Calculate lai
474          DO ipts = 1,npts
475
476             lai(ipts,ivm) = biomass_to_lai(biomass(ipts,ivm,ileaf,icarbon),ivm)
477
478          ENDDO
479
480       DO ipar = 1, nparts ! Loop over # plant parts
481
482             ! Leaf respiration: depends on leaf mass and LAI
483             IF ( ipar .EQ. ileaf ) THEN
484
485                WHERE ( (biomass(:,ivm,ileaf,icarbon).GT.min_stomate) .AND. (lai(:,ivm).GT.min_stomate) )
486
487                   ! Maintenance respiration is calculated as a fraction of biomass as defined by coeff_maint
488                   ! and is adjusted for the nitrogen effect through a third factor depending on LAI. The
489                   ! hypothesis here is that the vcmax (i.e. the nitrogen distribution) in the canopy decreases
490                   ! exponentially with LAI following the Beer-Lambert law with an asymptote defining the
491                   ! minimum of the function at 30% of the LAI. The 1.4 parameter is an integration constant.
492                   ! This method is also used in diffuco_trans_co2 2.4.1 for scaling vmax based on nitrogen
493                   ! reduction in the canopy.
494                   resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * biomass(:,ivm,ipar,icarbon) * &
495                        ( maint_resp_min_vmax*lai(:,ivm) + maint_resp_coeff*(un - exp(-ext_coeff(ivm)*lai(:,ivm))) ) / lai(:,ivm)
496
497                ELSEWHERE
498
499                   resp_maint_part_radia(:,ivm,ileaf) = zero
500
501                ENDWHERE
502
503             ! All other components
504             ELSE
505
506                ! All components except ileaves and ilabile
507                IF ( ipar.NE.ilabile ) THEN
508
509                   resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * biomass(:,ivm,ipar,icarbon)
510
511                ! Respiration for ilabile
512                ELSE
513
514                   resp_maint_part_radia(:,ivm,ilabile) = zero
515
516                ENDIF !ipar.NE.ilabile
517
518             ENDIF !ipar.EQ.ileaf
519
520          ENDDO ! Loop over # plant parts
521
522       ENDDO ! Loop over # PFTs
523
524    ! Allometric-based allocation
525    ELSE
526 
527       ! In the allometric based allocation scheme, maintentance respiration is calculated
528       ! the minimum of supply and demand
529       resp_maint_part_radia(:,:,:) = zero
530     
531       DO ivm = 2,nvm ! Loop over # PFTs
532
533          ! Demand based respiration
534          resp_maint_demand(:,ivm) = 0.0
535
536          DO ipar = 1, nparts ! Loop over # plant parts 
537           
538             ! LPJ respiration factors based on Sitch et al. 2003 - second part of the calculation
539             ! Temperature response, LLoyd and Taylor, 1994. E0 = 308.56 comes from the paper of
540             ! Lloyd and Taylor but was fitted for soil respiration which only partly consists of
541             ! authotrophic (root) respiration.   
542             WHERE(t_maint_radia(:,ipar)-ZeroCelsius.GT.-46.01)
543
544                gtemp(:) = dt/one_day * & 
545                    EXP(308.56*(1.0/56.02-1.0/(t_maint_radia(:,ipar)-ZeroCelsius+46.02)))
546
547             ! No gtemp below -46.01 degrees Celsius
548             ELSEWHERE
549
550                gtemp(:) = 0.0
551
552             ENDWHERE           
553           
554             ! Calculate the limiting C/N ratio
555             IF ( ipar.EQ.ileaf ) THEN
556
557                limit_cn = cn_leaf_prescribed(ivm)
558
559             ELSEIF ( ipar.EQ.iroot .OR. ipar.EQ.ifruit ) THEN
560
561                limit_cn = cn_leaf_prescribed(ivm)/fcn_root(ivm)
562
563             ELSEIF ( ipar.EQ.isapabove .OR. ipar.EQ.isapbelow ) THEN
564
565                limit_cn = cn_leaf_prescribed(ivm)/fcn_wood(ivm)
566
567             ELSE
568
569                limit_cn = cn_leaf_prescribed(ivm)
570
571             ENDIF
572           
573             !---TEMP---
574             !IF (ivm.EQ.test_pft) THEN 
575             !   WRITE(numout,*) 'limit - ipar, temp output,', ipar, limit_cn
576             !ENDIF
577             !----------
578
579             resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * gtemp(:) * & 
580                    biomass(:,ivm,ipar,icarbon) / limit_cn
581             resp_maint_demand(:,ivm) = resp_maint_demand(:,ivm) + resp_maint_part_radia(:,ivm,ipar)
582
583          ENDDO ! Loop over # plant parts
584
585       ENDDO ! Loop over # PFTs
586   
587    ENDIF ! .NOT.control%ok_functional_allocation
588
589    IF (bavard.GE.4) WRITE(numout,*) 'Leaving maintenance respiration'
590
591  END SUBROUTINE maint_respiration
592
593END MODULE stomate_resp
Note: See TracBrowser for help on using the repository browser.