SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/carbon_litter.F90
Go to the documentation of this file.
00001 !     #########
00002 SUBROUTINE CARBON_LITTER (PTSTEP, PTURNOVER, PLITTER, PLIGNIN_STRUC,          &
00003                           PCONTROL_TEMP, PCONTROL_MOIST,                      &
00004                           PRESP_HETERO_LITTER, PSOILCARBON_INPUT)  
00005 
00006 !   ###############################################################
00007 !!**  CARBON_LITTER 
00008 !!
00009 !!    PURPOSE
00010 !!    -------
00011 !!    Calculates litter evolution.
00012 !!
00013 !!**  METHOD
00014 !!    ------
00015 !!
00016 !!    EXTERNAL
00017 !!    --------
00018 !!    none
00019 !!
00020 !!    IMPLICIT ARGUMENTS
00021 !!    ------------------
00022 !!      
00023 !!    none
00024 !!
00025 !!    REFERENCE
00026 !!    ---------
00027 !!
00028 !!      Parton et al., Biogeochemestry, 1988
00029 !!      Krinner et al., Global Biochemical Cycles, 2005
00030 !!      Gibelin et al. 2008, AFM
00031 !!      
00032 !!    AUTHOR
00033 !!    ------
00034 !!
00035 !!      A.-L. Gibelin           * Meteo-France *
00036 !!
00037 !!    MODIFICATIONS
00038 !!    -------------
00039 !!      Original    23/06/09
00040 !!      B. Decharme 05/2012 : Optimization
00041 !!
00042 !-------------------------------------------------------------------------------
00043 !
00044 !*       0.     DECLARATIONS
00045 !               ------------
00046 !    
00047 USE MODD_CO2V_PAR,       ONLY : XLC, XTAU_LITTER, XFRAC_LITTER, XFRAC_SOILCARB
00048 USE MODD_CSTS,           ONLY : XDAY, XTT
00049 !
00050 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00051 USE PARKIND1  ,ONLY : JPRB
00052 !
00053 IMPLICIT NONE
00054 !
00055 !*       0.1 input
00056 !
00057 ! time step in s
00058 REAL, INTENT(IN)                                                 :: PTSTEP
00059 !time step in s
00060 ! Turnover rates (gC/m**2/s)
00061 REAL, DIMENSION(:,:), INTENT(IN)                                 :: PTURNOVER
00062 ! temperature control of heterotrophic respiration, above and below
00063 REAL, DIMENSION(:,:), INTENT(IN)                                 :: PCONTROL_TEMP
00064 ! moisture control of heterotrophic respiration
00065 REAL, DIMENSION(:,:), INTENT(IN)                                 :: PCONTROL_MOIST
00066 !
00067 !*       0.2 modified fields
00068 !
00069 ! metabolic and structural litter, above and below ground (gC/m**2)
00070 REAL, DIMENSION(:,:,:), INTENT(INOUT)                            :: PLITTER
00071 ! ratio Lignin/Carbon in structural litter, above and below ground (gC/m**2)
00072 REAL, DIMENSION(:,:), INTENT(INOUT)                              :: PLIGNIN_STRUC
00073 !
00074 !*       0.3 output
00075 !
00076 ! litter heterotrophic respiration (in gC/m**2/day)
00077 REAL, DIMENSION(:), INTENT(OUT)                                  :: PRESP_HETERO_LITTER
00078 ! quantity of carbon going into carbon pools from litter decomposition
00079 !   (gC/m**2/day)
00080 REAL, DIMENSION(:,:), INTENT(OUT)                                :: PSOILCARBON_INPUT
00081 !
00082 !*       0.4 local
00083 !
00084 ! time step in days
00085 REAL                                                             :: ZDT
00086 ! fraction of structural or metabolic litter decomposed
00087 REAL                                                             :: ZFD
00088 ! quantity of structural or metabolic litter decomposed (gC/m**2)
00089 REAL                                                             :: ZQD
00090 ! old structural litter, above and below (gC/m**2)
00091 REAL, DIMENSION(SIZE(PLITTER,1),SIZE(PLITTER,3))                 :: ZOLD_STRUC
00092 ! increase of metabolic and structural litter, above and below ground (gC/m**2)
00093 REAL, DIMENSION(SIZE(PLITTER,1),SIZE(PLITTER,2),SIZE(PLITTER,3)) :: ZLITTER_INC
00094 ! lignin increase in structural litter, above and below ground (gC/m**2)
00095 REAL, DIMENSION(SIZE(PLITTER,1),SIZE(PLITTER,3))                 :: ZLIGNIN_STRUC_INC
00096 ! dimensions
00097 INTEGER                                                          :: INLITTER,INLITTLEVS
00098 ! indices
00099 INTEGER                                                          :: INI,JI,JL
00100 !
00101 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00102 !
00103 ! correspondence between array indices and biomass compartments
00104 ! LEAF = 1
00105 ! STRUCT_ACT = 2
00106 ! STRUCT_PAS = 3
00107 ! STRUCT_BELOW = 4
00108 ! WOOD_ABOVE = 5
00109 ! WOOD_BELOW = 6
00110 ! correspondence between array indices and litter type
00111 ! LT_METABOLIC = 1
00112 ! LT_STRUCTURAL = 2
00113 ! correspondence between array indices and litter levels
00114 ! LT_ABOVE = 1
00115 ! LT_BELOW = 2
00116 ! correspondence between array indices and soil carbon pools
00117 ! SL_ACTIVE = 1
00118 ! SL_SLOW = 2
00119 ! SL_PASSIVE = 3
00120 !-------------------------------------------------------------------------------
00121 !
00122 !*    1 Initialisations
00123 !
00124 !
00125 !*    1.1 dimensions
00126 !
00127 IF (LHOOK) CALL DR_HOOK('CARBON_LITTER',0,ZHOOK_HANDLE)
00128 !
00129 INI        = SIZE(PLITTER,1)
00130 INLITTER   = SIZE(PLITTER,2)
00131 INLITTLEVS = SIZE(PLITTER,3)
00132 !
00133 !*    1.2 set output to zero
00134 !
00135 PRESP_HETERO_LITTER(:) = 0.0
00136 PSOILCARBON_INPUT(:,:) = 0.0
00137 !
00138 !*    2 Add biomass to different litterpools
00139 !
00140 ZDT = PTSTEP/XDAY
00141 !
00142 !*    2.1 first, save old structural litter (needed for lignin fractions).
00143 !            (above/below)
00144 !
00145 ZOLD_STRUC(:,:) = PLITTER(:,2,:)
00146 !
00147 ! *   2.2 update litter, and lignin content in structural litter
00148 !
00149 ZLITTER_INC    (:,:,:) = 0.0
00150 ZLIGNIN_STRUC_INC(:,:) = 0.0
00151 !
00152 !*    2.2.1 calculate litter increase (per m**2 of ground).
00153 !           Litter increase for structural and metabolic, above/below
00154 !
00155 ZLITTER_INC(:,1,1) = ( XFRAC_LITTER(1,1) * PTURNOVER(:,1) +          &
00156                        XFRAC_LITTER(2,1) * PTURNOVER(:,2) +          &
00157                        XFRAC_LITTER(3,1) * PTURNOVER(:,3) +          &
00158                        XFRAC_LITTER(5,1) * PTURNOVER(:,5) ) * PTSTEP 
00159 
00160 ZLITTER_INC(:,1,2) = ( XFRAC_LITTER(4,1) * PTURNOVER(:,4) +          &
00161                        XFRAC_LITTER(6,1) * PTURNOVER(:,6) ) * PTSTEP  
00162 !
00163 ZLITTER_INC(:,2,1) = ( XFRAC_LITTER(1,2) * PTURNOVER(:,1) +          &
00164                        XFRAC_LITTER(2,2) * PTURNOVER(:,2) +          &
00165                        XFRAC_LITTER(3,2) * PTURNOVER(:,3) +          &
00166                        XFRAC_LITTER(5,2) * PTURNOVER(:,5) ) * PTSTEP 
00167 
00168 ZLITTER_INC(:,2,2) = ( XFRAC_LITTER(4,2) * PTURNOVER(:,4) +          &
00169                        XFRAC_LITTER(6,2) * PTURNOVER(:,6) ) * PTSTEP  
00170 !
00171 !*    2.2.2 lignin increase in structural litter
00172 !
00173 ZLIGNIN_STRUC_INC(:,1) = ZLIGNIN_STRUC_INC(:,1) + ( XLC(1)*PTURNOVER(:,1) + XLC(2)*PTURNOVER(:,2) +          &
00174                                                     XLC(3)*PTURNOVER(:,3) + XLC(5)*PTURNOVER(:,5) ) * PTSTEP  
00175 ZLIGNIN_STRUC_INC(:,2) = ZLIGNIN_STRUC_INC(:,2) + ( XLC(4)*PTURNOVER(:,4) + XLC(6)*PTURNOVER(:,6) ) * PTSTEP  
00176 !
00177 !*    2.2.3 add new litter (struct/met, above/below)
00178 !
00179 PLITTER(:,:,:) = PLITTER(:,:,:) + ZLITTER_INC(:,:,:)
00180 !
00181 !*    2.2.4 for security: can't add more lignin than structural litter
00182 !           (above/below)
00183 !
00184 ZLIGNIN_STRUC_INC(:,:) = MIN( ZLIGNIN_STRUC_INC(:,:), ZLITTER_INC(:,2,:) )
00185 !
00186 !*    2.2.5 new lignin content: add old lignin and lignin increase, divide by 
00187 !           total structural litter (above/below)
00188 !
00189 WHERE(PLITTER(:,2,:)>0.0)
00190       PLIGNIN_STRUC(:,:) = (PLIGNIN_STRUC(:,:)*ZOLD_STRUC(:,:)+ZLIGNIN_STRUC_INC(:,:))/PLITTER(:,2,:)
00191 ENDWHERE
00192 !
00193 !*    3 fluxes from litter to carbon pools and respiration
00194 !
00195 DO JL=1,INLITTLEVS
00196    DO JI=1,INI
00197 !
00198 !*    3.1 structural litter: goes into active and slow carbon pools + respiration
00199 !
00200 !*    3.1.1 total quantity of structural litter which is decomposed
00201 !
00202       ZFD=PTSTEP/XTAU_LITTER(2)*PCONTROL_TEMP(JI,JL)*PCONTROL_MOIST(JI,JL)*EXP(-3.0*PLIGNIN_STRUC(JI,JL))  
00203 !
00204       ZQD=PLITTER(JI,2,JL)*ZFD
00205 !      
00206       PLITTER(JI,2,JL)=PLITTER(JI,2,JL)-ZQD
00207 !
00208 !*    3.1.2 non-lignin fraction of structural litter goes into active carbon pool + respiration
00209 !
00210       PSOILCARBON_INPUT(JI,1)=PSOILCARBON_INPUT(JI,1)+XFRAC_SOILCARB(2,1,JL)*ZQD*(1.0-PLIGNIN_STRUC(JI,JL))/ZDT  
00211 !
00212       PRESP_HETERO_LITTER(JI)=PRESP_HETERO_LITTER(JI)+(1.0-XFRAC_SOILCARB(2,1,JL))*ZQD*(1.0-PLIGNIN_STRUC(JI,JL))/ZDT  
00213 !
00214 !*    3.1.3 lignin fraction of structural litter goes into slow carbon pool + respiration
00215 !
00216       PSOILCARBON_INPUT(JI,2)=PSOILCARBON_INPUT(JI,2)+XFRAC_SOILCARB(2,2,JL)*ZQD*PLIGNIN_STRUC(JI,JL)/ZDT  
00217 !
00218       PRESP_HETERO_LITTER(JI)=PRESP_HETERO_LITTER(JI)+(1.0-XFRAC_SOILCARB(2,2,JL))*ZQD*PLIGNIN_STRUC(JI,JL)/ZDT  
00219 !
00220 !*    3.2 metabolic litter goes into active carbon pool + respiration
00221 !
00222 !*    3.2.1 total quantity of metabolic litter that is decomposed
00223 !
00224       ZFD = PTSTEP/XTAU_LITTER(1)*PCONTROL_TEMP(JI,JL)*PCONTROL_MOIST(JI,JL)
00225 !
00226       ZQD = PLITTER(JI,1,JL)*ZFD
00227 !
00228       PLITTER(JI,1,JL)=PLITTER(JI,1,JL)-ZQD
00229 !
00230 !*    3.2.2 put decomposed litter into carbon pool + respiration
00231 !
00232       PSOILCARBON_INPUT(JI,1)=PSOILCARBON_INPUT(JI,1)+XFRAC_SOILCARB(1,1,JL)*ZQD/ZDT  
00233 !
00234       PRESP_HETERO_LITTER(JI) = PRESP_HETERO_LITTER(JI)+(1.0-XFRAC_SOILCARB(1,1,JL))*ZQD/ZDT
00235 !
00236    ENDDO
00237 ENDDO
00238 !
00239 IF (LHOOK) CALL DR_HOOK('CARBON_LITTER',1,ZHOOK_HANDLE)
00240 
00241 !
00242 END SUBROUTINE CARBON_LITTER