source: branches/publications/ORCHIDEE_CN_CAN_r5698/src_stomate/stomate_resp.f90 @ 7346

Last change on this file since 7346 was 5691, checked in by sebastiaan.luyssaert, 6 years ago

DEV: tested with 13, 37 and 64 PFTs with LCC on different pixels. Some configuration run for 20 years on a given pixel, other crash on another pixel. There is a mass balance problem in sapiens_lcc (ticket #482). This commit fixes a problem with PFT1 in littercalc. This PFT is now fully integrated in LCC and subsequent litter and soil dynamics. veget_max was changed in veget_cov_max where appropriate, a typo in enerbil was corrected.

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 24.4 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_resp = .TRUE.                 !! first call
50!$OMP THREADPRIVATE(firstcall_resp)
51
52  CONTAINS
53
54
55!! ================================================================================================================================
56!! SUBROUTINE   : maint_respiration_clear
57!!
58!>\BRIEF        : Set the flag ::firstcall_resp 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_resp=.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_sechiba^{-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_cov_max, rprof, 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(npts), 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!++++CHECK++++
140! gpp and gpp_week are not used in the code
141! They can perhaps be removed
142    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: gpp          !! Gross primary production per day per unit PFT
143                                                                    !! @tex $ (gC m^{-2} dt^{-1})$ @endtex
144    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: gpp_week     !! Weekly mean gross primary production per day per unit PFT
145                                                                    !! @tex $ (gC m^{-2} dt^{-1})$ @endtex
146!++++++++++++
147    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: veget_cov_max    !! PFT "maximal" coverage fraction of a PFT (unitless)
148    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: rprof        !! PFT root depth as calculated in stomate.f90 from parameter
149                                                                    !! humcste which is root profile for different PFTs
150                                                                    !! in slowproc.f90 (m)
151    REAL(r_std), DIMENSION(:,:), INTENT(in)         :: lab_fac      !! Activity of labile pool (??UNITS??)
152    REAL(r_std), DIMENSION(:,:,:), INTENT(in)       :: circ_class_n !! Number of individuals in each circ class
153                                                                    !! @tex $(ind m^{-2})$ @endtex
154    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)   :: circ_class_biomass !! Biomass components of the model tree 
155                                                                    !! within a circumference class
156                                                                    !! class @tex $(g C ind^{-1})$ @endtex
157    !! 0.2 Output variables
158
159    REAL(r_std), DIMENSION(:,:,:), INTENT(out)      :: resp_maint_part_radia !! PFT maintenance respiration of different
160                                                                    !! plant parts @tex $(gC.m^{-2}dt^{-1} )$ @endtex
161
162    !! 0.3 Modified variables
163   
164 
165    !! 0.4 Local variables
166
167    REAL(r_std), DIMENSION(npts,nvm)        :: lai                  !! PFT leaf area index @tex $(m^2 m^{-2})$ @endtex
168    INTEGER(i_std)                          :: ipts,ivm,ipar,ibdl   !! Indeces (unitless)
169    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)    :: z_soil       !! Variable to store depth of the different soil layers (m)
170!$OMP THREADPRIVATE(z_soil)
171    REAL(r_std), DIMENSION(npts,nvm)        :: t_root               !! PFT root temperature (convolution of root and soil
172                                                                    !! temperature profiles) (K)
173    REAL(r_std), DIMENSION(npts,nvm,nparts) :: coeff_maint          !! PFT maintenance respiration coefficients of different
174                                                                    !! plant compartments at 0 deg C
175    REAL(r_std), DIMENSION(npts,nparts)     :: t_maint_radia        !! Temperature which is pertinent for maintenance respiration,
176                                                                    !! which is air/root temperature for above/below-ground
177                                                                    !! compartments (K)
178    REAL(r_std), DIMENSION(nvm,nparts)      :: fcn                  !! C/N ratio in tissue (unitless)
179    REAL(r_std), DIMENSION(npts,nvm)        :: resp_maint_demand    !! Rate of maintanance respiration
180                                                                    !! @tex $(gC.dt^{-1})$ @endtex
181    REAL(r_std), DIMENSION(npts,nvm)        :: resp_maint_supply    !! Rate of growth respiration
182                                                                    !! @tex $(gC.dt^{-1})$ @endtex                                 
183    REAL(r_std), DIMENSION(npts,nvm)        :: resp_maint           !! Effective rate of maintanance respiration
184                                                                    !! @tex $(gC.dt^{-1})$ @endtex   
185    REAL(r_std), DIMENSION(npts)            :: tl                   !! Long term reference temperature in degrees Celcius
186                                                                    !! (= tlong_ref - 273.15) (C)
187    REAL(r_std), DIMENSION(npts)            :: slope                !! slope of the temperature dependence of maintenance
188                                                                    !! respiration coefficient (1/K)
189    REAL(r_std), DIMENSION(npts)            :: rpc                  !! Scaling factor for integrating vertical soil
190                                                                    !! profiles (unitless)
191    REAL(r_std), DIMENSION(nvm)             :: coeff_maint_temp     !! PFT maintenance respiration coefficients of different
192                                                                    !! plant compartments at 0 deg C
193                                                                    !! @tex $(g.g^{-1}dt^{-1})$ @endtex
194    REAL(r_std)                             :: deficit              !! Calculate maintenance respiration based on
195                                                                    !! tissue pools (or labile pool size) (??UNIT??)
196    REAL(r_std)                             :: temp_share           !! Temporary variable to store the share
197                                                                    !! of biomass of each circumference class
198                                                                    !! to the total biomass           
199    REAL(r_std)                            :: temp_class_biomass    !! Biomass across parts for a single circ
200                                                                    !! class @tex $(gC m^{-2})$ @endtex
201    REAL(r_std)                             :: temp_total_biomass   !! Biomass across parts and circ classes
202                                                                    !! @tex $(gC m^{-2})$ @endtex
203    REAL(r_std)                             :: temp                 !! generic temporary variable
204    REAL(r_std), DIMENSION(npts,nvm)        :: gtemp                !! Temperature response of respiration in the
205                                                                    !! Lloyd-Taylor Model (-)
206    REAL(r_std), DIMENSION(npts)            :: cn                   !! CN ratio of a biomass pool ((gC)(gN)-1)
207    REAL(r_std)                             :: limit_cn             !! Calculate limiting C/N ratio ((gC)(gN)-1)
208    INTEGER(i_std)                          :: ier                  !! Error handling
209
210   !! 0.5 Externalize
211   REAL(r_std), PARAMETER                   :: gtemp_ref=1.6        !! Correction factor for respiration calculation,
212                                                                    !! since ORCHIDEE maintenance respiration rates
213                                                                    !! refer to zero degrees but Lloyd and Taylor assumes
214                                                                    !! base temperature of 10 degrees (unitless)
215       
216!_ ================================================================================================================================
217       
218    IF (printlev>=3) WRITE(numout,*) 'Entering maintenance respiration'
219   
220 !! 1. Initializations
221   
222    IF ( firstcall_resp ) THEN
223
224       !! 1.1. Soil levels (first call only)
225       !       Set the depth of the different soil layers (number of layers: nbdl)
226       !       previously calculated as variable diaglev in routines sechiba.f90 and slowproc.f90
227       ALLOCATE(z_soil(0:nbdl), stat=ier)
228       IF ( ier /= 0 ) CALL ipslerr_p(3,'maint_respiration','Pb in allocate of z_soil','','')
229       z_soil(0) = zero
230       z_soil(1:nbdl) = diaglev(1:nbdl)
231
232       ! Set first call to false for all subsequent calls
233       firstcall_resp = .FALSE.
234
235    ENDIF
236
237   
238    !! 1.2. Calculate root temperature
239    !       Calculate root temperature as the convolution of root and soil temperature profiles
240    DO ivm = 2,nvm ! Loop over # PFTs
241
242       !! 1.2.1 Calculate rpc
243       !  - rpc is an integration constant to make the integral over the root profile is equal 'one',
244       !    calculated as follows:\n
245       !  \latexonly
246       !    \input{resp1.tex}
247       !  \endlatexonly
248       rpc(:) = un / ( un - EXP( -z_soil(nbdl) / rprof(:,ivm) ) )
249
250       !! 1.2.2 Calculate root temperature
251       !        - Integrate root profile temperature (K) over soil layers (number of layers = nbdl)
252       !          with rpc and soil temperature (K) of each soil layer as follows:\n
253       !        \latexonly
254       !          \input{resp2.tex}
255       !        \endlatexonly
256       !        Where, stempdiag is diagnostic temperature profile of soil (K)\n
257       t_root(:,ivm) = zero
258
259       DO ibdl = 1, nbdl ! Loop over # soil layers
260
261          t_root(:,ivm) = &
262               t_root(:,ivm) + stempdiag(:,ibdl) * rpc(:) * &
263               ( EXP( -z_soil(ibdl-1)/rprof(:,ivm) ) - EXP( -z_soil(ibdl)/rprof(:,ivm) ) )
264
265       ENDDO ! Loop over # soil layers
266
267    ENDDO ! Loop over # PFTs
268
269    resp_maint_part_radia(:,:,:) = zero
270
271 !! 2. Define maintenance respiration coefficients
272
273    DO ivm = 2,nvm ! Loop over # PFTs
274
275       !! 2.1 Temperature for maintenanace respiration
276       !      Temperature which is used to calculate maintenance respiration for different plant compartments
277       !      (above- and belowground)\n
278       !      - for aboveground parts, we use 2-meter air temperature, t2m\n
279       !      - for belowground parts, we use root temperature calculated in section 1.2 of this subroutine\n
280       
281       ! 2.1.1 Aboveground biomass
282       t_maint_radia(:,ileaf) = t2m(:)
283       t_maint_radia(:,isapabove) = t2m(:)
284       t_maint_radia(:,ifruit) = t2m(:)
285
286       ! 2.1.2 Belowground biomass
287       t_maint_radia(:,isapbelow) = t_root(:,ivm)
288       t_maint_radia(:,iroot) = t_root(:,ivm)
289
290       !! 2.1.3 Heartwood biomass
291       !  Heartwood does does not respire (coeff_maint_zero is set to zero).
292       !  Any temperature could have been set 
293       !  [code cleaning: set t(heartwood) to undef to 'undef']
294
295       t_maint_radia(:,iheartbelow) = t_root(:,ivm)
296       t_maint_radia(:,iheartabove) = t2m(:)
297
298       t_maint_radia(:,ilabile) = t2m(:)
299       !! 2.1.4 Reserve biomass
300       !  Use aboveground temperature for trees and belowground temeperature for grasses
301       IF ( is_tree(ivm) ) THEN
302
303          t_maint_radia(:,icarbres) = t2m(:)
304
305       ELSE
306
307          t_maint_radia(:,icarbres) = t_root(:,ivm)
308
309       ENDIF
310
311       !! 2.1.5 Labile biomass pool
312       !  Use aboveground temperature for the labile biomass pool
313       t_maint_radia(:,ilabile) = t2m(:)
314       
315       !! 2.2 Calculate maintenance respiration coefficients (coeff_maint)
316       !  Maintenance respiration is a fraction of biomass defined by the coefficient
317       !  coeff_maint [Mc Cree, 1969]. Coeff_maint is defined through a linear relationship of temperature [Ruimy et al, 1996]
318       !  which slope is the coefficient 'slope' and which intercept is 'coeff_maint_zero'.
319       !  - Coeff_maint_zero is defined in stomate_data to cm_zero_plantpartname
320       !  - Slope is calculated here through a second-degree polynomial [Krinner et al, 2005]
321       !  equation that makes it dependent on the long term temperature (to represent adaptation
322       !  of the ecosystem to long term temperature).
323       !   \latexonly
324       !    \input{resp3.tex}
325       !   \endlatexonly
326       !  Where, maint_resp_slope1, maint_resp_slope2, maint_resp_slope3 are constant in stomate_constants.f90.
327       !  Then coeff_maint is calculated as follows:\n
328       !   \latexonly
329       !    \input{resp4.tex}
330       !   \endlatexonly
331       !  If the calculation result is negative, coeff_maint will take the value 0.\n   
332       tl(:) = tlong_ref(:) - ZeroCelsius
333       slope(:) = maint_resp_slope(ivm,1) + tl(:) * maint_resp_slope(ivm,2) + &
334            tl(:)*tl(:) * maint_resp_slope(ivm,3)
335
336       DO ipar = 1, nparts ! Loop over # plant parts
337
338          !+++CHECK+++
339          ! The original code refers to the Sitch et al 2003 as the source of the equations and parameters
340          ! for modelling maintenance respiration. The equations below are consistent with the paper. The
341          ! parameter setting for coeff_maint is in the range of 0.066 to 0.011 as reported in the paper but
342          ! exact values are not given. Although, the principle of a climate correction for coeff_maint is
343          ! mentioned in Sitch et al 2003, the reduction factors themselves were not given. As it appears
344          ! now this block of code pretends much more knowledge then we actually have. Rather than using a
345          ! baseline coeff_maint that is later corrected for the climate region, the parameter values for
346          ! coeff_maint could be simply prescribed and made pft-specific.
347          ! Further down in the code C/N ratios are used to constrain respiration. The C/N ratios were reset
348          ! to the values presented in Sitch et al 2003 but still seem on the low side. If pft-specific
349          ! values are to be used, changes in respiration could be compensated for by changing
350          ! coeff_maint_init. Given Vicca et al 2012 (Ecology Letters) an NPP/GPP ratio of 0.5 is 'universal'
351          ! for forests given a sufficient nutrient supply and strictly defining NPP as solely its biomass
352          ! components (thus excluding VOC, exudation and subsidies to myccorrhizae as is the case in ORCHIDEE).
353          ! Unless observation based values are available for coeff_maint_init, these values could be adjusted
354          ! within the range of 0.066 to 0.011 to obtain an NPP/GPP of 0.5 in the absence of nutrient
355          ! limitations.
356         
357          ! LPJ respiration factors based on Sitch et al. 2003 - first part of the calculation
358          IF ( ipar.EQ.ileaf .OR. ipar.EQ.iroot .OR. ipar.EQ.ifruit .OR. &
359               ipar.EQ.isapabove .OR. ipar.EQ.isapbelow .OR. ipar.EQ.ilabile) THEN
360             
361             ! Sonke uses
362             !coeff_maint(:,ivm,ipar) = 0.0548
363             
364             ! The Sitch et al 2003 paper gives a value of 0.066 (Table 3) and 0.011 for tropical systems
365             !coeff_maint(:,ivm,ipar) = 0.066
366             
367             ! Use an effective PFT-specific value - this value has been optimized
368             ! to reproduce observed NPP/GPP ratios
369             coeff_maint(:,ivm,ipar) = coeff_maint_init(ivm)
370             
371             ! heartwood and reserves pool   
372          ELSE
373             
374             coeff_maint(:,ivm,ipar) = zero
375             
376          ENDIF
377
378       ENDDO ! Loop over # plant parts
379           
380    ENDDO ! Loop over # PFTs
381       
382
383!! 3. Calculate maintenance respiration
384 
385    ! In the allometric based allocation scheme, maintentance respiration is calculated as
386    ! the minimum of supply and demand
387
388    resp_maint_part_radia(:,:,:) = zero
389   
390    DO ivm = 2,nvm ! Loop over # PFTs
391       
392       ! Demand based respiration
393       resp_maint_demand(:,ivm) = 0.0
394       
395       DO ipar = 1, nparts ! Loop over # plant parts 
396
397          ! LPJ respiration factors based on Sitch et al. 2003 - second part of the calculation
398          ! Temperature response, LLoyd and Taylor, 1994. E0 = 308.56 comes from the paper of
399          ! Lloyd and Taylor but was fitted for soil respiration which only partly consists of
400          ! authotrophic (root) respiration.
401         
402          WHERE(t_maint_radia(:,ipar)-ZeroCelsius-tmin_maint_resp(ivm) .GT.min_stomate)
403                 
404             gtemp(:,ivm) = dt/one_day * & 
405                 EXP(e0_maint_resp(ivm)*(1.0/(tref_maint_resp(ivm)-tmin_maint_resp(ivm)) - &
406                 1.0/(t_maint_radia(:,ipar)-ZeroCelsius-tmin_maint_resp(ivm))))
407
408          ! No gtemp below -46.01 degrees Celsius
409
410          ELSEWHERE
411             
412             gtemp(:,ivm) = 0.0
413             
414          ENDWHERE
415
416          WHERE(SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2).GT.min_stomate)
417             cn(:)=SUM(circ_class_biomass(:,ivm,:,ipar,icarbon)*circ_class_n(:,ivm,:),2)/&
418                SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2)
419          ELSEWHERE
420             cn(:)=zero
421          ENDWHERE
422
423          ! Calculate the limiting C/N ratio
424          IF ( ipar.EQ.ileaf ) THEN
425             
426             limit_cn = cn_leaf_prescribed(ivm)
427             
428          ELSEIF ( ipar.EQ.iroot .OR. ipar.EQ.ifruit ) THEN
429               
430             limit_cn = cn_leaf_prescribed(ivm)/fcn_root(ivm)
431             
432          ELSEIF ( ipar.EQ.isapabove .OR. ipar.EQ.isapbelow ) THEN
433             
434             limit_cn = cn_leaf_prescribed(ivm)/fcn_wood(ivm)
435             
436          ELSE
437             
438             limit_cn = cn_leaf_prescribed(ivm)
439             
440          ENDIF
441         
442          !---TEMP---
443          !IF (ivm.EQ.test_pft) THEN 
444          !   WRITE(numout,*) 'limit - ipar, temp output,', ipar, limit_cn
445          !ENDIF
446          !----------
447         
448          WHERE(cn(:).GT.limit_cn)
449             resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * gtemp(:,ivm) * & 
450                  SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2) 
451          ELSEWHERE
452             !avoid that respiration increases when CN is low -> respiring dead problem
453             ! could in extreme cases cause instability when deactivated
454             resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * gtemp(:,ivm) * & 
455                  SUM(circ_class_biomass(:,ivm,:,ipar,icarbon)*circ_class_n(:,ivm,:),2)/ limit_cn
456          ENDWHERE
457          resp_maint_demand(:,ivm) = resp_maint_demand(:,ivm) + resp_maint_part_radia(:,ivm,ipar)
458
459       ENDDO ! Loop over # plant parts
460       
461    ENDDO ! Loop over # PFTs
462
463 !! 4. Check consistency of this routine
464
465    !  This routine only calculates respiration factors but respiration itself
466    !  is not accounted for through pools and fluxes. Hence, there is no need to
467    !  CALL check_veget_cov_max
468    !  CALL check_mass_balance
469
470    IF (printlev>=3) WRITE(numout,*) 'Leaving maintenance respiration'
471
472  END SUBROUTINE maint_respiration
473
474END MODULE stomate_resp
Note: See TracBrowser for help on using the repository browser.