SUBROUTINE InitReservoirs &
!
(filename_ini,tbegin, mask, list)
IMPLICIT NONE
!arguments with intent in:
CHARACTER ( LEN = * ), INTENT(IN) :: filename_ini
TYPE (DateTime), INTENT(IN) :: tbegin
TYPE (grid_integer), INTENT(IN) :: mask
!arguments with intent out:
TYPE(Reservoir),POINTER,INTENT(out) :: list !list of reservoirs
!local declarations
CHARACTER(LEN=1000) :: filename
LOGICAL :: hotstart
TYPE(reservoir),POINTER :: currentReservoir !points to current reservoir
INTEGER(KIND = short) :: id_res !reservoir id
INTEGER(KIND = short) :: k, i, j
TYPE(IniList) :: iniDB
INTEGER(KIND = short) :: fileunit_geometry
INTEGER(KIND = short) :: fileunit_weir
CHARACTER (LEN = 300) :: string
LOGICAL :: error
INTEGER(KIND = short) :: err_io
INTEGER(KIND = short), ALLOCATABLE :: doy (:)
INTEGER (KIND = short) :: nDOY
INTEGER (KIND = short) :: shortInt
LOGICAL :: isString
!-------------------------------end of declaration-----------------------------
CALL Catch ('info', 'Reservoirs', 'Initializing reservoirs ')
!--------------------------------------------
! open and read configuration file
!--------------------------------------------
CALL IniOpen (filename_ini, iniDB)
!--------------------------------------------
! hot / cold start
!--------------------------------------------
IF ( KeyIsPresent ('path-hotstart', iniDB ) ) THEN
hotstart = .TRUE.
ELSE
hotstart = .FALSE.
END IF
!--------------------------------------------
! allocate variables
!--------------------------------------------
nReservoirs = IniReadInt ('nreservoirs', iniDB)
nReservoirsWithDiversion = 0
!prepare list of reservoirs
NULLIFY (list)
DO k = 1, nReservoirs
IF (.NOT. ASSOCIATED (list) ) THEN
ALLOCATE (list)
currentReservoir => list
ELSE
ALLOCATE (currentReservoir % next)
currentReservoir => currentReservoir % next
END IF
!id
currentReservoir % id = IniReadInt ('id', iniDB, section = ToString(k))
!reservoir type: on-stream, off-stream
currentReservoir % typ = &
IniReadString ('type', iniDB, section = ToString(k))
!name
currentReservoir % name = &
IniReadString ('name', iniDB, section = ToString(k))
!coordinate
currentReservoir % xyz % easting = &
IniReadReal ('easting', iniDB, section = ToString(k))
currentReservoir % xyz % northing = &
IniReadReal ('northing', iniDB, section = ToString(k))
currentReservoir % xyz % system = DecodeEpsg (IniReadInt ('epsg', iniDB))
!local coordinate
CALL GetIJ ( X = currentReservoir % xyz % easting, &
Y = currentReservoir % xyz % northing, &
grid = mask, i = currentReservoir % r, &
j = currentReservoir % c )
!runge-kutta order
currentReservoir % rk = IniReadInt ('rk', iniDB, section = ToString(k))
!initial stage
IF (.NOT. hotstart) THEN
currentReservoir % stage = &
IniReadReal ('stage', iniDB, section = ToString(k))
END IF
SELECT CASE ( currentReservoir % typ )
CASE ( 'on' ) !on-stream detention basin
!target stage
currentReservoir % eFlow = 0.
IF (KeyIsPresent ('stage-target-file', iniDB, section = ToString(k) ) ) THEN
string = IniReadString ('stage-target-file', iniDB, section = ToString(k))
currentReservoir % unit = GetUnit ()
OPEN ( unit=currentReservoir % unit , file=string)
currentReservoir % typOut = 2
currentReservoir % tReadNewStage = tbegin
CALL ReadMetadata (currentReservoir % unit, currentReservoir % network )
!environmental flow
string = IniReadString ('e-flow', iniDB, section = ToString(k))
currentReservoir % eFlow = SetDailyArray (string)
ELSE
currentReservoir % typOut = 1
END IF
!discharge downstream file
IF (KeyIsPresent ('discharge-downstream-file', iniDB, &
section = ToString(k) ) ) THEN
string = IniReadString ('discharge-downstream-file', iniDB, &
section = ToString(k))
currentReservoir % unitDischargeDownstream = GetUnit ()
OPEN ( unit = currentReservoir % unitDischargeDownstream , &
file = string)
currentReservoir % tReadNewDischargeDownstream = tbegin
CALL ReadMetadata (currentReservoir % unitDischargeDownstream, &
currentReservoir % networkDischargeDownstream )
currentReservoir % dischargeDownstream = .TRUE.
ELSE
currentReservoir % dischargeDownstream = .FALSE.
END IF
!discharge diverted file
IF (KeyIsPresent ('discharge-diverted-file', iniDB, &
section = ToString(k) ) ) THEN
string = IniReadString ('discharge-diverted-file', iniDB, &
section = ToString(k))
currentReservoir % unitDischargeDiverted = GetUnit ()
OPEN ( unit = currentReservoir % unitDischargeDiverted , &
file = string)
currentReservoir % tReadNewDischargeDiverted = tbegin
CALL ReadMetadata (currentReservoir % unitDischargeDiverted, &
currentReservoir % networkDischargeDiverted )
currentReservoir % dischargeDiverted = .TRUE.
ELSE
currentReservoir % dischargeDiverted = .FALSE.
END IF
!free flow
IF ( KeyIsPresent (key = 'free-flow', iniDB = iniDB, &
section = ToString(k) ) ) THEN
currentReservoir % freeFlow = IniReadReal ('free-flow', iniDB, &
section = ToString(k) )
ELSE
currentReservoir % freeFlow = 0.
END IF
!free flow elevation
IF ( KeyIsPresent (key = 'free-flow-elevation', iniDB = iniDB, &
section = ToString(k) ) ) THEN
currentReservoir % freeFlowElevation = &
IniReadReal ('free-flow-elevation', iniDB, &
section = ToString(k) )
ELSE
currentReservoir % freeFlowElevation = 0.
END IF
!geometry
CALL ReadGeometry (iniDB, k, currentReservoir )
!manage high level options
IF ( SubSectionIsPresent ('manage-high-level',ToString(k), iniDB ) ) THEN
currentReservoir % highLevel = .TRUE.
!read full reservoir level
currentReservoir % fullReservoirLevel = &
IniReadReal ( 'full-reservoir-level', iniDB, ToString(k), &
'manage-high-level')
!read how to compute qout
string = IniReadString ('qout', iniDB, ToString(k), &
'manage-high-level')
SELECT CASE ( StringToUpper(string) )
CASE ('QIN')
currentReservoir % qoutRule = QIN
END SELECT
currentReservoir % rising = &
IniReadInt ( 'rising', iniDB, ToString(k), 'manage-high-level')
ELSE
currentReservoir % highLevel = .FALSE.
END IF
CASE ( 'off' ) !off-stream detention basin
!maximum stage
currentReservoir % stageMax = StringToFloat (string, error)
currentReservoir % typOut = 1
!geometry
string = IniReadString ('geometry', iniDB, section = ToString(k))
CALL TableNew (string, currentReservoir % geometry)
!weir
string = IniReadString ('weir', iniDB, section = ToString(k))
CALL TableNew (string, currentReservoir % weir)
!read x and y coordinate where outflow from reservoir is discharged
currentReservoir % xout = &
IniReadReal ('xout', iniDB, section = ToString(k))
currentReservoir % yout = &
IniReadReal ('yout', iniDB, section = ToString(k))
CALL GetIJ ( X = currentReservoir % xout, &
Y = currentReservoir % yout, &
grid = mask, i = currentReservoir % rout, &
j = currentReservoir % cout )
CASE DEFAULT
CALL Catch ('error', 'Reservoirs', &
'unknown reservoir type: ', argument = currentReservoir % typ )
END SELECT
!diversion channel (optional)
IF ( SubSectionIsPresent ('diversion',ToString(k), iniDB ) ) THEN
currentReservoir % bypassIsPresent = .TRUE.
nReservoirsWithDiversion = nReservoirsWithDiversion + 1
!read x and y coordinate where outflow from reservoir is discharged
currentReservoir % bypass % xout = &
IniReadReal ('xout', iniDB, section = ToString(k), &
subsection = 'diversion')
currentReservoir % bypass % yout = &
IniReadReal ('yout', iniDB, section = ToString(k), &
subsection = 'diversion')
!local coordinate in raster reference system
CALL GetIJ ( X = currentReservoir % bypass % xout, &
Y = currentReservoir % bypass % yout, &
grid = mask, i = currentReservoir % bypass % rout, &
j = currentReservoir % bypass % cout )
!read weir data
CALL ReadWeir (iniDB, k, currentReservoir % bypass )
!channel lenght
currentReservoir % bypass % channelLenght = &
IniReadReal ('channel-lenght', iniDB, section = ToString(k), &
subsection = 'diversion' )
!channel slope
currentReservoir % bypass % channelSlope = &
IniReadReal ('channel-slope', iniDB, section = ToString(k), &
subsection = 'diversion' )
!channel roughness coefficient
currentReservoir % bypass % channelManning = &
IniReadReal ('channel-manning', iniDB, section = ToString(k), &
subsection = 'diversion' )
!channel section bottom width
currentReservoir % bypass % channelWidth = &
IniReadReal ('section-bottom-width', iniDB, section = ToString(k), &
subsection = 'diversion' )
!channel section bank slope
currentReservoir % bypass % channelBankSlope = &
IniReadReal ('section-bank-slope', iniDB, section = ToString(k), &
subsection = 'diversion' )
!environmental flow
IF ( KeyIsPresent ('e-flow', iniDB, section = ToString(k), &
subsection = 'diversion' ) ) THEN
string = IniReadString ('e-flow', iniDB, section = ToString(k), &
subsection = 'diversion' )
currentReservoir % bypass % eFlow = SetDailyArray (string)
ELSE !e-flow = 0.
currentReservoir % bypass % eFlow = 0.
END IF
ELSE
currentReservoir % bypassIsPresent = .FALSE.
END IF
NULLIFY (currentReservoir % next)
END DO
IF (hotstart) THEN
string = IniReadString ('path-hotstart', iniDB)
CALL ReservoirReadStatus (string)
END IF
!--------------------------------------------
! close configuration file
!--------------------------------------------
CALL IniClose (iniDb)
RETURN
END SUBROUTINE InitReservoirs