GroundwaterRiverInit Subroutine

private subroutine GroundwaterRiverInit(inifile)

Configure river-groundwater interaction

Arguments

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

configuration file


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: i
type(IniList), public :: iniDB
integer(kind=short), public :: j

Source Code

SUBROUTINE GroundwaterRiverInit &
!
( inifile )

IMPLICIT NONE

!Arguments with intent (in):
CHARACTER (LEN = *), INTENT(IN) :: inifile  !! configuration file

!local variables:
TYPE (IniList)         :: iniDB
INTEGER (KIND = short) :: i,j


!----------------------------end of declarations-------------------------------

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

!load river id
IF (SubSectionisPresent (subsection = 'river-id', &
                            section = 'river-groundwater', iniDB = iniDB) ) THEN
     CALL GridByIni ( ini = iniDB, &
                             grid = riverGroundwaterID, &
                             section = 'river-groundwater', &
                             subsection = 'river-id')
ELSE
     CALL Catch ('error', 'Groundwater',   &
                'missing river-id in configuration file' )
END IF

!load river dem
IF (SubSectionisPresent (subsection = 'river-dem', &
                            section = 'river-groundwater', iniDB = iniDB) ) THEN
     CALL GridByIni ( ini = iniDB, &
                             grid = riverDem, &
                             section = 'river-groundwater', &
                             subsection = 'river-dem')
ELSE
     CALL Catch ('error', 'Groundwater',   &
                'missing river-dem in configuration file' )
END IF

!exchange parameters
CALL TableNew ( file = inifile, tab = riverGroundwaterParameters, &
                id = 'river-groundwater')

!allocate exchange flux maps
CALL NewGrid ( riverToGroundwater, riverGroundwaterID, 0. )
CALL NewGrid ( groundwaterToRiver, riverGroundwaterID, 0. )

!allocate streambed parameter maps
CALL NewGrid ( streambedThickness, riverGroundwaterID, 0. )
CALL NewGrid ( streambedConductivity, riverGroundwaterID, 0. )

!populate streambed parameter maps
DO i = 1, riverGroundwaterID % idim
    DO j = 1, riverGroundwaterID % jdim
        IF ( riverGroundwaterID % mat (i,j) /= &
             riverGroundwaterID % nodata ) THEN
            
            CALL TableGetValue ( &
                valueIn =  REAL(riverGroundwaterID % mat (i,j)),&
                tab = riverGroundwaterParameters, &
                keyIn = 'id', keyOut ='streambed-conductivity', &
                match = 'exact', valueOut = streambedConductivity % mat (i,j) )
            
            CALL TableGetValue ( &
                valueIn =  REAL(riverGroundwaterID % mat (i,j)),&
                tab = riverGroundwaterParameters, &
                keyIn = 'id', keyOut ='streambed-thickness', &
                match = 'exact', valueOut = streambedThickness % mat (i,j) )
            
        END IF
    END DO
END DO


!free db
CALL IniClose ( iniDB )


RETURN
END SUBROUTINE GroundwaterRiverInit