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

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

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

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 27.3 KB
Line 
1! =================================================================================================================================
2! MODULE           : stomate_resp
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           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 xios_orchidee
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, t2m, t2m_longterm, stempdiag, &
125       root_profile, circ_class_n, circ_class_biomass,resp_maint_part_radia, cn_leaf_init_2D)
126
127!! 0. Variable and parameter declaration
128
129    !! 0.1 Input variables
130
131    INTEGER(i_std), INTENT(in)                         :: npts                !! Domain size - number of grid cells (unitless)
132    REAL(r_std), DIMENSION(:), INTENT(in)              :: t2m                 !! 2 meter air temperature - forcing variable (K)
133    REAL(r_std), DIMENSION(:), INTENT(in)              :: t2m_longterm        !! Long term annual mean 2 meter reference air temperatures
134                                                                              !! calculated in stomate_season.f90 (K)
135    REAL(r_std), DIMENSION(:,:), INTENT (in)           :: stempdiag           !! Soil temperature of each soil layer (K)
136    REAL(r_std), DIMENSION(:,:,:,:), INTENT(in)        :: root_profile        !! Normalized root mass/length fraction in each soil layer
137                                                                              !! (0-1, unitless)
138    REAL(r_std), DIMENSION(:,:,:), INTENT(in)          :: circ_class_n        !! Number of individuals in each circ class
139                                                                              !! @tex $(ind m^{-2})$ @endtex
140    REAL(r_std), DIMENSION(:,:,:,:,:), INTENT(in)      :: circ_class_biomass  !! Biomass components of the model tree 
141                                                                              !! within a circumference class
142                                                                              !! class @tex $(g C ind^{-1})$ @endtex
143    REAL(r_std),DIMENSION(:,:), INTENT(in)             :: cn_leaf_init_2D     !! initial leaf C/N ratio
144
145    !! 0.2 Output variables
146
147    REAL(r_std), DIMENSION(:,:,:), INTENT(out)         :: resp_maint_part_radia !! PFT maintenance respiration of different
148                                                                              !! plant parts @tex $(gC.m^{-2}dt^{-1} )$ @endtex
149
150    !! 0.3 Modified variables
151   
152 
153    !! 0.4 Local variables
154
155    INTEGER(i_std)                                    :: ipts,ivm,ipar,islm   !! Indeces (unitless)
156    REAL(r_std), DIMENSION(npts,nvm)                  :: t_root               !! PFT root temperature (convolution of root and soil
157                                                                              !! temperature profiles) (K)
158    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: coeff_maint          !! PFT maintenance respiration coefficients of different
159                                                                              !! plant compartments at 0 deg C
160    REAL(r_std), DIMENSION(npts,nparts)               :: t_maint_radia        !! Temperature which is pertinent for maintenance respiration,
161                                                                              !! which is air/root temperature for above/below-ground
162                                                                              !! compartments (K)     
163    REAL(r_std), DIMENSION(npts)                      :: rpc                  !! Scaling factor for integrating vertical soil
164                                                                              !! profiles (unitless)
165    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: gtemp                !! Temperature response of respiration in the
166                                                                              !! Lloyd-Taylor Model (-)
167    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: cn                   !! CN ratio of a biomass pool ((gC)(gN)-1)
168    REAL(r_std), DIMENSION(npts)                      :: limit_cn             !! Calculate limiting C/N ratio ((gC)(gN)-1)
169    INTEGER(i_std)                                    :: ier                  !! Error handling
170    REAL(r_std)                                       :: ref_cn               !! Prescribed reference C/N ratio
171    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: adjust_resp          !! C/N-based modulator of respiration
172    REAL(r_std), DIMENSION(npts)                      :: tl                   !! Long term reference temperature in degrees Celcius
173                                                                              !! (= t2m_longterm - 273.15) (C)
174    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: slope                !! slope of the temperature dependence of maintenance
175                                                                              !! respiration coefficient (1/K)
176    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: temp                 !! temporary variable to write to XIOS
177    REAL(r_std), DIMENSION(npts,nvm,nparts)           :: temp2                !! temporary variable to write to XIOS
178
179!_ ================================================================================================================================
180       
181    IF (printlev>=3) WRITE(numout,*) 'Entering maintenance respiration'
182   
183 !! 1. Initializations
184 
185    !! 1.2. Calculate root temperature
186    !  Calculate root temperature as the convolution of root and soil temperature profiles
187    DO ivm = 2,nvm
188
189       ! Calculate root temperature
190       ! Use the root profile temperature (K) to weight the soil layers
191       ! (number of layers = nslm) at different depths. Note that the vertical axis
192       ! of root_profile and stempdiag are centered around the nodes. For root_profile
193       ! the center of each layer us given by znh (see vertical_soil.f90). The top
194       ! and bottom of the layer are calculated in hydrol_root_profile. If the
195       ! naming is correct, the discretisation of the variable stempdiag should follow
196       ! diaglev. diaglev is defined in control.f90 making use of znt (see
197       ! vertical_soil.f90) 
198       t_root(:,ivm) = zero
199       DO islm = 1, nslm ! Loop over # soil layers
200
201          t_root(:,ivm) = t_root(:,ivm) + stempdiag(:,islm) * &
202               root_profile(:,ivm,islm,istruc)
203         
204       ENDDO ! Loop over # soil layers
205       
206    ENDDO ! Loop over # PFTs
207
208    ! Initialise
209    slope(:,:,:) = zero
210    gtemp(:,:,:) = zero
211    cn(:,:,:) = zero
212    adjust_resp(:,:,:) = zero
213    resp_maint_part_radia(:,:,:) = zero
214    temp2(:,:,:) = zero
215
216 !! 2. Define maintenance respiration coefficients
217   
218    DO ivm = 2,nvm ! Loop over # PFTs
219
220       !! 2.1 Temperature for maintenanace respiration
221       !  Temperature which is used to calculate maintenance respiration for different
222       !  plant compartments (above- and belowground):
223       !  - for aboveground parts, we use 2-meter air temperature, t2m
224       !  - for belowground parts, we use root temperature calculated in section 1.2 of
225       !    this subroutine
226
227       ! 2.1.1 Aboveground biomass
228       t_maint_radia(:,ileaf) = t2m(:)
229       t_maint_radia(:,isapabove) = t2m(:)
230       t_maint_radia(:,ifruit) = t2m(:)
231       t_maint_radia(:,ilabile) = t2m(:)
232       t_maint_radia(:,iheartabove) = t2m(:)
233
234       ! 2.1.2 Belowground biomass
235       t_maint_radia(:,isapbelow) = t_root(:,ivm)
236       t_maint_radia(:,iroot) = t_root(:,ivm)
237       t_maint_radia(:,iheartbelow) = t_root(:,ivm)
238
239       ! 2.1.3 Depending on the PFT
240       IF ( is_tree(ivm) ) THEN
241          t_maint_radia(:,icarbres) = t2m(:)
242       ELSE
243          t_maint_radia(:,icarbres) = t_root(:,ivm)
244       ENDIF
245
246       !! 2.2 Calculate maitenance respiration coefficients (coeff_maint)
247       ! The calculation of the maintenance repiration has been a topic of long and unresolved
248       ! debate. This is reflected in the different approaches that can be found in the CMIP5
249       ! trunk, ORCHIDEE-CAN, ORCHIDEE-CNP, O-CN, and the CMIP6 trunk. The approach for CMIP5
250       ! was inspired on Krinner et al 2005. The later approaches were inspired on Sitch et al
251       ! 2003 and the equations were consistent with that paper. The parameter setting for
252       ! coeff_maint is in the range of 0.066 to 0.011 as reported in the paper but exact values
253       ! are not given. Although, the principle of a climate correction for coeff_maint is
254       ! mentioned in Sitch et al 2003, the reduction factors themselves were not given. As it
255       ! appears now this block of code pretends much more knowledge then we actually have. Rather
256       ! than using a baseline coeff_maint that is later corrected for the climate region, the
257       ! parameter values for coeff_maint could be simply prescribed and made pft-specific.
258
259       ! There are however a couple of problems with that approach:
260       ! (1) a PFT specific respiration coefficient is used to
261       ! address the observation that plants that grow in warmer regions repsire for a given
262       ! air temperature less than plants growing in a colder region. In Sitch et al, the PFT
263       ! specific maint_coeff thus compensate for the temperature effect calculated by gtemp
264       ! (see below). (2) Maintenance respiration increase if the N pool increases resulting in
265       ! an apparent decrease in NPP (but the absolute value of GPP and NPP should still increase).
266       ! Following increased N-availability, NPP/GPP in ORCHIDEE does not changes a  lot.
267       ! This is the opposite of what has been observed in over a century of fertilization experiments
268       ! and in more recent meta-analyses such as Vicca et al 2012. Vicca et al 2012 suggest that
269       ! an increase in NPP/GPP following fertilization is due to the fact that the C loss to
270       ! myccorgizae are decreasing. In ORCHIDEE this loss is accounted for the maintenance
271       ! respiration, it is hidden in COEFF_MAINT_RESP, and (3) estimates of Ra_maint also
272       ! include the C-fluxes to leaching, BVOCs mycorrhizae, etc. and will therefore be higher
273       ! than the observations. This issue should be addressed by adding mycorrhizae in the
274       ! in the model.
275
276       ! Given Vicca et al 2012 (Ecology Letters) an NPP/GPP ratio of 0.5 is 'universal' for
277       ! forests given a sufficient nutrient supply and strictly defining NPP as solely its
278       ! biomass components (thus excluding VOC, exudation and subsidies to myccorrhizae as is
279       ! the case in ORCHIDEE). Unless these currently missing fluxes are added to ORCHIDEE and
280       ! observation based values become available for coeff_maint_init, this parameter will be
281       ! adjusted to obtain an NPP/GPP of 0.5 in the absence of nutrient limitations.
282
283       SELECT CASE (maint_resp_control)
284
285       CASE ('nitrogen')
286
287          ! This approach follows the idea that maintenance respiration is driven by the
288          ! nitrogen pools. A PFT specific coeff_maint_init was kept as was the temperature
289          ! correction. Following Ali et al 2016 a small correction was made for structural
290          ! nitrogen (which is considered to be 4% of the nitrogen in the respiring pools.
291          ! We no longer use the parameters values for coeff_maint_init as presented in
292          ! Sitch et al 2003 as a plausible range. Values have been adjusted to obtain
293          ! reasonable NPP/GPP values which is more important for the rest of the
294          ! simulation.
295          DO ipar = 1, nparts
296
297             IF ( ipar.EQ.ileaf .OR. ipar.EQ.iroot .OR. ipar.EQ.ifruit .OR. &
298                  ipar.EQ.isapabove .OR. ipar.EQ.isapbelow) THEN
299
300                ! Plant parts that respire - the values have been optimized to reproduce
301                ! observed NPP/GPP ratios
302                coeff_maint(:,ivm,ipar) = coeff_maint_init(ivm) * dt_sechiba/one_day
303
304             ELSE
305
306                ! None respiring plant parts: heartwood, reserve pool
307                coeff_maint(:,ivm,ipar) = zero
308
309             ENDIF
310
311          ENDDO
312
313          !! Calculate maintenance respiration coefficients
314          DO ipar = 1, nparts ! Loop over # plant parts
315
316             ! LPJ respiration factors based on Sitch et al. 2003 - second part of the calculation
317             ! Temperature response, LLoyd and Taylor, 1994. E0 = 308.56 comes from the paper of
318             ! Lloyd and Taylor but was fitted for soil respiration which only partly consists of
319             ! authotrophic (root) respiration. With E0 = 308.56 the temperature sensitivity of
320             ! resp_maint is way too high for PFTs that occur along a substantial temperature gradient
321             ! such as the C3 grasslands. Too high means that the simulated NPP/GPP ratio (0.1 to 0.9)
322             ! exceeds the observed NPP/GPP across PFTs (0.3 to 0.7). There are two ways to tackle this
323             ! issue: (1) reduce the range of a single PFT (this has been done when moving from 13 to 15 
324             ! PFTs) and (2) reduce the temperature sensitivity. The latter is what is being done by
325             ! introducing the slope_ra parameter. Slope_ra is arbitrary so reducing the spatial extent
326             ! of a single PFT is probably the more scientific way forward.
327             WHERE(t_maint_radia(:,ipar)-ZeroCelsius-tmin_maint_resp(ivm).GT.min_stomate)
328                gtemp(:,ivm,ipar) = EXP((e0_maint_resp(ivm)/slope_ra)*&
329                     (1.0/(tref_maint_resp(ivm)-tmin_maint_resp(ivm))-1.0 / &
330                     (t_maint_radia(:,ipar)-ZeroCelsius-tmin_maint_resp(ivm))))
331             ELSEWHERE
332                ! No gtemp below -46.01 degrees Celsius
333                gtemp(:,ivm,ipar) = 0.0
334             ENDWHERE
335             
336             ! maint_resp seems very low for deciduous species with this formulation.
337             ! Following Ali et al. (2016) we account for structural N which does not
338             ! contribute to respiration
339             resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * gtemp(:,ivm,ipar) * & 
340                  (SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2) - &
341                  snc*SUM(circ_class_biomass(:,ivm,:,ipar,icarbon)*circ_class_n(:,ivm,:),2))
342             
343          ENDDO ! Loop over # plant parts
344
345
346       CASE ('cn')
347
348          ! This approach refines Sitch et al 2003 by constraining the respiration with C/N ratios.
349          ! The C/N ratios were reset to the values presented in Sitch et al 2003 but still seem on the low side.
350          ! If pft-specific values are to be used, changes in respiration could be compensated for by changing
351          ! coeff_maint_init. Given Vicca et al 2012 (Ecology Letters) an NPP/GPP ratio of 0.5 is 'universal'
352          ! for forests given a sufficient nutrient supply and strictly defining NPP as solely its biomass
353          ! components (thus excluding VOC, exudation and subsidies to myccorrhizae as is the case in ORCHIDEE).
354          ! Unless observation based values are available for coeff_maint_init, these values could be adjusted
355          ! within the range of 0.066 to 0.011 to obtain an NPP/GPP of 0.5 in the absence of nutrient
356          ! limitations.
357          DO ipar = 1, nparts ! Loop over # plant parts
358
359             ! LPJ respiration factors based on Sitch et al. 2003 - first part of the calculation
360             IF ( ipar.EQ.iheartabove .OR. ipar.EQ.iheartbelow .OR. ipar.EQ.icarbres) THEN
361                coeff_maint(:,ivm,ipar) = zero
362             ELSE
363                ! Use a  PFT-specific value - Values from OCN are used
364                coeff_maint(:,ivm,ipar) = coeff_maint_init(ivm)*dt_sechiba/one_day
365
366             ENDIF
367
368             ! Fall back on Krinner et al 2005 to calculate the temperature
369             ! dependency of each PFT. Note that the calculations of the slope is tricky. In
370             ! ORCHIDEE the calculation of Ra includes Rm (which is likely to be temperature
371             ! dependent), Rg (which depends on the growth) as well as C-subsidies to mycorrhizae
372             ! and leaching. C-subsisdies to mycorrhizae are nutrient-dependent. We are using
373             ! a strict temperature dependency to simulate Rm and to account for the fact
374             ! that we don calculate C-subsidies (Ra will be too high but NPP should still be
375             ! correct in ORCHIDEE). NPP/GPP should be highest in the temperate zone and lowest
376             ! in the boreal and tropics. If we allow tl to become negative (which is the case
377             ! in the high artic) the slope calculations becomes extremely difficult to control.
378             ! Hence, tl is trucated at zero.
379             tl(:) = MAX(zero, t2m_longterm(:) - ZeroCelsius)
380             slope(:,ivm,ipar) = maint_resp_slope(ivm,1) + tl(:) * maint_resp_slope(ivm,2) + &
381                  tl(:)*tl(:) * maint_resp_slope(ivm,3)
382
383             ! When, in the original formulation, the temperature dropped below zero,
384             ! gtemp dropped below one but it was prevented that it became negative.
385             ! Such and approached implied that we believed that respiration decreases
386             ! at sub zero temperature until it becomes zero somewhere between -5 and -10
387             ! depending the value of slope (which depends on the PFT). In other words at
388             ! sub zero temperatures Rm was believed to stop. In the new formulation
389             ! we think that at zero degrees Rm reaches its minimum but can no longer
390             ! decrease. The difference between the new and the old approach is either
391             ! zero (old) or a one (un; new) in the MAX statements
392             gtemp(:,ivm,ipar) = MAX(( un + slope(:,ivm,ipar) * &
393                  (t_maint_radia(:,ipar)-ZeroCelsius) ), un)
394
395             ! Calculate the actual C/N ratio
396             WHERE(SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2).GT.min_stomate)
397                cn(:,ivm,ipar) = SUM(circ_class_biomass(:,ivm,:,ipar,icarbon)*circ_class_n(:,ivm,:),2) / &
398                     SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2)
399             ELSEWHERE
400                cn(:,ivm,ipar) = zero
401             ENDWHERE
402
403             ! The model does not control the C/N ratio of the labile and carbohydrate
404             ! pools. The C/N ratio is truncated here. This has probably a relative small
405             ! impact because a very high c/n happens when the nitrogen in this pool is
406             ! very low. When nitrogen is very low it has little impact on the calculation
407             ! of resp_maint_part_radia because that is based on the nitrogen pool. The
408             ! threshold of 200 is a bit arbitrairy but it should ensure that it stays
409             ! with the physiological boundaries.
410             WHERE (cn(:,ivm,ipar) .GT. 200)
411                cn(:,ivm,ipar) = 200
412             ENDWHERE
413
414             ! Calculate the limiting C/N ratio
415             IF ( ipar.EQ.ileaf ) THEN
416                ref_cn=45.
417             ELSEIF ( ipar.EQ.iroot .OR. ipar.EQ.ifruit ) THEN
418                ref_cn=45./fcn_root(ivm)
419             ELSEIF ( ipar.EQ.isapabove .OR. ipar.EQ.isapbelow .OR. ipar.EQ.icarbres) THEN
420                ref_cn=45./fcn_wood(ivm)
421             ELSE
422                ref_cn=45.
423             ENDIF
424
425             ! Use the ref_cn to calculate a reduction factor. Several of the values
426             ! in this equation were tuned for the ORCHIDEE 3.0
427             adjust_resp(:,ivm,ipar)=cn(:,ivm,ipar)/ref_cn * &
428                  MAX(MIN( ( 1. + ( 1. - cn(:,ivm,ipar) / ref_cn ) * 3./10. ), 1.2),&
429                  0.8)
430             WHERE(SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2) .GT. min_stomate)
431                resp_maint_part_radia(:,ivm,ipar) = coeff_maint(:,ivm,ipar) * gtemp(:,ivm,ipar) * &
432                     SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2) * adjust_resp(:,ivm,ipar)
433                ! Debug - understanding the impact of the nitrogen pool
434                temp2(:,ivm,ipar) = adjust_resp(:,ivm,ipar) * &
435                     SUM(circ_class_biomass(:,ivm,:,ipar,initrogen)*circ_class_n(:,ivm,:),2)
436             ELSEWHERE
437                resp_maint_part_radia(:,ivm,ipar) = zero
438                ! Debug - understanding the impact of the nitrogen pool
439                temp2(:,ivm,ipar) = zero
440             ENDWHERE
441
442          ENDDO ! Loop over # plant parts
443
444       CASE default
445
446          ! All other cases
447          WRITE(numout,*) 'MAINT_RESP_CONTROL was set to: ',maint_resp_control
448          CALL ipslerr_p (3,'stomate_resp', 'don''t know how to calculate maint_resp', &
449               'Check orchidee.def', '')
450
451       END SELECT
452
453    ENDDO ! Loop over # PFTs 
454 
455    ! Write details for debugging and tuning
456    WHERE (resp_maint_part_radia(:,:,:) .EQ. zero)
457       temp(:,:,:) = xios_default_val
458    ELSEWHERE
459       temp(:,:,:) = resp_maint_part_radia(:,:,:)
460    ENDWHERE
461    CALL xios_orchidee_send_field("RESP_MAINT_PART",temp)
462   
463    WHERE (slope(:,:,:) .EQ. zero)
464       temp(:,:,:) = xios_default_val
465    ELSEWHERE
466       temp(:,:,:) = slope(:,:,:)
467    ENDWHERE
468    CALL xios_orchidee_send_field("SLOPE_MAINT_PART",temp)
469   
470    WHERE (gtemp(:,:,:) .EQ. zero)
471       temp(:,:,:) = xios_default_val
472    ELSEWHERE
473       temp(:,:,:) = gtemp(:,:,:)
474    ENDWHERE
475    CALL xios_orchidee_send_field("GTEMP_MAINT_PART",temp)
476   
477    WHERE (cn(:,:,:) .EQ. zero)
478       temp(:,:,:) = xios_default_val
479    ELSEWHERE
480       temp(:,:,:) = cn(:,:,:)
481    ENDWHERE
482    CALL xios_orchidee_send_field("CN_MAINT_PART",temp)
483   
484    WHERE (adjust_resp(:,:,:) .EQ. zero)
485       temp(:,:,:) = xios_default_val
486    ELSEWHERE
487       temp(:,:,:) = adjust_resp(:,:,:)
488    ENDWHERE
489    CALL xios_orchidee_send_field("ADJUST_MAINT_PART",temp)
490
491    WHERE (temp2(:,:,:) .EQ. zero)
492       temp2(:,:,:) = xios_default_val
493    ENDWHERE
494    CALL xios_orchidee_send_field("NPOOL_MAINT_PART",temp2)
495
496 !! 4. Check consistency of this routine
497
498    !  This routine only calculates respiration factors but respiration itself
499    !  is not accounted for through pools and fluxes. Hence, there is no need to
500    !  CALL check_veget_max and CALL check_mass_balance
501
502    IF (printlev>=3) WRITE(numout,*) 'Leaving maintenance respiration'
503
504  END SUBROUTINE maint_respiration
505
506END MODULE stomate_resp
Note: See TracBrowser for help on using the repository browser.