MODFLOW 6  version 6.7.0.dev0
USGS Modular Hydrologic Model
Mf6FileGridInput.f90
Go to the documentation of this file.
1 !> @brief This module contains the Mf6FileGridInputModule
2 !!
3 !! This module contains the routines for reading period block
4 !! array based input.
5 !!
6 !<
8 
9  use kindmodule, only: i4b, dp, lgp
12  use simvariablesmodule, only: errmsg
23 
24  implicit none
25  private
26  public :: boundgridinputtype
27 
28  !> @brief Ascii grid based dynamic loader type
29  !<
31  integer(I4B) :: tas_active !< Are TAS6 inputs defined
32  type(characterstringtype), dimension(:), contiguous, &
33  pointer :: aux_tasnames !< array of AUXVAR TAS names
34  type(characterstringtype), dimension(:), contiguous, &
35  pointer :: param_tasnames !< array of dynamic param TAS names
36  type(readstatevartype), dimension(:), allocatable :: param_reads !< read states for current load
37  type(timearrayseriesmanagertype), pointer :: tasmanager !< TAS manager
38  type(boundinputcontexttype) :: bound_context
39  contains
40  procedure :: ainit => bndgrid_init
41  procedure :: df => bndgrid_df
42  procedure :: ad => bndgrid_ad
43  procedure :: rp => bndgrid_rp
44  procedure :: destroy => bndgrid_destroy
45  procedure :: reset => bndgrid_reset
46  procedure :: init_charstr1d
47  procedure :: params_alloc => bndgrid_params_alloc
48  procedure :: param_load => bndgrid_param_load
49  procedure :: tas_arrays_alloc => bndgrid_tas_arrays_alloc
50  procedure :: tas_links_create => bndgrid_tas_links_create
51  end type boundgridinputtype
52 
53 contains
54 
55  subroutine bndgrid_init(this, mf6_input, component_name, &
56  component_input_name, input_name, &
57  iperblock, parser, iout)
61  class(boundgridinputtype), intent(inout) :: this
62  type(modflowinputtype), intent(in) :: mf6_input
63  character(len=*), intent(in) :: component_name
64  character(len=*), intent(in) :: component_input_name
65  character(len=*), intent(in) :: input_name
66  integer(I4B), intent(in) :: iperblock
67  type(blockparsertype), pointer, intent(inout) :: parser
68  integer(I4B), intent(in) :: iout
69  type(loadmf6filetype) :: loader
70  type(characterstringtype), dimension(:), pointer, &
71  contiguous :: tas_fnames
72  character(len=LINELENGTH) :: fname
73  integer(I4B) :: tas6_size, n
74 
75  ! initialize base type
76  call this%DynamicPkgLoadType%init(mf6_input, component_name, &
77  component_input_name, &
78  input_name, iperblock, iout)
79  ! initialize
80  nullify (this%aux_tasnames)
81  nullify (this%param_tasnames)
82  this%tas_active = 0
83  this%iout = iout
84 
85  ! load static input
86  call loader%load(parser, mf6_input, this%nc_vars, this%input_name, iout)
87 
88  ! create tasmanager
89  allocate (this%tasmanager)
90  call tasmanager_cr(this%tasmanager, modelname=this%mf6_input%component_name, &
91  iout=this%iout)
92 
93  ! determine if TAS6 files were provided in OPTIONS block
94  call get_isize('TAS6_FILENAME', this%mf6_input%mempath, tas6_size)
95  if (tas6_size > 0) then
96  this%tas_active = 1
97  call mem_setptr(tas_fnames, 'TAS6_FILENAME', this%mf6_input%mempath)
98  ! add files to tasmanager
99  do n = 1, size(tas_fnames)
100  fname = tas_fnames(n)
101  call this%tasmanager%add_tasfile(fname)
102  end do
103  end if
104 
105  ! initialize input context memory
106  call this%bound_context%create(mf6_input, this%readasarrays)
107 
108  ! allocate dfn params
109  call this%params_alloc()
110 
111  ! allocate memory for storing TAS strings
112  call this%tas_arrays_alloc()
113  end subroutine bndgrid_init
114 
115  subroutine bndgrid_df(this)
116  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
117  call this%tasmanager%tasmanager_df()
118  end subroutine bndgrid_df
119 
120  subroutine bndgrid_ad(this)
121  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
122  call this%tasmanager%ad()
123  end subroutine bndgrid_ad
124 
125  subroutine bndgrid_rp(this, parser)
130  use arrayhandlersmodule, only: ifind
133  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
134  type(blockparsertype), pointer, intent(inout) :: parser
135  logical(LGP) :: endOfBlock, netcdf
136  character(len=LINELENGTH) :: keyword, param_tag
137  type(inputparamdefinitiontype), pointer :: idt
138  integer(I4B) :: iaux, iparam
139  character(len=LENTIMESERIESNAME) :: tas_name
140  integer(I4B), dimension(:), pointer, contiguous :: int1d
141 
142  ! reset for this period
143  call this%reset()
144 
145  ! log lst file header
146  call idm_log_header(this%mf6_input%component_name, &
147  this%mf6_input%subcomponent_name, this%iout)
148 
149  ! read array block
150  do
151  ! initialize
152  iaux = 0
153  netcdf = .false.
154 
155  ! read next line
156  call parser%GetNextLine(endofblock)
157  if (endofblock) exit
158  ! read param_tag
159  call parser%GetStringCaps(param_tag)
160 
161  ! is param tag an auxvar?
162  iaux = ifind_charstr(this%bound_context%auxname_cst, param_tag)
163  ! any auvxar corresponds to the definition tag 'AUX'
164  if (iaux > 0) param_tag = 'AUX'
165 
166  ! set input definition
167  idt => get_param_definition_type(this%mf6_input%param_dfns, &
168  this%mf6_input%component_type, &
169  this%mf6_input%subcomponent_type, &
170  'PERIOD', param_tag, this%input_name)
171  ! look for TAS and NetCDF keywords
172  call parser%GetStringCaps(keyword)
173  if (keyword == 'TIMEARRAYSERIES') then
174  if (this%tas_active /= 0) then
175  call parser%GetStringCaps(tas_name)
176  if (param_tag == 'AUX') then
177  this%aux_tasnames(iaux) = tas_name
178  else
179  iparam = ifind(this%param_names, param_tag)
180  this%param_tasnames(iparam) = tas_name
181  this%param_reads(iparam)%invar = 2
182  end if
183  ! log variable
184  call idm_log_var(param_tag, this%mf6_input%mempath, this%iout, .true.)
185  ! cycle to next input param
186  cycle
187  else
188  ! TODO: throw error
189  end if
190  else if (keyword == 'NETCDF') then
191  netcdf = .true.
192  end if
193 
194  ! read and load the parameter
195  call this%param_load(parser, idt, this%mf6_input%mempath, netcdf, iaux)
196  end do
197 
198  ! check if layer index variable was read
199  ! TODO: assumes layer index variable is always in scope
200  if (this%param_reads(1)%invar == 0) then
201  ! set to default of 1 without updating invar
202  idt => get_param_definition_type(this%mf6_input%param_dfns, &
203  this%mf6_input%component_type, &
204  this%mf6_input%subcomponent_type, &
205  'PERIOD', this%param_names(1), &
206  this%input_name)
207  call mem_setptr(int1d, idt%mf6varname, this%mf6_input%mempath)
208  int1d = 1
209  end if
210 
211  if (this%tas_active /= 0) then
212  call this%tas_links_create(parser%iuactive)
213  end if
214 
215  ! log lst file header
216  call idm_log_close(this%mf6_input%component_name, &
217  this%mf6_input%subcomponent_name, this%iout)
218  end subroutine bndgrid_rp
219 
220  subroutine bndgrid_destroy(this)
221  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
222  !
223  ! deallocate tasmanager
224  call this%tasmanager%da()
225  deallocate (this%tasmanager)
226  nullify (this%tasmanager)
227  end subroutine bndgrid_destroy
228 
229  subroutine bndgrid_reset(this)
230  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
231  integer(I4B) :: n, m
232 
233  if (this%tas_active /= 0) then
234  ! reset tasmanager
235  call this%tasmanager%reset(this%mf6_input%subcomponent_name)
236  ! reinitialize tas name arrays
237  call this%init_charstr1d('AUXTASNAME', this%input_name)
238  call this%init_charstr1d('PARAMTASNAME', this%input_name)
239  end if
240 
241  do n = 1, this%nparam
242  ! reset read state
243  this%param_reads(n)%invar = 0
244  end do
245 
246  ! explicitly reset auxvar array each period
247  do m = 1, this%bound_context%ncpl
248  do n = 1, this%bound_context%naux
249  this%bound_context%auxvar(n, m) = dzero
250  end do
251  end do
252  end subroutine bndgrid_reset
253 
254  subroutine init_charstr1d(this, varname, input_name)
256  class(boundgridinputtype) :: this
257  character(len=*), intent(in) :: varname
258  character(len=*), intent(in) :: input_name
259  type(characterstringtype), dimension(:), pointer, &
260  contiguous :: charstr1d
261  integer(I4B) :: n
262  call mem_setptr(charstr1d, varname, this%mf6_input%mempath)
263  do n = 1, size(charstr1d)
264  charstr1d(n) = ''
265  end do
266  end subroutine init_charstr1d
267 
268  subroutine bndgrid_params_alloc(this)
269  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
270  character(len=LENVARNAME) :: rs_varname
271  integer(I4B), pointer :: intvar
272  integer(I4B) :: iparam
273 
274  ! set in scope param names
275  call this%bound_context%bound_params(this%param_names, this%nparam, &
276  this%input_name)
277  call this%bound_context%allocate_arrays()
278 
279  ! allocate and set param_reads pointer array
280  allocate (this%param_reads(this%nparam))
281 
282  ! store read state variable pointers
283  do iparam = 1, this%nparam
284  ! allocate and store name of read state variable
285  rs_varname = this%bound_context%rsv_alloc(this%param_names(iparam))
286  call mem_setptr(intvar, rs_varname, this%mf6_input%mempath)
287  this%param_reads(iparam)%invar => intvar
288  this%param_reads(iparam)%invar = 0
289  end do
290  end subroutine bndgrid_params_alloc
291 
292  subroutine bndgrid_param_load(this, parser, idt, mempath, netcdf, iaux)
293  use tdismodule, only: kper
295  use arrayhandlersmodule, only: ifind
302  use idmloggermodule, only: idm_log_var
303  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
304  type(blockparsertype), intent(in) :: parser
305  type(inputparamdefinitiontype), intent(in) :: idt
306  character(len=*), intent(in) :: mempath
307  logical(LGP), intent(in) :: netcdf
308  integer(I4B), intent(in) :: iaux
309  integer(I4B), dimension(:), pointer, contiguous :: int1d
310  real(DP), dimension(:), pointer, contiguous :: dbl1d
311  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
312  integer(I4B) :: iparam, n
313 
314  select case (idt%datatype)
315  case ('INTEGER1D')
316  call mem_setptr(int1d, idt%mf6varname, mempath)
317  if (netcdf) then
318  call netcdf_read_array(int1d, this%bound_context%mshape, idt, &
319  this%mf6_input, this%nc_vars, this%input_name, &
320  this%iout, kper)
321  else
322  call read_int1d(parser, int1d, idt%mf6varname)
323  end if
324  call idm_log_var(int1d, idt%tagname, mempath, this%iout)
325  case ('DOUBLE1D')
326  call mem_setptr(dbl1d, idt%mf6varname, mempath)
327  if (netcdf) then
328  call netcdf_read_array(dbl1d, this%bound_context%mshape, idt, &
329  this%mf6_input, this%nc_vars, this%input_name, &
330  this%iout, kper)
331  else
332  call read_dbl1d(parser, dbl1d, idt%mf6varname)
333  end if
334  call idm_log_var(dbl1d, idt%tagname, mempath, this%iout)
335  case ('DOUBLE2D')
336  call mem_setptr(dbl2d, idt%mf6varname, mempath)
337  allocate (dbl1d(this%bound_context%ncpl))
338  if (netcdf) then
339  call netcdf_read_array(dbl1d, this%bound_context%mshape, idt, &
340  this%mf6_input, this%nc_vars, this%input_name, &
341  this%iout, kper, iaux)
342  else
343  call read_dbl1d(parser, dbl1d, idt%mf6varname)
344  end if
345  do n = 1, this%bound_context%ncpl
346  dbl2d(iaux, n) = dbl1d(n)
347  end do
348  call idm_log_var(dbl1d, idt%tagname, mempath, this%iout)
349  deallocate (dbl1d)
350  case default
351  errmsg = 'IDM unimplemented. Mf6FileGridInput::param_load &
352  &datatype='//trim(idt%datatype)
353  call store_error(errmsg)
354  call store_error_filename(this%input_name)
355  end select
356 
357  ! if param is tracked set read state
358  iparam = ifind(this%param_names, idt%tagname)
359  if (iparam > 0) then
360  this%param_reads(iparam)%invar = 1
361  end if
362  end subroutine bndgrid_param_load
363 
364  subroutine bndgrid_tas_arrays_alloc(this)
366  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
367 
368  ! count params other than AUX
369  if (this%tas_active /= 0) then
370  call mem_allocate(this%aux_tasnames, lentimeseriesname, &
371  this%bound_context%naux, 'AUXTASNAME', &
372  this%mf6_input%mempath)
373  call mem_allocate(this%param_tasnames, lentimeseriesname, this%nparam, &
374  'PARAMTASNAME', this%mf6_input%mempath)
375  call this%init_charstr1d('AUXTASNAME', this%input_name)
376  call this%init_charstr1d('PARAMTASNAME', this%input_name)
377  else
378  call mem_allocate(this%aux_tasnames, lentimeseriesname, 0, &
379  'AUXTASNAME', this%mf6_input%mempath)
380  call mem_allocate(this%param_tasnames, lentimeseriesname, 0, &
381  'PARAMTASNAME', this%mf6_input%mempath)
382  end if
383  end subroutine bndgrid_tas_arrays_alloc
384 
385  ! FLUX and SFAC are handled in model context
386  subroutine bndgrid_tas_links_create(this, inunit)
389  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
390  integer(I4B), intent(in) :: inunit
391  type(inputparamdefinitiontype), pointer :: idt
392  ! non-contiguous because a slice of bound is passed
393  real(DP), dimension(:), pointer :: auxArrayPtr, bndArrayPtr
394  real(DP), dimension(:), pointer, contiguous :: bound
395  integer(I4B), dimension(:), pointer, contiguous :: nodelist
396  character(len=LENTIMESERIESNAME) :: tas_name
397  character(len=LENAUXNAME) :: aux_name
398  logical :: convertFlux
399  integer(I4B) :: n
400 
401  ! initialize
402  nullify (auxarrayptr)
403  nullify (bndarrayptr)
404  nullify (nodelist)
405  convertflux = .false.
406 
407  ! Create AUX Time Array Series links
408  do n = 1, this%bound_context%naux
409  tas_name = this%aux_tasnames(n)
410  if (tas_name /= '') then
411  ! set auxvar pointer
412  auxarrayptr => this%bound_context%auxvar(n, :)
413  aux_name = this%bound_context%auxname_cst(n)
414  call this%tasmanager%MakeTasLink(this%mf6_input%subcomponent_name, &
415  auxarrayptr, this%bound_context%iprpak, &
416  tas_name, aux_name, convertflux, &
417  nodelist, inunit)
418  end if
419  end do
420 
421  ! Create BND Time Array Series links
422  do n = 1, this%nparam
423  ! assign param definition pointer
424  idt => get_param_definition_type(this%mf6_input%param_dfns, &
425  this%mf6_input%component_type, &
426  this%mf6_input%subcomponent_type, &
427  'PERIOD', this%param_names(n), &
428  this%input_name)
429  if (idt%timeseries) then
430  if (this%param_reads(n)%invar == 2) then
431  tas_name = this%param_tasnames(n)
432  call mem_setptr(bound, idt%mf6varname, this%mf6_input%mempath)
433  ! set bound pointer
434  bndarrayptr => bound(:)
435  call this%tasmanager%MakeTasLink(this%mf6_input%subcomponent_name, &
436  bndarrayptr, &
437  this%bound_context%iprpak, &
438  tas_name, idt%mf6varname, &
439  convertflux, nodelist, inunit)
440  end if
441  end if
442  end do
443  end subroutine bndgrid_tas_links_create
444 
445 end module mf6filegridinputmodule
This module contains the AsciiInputLoadTypeModule.
This module contains block parser methods.
Definition: BlockParser.f90:7
This module contains the BoundInputContextModule.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lentimeseriesname
maximum length of a time series name
Definition: Constants.f90:42
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
integer(i4b), parameter lenauxname
maximum length of a aux variable
Definition: Constants.f90:35
integer(i4b), parameter izero
integer constant zero
Definition: Constants.f90:51
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
This module contains the DefinitionSelectModule.
type(inputparamdefinitiontype) function, pointer, public get_param_definition_type(input_definition_types, component_type, subcomponent_type, blockname, tagname, filename)
Return parameter definition.
subroutine, public read_dbl1d(parser, dbl1d, aname)
subroutine, public read_dbl2d(parser, dbl2d, aname)
This module contains the Input Data Model Logger Module.
Definition: IdmLogger.f90:7
subroutine, public idm_log_close(component, subcomponent, iout)
@ brief log the closing message
Definition: IdmLogger.f90:56
subroutine, public idm_log_header(component, subcomponent, iout)
@ brief log a header message
Definition: IdmLogger.f90:44
This module contains the InputDefinitionModule.
subroutine, public read_int1d(parser, int1d, aname)
This module defines variable data types.
Definition: kind.f90:8
This module contains the LoadMf6FileModule.
Definition: LoadMf6File.f90:8
This module contains the LoadNCInputModule.
Definition: LoadNCInput.F90:7
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains the Mf6FileGridInputModule.
subroutine bndgrid_tas_arrays_alloc(this)
subroutine bndgrid_df(this)
subroutine init_charstr1d(this, varname, input_name)
subroutine bndgrid_rp(this, parser)
subroutine bndgrid_ad(this)
subroutine bndgrid_reset(this)
subroutine bndgrid_tas_links_create(this, inunit)
subroutine bndgrid_destroy(this)
subroutine bndgrid_init(this, mf6_input, component_name, component_input_name, input_name, iperblock, parser, iout)
subroutine bndgrid_param_load(this, parser, idt, mempath, netcdf, iaux)
subroutine bndgrid_params_alloc(this)
This module contains the ModflowInputModule.
Definition: ModflowInput.f90:9
type(modflowinputtype) function, public getmodflowinput(pkgtype, component_type, subcomponent_type, component_name, subcomponent_name, filename)
function to return ModflowInputType
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
This module contains the SourceCommonModule.
Definition: SourceCommon.f90:7
integer(i4b) function, public ifind_charstr(array, str)
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
subroutine, public tasmanager_cr(this, dis, modelname, iout)
Create the time-array series manager.
base abstract type for ascii source dynamic load
derived type for boundary package input context
Pointer type for read state variable.
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
Static parser based input loader.
Definition: LoadMf6File.f90:48
Ascii grid based dynamic loader type.
derived type for storing input definition for a file