SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/hydro_veg.F90
Go to the documentation of this file.
00001 !     #########
00002       SUBROUTINE HYDRO_VEG(HRAIN, PTSTEP, PMUF, PRR, PLEV, PLETR,    &
00003                               PVEG, PPSNV, PWR, PWRMAX, PPG, PDRIP,    &
00004                               PRRVEG  )    
00005 !     #####################################################################
00006 !
00007 !!****  *HYDRO_VEG*  
00008 !!
00009 !!    PURPOSE
00010 !!    -------
00011 !
00012 !     Calculates the evolution of the liquid water retained in the vegetation 
00013 !     canopy (Wr). Also determine the runoff from the canopy that reaches the
00014 !     ground (Mahfouf et al. 1995). This routine take into account the spatially 
00015 !     exponential distribution of precip introduced by Entekhabi and Eagleson (1989).
00016 !         
00017 !     
00018 !!**  METHOD
00019 !!    ------
00020 !
00021 !!    EXTERNAL
00022 !!    --------
00023 !!
00024 !!    none
00025 !!
00026 !!    IMPLICIT ARGUMENTS
00027 !!    ------------------ 
00028 !!
00029 !!    USE MODD_CST
00030 !!      
00031 !!    REFERENCE
00032 !!    ---------
00033 !!
00034 !!    Noilhan and Planton (1989)
00035 !!    Belair (1995)
00036 !!    Mahfouf et al. 1995
00037 !!    Decharme and Douville (2006)
00038 !!      
00039 !!    AUTHOR
00040 !!    ------
00041 !!
00042 !!      S. Belair           * Meteo-France *
00043 !!
00044 !!    MODIFICATIONS
00045 !!    -------------
00046 !!
00047 !!      Original    14/03/95 
00048 !!                  31/08/98 (V. Masson and F. Habets) add Dumenil et Todini
00049 !!                           runoff scheme
00050 !!                  31/08/98 (V. Masson and A. Boone) add the third soil-water
00051 !!                           reservoir (WG3,D3)
00052 !!                  31/05/04 (B. Decharme) add the rainfall spatial distribution
00053 !!                      2008 (B. Decharme) add the dripping rate as new diag
00054 !!                  11/2009  (S.Senesi) returns precipitation intercepted by  
00055 !                               the vegetation 
00056 !!                  07/2011  (B. Decharme) delete SGH for very fine precipitation
00057 !!                  09/2012  (B. Decharme) Computation efficiency for HRAIN=='SGH'
00058 !!                  10/2012  (B. Decharme) PPG intent(out)
00059 !
00060 !-------------------------------------------------------------------------------
00061 !
00062 !*       0.     DECLARATIONS
00063 !               ------------
00064 !
00065 USE MODD_CSTS,ONLY : XLVTT
00066 !
00067 USE MODD_SGH_PAR, ONLY : X001
00068 !
00069 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00070 USE PARKIND1  ,ONLY : JPRB
00071 !
00072 IMPLICIT NONE
00073 !
00074 !*      0.1    declarations of arguments
00075 !
00076  CHARACTER(LEN=*),     INTENT(IN)   :: HRAIN   ! Rainfall spatial distribution
00077                                               ! 'DEF' = No rainfall spatial distribution
00078                                               ! 'SGH' = Rainfall exponential spatial distribution
00079                                               ! 
00080 !
00081 REAL, INTENT(IN)                    :: PTSTEP
00082 !                                      timestep of the integration
00083 !
00084 REAL, DIMENSION(:), INTENT(IN)    :: PRR,  PLEV, PLETR, PMUF
00085 !                                      PRR   = rain rate
00086 !                                      PLEV = latent heat of evaporation over vegetation
00087 !                                      PLETR = evapotranspiration of the vegetation
00088 !                                      PMUF   = fraction of the grid cell reached by the precipitation
00089 !
00090 REAL, DIMENSION(:), INTENT(IN)    :: PVEG, PWRMAX
00091 !                                      PVEG   = fraction of vegetation
00092 !                                      PWRMAX = maximum equivalent water content
00093 !                                               in the vegetation canopy
00094 !
00095 REAL, DIMENSION(:), INTENT(IN)    :: PPSNV
00096 !                                      PPSNV = vegetation covered by snow
00097 !
00098 REAL, DIMENSION(:), INTENT(INOUT) :: PWR
00099 !                                      PWR = liquid water retained on the foliage
00100 !                                             of the vegetation at time 't+dt'
00101 !
00102 REAL, DIMENSION(:), INTENT(OUT)   :: PPG,PDRIP
00103 !                                      PPG   = total water reaching the ground
00104 !                                      PDRIP = Dripping from the vegetation
00105 REAL, DIMENSION(:), INTENT(OUT)   :: PRRVEG  
00106 !                                      PRRVEG = Precip. intercepted by vegetation (kg/m2/s)
00107 !
00108 !
00109 !*      0.2    declarations of local variables
00110 !
00111 REAL, DIMENSION(SIZE(PVEG)) :: ZER
00112 !                                  ZER = evaporation rate from the canopy
00113 !
00114 REAL, DIMENSION(SIZE(PVEG)) :: ZWR ! for time stability scheme
00115 !
00116 REAL, DIMENSION(SIZE(PVEG)) :: ZRUIR, ZRUIR2 ! dripping from the vegetation
00117 !
00118 REAL                        :: ZLIM
00119 !
00120 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00121 !
00122 !-------------------------------------------------------------------------------
00123 !
00124 IF (LHOOK) CALL DR_HOOK('HYDRO_VEG',0,ZHOOK_HANDLE)
00125 ZRUIR (:) = 0.
00126 ZRUIR2(:) = 0.
00127 PDRIP (:) = 0.
00128 ZWR   (:) = 0.
00129 !
00130 !*       1.     EVOLUTION OF THE EQUIVALENT WATER CONTENT Wr
00131 !               --------------------------------------------
00132 !
00133 !evaporation rates
00134 !
00135 ZER(:)    = (PLEV(:)-PLETR(:))  / XLVTT
00136 !
00137 !intercepted rainfall rate
00138 !
00139 PRRVEG(:) = PVEG(:) * (1.-PPSNV(:)) * PRR(:)
00140 !
00141 !evolution of the intercepted water
00142 !(if we don't consider the runoff)
00143 !
00144 PWR(:)  = PWR(:) - PTSTEP * (ZER(:) - PRRVEG(:))
00145 !
00146 !When Wr < 0, the direct evaporation
00147 !(i.e., EV-ETR) removes too much
00148 !liquid water from the vegetation
00149 !reservoir.  This is considered as
00150 !negative runoff, and it is stocked
00151 !in ZRUIR2.
00152 !
00153 ZRUIR2(:) = MIN(0.,PWR(:)/PTSTEP)
00154 !
00155 !Wr must be positive
00156 !
00157 PWR(:)    = MAX(0., PWR(:))
00158 !
00159 IF(HRAIN=='SGH')THEN
00160 !        
00161 !*       2.     SPATIALLY EXPONENTIAL DISTRIBUTION OF PRECIPITATION
00162 !               ---------------------------------------------------
00163 !
00164 !
00165 !  Subgrid dripping from Wr
00166 !
00167    ZLIM=X001/PTSTEP
00168 !
00169    WHERE(PRRVEG(:)>ZLIM.AND.PWR(:)>0.0)
00170         ZRUIR(:) = PRRVEG(:)*EXP(PMUF(:)*(PWR(:)-PWRMAX(:))/(PRRVEG(:)*PTSTEP))
00171         ZRUIR(:) = MIN(ZRUIR(:),PWR(:)/PTSTEP) 
00172    ENDWHERE
00173 !
00174    IF(PTSTEP>300.)THEN
00175 !
00176 !    if the isba time step is coarser than 5min, the "prediction/correction" method is applied
00177 !    to Wr using the predicted Wr* at the end of the time step for time numerical stability
00178 !
00179      ZWR(:)   = PWR(:)-PTSTEP*ZRUIR(:)
00180      ZRUIR(:) = 0.0
00181 !
00182 !    if the dripping is too big, the "prediction/correction" method is applied to Wr using
00183 !    the predicted Wr* at the midle of the time step for time numerical stability 
00184 !    (<=> Runge-Kutta order 1 rang 1)
00185 !
00186      WHERE(PRRVEG(:)>ZLIM.AND.ZWR(:)<=0.0)
00187            ZRUIR(:) = PRRVEG(:)*EXP(PMUF(:)*(PWR(:)-PWRMAX(:))/(PRRVEG(:)*PTSTEP/2.))
00188            ZRUIR(:) = MIN(ZRUIR(:),PWR(:)/(PTSTEP/2.))
00189            ZWR  (:) = PWR(:)-PTSTEP*ZRUIR(:)/2.
00190            ZRUIR(:) = 0.0
00191      ENDWHERE
00192 !
00193 !    Calculate the corrected dripping from the predicted Wr*
00194 !
00195      WHERE(PRRVEG(:)>ZLIM.AND.ZWR(:)>0.0)
00196           ZRUIR(:) = PRRVEG(:)*EXP(PMUF(:)*(ZWR(:)-PWRMAX(:))/(PRRVEG(:)*PTSTEP))
00197           ZRUIR(:) = MIN(ZRUIR(:),PWR(:)/PTSTEP) 
00198      ENDWHERE
00199 !
00200    ENDIF
00201 !
00202    PWR(:)   = PWR(:)-PTSTEP*ZRUIR(:)  
00203 !
00204 !  As previously Wr must be positive (numerical artefact)
00205 !
00206    ZRUIR2(:) = ZRUIR2(:) + MIN(0.,PWR(:)/PTSTEP)
00207    PWR(:)    = MAX( 0., PWR(:) )
00208 !
00209 !  Wr must be smaller then Wrmax
00210 !  Then if Wr remain > Wrmax, there is runoff
00211 !
00212    ZRUIR(:) = ZRUIR(:) + MAX(0., (PWR(:) - PWRMAX(:)) / PTSTEP )
00213 !   
00214 ELSE
00215 !
00216 ! if Wr > Wrmax, there is runoff
00217 !
00218   ZRUIR(:) = MAX(0., (PWR(:) - PWRMAX(:)) / PTSTEP )
00219 !
00220 ENDIF
00221 !
00222 !Wr must be smaller then Wrmax
00223 !
00224 PWR(:)   = MIN(PWR(:), PWRMAX(:))
00225 !
00226 !
00227 !*       3.     LIQUID WATER REACHING THE GROUND Pg
00228 !               -----------------------------------
00229 !
00230 !Thus, the rate of liquid water reaching the ground is the 
00231 !precipitation plus the vegetation runoff (we also consider the
00232 !negative runoff).
00233 !
00234 PPG(:) = (1.-PVEG(:)*(1-PPSNV(:))) * PRR(:) + ZRUIR(:) + ZRUIR2(:)
00235 !
00236 PDRIP(:) = ZRUIR(:) + ZRUIR2(:)
00237 IF (LHOOK) CALL DR_HOOK('HYDRO_VEG',1,ZHOOK_HANDLE)
00238 
00239 !
00240 !-------------------------------------------------------------------------------
00241 !
00242 END SUBROUTINE HYDRO_VEG