source: branches/publications/ORCHIDEE-MICT-OP-r6850/src_stomate/stomate_soilcarbon.f90 @ 8066

Last change on this file since 8066 was 5316, checked in by albert.jornet, 7 years ago

Merge: from revisions [4870:4964/trunk/ORCHIDEE]

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 21.0 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$
17!! $Date$
18!! $Revision$
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, dt, clay, &
147       soilcarbon_input, control_temp, control_moist, veget_cov_max, &
148       carbon, resp_hetero_soil, MatrixA)
149!gmjc
150!       resp_hetero_soil_part)
151!end gmjc
152
153!! 0. Variable and parameter declaration
154
155    !! 0.1 Input variables
156   
157    INTEGER(i_std), INTENT(in)                            :: npts             !! Domain size (unitless)
158    REAL(r_std), INTENT(in)                               :: dt               !! Time step
159    REAL(r_std), DIMENSION(npts), INTENT(in)              :: clay             !! Clay fraction (unitless, 0-1)
160    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
161    REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)        :: control_temp     !! Temperature control of heterotrophic respiration (unitless: 0->1)
162    REAL(r_std), DIMENSION(npts,nlevs), INTENT(in)        :: control_moist    !! Moisture control of heterotrophic respiration (unitless: 0.25->1)
163    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)          :: veget_cov_max    !! Fractional coverage: maximum share of the pixel taken by a pft
164
165    !! 0.2 Output variables
166   
167    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)         :: resp_hetero_soil !! Soil heterotrophic respiration \f$(gC m^{-2} dt^{-1})$\f
168
169    !! 0.3 Modified variables
170   
171    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(inout) :: carbon             !! Soil carbon pools: active, slow, or passive, \f$(gC m^{2})$\f
172    REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(inout) :: MatrixA  !! Matrix containing the fluxes between the carbon pools
173                                                                                !! per sechiba time step
174                                                                                !! @tex $(gC.m^2.day^{-1})$ @endtex
175!gmjc
176    !! 0.4 Local variables
177    REAL(r_std), SAVE, DIMENSION(ncarb)                   :: carbon_tau       !! Residence time in carbon pools (days)
178!$OMP THREADPRIVATE(carbon_tau)
179    REAL(r_std), DIMENSION(npts,ncarb,ncarb)              :: frac_carb        !! Flux fractions between carbon pools
180                                                                              !! (second index=origin, third index=destination)
181                                                                              !! (unitless, 0-1)
182    REAL(r_std), DIMENSION(npts,ncarb)                    :: frac_resp        !! Flux fractions from carbon pools to the atmosphere (respiration) (unitless, 0-1)
183    REAL(r_std), DIMENSION(npts,ncarb,nelements)          :: fluxtot          !! Total flux out of carbon pools \f$(gC m^{2})$\f
184    REAL(r_std), DIMENSION(npts,ncarb,ncarb,nelements)    :: flux             !! Fluxes between carbon pools \f$(gC m^{2})$\f
185    CHARACTER(LEN=7), DIMENSION(ncarb)                    :: carbon_str       !! Name of the carbon pools for informative outputs (unitless)
186    INTEGER(i_std)                                        :: k,kk,m,j,ij      !! Indices (unitless)
187    REAL(r_std), DIMENSION(npts,nvm,ncarb)                :: decomp_rate_soilcarbon !! Decomposition rate of the soil carbon pools (s)
188    REAL(r_std), DIMENSION(npts,ncarb)                    :: tsoilpools       !! Diagnostic for soil carbon turnover rate by pool (1/s)
189
190!_ ================================================================================================================================
191
192    !! printlev is the level of diagnostic information, 0 (none) to 4 (full)
193    IF (printlev>=3) WRITE(numout,*) 'Entering soilcarbon' 
194
195!! 1. Initializations
196
197    !! 1.1 Get soil "constants"
198    !! 1.1.1 Flux fractions between carbon pools: depend on clay content, recalculated each time
199    ! From active pool: depends on clay content
200    frac_carb(:,iactive,iactive) = zero
201    frac_carb(:,iactive,ipassive) = frac_carb_ap
202    frac_carb(:,iactive,islow) = un - (metabolic_ref_frac - active_to_pass_clay_frac*clay(:)) - frac_carb(:,iactive,ipassive)
203
204    ! 1.1.1.2 from slow pool
205
206    frac_carb(:,islow,islow) = zero
207    frac_carb(:,islow,iactive) = frac_carb_sa
208    frac_carb(:,islow,ipassive) = frac_carb_sp
209
210    ! From passive pool
211    frac_carb(:,ipassive,ipassive) = zero
212    frac_carb(:,ipassive,iactive) = frac_carb_pa
213    frac_carb(:,ipassive,islow) = frac_carb_ps
214
215    IF ( firstcall_soilcarbon ) THEN
216
217        !! 1.1.2 Residence times in carbon pools (days)
218        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.
219        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.
220        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.
221       
222        !! 1.2 Messages : display the residence times 
223        carbon_str(iactive) = 'active'
224        carbon_str(islow) = 'slow'
225        carbon_str(ipassive) = 'passive'
226       
227        IF (printlev >= 2) THEN
228           WRITE(numout,*) 'soilcarbon:'
229           WRITE(numout,*) '   > minimal carbon residence time in carbon pools (d):'
230           DO k = 1, ncarb ! Loop over carbon pools
231              WRITE(numout,*) '(1, ::carbon_str(k)):',carbon_str(k),' : (1, ::carbon_tau(k)):',carbon_tau(k)
232           ENDDO
233           WRITE(numout,*) '   > flux fractions between carbon pools: depend on clay content'
234        END IF
235        firstcall_soilcarbon = .FALSE.
236       
237    ENDIF
238
239    !! 1.3 Set soil respiration and decomposition rate to zero
240    resp_hetero_soil(:,:) = zero
241    decomp_rate_soilcarbon(:,:,:) = zero
242! gmjc
243!    resp_hetero_soil_part(:,:,:) = zero
244! end gmjc
245
246!! 2. Update the carbon stocks with the different soil carbon input
247
248    carbon(:,:,:) = carbon(:,:,:) + soilcarbon_input(:,:,:) * dt
249
250!! 3. Fluxes between carbon reservoirs, and to the atmosphere (respiration) \n
251
252    !! 3.1. Determine the respiration fraction : what's left after
253    ! subtracting all the 'pool-to-pool' flux fractions
254    ! Diagonal elements of frac_carb are zero
255    !    VPP killer:
256    !     frac_resp(:,:) = 1. - SUM( frac_carb(:,:,:), DIM=3 )
257    frac_resp(:,:) = un - frac_carb(:,:,iactive) - frac_carb(:,:,islow) - &
258         frac_carb(:,:,ipassive) 
259
260    !! 3.2. Calculate fluxes
261
262    DO m = 1, nvm ! Loop over # PFTs
263
264      !! 3.2.1. Flux out of pools
265
266      DO k = 1, ncarb ! Loop over carbon pools from which the flux comes
267       
268        ! Determine total flux out of pool
269        ! S.L. Piao 2006/05/05 - for crop multiply tillage factor of decomposition
270        ! Not crop
271         IF ( natural(m) ) THEN
272            fluxtot(:,k,icarbon) = dt/carbon_tau(k) * carbon(:,k,m) * &
273                  control_moist(:,ibelow) * control_temp(:,ibelow)
274
275            decomp_rate_soilcarbon(:,m,k)=dt/carbon_tau(k) * &
276                      control_moist(:,ibelow) * control_temp(:,ibelow)
277         ! C3 crop
278          ELSEIF ( (.NOT. natural(m)) .AND. (.NOT. 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(1)
281             decomp_rate_soilcarbon(:,m,k)=dt/carbon_tau(k) * &
282                       control_moist(:,ibelow) * control_temp(:,ibelow)*flux_tot_coeff(1)
283          ! C4 Crop   
284          ELSEIF ( (.NOT. natural(m)) .AND. is_c4(m) ) THEN
285             fluxtot(:,k,icarbon) = dt/carbon_tau(k) * carbon(:,k,m) * &
286                  control_moist(:,ibelow) * control_temp(:,ibelow) * flux_tot_coeff(2)
287             decomp_rate_soilcarbon(:,m,k)=dt/carbon_tau(k) * &
288                       control_moist(:,ibelow) *control_temp(:,ibelow)*flux_tot_coeff(2)
289        ENDIF
290        ! END - S.L. Piao 2006/05/05 - for crop multiply tillage factor of decomposition
291
292        ! Carbon flux from active pools depends on clay content
293        IF ( k .EQ. iactive ) THEN
294            fluxtot(:,k,icarbon) = fluxtot(:,k,icarbon) * ( un - flux_tot_coeff(3) * clay(:) )
295            decomp_rate_soilcarbon(:,m,k)=decomp_rate_soilcarbon(:,m,k)* ( un - flux_tot_coeff(3) * clay(:) ) 
296        ENDIF
297       
298        ! Update the loss in each carbon pool
299        carbon(:,k,m) = carbon(:,k,m) - fluxtot(:,k,icarbon)
300       
301        ! Fluxes towards the other pools (k -> kk)
302        DO kk = 1, ncarb ! Loop over the carbon pools where the flux goes
303          flux(:,k,kk,icarbon) = frac_carb(:,k,kk) * fluxtot(:,k,icarbon)
304        ENDDO
305      ENDDO ! End of loop over carbon pools
306     
307      !! 3.2.2 respiration
308      !       VPP killer:
309      !       resp_hetero_soil(:,m) = SUM( frac_resp(:,:) * fluxtot(:,:), DIM=2 ) / dt
310     
311      resp_hetero_soil(:,m) = &
312         ( frac_resp(:,iactive) * fluxtot(:,iactive,icarbon) + &
313         frac_resp(:,islow) * fluxtot(:,islow,icarbon) + &
314         frac_resp(:,ipassive) * fluxtot(:,ipassive,icarbon)  ) / dt
315!gmjc
316!       resp_hetero_soil_part(:,iactive,m) = &
317!            frac_resp(:,iactive) * fluxtot(:,iactive,icarbon)/dt
318!       resp_hetero_soil_part(:,islow,m) = &
319!            frac_resp(:,islow) * fluxtot(:,islow,icarbon)/dt
320!       resp_hetero_soil_part(:,ipassive,m) = &
321!            frac_resp(:,ipassive) * fluxtot(:,ipassive,icarbon)/dt
322!end gmjc     
323      !! 3.2.3 add fluxes to active, slow, and passive pools
324      !       VPP killer:
325      !       carbon(:,:,m) = carbon(:,:,m) + SUM( flux(:,:,:), DIM=2 )
326     
327      DO k = 1, ncarb ! Loop over carbon pools
328        carbon(:,k,m) = carbon(:,k,m) + &
329           flux(:,iactive,k,icarbon) + flux(:,ipassive,k,icarbon) + flux(:,islow,k,icarbon)
330      ENDDO ! Loop over carbon pools
331     
332    ENDDO ! End loop over PFTs
333   
334 !! 4. (Quasi-)Analytical Spin-up
335   
336    !! 4.1.1 Finish to fill MatrixA with fluxes between soil pools
337   
338    IF (spinup_analytic) THEN
339
340       DO m = 2,nvm 
341
342          ! flux leaving the active pool
343          MatrixA(:,m,iactive_pool,iactive_pool) = moins_un * &
344               dt/carbon_tau(iactive) * &
345               control_moist(:,ibelow) * control_temp(:,ibelow) * &
346               ( 1. - flux_tot_coeff(3) * clay(:)) 
347
348          ! flux received by the active pool from the slow pool
349          MatrixA(:,m,iactive_pool,islow_pool) =  frac_carb(:,islow,iactive)*dt/carbon_tau(islow) * &
350               control_moist(:,ibelow) * control_temp(:,ibelow)
351
352          ! flux received by the active pool from the passive pool
353          MatrixA(:,m,iactive_pool,ipassive_pool) =  frac_carb(:,ipassive,iactive)*dt/carbon_tau(ipassive) * &
354               control_moist(:,ibelow) * control_temp(:,ibelow) 
355
356          ! flux received by the slow pool from the active pool
357          MatrixA(:,m,islow_pool,iactive_pool) =  frac_carb(:,iactive,islow) *&
358               dt/carbon_tau(iactive) * &
359               control_moist(:,ibelow) * control_temp(:,ibelow) * &
360               ( 1. - flux_tot_coeff(3) * clay(:) ) 
361
362          ! flux leaving the slow pool
363          MatrixA(:,m,islow_pool,islow_pool) = moins_un * &
364               dt/carbon_tau(islow) * &
365               control_moist(:,ibelow) * control_temp(:,ibelow)
366
367          ! flux received by the passive pool from the active pool
368          MatrixA(:,m,ipassive_pool,iactive_pool) =  frac_carb(:,iactive,ipassive)* &
369               dt/carbon_tau(iactive) * &
370               control_moist(:,ibelow) * control_temp(:,ibelow) *&
371               ( 1. - flux_tot_coeff(3) * clay(:) )
372
373          ! flux received by the passive pool from the slow pool
374          MatrixA(:,m,ipassive_pool,islow_pool) =  frac_carb(:,islow,ipassive) * &
375               dt/carbon_tau(islow) * &
376               control_moist(:,ibelow) * control_temp(:,ibelow)
377
378          ! flux leaving the passive pool
379          MatrixA(:,m,ipassive_pool,ipassive_pool) =  moins_un * &
380               dt/carbon_tau(ipassive) * &
381               control_moist(:,ibelow) * control_temp(:,ibelow)     
382
383
384          IF ( (.NOT. natural(m)) .AND. (.NOT. is_c4(m)) ) THEN ! C3crop
385
386             ! flux leaving the active pool
387             MatrixA(:,m,iactive_pool,iactive_pool) = MatrixA(:,m,iactive_pool,iactive_pool) * &
388                  flux_tot_coeff(1) 
389
390             ! flux received by the active pool from the slow pool
391             MatrixA(:,m,iactive_pool,islow_pool)= MatrixA(:,m,iactive_pool,islow_pool) * &
392                  flux_tot_coeff(1) 
393
394             ! flux received by the active pool from the passive pool
395             MatrixA(:,m,iactive_pool,ipassive_pool) = MatrixA(:,m,iactive_pool,ipassive_pool) * &
396                  flux_tot_coeff(1)   
397
398             ! flux received by the slow pool from the active pool
399             MatrixA(:,m,islow_pool,iactive_pool) =  MatrixA(:,m,islow_pool,iactive_pool) * &
400                  flux_tot_coeff(1) 
401
402             ! flux leaving the slow pool
403             MatrixA(:,m,islow_pool,islow_pool) = MatrixA(:,m,islow_pool,islow_pool) * &
404                  flux_tot_coeff(1)     
405
406             ! flux received by the passive pool from the active pool
407             MatrixA(:,m,ipassive_pool,iactive_pool) = MatrixA(:,m,ipassive_pool,iactive_pool) * &
408                  flux_tot_coeff(1)
409
410             ! flux received by the passive pool from the slow pool
411             MatrixA(:,m,ipassive_pool,islow_pool) = MatrixA(:,m,ipassive_pool,islow_pool) * &
412                  flux_tot_coeff(1)
413
414             ! flux leaving the passive pool
415             MatrixA(:,m,ipassive_pool,ipassive_pool) =  MatrixA(:,m,ipassive_pool,ipassive_pool) *&
416                  flux_tot_coeff(1)
417
418          ENDIF ! (.NOT. natural(m)) .AND. (.NOT. is_c4(m))
419
420
421          IF ( (.NOT. natural(m)) .AND. is_c4(m) ) THEN ! C4crop
422
423             ! flux leaving the active pool
424             MatrixA(:,m,iactive_pool,iactive_pool) = MatrixA(:,m,iactive_pool,iactive_pool) * &
425                  flux_tot_coeff(2) 
426
427            ! flux received by the active pool from the slow pool
428             MatrixA(:,m,iactive_pool,islow_pool)= MatrixA(:,m,iactive_pool,islow_pool) * &
429                  flux_tot_coeff(2) 
430
431             ! flux received by the active pool from the passive pool
432             MatrixA(:,m,iactive_pool,ipassive_pool) = MatrixA(:,m,iactive_pool,ipassive_pool) * &
433                  flux_tot_coeff(2)   
434
435             ! flux received by the slow pool from the active pool
436             MatrixA(:,m,islow_pool,iactive_pool) =  MatrixA(:,m,islow_pool,iactive_pool) * &
437                  flux_tot_coeff(2) 
438
439             ! flux leaving the slow pool
440             MatrixA(:,m,islow_pool,islow_pool) = MatrixA(:,m,islow_pool,islow_pool) * &
441                  flux_tot_coeff(2)     
442
443             ! flux received by the passive pool from the active pool
444             MatrixA(:,m,ipassive_pool,iactive_pool) = MatrixA(:,m,ipassive_pool,iactive_pool) * &
445                  flux_tot_coeff(2)
446
447             ! flux received by the passive pool from the slow pool
448             MatrixA(:,m,ipassive_pool,islow_pool) = MatrixA(:,m,ipassive_pool,islow_pool) * &
449                  flux_tot_coeff(2)
450
451             ! flux leaving the passive pool
452             MatrixA(:,m,ipassive_pool,ipassive_pool) =  MatrixA(:,m,ipassive_pool,ipassive_pool) * &
453                  flux_tot_coeff(2)
454
455          ENDIF ! (.NOT. natural(m)) .AND. is_c4(m)
456
457          IF (printlev>=4) WRITE(numout,*)'Finish to fill MatrixA'
458
459       ENDDO ! Loop over # PFTS
460
461
462       ! 4.2 Add Identity for each submatrix(7,7)
463
464       DO j = 1,nbpools
465          MatrixA(:,:,j,j) = MatrixA(:,:,j,j) + un 
466       ENDDO
467
468    ENDIF ! (spinup_analytic)
469
470
471    ! Output diagnostics
472    DO k = 1, ncarb ! Loop over carbon pools
473       DO ij = 1, npts
474          IF (SUM(decomp_rate_soilcarbon(ij,:,k)*veget_cov_max(ij,:)) > min_sechiba) THEN
475             tsoilpools(ij,k) = 1./(SUM(decomp_rate_soilcarbon(ij,:,k)*veget_cov_max(ij,:))/dt_sechiba)
476          ELSE
477             tsoilpools(ij,k) = xios_default_val
478          END IF
479       END DO
480    END DO
481    CALL xios_orchidee_send_field("tSoilPools",tsoilpools)
482
483    IF (printlev>=4) WRITE(numout,*) 'Leaving soilcarbon'
484   
485  END SUBROUTINE soilcarbon
486
487END MODULE stomate_soilcarbon
Note: See TracBrowser for help on using the repository browser.