source: branches/publications/ORCHIDEE_gmd-2018-261/src_stomate/stomate_resp.f90 @ 8692

Last change on this file since 8692 was 4995, checked in by nicolas.vuichard, 7 years ago

rev02102017

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 16.6 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: Pudoc; 1970. p. 221-229.
18!! - Krinner G, Viovy N, de Noblet-Ducoudre N, Ogee J, Polcher J, Friedlingstein P,
19!! Ciais P, Sitch S, Prentice I C (2005) A dynamic global vegetation model for studies
20!! of the coupled atmosphere-biosphere system. Global Biogeochemical Cycles, 19, GB1015,
21!! doi: 10.1029/2003GB002199.\n
22!! Ruimy A., Dedieu G., Saugier B. (1996), TURC: A diagnostic model
23!! of continental gross primary productivity and net primary productivity,
24!! Global Biogeochemical Cycles, 10, 269-285.\n
25
26!! SVN :
27!! $HeadURL$
28!! $Date$
29!! $Revision$
30!! \n
31!_ ================================================================================================================================
32 
33MODULE stomate_resp
34
35  ! modules used:
36  USE stomate_data
37  USE pft_parameters
38  USE constantes 
39  USE constantes_soil 
40
41  IMPLICIT NONE
42
43  ! private & public routines
44  PRIVATE
45  PUBLIC maint_respiration,maint_respiration_clear
46
47  LOGICAL, SAVE                                              :: firstcall_resp = .TRUE.                 !! first call
48!$OMP THREADPRIVATE(firstcall_resp)
49
50CONTAINS
51
52
53!! ================================================================================================================================
54!! SUBROUTINE   : maint_respiration_clear
55!!
56!>\BRIEF        : Set the flag ::firstcall_resp to .TRUE. and as such activate section
57!!                1.1 of the subroutine maint_respiration (see below).
58!_ ================================================================================================================================
59
60  SUBROUTINE maint_respiration_clear
61    firstcall_resp=.TRUE.
62  END SUBROUTINE maint_respiration_clear
63
64
65!! ================================================================================================================================
66!! SUBROUTINE   : maint_respiration
67!!
68!>\BRIEF         Calculate PFT maintenance respiration of each living plant part by
69!! multiplying the biomass of plant part by maintenance respiration coefficient which
70!! depends on long term mean annual temperature. PFT maintenance respiration is carbon flux
71!! with the units @tex $(gC.m^{-2}dt_sechiba^{-1})$ @endtex, and the convention is from plants to the
72!! atmosphere.
73!!
74!! DESCRIPTION : The maintenance respiration of each plant part for each PFT is the biomass of the plant
75!! part multiplied by maintenance respiration coefficient. The biomass allocation to different
76!! plant parts is done in routine stomate_alloc.f90. The maintenance respiration coefficient is
77!! calculated in this routine.\n
78!!
79!! The maintenance respiration coefficient is the fraction of biomass that is lost during
80!! each time step, which increases linearly with temperature (2-meter air temperature for aboveground plant
81!! tissues; root-zone temperature for below-ground tissues). Air temperature is an input forcing variable.
82!! Root-zone temperature is a convolution of root and soil temperature profiles and also calculated
83!! in this routine.\n
84!!
85!! The calculation of maintenance respiration coefficient (fraction of biomass respired) depends linearly
86!! on temperature:
87!! - the relevant temperature for different plant parts (air temperature or root-zone temperature)\n
88!! - intercept: prescribed maintenance respiration coefficients at 0 Degree Celsius for
89!!   different plant parts for each PFT in routine stomate_constants.f90\n
90!! - slope: calculated with a quadratic polynomial with the multi-annual mean air temperature
91!! (the constants are in routine stomate_constants.f90) as follows\n
92!!    \latexonly
93!!      \input{resp3.tex}
94!!    \endlatexonly
95!!   Where, maint_resp_slope1, maint_resp_slope2, maint_resp_slope3 are constant in stomate_constants.f90.
96!!   Then coeff_maint is calculated as follows:\n
97!!    \latexonly
98!!      \input{resp4.tex}
99!!    \endlatexonly 
100!! If the calculation result is negative, maintenance respiration coefficient will take the value 0.
101!! Therefore the maintenance respiration will also be 0.\n
102!!
103!! RECENT CHANGE(S): None
104!!
105!! MAIN OUTPUT VARIABLE(S): PFT maintenance respiration of different plant parts (::resp_maint_part_radia)
106!!
107!! REFERENCE(S) :
108!! McCree KJ. An equation for the respiration of white clover plants grown under controlled conditions. In:
109!! Setlik I, editor. Prediction and measurement of photosynthetic productivity. Wageningen,
110!! The Netherlands: Pudoc; 1970. p. 221-229.
111!! Krinner G, Viovy N, de Noblet-Ducoudre N, Ogee J, Polcher J, Friedlingstein P,
112!! Ciais P, Sitch S, Prentice I C (2005) A dynamic global vegetation model for studies
113!! of the coupled atmosphere-biosphere system. Global Biogeochemical Cycles, 19, GB1015,
114!! doi: 10.1029/2003GB002199.\n
115!! Ruimy A., Dedieu G., Saugier B. (1996), TURC: A diagnostic model
116!! of continental gross primary productivity and net primary productivity,
117!! Global Biogeochemical Cycles, 10, 269-285.\n
118!! FLOWCHART    : None
119!! \n
120!_ ================================================================================================================================
121
122  SUBROUTINE maint_respiration ( npts, t2m,stempdiag,&
123       rprof,biomass,resp_maint_part_radia)
124
125!! 0. Variable and parameter declaration
126
127    !! 0.1 Input variables
128
129    INTEGER(i_std), INTENT(in)                         :: npts      !! Domain size - number of grid cells (unitless)
130    REAL(r_std), DIMENSION(npts), INTENT(in)           :: t2m       !! 2 meter air temperature - forcing variable (K)
131    REAL(r_std), DIMENSION(npts,nbdl), INTENT (in)     :: stempdiag !! Soil temperature of each soil layer (K)
132    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)       :: rprof     !! PFT root depth as calculated in stomate.f90 from parameter
133                                                                    !! humcste which is root profile for different PFTs
134                                                                    !! in slowproc.f90 (m)
135    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: biomass   !! PFT total biomass calculated in stomate_alloc.f90
136                                                                    !! @tex $(gC.m^{-2})$ @endtex
137
138    !! 0.2 Output variables
139
140    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out) :: resp_maint_part_radia !! PFT maintenance respiration of different plant
141                                                                                  !! parts @tex $(gC.m^{-2}dt_sechiba^{-1} )$ @endtex
142
143    !! 0.3 Modified variables
144 
145    !! 0.4 Local variables
146
147    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)    :: z_soil       !! Variable to store depth of the different soil layers (m)
148!$OMP THREADPRIVATE(z_soil)
149    REAL(r_std), DIMENSION(npts,nvm)        :: t_root               !! PFT root temperature (convolution of root and soil
150                                                                    !! temperature profiles) (K)
151    REAL(r_std), DIMENSION(npts,nvm,nparts) :: coeff_maint          !! PFT maintenance respiration coefficients of different
152                                                                    !! plant compartments at 0 deg C
153                                                                    !! @tex $(g.g^{-1}dt_sechiba^{-1})$ @endtex
154    REAL(r_std), DIMENSION(npts)            :: rpc                  !! Scaling factor for integrating vertical soil
155                                                                    !! profiles (unitless)
156    REAL(r_std), DIMENSION(npts,nparts)     :: t_maint_radia        !! Temperature which is pertinent for maintenance respiration,
157                                                                    !! which is air/root temperature for above/below-ground
158                                                                    !! compartments (K)
159    INTEGER(i_std)                          :: i,j,k,l,m            !! Indeces (unitless)
160    REAL(r_std), DIMENSION(npts,nvm)        :: gtemp                !! Temperature response of respiration in the
161                                                                    !! Lloyd-Taylor Model (-)
162    REAL(r_std), DIMENSION(npts)            :: cn                   !! CN ratio of a biomass pool ((gC)(gN)-1)
163    REAL(r_std)                             :: limit_cn             !! Calculate limiting C/N ratio ((gC)(gN)-1)
164    INTEGER(i_std)                          :: ier                  !! Error handling
165
166!_ ================================================================================================================================
167   
168   
169    IF (printlev>=3) WRITE(numout,*) 'Entering respiration'
170   
171 !! 1. Initializations
172   
173    IF ( firstcall_resp ) THEN
174
175       !! 1.1. Soil levels (first call only)
176       !       Set the depth of the different soil layers (number of layers: nbdl)
177       !       previously calculated as variable diaglev in routines sechiba.f90 and slowproc.f90
178       ALLOCATE(z_soil(0:nbdl), stat=ier)
179       IF ( ier /= 0 ) CALL ipslerr_p(3,'maint_respiration','Pb in allocate of z_soil','','')
180       z_soil(0) = zero
181       z_soil(1:nbdl) = diaglev(1:nbdl)
182
183       !! 1.1.2. Write message
184       !         Notify user of the start of this subroutine
185       WRITE(numout,*) 'respiration:'
186
187       firstcall_resp = .FALSE.
188
189    ENDIF
190
191   
192   
193    !! 1.2. Calculate root temperature
194    !       Calculate root temperature as the convolution of root and soil temperature profiles
195    DO j = 2,nvm ! Loop over # PFTs
196
197       !! 1.2.1 Calculate rpc
198       !  - rpc is an integration constant to make the integral over the root profile is equal 'one',
199       !    calculated as follows:\n
200       !  \latexonly
201       !    \input{resp1.tex}
202       !  \endlatexonly
203       rpc(:) = un / ( un - EXP( -z_soil(nbdl) / rprof(:,j) ) )
204
205       !! 1.2.2 Calculate root temperature
206       !        - Integrate root profile temperature (K) over soil layers (number of layers = nbdl)
207       !          with rpc and soil temperature (K) of each soil layer as follows:\n
208       !        \latexonly
209       !          \input{resp2.tex}
210       !        \endlatexonly
211       !        Where, stempdiag is diagnostic temperature profile of soil (K)\n
212       t_root(:,j) = zero
213
214       DO l = 1, nbdl ! Loop over # soil layers
215
216          t_root(:,j) = &
217               t_root(:,j) + stempdiag(:,l) * rpc(:) * &
218               ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) )
219
220       ENDDO ! Loop over # soil layers
221
222    ENDDO ! Loop over # PFTs
223
224
225    resp_maint_part_radia(:,:,:) = zero
226   
227 !! 2. Define maintenance respiration coefficients
228
229    DO j = 2,nvm ! Loop over # PFTs
230
231       !! 2.1 Temperature for maintenanace respiration
232       !      Temperature which is used to calculate maintenance respiration for different plant compartments
233       !      (above- and belowground)\n
234       !      - for aboveground parts, we use 2-meter air temperature, t2m\n
235       !      - for belowground parts, we use root temperature calculated in section 1.2 of this subroutine\n
236       
237       ! 2.1.1 Aboveground biomass
238       t_maint_radia(:,ileaf) = t2m(:)
239       t_maint_radia(:,isapabove) = t2m(:)
240       t_maint_radia(:,ifruit) = t2m(:)
241
242       ! 2.1.2 Belowground biomass
243       t_maint_radia(:,isapbelow) = t_root(:,j)
244       t_maint_radia(:,iroot) = t_root(:,j)
245
246       !! 2.1.3 Heartwood biomass
247       !        Heartwood does does not respire (coeff_maint_zero is set to zero)
248
249       t_maint_radia(:,iheartbelow) = t_root(:,j)
250       t_maint_radia(:,iheartabove) = t2m(:)
251
252       t_maint_radia(:,ilabile) = t2m(:)
253       !! 2.1.4 Reserve biomass
254       !        Use aboveground temperature for trees and belowground temeperature for grasses
255       IF ( is_tree(j) ) THEN
256          t_maint_radia(:,icarbres) = t2m(:)
257       ELSE
258          t_maint_radia(:,icarbres) = t_root(:,j)
259       ENDIF
260
261       DO k = 1, nparts ! Loop over # plant parts
262
263          ! Comment taken from DOFOCO: The original code refers to the Sitch et al 2003 as the source of the equations and parameters
264          ! for modelling maintenance respiration. The equations below are consistent with the paper. The
265          ! parameter setting for coeff_maint is in the range of 0.066 to 0.011 as reported in the paper but
266          ! exact values are not given. Although, the principle of a climate correction for coeff_maint is
267          ! mentioned in Sitch et al 2003, the reduction factors themselves were not given. As it appears
268          ! now this block of code pretends much more knowledge then we actually have. Rather than using a
269          ! baseline coeff_maint that is later corrected for the climate region, the parameter values for
270          ! coeff_maint could be simply prescribed and made pft-specific.
271          ! Further down in the code C/N ratios are used to constrain respiration. The C/N ratios were reset
272          ! to the values presented in Sitch et al 2003 but still seem on the low side. If pft-specific
273          ! values are to be used, changes in respiration could be compensated for by changing
274          ! coeff_maint_init. Given Vicca et al 2012 (Ecology Letters) an NPP/GPP ratio of 0.5 is 'universal'
275          ! for forests given a sufficient nutrient supply and strictly defining NPP as solely its biomass
276          ! components (thus excluding VOC, exudation and subsidies to myccorrhizae as is the case in ORCHIDEE).
277          ! Unless observation based values are available for coeff_maint_init, these values could be adjusted
278          ! within the range of 0.066 to 0.011 to obtain an NPP/GPP of 0.5 in the absence of nutrient
279          ! limitations.
280         
281          ! LPJ respiration factors based on Sitch et al. 2003 - first part of the calculation
282          IF ( k.EQ.iheartabove .OR. k.EQ.iheartbelow .OR. k.EQ.icarbres ) THEN
283             coeff_maint(:,j,k) = zero
284          ELSE
285             ! Use a  PFT-specific value - Values from OCN are used
286             coeff_maint(:,j,k) = coeff_maint_init(j)* dt_sechiba/one_day
287                     
288          ENDIF
289
290       ENDDO
291
292   
293 !! 3. Calculate maintenance respiration
294       
295       DO k = 1, nparts ! Loop over # plant parts
296           
297          ! LPJ respiration factors based on Sitch et al. 2003 - second part of the calculation
298          ! Temperature response, LLoyd and Taylor, 1994. E0 = 308.56 comes from the paper of
299          ! Lloyd and Taylor but was fitted for soil respiration which only partly consists of
300          ! authotrophic (root) respiration.   
301          WHERE(t_maint_radia(:,k)-ZeroCelsius-tmin_maint_resp(j) .GT.min_stomate)
302             gtemp(:,j) = EXP(e0_maint_resp(j)*(1.0/(tref_maint_resp(j)-tmin_maint_resp(j)) - &
303                  1.0/(t_maint_radia(:,k)-ZeroCelsius-tmin_maint_resp(j))))
304          ! No gtemp below -46.01 degrees Celsius
305          ELSEWHERE
306             gtemp(:,j) = 0.0
307          ENDWHERE
308           
309          WHERE(biomass(:,j,k,initrogen).GT.min_stomate)
310             cn(:)=biomass(:,j,k,icarbon)/biomass(:,j,k,initrogen)
311          ELSEWHERE
312             cn(:)=zero
313          ENDWHERE
314
315          ! Calculate the limiting C/N ratio
316          IF ( k.EQ.ileaf ) THEN
317             limit_cn = cn_leaf_init(j)
318          ELSEIF ( k.EQ.iroot .OR. k.EQ.ifruit ) THEN
319             limit_cn = cn_leaf_init(j)/fcn_root(j)
320          ELSEIF ( k.EQ.isapabove .OR. k.EQ.isapbelow ) THEN
321             limit_cn = cn_leaf_init(j)/fcn_wood(j)
322          ELSE
323             limit_cn = cn_leaf_init(j)
324          ENDIF
325           
326          WHERE(cn(:).GT.limit_cn)
327             resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * gtemp(:,j) * & 
328                  biomass(:,j,k,initrogen) 
329          ELSEWHERE
330             !avoid that respiration increases when CN is low -> respiring dead problem
331             ! could in extreme cases cause instability when deactivated
332             resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * gtemp(:,j) * & 
333                  biomass(:,j,k,icarbon) / limit_cn
334          ENDWHERE
335!!            resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * gtemp(:,j) * &
336!!                 biomass(:,j,k,initrogen)
337
338       ENDDO ! Loop over # plant parts
339
340    ENDDO
341
342    IF (printlev>=4) WRITE(numout,*) 'Leaving respiration'
343
344  END SUBROUTINE maint_respiration
345
346END MODULE stomate_resp
Note: See TracBrowser for help on using the repository browser.