source: branches/ORCHIDEE_EXT/ORCHIDEE/src_stomate/stomate_soilcarbon.f90 @ 108

Last change on this file since 108 was 108, checked in by didier.solyga, 13 years ago

Replace the test by PFT_name by more general test for the computation of fluxtot

File size: 7.4 KB
Line 
1!
2! Soil dynamics. Essentially after Century.
3! FOR THE MOMENT, NO VERTICAL DISCRETISATION !!!!
4!
5! $Header: /home/ssipsl/CVSREP/ORCHIDEE/src_stomate/stomate_soilcarbon.f90,v 1.7 2009/01/06 17:18:32 ssipsl Exp $
6! IPSL (2006)
7!  This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9MODULE stomate_soilcarbon
10
11  ! modules used:
12
13  USE ioipsl
14  USE stomate_data
15  USE constantes
16
17  IMPLICIT NONE
18
19  ! private & public routines
20
21  PRIVATE
22  PUBLIC soilcarbon,soilcarbon_clear
23
24  ! first call
25  LOGICAL, SAVE                                                     :: firstcall = .TRUE.
26
27CONTAINS
28
29
30  SUBROUTINE soilcarbon_clear
31    firstcall=.TRUE.
32  ENDSUBROUTINE soilcarbon_clear
33
34  SUBROUTINE soilcarbon (npts, dt, clay, &
35       soilcarbon_input, control_temp, control_moist, &
36       carbon, &
37       resp_hetero_soil)
38
39    !
40    ! 0 declarations
41    !
42
43    ! 0.1 input
44
45    ! Domain size
46    INTEGER(i_std), INTENT(in)                                               :: npts
47    ! time step in days
48    REAL(r_std), INTENT(in)                                            :: dt
49    ! clay fraction (between 0 and 1)
50    REAL(r_std), DIMENSION(npts), INTENT(in)                           :: clay
51    ! quantity of carbon going into carbon pools from litter decomposition
52    !   (gC/(m**2 of ground)/day)
53    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(in)           :: soilcarbon_input
54    ! temperature control of heterotrophic respiration
55    REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)                     :: control_temp
56    ! moisture control of heterotrophic respiration
57    REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)                     :: control_moist
58
59    ! 0.2 modified fields
60
61    ! carbon pool: active, slow, or passive, (gC/m**2 of ground)
62    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout)        :: carbon
63
64    ! 0.3 output
65
66    ! soil heterotrophic respiration (first in gC/day/m**2 of ground )
67    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: resp_hetero_soil
68
69    ! 0.4 local
70
71    ! residence time in carbon pools (days)
72    REAL(r_std), SAVE, DIMENSION(ncarb)                                :: carbon_tau
73    ! flux fractions within carbon pools
74    REAL(r_std), DIMENSION(npts,ncarb,ncarb)                           :: frac_carb
75    ! fraction of carbon flux which goes into heterotrophic respiration
76    REAL(r_std), DIMENSION(npts,ncarb)                                 :: frac_resp
77    ! total flux out of carbon pools (gC/m**2)
78    REAL(r_std), DIMENSION(npts,ncarb)                                 :: fluxtot
79    ! fluxes between carbon pools (gC/m**2)
80    REAL(r_std), DIMENSION(npts,ncarb,ncarb)                           :: flux
81    ! for messages
82    CHARACTER*7, DIMENSION(ncarb)                                     :: carbon_str
83    ! Indices
84    INTEGER(i_std)                                                    :: k,kk,m
85
86    ! =========================================================================
87
88    IF (bavard.GE.3) WRITE(numout,*) 'Entering soilcarbon'
89
90    !
91    ! 1 initializations
92    !
93
94    !
95    ! 1.1 get soil "constants"
96    !
97
98    ! 1.1.1 flux fractions between carbon pools: depend on clay content, recalculated
99    !       each time
100
101    ! 1.1.1.1 from active pool: depends on clay content
102
103    frac_carb(:,iactive,iactive) = frac_carb_aa
104    frac_carb(:,iactive,ipassive) = frac_carb_ap
105    frac_carb(:,iactive,islow) = 1. - (metabolic_ref_frac - active_to_pass_clay_frac*clay(:)) - frac_carb(:,iactive,ipassive)
106
107
108    ! 1.1.1.2 from slow pool
109
110    frac_carb(:,islow,islow) = frac_carb_ss
111    frac_carb(:,islow,iactive) = frac_carb_sa
112    frac_carb(:,islow,ipassive) = frac_carb_sp
113
114
115    ! 1.1.1.3 from passive pool
116
117    frac_carb(:,ipassive,ipassive) = frac_carb_pp
118    frac_carb(:,ipassive,iactive) = frac_carb_pa
119    frac_carb(:,ipassive,islow) = frac_carb_ps
120
121
122
123    IF ( firstcall ) THEN
124
125       ! 1.1.2 residence times in carbon pools (days)
126
127       carbon_tau(iactive) = carbon_tau_iactive * one_year        !!!!???? 1.5 years
128       carbon_tau(islow) = carbon_tau_islow * one_year          !!!!???? 25 years
129       carbon_tau(ipassive) = carbon_tau_ipassive * one_year       !!!!???? 1000 years
130
131       !
132       ! 1.2 messages
133       !
134
135       carbon_str(iactive) = 'active'
136       carbon_str(islow) = 'slow'
137       carbon_str(ipassive) = 'passive'
138
139       WRITE(numout,*) 'soilcarbon:'
140
141       WRITE(numout,*) '   > minimal carbon residence time in carbon pools (d):'
142       DO k = 1, ncarb
143          WRITE(numout,*) '       ',carbon_str(k),':',carbon_tau(k)
144       ENDDO
145
146       WRITE(numout,*) '   > flux fractions between carbon pools: depend on clay content'
147
148       firstcall = .FALSE.
149
150    ENDIF
151
152    !
153    ! 1.3 set output to zero
154    !
155
156    resp_hetero_soil(:,:) = 0.0
157
158    !
159    ! 2 input into carbon pools
160    !
161
162    carbon(:,:,:) = carbon(:,:,:) + soilcarbon_input(:,:,:) * dt
163
164    !
165    ! 3 fluxes within carbon reservoirs + respiration
166    !
167
168    !
169    ! 3.1 determine fraction of flux that is respiration
170    !     diagonal elements of frac_carb are zero
171    !     VPP killer:
172    !     frac_resp(:,:) = 1. - SUM( frac_carb(:,:,:), DIM=3 )
173    !
174
175    frac_resp(:,:) = 1. - frac_carb(:,:,iactive) - frac_carb(:,:,islow) - &
176         frac_carb(:,:,ipassive) 
177
178    !
179    ! 3.2 calculate fluxes
180    !
181
182    DO m = 2,nvm
183
184       ! 3.2.1 flux out of pools
185
186       DO k = 1, ncarb
187
188          ! determine total flux out of pool
189          ! shilong060505 for crop multiply tillage factor of decomposition
190          IF ( natural(m) ) THEN
191             fluxtot(:,k) = dt/carbon_tau(k) * carbon(:,k,m) * &
192                  control_moist(:,ibelow) * control_temp(:,ibelow)
193!!$   DS       ELSEIF ( PFT_name(m)=='          C3           agriculture' ) THEN
194          ELSEIF ( (.NOT. natural(m)) .AND. (.NOT. is_c4(m)) ) THEN
195             fluxtot(:,k) = dt/carbon_tau(k) * carbon(:,k,m) * &
196                  control_moist(:,ibelow) * control_temp(:,ibelow) * flux_tot_coeff(1)
197!!$  DS         ELSEIF ( PFT_name(m)=='          C4           agriculture' ) THEN
198          ELSEIF ( (.NOT. natural(m)) .AND. is_c4(m) ) THEN
199             fluxtot(:,k) = dt/carbon_tau(k) * carbon(:,k,m) * &
200                  control_moist(:,ibelow) * control_temp(:,ibelow) * flux_tot_coeff(2)
201          ENDIF
202          ! end edit shilong
203          IF ( k .EQ. iactive ) THEN
204             fluxtot(:,k) = fluxtot(:,k) * ( 1. - flux_tot_coeff(3) * clay(:) )
205          ENDIF
206
207          ! decrease this carbon pool
208
209          carbon(:,k,m) = carbon(:,k,m) - fluxtot(:,k)
210
211          ! fluxes towards the other pools (k -> kk)
212
213          DO kk = 1, ncarb
214             flux(:,k,kk) = frac_carb(:,k,kk) * fluxtot(:,k)
215          ENDDO
216
217       ENDDO
218
219       ! 3.2.2 respiration
220       !       VPP killer:
221       !       resp_hetero_soil(:,m) = SUM( frac_resp(:,:) * fluxtot(:,:), DIM=2 ) / dt
222
223       resp_hetero_soil(:,m) = &
224            ( frac_resp(:,iactive) * fluxtot(:,iactive) + &
225            frac_resp(:,islow) * fluxtot(:,islow) + &
226            frac_resp(:,ipassive) * fluxtot(:,ipassive)  ) / dt
227
228       ! 3.2.3 add fluxes to active, slow, and passive pools
229       !       VPP killer:
230       !       carbon(:,:,m) = carbon(:,:,m) + SUM( flux(:,:,:), DIM=2 )
231
232       DO k = 1, ncarb
233          carbon(:,k,m) = carbon(:,k,m) + &
234               flux(:,iactive,k) + flux(:,ipassive,k) + flux(:,islow,k)
235       ENDDO
236
237    ENDDO
238
239    IF (bavard.GE.4) WRITE(numout,*) 'Leaving soilcarbon'
240
241  END SUBROUTINE soilcarbon
242
243END MODULE stomate_soilcarbon
Note: See TracBrowser for help on using the repository browser.