SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/lailoss.F90
Go to the documentation of this file.
00001 !     #########
00002     SUBROUTINE LAILOSS(PVEG, PSEFOLD, PANMAX, PANDAY, PANFM, PBIOMASS)  
00003 !   ###############################################################
00004 !!****  *LAILOSS*  
00005 !!
00006 !!    PURPOSE
00007 !!    -------
00008 !
00009 !     Calculates the time change in LAI due to senesence 
00010 !     and cutting: ie losses/decreases to LAI. This in turn
00011 !     reduces the dry biomass of the canopy.
00012 !              
00013 !!**  METHOD
00014 !!    ------
00015 !     Calvet at al (1997) [from model of Jacobs(1994)]
00016 !!
00017 !!    EXTERNAL
00018 !!    --------
00019 !!    none
00020 !!
00021 !!    IMPLICIT ARGUMENTS
00022 !!    ------------------
00023 !!      
00024 !!    none
00025 !!
00026 !!    REFERENCE
00027 !!    ---------
00028 !!
00029 !!    Calvet et al. (1997)
00030 !!      
00031 !!    AUTHOR
00032 !!    ------
00033 !!
00034 !!      A. Boone           * Meteo-France *
00035 !!      (following Belair)
00036 !!
00037 !!    MODIFICATIONS
00038 !!    -------------
00039 !!      Original    27/10/97 
00040 !!      Modified    12/03/04  by P LeMoigne: ZXSEFOLD in days
00041 !!      L. Jarlan   27/10/04  add RHOA as input to express PANMAX in
00042 !!                            kgCO2 m-2s-1 instead of kgCO2 kgAir-1 m s-1
00043 !!      P Le Moigne 09/2005 AGS modifs of L. Jarlan
00044 !!      S. Lafont   03/2011 modification for consistency with nitro_decline
00045 !!
00046 !-------------------------------------------------------------------------------
00047 !
00048 USE MODD_CSTS,  ONLY : XDAY
00049 USE MODD_CO2V_PAR, ONLY: XMC, XMCO2, XPCCO2
00050 !
00051 !*       0.     DECLARATIONS
00052 !               ------------
00053 !
00054 !
00055 !
00056 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00057 USE PARKIND1  ,ONLY : JPRB
00058 !
00059 IMPLICIT NONE
00060 !
00061 !*      0.1    declarations of arguments
00062 !
00063 !
00064 REAL,   DIMENSION(:),INTENT(IN)    :: PVEG      ! vegetation fraction
00065 REAL,   DIMENSION(:), INTENT(IN)   :: PSEFOLD   ! e-folding time for senescence (s)
00066 REAL,   DIMENSION(:), INTENT(IN)   :: PANMAX    ! maximum photosynthesis rate
00067 REAL,   DIMENSION(:), INTENT(IN)   :: PANDAY    ! daily net CO2 accumulation
00068 !
00069 REAL,   DIMENSION(:), INTENT(INOUT) :: PANFM    ! maximum leaf assimilation
00070 REAL,   DIMENSION(:), INTENT(INOUT) :: PBIOMASS ! total dry canopy biomass 
00071 !
00072 !*      0.2    declarations of local variables
00073 !
00074 REAL,    DIMENSION(SIZE(PSEFOLD))  :: ZXSEFOLD, ZXM
00075 REAL                               :: ZBMCOEF
00076 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00077 !
00078 !-----------------------------------------------------------------
00079 IF (LHOOK) CALL DR_HOOK('LAILOSS',0,ZHOOK_HANDLE)
00080 !
00081 ZBMCOEF     = XMC/(XMCO2*XPCCO2)
00082 !
00083 ! Once a day (at midnight), adjust biomass:
00084 ! ----------------------------------------
00085 !
00086 WHERE((PVEG(:)>0) )
00087   !
00088   ! leaf life expectancy
00089   !
00090   ZXSEFOLD(:) = PSEFOLD(:)*MIN(1.0, PANFM(:)/PANMAX(:))/XDAY
00091   !
00092   ! avoid possible but unlikely division by zero
00093   !
00094   ZXSEFOLD(:) = MAX(1.0E-8,ZXSEFOLD(:))
00095   !
00096   ! limitation of leaf life expectancy
00097   !
00098   ZXSEFOLD(:) = MAX(5.,ZXSEFOLD(:))
00099   !
00100   ! senesence of active biomass
00101   !
00102   ZXM(:)      = PBIOMASS(:)*(1.0-EXP(-1.0/ZXSEFOLD(:)))
00103   !
00104   ! decrease biomass:
00105   !
00106   PBIOMASS(:) = PBIOMASS(:) - ZXM(:)
00107   !
00108   ! same modification than nitro_decline.f90
00109   ! now the assimilation is added here
00110   ! in that way laigain.f90 is consistant between the different carbon options.
00111   PBIOMASS(:) =  PBIOMASS(:) + PANDAY(:)*ZBMCOEF
00112   !
00113   ! maximum leaf assimilation (kgCO2 kgAir-1 m s-1):
00114   !
00115   PANFM(:)    = 0.0
00116   !
00117 END WHERE
00118 !
00119 IF (LHOOK) CALL DR_HOOK('LAILOSS',1,ZHOOK_HANDLE)
00120 !
00121 END SUBROUTINE LAILOSS