SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/hydro_sgh.F90
Go to the documentation of this file.
00001 !     #########
00002       SUBROUTINE HYDRO_SGH  (HISBA,HRUNOFF,HRAIN,HHORT,PTSTEP,           &
00003                                PD_G,PDZG,PWSAT,PWWILT,PWG,PWGI,          &
00004                                KWG_LAYER,PPG,PPG_MELT,PMUF,              &
00005                                PCONDSAT,PBCOEF,PMPOTSAT,                 &
00006                                PKSAT_ICE,PD_ICE,PFSAT,PHORTON,PDUNNE,    &
00007                                PFFLOOD,PPIFLOOD,PIFLOOD,PPFLOOD,         &
00008                                PRUNOFFB,PRUNOFFD,PTDIURN,PSOILWGHT,      &
00009                                OFLOOD,KLAYER_HORT,KLAYER_DUN             )  
00010 !
00011 !     #####################################################################
00012 !
00013 !!****  *HYDRO_SGH*  
00014 !!
00015 !!    PURPOSE
00016 !!    =======
00017 !
00018 !     1. Determine the Horton runoff that take account of a spatial subgrid 
00019 !        exponential distribution of the precipitation and of the surface ksat.
00020 !     1. Determine the surface saturated fraction (dt92 or Topmodel).
00021 !     3. Determine the Dunne runoff (dt92 or Topmodel).
00022 !     4. Determine the infiltration rate.
00023 !     5. Determine the flooplains interception and infiltration rate.
00024 !
00025 !-------------------------------------------------------------------------------
00026 !
00027 !*       0.     DECLARATIONS
00028 !        ===================
00029 !
00030 !
00031 USE MODD_CSTS,      ONLY : XRHOLW, XDAY
00032 USE MODD_ISBA_PAR,  ONLY : XWGMIN
00033 USE MODD_SURF_PAR,  ONLY : XUNDEF
00034 USE MODD_SGH_PAR,   ONLY : XHORT_DEPTH
00035 !
00036 USE MODD_SURF_PAR,  ONLY : XUNDEF
00037 USE MODD_SURF_ATM_n, ONLY : NR_NATURE
00038 USE MODD_COUPLING_TOPD, ONLY : LCOUPL_TOPD, XAS_NATURE, XATOP
00039 !
00040 USE MODI_HYDRO_DT92
00041 !
00042 USE MODE_HYDRO_DIF
00043 !
00044 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00045 USE PARKIND1  ,ONLY : JPRB
00046 !
00047 IMPLICIT NONE
00048 !
00049 !*      0.1    declarations of arguments
00050 !
00051 !
00052 !
00053  CHARACTER(LEN=*),INTENT(IN)      :: HISBA   ! hydrology/soil:
00054 !                                           ! '2-L'  = single column
00055 !                                           ! '3-L'  = root zone/baseflow layer
00056 !                                           ! 'DIF'  = N-layer diffusion: Richard's Eq.
00057 !                                           !         (Boone and Etchevers 2001)
00058 !
00059  CHARACTER(LEN=*),     INTENT(IN) :: HRUNOFF ! surface runoff formulation
00060 !                                           ! 'WSAT'
00061 !                                           ! 'DT92'
00062 !                                           ! 'SGH ' Topmodel
00063 !
00064 !
00065  CHARACTER(LEN=*), INTENT(IN)     :: HRAIN   ! Rainfall spatial distribution
00066                                             ! 'DEF' = No rainfall spatial distribution
00067                                             ! 'SGH' = Rainfall exponential spatial distribution
00068                                             ! 
00069 !
00070  CHARACTER(LEN=*), INTENT(IN)     :: HHORT   ! Horton runoff
00071                                             ! 'DEF' = no Horton runoff
00072                                             ! 'SGH' = Horton runoff
00073 !
00074 LOGICAL, INTENT(IN)              :: OFLOOD ! Flood scheme 
00075 !
00076 REAL, INTENT(IN)                 :: PTSTEP
00077 !                                   timestep of the integration
00078 !
00079 REAL, DIMENSION(:,:), INTENT(IN) :: PWG,PWGI
00080 !                                   PWG   = layer average liquid volumetric water content (m3 m-3)
00081 !                                   PWGI  = layer average frozen volumetric water content (m3 m-3)
00082 !
00083 INTEGER, DIMENSION(:),INTENT(IN) :: KWG_LAYER  
00084 !                                   KWG_LAYER = Number of soil moisture layers (DIF option)
00085 !
00086 REAL, DIMENSION(:,:), INTENT(IN) :: PD_G,PDZG,PWSAT,PWWILT
00087 REAL, DIMENSION(:,:), INTENT(IN) :: PCONDSAT
00088 !                                   PD_G  = layer depth (m)
00089 !                                   PDZG= layer thickness (m)
00090 !                                   PCONDSAT = surface saturated hydraulic conductivity
00091 !                                   PWSAT = soil porosity (m3 m-3)
00092 !
00093 REAL, DIMENSION(:,:), INTENT(IN) :: PBCOEF,PMPOTSAT
00094 !                                   PMPOTSAT = matric potential at saturation (m) (BC parameters)
00095 !                                   PBCOEF   = slope of the retention curve (-) (BC parameters)
00096 !
00097 REAL, DIMENSION(:,:),INTENT(IN) :: PSOILWGHT  ! ISBA-DIF: weights for vertical
00098 !                                             ! integration of soil water and properties
00099 INTEGER,             INTENT(IN) :: KLAYER_HORT! DIF optimization
00100 INTEGER,             INTENT(IN) :: KLAYER_DUN ! DIF optimization
00101 !
00102 REAL, DIMENSION(:), INTENT(INOUT):: PFSAT
00103 !                                   PFSAT = satured fraction
00104 !
00105 REAL, DIMENSION(:), INTENT(INOUT):: PPG
00106 REAL, DIMENSION(:), INTENT(IN)   :: PPG_MELT, PMUF
00107 !                                   PPG      = water reaching the ground
00108 !                                   PPG_MELT = snowmelt reaching the ground
00109 !                                   PMUF      = wet fraction reached by rain
00110 !
00111 REAL, DIMENSION(:), INTENT(IN)   :: PKSAT_ICE, PD_ICE
00112 !                                   PKSAT_ICE = hydraulic conductivity at saturation (m s-1)
00113 !                                               on frozen soil depth (Horton calculation)
00114 !                                   PD_ICE    = depth of the soil column for
00115 !                                               fraction of frozen soil calculation (m)
00116 !
00117 REAL, DIMENSION(:), INTENT(OUT)  :: PDUNNE, PHORTON
00118 !                                   PDUNNE  = Dunne runoff
00119 !                                   PHORTON = Horton runoff
00120 !
00121 REAL, DIMENSION(:), INTENT(IN   ) :: PFFLOOD
00122 REAL, DIMENSION(:), INTENT(IN   ) :: PPIFLOOD
00123 REAL, DIMENSION(:), INTENT(INOUT) :: PIFLOOD, PPFLOOD
00124 !                                    PIFLOOD = Floodplain infiltration     [kg/m²/s]
00125 !                                    PPFLOOD = Floodplain interception     [kg/m²/s]
00126 !
00127 REAL, DIMENSION(:), INTENT(IN)    :: PRUNOFFB ! slope of the runoff curve
00128 REAL, DIMENSION(:), INTENT(IN)    :: PRUNOFFD
00129 !                                    PRUNOFFD = depth over which sub-grid runoff calculated (m)
00130 !
00131 REAL, DIMENSION(:), INTENT(IN)    :: PTDIURN
00132 !                                    PTDIURN      = penetration depth for restore (m)
00133 !
00134 !*      0.2    declarations of local variables
00135 !
00136 REAL, PARAMETER                            :: ZEICE = 6.0  ! Ice vertical diffusion impedence factor 
00137 !
00138 REAL, DIMENSION(SIZE(PPG))                 :: ZPG_INI, ZFROZEN, ZIMAX_ICE, ZIMAX, 
00139                                               ZHORT_R, ZHORT_M, ZSOILMAX, ZIF_MAX                   
00140 !                                             ZFROZEN  = frozen soil fraction for runoff
00141 !                                             ZIMAX_ICE    = maximum infiltration rate for frozen soil
00142 !                                             ZIMAX     = maximum infiltration rate for unfrozen soil
00143 REAL, DIMENSION(SIZE(PPG))                 :: ZWG2_AVG, ZWGI2_AVG, ZWSAT_AVG, ZWWILT_AVG
00144 !                                             Average water and ice content
00145 !                                             values over the soil depth D2 (for calculating surface runoff)
00146 !
00147 REAL, DIMENSION(SIZE(PD_G,1),SIZE(PD_G,2)) :: ZNOFRZ, ZWSAT
00148 !
00149 REAL, DIMENSION(SIZE(PPG))                 :: ZPG_WORK, ZRUISDT, ZNL_HORT, ZDEPTH
00150 !
00151 REAL, DIMENSION(SIZE(PPG))                 :: ZRUNOFF_TOPD
00152 !
00153 REAL                                       :: ZEFFICE, ZLOG10, ZLOG, ZS, ZD_H, ZFRZ
00154 !
00155 INTEGER                                    :: INI, INL, JJ, JL, IDEPTH
00156 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00157 !
00158 !-------------------------------------------------------------------------------
00159 !
00160 !allocate
00161 !
00162 IF (LHOOK) CALL DR_HOOK('HYDRO_SGH',0,ZHOOK_HANDLE)
00163 !
00164 !initialize
00165 !
00166 ZFROZEN  (:)  = 0.0
00167 ZIMAX_ICE(:)  = 0.0
00168 ZIMAX    (:)  = 0.0
00169 !
00170 ZWSAT  (:,:)  = 0.0
00171 !
00172 ZLOG10 = LOG(10.0)
00173 !
00174 !HRUNOFF = DT92 ZFSAT calculation
00175 ZWG2_AVG(:)   = 0.0
00176 ZWGI2_AVG(:)  = 0.0
00177 ZWSAT_AVG(:)  = 0.0
00178 ZWWILT_AVG(:) = 0.0
00179 !
00180 !HHORT=SGH
00181 ZHORT_R(:) = 0.0
00182 ZHORT_M(:) = 0.0
00183 !
00184 !PIFLOOD calculation
00185 ZSOILMAX(:) = 0.0
00186 ZIF_MAX(:)  = 0.0
00187 !
00188 !HRUNOFF = DT92 DUNNE calculation
00189 ZPG_WORK(:)   = 0.0
00190 ZRUISDT(:)    = 0.0
00191 !
00192 !HRUNOFF = TOPD DUNNE calculation
00193 ZRUNOFF_TOPD(:) = 0.0
00194 !
00195 !to limit numerical artifacts
00196 ZPG_INI(:) = PPG(:) + PPG_MELT(:)
00197 !
00198 !
00199 INI=SIZE(PD_G,1)
00200 INL=MAXVAL(KWG_LAYER(:))
00201 !
00202 !-------------------------------------------------------------------------------
00203 !
00204 !*           1. Surface saturated fraction
00205 !            -----------------------------
00206 !
00207 IF( HRUNOFF=='DT92' .OR. HRUNOFF == 'TOPD' )THEN
00208 !
00209 ! Calculate the layer average water content for the sub-grid
00210 ! surface runoff computation: use PRUNOFFD as the depth over which
00211 ! runoff is calculated.
00212 !
00213 ! First, determine a weight for each layer's contribution
00214 ! to thickness averaged water content and soil properties for runoff.
00215 !
00216    IF (HISBA == 'DIF') THEN
00217 !
00218 ! Vertically averaged soil properties and moisture for surface runoff computation:
00219 !
00220       DO JL=1,KLAYER_DUN
00221          DO JJ=1,INI
00222             IDEPTH=KWG_LAYER(JJ)
00223             IF(JL<=IDEPTH)THEN
00224               ZWG2_AVG  (JJ) = ZWG2_AVG  (JJ) + PSOILWGHT(JJ,JL)*PWG   (JJ,JL)/MAX(1.E-6,PRUNOFFD(JJ))
00225               ZWGI2_AVG (JJ) = ZWGI2_AVG (JJ) + PSOILWGHT(JJ,JL)*PWGI  (JJ,JL)/MAX(1.E-6,PRUNOFFD(JJ))
00226               ZWSAT_AVG (JJ) = ZWSAT_AVG (JJ) + PSOILWGHT(JJ,JL)*PWSAT (JJ,JL)/MAX(1.E-6,PRUNOFFD(JJ))
00227               ZWWILT_AVG(JJ) = ZWWILT_AVG(JJ) + PSOILWGHT(JJ,JL)*PWWILT(JJ,JL)/MAX(1.E-6,PRUNOFFD(JJ))
00228             ENDIF
00229          ENDDO
00230       ENDDO
00231 !
00232    ELSE
00233 !           
00234       ZWG2_AVG(:)   = PWG(:, 2)
00235       ZWGI2_AVG(:)  = PWGI(:,2)
00236       ZWSAT_AVG(:)  = PWSAT(:,1)
00237       ZWWILT_AVG(:) = PWWILT(:,1)
00238 !      
00239    ENDIF
00240 !
00241    IF(HHORT=='SGH')THEN
00242      !runoff over frozen soil explicitly calculated
00243      ZWGI2_AVG(:)=0.0
00244    ENDIF
00245 !
00246    DO JJ=1,INI
00247       ZS=MIN(1.0,(ZWG2_AVG(JJ)+ZWGI2_AVG(JJ)-ZWWILT_AVG(JJ))/(ZWSAT_AVG(JJ)-ZWWILT_AVG(JJ)))
00248       PFSAT(JJ) = 1.0-(1.0-MAX(0.0,ZS))**(PRUNOFFB(JJ)/(PRUNOFFB(JJ)+1.))
00249    ENDDO        
00250 !
00251 ENDIF
00252 !
00253 !*           2. Horton runoff
00254 !            ----------------
00255 !
00256 IF(HHORT=='SGH'.OR.OFLOOD)THEN  
00257 !
00258   IF(HISBA == 'DIF')THEN
00259 !
00260     ZDEPTH(:) = 0.0
00261 !    
00262     DO JL=1,KLAYER_HORT
00263       DO JJ=1,INI   
00264 !                     
00265       IF(ZDEPTH(JJ)<XHORT_DEPTH)THEN
00266 !              
00267 !       Modify soil porosity as ice assumed to become part
00268 !       of solid soil matrix (with respect to liquid flow):                
00269         ZWSAT(JJ,JL) = MAX(XWGMIN, PWSAT(JJ,JL)-PWGI(JJ,JL)) 
00270 !         
00271 !       Subgrid frozen soil fraction of the grid cells
00272         ZFROZEN(JJ)=ZFROZEN(JJ)+(PWGI(JJ,JL)/PWSAT(JJ,JL))*PDZG(JJ,JL)    
00273 !        
00274 !       Impedance Factor from (Johnsson and Lundin 1991).
00275         ZFRZ = EXP(ZLOG10*(-ZEICE*(PWGI(JJ,JL)/(PWGI(JJ,JL)+PWG(JJ,JL)))))       
00276 !  
00277 !       Calculate infiltration MAX on frozen soil as Johnsson and Lundin (1991).
00278 !       The max infiltration is equal to the unsaturated conductivity function at a
00279 !       water content corresponding to the total porosity less the ice-filled volume.
00280 !       The unsaturated conductivity function is computed using LOG/EXP transformation
00281 !
00282         ZS           = MIN(1.,ZWSAT(JJ,JL)/PWSAT(JJ,JL))
00283 !       Matric potential psi=mpotsat*(w/wsat)**(-bcoef) (m)
00284         ZLOG         = PBCOEF(JJ,JL)*LOG(ZS)
00285 !       Hydraulic conductivity k=frz*condsat*(psi/mpotsat)**(-2-3/bcoef) (m s-1)
00286         ZLOG         = -(2.0+3.0/PBCOEF(JJ,JL))*ZLOG
00287         ZIMAX_ICE(JJ)= ZIMAX_ICE(JJ)+PDZG(JJ,JL)*ZFRZ*PCONDSAT(JJ,JL)*EXP(-ZLOG)
00288 !       
00289         ZDEPTH(JJ) = PD_G(JJ,JL)
00290 !
00291       ENDIF
00292 !
00293       ENDDO
00294     ENDDO    
00295 !
00296     ZFROZEN  (:)=ZFROZEN  (:)/ZDEPTH(:)
00297     ZIMAX_ICE(:)=ZIMAX_ICE(:)/ZDEPTH(:)
00298 !
00299 !   Calculate infiltration MAX using green-ampt approximation (derived form)
00300 !
00301     ZNOFRZ(:,:)=1.0
00302 !  
00303     ZIMAX(:) = INFMAX_FUNC(PWG,ZWSAT,ZNOFRZ,PCONDSAT,PMPOTSAT,PBCOEF,PDZG,PD_G,KLAYER_HORT)
00304 !  
00305   ELSE
00306 !
00307     DO JJ=1,INI
00308 !
00309 !     Effective frozen depth penetration 
00310 !
00311       ZEFFICE=PD_G(JJ,2)*PWGI(JJ,2)/(PWGI(JJ,2)+PWG(JJ,2))
00312 !
00313 !     Modify soil porosity as ice assumed to become part
00314 !     of solid soil matrix (with respect to liquid flow):
00315 !
00316       ZWSAT(JJ,1) = MAX(XWGMIN, PWSAT(JJ,1)-PWGI(JJ,2)) 
00317 !
00318 !     calculate the subgrid frozen soil fraction of the grid cells
00319 !
00320       ZFROZEN (JJ) = MIN(1.,ZEFFICE/MAX(PD_ICE(JJ),PTDIURN(JJ)))
00321 !
00322 !     Impedance Factor from (Johnsson and Lundin 1991).
00323 !
00324       ZFRZ = EXP(ZLOG10*(-ZEICE*MIN(1.,ZEFFICE/PTDIURN(JJ))))
00325 !
00326 !     Calculate infiltration MAX on frozen soil as Johnsson and Lundin (1991).
00327 !     The max infiltration is equal to the unsaturated conductivity function at a
00328 !     water content corresponding to the total porosity less the ice-filled volume.
00329 !
00330       ZS =MIN(1.,ZWSAT(JJ,1)/PWSAT(JJ,1))
00331       ZIMAX_ICE(JJ)=ZFRZ*PKSAT_ICE(JJ)*(ZS**(2*PBCOEF(JJ,1)+3.))
00332 !
00333 !     Calculate infiltration MAX on unfrozen soil using green-ampt approximation
00334 !    
00335       ZS   =MIN(1.,PWG(JJ,2)/ZWSAT(JJ,1))
00336       ZD_H =MIN(0.10,PD_G(JJ,2))
00337       ZIMAX(JJ)=PCONDSAT(JJ,1)*(PBCOEF(JJ,1)*PMPOTSAT(JJ,1)*(ZS-1.0)/ZD_H+1.0)
00338 !
00339     ENDDO
00340 !
00341   ENDIF
00342 !
00343 ENDIF
00344 !
00345 IF(HHORT=='SGH')THEN
00346 !
00347 ! calculate the Horton runoff generated by the rainfall rate
00348 !
00349   IF(HRAIN=='SGH')THEN
00350 !
00351     WHERE(PPG(:)>0.)
00352        ZHORT_R(:) = (1.- ZFROZEN(:))* PPG(:)/((ZIMAX    (:)*XRHOLW*PMUF(:)/PPG(:)) + 1.) & !unfrozen soil
00353                   +      ZFROZEN(:) * PPG(:)/((ZIMAX_ICE(:)*XRHOLW*PMUF(:)/PPG(:)) + 1.)   !frozen soil
00354     END WHERE        
00355 !
00356   ELSE
00357 !
00358     ZHORT_R(:) = (1.- ZFROZEN(:))* MAX(0.,PPG(:)-ZIMAX    (:)*XRHOLW)          & !unfrozen soil
00359                +      ZFROZEN(:) * MAX(0.,PPG(:)-ZIMAX_ICE(:)*XRHOLW)            !frozen soil
00360 !
00361   ENDIF
00362 !
00363 ! calculate the Horton runoff generated by the snow melt
00364 !        
00365   ZHORT_M(:) = (1.- ZFROZEN(:))* MAX(0.,PPG_MELT(:)-ZIMAX    (:)*XRHOLW)          & !unfrozen soil
00366              +      ZFROZEN(:) * MAX(0.,PPG_MELT(:)-ZIMAX_ICE(:)*XRHOLW)            !frozen soil
00367 !
00368 ! calculate the  total Horton runoff 
00369 !
00370   WHERE(PFFLOOD(:)<=PFSAT(:))
00371         PHORTON(:) = (1. -   PFSAT(:)) * (ZHORT_R(:) + ZHORT_M(:))
00372   ELSEWHERE
00373         PHORTON(:) = (1. - PFFLOOD(:)) * (ZHORT_R(:) + ZHORT_M(:))
00374   ENDWHERE
00375 !
00376 ELSE
00377 !
00378   PHORTON(:) = 0.0
00379 !
00380 ENDIF
00381 !
00382 ! calculate all water reaching the ground
00383 !
00384 PPG  (:) = PPG(:) + PPG_MELT(:)        
00385 !
00386 !
00387 !*           3. Dunne runoff and flood interception
00388 !            --------------------------------------
00389 !
00390 ! Interception by the flooplains
00391 !
00392 IF(OFLOOD)THEN
00393   PPFLOOD(:)=PFFLOOD(:)*MAX(0.0,PPG(:))
00394 ELSE
00395   PPFLOOD(:)=0.0
00396 ENDIF
00397 !
00398 IF(HRUNOFF=='SGH ')THEN
00399 !        
00400 ! calculate the Dunne runoff with TOPMODEL
00401 !
00402   PDUNNE(:) = MAX(PPG(:),0.0) * MAX(PFSAT(:)-PFFLOOD(:),0.0)
00403 !
00404 ELSEIF (HRUNOFF=='DT92' .OR. HRUNOFF=='TOPD')THEN
00405 !
00406 !*       Dumenil et Todini (1992)  RUNOFF SCHEME
00407 !        ---------------------------------------         
00408 !
00409 ! surface runoff done only on the Fsat-Fflood fraction
00410 !
00411   ZPG_WORK(:) = PPG(:) - PHORTON(:) - PPFLOOD(:)
00412 !
00413   IF ( LCOUPL_TOPD.AND.HRUNOFF == 'TOPD' )THEN
00414     !
00415     WHERE ( XATOP(:)/=0. .AND. XAS_NATURE(:)/=XUNDEF )
00416       ZRUNOFF_TOPD(:) = MAX(PPG(:),0.0) * MAX(XAS_NATURE(:),0.0)
00417     ENDWHERE
00418     !
00419   ENDIF
00420   !
00421   CALL HYDRO_DT92(PTSTEP,                                &
00422                   PRUNOFFB, ZWWILT_AVG,                  &
00423                   PRUNOFFD, ZWSAT_AVG,                   &
00424                   ZWG2_AVG, ZWGI2_AVG,                   &
00425                   ZPG_WORK, ZRUISDT                      )
00426 !
00427   PDUNNE(:) = ZRUISDT(:)*PRUNOFFD(:)*XRHOLW/PTSTEP
00428   !
00429   IF (LCOUPL_TOPD.AND.HRUNOFF == 'TOPD') THEN
00430     PDUNNE(:) = ZRUNOFF_TOPD(:) +  PDUNNE(:)*(1-XATOP(:))
00431   ENDIF
00432   !
00433   IF(OFLOOD)THEN
00434     WHERE(PFFLOOD(:)>=PFSAT(:).AND.PFFLOOD(:)>0.0)PDUNNE(:) = 0.0
00435   ENDIF   
00436   !
00437 ELSE
00438 ! 
00439 ! Default case (no subgrid runoff)
00440 !
00441   PFSAT (:) = 0.0
00442   PDUNNE(:) = 0.0
00443 !
00444 ENDIF
00445 !
00446 ! calculate the infiltration rate after runoff
00447 !
00448 PPG  (:) = PPG(:) - PDUNNE(:) - PHORTON(:) - PPFLOOD(:)
00449 !
00450 ! Supress numerical artifacts:
00451 !
00452 WHERE (ZPG_INI(:)<0.0)
00453        PPG(:)     = ZPG_INI(:)
00454        PHORTON(:) = 0.0
00455        PDUNNE (:) = 0.0
00456        PPFLOOD(:) = 0.0
00457 ENDWHERE
00458 !
00459 !*           4. infiltration rate from floodplains (à revoir pour DF !!!)
00460 !            -------------------------------------
00461 !
00462 IF(OFLOOD)THEN
00463 !
00464 ! calculate the maximum flood infiltration
00465 !
00466   ZIF_MAX(:) = MAX(0.,(1.- ZFROZEN(:))) * ZIMAX(:)*XRHOLW &   !unfrozen soil
00467              +      ZFROZEN(:) * ZIMAX_ICE(:)*XRHOLW     !frozen soil
00468 !
00469   PIFLOOD(:)=MAX(0.0,(PFFLOOD(:)-PFSAT(:)))*MIN(PPIFLOOD(:),ZIF_MAX(:))
00470 !
00471   IF(HISBA == 'DIF')THEN
00472     ZDEPTH(:)=0.0
00473     DO JL=1,KLAYER_HORT
00474        DO JJ=1,INI
00475           IF(ZDEPTH(JJ)<XHORT_DEPTH)THEN
00476             ZSOILMAX(JJ) = ZSOILMAX(JJ)+MAX(0.0,ZWSAT(JJ,JL)-PWG(JJ,JL))*PDZG(JJ,JL)*XRHOLW/PTSTEP
00477             ZDEPTH  (JJ) = PD_G(JJ,JL)
00478           ENDIF
00479        ENDDO
00480     ENDDO
00481   ELSE
00482     DO JJ=1,INI
00483        ZWSAT(JJ,1)  = MAX(XWGMIN, PWSAT(JJ,1)-PWGI(JJ,2)) 
00484        ZSOILMAX(JJ) = MAX(0.0,ZWSAT(JJ,1)-PWG(JJ,2))*PD_G(JJ,2)*XRHOLW/PTSTEP
00485     ENDDO
00486   ENDIF
00487 !
00488   PIFLOOD(:)=MIN(PIFLOOD(:),ZSOILMAX(:))
00489 !
00490 ELSE
00491 !
00492   PIFLOOD(:)=0.0
00493 !
00494 ENDIF
00495 !
00496 !calculate the infiltration rate
00497 !
00498 PPG  (:) = PPG(:) + PIFLOOD(:)
00499 !
00500 !-------------------------------------------------------------------------------
00501 !
00502 IF (LHOOK) CALL DR_HOOK('HYDRO_SGH',1,ZHOOK_HANDLE)
00503 !
00504 END SUBROUTINE HYDRO_SGH