source: branches/publications/ORCHIDEE_2.2_r7266/ORCHIDEE/src_stomate/stomate_soilcarbon.f90 @ 7541

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 21.2 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_soilcarbon
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       Calculate soil dynamics largely following the Century model
10!!     
11!!\n DESCRIPTION: None
12!!
13!! RECENT CHANGE(S): None
14!!
15!! SVN          :
16!! $HeadURL: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_soilcarbon.f90 $
17!! $Date: 2018-01-24 08:45:20 +0100 (Wed, 24 Jan 2018) $
18!! $Revision: 4906 $
19!! \n
20!_ ================================================================================================================================
21
22MODULE stomate_soilcarbon
23
24  ! modules used:
25
26  USE ioipsl_para
27  USE stomate_data
28  USE constantes
29  USE xios_orchidee
30
31  IMPLICIT NONE
32
33  ! private & public routines
34
35  PRIVATE
36  PUBLIC soilcarbon,soilcarbon_clear
37
38  ! Variables shared by all subroutines in this module
39 
40  LOGICAL, SAVE    :: firstcall_soilcarbon = .TRUE.   !! Is this the first call? (true/false)
41!$OMP THREADPRIVATE(firstcall_soilcarbon)
42
43CONTAINS
44
45
46!! ================================================================================================================================
47!!  SUBROUTINE   : soilcarbon_clear
48!!
49!>\BRIEF        Set the flag ::firstcall_soilcarbon to .TRUE. and as such activate sections 1.1.2 and 1.2 of the subroutine soilcarbon
50!! (see below).
51!!
52!_ ================================================================================================================================
53 
54  SUBROUTINE soilcarbon_clear
55    firstcall_soilcarbon=.TRUE.
56  ENDSUBROUTINE soilcarbon_clear
57
58
59!! ================================================================================================================================
60!!  SUBROUTINE   : soilcarbon
61!!
62!>\BRIEF        Computes the soil respiration and carbon stocks, essentially
63!! following Parton et al. (1987).
64!!
65!! DESCRIPTION  : The soil is divided into 3 carbon pools, with different
66!! characteristic turnover times : active (1-5 years), slow (20-40 years)
67!! and passive (200-1500 years).\n
68!! There are three types of carbon transferred in the soil:\n
69!! - carbon input in active and slow pools from litter decomposition,\n
70!! - carbon fluxes between the three pools,\n
71!! - carbon losses from the pools to the atmosphere, i.e., soil respiration.\n
72!!
73!! The subroutine performs the following tasks:\n
74!!
75!! Section 1.\n
76!! The flux fractions (f) between carbon pools are defined based on Parton et
77!! al. (1987). The fractions are constants, except for the flux fraction from
78!! the active pool to the slow pool, which depends on the clay content,\n
79!! \latexonly
80!! \input{soilcarbon_eq1.tex}
81!! \endlatexonly\n
82!! In addition, to each pool is assigned a constant turnover time.\n
83!!
84!! Section 2.\n
85!! The carbon input, calculated in the stomate_litter module, is added to the
86!! carbon stock of the different pools.\n
87!!
88!! Section 3.\n
89!! First, the outgoing carbon flux of each pool is calculated. It is
90!! proportional to the product of the carbon stock and the ratio between the
91!! iteration time step and the residence time:\n
92!! \latexonly
93!! \input{soilcarbon_eq2.tex}
94!! \endlatexonly
95!! ,\n
96!! Note that in the case of crops, the additional multiplicative factor
97!! integrates the faster decomposition due to tillage (following Gervois et
98!! al. (2008)).
99!! In addition, the flux from the active pool depends on the clay content:\n
100!! \latexonly
101!! \input{soilcarbon_eq3.tex}
102!! \endlatexonly
103!! ,\n
104!! Each pool is then cut from the carbon amount corresponding to each outgoing
105!! flux:\n
106!! \latexonly
107!! \input{soilcarbon_eq4.tex}
108!! \endlatexonly\n
109!! Second, the flux fractions lost to the atmosphere is calculated in each pool
110!! by subtracting from 1 the pool-to-pool flux fractions. The soil respiration
111!! is then the summed contribution of all the pools,\n
112!! \latexonly
113!! \input{soilcarbon_eq5.tex}
114!! \endlatexonly\n
115!! Finally, each carbon pool accumulates the contribution of the other pools:
116!! \latexonly
117!! \input{soilcarbon_eq6.tex}
118!! \endlatexonly
119!!
120!! Section 4.\n
121!! If the flag SPINUP_ANALYTIC is set to true, the matrix A is updated following
122!! Lardy (2011).
123!!
124!! RECENT CHANGE(S): None
125!!
126!! MAIN OUTPUTS VARIABLE(S): carbon, resp_hetero_soil
127!!
128!! REFERENCE(S)   :
129!! - Parton, W.J., D.S. Schimel, C.V. Cole, and D.S. Ojima. 1987. Analysis of
130!! factors controlling soil organic matter levels in Great Plains grasslands.
131!! Soil Sci. Soc. Am. J., 51, 1173-1179.
132!! - Gervois, S., P. Ciais, N. de Noblet-Ducoudre, N. Brisson, N. Vuichard,
133!! and N. Viovy (2008), Carbon and water balance of European croplands
134!! throughout the 20th century, Global Biogeochem. Cycles, 22, GB2022,
135!! doi:10.1029/2007GB003018.
136!! - Lardy, R, et al., A new method to determine soil organic carbon equilibrium,
137!! Environmental Modelling & Software (2011), doi:10.1016|j.envsoft.2011.05.016
138!!
139!! FLOWCHART    :
140!! \latexonly
141!! \includegraphics[scale=0.5]{soilcarbon_flowchart.jpg}
142!! \endlatexonly
143!! \n
144!_ ================================================================================================================================
145
146  SUBROUTINE soilcarbon (npts, clay, &
147       soilcarbon_input, control_temp, control_moist, veget_cov_max, &
148       carbon, resp_hetero_soil, MatrixA)
149
150!! 0. Variable and parameter declaration
151
152    !! 0.1 Input variables
153   
154    INTEGER(i_std), INTENT(in)                            :: npts             !! Domain size (unitless)
155    REAL(r_std), DIMENSION(npts), INTENT(in)              :: clay             !! Clay fraction (unitless, 0-1)
156    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(in)    :: soilcarbon_input !! Amount of carbon going into the carbon pools from litter decomposition \f$(gC m^{-2} day^{-1})$\f
157    REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)        :: control_temp     !! Temperature control of heterotrophic respiration (unitless: 0->1)
158    REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)        :: control_moist    !! Moisture control of heterotrophic respiration (unitless: 0.25->1)
159    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)          :: veget_cov_max    !! Fractional coverage: maximum share of the pixel taken by a pft
160
161    !! 0.2 Output variables
162   
163    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)         :: resp_hetero_soil !! Soil heterotrophic respiration \f$(gC m^{-2} (dt_sechiba one_day^{-1})^{-1})$\f
164
165    !! 0.3 Modified variables
166   
167    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout) :: carbon             !! Soil carbon pools: active, slow, or passive, \f$(gC m^{2})$\f
168    REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(inout) :: MatrixA  !! Matrix containing the fluxes between the carbon pools
169                                                                                !! per sechiba time step
170                                                                                !! @tex $(gC.m^2.day^{-1})$ @endtex
171
172    !! 0.4 Local variables
173    REAL(r_std)                                           :: dt               !! Time step \f$(dt_sechiba one_day^{-1})$\f
174    REAL(r_std), SAVE, DIMENSION(ncarb)                   :: carbon_tau       !! Residence time in carbon pools (days)
175!$OMP THREADPRIVATE(carbon_tau)
176    REAL(r_std), DIMENSION(npts,ncarb,ncarb)              :: frac_carb        !! Flux fractions between carbon pools
177                                                                              !! (second index=origin, third index=destination)
178                                                                              !! (unitless, 0-1)
179    REAL(r_std), DIMENSION(npts,ncarb)                    :: frac_resp        !! Flux fractions from carbon pools to the atmosphere (respiration) (unitless, 0-1)
180    REAL(r_std), DIMENSION(npts,ncarb,nelements)          :: fluxtot          !! Total flux out of carbon pools \f$(gC m^{2})$\f
181    REAL(r_std), DIMENSION(npts,ncarb,ncarb,nelements)    :: flux             !! Fluxes between carbon pools \f$(gC m^{2})$\f
182    CHARACTER(LEN=7), DIMENSION(ncarb)                    :: carbon_str       !! Name of the carbon pools for informative outputs (unitless)
183    INTEGER(i_std)                                        :: k,kk,m,j,ij      !! Indices (unitless)
184    REAL(r_std), DIMENSION(npts,nvm,ncarb)                :: decomp_rate_soilcarbon !! Decomposition rate of the soil carbon pools (s)
185    REAL(r_std), DIMENSION(npts,ncarb)                    :: tsoilpools       !! Diagnostic for soil carbon turnover rate by pool (1/s)
186
187!_ ================================================================================================================================
188
189    !! printlev is the level of diagnostic information, 0 (none) to 4 (full)
190    IF (printlev>=3) WRITE(numout,*) 'Entering soilcarbon' 
191
192!! 1. Initializations
193    dt = dt_sechiba/one_day
194    !! 1.1 Get soil "constants"
195    !! 1.1.1 Flux fractions between carbon pools: depend on clay content, recalculated each time
196    ! From active pool: depends on clay content
197    frac_carb(:,iactive,iactive) = zero
198    frac_carb(:,iactive,ipassive) = frac_carb_ap
199    frac_carb(:,iactive,islow) = un - (metabolic_ref_frac - active_to_pass_clay_frac*clay(:)) - frac_carb(:,iactive,ipassive)
200
201    ! 1.1.1.2 from slow pool
202
203    frac_carb(:,islow,islow) = zero
204    frac_carb(:,islow,iactive) = frac_carb_sa
205    frac_carb(:,islow,ipassive) = frac_carb_sp
206
207    ! From passive pool
208    frac_carb(:,ipassive,ipassive) = zero
209    frac_carb(:,ipassive,iactive) = frac_carb_pa
210    frac_carb(:,ipassive,islow) = frac_carb_ps
211
212    IF ( firstcall_soilcarbon ) THEN
213
214        !! 1.1.2 Residence times in carbon pools (days)
215        carbon_tau(iactive) = carbon_tau_iactive * one_year       ! 1.5 years. This is same as CENTURY. But, in Parton et al. (1987), it's weighted by moisture and temperature dependences.
216        carbon_tau(islow) = carbon_tau_islow * one_year          ! 25 years. This is same as CENTURY. But, in Parton et al. (1987), it's weighted by moisture and temperature dependences.
217        carbon_tau(ipassive) = carbon_tau_ipassive * one_year       ! 1000 years. This is same as CENTURY. But, in Parton et al. (1987), it's weighted by moisture and temperature dependences.
218       
219        !! 1.2 Messages : display the residence times 
220        carbon_str(iactive) = 'active'
221        carbon_str(islow) = 'slow'
222        carbon_str(ipassive) = 'passive'
223       
224        IF (printlev >= 2) THEN
225           WRITE(numout,*) 'soilcarbon:'
226           WRITE(numout,*) '   > minimal carbon residence time in carbon pools (d):'
227           DO k = 1, ncarb ! Loop over carbon pools
228              WRITE(numout,*) '(1, ::carbon_str(k)):',carbon_str(k),' : (1, ::carbon_tau(k)):',carbon_tau(k)
229           ENDDO
230           WRITE(numout,*) '   > flux fractions between carbon pools: depend on clay content'
231        END IF
232        firstcall_soilcarbon = .FALSE.
233       
234    ENDIF
235
236    !! 1.3 Set soil respiration and decomposition rate to zero
237    resp_hetero_soil(:,:) = zero
238    decomp_rate_soilcarbon(:,:,:) = zero
239
240!! 2. Update the carbon stocks with the different soil carbon input
241
242    carbon(:,:,:) = carbon(:,:,:) + soilcarbon_input(:,:,:) * dt
243
244!! 3. Fluxes between carbon reservoirs, and to the atmosphere (respiration) \n
245
246    !! 3.1. Determine the respiration fraction : what's left after
247    ! subtracting all the 'pool-to-pool' flux fractions
248    ! Diagonal elements of frac_carb are zero
249    !    VPP killer:
250    !     frac_resp(:,:) = 1. - SUM( frac_carb(:,:,:), DIM=3 )
251    frac_resp(:,:) = un - frac_carb(:,:,iactive) - frac_carb(:,:,islow) - &
252         frac_carb(:,:,ipassive) 
253
254    !! 3.2. Calculate fluxes
255
256    DO m = 1, nvm ! Loop over # PFTs
257
258      !! 3.2.1. Flux out of pools
259
260      DO k = 1, ncarb ! Loop over carbon pools from which the flux comes
261       
262        ! Determine total flux out of pool
263        ! S.L. Piao 2006/05/05 - for crop multiply tillage factor of decomposition
264        ! Not crop
265         IF ( natural(m) ) THEN
266            fluxtot(:,k,icarbon) = dt/carbon_tau(k) * carbon(:,k,m) * &
267                  control_moist(:,ibelow) * control_temp(:,ibelow)
268
269            decomp_rate_soilcarbon(:,m,k)=dt/carbon_tau(k) * &
270                      control_moist(:,ibelow) * control_temp(:,ibelow)
271         ! C3 crop
272          ELSEIF ( (.NOT. natural(m)) .AND. (.NOT. is_c4(m)) ) THEN
273             fluxtot(:,k,icarbon) = dt/carbon_tau(k) * carbon(:,k,m) * &
274                  control_moist(:,ibelow) * control_temp(:,ibelow) * flux_tot_coeff(1)
275             decomp_rate_soilcarbon(:,m,k)=dt/carbon_tau(k) * &
276                       control_moist(:,ibelow) * control_temp(:,ibelow)*flux_tot_coeff(1)
277          ! C4 Crop   
278          ELSEIF ( (.NOT. natural(m)) .AND. is_c4(m) ) THEN
279             fluxtot(:,k,icarbon) = dt/carbon_tau(k) * carbon(:,k,m) * &
280                  control_moist(:,ibelow) * control_temp(:,ibelow) * flux_tot_coeff(2)
281             decomp_rate_soilcarbon(:,m,k)=dt/carbon_tau(k) * &
282                       control_moist(:,ibelow) *control_temp(:,ibelow)*flux_tot_coeff(2)
283        ENDIF
284        ! END - S.L. Piao 2006/05/05 - for crop multiply tillage factor of decomposition
285
286        ! Carbon flux from active pools depends on clay content
287        IF ( k .EQ. iactive ) THEN
288            fluxtot(:,k,icarbon) = fluxtot(:,k,icarbon) * ( un - flux_tot_coeff(3) * clay(:) )
289            decomp_rate_soilcarbon(:,m,k)=decomp_rate_soilcarbon(:,m,k)* ( un - flux_tot_coeff(3) * clay(:) ) 
290        ENDIF
291       
292        ! Update the loss in each carbon pool
293        carbon(:,k,m) = carbon(:,k,m) - fluxtot(:,k,icarbon)
294       
295        ! Fluxes towards the other pools (k -> kk)
296        DO kk = 1, ncarb ! Loop over the carbon pools where the flux goes
297          flux(:,k,kk,icarbon) = frac_carb(:,k,kk) * fluxtot(:,k,icarbon)
298        ENDDO
299      ENDDO ! End of loop over carbon pools
300     
301      !! 3.2.2 respiration
302      !BE CAREFUL: Here resp_hetero_soil is divided by dt to have a value which corresponds to
303      ! the sechiba time step but then in stomate.f90 resp_hetero_soil is multiplied by dt.
304      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dt_sechiba/one_day
305      ! time step and avoid some constructions that could create bug during future developments.
306      !
307      !       VPP killer:
308      !       resp_hetero_soil(:,m) = SUM( frac_resp(:,:) * fluxtot(:,:), DIM=2 ) / dt
309     
310      resp_hetero_soil(:,m) = &
311         ( frac_resp(:,iactive) * fluxtot(:,iactive,icarbon) + &
312         frac_resp(:,islow) * fluxtot(:,islow,icarbon) + &
313         frac_resp(:,ipassive) * fluxtot(:,ipassive,icarbon)  ) / dt
314     
315      !! 3.2.3 add fluxes to active, slow, and passive pools
316      !       VPP killer:
317      !       carbon(:,:,m) = carbon(:,:,m) + SUM( flux(:,:,:), DIM=2 )
318     
319      DO k = 1, ncarb ! Loop over carbon pools
320        carbon(:,k,m) = carbon(:,k,m) + &
321           flux(:,iactive,k,icarbon) + flux(:,ipassive,k,icarbon) + flux(:,islow,k,icarbon)
322      ENDDO ! Loop over carbon pools
323     
324    ENDDO ! End loop over PFTs
325   
326 !! 4. (Quasi-)Analytical Spin-up
327   
328    !! 4.1.1 Finish to fill MatrixA with fluxes between soil pools
329   
330    IF (spinup_analytic) THEN
331
332       DO m = 2,nvm 
333
334          ! flux leaving the active pool
335          MatrixA(:,m,iactive_pool,iactive_pool) = moins_un * &
336               dt/carbon_tau(iactive) * &
337               control_moist(:,ibelow) * control_temp(:,ibelow) * &
338               ( 1. - flux_tot_coeff(3) * clay(:)) 
339
340          ! flux received by the active pool from the slow pool
341          MatrixA(:,m,iactive_pool,islow_pool) =  frac_carb(:,islow,iactive)*dt/carbon_tau(islow) * &
342               control_moist(:,ibelow) * control_temp(:,ibelow)
343
344          ! flux received by the active pool from the passive pool
345          MatrixA(:,m,iactive_pool,ipassive_pool) =  frac_carb(:,ipassive,iactive)*dt/carbon_tau(ipassive) * &
346               control_moist(:,ibelow) * control_temp(:,ibelow) 
347
348          ! flux received by the slow pool from the active pool
349          MatrixA(:,m,islow_pool,iactive_pool) =  frac_carb(:,iactive,islow) *&
350               dt/carbon_tau(iactive) * &
351               control_moist(:,ibelow) * control_temp(:,ibelow) * &
352               ( 1. - flux_tot_coeff(3) * clay(:) ) 
353
354          ! flux leaving the slow pool
355          MatrixA(:,m,islow_pool,islow_pool) = moins_un * &
356               dt/carbon_tau(islow) * &
357               control_moist(:,ibelow) * control_temp(:,ibelow)
358
359          ! flux received by the passive pool from the active pool
360          MatrixA(:,m,ipassive_pool,iactive_pool) =  frac_carb(:,iactive,ipassive)* &
361               dt/carbon_tau(iactive) * &
362               control_moist(:,ibelow) * control_temp(:,ibelow) *&
363               ( 1. - flux_tot_coeff(3) * clay(:) )
364
365          ! flux received by the passive pool from the slow pool
366          MatrixA(:,m,ipassive_pool,islow_pool) =  frac_carb(:,islow,ipassive) * &
367               dt/carbon_tau(islow) * &
368               control_moist(:,ibelow) * control_temp(:,ibelow)
369
370          ! flux leaving the passive pool
371          MatrixA(:,m,ipassive_pool,ipassive_pool) =  moins_un * &
372               dt/carbon_tau(ipassive) * &
373               control_moist(:,ibelow) * control_temp(:,ibelow)     
374
375
376          IF ( (.NOT. natural(m)) .AND. (.NOT. is_c4(m)) ) THEN ! C3crop
377
378             ! flux leaving the active pool
379             MatrixA(:,m,iactive_pool,iactive_pool) = MatrixA(:,m,iactive_pool,iactive_pool) * &
380                  flux_tot_coeff(1) 
381
382             ! flux received by the active pool from the slow pool
383             MatrixA(:,m,iactive_pool,islow_pool)= MatrixA(:,m,iactive_pool,islow_pool) * &
384                  flux_tot_coeff(1) 
385
386             ! flux received by the active pool from the passive pool
387             MatrixA(:,m,iactive_pool,ipassive_pool) = MatrixA(:,m,iactive_pool,ipassive_pool) * &
388                  flux_tot_coeff(1)   
389
390             ! flux received by the slow pool from the active pool
391             MatrixA(:,m,islow_pool,iactive_pool) =  MatrixA(:,m,islow_pool,iactive_pool) * &
392                  flux_tot_coeff(1) 
393
394             ! flux leaving the slow pool
395             MatrixA(:,m,islow_pool,islow_pool) = MatrixA(:,m,islow_pool,islow_pool) * &
396                  flux_tot_coeff(1)     
397
398             ! flux received by the passive pool from the active pool
399             MatrixA(:,m,ipassive_pool,iactive_pool) = MatrixA(:,m,ipassive_pool,iactive_pool) * &
400                  flux_tot_coeff(1)
401
402             ! flux received by the passive pool from the slow pool
403             MatrixA(:,m,ipassive_pool,islow_pool) = MatrixA(:,m,ipassive_pool,islow_pool) * &
404                  flux_tot_coeff(1)
405
406             ! flux leaving the passive pool
407             MatrixA(:,m,ipassive_pool,ipassive_pool) =  MatrixA(:,m,ipassive_pool,ipassive_pool) *&
408                  flux_tot_coeff(1)
409
410          ENDIF ! (.NOT. natural(m)) .AND. (.NOT. is_c4(m))
411
412
413          IF ( (.NOT. natural(m)) .AND. is_c4(m) ) THEN ! C4crop
414
415             ! flux leaving the active pool
416             MatrixA(:,m,iactive_pool,iactive_pool) = MatrixA(:,m,iactive_pool,iactive_pool) * &
417                  flux_tot_coeff(2) 
418
419            ! flux received by the active pool from the slow pool
420             MatrixA(:,m,iactive_pool,islow_pool)= MatrixA(:,m,iactive_pool,islow_pool) * &
421                  flux_tot_coeff(2) 
422
423             ! flux received by the active pool from the passive pool
424             MatrixA(:,m,iactive_pool,ipassive_pool) = MatrixA(:,m,iactive_pool,ipassive_pool) * &
425                  flux_tot_coeff(2)   
426
427             ! flux received by the slow pool from the active pool
428             MatrixA(:,m,islow_pool,iactive_pool) =  MatrixA(:,m,islow_pool,iactive_pool) * &
429                  flux_tot_coeff(2) 
430
431             ! flux leaving the slow pool
432             MatrixA(:,m,islow_pool,islow_pool) = MatrixA(:,m,islow_pool,islow_pool) * &
433                  flux_tot_coeff(2)     
434
435             ! flux received by the passive pool from the active pool
436             MatrixA(:,m,ipassive_pool,iactive_pool) = MatrixA(:,m,ipassive_pool,iactive_pool) * &
437                  flux_tot_coeff(2)
438
439             ! flux received by the passive pool from the slow pool
440             MatrixA(:,m,ipassive_pool,islow_pool) = MatrixA(:,m,ipassive_pool,islow_pool) * &
441                  flux_tot_coeff(2)
442
443             ! flux leaving the passive pool
444             MatrixA(:,m,ipassive_pool,ipassive_pool) =  MatrixA(:,m,ipassive_pool,ipassive_pool) * &
445                  flux_tot_coeff(2)
446
447          ENDIF ! (.NOT. natural(m)) .AND. is_c4(m)
448
449          IF (printlev>=4) WRITE(numout,*)'Finish to fill MatrixA'
450
451       ENDDO ! Loop over # PFTS
452
453
454       ! 4.2 Add Identity for each submatrix(7,7)
455
456       DO j = 1,nbpools
457          MatrixA(:,:,j,j) = MatrixA(:,:,j,j) + un 
458       ENDDO
459
460    ENDIF ! (spinup_analytic)
461
462
463    ! Output diagnostics
464    DO k = 1, ncarb ! Loop over carbon pools
465       DO ij = 1, npts
466          IF (SUM(decomp_rate_soilcarbon(ij,:,k)*veget_cov_max(ij,:)) > min_sechiba) THEN
467             tsoilpools(ij,k) = 1./(SUM(decomp_rate_soilcarbon(ij,:,k)*veget_cov_max(ij,:))/dt_sechiba)
468          ELSE
469             tsoilpools(ij,k) = xios_default_val
470          END IF
471       END DO
472    END DO
473    CALL xios_orchidee_send_field("tSoilPools",tsoilpools)
474
475    IF (printlev>=4) WRITE(numout,*) 'Leaving soilcarbon'
476   
477  END SUBROUTINE soilcarbon
478
479END MODULE stomate_soilcarbon
Note: See TracBrowser for help on using the repository browser.