source: tags/ORCHIDEE_1_9_5/ORCHIDEE/src_stomate/stomate_soilcarbon.f90 @ 8

Last change on this file since 8 was 8, checked in by orchidee, 14 years ago

import first tag equivalent to CVS orchidee_1_9_5 + OOL_1_9_5

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