SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
carbon_soil.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_soil (PTSTEP, PSAND, &
7  psoilcarbon_input, pcontrol_temp, pcontrol_moist, &
8  psoilcarb, presp_hetero_soil)
9 
10 ! ###############################################################
11 !!** CARBON_SOIL
12 !!
13 !! PURPOSE
14 !! -------
15 !! Calculates soil carbon pools 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 : xtau_soilcarb
52 USE modd_csts, ONLY : xday
53 !
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 IMPLICIT NONE
59 
60 
61 !* 0.1 input
62 
63 ! time step in s
64 REAL, INTENT(IN) :: ptstep
65 ! sand fraction (between 0 and 1)
66 REAL, DIMENSION(:), INTENT(IN) :: psand
67 ! quantity of carbon going into carbon pools from litter decomposition
68 ! (gC/m**2/day)
69 REAL, DIMENSION(:,:), INTENT(IN) :: psoilcarbon_input
70 ! temperature control of heterotrophic respiration
71 REAL, DIMENSION(:,:), INTENT(IN) :: pcontrol_temp
72 ! moisture control of heterotrophic respiration
73 REAL, DIMENSION(:,:), INTENT(IN) :: pcontrol_moist
74 
75 !* 0.2 modified fields
76 
77 ! carbon pool: active, slow, or passive (gC/m**2)
78 REAL, DIMENSION(:,:), INTENT(INOUT) :: psoilcarb
79 
80 !* 0.3 output
81 
82 ! soil heterotrophic respiration (in gC/day/m**2)
83 REAL, DIMENSION(:), INTENT(OUT) :: presp_hetero_soil
84 
85 !* 0.4 local
86 
87 ! time step in days
88 REAL :: zdt
89 ! flux fractions within carbon pools
90 REAL, DIMENSION(SIZE(PSOILCARB,1),SIZE(PSOILCARB,2),SIZE(PSOILCARB,2)) :: zfrac_carb
91 ! fraction of carbon flux which goes into heterotrophic respiration
92 REAL, DIMENSION(SIZE(PSOILCARB,1),SIZE(PSOILCARB,2)) :: zfrac_resp
93 ! total flux out of carbon pools (gC/m**2)
94 REAL, DIMENSION(SIZE(PSOILCARB,1),SIZE(PSOILCARB,2)) :: zfluxtot
95 ! fluxes between carbon pools (gC/m**2)
96 REAL, DIMENSION(SIZE(PSOILCARB,1),SIZE(PSOILCARB,2),SIZE(PSOILCARB,2)) :: zflux
97 !
98 REAL, DIMENSION(SIZE(PSOILCARB,1)) :: zwork ! Work array
99 !
100 ! dimensions
101 INTEGER :: ini, insoilcarb
102 ! indices
103 INTEGER :: ji, jl
104 REAL(KIND=JPRB) :: zhook_handle
105 !
106 ! correspondence between array indices and litter levels
107 ! LT_ABOVE = 1
108 ! LT_BELOW = 2
109 ! correspondence between array indices and soil carbon pools
110 ! SL_ACTIVE = 1
111 ! SL_SLOW = 2
112 ! SL_PASSIVE = 3
113 !-------------------------------------------------------------------------------
114 
115 !
116 !* 1 Initialisations
117 !
118 !
119 !* 1.1 dimensions
120 !
121 IF (lhook) CALL dr_hook('CARBON_SOIL',0,zhook_handle)
122 !
123 ini = SIZE(psoilcarb,1)
124 insoilcarb = SIZE(psoilcarb,2)
125 !
126 !* 1.2 get soil "constants"
127 !
128 !* 1.2.1 flux fractions between carbon pools: depend on soil texture, recalculated each time
129 !
130 !* 1.2.1.1 from active pool: depends on soil texture
131 !
132 zfrac_carb(:,1,1) = 0.0
133 zfrac_carb(:,1,3) = 0.004
134 zfrac_carb(:,1,2) = 1. - ( .85 - .68 * (1.-psand(:)) ) - zfrac_carb(:,1,3)
135 !
136 !* 1.2.1.2 from slow pool
137 !
138 zfrac_carb(:,2,2) = .0
139 zfrac_carb(:,2,1) = .42
140 zfrac_carb(:,2,3) = .03
141 !
142 !* 1.2.1.3 from passive pool
143 !
144 zfrac_carb(:,3,3) = .0
145 zfrac_carb(:,3,1) = .45
146 zfrac_carb(:,3,2) = .0
147 !
148 !* 1.3 set output to zero
149 !
150 presp_hetero_soil(:) = 0.0
151 !
152 !
153 !* 2 input into carbon pools
154 !
155 zdt = ptstep/xday
156 !
157 psoilcarb(:,:) = psoilcarb(:,:) + psoilcarbon_input(:,:) * zdt
158 !
159 !
160 !* 3 fluxes within carbon reservoirs + respiration
161 !
162 !* 3.1 determine fraction of flux that is respiration
163 ! diagonal elements of frac_carb are zero
164 !
165 zfrac_resp(:,:) = 1. - zfrac_carb(:,:,1) - zfrac_carb(:,:,2) - zfrac_carb(:,:,3)
166 !
167 !* 3.2 calculate fluxes
168 !
169 !* 3.2.1 flux out of pools
170 !
171 !soil property dependance (1.0-0.75*(1.0-PSAND(:)))
172 zwork(:)=0.25+0.75*psand(:)
173 !
174 ! determine total flux out of pool
175 zfluxtot(:,1) = ptstep/xtau_soilcarb(1)*psoilcarb(:,1)*pcontrol_moist(:,2)*pcontrol_temp(:,2)*zwork(:)
176 zfluxtot(:,2) = ptstep/xtau_soilcarb(2)*psoilcarb(:,2)*pcontrol_moist(:,2)*pcontrol_temp(:,2)
177 zfluxtot(:,3) = ptstep/xtau_soilcarb(3)*psoilcarb(:,3)*pcontrol_moist(:,2)*pcontrol_temp(:,2)
178 !
179 !decrease this carbon pool
180 psoilcarb(:,:) = psoilcarb(:,:) - zfluxtot(:,:)
181 !
182 !fluxes towards the other pools (k -> kk)
183 DO jl=1,insoilcarb
184  DO ji=1,ini
185  zflux(ji,1,jl) = zfrac_carb(ji,1,jl) * zfluxtot(ji,1)
186  zflux(ji,2,jl) = zfrac_carb(ji,2,jl) * zfluxtot(ji,2)
187  zflux(ji,3,jl) = zfrac_carb(ji,3,jl) * zfluxtot(ji,3)
188  ENDDO
189 ENDDO
190 !
191 !* 3.2.2 respiration
192 !
193 presp_hetero_soil(:) = ( zfrac_resp(:,1) * zfluxtot(:,1) + &
194  zfrac_resp(:,2) * zfluxtot(:,2) + &
195  zfrac_resp(:,3) * zfluxtot(:,3) ) / zdt
196 !
197 !* 3.2.3 add fluxes to active, slow, and passive pools
198 !
199 psoilcarb(:,1) = psoilcarb(:,1) + zflux(:,1,1) + zflux(:,2,1) + zflux(:,3,1)
200 psoilcarb(:,2) = psoilcarb(:,2) + zflux(:,1,2) + zflux(:,2,2) + zflux(:,3,2)
201 psoilcarb(:,3) = psoilcarb(:,3) + zflux(:,1,3) + zflux(:,2,3) + zflux(:,3,3)
202 !
203 IF (lhook) CALL dr_hook('CARBON_SOIL',1,zhook_handle)
204 !
205 END SUBROUTINE carbon_soil
subroutine carbon_soil(PTSTEP, PSAND, PSOILCARBON_INPUT, PCONTROL_TEMP, PCONTROL_MOIST, PSOILCARB, PRESP_HETERO_SOIL)
Definition: carbon_soil.F90:6