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

Last change on this file since 7541 was 7541, checked in by fabienne.maignan, 2 years ago
  1. Zhang publication on coupling factor
File size: 45.1 KB
Line 
1! =================================================================================================================================
2! MODULE       : stomate_litter
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2006)
7! This software is governed by the CeCILL licence see ORCHIDEE/ORCHIDEE_CeCILL.LIC
8!
9!>\BRIEF       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: svn://forge.ipsl.jussieu.fr/orchidee/branches/ORCHIDEE_2_2/ORCHIDEE/src_stomate/stomate_litter.f90 $
20!! $Date: 2017-10-18 11:15:06 +0200 (Wed, 18 Oct 2017) $
21!! $Revision: 4693 $
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  LOGICAL, SAVE                        :: firstcall_litter = .TRUE.       !! first call
43!$OMP THREADPRIVATE(firstcall_litter)
44
45CONTAINS
46
47!! ================================================================================================================================
48!! SUBROUTINE   : littercalc_calc
49!!
50!!\BRIEF        Set the flag ::firstcall_litter to .TRUE. and as such activate section
51!! 1.1 of the subroutine littercalc (see below).
52!!
53!! DESCRIPTION  : None
54!!
55!! RECENT CHANGE(S) : None
56!!
57!! MAIN OUTPUT VARIABLE(S) : None
58!!
59!! REFERENCE(S) : None
60!!
61!! FLOWCHART : None
62!! \n
63!_ ================================================================================================================================
64
65  SUBROUTINE littercalc_clear
66    firstcall_litter =.TRUE.
67  END SUBROUTINE littercalc_clear
68
69
70!! ================================================================================================================================
71!! SUBROUTINE   : littercalc
72!!
73!!\BRIEF        Calculation of the litter decomposition and therefore of the
74!! heterotrophic respiration from litter following Parton et al. (1987).
75!!
76!! DESCRIPTION  : The littercal routine splits the litter in 4 pools:
77!! aboveground metaboblic, aboveground structural, belowground metabolic and
78!! belowground structural. the fraction (F) of plant material going to metabolic
79!! and structural is defined following Parton et al. (1987)
80!! \latexonly
81!! \input{littercalc1.tex}
82!! \endlatexonly
83!! \n
84!! where L is the lignin content of the plant carbon pools considered and CN
85!! its CN ratio. L and CN are fixed parameters for each plant carbon pools,
86!! therefore it is the ratio between each plant carbon pool within a PFT, which
87!! controlled the part of the total litter, that will be considered as
88!! recalcitrant (i.e. structural litter) or labile (i.e. metabolic litter).\n 
89!!
90!! The routine calculates the fraction of aboveground litter which is metabolic
91!! or structural (the litterpart variable) which is then used in lpj_fire.f90.\n
92!!
93!! In the section 2, the routine calculate the new plant material entering the
94!! litter pools by phenological death of plants organs (corresponding to the
95!! variable turnover) and by fire, herbivory and others non phenological causes
96!! (variable bm_to_litter). This calculation is first done for each PFT and then
97!! the values calculated for each PFT are added up. Following the same approach
98!! the lignin content of the total structural litter is calculated and will be
99!! then used as a factor control of the decomposition of the structural litter
100!! (lignin_struc) in the section 5.1.2. A test is performed to avoid that we add
101!! more lignin than structural litter. Finally, the variable litterpart is
102!! updated.\n
103!!
104!! In the section 3 and 4 the temperature and the moisture controlling the
105!! decomposition are calculated for above and belowground. For aboveground
106!! litter, air temperature and litter moisture are calculated in sechiba and used
107!! directly. For belowground, soil temperature and moisture are also calculated
108!! in sechiba but are modulated as a function of the soil depth. The modulation
109!! is a multiplying factor exponentially distributed between 0 (in depth) and 1
110!! in surface.\n 
111!!
112!! Then, in the section 5, the routine calculates the structural litter decomposition
113!! (C) following first order kinetics following Parton et al. (1987).
114!! \latexonly
115!! \input{littercalc2.tex}
116!! \endlatexonly
117!! \n
118!! with k the decomposition rate of the structural litter.
119!! k corresponds to
120!! \latexonly
121!! \input{littercalc3.tex}
122!! \endlatexonly
123!! \n
124!! with littertau the turnover rate, T a function of the temperature and M a function of
125!! the moisture described below.\n
126!! 
127!! Then, the fraction of dead leaves (DL) composed by aboveground structural litter is
128!! calculated as following
129!! \latexonly
130!! \input{littercalc4.tex}
131!! \endlatexonly
132!! \n
133!! with k the decomposition rate of the structural litter previously
134!! described.\n
135!!
136!! In the section 5.1, the fraction of decomposed structural litter
137!! incorporated to the soil (Input) and its associated heterotrophic respiration are
138!! calculated. For structural litter, the C decomposed could go in the active
139!! soil carbon pool or in the slow carbon, as described in
140!! stomate_soilcarbon.f90.\n
141!! \latexonly
142!! \input{littercalc5.tex}
143!! \endlatexonly
144!! \n
145!! with f a parameter describing the fraction of structural litter incorporated
146!! into the considered soil carbon pool, C the amount of litter decomposed and L
147!! the amount of lignin in the litter. The litter decomposed which is not
148!! incorporated into the soil is respired.\n
149!!
150!! In the section 5.2, the fraction of decomposed metabolic litter
151!! incorporated to the soil and its associated heterotrophic respiration are
152!! calculated with the same approaches presented for 5.1 but no control factor
153!! depending on the lignin content are used.\n
154!!
155!! In the section 6 the dead leaf cover is calculated through a call to the
156!! deadleaf subroutine presented below.\n
157!!
158!! In the section 7, if the flag SPINUP_ANALYTIC is set to true, we fill MatrixA
159!! and VectorB following Lardy(2011).
160!!
161!! MAIN OUTPUT VARIABLES: ::deadleaf_cover, ::resp_hetero_litter, ::soilcarbon_input,
162!! ::control_temp, ::control_moist
163!!
164!! REFERENCES:
165!! - Parton, WJ, Schimel, DS, Cole, CV, and Ojima, DS. 1987. Analysis
166!! of factors controlling soil organic matter levels in Great Plains
167!! grasslands. Soil Science Society of America journal (USA)
168!! (51):1173-1179.
169!! - Lardy, R, et al., A new method to determine soil organic carbon equilibrium,
170!! Environmental Modelling & Software (2011), doi:10.1016|j.envsoft.2011.05.016
171!!
172!! FLOWCHART    :
173!! \latexonly
174!! \includegraphics(scale=0.5){littercalcflow.jpg}
175!! \endlatexonly
176!! \n
177!_ ================================================================================================================================
178
179  SUBROUTINE littercalc (npts, &
180       turnover, bm_to_litter, &
181       veget_cov_max, tsurf, tsoil, soilhum, litterhum, &
182       litterpart, litter, dead_leaves, lignin_struc, &
183       deadleaf_cover, resp_hetero_litter, &
184       soilcarbon_input, control_temp, control_moist, &
185       MatrixA, VectorB)
186
187    !! 0. Variable and parameter declaration
188   
189    !! 0.1 Input variables
190
191    INTEGER(i_std), INTENT(in)                                  :: npts               !! Domain size - number of grid pixels
192    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: turnover         !! Turnover rates of plant biomass
193                                                                                      !! @tex $(gC m^{-2} dt\_slow^{-1})$ @endtex
194    REAL(r_std), DIMENSION(npts,nvm,nparts,nelements), INTENT(in) :: bm_to_litter     !! Conversion of biomass to litter
195                                                                                      !! @tex $(gC m^{-2} dt\_slow^{-1})$ @endtex
196    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)                  :: veget_cov_max      !! PFT "Maximal" coverage fraction of a PFT
197                                                                                      !! defined in the input vegetation map
198                                                                                      !! @tex $(m^2 m^{-2})$ @endtex
199    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: tsurf              !! Temperature (K) at the surface
200    REAL(r_std), DIMENSION(npts,nslm), INTENT(in)               :: tsoil              !! Soil temperature (K)
201    REAL(r_std), DIMENSION(npts,nslm), INTENT(in)               :: soilhum            !! Daily soil humidity of each soil layer
202                                                                                      !! (unitless)
203    REAL(r_std), DIMENSION(npts), INTENT(in)                    :: litterhum          !! Daily litter humidity (unitless)
204
205    !! 0.2 Output variables
206   
207    REAL(r_std), DIMENSION(npts), INTENT(out)                   :: deadleaf_cover     !! Fraction of soil covered by dead leaves
208                                                                                      !! over all PFTs (0-1, unitless)
209    REAL(r_std), DIMENSION(npts,nvm), INTENT(out)               :: resp_hetero_litter !! Litter heterotrophic respiration. The unit
210                                                                                      !! is given by m^2 of ground. 
211                                                                                      !! @tex $(gC dt_sechiba one\_day^{-1}) m^{-2})$ @endtex
212    REAL(r_std), DIMENSION(npts,ncarb,nvm), INTENT(out)         :: soilcarbon_input   !! Quantity of carbon going into carbon pools
213                                                                                      !! from litter decomposition. The unit is 
214                                                                                      !! given by m^2 of ground
215                                                                                      !! @tex $(gC m^{-2} dt\_slow^{-1})$ @endtex
216    REAL(r_std), DIMENSION(npts,nlevs), INTENT(out)             :: control_temp       !! Temperature control of heterotrophic
217                                                                                      !! respiration, above and below (0-1,
218                                                                                      !! unitless)
219    REAL(r_std), DIMENSION(npts,nlevs), INTENT(out)             :: control_moist      !! Moisture control of heterotrophic
220                                                                                      !! respiration (0.25-1, unitless)
221    REAL(r_std), DIMENSION(npts,nvm,nbpools,nbpools), INTENT(out) :: MatrixA          !! Matrix containing the fluxes between the
222                                                                                      !! carbon pools per sechiba time step
223                                                                                      !! @tex $(gC.m^2.day^{-1})$ @endtex
224    REAL(r_std), DIMENSION(npts,nvm,nbpools), INTENT(out)         :: VectorB          !! Vector containing the litter increase per
225                                                                                      !! sechiba time step
226                                                                                      !! @tex $(gC m^{-2})$ @endtex
227   
228    !! 0.3 Modified variables
229   
230    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)       :: litterpart         !! Fraction of litter above the ground
231                                                                                      !! belonging to the different PFTs (0-1,
232                                                                                      !! unitless)
233    REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs,nelements), INTENT(inout) :: litter   !! Metabolic and structural litter,above and
234                                                                                      !! below ground. The unit is given by m^2 of
235                                                                                      !! ground @tex $(gC m^{-2})$ @endtex
236    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(inout)       :: dead_leaves        !! Dead leaves per ground unit area, per PFT,
237                                                                                      !! metabolic and structural in
238                                                                                      !! @tex $(gC m^{-2})$ @endtex
239    REAL(r_std), DIMENSION(npts,nvm,nlevs), INTENT(inout)       :: lignin_struc       !! Ratio Lignin content in structural litter,
240                                                                                      !! above and below ground, (0-1, unitless)
241   
242    !! 0.4 Local variables
243 
244    REAL(r_std)                                                 :: dt                 !! Number of sechiba(fast processes) time-step per day
245    REAL(r_std), SAVE, DIMENSION(nparts,nlitt)                  :: litterfrac         !! The fraction of leaves, wood, etc. that
246                                                                                      !! goes into metabolic and structural
247                                                                                      !! litterpools (0-1, unitless)
248!$OMP THREADPRIVATE(litterfrac)
249    REAL(r_std), SAVE, ALLOCATABLE, DIMENSION(:)                :: z_soil             !! Soil levels (m)
250!$OMP THREADPRIVATE(z_soil)
251    REAL(r_std), DIMENSION(npts)                                :: rpc                !! Integration constant for vertical root
252                                                                                      !! profiles (unitless)
253    REAL(r_std), SAVE, DIMENSION(nlitt)                         :: litter_tau         !! Turnover time in litter pools (days)
254!$OMP THREADPRIVATE(litter_tau)
255    REAL(r_std), SAVE, DIMENSION(nlitt,ncarb,nlevs)             :: frac_soil          !! Fraction of litter that goes into soil
256                                                                                      !! (litter -> carbon, above and below). The
257                                                                                      !! remaining part goes to the atmosphere
258!$OMP THREADPRIVATE(frac_soil)
259    REAL(r_std), DIMENSION(npts)                                :: tsoil_decomp       !! Temperature used for decompostition in
260                                                                                      !! soil (K)
261    REAL(r_std), DIMENSION(npts)                                :: soilhum_decomp     !! Humidity used for decompostition in soil
262                                                                                      !! (unitless)
263    REAL(r_std), DIMENSION(npts)                                :: fd                 !! Fraction of structural or metabolic litter
264                                                                                      !! decomposed (unitless)
265    REAL(r_std), DIMENSION(npts,nelements)                      :: qd                 !! Quantity of structural or metabolic litter
266                                                                                      !! decomposed @tex $(gC m^{-2})$ @endtex
267    REAL(r_std), DIMENSION(npts,nvm,nlevs)                      :: old_struc          !! Old structural litter, above and below
268                                                                                      !! @tex $(gC m^{-2})$ @endtex
269    REAL(r_std), DIMENSION(npts,nvm,nlitt,nlevs,nelements)      :: litter_inc_PFT     !! Increase of litter, per PFT, metabolic and
270                                                                                      !! structural, above and below ground. The
271                                                                                      !! unit is given by m^2 of ground. 
272                                                                                      !! @tex $(gC m^{-2})$ @endtex
273    REAL(r_std), DIMENSION(npts,nlitt,nvm,nlevs,nelements)      :: litter_inc         !! Increase of metabolic and structural
274                                                                                      !! litter, above and below ground. The unit
275                                                                                      !! is given by m^2 of ground.
276                                                                                      !! @tex $(gC m^{-2})$ @endtex
277    REAL(r_std), DIMENSION(npts,nvm,nlevs)                      :: lignin_struc_inc   !! Lignin increase in structural litter,
278                                                                                      !! above and below ground. The unit is given
279                                                                                      !! by m^2 of ground.
280                                                                                      !! @tex $(gC m^{-2})$ @endtex
281    REAL(r_std), DIMENSION(npts,nvm,nlitt,nelements)            :: litter_pft         !! Metabolic and structural litter above the
282                                                                                      !! ground per PFT
283    REAL(r_std), DIMENSION(npts)                                :: zdiff_min          !! Intermediate field for looking for minimum
284                                                                                      !! of what? this is not used in the code.
285                                                                                      !! [??CHECK] could we delete it?
286    CHARACTER(LEN=10), DIMENSION(nlitt)                         :: litter_str         !! Messages to write output information about
287                                                                                      !! the litter
288    CHARACTER(LEN=22), DIMENSION(nparts)                        :: part_str           !! Messages to write output information about
289                                                                                      !! the plant
290    CHARACTER(LEN=7), DIMENSION(ncarb)                          :: carbon_str         !! Messages to write output information about
291                                                                                      !! the soil carbon
292    CHARACTER(LEN=5), DIMENSION(nlevs)                          :: level_str          !! Messages to write output information about
293                                                                                      !! the level (aboveground or belowground litter)
294    INTEGER(i_std)                                              :: i,j,k,l,m          !! Indices (unitless)
295    INTEGER(i_std)                                              :: ier                !! Error handling
296!_ ================================================================================================================================
297
298    IF (printlev>=3) WRITE(numout,*) 'Entering littercalc'
299
300  !! 1. Initialisations of the different fields during the first call of the routine
301    dt = dt_sechiba/one_day
302    IF ( firstcall_litter ) THEN
303
304       !! 1.1.3 litter fractions:
305       !!   what fraction of leaves, wood, etc. goes into metabolic and structural litterpools
306       DO k = 1, nparts
307
308          litterfrac(k,imetabolic) = metabolic_ref_frac - metabolic_LN_ratio * LC(k) * CN(k)
309          litterfrac(k,istructural) = un - litterfrac(k,imetabolic)
310
311       ENDDO
312
313       !! 1.1.4 residence times in litter pools (days)
314       litter_tau(imetabolic) = tau_metabolic * one_year      ! .5 years
315       litter_tau(istructural) = tau_struct * one_year     ! 3 years
316
317       !! 1.1.5 decomposition flux fraction that goes into soil
318       !       (litter -> carbon, above and below)
319       !       1-frac_soil goes into atmosphere
320       frac_soil(:,:,:) = zero
321
322       ! structural litter: lignin fraction goes into slow pool + respiration,
323       !                    rest into active pool + respiration
324       frac_soil(istructural,iactive,iabove) = frac_soil_struct_aa
325       frac_soil(istructural,iactive,ibelow) = frac_soil_struct_ab
326       frac_soil(istructural,islow,iabove) = frac_soil_struct_sa
327       frac_soil(istructural,islow,ibelow) = frac_soil_struct_sb
328
329       ! metabolic litter: all goes into active pool + respiration.
330       !   Nothing into slow or passive pool.
331       frac_soil(imetabolic,iactive,iabove) = frac_soil_metab_aa
332       frac_soil(imetabolic,iactive,ibelow) = frac_soil_metab_ab
333
334       
335       !! 1.2 soil levels
336       ALLOCATE(z_soil(0:nslm), stat=ier)
337       IF ( ier /= 0 ) CALL ipslerr_p(3,'littercalc','Pb in allocate of z_soil','','')
338
339       z_soil(0) = zero
340       z_soil(1:nslm) = diaglev(1:nslm)
341
342       
343       !! 1.3 messages
344       litter_str(imetabolic) = 'metabolic'
345       litter_str(istructural) = 'structural'
346
347       carbon_str(iactive) = 'active'
348       carbon_str(islow) = 'slow'
349       carbon_str(ipassive) = 'passive'
350
351       level_str(iabove) = 'above'
352       level_str(ibelow) = 'below'
353
354       part_str(ileaf) = 'leaves'
355       part_str(isapabove) = 'sap above ground'
356       part_str(isapbelow) = 'sap below ground'
357       part_str(iheartabove) = 'heartwood above ground'
358       part_str(iheartbelow) = 'heartwood below ground'
359       part_str(iroot) = 'roots'
360       part_str(ifruit) = 'fruits'
361       part_str(icarbres) = 'carbohydrate reserve'
362
363       IF (printlev >=2) THEN
364          WRITE(numout,*) 'litter:'
365
366          WRITE(numout,*) '   > C/N ratios: '
367          DO k = 1, nparts
368             WRITE(numout,*) '       ', part_str(k), ': ',CN(k)
369          ENDDO
370
371          WRITE(numout,*) '   > Lignine/C ratios: '
372          DO k = 1, nparts
373             WRITE(numout,*) '       ', part_str(k), ': ',LC(k)
374          ENDDO
375
376          WRITE(numout,*) '   > fraction of compartment that goes into litter: '
377          DO k = 1, nparts
378             DO m = 1, nlitt
379                WRITE(numout,*) '       ', part_str(k), '-> ',litter_str(m), ':',litterfrac(k,m)
380             ENDDO
381          ENDDO
382
383          WRITE(numout,*) '   > scaling depth for decomposition (m): ',z_decomp
384
385          WRITE(numout,*) '   > minimal carbon residence time in litter pools (d):'
386          DO m = 1, nlitt
387             WRITE(numout,*) '       ',litter_str(m),':',litter_tau(m)
388          ENDDO
389
390          WRITE(numout,*) '   > litter decomposition flux fraction that really goes '
391          WRITE(numout,*) '     into carbon pools (rest into the atmosphere):'
392          DO m = 1, nlitt
393             DO l = 1, nlevs
394                DO k = 1, ncarb
395                   WRITE(numout,*) '       ',litter_str(m),' ',level_str(l),' -> ',&
396                        carbon_str(k),':', frac_soil(m,k,l)
397                ENDDO
398             ENDDO
399          ENDDO
400       END IF ! printlev >=2
401       firstcall_litter = .FALSE.
402
403    ENDIF
404
405   
406    !! 1.3 litter above the ground per PFT.
407    DO j = 1, nvm ! Loop over # PFTs
408
409       DO k = 1, nlitt !Loop over litter pool
410          litter_pft(:,j,k,icarbon) = litterpart(:,j,k) * litter(:,k,j,iabove,icarbon)
411       ENDDO
412
413    ENDDO
414
415   
416    !! 1.4 set output to zero
417    deadleaf_cover(:) = zero
418    resp_hetero_litter(:,:) = zero
419    soilcarbon_input(:,:,:) = zero
420
421   
422  !! 2. Add biomass to different litterpools (per m^2 of ground)
423   
424    !! 2.1 first, save old structural litter (needed for lignin fractions).
425    !     above/below
426    DO l = 1, nlevs !Loop over litter levels (above and below ground)
427       DO m = 1,nvm !Loop over PFTs
428
429          old_struc(:,m,l) = litter(:,istructural,m,l,icarbon)
430
431       ENDDO
432    ENDDO
433
434   
435    !! 2.2 update litter, dead leaves, and lignin content in structural litter
436    litter_inc(:,:,:,:,:) = zero
437    lignin_struc_inc(:,:,:) = zero
438
439    DO j = 1,nvm !Loop over PFTs
440
441       !! 2.2.1 litter
442       DO k = 1, nlitt    !Loop over litter pools (metabolic and structural)
443
444          !! 2.2.2 calculate litter increase (per m^2 of ground).
445          !       Only a given fracion of fruit turnover is directly coverted into litter.
446          !       Litter increase for each PFT, structural and metabolic, above/below
447          litter_inc_PFT(:,j,k,iabove,icarbon) = &
448               litterfrac(ileaf,k) * bm_to_litter(:,j,ileaf,icarbon) + &
449               litterfrac(isapabove,k) * bm_to_litter(:,j,isapabove,icarbon) + &
450               litterfrac(iheartabove,k) * bm_to_litter(:,j,iheartabove,icarbon) + &
451               litterfrac(ifruit,k) * bm_to_litter(:,j,ifruit,icarbon) + &
452               litterfrac(icarbres,k) * bm_to_litter(:,j,icarbres,icarbon) + &
453               litterfrac(ileaf,k) * turnover(:,j,ileaf,icarbon) + &
454               litterfrac(isapabove,k) * turnover(:,j,isapabove,icarbon) + &
455               litterfrac(iheartabove,k) * turnover(:,j,iheartabove,icarbon) + &
456               litterfrac(ifruit,k) * turnover(:,j,ifruit,icarbon) + &
457               litterfrac(icarbres,k) * turnover(:,j,icarbres,icarbon)
458
459          litter_inc_PFT(:,j,k,ibelow,icarbon) = &
460               litterfrac(isapbelow,k) * bm_to_litter(:,j,isapbelow,icarbon) + &
461               litterfrac(iheartbelow,k) * bm_to_litter(:,j,iheartbelow,icarbon) + &
462               litterfrac(iroot,k) * bm_to_litter(:,j,iroot,icarbon) + &
463               litterfrac(isapbelow,k) * turnover(:,j,isapbelow,icarbon) + &
464               litterfrac(iheartbelow,k) * turnover(:,j,iheartbelow,icarbon) + &
465               litterfrac(iroot,k) * turnover(:,j,iroot,icarbon)
466
467          ! litter increase, met/struct, above/below
468          litter_inc(:,k,j,iabove,icarbon) = litter_inc(:,k,j,iabove,icarbon) + litter_inc_PFT(:,j,k,iabove,icarbon)
469          litter_inc(:,k,j,ibelow,icarbon) = litter_inc(:,k,j,ibelow,icarbon) + litter_inc_PFT(:,j,k,ibelow,icarbon)
470
471          !! 2.2.3 dead leaves, for soil cover.
472          dead_leaves(:,j,k) = &
473               dead_leaves(:,j,k) + &
474               litterfrac(ileaf,k) * ( bm_to_litter(:,j,ileaf,icarbon) + turnover(:,j,ileaf,icarbon) )
475
476          !! 2.2.4 lignin increase in structural litter
477          IF ( k .EQ. istructural ) THEN
478
479             lignin_struc_inc(:,j,iabove) = &
480                  lignin_struc_inc(:,j,iabove) + &
481                  LC(ileaf) * bm_to_litter(:,j,ileaf,icarbon) + &
482                  LC(isapabove) * bm_to_litter(:,j,isapabove,icarbon) + &
483                  LC(iheartabove) * bm_to_litter(:,j,iheartabove,icarbon) + &
484                  LC(ifruit) * bm_to_litter(:,j,ifruit,icarbon) + &
485                  LC(icarbres) * bm_to_litter(:,j,icarbres,icarbon) + &
486                  LC(ileaf) * turnover(:,j,ileaf,icarbon) + &
487                  LC(isapabove) * turnover(:,j,isapabove,icarbon) + &
488                  LC(iheartabove) * turnover(:,j,iheartabove,icarbon) + &
489                  LC(ifruit) * turnover(:,j,ifruit,icarbon) + &
490                  LC(icarbres) * turnover(:,j,icarbres,icarbon)
491
492             lignin_struc_inc(:,j,ibelow) = &
493                  lignin_struc_inc(:,j,ibelow) + &
494                  LC(isapbelow) * bm_to_litter(:,j,isapbelow,icarbon) + &
495                  LC(iheartbelow) * bm_to_litter(:,j,iheartbelow,icarbon) + &
496                  LC(iroot) * bm_to_litter(:,j,iroot,icarbon) + &
497                  LC(isapbelow)*turnover(:,j,isapbelow,icarbon) + &
498                  LC(iheartbelow)*turnover(:,j,iheartbelow,icarbon) + &
499                  LC(iroot)*turnover(:,j,iroot,icarbon)
500
501          ENDIF
502
503       ENDDO
504    ENDDO
505
506    !! 2.2.5 add new litter (struct/met, above/below)
507    litter(:,:,:,:,:) = litter(:,:,:,:,:) + litter_inc(:,:,:,:,:)
508
509    !! 2.2.6 for security: can't add more lignin than structural litter (above/below)
510    DO l = 1, nlevs !Loop over litter levels (above and below ground)
511       DO m = 1,nvm !Lopp over PFTs
512
513          lignin_struc_inc(:,m,l) = &
514               MIN( lignin_struc_inc(:,m,l), litter_inc(:,istructural,m,l,icarbon) )
515
516       ENDDO
517    ENDDO
518
519    !! 2.2.7 new lignin content: add old lignin and lignin increase, divide by
520    !!       total structural litter (above/below)
521    DO l = 1, nlevs !Loop over litter levels (above and below ground)
522       DO m = 1,nvm !Loop over PFTs
523          WHERE( litter(:,istructural,m,l,icarbon) .GT. min_stomate )
524
525       !MM : Soenke modif
526       ! Best vectorization ?
527!!$       lignin_struc(:,:,:) = &
528!!$            ( lignin_struc(:,:,:)*old_struc(:,:,:) + lignin_struc_inc(:,:,:) ) / &
529!!$            litter(:,istructural,:,:,icarbon)
530
531             lignin_struc(:,m,l) = lignin_struc(:,m,l) * old_struc(:,m,l)
532             lignin_struc(:,m,l) = lignin_struc(:,m,l) + lignin_struc_inc(:,m,l)
533             lignin_struc(:,m,l) = lignin_struc(:,m,l) / litter(:,istructural,m,l,icarbon)
534          ELSEWHERE
535             lignin_struc(:,m,l) = zero
536          ENDWHERE
537       ENDDO
538    ENDDO
539
540   
541    !! 2.3 new litter fraction per PFT (for structural and metabolic litter, above
542    !!       the ground).
543    DO j = 1,nvm !Loop over PFTs
544
545       WHERE ( litter(:,:,j,iabove,icarbon) .GT. min_stomate )
546
547          litterpart(:,j,:) = &
548               ( litter_pft(:,j,:,icarbon) + litter_inc_PFT(:,j,:,iabove,icarbon) ) / litter(:,:,j,iabove,icarbon)
549
550       ELSEWHERE
551
552          litterpart(:,j,:) = zero
553
554       ENDWHERE
555
556    ENDDO
557
558   
559  !! 3. Temperature control on decay: Factor between 0 and 1
560
561    !! 3.1 above: surface temperature
562    control_temp(:,iabove) = control_temp_func (npts, tsurf)
563
564   
565    !! 3.2 below: convolution of temperature and decomposer profiles
566    !!            (exponential decomposer profile supposed)
567   
568    !! 3.2.1 rpc is an integration constant such that the integral of the root profile is 1.
569    rpc(:) = un / ( un - EXP( -z_soil(nslm) / z_decomp ) )
570
571    !! 3.2.2 integrate over the nslm levels
572    tsoil_decomp(:) = zero
573
574    DO l = 1, nslm
575
576       tsoil_decomp(:) = &
577            tsoil_decomp(:) + tsoil(:,l) * rpc(:) * &
578            ( EXP( -z_soil(l-1)/z_decomp ) - EXP( -z_soil(l)/z_decomp ) )
579
580    ENDDO
581
582    control_temp(:,ibelow) = control_temp_func (npts, tsoil_decomp)
583
584  !! 4. Moisture control. Factor between 0 and 1
585   
586    !! 4.1 above the ground: litter humidity
587    control_moist(:,iabove) = control_moist_func (npts, litterhum)
588
589    !
590    !! 4.2 below: convolution of humidity and decomposer profiles
591    !            (exponential decomposer profile supposed)
592
593    !! 4.2.1 rpc is an integration constant such that the integral of the root profile is 1.
594    rpc(:) = un / ( un - EXP( -z_soil(nslm) / z_decomp ) )
595
596    !! 4.2.2 integrate over the nslm levels
597    soilhum_decomp(:) = zero
598
599    DO l = 1, nslm !Loop over soil levels
600
601       soilhum_decomp(:) = &
602            soilhum_decomp(:) + soilhum(:,l) * rpc(:) * &
603            ( EXP( -z_soil(l-1)/z_decomp ) - EXP( -z_soil(l)/z_decomp ) )
604
605    ENDDO
606
607    control_moist(:,ibelow) = control_moist_func (npts, soilhum_decomp)
608
609  !! 5. fluxes from litter to carbon pools and respiration
610
611    DO l = 1, nlevs !Loop over litter levels (above and below ground)
612       DO m = 1,nvm !Loop over PFTs
613
614          !! 5.1 structural litter: goes into active and slow carbon pools + respiration
615
616          !! 5.1.1 total quantity of structural litter which is decomposed
617          fd(:) = dt/litter_tau(istructural) * &
618               control_temp(:,l) * control_moist(:,l) * exp( -litter_struct_coef * lignin_struc(:,m,l) )
619
620          DO k = 1,nelements
621             
622             qd(:,k) = litter(:,istructural,m,l,k) * fd(:)
623
624          END DO
625
626          litter(:,istructural,m,l,:) = litter(:,istructural,m,l,:) - qd(:,:)
627
628          !! 5.1.2 decompose same fraction of structural part of dead leaves. Not exact
629          !!       as lignine content is not the same as that of the total structural litter.
630          ! to avoid a multiple (for ibelow and iabove) modification of dead_leaves,
631          ! we do this test to do this calcul only ones in 1,nlev loop
632          if (l == iabove)  dead_leaves(:,m,istructural) = dead_leaves(:,m,istructural) * ( un - fd(:) )
633
634          !! 5.1.3 non-lignin fraction of structural litter goes into
635          !!       active carbon pool + respiration
636          soilcarbon_input(:,iactive,m) = soilcarbon_input(:,iactive,m) + &
637               frac_soil(istructural,iactive,l) * qd(:,icarbon) * ( 1. - lignin_struc(:,m,l) ) / dt
638
639      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
640      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
641      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dt_sechiba/one_day
642      ! time step and avoid some constructions that could create bug during future developments.
643          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
644               ( 1. - frac_soil(istructural,iactive,l) ) * qd(:,icarbon) * &
645               ( 1. - lignin_struc(:,m,l) ) / dt
646
647          !! 5.1.4 lignin fraction of structural litter goes into
648          !!       slow carbon pool + respiration
649          soilcarbon_input(:,islow,m) = soilcarbon_input(:,islow,m) + &
650               frac_soil(istructural,islow,l) * qd(:,icarbon) * lignin_struc(:,m,l) / dt
651
652      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
653      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
654      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dt_sechiba/one_day
655      ! time step and avoid some constructions that could create bug during future developments.
656          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
657               ( 1. - frac_soil(istructural,islow,l) ) * qd(:,icarbon) * lignin_struc(:,m,l) / dt
658
659         
660          !! 5.2 metabolic litter goes into active carbon pool + respiration
661         
662          !! 5.2.1 total quantity of metabolic litter that is decomposed
663          fd(:) = dt/litter_tau(imetabolic) * control_temp(:,l) * control_moist(:,l)
664
665          DO k = 1,nelements
666         
667             qd(:,k) = litter(:,imetabolic,m,l,k) * fd(:)
668
669          END DO
670
671          litter(:,imetabolic,m,l,:) = litter(:,imetabolic,m,l,:) - qd(:,:)
672
673          !! 5.2.2 decompose same fraction of metabolic part of dead leaves.
674          !  to avoid a multiple (for ibelow and iabove) modification of dead_leaves,
675          !  we do this test to do this calcul only ones in 1,nlev loop
676          if (l == iabove)  dead_leaves(:,m,imetabolic) = dead_leaves(:,m,imetabolic) * ( 1. - fd(:) )
677
678
679          !! 5.2.3 put decomposed litter into carbon pool + respiration
680          soilcarbon_input(:,iactive,m) = soilcarbon_input(:,iactive,m) + &
681               frac_soil(imetabolic,iactive,l) * qd(:,icarbon) / dt
682
683      !BE CAREFUL: Here resp_hetero_litter is divided by dt to have a value which corresponds to
684      ! the sechiba time step but then in stomate.f90 resp_hetero_litter is multiplied by dt.
685      ! Perhaps it could be simplified. Moreover, we must totally adapt the routines to the dt_sechiba/one_day
686      ! time step and avoid some constructions that could create bug during future developments.
687          resp_hetero_litter(:,m) = resp_hetero_litter(:,m) + &
688               ( 1. - frac_soil(imetabolic,iactive,l) ) * qd(:,icarbon) / dt
689
690       ENDDO
691    ENDDO
692
693   
694  !! 6. calculate fraction of total soil covered by dead leaves
695
696    CALL deadleaf (npts, veget_cov_max, dead_leaves, deadleaf_cover)
697
698  !! 7. (Quasi-)Analytical Spin-up : Start filling MatrixA
699
700    IF (spinup_analytic) THEN
701
702       MatrixA(:,:,:,:) = zero
703       VectorB(:,:,:) = zero
704       
705       
706       DO m = 1,nvm
707
708          !- MatrixA : carbon fluxes leaving the litter
709         
710          MatrixA(:,m,istructural_above,istructural_above)= - dt/litter_tau(istructural) * &
711               control_temp(:,iabove) * control_moist(:,iabove) * exp( -litter_struct_coef * lignin_struc(:,m,iabove) )
712         
713          MatrixA(:,m,istructural_below,istructural_below) = - dt/litter_tau(istructural) * &
714               control_temp(:,ibelow) * control_moist(:,ibelow) * exp( -litter_struct_coef * lignin_struc(:,m,ibelow) )
715         
716          MatrixA(:,m,imetabolic_above,imetabolic_above) = - dt/litter_tau(imetabolic) * & 
717               control_temp(:,iabove) * control_moist(:,iabove)
718         
719          MatrixA(:,m,imetabolic_below,imetabolic_below) = - dt/litter_tau(imetabolic) * & 
720               control_temp(:,ibelow) * control_moist(:,ibelow)
721         
722         
723          !- MatrixA : carbon fluxes between the litter and the pools (the rest of the matrix is filled in stomate_soilcarbon.f90)
724         
725          MatrixA(:,m,iactive_pool,istructural_above) = frac_soil(istructural,iactive,iabove) * &
726               dt/litter_tau(istructural) * &                   
727               control_temp(:,iabove) * control_moist(:,iabove) * & 
728               exp( -litter_struct_coef * lignin_struc(:,m,iabove) ) * &
729               ( 1. - lignin_struc(:,m,iabove) ) 
730         
731
732          MatrixA(:,m,iactive_pool,istructural_below) = frac_soil(istructural,iactive,ibelow) * &
733               dt/litter_tau(istructural) * &                     
734               control_temp(:,ibelow) * control_moist(:,ibelow) * & 
735               exp( -litter_struct_coef * lignin_struc(:,m,ibelow) ) * &
736               ( 1. - lignin_struc(:,m,ibelow) ) 
737         
738         
739          MatrixA(:,m,iactive_pool,imetabolic_above) =  frac_soil(imetabolic,iactive,iabove) * &
740               dt/litter_tau(imetabolic) * control_temp(:,iabove) * control_moist(:,iabove) 
741         
742         
743          MatrixA(:,m,iactive_pool,imetabolic_below) =  frac_soil(imetabolic,iactive,ibelow) * &
744               dt/litter_tau(imetabolic) * control_temp(:,ibelow) * control_moist(:,ibelow)
745         
746          MatrixA(:,m,islow_pool,istructural_above) = frac_soil(istructural,islow,iabove) * &
747               dt/litter_tau(istructural) * &                   
748               control_temp(:,iabove) * control_moist(:,iabove) * &
749               exp( -litter_struct_coef * lignin_struc(:,m,iabove) )* &
750               lignin_struc(:,m,iabove)
751         
752         
753          MatrixA(:,m,islow_pool,istructural_below) = frac_soil(istructural,islow,ibelow) * &
754               dt/litter_tau(istructural) * &   
755               control_temp(:,ibelow) * control_moist(:,ibelow) *  &
756                  exp( -litter_struct_coef * lignin_struc(:,m,ibelow) )* &
757                  lignin_struc(:,m,ibelow) 
758         
759         
760          !- VectorB : carbon input -
761         
762          VectorB(:,m,istructural_above) = litter_inc_PFT(:,m,istructural,iabove,icarbon)
763          VectorB(:,m,istructural_below) = litter_inc_PFT(:,m,istructural,ibelow,icarbon)
764          VectorB(:,m,imetabolic_above) = litter_inc_PFT(:,m,imetabolic,iabove,icarbon)
765          VectorB(:,m,imetabolic_below) = litter_inc_PFT(:,m,imetabolic,ibelow,icarbon)
766         
767          IF (printlev>=4) WRITE(numout,*) 'We filled MatrixA and VectorB' 
768         
769       ENDDO ! Loop over # PFTs
770         
771    ENDIF ! spinup analytic
772
773    IF (printlev>=4) WRITE(numout,*) 'Leaving littercalc'
774
775  END SUBROUTINE littercalc
776
777
778!! ==============================================================================================================================\n
779!! SUBROUTINE   : deadleaf
780!!
781!>\BRIEF        This routine calculates the deadleafcover.
782!!
783!! DESCRIPTION  : It first calculates the lai corresponding to the dead leaves (LAI) using
784!! the dead leaves carbon content (DL) the specific leaf area (sla) and the
785!! maximal coverage fraction of a PFT (vegetmax) using the following equations:
786!! \latexonly
787!! \input{deadleaf1.tex}
788!! \endlatexonly
789!! \n
790!! Then, the dead leaf cover (DLC) is calculated as following:\n
791!! \latexonly
792!! \input{deadleaf2.tex}
793!! \endlatexonly
794!! \n
795!!
796!! RECENT CHANGE(S) : None
797!!
798!! MAIN OUTPUT VARIABLE: ::deadleaf_cover
799!!
800!! REFERENCE(S) : None
801!!
802!! FLOWCHART : None
803!! \n
804!_ ================================================================================================================================
805
806  SUBROUTINE deadleaf (npts, veget_cov_max, dead_leaves, deadleaf_cover)
807
808  !! 0. Variable and parameter declaration
809   
810    !! 0.1 Input variables
811
812    INTEGER(i_std), INTENT(in)                          :: npts           !! Domain size - number of grid pixels (unitless)
813    REAL(r_std), DIMENSION(npts,nvm,nlitt), INTENT(in)  :: dead_leaves    !! Dead leaves per ground unit area, per PFT,
814                                                                          !! metabolic and structural 
815                                                                          !! @tex $(gC m^{-2})$ @endtex
816    REAL(r_std),DIMENSION(npts,nvm),INTENT(in)          :: veget_cov_max  !! PFT "Maximal" coverage fraction of a PFT defined in
817                                                                          !! the input vegetation map
818                                                                          !! @tex $(m^2 m^{-2})$ @endtex
819   
820    !! 0.2 Output variables
821   
822    REAL(r_std), DIMENSION(npts), INTENT(out)           :: deadleaf_cover !! Fraction of soil covered by dead leaves over all PFTs
823                                                                          !! (0-1, unitless)
824
825    !! 0.3 Modified variables
826
827    !! 0.4 Local variables
828
829    REAL(r_std), DIMENSION(npts)                        :: dead_lai       !! LAI of dead leaves @tex $(m^2 m^{-2})$ @endtex
830    INTEGER(i_std)                                      :: j              !! Index (unitless)
831!_ ================================================================================================================================
832   
833  !! 1. LAI of dead leaves
834 
835    dead_lai(:) = zero
836
837    DO j = 1,nvm !Loop over PFTs
838       dead_lai(:) = dead_lai(:) + ( dead_leaves(:,j,imetabolic) + dead_leaves(:,j,istructural) ) * sla(j) &
839            * veget_cov_max(:,j)
840    ENDDO
841
842  !! 2. fraction of soil covered by dead leaves
843
844    deadleaf_cover(:) = un - exp( - 0.5 * dead_lai(:) )
845
846    IF (printlev>=4) WRITE(numout,*) 'Leaving deadleaf'
847
848  END SUBROUTINE deadleaf
849
850
851!! ================================================================================================================================
852!! FUNCTION     : control_moist_func
853!!
854!>\BRIEF        Calculate moisture control for litter and soil C decomposition
855!!
856!! DESCRIPTION  : Calculate moisture control factor applied
857!! to litter decomposition and to soil carbon decomposition in
858!! stomate_soilcarbon.f90 using the following equation: \n
859!! \latexonly
860!! \input{control_moist_func1.tex}
861!! \endlatexonly
862!! \n
863!! with M the moisture control factor and soilmoisutre, the soil moisture
864!! calculated in sechiba.
865!! Then, the function is ranged between Moistcont_min and 1:\n
866!! \latexonly
867!! \input{control_moist_func2.tex}
868!! \endlatexonly
869!! \n
870!! RECENT CHANGE(S) : None
871!!
872!! RETURN VALUE : ::moistfunc_result
873!!
874!! REFERENCE(S) : None
875!!
876!! FLOWCHART : None
877!! \n
878!_ ================================================================================================================================
879 
880  FUNCTION control_moist_func (npts, moist_in) RESULT (moistfunc_result)
881
882  !! 0. Variable and parameter declaration
883   
884    !! 0.1 Input variables
885         
886    INTEGER(i_std), INTENT(in)               :: npts                !! Domain size - number of grid pixel (unitless)
887    REAL(r_std), DIMENSION(npts), INTENT(in) :: moist_in            !! relative humidity (unitless)
888
889    !! 0.2 Output variables
890   
891    REAL(r_std), DIMENSION(npts)             :: moistfunc_result    !! Moisture control factor (0.25-1, unitless)
892
893    !! 0.3 Modified variables
894
895    !! 0.4 Local variables
896
897!_ ================================================================================================================================
898
899    moistfunc_result(:) = -moist_coeff(1) * moist_in(:) * moist_in(:) + moist_coeff(2)* moist_in(:) - moist_coeff(3)
900    moistfunc_result(:) = MAX( moistcont_min, MIN( un, moistfunc_result(:) ) )
901
902  END FUNCTION control_moist_func
903
904
905!! ================================================================================================================================
906!! FUNCTION     : control_temp_func
907!!
908!>\BRIEF        Calculate temperature control for litter and soild C decomposition
909!!
910!! DESCRIPTION  : Calculate temperature control factor applied
911!! to litter decomposition and to soil carbon decomposition in
912!! stomate_soilcarbon.f90 using the following equation: \n
913!! \latexonly
914!! \input{control_temp_func1.tex}
915!! \endlatexonly
916!! \n
917!! with T the temperature control factor, temp the temperature in Kelvin of
918!! the air (for aboveground litter) or of the soil (for belowground litter
919!! and soil)
920!! Then, the function is limited in its maximal range to 1:\n
921!! \latexonly
922!! \input{control_temp_func2.tex}
923!! \endlatexonly
924!! \n
925!! RECENT CHANGE(S) : None
926!!
927!! RETURN VALUE: ::tempfunc_result
928!!
929!! REFERENCE(S) : None
930!!
931!! FLOWCHART : None
932!! \n
933!_ ================================================================================================================================
934
935  FUNCTION control_temp_func (npts, temp_in) RESULT (tempfunc_result)
936
937  !! 0. Variable and parameter declaration
938   
939    !! 0.1 Input variables
940    INTEGER(i_std), INTENT(in)                 :: npts            !! Domain size - number of land pixels (unitless)
941    REAL(r_std), DIMENSION(npts), INTENT(in)   :: temp_in         !! Temperature (K)
942
943    !! 0.2 Output variables
944    REAL(r_std), DIMENSION(npts)               :: tempfunc_result !! Temperature control factor (0-1, unitless)
945
946    !! 0.3 Modified variables
947
948    !! 0.4 Local variables
949
950!_ ================================================================================================================================
951
952    tempfunc_result(:) = exp( soil_Q10 * ( temp_in(:) - (ZeroCelsius+tsoil_ref)) / Q10 )
953    tempfunc_result(:) = MIN( un, tempfunc_result(:) )
954
955  END FUNCTION control_temp_func
956
957END MODULE stomate_litter
Note: See TracBrowser for help on using the repository browser.