source: branches/publications/ORCHIDEE_GLUC_r6545/src_stomate/stomate_resp.f90 @ 6737

Last change on this file since 6737 was 4956, checked in by albert.jornet, 6 years ago

Clean: remove unused argument

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