InitSoilBalance Subroutine

public subroutine InitSoilBalance(inifile, flowDirection, time)

Initialize soil water balance

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile

stores configuration information

type(grid_integer), intent(in) :: flowDirection

flow direction map

type(DateTime), intent(in) :: time

start time


Variables

Type Visibility Attributes Name Initial
character(len=1000), public :: filename
integer(kind=short), public :: i
integer(kind=short), public :: iin
type(IniList), public :: iniDB
integer(kind=short), public :: is
integer(kind=short), public :: j
integer(kind=short), public :: jin
integer(kind=short), public :: js
integer(kind=short), public :: k
real(kind=float), public :: scalar

Source Code

SUBROUTINE InitSoilBalance   & 
  !
  (inifile, flowDirection, time)       

IMPLICIT NONE

!Arguments with intent(in):
CHARACTER (LEN = *), INTENT(IN) :: inifile !!stores configuration information
TYPE (grid_integer), INTENT(IN) :: flowDirection !!flow direction map 
TYPE (DateTime),     INTENT(IN) :: time !!start time

!local declarations:
TYPE (IniList) :: iniDB
CHARACTER (LEN = 1000) :: filename
INTEGER (KIND = short) :: k, i, j, iin, jin, is, js
REAL (KIND = float) :: scalar

!------------end of declaration------------------------------------------------ 

!open and read configuration file
CALL IniOpen (inifile, iniDB)

!read balance id
IF (SectionIsPresent('balance-id', iniDB)) THEN
  CALL GridByIni (iniDB, balanceId, section = 'balance-id')
ELSE !grid is mandatory: stop the program if not present
   CALL Catch ('error', 'SoilBalance',   &
			   'error in loading balance-id: ' ,  &
			    argument = 'section not defined in ini file' )
END IF

!read subsurface soil hydraulic conductivity
IF (SectionIsPresent('ksat-subsurface', iniDB)) THEN
    IF (KeyIsPresent ('scalar', iniDB, 'ksat-subsurface') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'ksat-subsurface')
        CALL NewGrid (ksat_sub, mask, scalar)
    ELSE
        CALL GridByIni (iniDB, ksat_sub, section = 'ksat-subsurface')
    END IF
ELSE !grid is mandatory: stop the program if not present
   CALL Catch ('error', 'SoilBalance',   &
			   'error in loading subsurface conductivity: ' ,  &
			    argument = 'section not defined in ini file' )
END IF

!read soil depth (m)
IF (SectionIsPresent('soil-depth', iniDB)) THEN
    IF (KeyIsPresent ('scalar', iniDB, 'soil-depth') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'soil-depth')
        CALL NewGrid (soilDepth, mask, scalar)
    ELSE
        CALL GridByIni (iniDB, soilDepth, section = 'soil-depth')
    END IF
ELSE !grid is mandatory: stop the program if not present
   CALL Catch ('error', 'SoilBalance',   &
			   'error in loading soil depth: ' ,  &
			    argument = 'section not defined in ini file' )
END IF



!read deep percolation factor (-)
IF (SectionIsPresent('deep-percolation-factor', iniDB)) THEN
    IF (KeyIsPresent ('scalar', iniDB, 'deep-percolation-factor') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'deep-percolation-factor')
        CALL NewGrid (percolationFactor, mask, scalar)
    ELSE
        CALL GridByIni (iniDB, percolationFactor, section = 'deep-percolation-factor')
    END IF
ELSE !grid is optional: default = 1.
   CALL NewGrid (percolationFactor, mask, 1.0)
END IF



!read root zone depth (m)
IF (SectionIsPresent('root-zone-depth', iniDB)) THEN
    IF (KeyIsPresent ('scalar', iniDB, 'root-zone-depth') ) THEN
        scalar = IniReadReal ('scalar', iniDB, 'root-zone-depth')
        CALL NewGrid (soilDepthRZ, mask, scalar)
    ELSE
        CALL GridByIni (iniDB, soilDepthRZ, section = 'root-zone-depth')
    END IF
ELSE !grid is mandatory: stop the program if not present
   CALL Catch ('error', 'SoilBalance',   &
			   'error in loading root zone depth: ' ,  &
			    argument = 'section not defined in ini file' )
END IF


!compute transmission zone depth
CALL NewGrid ( soilDepthTZ, mask, 0.)

DO i = 1, mask % idim
    DO j = 1, mask % jdim
        IF ( mask % mat (i,j) /= mask % nodata ) THEN
            soilDepthTZ % mat(i,j) = soilDepth % mat(i,j) -  &
                                     soilDepthRZ % mat(i,j)
            IF ( soilDepthTZ % mat(i,j) <= 0. ) THEN
                soilDepthTZ % mat(i,j) = 0.1
            END IF
        END IF
    END DO
END DO

    
!configure evapotranspiration
IF (KeyIsPresent('evapotranspiration', iniDB)) THEN	
   filename = IniReadString ('evapotranspiration', iniDB)
   CALL ETinit (filename, time)
ELSE
    CALL Catch ('error', 'SoilBalance',   &
			      'evapotranspiration not found in configuration file' )
END IF


!threshold to initiate storm period, read and convert from mm/h to m/s
thresholdStartEvent = IniReadReal ('threshold-storm-start', iniDB)
thresholdStartEvent = thresholdStartEvent / 1000. / 3600.

!interstorm duration to terminate an event, read and convert from hours to seconds
interstorm = IniReadReal ('interstorm', iniDB)
interstorm = interstorm * 3600.
    

!configure infiltration
IF (KeyIsPresent('infiltration', iniDB)) THEN	
   filename = IniReadString ('infiltration', iniDB)
   CALL InfiltrationInit (filename, soilMoisture, soilDepth )
ELSE
    CALL Catch ('error', 'SoilBalance',   &
			      'infiltration not found in configuration file' )
END IF

  
!set initial condition
CALL SetInitialCondition (iniDB)

  
!set wetland
CALL SetWetland (iniDB, inifile)
  
!allocate coomon variables used to solve soil water and energy balance
!vertical fluxes
CALL NewGrid (rainBalance, mask, 0.)
CALL NewGrid (infilt, mask, 0.)
CALL NewGrid (runoff, mask, 0.)
CALL NewGrid (et, mask, 0.)
CALL NewGrid (percolation, mask, 0.)
CALL NewGrid (capRise, mask, 0.)
          
!energy balance
CALL NewGrid (Ts, mask, 0.)
CALL NewGrid (Rnetta, mask, 0.)
CALL NewGrid (Xle, mask, 0.)
CALL NewGrid (Hse, mask, 0.)
CALL NewGrid (Ge, mask, 0.) 
CALL NewGrid (Ta_prec, mask, 0.) 
CALL NewGrid (Ts_prec, mask, 0.) 

!lateral fluxes at time t
CALL NewGrid (QinSoilSub, mask, 0.)
CALL NewGrid (QoutSoilSub, mask, 0.)

!balance error
CALL NewGrid (balanceError, mask, 0.)

!soil mositure variation
CALL NewGrid (deltaSoilMoisture, mask, 0.)


!  Configuration terminated. Deallocate ini database
CALL IniClose (iniDB)  
  
RETURN
END SUBROUTINE InitSoilBalance