SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
lailoss.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE lailoss(PVEG, PSEFOLD, PANMAX, PANDAY, PANFM, PBIOMASS)
7 ! ###############################################################
8 !!**** *LAILOSS*
9 !!
10 !! PURPOSE
11 !! -------
12 !
13 ! Calculates the time change in LAI due to senesence
14 ! and cutting: ie losses/decreases to LAI. This in turn
15 ! reduces the dry biomass of the canopy.
16 !
17 !!** METHOD
18 !! ------
19 ! Calvet at al (1997) [from model of Jacobs(1994)]
20 !!
21 !! EXTERNAL
22 !! --------
23 !! none
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !! none
29 !!
30 !! REFERENCE
31 !! ---------
32 !!
33 !! Calvet et al. (1997)
34 !!
35 !! AUTHOR
36 !! ------
37 !!
38 !! A. Boone * Meteo-France *
39 !! (following Belair)
40 !!
41 !! MODIFICATIONS
42 !! -------------
43 !! Original 27/10/97
44 !! Modified 12/03/04 by P LeMoigne: ZXSEFOLD in days
45 !! L. Jarlan 27/10/04 add RHOA as input to express PANMAX in
46 !! kgCO2 m-2s-1 instead of kgCO2 kgAir-1 m s-1
47 !! P Le Moigne 09/2005 AGS modifs of L. Jarlan
48 !! S. Lafont 03/2011 modification for consistency with nitro_decline
49 !!
50 !-------------------------------------------------------------------------------
51 !
52 USE modd_csts, ONLY : xday
53 USE modd_co2v_par, ONLY: xmc, xmco2, xpcco2
54 !
55 !* 0. DECLARATIONS
56 ! ------------
57 !
58 !
59 !
60 USE yomhook ,ONLY : lhook, dr_hook
61 USE parkind1 ,ONLY : jprb
62 !
63 IMPLICIT NONE
64 !
65 !* 0.1 declarations of arguments
66 !
67 !
68 REAL, DIMENSION(:),INTENT(IN) :: pveg ! vegetation fraction
69 REAL, DIMENSION(:), INTENT(IN) :: psefold ! e-folding time for senescence (s)
70 REAL, DIMENSION(:), INTENT(IN) :: panmax ! maximum photosynthesis rate
71 REAL, DIMENSION(:), INTENT(IN) :: panday ! daily net CO2 accumulation
72 !
73 REAL, DIMENSION(:), INTENT(INOUT) :: panfm ! maximum leaf assimilation
74 REAL, DIMENSION(:), INTENT(INOUT) :: pbiomass ! total dry canopy biomass
75 !
76 !* 0.2 declarations of local variables
77 !
78 REAL, DIMENSION(SIZE(PSEFOLD)) :: zxsefold, zxm
79 REAL :: zbmcoef
80 REAL(KIND=JPRB) :: zhook_handle
81 !
82 !-----------------------------------------------------------------
83 IF (lhook) CALL dr_hook('LAILOSS',0,zhook_handle)
84 !
85 zbmcoef = xmc/(xmco2*xpcco2)
86 !
87 ! Once a day (at midnight), adjust biomass:
88 ! ----------------------------------------
89 !
90 WHERE((pveg(:)>0) )
91  !
92  ! leaf life expectancy
93  !
94  zxsefold(:) = psefold(:)*min(1.0, panfm(:)/panmax(:))/xday
95  !
96  ! avoid possible but unlikely division by zero
97  !
98  zxsefold(:) = max(1.0e-8,zxsefold(:))
99  !
100  ! limitation of leaf life expectancy
101  !
102  zxsefold(:) = max(5.,zxsefold(:))
103  !
104  ! senesence of active biomass
105  !
106  zxm(:) = pbiomass(:)*(1.0-exp(-1.0/zxsefold(:)))
107  !
108  ! decrease biomass:
109  !
110  pbiomass(:) = pbiomass(:) - zxm(:)
111  !
112  ! same modification than nitro_decline.f90
113  ! now the assimilation is added here
114  ! in that way laigain.f90 is consistant between the different carbon options.
115  pbiomass(:) = pbiomass(:) + panday(:)*zbmcoef
116  !
117  ! maximum leaf assimilation (kgCO2 kgAir-1 m s-1):
118  !
119  panfm(:) = 0.0
120  !
121 END WHERE
122 !
123 IF (lhook) CALL dr_hook('LAILOSS',1,zhook_handle)
124 !
125 END SUBROUTINE lailoss
subroutine lailoss(PVEG, PSEFOLD, PANMAX, PANDAY, PANFM, PBIOMASS)
Definition: lailoss.F90:6