source: branches/publications/ORCHIDEE-MUSLE-r6129/src_stomate/stomate_litter.f90 @ 7442

Last change on this file since 7442 was 4381, checked in by bertrand.guenet, 7 years ago

Improve the restart file writing

  • Property svn:keywords set to HeadURL Date Author Revision
File size: 85.6 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_litter
3!
4! CONTACT      : orchidee-help _at_ ipsl.jussieu.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       Update litter and lignine content after litter fall and
10!! calculating litter decomposition.     
11!!
12!!\n DESCRIPTION: None
13!!
14!! RECENT CHANGE(S): None
15!!
16!! REFERENCE(S) : None
17!!
18!! SVN          :
19!! $HeadURL$
20!! $Date$
21!! $Revision$
22!! \n
23!_ ================================================================================================================================
24
25MODULE stomate_litter
26
27  ! modules used:
28
29  USE ioipsl_para
30  USE stomate_data
31  USE constantes
32  USE constantes_soil
33  USE pft_parameters
34
35  IMPLICIT NONE
36
37  ! private & public routines
38
39  PRIVATE
40  PUBLIC littercalc,littercalc_clear, deadleaf
41
42
43
44  LOGICAL, SAVE                        :: firstcall = .TRUE.       !! first call
45!$OMP THREADPRIVATE(firstcall)
46
47CONTAINS
48
49!! ================================================================================================================================
50!! SUBROUTINE   : littercalc_calc
51!!
52!!\BRIEF        Set the flag ::firstcall to .TRUE. and as such activate section
53!! 1.1 of the subroutine littercalc (see below).
54!!
55!! DESCRIPTION  : None
56!!
57!! RECENT CHANGE(S) : None
58!!
59!! MAIN OUTPUT VARIABLE(S) : None
60!!
61!! REFERENCE(S) : None
62!!
63!! FLOWCHART : None
64!! \n
65!_ ================================================================================================================================
66
67  SUBROUTINE littercalc_clear
68    firstcall =.TRUE.
69  END SUBROUTINE littercalc_clear
70
71
72!! ================================================================================================================================
73!! SUBROUTINE   : littercalc
74!!
75!!\BRIEF        Calculation of the litter decomposition and therefore of the
76!! heterotrophic respiration from litter following Parton et al. (1987).
77!!
78!! DESCRIPTION  : The littercal routine splits the litter in 4 pools:
79!! aboveground metaboblic, aboveground structural, belowground metabolic and
80!! belowground structural. the fraction (F) of plant material going to metabolic
81!! and structural is defined following Parton et al. (1987). The below ground
82!! litter is discretized over 11 layers (the same used by the CWRR hydrology
83!! scheme).
84!! \latexonly
85!! \input{littercalc1.tex}
86!! \endlatexonly
87!! \n
88!! where L is the lignin content of the plant carbon pools considered and CN
89!! its CN ratio. L and CN are fixed parameters for each plant carbon pools,
90!! therefore it is the ratio between each plant carbon pool within a PFT, which
91!! controlled the part of the total litter, that will be considered as
92!! recalcitrant (i.e. structural litter) or labile (i.e. metabolic litter).\n 
93!!
94!! The routine calculates the fraction of aboveground litter which is metabolic
95!! or structural (the litterpart variable) which is then used in lpj_fire.f90.\n
96!!
97!! In the section 2, the routine calculate the new plant material entering the
98!! litter pools by phenological death of plants organs (corresponding to the
99!! variable turnover) and by fire, herbivory and others non phenological causes
100!! (variable bm_to_litter). This calculation is first done for each PFT and then
101!! the values calculated for each PFT are added up. Following the same approach
102!! the lignin content of the total structural litter is calculated and will be
103!! then used as a factor control of the decomposition of the structural litter
104!! (lignin_struc) in the section 5.1.2. A test is performed to avoid that we add
105!! more lignin than structural litter. Finally, the variable litterpart is
106!! updated.\n
107!!
108!! In the section 3 and 4 the temperature and the moisture controlling the
109!! decomposition are calculated for above and belowground. For aboveground
110!! litter, air temperature and litter moisture are calculated in sechiba and used
111!! directly. For belowground, soil temperature and moisture are also calculated
112!! in sechiba but are modulated as a function of the soil depth. The modulation
113!! is a multiplying factor exponentially distributed between 0 (in depth) and 1
114!! in surface.\n 
115!!
116!! Then, in the section 5 and 6, the routine calculates the structural litter decomposition
117!! (C) following first order kinetics following Parton et al. (1987).
118!! \latexonly
119!! \input{littercalc2.tex}
120!! \endlatexonly
121!! \n
122!! with k the decomposition rate of the structural litter.
123!! k corresponds to
124!! \latexonly
125!! \input{littercalc3.tex}
126!! \endlatexonly
127!! \n
128!! with littertau the turnover rate, T a function of the temperature and M a function of
129!! the moisture described below.\n
130!! 
131!! Then, the fraction of dead leaves (DL) composed by aboveground structural litter is
132!! calculated as following
133!! \latexonly
134!! \input{littercalc4.tex}
135!! \endlatexonly
136!! \n
137!! with k the decomposition rate of the structural litter previously
138!! described.\n
139!!
140!! In the section 5.1 and 6.1, the fraction of decomposed structural litter
141!! incorporated to the soil (Input) and its associated heterotrophic respiration are
142!! calculated. For structural litter, the C decomposed could go in the active
143!! soil carbon pool or in the slow carbon, as described in
144!! stomate_soilcarbon.f90.\n
145!! \latexonly
146!! \input{littercalc5.tex}
147!! \endlatexonly
148!! \n
149!! with f a parameter describing the fraction of structural litter incorporated
150!! into the considered soil carbon pool, C the amount of litter decomposed and L
151!! the amount of lignin in the litter. The litter decomposed which is not
152!! incorporated into the soil is respired.\n
153!!
154!! In the section 5.2 and 6.2, the fraction of decomposed metabolic litter
155!! incorporated to the soil and its associated heterotrophic respiration are
156!! calculated with the same approaches presented for 5.1 but no control factor
157!! depending on the lignin content are used.\n
158!!
159!! In the section 7 the dead leaf cover is calculated through a call to the
160!! deadleaf subroutine presented below.\n
161!!
162!! MAIN OUTPUT VARIABLES: ::deadleaf_cover, ::resp_hetero_litter,
163!! ::control_temp, ::control_moist
164!!
165!! REFERENCES:
166!! - Parton, WJ, Schimel, DS, Cole, CV, and Ojima, DS. 1987. Analysis
167!! of factors controlling soil organic matter levels in Great Plains
168!! grasslands. Soil Science Society of America journal (USA)
169!! (51):1173-1179.
170!! - Lardy, R, et al., A new method to determine soil organic carbon equilibrium,
171!! Environmental Modelling & Software (2011), doi:10.1016|j.envsoft.2011.05.016
172!!
173!! FLOWCHART    :
174!! \latexonly
175!! \includegraphics(scale=0.5){littercalcflow.jpg}
176!! \endlatexonly
177!! \n
178!_ ================================================================================================================================
179
180  SUBROUTINE littercalc (npts, dt, &
181       turnover, bm_to_litter, &
182       veget_max, tsurf, tsoil, soilhum, litterhum, rprof, &
183       litterpart, litter_above, litter_below, dead_leaves, &
184       lignin_struc_above, lignin_struc_below, &
185       deadleaf_cover, resp_hetero_litter, &
186       control_temp_above, control_temp_soil, &
187       control_moist_above, control_moist_soil, &
188       litter_mc,soilcarbon_input, soil_mc, soiltile, &
189       clay, bulk_dens, soil_ph, carbon)
190
191    !! 0. Variable and parameter declaration
192   
193    !! 0.1 Input variables
194
195    INTEGER(i_std), INTENT(in)                                  :: npts                !! Domain size - number of grid pixels
196    REAL(r_std), INTENT(in)                                     :: dt                  !! Time step of the simulations for stomate
197                                                                                       !! @tex $(dtradia one\_day^{-1})$ @endtex
198    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: turnover          !! Turnover rates of plant biomass
199                                                                                       !! @tex $(gC m^{-2} dt\_slow^{-1})$ @endtex
200    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: bm_to_litter      !! Conversion of biomass to litter
201                                                                                       !! @tex $(gC m^{-2} dt\_slow^{-1})$ @endtex
202    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                   :: veget_max          !! PFT "Maximal" coverage fraction of a PFT
203                                                                                       !! defined in the input vegetation map
204                                                                                       !! @tex $(m^2 m^{-2})$ @endtex
205    REAL(r_std), DIMENSION(npts), INTENT(in)                     :: tsurf              !! Temperature (K) at the surface
206    REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                :: tsoil              !! Soil temperature (K)
207    REAL(r_std), DIMENSION(npts,nbdl), INTENT(in)                :: soilhum            !! Daily soil humidity of each soil layer
208                                                                                       !! (unitless)
209    REAL(r_std), DIMENSION(npts), INTENT(in)                     :: litterhum          !! Daily litter humidity (unitless)
210    REAL(r_std), DIMENSION(npts,nvm), INTENT(in)                 :: rprof              !! PFT root depth as calculated in stomate.f90 from parameter
211                                                                                       !! humcste which is root profile for different PFTs
212                                                                                       !! in slowproc.f90 (m)
213    REAL(r_std),DIMENSION (npts,nstm), INTENT(in)                :: litter_mc          !! soil moisture content \f($m^3 \times m^3$)\f
214    REAL(r_std),DIMENSION (npts,nbdl,nstm), INTENT(in)           :: soil_mc            !! soil moisture content \f($m^3 \times m^3$)\f
215    REAL(r_std),DIMENSION (npts,nstm), INTENT (in)               :: soiltile           !! Fraction of each soil tile (0-1, unitless)
216    REAL(r_std), DIMENSION(npts), INTENT(in)                     :: clay               !! Clay fraction (unitless, 0-1)
217    REAL(r_std), DIMENSION(npts), INTENT(inout)                  :: bulk_dens          !! Variable local of bulk density for the moment must change in the futur (kg m-3)
218
219    REAL(r_std), DIMENSION(npts), INTENT(in)                     :: soil_ph            !! soil pH (pH unit, 0-14)
220    REAL(r_std), DIMENSION(npts,ncarb,nvm,nbdl), INTENT(in)      :: carbon             !! Soil carbon pools: active, slow, or passive, \f$(gC m^{2})$\f
221    !! 0.2 Output variables
222   
223    REAL(r_std), DIMENSION(npts), INTENT(out)                    :: deadleaf_cover     !! Fraction of soil covered by dead leaves
224                                                                                       !! over all PFTs (0-1, unitless)
225    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: resp_hetero_litter !! Litter heterotrophic respiration. The unit
226                                                                                       !! is given by m^2 of ground. 
227                                                                                       !! @tex $(gC dtradia one\_day^{-1}) m^{-2})$ @endtex
228    REAL(r_std), DIMENSION(npts,nbdl,npool*2), INTENT(out)       :: control_temp_soil  !! Temperature control of heterotrophic
229                                                                                       !! respiration belowground,(0-1, unitless)
230    REAL(r_std), DIMENSION(npts,nbdl,nvm), INTENT(out)           :: control_moist_soil !! Moisture control of heterotrophic
231                                                                                       !! respiration aboveground(0.25-1,unitless)
232    REAL(r_std), DIMENSION(npts,nlitt), INTENT(out)              :: control_temp_above !! Temperature control of heterotrophic 
233                                                                                       !! respiration, above (0-1, 
234                                                                                       !! unitless)
235    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)                :: control_moist_above!! Moisture control of heterotrophic 
236                                                                                       !! respiration aboveground(0.25-1, unitless)
237
238    !! 0.3 Modified variables
239   
240    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)       :: litterpart         !! Fraction of litter above the ground
241                                                                                      !! belonging to the different PFTs (0-1,
242                                                                                      !! unitless)
243    REAL(r_std), DIMENSION(npts,nlitt,nvm,nelements), INTENT(inout) :: litter_above   !! Metabolic and structural litter,above ground
244                                                                                      !! The unit is given by m^2 of
245                                                                                      !! ground @tex $(gC m^{-2})$ @endtex
246    REAL(r_std), DIMENSION(npts,nlitt,nvm,nbdl,nelements), INTENT(inout) ::litter_below  !! Metabolic and structural litter, below ground
247                                                                                      !! The unit is given by m^2 of
248                                                                                      !! ground @tex $(gC m^{-2} $ @endtex
249    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)       :: dead_leaves        !! Dead leaves per ground unit area, per PFT,
250                                                                                      !! metabolic and structural in
251                                                                                      !! @tex $(gC m^{-2})$ @endtex
252    REAL(r_std), DIMENSION(npts,nvm), INTENT(inout)            :: lignin_struc_above  !! Ratio Lignin content in structural litter,
253                                                                                      !! above ground, (0-1, unitless)
254    REAL(r_std), DIMENSION(npts,nvm,nbdl), INTENT(inout)       :: lignin_struc_below  !! Ratio Lignin content in structural litter,
255                                                                                      !! below ground, (0-1, unitless)
256    REAL(r_std), DIMENSION(npts,nvm,nbdl,npool,nelements), INTENT(inout) :: soilcarbon_input !! Dissolved Organic Carbon input from litter decomposition
257                                                                                      !! The unit is given by m^2 of
258                                                                                      !! water @tex $(gC m^{-2})$ @endtex
259    !! 0.4 Local variables
260 
261    REAL(r_std), SAVE, DIMENSION(nparts,nlitt)                  :: litterfrac         !! The fraction of leaves, wood, etc. that
262                                                                                      !! goes into metabolic and structural
263                                                                                      !! litterpools (0-1, unitless)
264!$OMP THREADPRIVATE(litterfrac)
265    REAL(r_std),DIMENSION(0:nbdl)                               :: z_soil             !! Soil levels (m)
266!$OMP THREADPRIVATE(z_soil)
267                                                                                      !! profiles (unitless)
268    REAL(r_std), SAVE, DIMENSION(nlitt)                         :: litter_tau         !! Turnover time in litter pools (days)
269!$OMP THREADPRIVATE(litter_tau)
270    REAL(r_std), SAVE, DIMENSION(npool)                         :: pool_tau         !! Turnover time in litter and soil carbon pools (days)
271!$OMP THREADPRIVATE(pool_tau)
272    REAL(r_std), DIMENSION(npool,nvm)                     :: DOC_tau          !! Residence time of DOC (days)   
273!$OMP THREADPRIVATE(DOC_tau)
274    REAL(r_std), SAVE, DIMENSION(nlitt,ncarb,nlevs)             :: frac_soil          !! Fraction of litter that goes into soil
275                                                                                      !! (litter -> carbon, above and below). The
276                                                                                      !! remaining part goes to the atmosphere
277!$OMP THREADPRIVATE(frac_soil)
278    REAL(r_std), DIMENSION(npts)                                :: tsoil_decomp       !! Temperature used for decompostition in
279                                                                                      !! soil (K)
280    REAL(r_std), DIMENSION(npts)                                :: soilhum_decomp     !! Humidity used for decompostition in soil
281                                                                                      !! (unitless)
282 !   REAL(r_std), SAVE, DIMENSION(npts)                          :: z_lit              !! Thickness of the above ground litter layer (mm)
283!!$OMP THREADPRIVATE(z_lit)
284
285    REAL(r_std), DIMENSION(npts)                                :: fd                 !! Fraction of structural or metabolic litter
286                                                                                      !! decomposed (unitless)
287    REAL(r_std), DIMENSION(npts,nelements)                      :: qd                 !! Quantity of structural or metabolic litter
288                                                                                      !! decomposed @tex $(gC m^{-2})$ @endtex
289    REAL(r_std), DIMENSION(npts,nvm)                            :: old_struc_above    !! Old structural litter, above ground
290                                                                                      !! @tex $(gC m^{-2})$ @endtex
291    REAL(r_std), DIMENSION(npts,nvm,nbdl)                       :: old_struc_below    !! Old structural litter, below ground
292                                                                                      !! @tex $(gC m^{-2})$ @endtex
293    REAL(r_std), DIMENSION(npts,nvm,nlitt, nelements)           :: litter_inc_PFT_above  !! Increase of litter, per PFT, metabolic and
294                                                                                      !! structural, above ground. The
295                                                                                      !! unit is given by m^2 of ground. 
296                                                                                      !! @tex $(gC m^{-2})$ @endtex
297    REAL(r_std), DIMENSION(npts,nvm,nlitt,nbdl,nelements)      :: litter_inc_PFT_below     !! Increase of litter, per PFT, metabolic and
298                                                                                      !! structural, above ground. The
299                                                                                      !!unit is given by m^2 of ground.
300                                                                                      !! @tex $(gC m^{-2})$ @endtex
301    REAL(r_std), DIMENSION(npts,nlitt,nvm,nelements)            :: litter_inc_above   !! Increase of metabolic and structural
302                                                                                      !! litter, above ground. The unit
303                                                                                      !! is given by m^2 of ground.
304                                                                                      !! @tex $(gC m^{-2})$ @endtex
305    REAL(r_std), DIMENSION(npts,nlitt,nvm,nbdl,nelements)       :: litter_inc_below   !! Increase of metabolic and structural
306                                                                                      !! litter below ground. The unit
307                                                                                      !! is given by m^2 of ground
308                                                                                      !! @tex $(gC m^{-2})$ @endtex
309
310    REAL(r_std), DIMENSION(npts,nvm)                            :: lignin_struc_inc_above !! Lignin increase in structural litter,
311                                                                                      !! above ground. The unit is given
312                                                                                      !! by m^2 of ground.
313                                                                                      !! @tex $(gC m^{-2})$ @endtex
314    REAL(r_std), DIMENSION(npts,nvm,nbdl)                       :: lignin_struc_inc_below   !! Lignin increase in structural litter,
315                                                                                      !! below ground. The unit is given
316                                                                                      !! by m^2 of ground
317                                                                                      !! @tex $(gC m^{-2})$ @endtex
318    REAL(r_std), DIMENSION(npts,nvm,nlitt,nelements)            :: litter_pft         !! Metabolic and structural litter above the
319                                                                                      !! ground per PFT
320    REAL(r_std), DIMENSION(npts)                                :: zdiff_min          !! Intermediate field for looking for minimum
321                                                                                      !! of what? this is not used in the code.
322                                                                                      !! [??CHECK] could we delete it?
323    CHARACTER(LEN=10), DIMENSION(nlitt)                         :: litter_str         !! Messages to write output information about
324                                                                                      !! the litter
325    CHARACTER(LEN=22), DIMENSION(nparts)                        :: part_str           !! Messages to write output information about
326                                                                                      !! the plant
327    CHARACTER(LEN=7), DIMENSION(ncarb)                          :: carbon_str         !! Messages to write output information about
328                                                                                      !! the soil carbon
329    CHARACTER(LEN=5), DIMENSION(nlevs)                          :: level_str          !! Messages to write output information about
330                                                                                      !! the level (aboveground or belowground litter)
331    INTEGER(i_std)                                              :: i,j,k,l,m          !! Indices (unitless)
332    REAL(r_std), DIMENSION(npts)                                :: Dif_coef           !! Diffusion coeficient used for bioturbation (m2 days-1)
333!!$OMP THREADPRIVATE(Dif_coef)
334
335    REAL(r_std), DIMENSION(npts,nlitt,nvm,nbdl,nelements)       :: litter_flux        !! Belowground litter carbon flux within pools towards the soil column\f$(gC m^{2} dt^{-1})$\f
336    REAL(r_std), DIMENSION(npts,nlitt,nvm,nbdl,nelements)       :: litter_flux_old    !! Belowground litter carbon flux within pools towards the soil column\f$(gC m^{2} dt^{-1})$\f
337                                                                                      !! used for storage
338    REAL(r_std), DIMENSION(npts,nlitt,nvm,nelements)            :: litter_above_flux  !! Above litter carbon flux within pools towards the soil column\f$(gC m^{2} dt^{-1})$\f
339    REAL(r_std), DIMENSION(npts,nlitt,nvm,nelements)            :: litter_above_flux_old  !! Above litter carbon flux within pools towards the soil column\f$(gC m^{2} dt^{-1})$\f
340                                                                                      !! used for storage
341    REAL(r_std), DIMENSION(npts)                                :: rpc                !! Scaling factor for integrating vertical soil
342                                                                                      !! profiles (unitless)
343    REAL(r_std), DIMENSION(npts,nvm,nmbcomp,nelements)     :: check_intern       !! Contains the components of the internal
344                                                                                      !! mass balance chech for this routine
345                                                                                      !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
346    REAL(r_std), DIMENSION(npts,nvm,nelements)             :: closure_intern     !! Check closure of internal mass balance
347
348    REAL(r_std), DIMENSION(npts,nvm,nelements)             :: pool_start         !! Start and end pool of this routine
349                                                                                      !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
350    REAL(r_std), DIMENSION(npts,nvm,nelements)             :: pool_end           !! End pool of this routine not corrected
351                                                                                      !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
352    REAL(r_std), DIMENSION(npts,nvm,nelements)             :: pool_end_after           !! Start and end pool of this routine
353                                                                                      !! @tex $(gC pixel^{-1} dt^{-1})$ @endtex
354    REAL(r_std), DIMENSION(npts,nbdl)                      :: moist_soil         !! moisture in soil for one pixel (m3/m3)
355
356   ! REAL(r_std), DIMENSION(npts,nvm,nbdl)                       :: resp_hetero_litter_layer !! Litter heterotrophic respiration per layer. The unit
357                                                                                      !! is given by m^2 of ground by z. 
358                                                                                      !! @tex $(gC dtradia one\_day^{-1}) m^{-2} z^{-1})$ @endtex
359    REAL(r_std), DIMENSION(npts,nlitt,nvm,nbdl,nelements)  ::litter_below_old         !! Metabolic and structural litter, below ground
360                                                                                      !! The unit is given by m^2 of
361                                                                                      !! ground @tex $(gC m^{-2} $ @endtex used for storage
362    REAL(r_std), DIMENSION(npts,nlitt,nvm,nbdl,nelements)  ::litter_below_old_buffer  !! Metabolic and structural litter, below ground
363                                                                                      !! The unit is given by m^2 of
364                                                                                      !! ground @tex $(gC m^{-2} $ @endtex used for storage
365    REAL(r_std), DIMENSION(npts,nlitt,nvm,nelements)       :: litter_above_old        !! Metabolic and structural litter,above ground
366                                                                                      !! The unit is given by m^2 of
367                                                                                      !! ground @tex $(gC m^{-2})$ @endtex used for storage
368!_ ================================================================================================================================
369
370    IF (printlev>=3) WRITE(numout,*) 'Entering littercalc'
371
372  !! 1. Initialisations of the different fields during the first call of the routine
373    !! 1.0 Calculation of soil moisture
374    moist_soil(:,:) = zero
375      DO l = 1,nbdl
376          DO i = 1, nstm
377             moist_soil(:,l)= moist_soil(:,l) + soil_mc(:,l,i)*soiltile(:,i)
378          ENDDO
379      ENDDO
380
381    WHERE (bulk_dens(:) .LT. 500)
382    bulk_dens(:) = bulk_dens(:)*1e3
383    ENDWHERE
384
385       z_soil(0) = zero
386       z_soil(1:nbdl) = diaglev(1:nbdl)
387
388    !! 1.1 Initialize check for mass balance closure
389    !  The mass balance is calculated at the end of this routine
390    !  in section 14. Initial biomass and harvest pool and all other
391    !  relevant pools were set to zero before calling this routine.
392    pool_start(:,:,:) = zero
393IF (ld_doc) THEN
394    DO m = 2, nvm
395       DO i = 1,nlitt
396          DO l = 1, nbdl
397                 pool_start(:,m,icarbon) = pool_start(:,m,icarbon) + &
398                           ( litter_below(:,i,m,l,icarbon) ) * veget_max(:,m)
399          ENDDO
400       ENDDO
401    ENDDO
402
403    DO m = 2, nvm
404       DO i = 1,nlitt
405                 pool_start(:,m,icarbon) = pool_start(:,m,icarbon) + &
406                           ( litter_above(:,i,m,icarbon) ) * veget_max(:,m)
407       ENDDO
408    ENDDO
409
410    DO m = 2, nvm
411       DO i = 1, nparts
412          pool_start(:,m,icarbon) = pool_start(:,m,icarbon) + &
413                    (turnover(:,m,i,icarbon) + bm_to_litter(:,m,i,icarbon)) * veget_max(:,m)
414      ENDDO
415    ENDDO
416ENDIF
417    IF ( firstcall ) THEN
418
419       !! 1.2.1 litter fractions:
420       !!   what fraction of leaves, wood, etc. goes into metabolic and structural litterpools
421       DO k = 1, nparts
422
423          litterfrac(k,imetabolic) = metabolic_ref_frac - metabolic_LN_ratio * LC(k) * CN(k)
424          litterfrac(k,istructural) = un - litterfrac(k,imetabolic)
425
426       ENDDO
427
428       !! 1.2.2 residence times in litter pools (days)
429       litter_tau(imetabolic) = tau_metabolic * one_year      ! .5 years
430       litter_tau(istructural) = tau_struct * one_year     ! 3 years
431
432       pool_tau(imetabo) = tau_metabolic 
433       pool_tau(istrabo) = tau_struct 
434       pool_tau(imetbel) = tau_metabolic 
435       pool_tau(istrbel) = tau_struct 
436       pool_tau(iact) = carbon_tau_iactive 
437       pool_tau(islo) = carbon_tau_islow 
438       pool_tau(ipas) = carbon_tau_ipassive 
439       DO m=1,nvm
440          DOC_tau(imetabo,m) = DOC_tau_labile(m) / one_year
441          DOC_tau(istrabo,m) = DOC_tau_labile(m) / one_year
442          DOC_tau(imetbel,m) = DOC_tau_labile(m) / one_year
443          DOC_tau(istrbel,m) = DOC_tau_labile(m) / one_year
444          DOC_tau(iact,m) = DOC_tau_labile(m) / one_year
445          DOC_tau(islo,m) = DOC_tau_stable(m) / one_year
446          DOC_tau(ipas,m) = DOC_tau_stable(m) / one_year
447       ENDDO
448       !! 1.2.3 decomposition flux fraction that goes into soil
449       !       (litter -> carbon, above and below)
450       !       1-frac_soil goes into atmosphere
451       frac_soil(:,:,:) = zero
452
453       ! structural litter: lignin fraction goes into slow pool + respiration,
454       !                    rest into active pool + respiration
455       frac_soil(istructural,iactive,iabove) = frac_soil_struct_aa
456       frac_soil(istructural,iactive,ibelow) = frac_soil_struct_ab
457       frac_soil(istructural,islow,iabove) = frac_soil_struct_sa
458       frac_soil(istructural,islow,ibelow) = frac_soil_struct_sb
459
460       ! metabolic litter: all goes into active pool + respiration.
461       !   Nothing into slow or passive pool.
462       frac_soil(imetabolic,iactive,iabove) = frac_soil_metab_aa
463       frac_soil(imetabolic,iactive,ibelow) = frac_soil_metab_ab
464       
465 
466       !! 1.4 messages
467       litter_str(imetabolic) = 'metabolic'
468       litter_str(istructural) = 'structural'
469
470       carbon_str(iactive) = 'active'
471       carbon_str(islow) = 'slow'
472       carbon_str(ipassive) = 'passive'
473
474       level_str(iabove) = 'above'
475       level_str(ibelow) = 'below'
476
477       part_str(ileaf) = 'leaves'
478       part_str(isapabove) = 'sap above ground'
479       part_str(isapbelow) = 'sap below ground'
480       part_str(iheartabove) = 'heartwood above ground'
481       part_str(iheartbelow) = 'heartwood below ground'
482       part_str(iroot) = 'roots'
483       part_str(ifruit) = 'fruits'
484       part_str(icarbres) = 'carbohydrate reserve'
485
486       WRITE(numout,*) 'litter:'
487
488       WRITE(numout,*) '   > C/N ratios: '
489       DO k = 1, nparts
490          WRITE(numout,*) '       ', part_str(k), ': ',CN(k)
491       ENDDO
492
493       WRITE(numout,*) '   > Lignine/C ratios: '
494       DO k = 1, nparts
495          WRITE(numout,*) '       ', part_str(k), ': ',LC(k)
496       ENDDO
497
498       WRITE(numout,*) '   > fraction of compartment that goes into litter: '
499       DO k = 1, nparts
500          DO m = 1, nlitt
501             WRITE(numout,*) '       ', part_str(k), '-> ',litter_str(m), ':',litterfrac(k,m)
502          ENDDO
503       ENDDO
504
505       WRITE(numout,*) '   > minimal carbon residence time in litter pools (d):'
506       DO m = 1, nlitt
507          WRITE(numout,*) '       ',litter_str(m),':',litter_tau(m)
508       ENDDO
509
510       WRITE(numout,*) '   > litter decomposition flux fraction that really goes '
511       WRITE(numout,*) '     into carbon pools (rest into the atmosphere):'
512       DO m = 1, nlitt
513          DO l = 1, nlevs
514             DO k = 1, ncarb
515                WRITE(numout,*) '       ',litter_str(m),' ',level_str(l),' -> ',&
516                     carbon_str(k),':', frac_soil(m,k,l)
517             ENDDO
518          ENDDO
519       ENDDO
520
521       firstcall = .FALSE.
522
523    ENDIF
524
525       DO m=1,nvm
526          DOC_tau(imetabo,m) = DOC_tau_labile(m) / one_year
527          DOC_tau(istrabo,m) = DOC_tau_labile(m) / one_year
528          DOC_tau(imetbel,m) = DOC_tau_labile(m) / one_year
529          DOC_tau(istrbel,m) = DOC_tau_labile(m) / one_year
530          DOC_tau(iact,m) = DOC_tau_labile(m) / one_year
531          DOC_tau(islo,m) = DOC_tau_stable(m) / one_year
532          DOC_tau(ipas,m) = DOC_tau_stable(m) / one_year
533       ENDDO
534
535    !! 1.3 Initialization
536    litter_above_flux(:,:,:,:) = zero
537    litter_flux(:,:,:,:,:) = zero
538    litter_flux_old(:,:,:,:,:) = zero
539    old_struc_above(:,:) = zero
540    old_struc_below(:,:,:) = zero
541    litter_pft(:,:,:,:) = zero
542    Dif_coef(:) = (Dif/one_year)*dt 
543
544   
545    !! 1.3 litter above the ground per PFT.
546    DO j = 2, nvm ! Loop over # PFTs
547       DO k = 1, nlitt !Loop over litter pool
548          litter_pft(:,j,k,icarbon) = litterpart(:,j,k) * litter_above(:,k,j,icarbon)
549       ENDDO
550    ENDDO
551
552   
553    !! 1.4 set output to zero
554    deadleaf_cover(:) = zero
555    resp_hetero_litter(:,:) = zero
556    soilcarbon_input(:,:,:,:,:)= zero
557    !resp_hetero_litter_layer(:,:,:) = zero
558
559  !! 2. Add biomass to different litterpools (per m^2 of ground)
560   
561    !! 2.1 first, save old structural litter (needed for lignin fractions).
562    !     above
563       DO m = 2,nvm !Loop over PFTs
564
565          old_struc_above(:,m) = litter_above(:,istructural,m,icarbon)
566
567       ENDDO
568
569    !below
570    DO l = 1, nbdl !Loop over soil levels (below ground)
571       DO m = 2,nvm !Loop over PFTs
572
573          old_struc_below(:,m,l) = litter_below(:,istructural,m,l,icarbon)
574
575       ENDDO
576    ENDDO
577   
578    !! 2.2 update litter, dead leaves, and lignin content in structural litter
579    litter_inc_above(:,:,:,:) = zero
580    lignin_struc_inc_above(:,:) = zero
581    litter_inc_below(:,:,:,:,:) = zero
582    lignin_struc_inc_below(:,:,:) = zero
583    litter_inc_PFT_above(:,:,:,:) = zero
584    litter_inc_PFT_below(:,:,:,:,:) = zero
585
586
587    DO j = 2,nvm !Loop over PFTs
588
589       !! 2.2.1 litter
590       DO k = 1, nlitt    !Loop over litter pools (metabolic and structural)
591
592          !! 2.2.2 calculate litter increase (per m^2 of ground).
593          !       Only a given fracion of fruit turnover is directly coverted into litter.
594          !       Litter increase for each PFT, structural and metabolic, above/below. It must
595          !       be noted that the distribution of above ground litter is done within the soil layers
596          !       as a proportion of the layer size. But for the below ground layer it follows the root profile
597
598          ! For the first litter layer
599          litter_inc_PFT_above(:,j,k,icarbon) = &
600               litterfrac(ileaf,k) * bm_to_litter(:,j,ileaf,icarbon) + &
601               litterfrac(isapabove,k) * bm_to_litter(:,j,isapabove,icarbon) + &
602               litterfrac(iheartabove,k) * bm_to_litter(:,j,iheartabove,icarbon) + &
603               litterfrac(ifruit,k) * bm_to_litter(:,j,ifruit,icarbon) + &
604               litterfrac(icarbres,k) * bm_to_litter(:,j,icarbres,icarbon) + &
605               litterfrac(ileaf,k) * turnover(:,j,ileaf,icarbon) + &
606               litterfrac(isapabove,k) * turnover(:,j,isapabove,icarbon) + &
607               litterfrac(iheartabove,k) * turnover(:,j,iheartabove,icarbon) + &
608               litterfrac(ifruit,k) * turnover(:,j,ifruit,icarbon) + &
609               litterfrac(icarbres,k) * turnover(:,j,icarbres,icarbon) 
610
611             ! litter increase, met/struct, above
612             litter_inc_above(:,k,j,icarbon) = litter_inc_above(:,k,j,icarbon) + litter_inc_PFT_above(:,j,k,icarbon)
613
614          !! The function used for root profile is coming from stomate_npp.f90
615       rpc(:) = un /( ( un - EXP( -z_soil(nbdl) / rprof(:,j) )) ) 
616
617          DO l = 1, nbdl
618             litter_inc_PFT_below(:,j,k,l,icarbon) = &
619                  litterfrac(isapbelow,k) * bm_to_litter(:,j,isapbelow,icarbon) *  &
620               rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
621                  litterfrac(iheartbelow,k) * bm_to_litter(:,j,iheartbelow,icarbon) * &
622               rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
623                  litterfrac(iroot,k) * bm_to_litter(:,j,iroot,icarbon) * &
624               rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
625                  litterfrac(isapbelow,k) * turnover(:,j,isapbelow,icarbon) * &
626               rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
627                  litterfrac(iheartbelow,k) * turnover(:,j,iheartbelow,icarbon) * &
628               rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
629                  litterfrac(iroot,k) * turnover(:,j,iroot,icarbon) * &
630               rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) )
631
632             ! litter increase, met/struct, below
633             litter_inc_below(:,k,j,l,icarbon) = litter_inc_below(:,k,j,l,icarbon) + litter_inc_PFT_below(:,j,k,l,icarbon)
634          ENDDO
635          !! 2.2.3 dead leaves, for soil cover.
636          dead_leaves(:,j,k) = &
637               dead_leaves(:,j,k) + &
638               litterfrac(ileaf,k) * ( bm_to_litter(:,j,ileaf,icarbon) + turnover(:,j,ileaf,icarbon) )
639
640          !! 2.2.4 lignin increase in structural litter
641          IF ( k .EQ. istructural ) THEN
642
643             lignin_struc_inc_above(:,j) = &
644                  lignin_struc_inc_above(:,j) + &
645                  LC(ileaf) * bm_to_litter(:,j,ileaf,icarbon) + &
646                  LC(isapabove) * bm_to_litter(:,j,isapabove,icarbon) + &
647                  LC(iheartabove) * bm_to_litter(:,j,iheartabove,icarbon) + &
648                  LC(ifruit) * bm_to_litter(:,j,ifruit,icarbon) + &
649                  LC(icarbres) * bm_to_litter(:,j,icarbres,icarbon) + &
650                  LC(ileaf) * turnover(:,j,ileaf,icarbon) + &
651                  LC(isapabove) * turnover(:,j,isapabove,icarbon) + &
652                  LC(iheartabove) * turnover(:,j,iheartabove,icarbon) + &
653                  LC(ifruit) * turnover(:,j,ifruit,icarbon) + &
654                  LC(icarbres) * turnover(:,j,icarbres,icarbon) 
655
656            !! The function used for root profile is coming from stomate_npp.f90
657            DO l = 1, nbdl
658
659               lignin_struc_inc_below(:,j,l) = &
660                  lignin_struc_inc_below(:,j,l) + &
661                  LC(isapbelow) * bm_to_litter(:,j,isapbelow,icarbon) * &
662                  rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
663                  LC(iheartbelow) * bm_to_litter(:,j,iheartbelow,icarbon) * &
664                  rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
665                  LC(iroot) * bm_to_litter(:,j,iroot,icarbon) * &
666                  rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
667                  LC(isapbelow)*turnover(:,j,isapbelow,icarbon) * &
668                  rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
669                  LC(iheartbelow)*turnover(:,j,iheartbelow,icarbon) * &
670                  rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) ) + &
671                  LC(iroot)*turnover(:,j,iroot,icarbon) * &
672                  rpc(:) * ( EXP( -z_soil(l-1)/rprof(:,j) ) - EXP( -z_soil(l)/rprof(:,j) ) )
673            ENDDO
674
675          ENDIF
676       ENDDO
677     ENDDO
678
679
680
681    !! 2.2.5 add new litter (struct/met, above/below)
682         litter_above(:,:,:,:) = litter_above(:,:,:,:) + litter_inc_above(:,:,:,:)
683         litter_below(:,:,:,:,:) = litter_below(:,:,:,:,:) + litter_inc_below(:,:,:,:,:)
684
685    !! 2.2.6 for security: can't add more lignin than structural litter (above/below)
686       DO m = 2,nvm !Lopp over PFTs
687
688          lignin_struc_inc_above(:,m) = &
689               MIN( lignin_struc_inc_above(:,m), litter_inc_above(:,istructural,m,icarbon) )
690
691       ENDDO
692
693    DO l = 1, nbdl !Loop over soil levels (below ground)
694       DO m = 2,nvm !Lopp over PFTs
695
696          lignin_struc_inc_below(:,m,l) = &
697               MIN( lignin_struc_inc_below(:,m,l), litter_inc_below(:,istructural,m,l,icarbon) )
698
699       ENDDO
700    ENDDO
701
702    !! 2.2.7.1 new lignin content: add old lignin and lignin increase, divide by
703    !!       total structural litter (above)
704
705       DO m = 2,nvm !Loop over PFTs
706          WHERE( litter_above(:,istructural,m,icarbon) .GT. min_stomate )
707
708       !MM : Soenke modif
709       ! Best vectorization ?
710!!$       lignin_struc(:,:,:) = &
711!!$            ( lignin_struc(:,:,:)*old_struc(:,:,:) + lignin_struc_inc(:,:,:) ) / &
712!!$            litter(:,istructural,:,:,icarbon)
713
714             lignin_struc_above(:,m) = lignin_struc_above(:,m) * old_struc_above(:,m)
715             lignin_struc_above(:,m) = lignin_struc_above(:,m) + lignin_struc_inc_above(:,m)
716             lignin_struc_above(:,m) = lignin_struc_above(:,m) / litter_above(:,istructural,m,icarbon)
717          ELSEWHERE
718             lignin_struc_above(:,m) = zero
719          ENDWHERE
720       ENDDO
721
722    !! 2.2.7.2 new lignin content: add old lignin and lignin increase, divide by
723    !!       total structural litter (below)
724    DO l = 1, nbdl !Loop over soil levels (below ground)
725       DO m = 2,nvm !Loop over PFTs
726          WHERE( litter_below(:,istructural,m,l,icarbon) .GT. min_stomate )
727
728       !MM : Soenke modif
729       ! Best vectorization ?
730!!$       lignin_struc(:,:,:) = &
731!!$            ( lignin_struc(:,:,:)*old_struc(:,:,:) + lignin_struc_inc(:,:,:)) / &
732!!$            litter(:,istructural,:,:,icarbon)
733
734             lignin_struc_below(:,m,l) = lignin_struc_below(:,m,l) * old_struc_below(:,m,l)
735             lignin_struc_below(:,m,l) = lignin_struc_below(:,m,l) + lignin_struc_inc_below(:,m,l)
736             lignin_struc_below(:,m,l) = lignin_struc_below(:,m,l) /litter_below(:,istructural,m,l,icarbon)
737          ELSEWHERE
738             lignin_struc_below(:,m,l) = zero
739          ENDWHERE
740       ENDDO
741    ENDDO
742
743   
744    !! 2.3 new litter fraction per PFT (for structural and metabolic litter, above
745    !!       the ground).
746       DO j = 2,nvm !Loop over PFTs
747         DO l =1,nlitt 
748         WHERE ( litter_above(:,l,j,icarbon) .GT. min_stomate )
749
750          litterpart(:,j,l) = &
751               ( litter_pft(:,j,l,icarbon) + litter_inc_PFT_above(:,j,l,icarbon) ) / litter_above(:,l,j,icarbon)
752
753         ELSEWHERE
754
755          litterpart(:,j,l) = zero
756
757         ENDWHERE
758         ENDDO
759       ENDDO
760  !! 3. Temperature control on decay: Factor between 0 and 1
761
762    !! 3.1 above: surface temperature
763    DO j=1,nlitt
764       control_temp_above(:,j) = control_temp_func (npts, tsurf,litter_tau(j)) 
765    ENDDO         
766    !! 3.2 below: convolution of temperature and decomposer profiles
767    !!            (exponential decomposer profile supposed)
768   
769    !! 3.2.1 integrate over the nbdl levels
770    tsoil_decomp(:) = zero
771
772    DO l = 1, nbdl
773       DO j = 1,npool
774
775          tsoil_decomp(:) = tsoil(:,l) 
776
777          control_temp_soil(:,l,j) = control_temp_func (npts,tsoil_decomp,pool_tau(j))
778
779       ENDDO
780    ENDDO
781!! #####BE CAREFUL WHEN I WILL CORRECT THE CONTROL_TEMP I SHOULD CHANGE THE
782!! FOLLOWING LINES####
783    DO l = 1, nbdl
784       DO j = 1,npool
785         DO m= 1,nvm
786          tsoil_decomp(:) = tsoil(:,l)
787
788          control_temp_soil(:,l,npool+j) = control_temp_func(npts,tsoil_decomp,DOC_tau(j,m))
789
790         ENDDO
791       ENDDO
792    ENDDO
793
794  !! 4. Moisture control. Factor between 0 and 1
795
796    !! 4.1 above the ground: litter humidity
797
798
799    soilhum_decomp(:) = zero
800    DO m= 1,nvm
801       !We used the sum over the 4 first layer as it is done to
802       !compute litterhum in hydrol.f90
803         soilhum_decomp(:) =soil_mc(:,1,pref_soil_veg(m))*(z_soil(1)/z_soil(4)) + &
804                            soil_mc(:,2,pref_soil_veg(m))*((z_soil(2)-z_soil(1))/z_soil(4)) + &
805                            soil_mc(:,3,pref_soil_veg(m))*((z_soil(3)-z_soil(2))/z_soil(4)) + &
806                            soil_mc(:,4,pref_soil_veg(m))*((z_soil(4)-z_soil(3))/z_soil(4))
807
808       IF (moist_func_Moyano) THEN
809        control_moist_above(:,m) = control_moist_func_moyano (npts, soilhum_decomp,bulk_dens, &
810                                                    clay, carbon, veget_max)
811       ELSE
812         control_moist_above(:,m) = control_moist_func (npts,soilhum_decomp)
813       ENDIF
814    ENDDO
815    !! 4.2 below: soil humidity for each soil layers
816
817    !! 4.2.1 integrate over the nbdl levels
818    soilhum_decomp(:) = zero
819
820    DO l = 1, nbdl !Loop over soil levels
821      DO m =1,nvm
822         soilhum_decomp(:) =soil_mc(:,l,pref_soil_veg(m))
823         IF (moist_func_Moyano) THEN
824         control_moist_soil(:,l,m) = control_moist_func_moyano (npts, soilhum_decomp,bulk_dens, &
825                                                  clay, carbon, veget_max)
826         ELSE
827         control_moist_soil(:,l,m) = control_moist_func (npts, soilhum_decomp)
828         ENDIF
829
830      ENDDO
831    ENDDO
832
833  !! 5. fluxes from above ground litter to carbon pools and respiration
834      DO m = 2,nvm !Loop over PFTs
835
836          !! 5.1 structural litter: goes into active and slow carbon pools + respiration
837
838          !! 5.1.1 total quantity of above ground structural litter which is decomposed
839
840      WHERE (soil_mc(:,1,pref_soil_veg(m)) .GT. zero)
841          fd(:) = dt/litter_tau(istructural) * &
842             control_temp_above(:,istructural) * control_moist_above(:,m) * exp( -litter_struct_coef * lignin_struc_above(:,m) )
843           
844      ELSEWHERE
845          fd(:) = zero
846      ENDWHERE
847          DO k = 1,nelements
848
849             qd(:,k) = litter_above(:,istructural,m,k) * fd(:)
850
851          ENDDO
852
853          !! 5.1.2 decompose same fraction of structural part of dead leaves. Not exact
854          !!       as lignine content is not the same as that of the total structural litter.
855          dead_leaves(:,m,istructural) = dead_leaves(:,m,istructural) * ( un - fd(:) )
856
857
858      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
859      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
860      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dtradia/one_day
861      ! time step and avoid some constructions that could create bug during future developments.
862          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
863               ( 1. - frac_soil(istructural,iactive,iabove) ) * qd(:,icarbon) * &
864               ( 1. - lignin_struc_above(:,m) ) / dt
865
866
867          !resp_hetero_litter_layer(:,m,1) = resp_hetero_litter_layer(:,m,1) + &
868          !    ( 1. - frac_soil(istructural,iactive,iabove) ) * qd(:,icarbon) * &
869          !     ( 1. - lignin_struc_above(:,m) ) / dt
870
871      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
872      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
873      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dtradia/one_day
874      ! time step and avoid some constructions that could create bug during future developments.
875          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
876               ( 1. - frac_soil(istructural,islow,iabove) ) * qd(:,icarbon) * lignin_struc_above(:,m) / dt
877
878         ! resp_hetero_litter_layer(:,m,1) = resp_hetero_litter_layer(:,m,1) + &
879         !      ( 1. - frac_soil(istructural,islow,iabove) ) * qd(:,icarbon) *lignin_struc_above(:,m) / dt
880
881          !! 5.1.3 Calculation of the soilcarbon_input in gC m^-2 of water
882
883!          DO k = 1, nelements
884!
885!             soilcarbon_input(:,m,1,istrabo,k) = (frac_soil(istructural,iactive,iabove) * ( 1. - lignin_struc_above(:,m) ) *  qd(:,k) + &
886!                                  frac_soil(istructural,islow,iabove) *  qd(:,k) * lignin_struc_above(:,m) ) /dt
887!         ENDDO
888
889
890          DO k = 1, nelements
891
892             soilcarbon_input(:,m,1,istrabo,k) = (z_soil(1)/z_soil(sro_bottom))*(frac_soil(istructural,iactive,iabove) * ( 1. - lignin_struc_above(:,m) ) *  qd(:,k) + &
893                                  frac_soil(istructural,islow,iabove) *  qd(:,k) * lignin_struc_above(:,m) ) /dt
894          IF (sro_bottom .GT. 1) THEN
895             DO l=2,sro_bottom !Loop over the first layers
896
897                 soilcarbon_input(:,m,l,istrabo,k) = ((z_soil(l)-z_soil(l-1))/z_soil(sro_bottom))*(frac_soil(istructural,iactive,iabove) * ( 1. - lignin_struc_above(:,m) ) *  qd(:,k) + &
898                                      frac_soil(istructural,islow,iabove) *  qd(:,k) * lignin_struc_above(:,m) ) /dt
899             ENDDO
900          ENDIF
901          ENDDO
902
903
904
905          litter_above(:,istructural,m,:) = litter_above(:,istructural,m,:) - qd(:,:)
906
907
908         
909          !! 5.2 above ground metabolic litter goes into active carbon pool + respiration
910         
911          !! 5.2.1 total quantity of aboveground metabolic litter that is decomposed
912      WHERE (soil_mc(:,1,pref_soil_veg(m)) .GT. zero)
913          fd(:) = dt/litter_tau(imetabolic) * control_temp_above(:,imetabolic) * control_moist_above(:,m)
914                 
915      ELSEWHERE
916          fd(:) = zero
917      ENDWHERE
918
919          DO k = 1,nelements
920         
921             qd(:,k) = litter_above(:,imetabolic,m,k) * fd(:)
922
923          ENDDO
924
925
926          !! 5.2.2 decompose same fraction of metabolic part of dead leaves.
927          dead_leaves(:,m,imetabolic) = dead_leaves(:,m,imetabolic) * ( 1. - fd(:) )
928
929
930      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
931      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
932      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dtradia/one_day
933      ! time step and avoid some constructions that could create bug during future developments.
934          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
935               ( 1. - frac_soil(imetabolic,iactive,iabove) ) * qd(:,icarbon) / dt
936
937         ! resp_hetero_litter_layer(:,m,1) = resp_hetero_litter_layer(:,m,1) + &
938         !      ( 1. - frac_soil(imetabolic,iactive,iabove) ) * qd(:,icarbon) / dt
939
940          !! 5.2.3 Calculation of the soilcarbon_input in gC m^-2 of water
941             ! For above ground litter we assume that the soilcarbon_input coming from AB
942             ! litter decomposition is directly incorporated into the 1st soil
943             ! layers
944
945!          DO k = 1, nelements
946!
947!             soilcarbon_input(:,m,1,imetabo,k) = frac_soil(imetabolic,iactive,iabove) *  qd(:,k) / dt
948!
949!         ENDDO
950
951          DO k = 1, nelements
952
953             soilcarbon_input(:,m,1,imetabo,k) = (z_soil(1)/z_soil(sro_bottom))*frac_soil(imetabolic,iactive,iabove) *  qd(:,k) / dt
954          IF (sro_bottom .GT. 1) THEN
955             DO l = 2,sro_bottom
956
957                 soilcarbon_input(:,m,l,imetabo,k) = ((z_soil(l)-z_soil(l-1))/z_soil(sro_bottom))*frac_soil(imetabolic,iactive,iabove) *  qd(:,k) / dt
958
959             ENDDO
960         ENDIF
961         ENDDO
962
963          litter_above(:,imetabolic,m,:) = litter_above(:,imetabolic,m,:) - qd(:,:)
964
965      ENDDO
966
967!! 6. fluxes from below ground litter to carbon pools and respiration
968   DO l = 1,nbdl
969       DO m = 2,nvm !Loop over PFTs
970
971          !! 6.1 structural litter: goes into active and slow carbon pools respiration
972
973          !! 6.1.1 total quantity of below ground structural litter which is decomposed
974    WHERE (soil_mc(:,l,pref_soil_veg(m)) .GT. zero)
975          fd(:) = dt/litter_tau(istructural) * &
976               control_temp_soil(:,l,istrbel) * control_moist_soil(:,l,m) * exp(-litter_struct_coef * lignin_struc_below(:,m,l) )
977               
978    ELSEWHERE
979          fd(:) = zero
980    ENDWHERE
981
982          DO k = 1,nelements
983
984             qd(:,k) = litter_below(:,istructural,m,l,k) * fd(:)
985
986          ENDDO
987
988
989      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
990      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
991      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dtradia/one_day
992      ! time step and avoid some constructions that could create bug during future developments.
993          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
994               ( 1. - frac_soil(istructural,iactive,ibelow) ) * qd(:,icarbon) * &
995               ( 1. - lignin_struc_below(:,m,l) ) / dt
996
997         ! resp_hetero_litter_layer(:,m,l) = resp_hetero_litter_layer(:,m,l) + &
998         !      ( 1. - frac_soil(istructural,iactive,ibelow) ) * qd(:,icarbon) * &
999         !      ( 1. - lignin_struc_below(:,m,l) ) / dt
1000
1001
1002      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
1003      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
1004      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dtradia/one_day
1005      ! time step and avoid some constructions that could create bug during future developments.
1006          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
1007               ( 1. - frac_soil(istructural,islow,ibelow) ) * qd(:,icarbon) * lignin_struc_below(:,m,l) / dt
1008
1009         ! resp_hetero_litter_layer(:,m,l) = resp_hetero_litter_layer(:,m,l) + &
1010         !      ( 1. - frac_soil(istructural,islow,ibelow) ) * qd(:,icarbon) * lignin_struc_below(:,m,l) / dt
1011
1012          !! 6.1 Calculation of the soilcarbon_input in gC m^-2
1013
1014          DO k = 1, nelements
1015
1016
1017                  soilcarbon_input(:,m,l,istrbel,k) = (frac_soil(istructural,iactive,ibelow) * ( 1. - lignin_struc_below(:,m,l) ) * qd(:,k) + & 
1018                                             (frac_soil(istructural,islow,ibelow) * qd(:,k) * lignin_struc_below(:,m,l) )) / dt 
1019         ENDDO
1020
1021      litter_below(:,istructural,m,l,:) = litter_below(:,istructural,m,l,:) - qd(:,:)
1022
1023          !! 6.2 below ground metabolic litter goes into active carbon pool + respiration
1024
1025          !! 6.2.1 total quantity of belowground metabolic litter that is decomposed
1026    WHERE (soil_mc(:,l,pref_soil_veg(m)) .GT. zero)
1027          fd(:) = dt/litter_tau(imetabolic) * control_temp_soil(:,l,imetbel) * control_moist_soil(:,l,m)
1028    ELSEWHERE
1029          fd(:) = zero
1030    ENDWHERE
1031
1032          DO k = 1,nelements
1033
1034             qd(:,k) = litter_below(:,imetabolic,m,l,k) * fd(:)
1035
1036          ENDDO
1037
1038
1039      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
1040      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
1041      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dtradia/one_day
1042      ! time step and avoid some constructions that could create bug during future developments.
1043          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
1044               ( 1. - frac_soil(imetabolic,iactive,ibelow) ) * qd(:,icarbon) /dt
1045
1046        !  resp_hetero_litter_layer(:,m,l) = resp_hetero_litter_layer(:,m,l) + &
1047        !       ( 1. - frac_soil(imetabolic,iactive,ibelow) ) * qd(:,icarbon) /dt
1048
1049
1050          !! 6.2.3 Calculation of the soilcarbon_input in gC m^-2 of water
1051
1052          DO k = 1, nelements
1053                soilcarbon_input(:,m,l,imetbel,k) = frac_soil(imetabolic,iactive,ibelow) * qd(:,k) / dt 
1054
1055         ENDDO
1056   
1057      litter_below(:,imetabolic,m,l,:) = litter_below(:,imetabolic,m,l,:) - qd(:,:)
1058
1059       ENDDO
1060   ENDDO
1061
1062
1063  !! 7. Transport of particulate organic C (i.e. active, slow and passive
1064  !! pools) following the second Fick's Law (O¿Brien and Stout, 1978; Wynn
1065  !! et al., 2005). Represent the bioturbation and is generally associated
1066  !! with transport in the liquid phase like in the section 3.2.5 (Elzein
1067  !! and Balesdent, 1995; Bruun et al., 2007; Braakhekke et al., 2011,
1068  !! Guenet et al., 2013)
1069
1070  ! Definition of the diffusion rate from Guenet et al., (2013) BG for the
1071  ! moment but must depends on clay, ph organic C, or whatever...
1072
1073!   DO m =2,nvm
1074!      DO k = 1, nelements
1075!         DO j = 1,nlitt
1076!            litter_above_flux(:,j,m,k) = Dif_coef(:)*dt*ABS(litter_above(:,j,m,k)/(z_litter*1e-3)-litter_below(:,j,m,1,k)/(z_litter*1e-3-z_soil(1)))
1077!            ! BE CAREFUL: Here very important assumption we assume the above ground litter layers to be 10mm thick by default.
1078!
1079!            litter_flux(:,j,m,1,k) = Dif_coef(:)*dt*ABS(litter_below(:,j,m,1,k)/(z_soil(1))-litter_below(:,j,m,2,k)/(z_soil(2)-z_soil(1)))/(z_soil(2)-z_soil(1))
1080!
1081!           DO l = 2, nbdl-1
1082!            litter_flux(:,j,m,l,k) = Dif_coef(:)*dt*ABS(litter_below(:,j,m,l,k)/(z_soil(l)-z_soil(l-1))-litter_below(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)))/(z_soil(l+1)-z_soil(l)) 
1083!           ENDDO
1084!
1085!           WHERE ((litter_above(:,j,m,k)/(z_litter*1e-3) .LT. litter_below(:,j,m,1,k)/(z_soil(1))) )
1086!            litter_above(:,j,m,k) = litter_above(:,j,m,k) + MIN(litter_below(:,j,m,1,k),litter_above_flux(:,j,m,k))
1087!            litter_below(:,j,m,1,k) = litter_below(:,j,m,1,k) - MIN(litter_below(:,j,m,1,k),litter_above_flux(:,j,m,k))
1088!           ELSEWHERE ((litter_above(:,j,m,k)/(z_litter*1e-3) .GT. litter_below(:,j,m,1,k)/(z_soil(1))))
1089!            litter_above(:,j,m,k) = litter_above(:,j,m,k) - MIN(litter_above(:,j,m,k),litter_above_flux(:,j,m,k))
1090!            litter_below(:,j,m,1,k) = litter_below(:,j,m,1,k) + MIN(litter_above(:,j,m,k),litter_above_flux(:,j,m,k))
1091!           ELSEWHERE
1092!            litter_above(:,j,m,k) = litter_above(:,j,m,k)
1093!            litter_below(:,j,m,1,k) = litter_below(:,j,m,1,k)
1094!           ENDWHERE
1095!
1096!           WHERE ((litter_below(:,j,m,1,k)/(z_soil(1)) .LT. litter_below(:,j,m,2,k)/(z_soil(2)-z_soil(1))))
1097!            litter_below(:,j,m,1,k) = litter_below(:,j,m,1,k) + MIN(litter_below(:,j,m,2,k),litter_flux(:,j,m,1,k))
1098!            litter_below(:,j,m,2,k) = litter_below(:,j,m,2,k) - MIN(litter_below(:,j,m,2,k),litter_flux(:,j,m,1,k))
1099!           ELSEWHERE ((litter_below(:,j,m,1,k)/(z_soil(1)) .GT. litter_below(:,j,m,2,k)/(z_soil(2)-z_soil(1))) )
1100!            litter_below(:,j,m,1,k) = litter_below(:,j,m,1,k) - MIN(litter_below(:,j,m,1,k),litter_flux(:,j,m,1,k))
1101!            litter_below(:,j,m,2,k) = litter_below(:,j,m,2,k) + MIN(litter_below(:,j,m,1,k),litter_flux(:,j,m,1,k))
1102!           ELSEWHERE
1103!            litter_below(:,j,m,1,k) = litter_below(:,j,m,1,k)
1104!            litter_below(:,j,m,2,k) = litter_below(:,j,m,2,k)
1105!           ENDWHERE
1106!
1107!
1108 !     DO l= 2, nbdl-1 ! Loop over soil layers
1109!
1110!           WHERE ((litter_below(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .LT. litter_below(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l))) )
1111!            litter_below(:,j,m,l,k) = litter_below(:,j,m,l,k) + MIN(litter_below(:,j,m,l+1,k),litter_flux(:,j,m,l,k))
1112!            litter_below(:,j,m,l+1,k) = litter_below(:,j,m,l+1,k) - MIN(litter_below(:,j,m,l+1,k),litter_flux(:,j,m,l,k))
1113!           ELSEWHERE ((litter_below(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .GT. litter_below(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l))) )
1114!            litter_below(:,j,m,l,k) = litter_below(:,j,m,l,k) - MIN(litter_below(:,j,m,l,k),litter_flux(:,j,m,l,k))
1115!            litter_below(:,j,m,l+1,k) = litter_below(:,j,m,l+1,k) + MIN(litter_below(:,j,m,l,k),litter_flux(:,j,m,l,k))
1116!           ELSEWHERE
1117!            litter_below(:,j,m,l,k) = litter_below(:,j,m,l,k)
1118!           ENDWHERE
1119!
1120!          ENDDO ! End loop over elements
1121!        ENDDO ! End loop over carbon pools
1122!      ENDDO ! End loop over soil layers
1123!
1124!    ENDDO
1125
1126DO m =2,nvm
1127
1128litter_below_old(:,:,m,:,:)=zero
1129litter_below_old_buffer(:,:,m,:,:)=zero
1130litter_below_old(:,:,m,:,:)=litter_below(:,:,m,:,:)
1131litter_above_old(:,:,m,:)=zero
1132litter_above_old(:,:,m,:)=litter_above(:,:,m,:)
1133      DO k = 1, nelements ! Loop over elements
1134         DO j = 1,nlitt ! Loop over litter pools
1135
1136        litter_flux(:,j,m,1,k) = Dif_coef(:)*ABS(litter_below_old(:,j,m,1,k)/(z_soil(1))-litter_below_old(:,j,m,2,k)/(z_soil(2)-z_soil(1)))/(z_soil(2)-z_soil(1))
1137        litter_above_flux(:,j,m,k) = Dif_coef(:)*ABS(litter_above(:,j,m,k)/(z_litter*1e-3)-litter_below(:,j,m,1,k)/(z_litter*1e-3-z_soil(1)))
1138            ! BE CAREFUL: Here very important assumption we assume the above ground litter layers to be 10mm thick by default.
1139
1140      DO l= 2, nbdl-1 ! Loop over soil layers
1141        litter_flux(:,j,m,l,k) = Dif_coef(:)*ABS(litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1))-litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)))/(z_soil(l+1)-z_soil(l))
1142      ENDDO
1143        litter_flux_old(:,j,m,:,k) = litter_flux(:,j,m,:,k)
1144        litter_above_flux_old(:,j,m,k) = litter_above_flux(:,j,m,k)
1145
1146       !Below we checked if in case that, in a given layer, you have diffusion in the above and below litters, both fluxes are not higher than the stocks of the given layer.
1147           WHERE (litter_above_old(:,j,m,k)/(z_litter*1e-3) .LT. litter_below_old(:,j,m,1,k)/(z_soil(1)) .AND. &
1148                  litter_below_old(:,j,m,2,k)/(z_soil(2)-z_soil(1)) .LT. litter_below_old(:,j,m,1,k)/(z_soil(1)) .AND. &
1149                  litter_above_flux_old(:,j,m,k)+litter_flux_old(:,j,m,1,k) .GT. litter_below_old(:,j,m,1,k))
1150            litter_above_flux(:,j,m,k) = litter_below_old(:,j,m,1,k)*(litter_above_flux_old(:,j,m,k)/(litter_above_flux_old(:,j,m,k)+litter_flux_old(:,j,m,1,k)))
1151            litter_flux(:,j,m,1,k) = litter_below_old(:,j,m,1,k)*(litter_flux_old(:,j,m,1,k)/(litter_above_flux_old(:,j,m,k)+litter_flux_old(:,j,m,1,k)))
1152           ELSEWHERE (litter_above_old(:,j,m,k)/(z_litter*1e-3) .GE. litter_below_old(:,j,m,1,k)/(z_soil(1)) .AND. &
1153                      litter_below_old(:,j,m,2,k)/(z_soil(2)-z_soil(1)) .LT. litter_below_old(:,j,m,1,k)/(z_soil(1)) .AND. &
1154                      litter_below_old(:,j,m,1,k) + litter_above_flux_old(:,j,m,k) - litter_flux_old(:,j,m,1,k) .LE. min_stomate)
1155            litter_above_flux(:,j,m,k) = litter_above_flux_old(:,j,m,k)
1156            litter_flux(:,j,m,1,k) = litter_below_old(:,j,m,1,k) + litter_above_flux_old(:,j,m,k)
1157           ELSEWHERE (litter_above_old(:,j,m,k)/(z_litter*1e-3) .LT. litter_below_old(:,j,m,1,k)/(z_soil(1)) .AND. &
1158                      litter_below_old(:,j,m,2,k)/(z_soil(2)-z_soil(1)) .GE. litter_below_old(:,j,m,1,k)/(z_soil(1)) .AND. &
1159                      litter_below_old(:,j,m,1,k) - litter_above_flux_old(:,j,m,k) + litter_flux_old(:,j,m,1,k) .LE. min_stomate)
1160            litter_above_flux(:,j,m,k) = litter_below_old(:,j,m,1,k) + litter_flux_old(:,j,m,1,k) 
1161            litter_flux(:,j,m,1,k) = litter_flux_old(:,j,m,1,k)
1162           ELSEWHERE
1163            litter_above_flux(:,j,m,k) = litter_above_flux_old(:,j,m,k)
1164            litter_flux(:,j,m,1,k) = litter_flux_old(:,j,m,1,k)
1165           ENDWHERE
1166
1167
1168      DO l =1, nbdl-2
1169           WHERE (litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .LT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)) .AND. &
1170                  litter_below_old(:,j,m,l+2,k)/(z_soil(l+2)-z_soil(l+1)) .LT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)) .AND. &
1171                  litter_flux_old(:,j,m,l,k)+litter_flux_old(:,j,m,l+1,k) .GT. litter_below_old(:,j,m,l+1,k))
1172            litter_flux(:,j,m,l,k) = litter_below_old(:,j,m,l+1,k)*(litter_flux_old(:,j,m,l,k)/(litter_flux_old(:,j,m,l,k)+litter_flux_old(:,j,m,l+1,k)))
1173            litter_flux(:,j,m,l+1,k) = litter_below_old(:,j,m,l+1,k)*(litter_flux_old(:,j,m,l+1,k)/(litter_flux_old(:,j,m,l,k)+litter_flux_old(:,j,m,l+1,k)))
1174           ELSEWHERE (litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .GE. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)) .AND. &
1175                      litter_below_old(:,j,m,l+2,k)/(z_soil(l+2)-z_soil(l+1)) .LT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)) .AND. &
1176                      litter_below_old(:,j,m,l+1,k) + litter_flux_old(:,j,m,l,k) - litter_flux_old(:,j,m,l+1,k) .LE. min_stomate)
1177            litter_flux(:,j,m,l,k) = litter_flux_old(:,j,m,l,k)
1178            litter_flux(:,j,m,l+1,k) = litter_below_old(:,j,m,l+1,k) + litter_flux_old(:,j,m,l,k)
1179           ELSEWHERE (litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .LT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)) .AND. &
1180                      litter_below_old(:,j,m,l+2,k)/(z_soil(l+2)-z_soil(l+1)) .GE. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l)) .AND. &
1181                      litter_below_old(:,j,m,l+1,k) - litter_flux_old(:,j,m,l,k) + litter_flux_old(:,j,m,l+1,k) .LE. min_stomate)
1182            litter_flux(:,j,m,l,k) = litter_below_old(:,j,m,l+1,k) + litter_flux_old(:,j,m,l+1,k)
1183            litter_flux(:,j,m,l+1,k) = litter_flux_old(:,j,m,l+1,k)
1184           ELSEWHERE
1185            litter_flux(:,j,m,l,k) = litter_flux_old(:,j,m,l,k)
1186            litter_flux(:,j,m,l+1,k) = litter_flux_old(:,j,m,l+1,k)
1187           ENDWHERE
1188      ENDDO
1189
1190          WHERE ((litter_above_old(:,j,m,k)/(z_litter*1e-3) .LT. litter_below_old(:,j,m,1,k)/(z_soil(1))) .AND. &
1191                 ((litter_above_flux(:,j,m,k) - litter_below_old(:,j,m,1,k)) .GE. min_stomate))
1192            litter_above(:,j,m,k) = litter_above_old(:,j,m,k) + litter_below_old(:,j,m,1,k) 
1193            litter_below_old_buffer(:,j,m,1,k) = -litter_below_old(:,j,m,1,k) 
1194            litter_below(:,j,m,1,k) = zero
1195           ELSEWHERE ((litter_above_old(:,j,m,k)/(z_litter*1e-3) .LT. litter_below_old(:,j,m,1,k)/(z_soil(1))) .AND. &
1196                  ((litter_below_old(:,j,m,1,k) - litter_above_flux(:,j,m,k)) .GT. min_stomate))
1197            litter_above(:,j,m,k) = litter_above_old(:,j,m,k) + litter_above_flux(:,j,m,k) 
1198            litter_below_old_buffer(:,j,m,1,k) =  - litter_above_flux(:,j,m,k)
1199            litter_below(:,j,m,1,k) = litter_below_old(:,j,m,1,k) - litter_above_flux(:,j,m,k)
1200           ELSEWHERE ((litter_above_old(:,j,m,k)/(z_litter*1e-3) .GT. litter_below_old(:,j,m,1,k)/(z_soil(1))) .AND. &
1201                  ((litter_above_flux(:,j,m,k) - litter_above_old(:,j,m,k)) .GE. min_stomate))
1202            litter_above(:,j,m,k) = zero 
1203            litter_below_old_buffer(:,j,m,1,k) = litter_above_old(:,j,m,k)
1204            litter_below(:,j,m,1,k) = litter_below_old(:,j,m,1,k) + litter_above_old(:,j,m,k)
1205           ELSEWHERE ((litter_above_old(:,j,m,k)/(z_litter*1e-3) .GT. litter_below_old(:,j,m,1,k)/(z_soil(1))) .AND. &
1206                  ((litter_above_old(:,j,m,k) - litter_above_flux(:,j,m,k)) .GT. min_stomate))
1207            litter_above(:,j,m,k) = litter_above_old(:,j,m,k) - litter_above_flux(:,j,m,k)
1208            litter_below_old_buffer(:,j,m,1,k) = litter_above_flux(:,j,m,k)
1209            litter_below(:,j,m,1,k) = litter_below_old(:,j,m,1,k) + litter_above_flux(:,j,m,k)
1210           ELSEWHERE
1211            litter_above(:,j,m,k) = litter_above_old(:,j,m,k)
1212            litter_below(:,j,m,1,k) = litter_below_old(:,j,m,1,k)
1213           ENDWHERE
1214
1215      DO l= 1, nbdl-1 ! Loop over soil layers
1216           WHERE ((litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .LT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l))) .AND. &
1217                 ((litter_flux(:,j,m,l,k) - litter_below_old(:,j,m,l+1,k)) .GE. min_stomate))
1218            litter_below(:,j,m,l,k) = litter_below_old(:,j,m,l,k) + litter_below_old(:,j,m,l+1,k) + litter_below_old_buffer(:,j,m,l,k)
1219            litter_below_old_buffer(:,j,m,l+1,k) = -litter_below_old(:,j,m,l+1,k)
1220            litter_below(:,j,m,l+1,k) = zero
1221           ELSEWHERE ((litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .LT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l))) .AND. &
1222                  ((litter_below_old(:,j,m,l+1,k) - litter_flux(:,j,m,l,k)) .GT. min_stomate))
1223            litter_below(:,j,m,l,k) = litter_below_old(:,j,m,l,k) + litter_flux(:,j,m,l,k) + litter_below_old_buffer(:,j,m,l,k)
1224            litter_below_old_buffer(:,j,m,l+1,k) =  - litter_flux(:,j,m,l,k)
1225            litter_below(:,j,m,l+1,k) = litter_below_old(:,j,m,l+1,k) - litter_flux(:,j,m,l,k)
1226           ELSEWHERE ((litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .GT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l))) .AND. &
1227                  ((litter_flux(:,j,m,l,k) - litter_below_old(:,j,m,l,k)) .GE. min_stomate))
1228            litter_below(:,j,m,l,k) = zero + litter_below_old_buffer(:,j,m,l,k)
1229            litter_below_old_buffer(:,j,m,l+1,k) = litter_below_old(:,j,m,l,k)
1230            litter_below(:,j,m,l+1,k) = litter_below_old(:,j,m,l+1,k) + litter_below_old(:,j,m,l,k)
1231           ELSEWHERE ((litter_below_old(:,j,m,l,k)/(z_soil(l)-z_soil(l-1)) .GT. litter_below_old(:,j,m,l+1,k)/(z_soil(l+1)-z_soil(l))) .AND. &
1232                  ((litter_below_old(:,j,m,l,k) - litter_flux(:,j,m,l,k)) .GT. min_stomate))
1233            litter_below(:,j,m,l,k) = litter_below_old(:,j,m,l,k) - litter_flux(:,j,m,l,k) + litter_below_old_buffer(:,j,m,l,k)
1234            litter_below_old_buffer(:,j,m,l+1,k) = litter_flux(:,j,m,l,k)
1235            litter_below(:,j,m,l+1,k) = litter_below_old(:,j,m,l+1,k) + litter_flux(:,j,m,l,k)
1236           ELSEWHERE
1237            litter_below(:,j,m,l,k) = litter_below_old(:,j,m,l,k)
1238            litter_below(:,j,m,l+1,k) = litter_below_old(:,j,m,l+1,k)
1239           ENDWHERE
1240        ENDDO ! End loop over soil layers
1241      ENDDO ! End loop over litter pools
1242    ENDDO ! End loop over elements
1243ENDDO ! End loop over PFT
1244
1245  !! 8. calculate fraction of total soil covered by dead leaves
1246
1247    CALL deadleaf (npts, veget_max, dead_leaves, deadleaf_cover)
1248
1249!! 9. Check mass balance closure
1250
1251    !! 9.1 Calculate components of the mass balance
1252    pool_end_after(:,:,:) = zero
1253    pool_end(:,:,:) = zero
1254IF (ld_doc) THEN
1255    DO m = 2, nvm
1256       DO i = 1,nlitt
1257          DO l = 1, nbdl
1258                 pool_end(:,m,icarbon) = pool_end(:,m,icarbon) + &
1259                           ( litter_below(:,i,m,l,icarbon) ) * veget_max(:,m)
1260          ENDDO
1261       ENDDO
1262    ENDDO
1263
1264    DO m = 2, nvm
1265       DO i = 1,nlitt
1266                 pool_end(:,m,icarbon) = pool_end(:,m,icarbon) + &
1267                           ( litter_above(:,i,m,icarbon) ) * veget_max(:,m)
1268       ENDDO
1269    ENDDO
1270
1271
1272    !! 9.2 Calculate mass balance
1273    !  Note that soilcarbon is transfered to other pools but that the pool
1274    !  was not updated. We should not account for it in ::pool_end
1275
1276WRITE(numout,*) " pool_start(:,m,icarbon) litter=",  pool_start(:,4,icarbon)
1277WRITE(numout,*) " pool_end(:,m,icarbon) litter=",  pool_end(:,4,icarbon)
1278
1279    check_intern(:,:,:,:) = zero
1280       check_intern(:,:,iatm2land,icarbon) = zero 
1281
1282   
1283    check_intern(:,:,iland2atm,icarbon) = -un * resp_hetero_litter(:,:) * &
1284         veget_max(:,:) * dt
1285   
1286
1287    DO m = 1,nvm
1288       DO l = 1, nbdl
1289          check_intern(:,m,ilat2out,icarbon) = check_intern(:,m,ilat2out,icarbon) -un * &
1290                      (soilcarbon_input(:,m,l,imetbel,icarbon)+soilcarbon_input(:,m,l,istrbel,icarbon)) * &
1291                      veget_max(:,m) * dt
1292      ENDDO
1293    ENDDO
1294
1295    DO m = 1,nvm
1296       DO l = 1, nbdl
1297       check_intern(:,m,ilat2out,icarbon) = check_intern(:,m,ilat2out,icarbon) -un * &
1298                   (soilcarbon_input(:,m,l,imetabo,icarbon)+soilcarbon_input(:,m,l,istrabo,icarbon)) * &
1299                   veget_max(:,m) * dt
1300       ENDDO
1301    ENDDO
1302
1303    check_intern(:,:,ilat2in,icarbon) = zero
1304   
1305    check_intern(:,:,ipoolchange,icarbon) = -un * (pool_end(:,:,icarbon) - &
1306         pool_start(:,:,icarbon))
1307   
1308    closure_intern = zero
1309    DO i = 1,nmbcomp
1310      closure_intern(:,:,icarbon) = closure_intern(:,:,icarbon) + &
1311            check_intern(:,:,i,icarbon)
1312    ENDDO
1313
1314    !! 9.3 Write verdict
1315
1316
1317    !WRITE(numout,*) 'l=',l
1318!    WRITE(numout,*) 'check_intern litter =',  check_intern(:,6,:,icarbon)
1319    IF (SUM(SUM(closure_intern(:,:,icarbon),2),1) .LT. min_stomate .AND. &
1320         SUM(SUM(closure_intern(:,:,icarbon),2),1) .GT. -min_stomate) THEN
1321       WRITE(numout,*) 'Mass balance closure in stomate_litter.f90'
1322    ELSE
1323       WRITE(numout,*) 'Error: mass balance is not closed in stomate_litter.f90'
1324       WRITE(numout,*) '   Difference is, ', SUM(SUM(closure_intern(:,:,icarbon),2),1)
1325       WRITE(numout,*) '   Difference is, ', closure_intern(:,:,icarbon)
1326    ENDIF
1327ENDIF
1328
1329
1330    IF (printlev>=4) WRITE(numout,*) 'Leaving littercalc'
1331
1332  END SUBROUTINE littercalc
1333
1334
1335!! ==============================================================================================================================\n
1336!! SUBROUTINE   : deadleaf
1337!!
1338!>\BRIEF        This routine calculates the deadleafcover.
1339!!
1340!! DESCRIPTION  : It first calculates the lai corresponding to the dead leaves (LAI) using
1341!! the dead leaves carbon content (DL) the specific leaf area (sla) and the
1342!! maximal coverage fraction of a PFT (vegetmax) using the following equations:
1343!! \latexonly
1344!! \input{deadleaf1.tex}
1345!! \endlatexonly
1346!! \n
1347!! Then, the dead leaf cover (DLC) is calculated as following:\n
1348!! \latexonly
1349!! \input{deadleaf2.tex}
1350!! \endlatexonly
1351!! \n
1352!!
1353!! RECENT CHANGE(S) : None
1354!!
1355!! MAIN OUTPUT VARIABLE: ::deadleaf_cover
1356!!
1357!! REFERENCE(S) : None
1358!!
1359!! FLOWCHART : None
1360!! \n
1361!_ ================================================================================================================================
1362
1363  SUBROUTINE deadleaf (npts, veget_max, dead_leaves, deadleaf_cover)
1364
1365  !! 0. Variable and parameter declaration
1366   
1367    !! 0.1 Input variables
1368
1369    INTEGER(i_std), INTENT(in)                          :: npts           !! Domain size - number of grid pixels (unitless)
1370    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(in)  :: dead_leaves    !! Dead leaves per ground unit area, per PFT,
1371                                                                          !! metabolic and structural 
1372                                                                          !! @tex $(gC m^{-2})$ @endtex
1373    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)          :: veget_max      !! PFT "Maximal" coverage fraction of a PFT defined in
1374                                                                          !! the input vegetation map
1375                                                                          !! @tex $(m^2 m^{-2})$ @endtex
1376   
1377    !! 0.2 Output variables
1378   
1379    REAL(r_std), DIMENSION(npts), INTENT(out)           :: deadleaf_cover !! Fraction of soil covered by dead leaves over all PFTs
1380                                                                          !! (0-1, unitless)
1381
1382    !! 0.3 Modified variables
1383
1384    !! 0.4 Local variables
1385
1386    REAL(r_std), DIMENSION(npts)                        :: dead_lai       !! LAI of dead leaves @tex $(m^2 m^{-2})$ @endtex
1387    INTEGER(i_std)                                      :: j              !! Index (unitless)
1388!_ ================================================================================================================================
1389   
1390  !! 1. LAI of dead leaves
1391 
1392    dead_lai(:) = zero
1393
1394    DO j = 2,nvm !Loop over PFTs
1395       dead_lai(:) = dead_lai(:) + ( dead_leaves(:,j,imetabolic) + dead_leaves(:,j,istructural) ) * sla(j) &
1396            * veget_max(:,j)
1397    ENDDO
1398
1399  !! 2. fraction of soil covered by dead leaves
1400
1401    deadleaf_cover(:) = un - exp( - 0.5 * dead_lai(:) )
1402
1403    IF (printlev>=4) WRITE(numout,*) 'Leaving deadleaf'
1404
1405  END SUBROUTINE deadleaf
1406
1407
1408!! ================================================================================================================================
1409!! FUNCTION     : control_moist_func_moyano
1410!!
1411!>\BRIEF        Calculate moisture control for litter and soild C decomposition
1412!!
1413!! DESCRIPTION  : Calculate moisture control factor applied
1414!! to litter decomposition and to soil carbon decomposition in
1415!! stomate_soilcarbon.f90 using the following equation: \n
1416!! \latexonly
1417!! \input{control_moist_func1.tex}
1418!! \endlatexonly
1419!! \n
1420!! with M the moisture control factor and soilmoisutre, the soil moisture
1421!! calculated in sechiba.
1422!! Then, the function is ranged between 0.25 and 1:\n
1423!! \latexonly
1424!! \input{control_moist_func2.tex}
1425!! \endlatexonly
1426!! \n
1427!! RECENT CHANGE(S) : None
1428!!
1429!! RETURN VALUE : ::moistfunc_result
1430!!
1431!! REFERENCE(S) : None
1432!!
1433!! FLOWCHART : None
1434!! \n
1435!_ ================================================================================================================================
1436 
1437  FUNCTION control_moist_func_moyano (npts, moist_in,bulk_dens, clay, carbon,veget_max) RESULT (moistfunc_result)
1438
1439  !! 0. Variable and parameter declaration
1440
1441    !! 0.1 Input variables
1442
1443    INTEGER(i_std), INTENT(in)               :: npts                !! Domain size - number of grid pixel (unitless)
1444    REAL(r_std), DIMENSION(npts), INTENT(in) :: moist_in            !! relative humidity (unitless)
1445    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: clay               !! Clay fraction (unitless, 0-1)
1446    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: bulk_dens          !! Variable local of bulk density for the moment must change in the futur (kg m-3)
1447    REAL(r_std), DIMENSION(npts,ncarb,nvm,nbdl), INTENT(in)     :: carbon             !! Soil carbon pools: active, slow, or passive, \f$(gC m^{2})$\f
1448    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                  :: veget_max          !! Maximum fraction of vegetation type including
1449                                                                                      !! non-biological fraction (unitless)
1450
1451    !! 0.2 Output variables
1452
1453    REAL(r_std), DIMENSION(npts)          :: moistfunc_result    !! Moisture control factor (0-1, unitless)
1454
1455    !! 0.3 Modified variables
1456
1457    !! 0.4 Local variables
1458   REAL(r_std), DIMENSION(npts)           :: total_soc              !! Total soil organic carbon for a grid pixel (g-C g-1 soil)
1459   INTEGER(i_std)                         :: k,i,j                  !! Indices
1460   INTEGER, PARAMETER                     :: nummoist = 120         !! We used numoist then divived by 100. because to calculate the function
1461                                                                    !! we need to predict PRsr for all the possible soil moisture values
1462   REAL(r_std), DIMENSION(npts,nummoist)  :: PRsr                   !! Proportional response or soil respiration at moist_in
1463   REAL(r_std), DIMENSION(npts,nummoist)  :: SR                     !! Soil respiration at moist_in to facilitate the understanding regarding
1464                                                                    !! the Moyano et al paper we keep the same nomenclature than in the paper
1465                                                                    !! but **BE CAREFUL** it does not correspond to the variable resp_hetero_soil
1466                                                                    !! or resp_hetero_litter in ORCHIDEE
1467   REAL(r_std), DIMENSION(0:nbdl)   :: z_soil                 !! Soil levels (m)
1468!$OMP THREADPRIVATE(z_soil)
1469   REAL(r_std), DIMENSION(npts,nummoist)  :: moistfunc              !! An intermediate variable to calculate the Moisture control factor
1470   INTEGER(i_std)                         :: ind                    !! A local variable to know what is the index of the max value for the statistical function
1471   INTEGER(i_std), DIMENSION(npts)        :: ind_i                  !! A local variable to know what is the index of the max value for the
1472                                                                    !! statistical function at each points
1473   REAL(r_std),ALLOCATABLE,SAVE,DIMENSION(:,:)    :: moistfunc_below_1 !! A allocatable variable to store the value of moistfunc that are below the max value
1474                                                                       !! to then rescale at is it done in Moyano et al. 2012 BG
1475!$OMP THREADPRIVATE(moistfunc_below_1)
1476   INTEGER(i_std)                         :: ier                    !! Check errors in netcdf call (unitless)
1477   LOGICAL                                :: l_error                !! Check errors in netcdf call
1478
1479!_ ================================================================================================================================
1480
1481       !! 1.3 soil levels
1482       z_soil(0) = zero
1483       z_soil(1:nbdl) = diaglev(1:nbdl)
1484
1485    ! In Moyano et al. 2012 BG, the function obtained is based on soil
1486    ! incubations were litter is generally manually removed, therefore we used
1487    ! only the variable carbon corresponding to the soil organic carbon even
1488    ! if some litter (metabolic litter) is not easy to remove manually since it
1489    ! corresponds to roots exudates. Therefore, we probably underestimate a bit
1490    ! the soil organic carbon compared to what is used in Moyano et al., 2012
1491    ! BG.
1492
1493 PRsr(:,:) = zero
1494 SR(:,:) = zero
1495 moistfunc(:,:) = zero
1496    l_error = .FALSE.
1497
1498    total_soc(:) = zero
1499    DO k = 1,nvm
1500       DO j = 1,nbdl
1501       total_soc(:) =  total_soc(:) + &
1502                      ((carbon(:,iactive,k,j)*veget_max(:,k) + &
1503                       carbon(:,islow,k,j)*veget_max(:,k) + &
1504                       carbon(:,ipassive,k,j)*veget_max(:,k))* &
1505                       ((z_soil(j)-z_soil(j-1))/z_soil(nbdl))) / &
1506                      (bulk_dens(:) ) 
1507       ENDDO
1508    ENDDO
1509
1510     DO k = 1,nummoist
1511
1512        PRsr(:,k) = 1.11066-0.83344*(k/100.) + 1.48095*((k/100.)**2) - 1.02959*((k/100.)**3) + 0.07995*clay(:) + 1.27892*total_soc(:)
1513
1514     ENDDO
1515
1516        SR(:,1)=PRsr(:,1)
1517     DO k=2,nummoist
1518        SR(:,k)= SR(:,k-1)* PRsr(:,k)
1519     ENDDO
1520
1521     DO i = 1,npts
1522         DO k= 1, nummoist
1523                moistfunc(i,k) = SR(i,k)/MAXVAL(SR(i,:))
1524         ENDDO
1525    ENDDO
1526
1527       ind_i(:) = MAXLOC(moistfunc(:,:),DIM=2)
1528
1529     DO i = 1,npts
1530         ind=ind_i(i)
1531
1532    ALLOCATE(moistfunc_below_1(npts,ind),stat=ier)
1533    l_error = l_error .OR. (ier /= 0)
1534    IF (l_error) THEN
1535       WRITE(numout,*) 'Memory allocation error for moistfunc_below_1. '
1536    ENDIF
1537
1538         DO k= 1,ind
1539            moistfunc_below_1(i,k)= moistfunc(i,k)
1540         ENDDO
1541
1542         DO k= 1,ind           
1543            moistfunc(i,k)=moistfunc(i,k) - MINVAL(moistfunc_below_1(i,:))
1544         ENDDO
1545
1546         DO k= 1,ind
1547            moistfunc_below_1(i,k)= moistfunc(i,k)
1548         ENDDO
1549
1550         DO k=1,ind
1551
1552            moistfunc(i,k)=moistfunc(i,k)/MAXVAL(moistfunc_below_1(i,:))
1553         ENDDO
1554
1555    IF (ALLOCATED(moistfunc_below_1)) DEALLOCATE(moistfunc_below_1)
1556
1557    ENDDO
1558    DO i=1,npts
1559               IF (NINT(moist_in(i)*100.) .GT. zero) THEN
1560               moistfunc_result(i) = moistfunc(i,NINT(moist_in(i)*100.))
1561               ELSE
1562               moistfunc_result(i) = zero
1563               ENDIF
1564    ENDDO
1565
1566  END FUNCTION control_moist_func_moyano
1567
1568!! ================================================================================================================================
1569!! FUNCTION     : control_moist_func
1570!!
1571!>\BRIEF        Calculate moisture control for litter and soild C decomposition
1572!!
1573!! DESCRIPTION  : Calculate moisture control factor applied
1574!! to litter decomposition and to soil carbon decomposition in
1575!! stomate_soilcarbon.f90 using the following equation: \n
1576!! \latexonly
1577!! \input{control_moist_func1.tex}
1578!! \endlatexonly
1579!! \n
1580!! with M the moisture control factor and soilmoisutre, the soil moisture
1581!! calculated in sechiba.
1582!! Then, the function is ranged between 0.25 and 1:\n
1583!! \latexonly
1584!! \input{control_moist_func2.tex}
1585!! \endlatexonly
1586!! \n
1587!! RECENT CHANGE(S) : None
1588!!
1589!! RETURN VALUE : ::moistfunc_result
1590!!
1591!! REFERENCE(S) : None
1592!!
1593!! FLOWCHART : None
1594!! \n
1595!_ ================================================================================================================================
1596
1597  FUNCTION control_moist_func (npts, moist_in) RESULT (moistfunc_result)
1598
1599  !! 0. Variable and parameter declaration
1600
1601    !! 0.1 Input variables
1602
1603    INTEGER(i_std), INTENT(in)               :: npts                !! Domain size - number of grid pixel (unitless)
1604    REAL(r_std), DIMENSION(npts), INTENT(in) :: moist_in            !! relative humidity (unitless)
1605
1606
1607    !! 0.2 Output variables
1608
1609    REAL(r_std), DIMENSION(npts)          :: moistfunc_result    !! Moisture control factor (0-1, unitless)
1610
1611    !! 0.3 Modified variables
1612
1613
1614!_ ================================================================================================================================
1615
1616
1617          moistfunc_result(:) = -moist_coeff(1) * moist_in(:) * moist_in(:) + moist_coeff(2)* moist_in(:) - moist_coeff(3)
1618          moistfunc_result(:) = MAX( 0.25_r_std, MIN( un, moistfunc_result(:) ) )
1619   
1620  END FUNCTION control_moist_func
1621
1622!! ================================================================================================================================
1623!! FUNCTION     : control_temp_func
1624!!
1625!>\BRIEF        Calculate temperature control for litter and soild C decomposition
1626!!
1627!! DESCRIPTION  : Calculate temperature control factor applied
1628!! to litter decomposition and to soil carbon decomposition in
1629!! stomate_soilcarbon.f90 using the following equation: \n
1630!! \latexonly
1631!! \input{control_temp_func1.tex}
1632!! \endlatexonly
1633!! \n
1634!! with T the temperature control factor, temp the temperature in Kelvin of
1635!! the air (for aboveground litter) or of the soil (for belowground litter
1636!! and soil)
1637!! Then, the function is limited in its maximal range to 1:\n
1638!! \latexonly
1639!! \input{control_temp_func2.tex}
1640!! \endlatexonly
1641!! \n
1642!! RECENT CHANGE(S) : None
1643!!
1644!! RETURN VALUE: ::tempfunc_result
1645!!
1646!! REFERENCE(S) : None
1647!!
1648!! FLOWCHART : None
1649!! \n
1650!_ ================================================================================================================================
1651
1652  FUNCTION control_temp_func (npts, temp_in,tau) RESULT (tempfunc_result)
1653
1654  !! 0. Variable and parameter declaration
1655   
1656    !! 0.1 Input variables
1657    INTEGER(i_std), INTENT(in)                 :: npts            !! Domain size - number of land pixels (unitless)
1658    REAL(r_std), DIMENSION(npts), INTENT(in)   :: temp_in         !! Temperature (K)
1659    REAL(r_std), INTENT(in)                    :: tau             !! residence time of the pool considered (years)
1660    !! 0.2 Output variables
1661    REAL(r_std), DIMENSION(npts)               :: tempfunc_result !! Temperature control factor (0-1, unitless)
1662
1663    !! 0.3 Modified variables
1664
1665    !! 0.4 Local variables
1666    REAL(r_std), DIMENSION(npts)               :: Ea              !! Activation Energy
1667    REAL(r_std), DIMENSION(npts)               :: Q10_soil        !! Q10 values calculated based on Ea
1668!_ ================================================================================================================================
1669
1670    ! This relationship is based on a reanalysis of the data published by LefÚvre et al. 2014 in global change biology
1671    ! We use MAX(cent,(temp_in(:)-ZeroCelsius)*(temp_in(:)-ZeroCelsius)))) because for values between -10 and 10 degC
1672    ! the Q10 values are close to infinity
1673!    Ea(:)=a_term_Q10_soil*tau + b_term_Q10_soil
1674!    Q10_soil(:)=exp((dix*Ea(:))/(RR*MAX(cent,(temp_in(:)-ZeroCelsius)*(temp_in(:)-ZeroCelsius))))
1675    Q10_soil(:)=0.69
1676    tempfunc_result(:) = exp( log(Q10_soil(:)) * ( temp_in(:) - (ZeroCelsius+tsoil_ref)) / Q10 )
1677    tempfunc_result(:) = MIN( un, tempfunc_result(:) )
1678    WHERE (temp_in(:) .LT. zero) 
1679        tempfunc_result(:) = zero
1680    ENDWHERE
1681  END FUNCTION control_temp_func
1682
1683END MODULE stomate_litter
Note: See TracBrowser for help on using the repository browser.