GroundwaterPointInit Subroutine

public subroutine GroundwaterPointInit(pointfile, path_out, time)

Initialize export of point site data

Arguments

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

file containing coordinate of points

character(len=*), intent(in) :: path_out

path of output folder

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

start time


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: err_io
integer(kind=short), public :: fileunit
integer(kind=short), public :: k

Source Code

SUBROUTINE GroundwaterPointInit &
!
( pointfile, path_out, time )

IMPLICIT NONE

!Arguments with intent (in):
CHARACTER (LEN = *), INTENT(IN) :: pointfile  !!file containing coordinate of points
CHARACTER (LEN = *), INTENT(IN) :: path_out  !!path of output folder
TYPE (DateTime),     INTENT(IN) :: time  !!start time

!local declarations
INTEGER (KIND = short) :: err_io
INTEGER (KIND = short) :: fileunit
INTEGER (KIND = short) :: k

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

timePointExport = time

fileunit = GetUnit ()
OPEN ( unit = fileunit, file = pointfile(1:LEN_TRIM(pointfile)), &
      status='OLD', iostat = err_io )

IF ( err_io /= 0 ) THEN
	!file does not exist
    CALL Catch ('error', 'Groundwater', 'out point file does not exist')
END IF 

!Read metadata
CALL ReadMetadata (fileunit, sites)

!check dt
IF (.NOT. ( MOD ( sites % timeIncrement, dtGroundwater ) == 0 ) ) THEN
  CALL Catch ('error', 'Groundwater', 'dt out sites must be multiple of dtGroundwater ')
END IF

CLOSE ( fileunit )

sites % description = 'groundwater head data exported from FEST'

sites % unit = 'm'

sites % offsetZ = 0.

!allocate file unit
ALLOCATE ( fileUnitPointGW ( basin % nAquifers ) )

!open and initialize files
DO k = 1, basin % nAquifers
    fileUnitPointGW (k) = GetUnit ()
    OPEN ( unit = fileUnitPointGW (k), &
    file = TRIM(path_out) // 'point_aquifer_' //  TRIM(ToString (k)) // '.fts' )
    
    CALL WriteMetadata ( network = sites, fileunit = fileUnitPointGW (k) )

    CALL WriteData (sites, fileUnitPointGW (k), .TRUE.)  
    
END DO 

RETURN
END SUBROUTINE GroundwaterPointInit