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

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 17.9 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: 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: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_resp.f90 $
28!! $Date: 2017-10-18 11:15:06 +0200 (Wed, 18 Oct 2017) $
29!! $Revision: 4693 $
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,lai, t2m,t2m_longterm,stempdiag,height,veget_cov_max,&
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), INTENT(in)           :: t2m_longterm !! Long term annual mean 2 meter reference air temperatures
132                                                                       !! calculated in stomate_season.f90 (K)
133    REAL(r_std), DIMENSION(npts,nslm), INTENT (in)     :: stempdiag !! Soil temperature of each soil layer (K)
134    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)       :: height    !! height of vegetation (m)
135    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)       :: veget_cov_max !! PFT "maximal" coverage fraction of a PFT (unitless)
136    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)       :: rprof     !! PFT root depth as calculated in stomate.f90 from parameter
137                                                                    !! humcste which is root profile for different PFTs
138                                                                    !! in slowproc.f90 (m)
139    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements),INTENT(in) :: biomass   !! PFT total biomass calculated in stomate_alloc.f90
140                                                                    !! @tex $(gC.m^{-2})$ @endtex
141
142    !! 0.2 Output variables
143
144    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)        :: lai                   !! PFT leaf area index @tex $(m^2 m^{-2})$ @endtex
145
146    REAL(r_std), DIMENSION(npts,nvm,nparts), INTENT(out) :: resp_maint_part_radia !! PFT maintenance respiration of different plant
147                                                                                  !! parts @tex $(gC.m^{-2}dt_sechiba^{-1} )$ @endtex
148
149    !! 0.3 Modified variables
150 
151    !! 0.4 Local variables
152
153    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)    :: z_soil       !! Variable to store depth of the different soil layers (m)
154!$OMP THREADPRIVATE(z_soil)
155    REAL(r_std), DIMENSION(npts,nvm)        :: t_root               !! PFT root temperature (convolution of root and soil
156                                                                    !! temperature profiles) (K)
157    REAL(r_std), DIMENSION(npts,nvm,nparts) :: coeff_maint          !! PFT maintenance respiration coefficients of different
158                                                                    !! plant compartments at 0 deg C
159                                                                    !! @tex $(g.g^{-1}dt_sechiba^{-1})$ @endtex
160    REAL(r_std), DIMENSION(npts)            :: rpc                  !! Scaling factor for integrating vertical soil
161                                                                    !! profiles (unitless)
162    REAL(r_std), DIMENSION(npts,nparts)     :: t_maint_radia        !! Temperature which is pertinent for maintenance respiration,
163                                                                    !! which is air/root temperature for above/below-ground
164                                                                    !! compartments (K)
165    REAL(r_std), DIMENSION(npts)            :: tl                   !! Long term reference temperature in degrees Celcius
166                                                                    !! (= t2m_longterm - 273.15) (C)
167    REAL(r_std), DIMENSION(npts)            :: slope                !! slope of the temperature dependence of maintenance
168                                                                    !! respiration coefficient (1/K)
169    INTEGER(i_std)                          :: i,j,k,l,m            !! Indeces (unitless)
170    INTEGER(i_std)                          :: ier                  !! Error handling
171
172!_ ================================================================================================================================
173   
174   
175    IF (printlev>=3) WRITE(numout,*) 'Entering respiration'
176   
177 !! 1. Initializations
178   
179    IF ( firstcall_resp ) THEN
180
181       !! 1.1. Soil levels (first call only)
182       !       Set the depth of the different soil layers (number of layers: nslm)
183       !       previously calculated as variable diaglev in routines sechiba.f90 and slowproc.f90
184       ALLOCATE(z_soil(0:nslm), stat=ier)
185       IF ( ier /= 0 ) CALL ipslerr_p(3,'maint_respiration','Pb in allocate of z_soil','','')
186       z_soil(0) = zero
187       z_soil(1:nslm) = diaglev(1:nslm)
188
189       firstcall_resp = .FALSE.
190    ENDIF
191
192   
193   
194    !! 1.2. Calculate root temperature
195    !       Calculate root temperature as the convolution of root and soil temperature profiles
196    DO j = 2,nvm ! Loop over # PFTs
197
198       !! 1.2.1 Calculate rpc
199       !  - rpc is an integration constant to make the integral over the root profile is equal 'one',
200       !    calculated as follows:\n
201       !  \latexonly
202       !    \input{resp1.tex}
203       !  \endlatexonly
204       rpc(:) = un / ( un - EXP( -z_soil(nslm) / rprof(:,j) ) )
205
206       !! 1.2.2 Calculate root temperature
207       !        - Integrate root profile temperature (K) over soil layers (number of layers = nslm)
208       !          with rpc and soil temperature (K) of each soil layer as follows:\n
209       !        \latexonly
210       !          \input{resp2.tex}
211       !        \endlatexonly
212       !        Where, stempdiag is diagnostic temperature profile of soil (K)\n
213       t_root(:,j) = zero
214
215       DO l = 1, nslm ! Loop over # soil layers
216
217          t_root(:,j) = &
218               t_root(:,j) + stempdiag(:,l) * rpc(:) * &
219               ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) )
220
221       ENDDO ! Loop over # soil layers
222
223    ENDDO ! Loop over # PFTs
224
225 !! 2. Define maintenance respiration coefficients
226
227    DO j = 2,nvm ! Loop over # PFTs
228
229       !! 2.1 Temperature for maintenanace respiration
230       !      Temperature which is used to calculate maintenance respiration for different plant compartments
231       !      (above- and belowground)\n
232       !      - for aboveground parts, we use 2-meter air temperature, t2m\n
233       !      - for belowground parts, we use root temperature calculated in section 1.2 of this subroutine\n
234       
235       ! 2.1.1 Aboveground biomass
236       t_maint_radia(:,ileaf) = t2m(:)
237       t_maint_radia(:,isapabove) = t2m(:)
238       t_maint_radia(:,ifruit) = t2m(:)
239
240       ! 2.1.2 Belowground biomass
241       t_maint_radia(:,isapbelow) = t_root(:,j)
242       t_maint_radia(:,iroot) = t_root(:,j)
243
244       !! 2.1.3 Heartwood biomass
245       !        Heartwood does does not respire (coeff_maint_zero is set to zero)
246
247       t_maint_radia(:,iheartbelow) = t_root(:,j)
248       t_maint_radia(:,iheartabove) = t2m(:)
249
250       !! 2.1.4 Reserve biomass
251       !        Use aboveground temperature for trees and belowground temeperature for grasses
252       IF ( is_tree(j) ) THEN
253          t_maint_radia(:,icarbres) = t2m(:)
254       ELSE
255          t_maint_radia(:,icarbres) = t_root(:,j)
256       ENDIF
257
258       
259       !! 2.2 Calculate maintenance respiration coefficients (coeff_maint)
260       !      Maintenance respiration is a fraction of biomass defined by the coefficient
261       !      coeff_maint [Mc Cree, 1969]. Coeff_maint is defined through a linear relationship of temperature [Ruimy et al, 1996]
262       !      which slope is the coefficient 'slope' and which intercept is 'coeff_maint_zero'.
263       !     - Coeff_maint_zero is defined in stomate_data to cm_zero_plantpartname
264       !     - Slope is calculated here through a second-degree polynomial [Krinner et al, 2005]
265       !    equation that makes it dependent on the long term temperature (to represent adaptation
266       !    of the ecosystem to long term temperature).
267       !         \latexonly
268       !           \input{resp3.tex}
269       !         \endlatexonly
270       !        Where, maint_resp_slope1, maint_resp_slope2, maint_resp_slope3 are constant in stomate_constants.f90.
271       !        Then coeff_maint is calculated as follows:\n
272       !         \latexonly
273       !           \input{resp4.tex}
274       !         \endlatexonly
275       ! If the calculation result is negative, coeff_maint will take the value 0.\n   
276       tl(:) = t2m_longterm(:) - ZeroCelsius
277       slope(:) = maint_resp_slope(j,1) + tl(:) * maint_resp_slope(j,2) + &
278            tl(:)*tl(:) * maint_resp_slope(j,3)
279
280       DO k = 1, nparts ! Loop over # plant parts
281
282          coeff_maint(:,j,k) = &
283               MAX( (coeff_maint_zero(j,k)*dt_sechiba/one_day) * &
284               ( un + slope(:) * (t_maint_radia(:,k)-ZeroCelsius) ), zero )
285
286       ENDDO ! Loop over # plant parts
287
288    ENDDO ! Loop over # PFTs
289   
290 !! 3. Calculate maintenance respiration
291
292    ! The maintenance respiration @tex $(gC.m^{-2}dt_sechiba^{-1})$ @endtex of each plant compartment for each PFT is
293    ! the biomass @tex $(gC.m^{-2})$ @endtex of the plant part multiplied by maintenance respiration
294    ! coefficient @tex $(g.g^{-1}dt_sechiba^{-1})$ @endtex, except that the maintenance respiration of leaves is
295    ! corrected by leaf area index (LAI) as follows:\n
296    ! \latexonly     
297    !   \input{resp5.tex}
298    ! \endlatexonly
299
300    ! ibare_sechiba = 1, which means the there is only bare soil but not any PFT, consequently no LAI and
301    !  maintenance respiration
302    lai(:,ibare_sechiba) = zero
303    resp_maint_part_radia(:,ibare_sechiba,:) = zero
304   
305    DO j = 2,nvm ! Loop over # PFTs
306       
307       ! 3.1 Maintenance respiration of the different plant parts
308       lai(:,j) = biomass(:,j,ileaf,icarbon) * sla(j)
309
310       DO k = 1, nparts ! Loop over # plant parts
311
312          IF ( k .EQ. ileaf ) THEN
313
314             ! Leaves: respiration depends on leaf mass AND LAI.
315!!$                WHERE ( (biomass(:,j,ileaf) > min_stomate) .AND. (lai(:,j) > 0.0) .AND. (lai(:,j) < val_exp) )
316!!$                resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * biomass(:,j,k) * &
317!!$                        ( .3*lai(:,j) + 1.4*(1.-exp(-.5*lai(:,j))) ) / lai(:,j)
318!!$             ELSEWHERE
319!!$                resp_maint_part_radia(:,j,k) = 0.0
320!!$             ENDWHERE
321             DO i = 1, npts ! Loop over # pixels
322                IF ( (biomass(i,j,ileaf,icarbon) > min_stomate) .AND. (lai(i,j) > min_stomate) ) THEN
323
324!$                         IF (lai(i,j) < 100._r_std) THEN
325!$                            resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k,icarbon) * &
326!$                                 ( .3*lai(i,j) + 1.4*(1.-exp(-.5*lai(i,j))) ) / lai(i,j)
327!$                         ELSE
328!$                            resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k,icarbon) * &
329!$                                 ( .3*lai(i,j) + 1.4 ) / lai(i,j)
330!$                         ENDIF
331
332                   ! Maintenance respiration is calculated as a fraction of biomass as defined by coeff_maint and
333                   ! is adjusted for the nitrogen effect through a third factor depending on LAI. The hypothesis
334                   ! here is that the vcmax (i.e. the nitrogen distribution) in the canopy decreases exponentially
335                   ! with LAI following the Beer-Lambert law with an asymptote defining the minimum of the function
336                   ! at 30% of the LAI. The 1.4 parameter is an integration constant.
337                   ! This method is also used in diffuco_trans_co2 2.4.1 for scaling vmax based on nitrogen reduction
338                   ! in the canopy.
339
340                   resp_maint_part_radia(i,j,k) = coeff_maint(i,j,k) * biomass(i,j,k,icarbon) * &
341                        ( maint_resp_min_vmax*lai(i,j) + maint_resp_coeff*(un - exp(-ext_coeff(j)*lai(i,j))) ) / lai(i,j)
342                ELSE
343                   resp_maint_part_radia(i,j,k) = zero
344                ENDIF
345             ENDDO ! Loop over # pixels
346          ELSE
347
348             resp_maint_part_radia(:,j,k) = coeff_maint(:,j,k) * biomass(:,j,k,icarbon)
349
350          ENDIF
351
352       ENDDO ! Loop over # plant parts
353
354       ! 3.2 Total maintenance respiration of the plant
355       !     VPP killer:
356       !     resp_maint(:,j) = SUM( resp_maint_part(:,:), DIM=2 )
357
358    ENDDO ! Loop over # PFTs
359
360
361  END SUBROUTINE maint_respiration
362
363END MODULE stomate_resp
Note: See TracBrowser for help on using the repository browser.