Skip to content

Commit

Permalink
cleanup #1
Browse files Browse the repository at this point in the history
  • Loading branch information
mjreno authored and mjreno committed Aug 31, 2023
1 parent cb6ad7f commit 1e5a609
Show file tree
Hide file tree
Showing 10 changed files with 86 additions and 96 deletions.
11 changes: 8 additions & 3 deletions src/Utilities/Idm/BoundInputContext.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,9 @@
! -- Generic List Reader Module
!> @brief This module contains the BoundInputContextModule
!!
!! This module contains a type that stores and creates context
!! relevant to stress package inputs.
!!
!<
module BoundInputContextModule

use KindModule, only: DP, I4B, LGP
Expand All @@ -12,7 +17,7 @@ module BoundInputContextModule

!> @brief derived type for boundary package input context
!!
!! This derived type is input context used by dynamic package loaders.
!! This derived type defines input context used by dynamic package loaders.
!! Some variables (e.g. iprpak) in the type may have already been created
!! by a static loader whereas others (e.g. nboound) are created by this
!! type, updated by to dynamic loader, and accessed from the model package.
Expand Down Expand Up @@ -143,7 +148,7 @@ end subroutine create_context
!!
!! This routine should be invoked after the loader allocates dynamic
!! input params. This routine will assign pointers to arrays if they
!! have been allocoated or allocate the arrays if they have not been.
!! have been allocated and allocate the arrays if not.
!!
!<
subroutine enable(this)
Expand Down
2 changes: 1 addition & 1 deletion src/Utilities/Idm/IdmLoad.f90
Original file line number Diff line number Diff line change
Expand Up @@ -441,7 +441,7 @@ subroutine allocate_simnam_param(input_mempath, idt)
end if
case default
write (errmsg, '(a,a)') &
'Programming error. Idm Load unhandled datatype: ', &
'Programming error. IdmLoad unhandled datatype: ', &
trim(idt%datatype)
call store_error(errmsg)
call store_error_filename(simfile)
Expand Down
33 changes: 19 additions & 14 deletions src/Utilities/Idm/InputLoadType.f90
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ module InputLoadTypeModule
character(len=LENMODELNAME) :: modelname !< name of model
character(len=LINELENGTH) :: modelfname !< name of model input file
character(len=LINELENGTH) :: sourcename !< source name, e.g. name of file
integer(I4B) :: iperblock
contains
procedure :: init => static_init
procedure :: destroy => static_destroy
Expand Down Expand Up @@ -89,7 +90,6 @@ end function load_if
subroutine period_load_if(this)
import DynamicPkgLoadBaseType, I4B
class(DynamicPkgLoadBaseType), intent(inout) :: this
!integer(I4B), intent(in) :: iout
end subroutine
end interface

Expand Down Expand Up @@ -125,11 +125,22 @@ subroutine static_init(this, mf6_input, modelname, modelfname, source)
character(len=*), intent(in) :: modelname
character(len=*), intent(in) :: modelfname
character(len=*), intent(in) :: source
integer(I4B) :: iblock
!
this%mf6_input = mf6_input
this%modelname = modelname
this%modelfname = modelfname
this%sourcename = source
this%iperblock = 0
!
! -- identify period block definition
do iblock = 1, size(mf6_input%block_dfns)
!
if (mf6_input%block_dfns(iblock)%blockname == 'PERIOD') then
this%iperblock = iblock
exit
end if
end do
!
return
end subroutine static_init
Expand All @@ -146,34 +157,25 @@ end subroutine static_destroy
!! must be allocated when derived dynamic loader is initialized.
!!
!<
subroutine dynamic_init(this, mf6_input, modelname, modelfname, source, iout)
subroutine dynamic_init(this, mf6_input, modelname, modelfname, source, &
iperblock, iout)
use SimVariablesModule, only: errmsg
use SimModule, only: store_error, store_error_filename
class(DynamicPkgLoadType), intent(inout) :: this
type(ModflowInputType), intent(in) :: mf6_input
character(len=*), intent(in) :: modelname
character(len=*), intent(in) :: modelfname
character(len=*), intent(in) :: source
integer(I4B), intent(in) :: iperblock
integer(I4B), intent(in) :: iout
integer(I4B) :: iblock
!
this%mf6_input = mf6_input
this%modelname = modelname
this%modelfname = modelfname
this%sourcename = source
this%iperblock = 0
this%iperblock = iperblock
this%iout = iout
!
! -- identify period block definition
do iblock = 1, size(mf6_input%block_dfns)
!
if (mf6_input%block_dfns(iblock)%blockname == 'PERIOD') then
this%iperblock = iblock
this%readasarrays = .not. mf6_input%block_dfns(iblock)%aggregate
exit
end if
end do
!
! -- throw error and exit if not found
if (this%iperblock == 0) then
write (errmsg, '(a,a)') &
Expand All @@ -182,6 +184,9 @@ subroutine dynamic_init(this, mf6_input, modelname, modelfname, source, iout)
trim(mf6_input%subcomponent_name)
call store_error(errmsg)
call store_error_filename(this%sourcename)
else
!
this%readasarrays = (.not. mf6_input%block_dfns(iperblock)%aggregate)
end if
!
! -- return
Expand Down
2 changes: 1 addition & 1 deletion src/Utilities/Idm/SourceLoad.F90
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
!> @brief This module contains the SourceLoadModule
!!
!! This module contains the routines needed to generate
!! a loading object for an input source and routines
!! a loader object for an input source and routines
!! that distribute processing to a particular source.
!!
!<
Expand Down
7 changes: 7 additions & 0 deletions src/Utilities/Idm/mf6blockfile/AsciiInputLoadType.f90
Original file line number Diff line number Diff line change
@@ -1,3 +1,10 @@
!> @brief This module contains the AsciiInputLoadTypeModule
!!
!! This module defines an abstract type that support generic
!! IDP dynamic input loading for traditional MODFLOW 6 ascii
!! files.
!!
!<
module AsciiInputLoadTypeModule

use KindModule, only: DP, I4B, LGP
Expand Down
89 changes: 31 additions & 58 deletions src/Utilities/Idm/mf6blockfile/IdmMf6File.f90
Original file line number Diff line number Diff line change
Expand Up @@ -91,38 +91,6 @@ subroutine generic_mf6_load(parser, mf6_input, iout)

end subroutine generic_mf6_load

!> @brief allocate dynamic load parser if expecting dynamic input
!<
function create_dynamic_parser(mf6_input, mf6_parser, static_parser) &
result(created)
type(ModflowInputType), intent(in) :: mf6_input
type(BlockParserType), pointer, intent(inout) :: mf6_parser
type(BlockParserType), allocatable, target, intent(inout) :: static_parser
logical(LGP) :: created
integer(I4B) :: iblock
!
! -- initialize
nullify (mf6_parser)
created = .false.
!
! -- check if package has dynamic input
do iblock = 1, size(mf6_input%block_dfns)
!
if (mf6_input%block_dfns(iblock)%blockname == 'PERIOD') then
!
! -- dynamic package, allocate parser
allocate (mf6_parser, source=static_parser)
created = .true.
!
exit
!
end if
end do
!
! -- return
return
end function

!> @brief input load for traditional mf6 simulation input file
!<
subroutine input_load(filename, mf6_input, component_filename, iout, &
Expand All @@ -135,10 +103,6 @@ subroutine input_load(filename, mf6_input, component_filename, iout, &
type(BlockParserType), allocatable, target :: parser !< block parser
type(PackageLoad) :: pkgloader
integer(I4B) :: inunit
logical(LGP) :: created
!
! -- initialize
created = .false.
!
! -- set parser based package loader by file type
select case (mf6_input%pkgtype)
Expand All @@ -163,17 +127,16 @@ subroutine input_load(filename, mf6_input, component_filename, iout, &
if (present(mf6_parser)) then
!
! -- create dynamic parser
created = create_dynamic_parser(mf6_input, mf6_parser, parser)
end if
!
! -- deallocate static load parser
if (allocated(parser)) then
!
if (.not. created) call parser%clear()
deallocate (parser)
allocate (mf6_parser, source=parser)
else
!
! -- clear parser file handles
call parser%clear()
end if
!
! -- cleanup
deallocate (parser)
!
! -- return
return
end subroutine input_load
Expand All @@ -197,35 +160,42 @@ function static_load(this, iout) result(period_loader)
class(Mf6FileStaticPkgLoadType), intent(inout) :: this
integer(I4B), intent(in) :: iout
class(DynamicPkgLoadBaseType), pointer :: period_loader
class(Mf6FileDynamicPkgLoadType), pointer :: mf6file_period_loader => null()
class(Mf6FileDynamicPkgLoadType), pointer :: mf6_loader => null()
type(BlockParserType), pointer :: parser => null()
!
! -- initialize
nullify (period_loader)
!
! -- load model package to input context
call input_load(this%sourcename, this%mf6_input, &
this%modelfname, iout, parser)
!
!
if (associated(parser)) then
if (this%iperblock > 0) then
!
! -- package is dynamic, allocate loader
allocate (mf6file_period_loader)
allocate (mf6_loader)
!
! -- load static input
call input_load(this%sourcename, this%mf6_input, &
this%modelfname, iout, parser)
!
! -- initialize dynamic loader
call mf6file_period_loader%init(this%mf6_input, this%modelname, &
this%modelfname, this%sourcename, &
iout)
call mf6_loader%init(this%mf6_input, this%modelname, &
this%modelfname, this%sourcename, &
this%iperblock, iout)
!
! -- set parser
call mf6file_period_loader%set(parser)
call mf6_loader%set(parser)
!
! -- set return pointer to base dynamic loader
period_loader => mf6file_period_loader
period_loader => mf6_loader
!
else
!
! -- load static input
call input_load(this%sourcename, this%mf6_input, &
this%modelfname, iout)
end if
!
! -- return
return
end function static_load

!> @brief static loader destroy
Expand All @@ -239,7 +209,8 @@ end subroutine static_destroy

!> @brief dynamic loader init
!<
subroutine dynamic_init(this, mf6_input, modelname, modelfname, source, iout)
subroutine dynamic_init(this, mf6_input, modelname, modelfname, source, &
iperblock, iout)
use InputDefinitionModule, only: InputParamDefinitionType
use DefinitionSelectModule, only: get_param_definition_type
use MemoryManagerModule, only: mem_allocate
Expand All @@ -248,10 +219,11 @@ subroutine dynamic_init(this, mf6_input, modelname, modelfname, source, iout)
character(len=*), intent(in) :: modelname
character(len=*), intent(in) :: modelfname
character(len=*), intent(in) :: source
integer(I4B), intent(in) :: iperblock
integer(I4B), intent(in) :: iout
!
call this%DynamicPkgLoadType%init(mf6_input, modelname, modelfname, &
source, iout)
source, iperblock, iout)
!
call mem_allocate(this%iper, 'IPER', this%mf6_input%mempath)
call mem_allocate(this%ionper, 'IONPER', this%mf6_input%mempath)
Expand Down Expand Up @@ -413,6 +385,7 @@ subroutine dynamic_create_loader(this)
this%modelname, &
this%modelfname, &
this%sourcename, &
this%iperblock, &
this%iout)
!
! -- return
Expand Down
16 changes: 9 additions & 7 deletions src/Utilities/Idm/mf6blockfile/StressGridInput.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
!> @brief This module contains the StressGridInputModule
!!
!! This module contains the routines for reading
!! period block array based input
!! This module contains the routines for reading period block
!! array based input.
!!
!<
module StressGridInputModule
Expand Down Expand Up @@ -63,23 +63,22 @@ module StressGridInputModule
contains

subroutine ingrid_init(this, mf6_input, modelname, modelfname, &
source, iout)
source, iperblock, iout)
use MemoryManagerModule, only: get_isize
class(StressGridInputType), intent(inout) :: this
type(ModflowInputType), intent(in) :: mf6_input
character(len=*), intent(in) :: modelname
character(len=*), intent(in) :: modelfname
character(len=*), intent(in) :: source
integer(I4B), intent(in) :: iperblock
integer(I4B), intent(in) :: iout
type(CharacterStringType), dimension(:), pointer, &
contiguous :: tas_fnames
character(len=LINELENGTH) :: fname
integer(I4B) :: tas6_size, n

!
call this%DynamicPkgLoadType%init(mf6_input, modelname, modelfname, &
source, iout)
!
source, iperblock, iout)
! -- initialize
this%tas_active = 0
this%nparam = 0
Expand All @@ -92,7 +91,7 @@ subroutine ingrid_init(this, mf6_input, modelname, modelfname, &
!
! -- determine if TAS6 files were provided in OPTIONS block
call get_isize('TAS6_FILENAME', this%mf6_input%mempath, tas6_size)

!
if (tas6_size > 0) then
!
this%tas_active = 1
Expand Down Expand Up @@ -190,8 +189,10 @@ subroutine ingrid_rp(this, parser)
! -- look for TAS keyword if tas is active
if (this%tas_active /= 0) then
call parser%GetStringCaps(keyword)
!
if (keyword == 'TIMEARRAYSERIES') then
call parser%GetStringCaps(tas_name)
!
if (param_tag == 'AUX') then
this%aux_tasnames(iaux) = tas_name
else
Expand All @@ -203,6 +204,7 @@ subroutine ingrid_rp(this, parser)
! -- cycle to next input param
cycle
end if
!
end if
!
! -- read and load the parameter
Expand Down
Loading

0 comments on commit 1e5a609

Please sign in to comment.