SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
carbon_litter.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6 SUBROUTINE carbon_litter (PTSTEP, PTURNOVER, PLITTER, PLIGNIN_STRUC, &
7  pcontrol_temp, pcontrol_moist, &
8  presp_hetero_litter, psoilcarbon_input)
9 
10 ! ###############################################################
11 !!** CARBON_LITTER
12 !!
13 !! PURPOSE
14 !! -------
15 !! Calculates litter evolution.
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !! none
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! none
28 !!
29 !! REFERENCE
30 !! ---------
31 !!
32 !! Parton et al., Biogeochemestry, 1988
33 !! Krinner et al., Global Biochemical Cycles, 2005
34 !! Gibelin et al. 2008, AFM
35 !!
36 !! AUTHOR
37 !! ------
38 !!
39 !! A.-L. Gibelin * Meteo-France *
40 !!
41 !! MODIFICATIONS
42 !! -------------
43 !! Original 23/06/09
44 !! B. Decharme 05/2012 : Optimization
45 !!
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 USE modd_co2v_par, ONLY : xlc, xtau_litter, xfrac_litter, xfrac_soilcarb
52 USE modd_csts, ONLY : xday, xtt
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 IMPLICIT NONE
58 !
59 !* 0.1 input
60 !
61 ! time step in s
62 REAL, INTENT(IN) :: ptstep
63 !time step in s
64 ! Turnover rates (gC/m**2/s)
65 REAL, DIMENSION(:,:), INTENT(IN) :: pturnover
66 ! temperature control of heterotrophic respiration, above and below
67 REAL, DIMENSION(:,:), INTENT(IN) :: pcontrol_temp
68 ! moisture control of heterotrophic respiration
69 REAL, DIMENSION(:,:), INTENT(IN) :: pcontrol_moist
70 !
71 !* 0.2 modified fields
72 !
73 ! metabolic and structural litter, above and below ground (gC/m**2)
74 REAL, DIMENSION(:,:,:), INTENT(INOUT) :: plitter
75 ! ratio Lignin/Carbon in structural litter, above and below ground (gC/m**2)
76 REAL, DIMENSION(:,:), INTENT(INOUT) :: plignin_struc
77 !
78 !* 0.3 output
79 !
80 ! litter heterotrophic respiration (in gC/m**2/day)
81 REAL, DIMENSION(:), INTENT(OUT) :: presp_hetero_litter
82 ! quantity of carbon going into carbon pools from litter decomposition
83 ! (gC/m**2/day)
84 REAL, DIMENSION(:,:), INTENT(OUT) :: psoilcarbon_input
85 !
86 !* 0.4 local
87 !
88 ! time step in days
89 REAL :: zdt
90 ! fraction of structural or metabolic litter decomposed
91 REAL :: zfd
92 ! quantity of structural or metabolic litter decomposed (gC/m**2)
93 REAL :: zqd
94 ! old structural litter, above and below (gC/m**2)
95 REAL, DIMENSION(SIZE(PLITTER,1),SIZE(PLITTER,3)) :: zold_struc
96 ! increase of metabolic and structural litter, above and below ground (gC/m**2)
97 REAL, DIMENSION(SIZE(PLITTER,1),SIZE(PLITTER,2),SIZE(PLITTER,3)) :: zlitter_inc
98 ! lignin increase in structural litter, above and below ground (gC/m**2)
99 REAL, DIMENSION(SIZE(PLITTER,1),SIZE(PLITTER,3)) :: zlignin_struc_inc
100 ! dimensions
101 INTEGER :: inlitter,inlittlevs
102 ! indices
103 INTEGER :: ini,ji,jl
104 !
105 REAL(KIND=JPRB) :: zhook_handle
106 !
107 ! correspondence between array indices and biomass compartments
108 ! LEAF = 1
109 ! STRUCT_ACT = 2
110 ! STRUCT_PAS = 3
111 ! STRUCT_BELOW = 4
112 ! WOOD_ABOVE = 5
113 ! WOOD_BELOW = 6
114 ! correspondence between array indices and litter type
115 ! LT_METABOLIC = 1
116 ! LT_STRUCTURAL = 2
117 ! correspondence between array indices and litter levels
118 ! LT_ABOVE = 1
119 ! LT_BELOW = 2
120 ! correspondence between array indices and soil carbon pools
121 ! SL_ACTIVE = 1
122 ! SL_SLOW = 2
123 ! SL_PASSIVE = 3
124 !-------------------------------------------------------------------------------
125 !
126 !* 1 Initialisations
127 !
128 !
129 !* 1.1 dimensions
130 !
131 IF (lhook) CALL dr_hook('CARBON_LITTER',0,zhook_handle)
132 !
133 ini = SIZE(plitter,1)
134 inlitter = SIZE(plitter,2)
135 inlittlevs = SIZE(plitter,3)
136 !
137 !* 1.2 set output to zero
138 !
139 presp_hetero_litter(:) = 0.0
140 psoilcarbon_input(:,:) = 0.0
141 !
142 !* 2 Add biomass to different litterpools
143 !
144 zdt = ptstep/xday
145 !
146 !* 2.1 first, save old structural litter (needed for lignin fractions).
147 ! (above/below)
148 !
149 zold_struc(:,:) = plitter(:,2,:)
150 !
151 ! * 2.2 update litter, and lignin content in structural litter
152 !
153 zlitter_inc(:,:,:) = 0.0
154 zlignin_struc_inc(:,:) = 0.0
155 !
156 !* 2.2.1 calculate litter increase (per m**2 of ground).
157 ! Litter increase for structural and metabolic, above/below
158 !
159 zlitter_inc(:,1,1) = ( xfrac_litter(1,1) * pturnover(:,1) + &
160  xfrac_litter(2,1) * pturnover(:,2) + &
161  xfrac_litter(3,1) * pturnover(:,3) + &
162  xfrac_litter(5,1) * pturnover(:,5) ) * ptstep
163 
164 zlitter_inc(:,1,2) = ( xfrac_litter(4,1) * pturnover(:,4) + &
165  xfrac_litter(6,1) * pturnover(:,6) ) * ptstep
166 !
167 zlitter_inc(:,2,1) = ( xfrac_litter(1,2) * pturnover(:,1) + &
168  xfrac_litter(2,2) * pturnover(:,2) + &
169  xfrac_litter(3,2) * pturnover(:,3) + &
170  xfrac_litter(5,2) * pturnover(:,5) ) * ptstep
171 
172 zlitter_inc(:,2,2) = ( xfrac_litter(4,2) * pturnover(:,4) + &
173  xfrac_litter(6,2) * pturnover(:,6) ) * ptstep
174 !
175 !* 2.2.2 lignin increase in structural litter
176 !
177 zlignin_struc_inc(:,1) = zlignin_struc_inc(:,1) + ( xlc(1)*pturnover(:,1) + xlc(2)*pturnover(:,2) + &
178  xlc(3)*pturnover(:,3) + xlc(5)*pturnover(:,5) ) * ptstep
179 zlignin_struc_inc(:,2) = zlignin_struc_inc(:,2) + ( xlc(4)*pturnover(:,4) + xlc(6)*pturnover(:,6) ) * ptstep
180 !
181 !* 2.2.3 add new litter (struct/met, above/below)
182 !
183 plitter(:,:,:) = plitter(:,:,:) + zlitter_inc(:,:,:)
184 !
185 !* 2.2.4 for security: can't add more lignin than structural litter
186 ! (above/below)
187 !
188 zlignin_struc_inc(:,:) = min( zlignin_struc_inc(:,:), zlitter_inc(:,2,:) )
189 !
190 !* 2.2.5 new lignin content: add old lignin and lignin increase, divide by
191 ! total structural litter (above/below)
192 !
193 WHERE(plitter(:,2,:)>0.0)
194  plignin_struc(:,:) = (plignin_struc(:,:)*zold_struc(:,:)+zlignin_struc_inc(:,:))/plitter(:,2,:)
195 ENDWHERE
196 !
197 !* 3 fluxes from litter to carbon pools and respiration
198 !
199 DO jl=1,inlittlevs
200  DO ji=1,ini
201 !
202 !* 3.1 structural litter: goes into active and slow carbon pools + respiration
203 !
204 !* 3.1.1 total quantity of structural litter which is decomposed
205 !
206  zfd=ptstep/xtau_litter(2)*pcontrol_temp(ji,jl)*pcontrol_moist(ji,jl)*exp(-3.0*plignin_struc(ji,jl))
207 !
208  zqd=plitter(ji,2,jl)*zfd
209 !
210  plitter(ji,2,jl)=plitter(ji,2,jl)-zqd
211 !
212 !* 3.1.2 non-lignin fraction of structural litter goes into active carbon pool + respiration
213 !
214  psoilcarbon_input(ji,1)=psoilcarbon_input(ji,1)+xfrac_soilcarb(2,1,jl)*zqd*(1.0-plignin_struc(ji,jl))/zdt
215 !
216  presp_hetero_litter(ji)=presp_hetero_litter(ji)+(1.0-xfrac_soilcarb(2,1,jl))*zqd*(1.0-plignin_struc(ji,jl))/zdt
217 !
218 !* 3.1.3 lignin fraction of structural litter goes into slow carbon pool + respiration
219 !
220  psoilcarbon_input(ji,2)=psoilcarbon_input(ji,2)+xfrac_soilcarb(2,2,jl)*zqd*plignin_struc(ji,jl)/zdt
221 !
222  presp_hetero_litter(ji)=presp_hetero_litter(ji)+(1.0-xfrac_soilcarb(2,2,jl))*zqd*plignin_struc(ji,jl)/zdt
223 !
224 !* 3.2 metabolic litter goes into active carbon pool + respiration
225 !
226 !* 3.2.1 total quantity of metabolic litter that is decomposed
227 !
228  zfd = ptstep/xtau_litter(1)*pcontrol_temp(ji,jl)*pcontrol_moist(ji,jl)
229 !
230  zqd = plitter(ji,1,jl)*zfd
231 !
232  plitter(ji,1,jl)=plitter(ji,1,jl)-zqd
233 !
234 !* 3.2.2 put decomposed litter into carbon pool + respiration
235 !
236  psoilcarbon_input(ji,1)=psoilcarbon_input(ji,1)+xfrac_soilcarb(1,1,jl)*zqd/zdt
237 !
238  presp_hetero_litter(ji) = presp_hetero_litter(ji)+(1.0-xfrac_soilcarb(1,1,jl))*zqd/zdt
239 !
240  ENDDO
241 ENDDO
242 !
243 IF (lhook) CALL dr_hook('CARBON_LITTER',1,zhook_handle)
244 
245 !
246 END SUBROUTINE carbon_litter
subroutine carbon_litter(PTSTEP, PTURNOVER, PLITTER, PLIGNIN_STRUC, PCONTROL_TEMP, PCONTROL_MOIST, PRESP_HETERO_LITTER, PSOILCARBON_INPUT)