SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/hydro.F90
Go to the documentation of this file.
00001 !     #########
00002       SUBROUTINE HYDRO(HISBA, HSNOW_ISBA, HRUNOFF, OGLACIER,                &
00003                          OFLOOD, PTSTEP, PVEGTYPE,                          &
00004                          PRR, PSR, PLEV, PLETR, PLEG, PLES,                 &
00005                          PRUNOFFB, PWDRAIN,                                 &
00006                          PC1, PC2, PC3, PC4B, PC4REF, PWGEQ, PCG, PCT,      &
00007                          PVEG, PWRMAX, PMELT, PDWGI1, PDWGI2, PLEGI,        &
00008                          PRUNOFFD, PSOILWGHT, KLAYER_HORT, KLAYER_DUN,      &
00009                          PPSNV, PPSNG,                                      &
00010                          PSNOW_THRUFAL, PEVAPCOR,                           &
00011                          PWR,                                               &
00012                          PSNOWSWE, PSNOWALB, PSNOWRHO,                      &
00013                          PBCOEF, PWSAT, PCONDSAT, PMPOTSAT, PWFC,           &
00014                          PWWILT, PF2WGHT, PF2, PD_G, PDZG, PDZDIF, PPS,     &
00015                          PWG, PWGI, PTG, KWG_LAYER,                         &
00016                          PDRAIN, PRUNOFF,                                   &
00017                          PIRRIG, PWATSUP, PTHRESHOLD, LIRRIDAY, LIRRIGATE,  &
00018                          HKSAT, HSOC, HRAIN, HHORT, PMUF, PFSAT, PKSAT_ICE, &
00019                          PD_ICE, PHORTON, PDRIP, PFFG, PFFV , PFFLOOD,      &
00020                          PPIFLOOD, PIFLOOD, PPFLOOD, PRRVEG, PTDIURN,       & 
00021                          PIRRIG_FLUX        )  
00022 !     #####################################################################
00023 !
00024 !!****  *HYDRO*  
00025 !!
00026 !!    PURPOSE
00027 !!    -------
00028 !
00029 !     Calculates the evolution of the water variables, i.e., the superficial
00030 !     and deep-soil volumetric water content (wg and w2), the equivalent
00031 !     liquid water retained in the vegetation canopy (Wr), the equivalent
00032 !     water of the snow canopy (Ws), and also of the albedo and density of
00033 !     the snow (i.e., SNOWALB and SNOWRHO).  Also determine the runoff and drainage
00034 !     into the soil.
00035 !         
00036 !     
00037 !!**  METHOD
00038 !!    ------
00039 !
00040 !!    EXTERNAL
00041 !!    --------
00042 !!
00043 !!    none
00044 !!
00045 !!    IMPLICIT ARGUMENTS
00046 !!    ------------------ 
00047 !!
00048 !!
00049 !!      
00050 !!    REFERENCE
00051 !!    ---------
00052 !!
00053 !!    Noilhan and Planton (1989)
00054 !!    Belair (1995)
00055 !!      
00056 !!    AUTHOR
00057 !!    ------
00058 !!
00059 !!      S. Belair           * Meteo-France *
00060 !!
00061 !!    MODIFICATIONS
00062 !!    -------------
00063 !!
00064 !!      Original    14/03/95 
00065 !!                  31/08/98 (V. Masson and F. Habets) add Dumenil et Todini
00066 !!                           runoff scheme
00067 !!                  31/08/98 (V. Masson and A. Boone) add the third soil-water
00068 !!                           reservoir (WG3,D3)
00069 !!                  19/07/05 (P. LeMoigne) bug in runoff computation if isba-2L
00070 !!                  10/10/05 (P. LeMoigne) bug in hydro-soil calling sequence
00071 !!                  25/05/08 (B. Decharme) Add floodplains
00072 !!                  27/11/09 (A. Boone)    Add possibility to do time-splitting when
00073 !!                                         calling hydro_soildif (DIF option only)
00074 !!                                         for *very* large time steps (30min to 1h+).
00075 !!                                         For *usual* sized time steps, time step
00076 !!                                         NOT split.
00077 !!                     08/11 (B. Decharme) DIF optimization
00078 !!                     09/12 (B. Decharme) Bug in wg2 ice energy budget
00079 !!                     10/12 (B. Decharme) EVAPCOR snow correction in DIF
00080 !!                                         Add diag IRRIG_FLUX
00081 !-------------------------------------------------------------------------------
00082 !
00083 !*       0.     DECLARATIONS
00084 !               ------------
00085 !
00086 USE MODD_CSTS,      ONLY : XRHOLW, XDAY, XTT, XLVTT, XLSTT
00087 USE MODD_ISBA_PAR,  ONLY : XWGMIN
00088 USE MODD_SURF_PAR,  ONLY : XUNDEF, NUNDEF
00089 !
00090 USE MODD_COUPLING_TOPD, ONLY : LCOUPL_TOPD, XAS_NATURE, XATOP, XRUNOFF_TOP
00091 !
00092 USE MODI_HYDRO_VEG
00093 USE MODI_HYDRO_SNOW
00094 USE MODI_HYDRO_SOIL
00095 USE MODI_HYDRO_SOILDIF                                          
00096 USE MODI_HYDRO_SGH
00097 !
00098 USE MODE_THERMOS
00099 !
00100 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00101 USE PARKIND1  ,ONLY : JPRB
00102 !
00103 IMPLICIT NONE
00104 !
00105 !*      0.1    declarations of arguments
00106 !
00107 !
00108  CHARACTER(LEN=*),     INTENT(IN)   :: HISBA   ! type of ISBA version:
00109 !                                             ! '2-L' (default)
00110 !                                             ! '3-L'
00111 !                                             ! 'DIF'   ISBA-DF
00112  CHARACTER(LEN=*),     INTENT(IN)  :: HSNOW_ISBA ! 'DEF' = Default F-R snow scheme
00113 !                                               !         (Douville et al. 1995)
00114 !                                               ! '3-L' = 3-L snow scheme (option)
00115 !                                               !         (Boone and Etchevers 2001)
00116  CHARACTER(LEN=*),     INTENT(IN)   :: HRUNOFF ! surface runoff formulation
00117 !                                             ! 'WSAT'
00118 !                                             ! 'DT92'
00119 !                                             ! 'SGH ' Topmodel
00120 LOGICAL, INTENT(IN)                :: OGLACIER ! True = Over permanent snow and ice, 
00121 !                                                initialise WGI=WSAT,
00122 !                                                Hsnow>=10m and allow 0.8<SNOALB<0.85
00123 !                                                False = No specific treatment
00124 !
00125 LOGICAL, INTENT(IN)                :: OFLOOD ! Flood scheme 
00126 !
00127 REAL, INTENT(IN)                    :: PTSTEP
00128 !                                      timestep of the integration
00129 !
00130 REAL, DIMENSION(:,:), INTENT(IN)  :: PVEGTYPE ! fraction of each vegetation
00131 !
00132 REAL, DIMENSION(:), INTENT(IN)    :: PRR, PSR, PLEV, PLETR, PLEG, PLES
00133 !                                      PRR = rain rate
00134 !                                      PSR = snow rate
00135 !                                      PLEV = latent heat of evaporation over vegetation
00136 !                                      PLETR = evapotranspiration of the vegetation
00137 !                                      PLEG = latent heat of evaporation over the ground
00138 !                                      PLES = latent heat of sublimation over the snow
00139 !
00140 REAL, DIMENSION(:), INTENT(IN)    :: PRUNOFFB ! slope of the runoff curve
00141 REAL, DIMENSION(:), INTENT(IN)    :: PWDRAIN  ! minimum Wg for drainage (m3/m3)
00142 !
00143 REAL, DIMENSION(:), INTENT(IN)    :: PC1, PC2, PWGEQ, PCG, PCT
00144 REAL, DIMENSION(:,:), INTENT(IN)  :: PC3
00145 !                                      soil coefficients
00146 !                                      C1, C2 = coefficients for the moisture calculations
00147 !                                      C3 = coefficient for WG2 calculation
00148 !                                      PWGEQ = equilibrium surface volumetric moisture
00149 !                                      PCG = soil heat capacity
00150 !                                      PCT = grid-averaged heat capacity
00151 !
00152 REAL, DIMENSION(:), INTENT(IN)    :: PVEG, PRUNOFFD, PWRMAX
00153 !                                      PVEG = fraction of vegetation 
00154 !                                      PRUNOFFD = depth over which sub-grid runoff calculated (m)
00155 !                                      PWRMAX = maximum equivalent water content
00156 !                                               in the vegetation canopy
00157 !
00158 REAL, DIMENSION(:), INTENT(IN)    :: PC4B, PC4REF
00159 !                                      PC4REF, PC4B = fiiting soil paramter for vertical diffusion (C4)
00160 !
00161 REAL, DIMENSION(:), INTENT(IN)    :: PPSNV, PPSNG
00162 !                                      PPSNV = vegetation covered by snow
00163 !                                      PPSNG = baresoil covered by snow
00164 !
00165 REAL, DIMENSION(:), INTENT(IN)    :: PDWGI1, PDWGI2, PLEGI
00166 !                                      PDWGI1 = surface layer liquid water equivalent 
00167 !                                               volumetric ice content time tendency
00168 !                                      PDWGI2 = deep-soil layer liquid water equivalent 
00169 !                                               volumetric ice content time tendency 
00170 !                                      PLEGI  = surface soil ice sublimation 
00171 !
00172 REAL, DIMENSION(:), INTENT(IN)    :: PSNOW_THRUFAL, PEVAPCOR
00173 !                                    PSNOW_THRUFAL = rate that liquid water leaves snow pack: 
00174 !                                               *ISBA-ES* [kg/(m2 s)]
00175 !                                    PEVAPCOR = correction if evaporation from snow exceeds
00176 !                                               actual amount on the surface [kg/(m2 s)]
00177 !
00178 REAL, DIMENSION(:), INTENT(IN)    :: PPS, PF2                                       
00179 !                                    PPS  = surface pressure (Pa)
00180 !                                    PF2  = total water stress factor (-)
00181 !
00182 REAL, DIMENSION(:,:), INTENT(IN)  :: PWSAT, PCONDSAT, PWFC, PD_G, PF2WGHT, PWWILT
00183 !                                    PD_G   = Depth of bottom of Soil layers (m)
00184 !                                    PWFC     = field capacity profile (m3/m3)
00185 !                                    PWWILT   = wilting point profile (m3/m3)
00186 !                                    PWSAT    = porosity profile (m3/m3)
00187 !                                    PCONDSAT = hydraulic conductivity at saturation (m/s)
00188 !                                    PF2WGHT   = water stress factor (profile) (-)
00189 
00190 REAL, DIMENSION(:,:), INTENT(IN)  :: PDZDIF, PDZG
00191 !                                    PDZDIF = distance between consecuative layer mid-points
00192 !                                    PDZG   = soil layers thicknesses
00193 !
00194 REAL, DIMENSION(:,:), INTENT(IN)  :: PSOILWGHT  ! ISBA-DIF: weights for vertical
00195 !                                               ! integration of soil water and properties
00196 INTEGER,             INTENT(IN)   :: KLAYER_HORT! DIF optimization
00197 INTEGER,             INTENT(IN)   :: KLAYER_DUN ! DIF optimization
00198 !
00199 REAL, DIMENSION(:,:), INTENT(IN)  :: PMPOTSAT,PBCOEF
00200 !                                    PMPOTSAT = matric potential at saturation (m)
00201 !                                    PBCOEF   = slope of the retention curve (-)
00202 !
00203 REAL, DIMENSION(:,:), INTENT(INOUT) :: PTG
00204 !                                    PTG   = soil layer average temperatures (K)
00205 !
00206 REAL, DIMENSION(:,:), INTENT(INOUT) :: PWGI, PWG
00207 !                                      PWGI  = soil frozen volumetric water content (m3/m3)
00208 !                                      PWG  = soil liquid volumetric water content (m3/m3)
00209 !                                      Prognostic variables of ISBA at 't-dt'
00210 !                                      ZWGI(:,1) = surface-soil volumetric ice content
00211 !                                      ZWGI(:,2) = deep-soil volumetric ice content
00212 !
00213 INTEGER, DIMENSION(:), INTENT(IN) :: KWG_LAYER  
00214 !                                    KWG_LAYER = Number of soil moisture layers (DIF option)
00215 !
00216 REAL, DIMENSION(:), INTENT(INOUT) :: PWR, PSNOWSWE, PSNOWALB, PSNOWRHO
00217 REAL, DIMENSION(:), INTENT(INOUT) :: PMELT
00218 REAL, DIMENSION(:), INTENT(OUT)   :: PDRAIN, PRUNOFF
00219 !                                      PWR = liquid water retained on the foliage
00220 !                                             of the vegetation at time 't+dt'
00221 !                                      PSNOWSWE = equivalent water content of the
00222 !                                             snow reservoir at time 't+dt'
00223 !                                      PSNOWALB = albedo of the snow at 't+dt'
00224 !                                      PSNOWRHO = density of the snow at 't+dt' 
00225 !                                      PMELT = melting rate of the snow
00226 !                                      PDRAIN = drainage (kg/m2/s)
00227 !                                      PRUNOFF = runoff  (kg/m2/s)
00228 !
00229 !
00230 REAL   ,DIMENSION(:),INTENT(IN)    :: PIRRIG
00231 REAL   ,DIMENSION(:),INTENT(IN)    :: PWATSUP
00232 REAL   ,DIMENSION(:),INTENT(IN)    :: PTHRESHOLD
00233 LOGICAL,DIMENSION(:),INTENT(INOUT) :: LIRRIDAY
00234 LOGICAL,DIMENSION(:),INTENT(IN)    :: LIRRIGATE
00235 REAL   ,DIMENSION(:),INTENT(OUT)   :: PIRRIG_FLUX ! irrigation rate (kg/m2/s)
00236 !
00237  CHARACTER(LEN=*),     INTENT(IN)   :: HKSAT   ! soil hydraulic profil option
00238 !                                             ! 'DEF'  = ISBA homogenous soil
00239 !                                             ! 'SGH'  = ksat exponential decay
00240 !
00241  CHARACTER(LEN=*),     INTENT(IN)   :: HSOC    ! soil organic carbon profil option
00242 !                                             ! 'DEF'  = ISBA homogenous soil
00243 !                                             ! 'SGH'  = SOC profile
00244 !
00245  CHARACTER(LEN=*), INTENT(IN)       :: HRAIN   ! Rainfall spatial distribution
00246                                               ! 'DEF' = No rainfall spatial distribution
00247                                               ! 'SGH' = Rainfall exponential spatial distribution
00248                                               ! 
00249 !
00250  CHARACTER(LEN=*), INTENT(IN)       :: HHORT   ! Horton runoff
00251                                               ! 'DEF' = no Horton runoff
00252                                               ! 'SGH' = Horton runoff
00253 !                                        
00254 REAL, DIMENSION(:),  INTENT(IN)   :: PD_ICE   !depth of the soil column for the calculation
00255 !                                              of the frozen soil fraction (m)
00256 REAL, DIMENSION(:),  INTENT(IN)   :: PKSAT_ICE!hydraulic conductivity at saturation (m/s)
00257 !                                            
00258 REAL, DIMENSION(:),  INTENT(IN)   :: PMUF     !fraction of the grid cell reached by the rainfall
00259 REAL, DIMENSION(:),  INTENT(INOUT):: PFSAT    !Topmodel/dt92 saturated fraction
00260 !
00261 REAL, DIMENSION(:),  INTENT(OUT)  :: PHORTON    !Horton runoff (kg/m2/s)
00262 !
00263 REAL, DIMENSION(:),  INTENT(OUT)   :: PDRIP    !Dripping from the vegetation (kg/m2/s)
00264 REAL, DIMENSION(:),  INTENT(OUT)   :: PRRVEG   !Precip. intercepted by vegetation (kg/m2/s)
00265 !
00266 REAL, DIMENSION(:),  INTENT(IN)    :: PFFG,PFFV
00267 REAL, DIMENSION(:),  INTENT(IN)    :: PFFLOOD  !Floodplain effective fraction
00268 REAL, DIMENSION(:),  INTENT(IN)    :: PPIFLOOD !Floodplain potential infiltration [kg/mē/s]
00269 !
00270 REAL, DIMENSION(:), INTENT(INOUT)  :: PIFLOOD  !Floodplain real infiltration      [kg/mē/s]
00271 REAL, DIMENSION(:), INTENT(INOUT)  :: PPFLOOD  !Floodplain interception           [kg/mē/s]
00272 !
00273 REAL, DIMENSION(:), INTENT(IN)     :: PTDIURN
00274 !                                     PTDIURN      = penetration depth for restore (m)
00275 !
00276 !*      0.2    declarations of local variables
00277 !
00278 !
00279 INTEGER                         :: JJ, JL      ! loop control                                       
00280 INTEGER                         :: INDT, JDT   ! Time splitting indicies
00281 INTEGER                         :: INI, INL, IDEPTH ! (ISBA-DF option)
00282 !
00283 REAL                            :: ZTSTEP      ! maximum time split time step (<= PTSTEP)
00284 !                                              ! ONLY used for DIF option.
00285 !
00286 REAL, DIMENSION(SIZE(PVEG))     :: ZPG, ZPG_MELT, ZDUNNE,                          
00287                                    ZLEV, ZLEG, ZLEGI, ZLETR, ZPSNV,                
00288                                    ZRR, ZDG, ZWG, ZWSAT_AVG, ZWWILT_AVG, ZWFC_AVG, 
00289                                    ZDRAIN, ZHORTON, ZEVAPCOR 
00290 !                                      Prognostic variables of ISBA at 't-dt'
00291 !                                      ZPG = total water reaching the ground
00292 !                                      ZPG_MELT = snowmelt reaching the ground 
00293 !                                      ZDUNNE  = Dunne runoff
00294 !                                 ZLEV, ZLEG, ZLEGI, ZLETR = Evapotranspiration amounts
00295 !                                      from the non-explicit snow area *ISBA-ES*
00296 !                                 ZPSNV = used to calculate interception of liquid
00297 !                                      water by the vegetation in FR snow method:
00298 !                                      For ES snow method, precipitation already modified
00299 !                                      so set this to zero here for this option.
00300 !                                 ZWSAT_AVG, ZWWILT_AVG, ZWFC_AVG = Average water and ice content
00301 !                                      values over the soil depth D2 (for calculating surface runoff)
00302 !                                 ZDRAIN and ZHORTON are working variables only used for DIF option
00303 !                                 ZEVAPCOR = correction if evaporation from snow exceeds
00304 !                                               actual amount on the surface [m/s]
00305 !
00306 REAL, DIMENSION(SIZE(PWG,1),SIZE(PWG,2)) :: ZQSAT, ZQSATI, ZTI, ZPS
00307 !                                           For specific humidity at saturation computation (ISBA-DIF)
00308 !
00309 REAL, PARAMETER :: ZRICHARDSDTMAX = 900.  ! s  Maximum timescale for Richard's Eq. If the model
00310 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00311                                           !    timestep exceeds this (rather large) value,
00312                                           !    then time split used for Richard's Eq. (DIF option only)
00313 !-------------------------------------------------------------------------------
00314 !
00315 !*       0.     Initialization:
00316 !               ---------------
00317 !
00318 IF (LHOOK) CALL DR_HOOK('HYDRO',0,ZHOOK_HANDLE)
00319 JDT    = 0
00320 INDT   = 0
00321 ZTSTEP = 0.0
00322 !
00323 ZPG(:)           = 0.0
00324 ZPG_MELT(:)      = 0.0
00325 ZDUNNE(:)        = 0.0
00326 ZEVAPCOR(:)      = 0.0
00327 !
00328 ZWSAT_AVG(:)     = 0.0
00329 ZWWILT_AVG(:)    = 0.0
00330 ZWFC_AVG(:)      = 0.0
00331 !
00332 ZRR(:)           = PRR(:)
00333 !
00334 PDRAIN(:)        = 0.
00335 PRUNOFF(:)       = 0.
00336 PHORTON(:)       = 0.
00337 !
00338 ! Initialize evaporation components: variable definitions
00339 ! depend on snow scheme:
00340 !
00341 IF(HSNOW_ISBA == '3-L' .OR. HSNOW_ISBA == 'CRO' .OR. HISBA == 'DIF')THEN
00342    ZLEV(:)          = (1.0-PPSNV(:)-PFFV(:)) * PLEV(:)
00343    ZLETR(:)         = (1.0-PPSNV(:)-PFFV(:)) * PLETR(:)
00344    ZLEG(:)          = (1.0-PPSNG(:)-PFFG(:)) * PLEG(:)
00345    ZLEGI(:)         = (1.0-PPSNG(:)-PFFG(:)) * PLEGI(:)
00346    ZPSNV(:)         = 0.0
00347 ELSE
00348    ZLEV(:)          = PLEV(:)
00349    ZLETR(:)         = PLETR(:)
00350    ZLEG(:)          = PLEG(:)
00351    ZLEGI(:)         = PLEGI(:)
00352    ZPSNV(:)         = PPSNV(:)+PFFV(:)
00353 ENDIF
00354 !
00355 ! Initialize average soil hydrological parameters
00356 ! over the entire soil column: if Isba Force-Restore
00357 ! is in use, then parameter profile is constant
00358 ! so simply use first element of this array: if
00359 ! the Diffusion option is in force, the relevant
00360 ! calculation is done later within this routine.
00361 !
00362 IF(HISBA == '2-L' .OR. HISBA == '3-L')THEN  
00363    ZWSAT_AVG(:)     = PWSAT(:,1)
00364    ZWWILT_AVG(:)    = PWWILT(:,1)
00365    ZWFC_AVG(:)      = PWFC(:,1)
00366 ENDIF
00367 !
00368 IF (HISBA == '3-L') THEN                                   
00369    ZDG(:) = PD_G(:,3)
00370    ZWG(:) = PWG (:,3)
00371 ELSE
00372    ZDG(:) = XUNDEF
00373    ZWG(:) = XUNDEF
00374 END IF
00375 !
00376 !* irrigation
00377 !
00378 PIRRIG_FLUX(:)=0.0
00379 !
00380 IF (SIZE(LIRRIGATE)>0) THEN
00381    WHERE (LIRRIGATE(:) .AND. PIRRIG(:)>0. .AND. PIRRIG(:) /= XUNDEF .AND. (PF2(:)<PTHRESHOLD(:)) )
00382       PIRRIG_FLUX(:) = PWATSUP(:) / XDAY           
00383       ZRR        (:) = ZRR(:) + PWATSUP(:) / XDAY
00384       LIRRIDAY   (:) = .TRUE.           
00385    END WHERE
00386 ENDIF
00387 !
00388 !-------------------------------------------------------------------------------
00389 !
00390 !*       1.     EVOLUTION OF THE EQUIVALENT WATER CONTENT Wr
00391 !               --------------------------------------------
00392 !
00393  CALL HYDRO_VEG(HRAIN, PTSTEP, PMUF,                              &
00394                  ZRR, ZLEV, ZLETR, PVEG, ZPSNV,                    &
00395                  PWR, PWRMAX, ZPG, PDRIP, PRRVEG                  ) 
00396 !
00397 !-------------------------------------------------------------------------------
00398 !
00399 !*       2.     EVOLUTION OF THE EQUIVALENT WATER CONTENT snowSWE 
00400 !               -------------------------------------------------
00401 !
00402 !*       3.     EVOLUTION OF SNOW ALBEDO 
00403 !               ------------------------
00404 !
00405 !*       4.     EVOLUTION OF SNOW DENSITY 
00406 !               -------------------------
00407 !
00408 ! Boone and Etchevers '3-L' snow option
00409 IF(HSNOW_ISBA == '3-L' .OR. HSNOW_ISBA == 'CRO' .OR. HISBA == 'DIF')THEN
00410 !
00411   ZPG_MELT(:)   = ZPG_MELT(:)   + PSNOW_THRUFAL(:)          ! [kg/(m2 s)]
00412 !
00413 ! Note that 'melt' is referred to as rain and meltwater
00414 ! running off from the snowpack in a timestep for ISBA-ES,
00415 ! not the actual amount of ice converted to liquid.
00416 !
00417   PMELT(:) = PMELT(:) + PSNOW_THRUFAL(:)          ! [kg/(m2 s)]
00418 !
00419 ELSE
00420   !
00421   CALL HYDRO_SNOW(OGLACIER, PTSTEP, PVEGTYPE,          &
00422                   PSR, PLES, PMELT,                    &
00423                   PSNOWSWE, PSNOWALB, PSNOWRHO,ZPG_MELT)
00424   !
00425 ENDIF
00426 !
00427 !-------------------------------------------------------------------------------
00428 !
00429 !*       5.     Sub Grid Hydrology
00430 !               ------------------
00431 !
00432 ! - Dunne runoff  : Dumenil et Todini (1992) or Topmodel
00433 ! - Horton runoff : Direct or exponential precipitation distribution
00434 ! - Floodplains interception and infiltration
00435 !
00436  CALL HYDRO_SGH(HISBA,HRUNOFF,HRAIN,HHORT,         &
00437                  PTSTEP,PD_G,PDZG,PWSAT,PWWILT,   &
00438                  PWG, PWGI, KWG_LAYER,            &
00439                  ZPG, ZPG_MELT, PMUF,             &
00440                  PCONDSAT, PBCOEF,                &
00441                  PMPOTSAT, PKSAT_ICE, PD_ICE,     &
00442                  PFSAT, PHORTON, ZDUNNE, PFFLOOD, &
00443                  PPIFLOOD, PIFLOOD, PPFLOOD,      &
00444                  PRUNOFFB, PRUNOFFD, PTDIURN,     &
00445                  PSOILWGHT, OFLOOD, KLAYER_HORT,  &
00446                  KLAYER_DUN                       )         
00447 !
00448 !-------------------------------------------------------------------------------
00449 !
00450 !*       6.     EVOLUTION OF THE SOIL WATER CONTENT
00451 !               -----------------------------------
00452 !
00453 !*       7.     EFFECT OF MELTING/FREEZING ON SOIL ICE AND LIQUID WATER CONTENTS
00454 !               ----------------------------------------------------------------
00455 !
00456 !*       8.     DRAINAGE FROM THE DEEP SOIL
00457 !               ---------------------------
00458 !
00459 !*      9.     RUN-OFF 
00460 !               -------
00461 !                                     when the soil water exceeds saturation, 
00462 !                                     there is fast-time-response runoff
00463 !
00464 IF (HISBA=='DIF') THEN                
00465 !
00466   INI = SIZE(PD_G(:,:),1)
00467   INL = MAXVAL(KWG_LAYER(:))
00468 !
00469 ! Initialize some field
00470 ! ---------------------
00471 !
00472   ZPS(:,:)=XUNDEF
00473   ZTI(:,:)=XUNDEF
00474   DO JL=1,INL
00475      DO JJ=1,INI
00476         IDEPTH=KWG_LAYER(JJ)
00477         IF(JL<=IDEPTH)THEN
00478           ZPS(JJ,JL) = PPS(JJ)
00479           ZTI(JJ,JL) = MIN(XTT,PTG(JJ,JL))
00480         ENDIF
00481      ENDDO
00482   ENDDO
00483 !
00484 ! Compute specific humidity at saturation for the vapor conductivity
00485 ! ------------------------------------------------------------------
00486 !
00487   ZQSAT (:,:) = QSAT (PTG(:,:),ZPS(:,:),KWG_LAYER(:),INL)
00488   ZQSATI(:,:) = QSATI(ZTI(:,:),ZPS(:,:),KWG_LAYER(:),INL)
00489 !
00490 ! Soil water sink terms: convert from (W m-2) and (kg m-2 s-1) to (m s-1)
00491 ! ------------------------------------------------------------------
00492 !
00493   ZPG     (:) =  ZPG    (:)        / XRHOLW
00494   ZEVAPCOR(:) = PEVAPCOR(:)        / XRHOLW
00495   ZLEG    (:) =  ZLEG   (:)        /(XRHOLW*XLVTT)
00496   ZLETR   (:) = (ZLETR  (:)/PF2(:))/(XRHOLW*XLVTT)
00497 !
00498 ! -----------------------------------------------------------------
00499 ! Time splitting for *very large time steps* since Richard's Eq is very
00500 ! non-linear and for large throughfall (snowmelt, rainfall) with a thin
00501 ! upper soil layer.
00502 ! NOTE for NWP/GCM type applications, the time step is generally not split
00503 ! (usually just for offline applications with a time step on order of 
00504 ! 15 minutes to an hour for example)
00505 ! ------------------------------------------------------------------
00506 !
00507   INDT = 1
00508   IF(PTSTEP>=ZRICHARDSDTMAX)THEN
00509     INDT = MAX(2,NINT(PTSTEP/ZRICHARDSDTMAX))
00510   ENDIF
00511 !
00512   ZTSTEP  = PTSTEP/REAL(INDT)
00513 !
00514   DO JDT     = 1,INDT
00515     CALL HYDRO_SOILDIF(ZTSTEP,                                      &
00516                 PBCOEF, PWSAT, PCONDSAT, PMPOTSAT, PWFC,            &
00517                 PD_G, PDZG, PDZDIF, ZPG, ZLETR, ZLEG, ZEVAPCOR,     &
00518                 PF2WGHT, PWG, PWGI, PTG, PPS, ZQSAT, ZQSATI,        &
00519                 PWDRAIN, ZDRAIN, ZHORTON, HKSAT, HSOC, PWWILT,      &
00520                 HHORT, PFSAT, KWG_LAYER, INL, KLAYER_HORT           )  
00521 !
00522     PDRAIN (:)  = PDRAIN (:) + ZDRAIN (:)/REAL(INDT)
00523     PHORTON(:)  = PHORTON(:) + ZHORTON(:)/REAL(INDT)
00524   ENDDO
00525 !
00526 ELSE
00527   !
00528   CALL HYDRO_SOIL(HISBA,                                           &
00529                   PTSTEP,                                          &
00530                   ZLETR, ZLEG, ZPG, PEVAPCOR,                      &
00531                   PWDRAIN,                                         &
00532                   PC1, PC2, PC3, PC4B, PC4REF, PWGEQ,              &
00533                   PD_G(:,2), ZDG, ZWSAT_AVG, ZWFC_AVG,             &
00534                   PDWGI1, PDWGI2, ZLEGI, PD_G(:,1), PCG, PCT,      &
00535                   PTG(:,1), PTG(:,2),                              &
00536                   PWG(:,1), PWG(:,2), ZWG,                         &
00537                   PWGI(:,1), PWGI(:,2),                            &
00538                   PDRAIN,HKSAT,ZWWILT_AVG                          )
00539   !
00540   IF (HISBA=='2-L' .OR. HISBA=='3-L') THEN
00541     !
00542     ! runoff of second layer
00543     PRUNOFF(:) = MAX( 0., PWG(:,2)+PWGI(:,2)-ZWSAT_AVG(:) )*      &
00544                  PD_G(:,2) * XRHOLW / PTSTEP  
00545     !
00546     ! now apply limits:
00547     !
00548     PWG(:,1) = MIN( PWG(:,1), ZWSAT_AVG(:) - PWGI(:,1) )
00549     PWG(:,1) = MAX( PWG(:,1), XWGMIN                   )
00550     !
00551     PWG(:,2) = MIN( PWG(:,2), ZWSAT_AVG(:) - PWGI(:,2) )
00552     PWG(:,2) = MAX( PWG(:,2), XWGMIN                   )
00553     !
00554     IF (HISBA=='3-L') THEN
00555 
00556       !    runoff of third layer added to drainage
00557       PDRAIN(:) = PDRAIN(:) + MAX( 0., ZWG(:)-ZWSAT_AVG(:) )*   &
00558                   (PD_G(:,3)-PD_G(:,2)) * XRHOLW / PTSTEP  
00559       PWG(:,3) = MIN( ZWG(:)  , ZWSAT_AVG(:)           )
00560       PWG(:,3) = MAX( PWG(:,3), XWGMIN                 )
00561     END IF
00562   ENDIF
00563   !
00564   IF (LCOUPL_TOPD) THEN
00565     !runoff topo cumule (kg/mē)
00566     WHERE ( XATOP(:)/=XUNDEF ) XRUNOFF_TOP(:) = XRUNOFF_TOP(:) + (PRUNOFF(:)+ PHORTON(:))*XATOP(:)*PTSTEP
00567     IF (HRUNOFF=='TOPD') THEN     
00568       WHERE ( XATOP(:)/=XUNDEF ) XRUNOFF_TOP(:) = XRUNOFF_TOP(:) + ZDUNNE(:)*PTSTEP
00569       ! ZDUNNE contains only saturated pixels on mesh so only catchment
00570     ELSE
00571       WHERE ( XATOP(:)/=XUNDEF ) XRUNOFF_TOP(:) = XRUNOFF_TOP(:) + ZDUNNE(:)*XATOP(:)*PTSTEP  
00572       ! ZDUNNE concerns all the mesh so not only catchment =>*XATOP
00573     ENDIF
00574   ENDIF
00575   !
00576 ENDIF
00577 !
00578 !-------------------------------------------------------------------------------
00579 !
00580 ! Add sub-grid surface runoff to saturation excess:
00581 !
00582 PRUNOFF(:) = PRUNOFF(:) + ZDUNNE(:) + PHORTON(:)
00583 !
00584 !-------------------------------------------------------------------------------
00585 !
00586 IF (LHOOK) CALL DR_HOOK('HYDRO',1,ZHOOK_HANDLE)
00587 !
00588 !-------------------------------------------------------------------------------
00589 !
00590 END SUBROUTINE HYDRO