MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
Mf6FileListInput.f90
Go to the documentation of this file.
1 !> @brief This module contains the Mf6FileListInputModule
2 !!
3 !! This module contains the routines for reading period block
4 !! list based input.
5 !!
6 !<
8 
9  use kindmodule, only: i4b, dp, lgp
13  use simvariablesmodule, only: errmsg
26 
27  implicit none
28  private
29  public :: boundlistinputtype
30 
31  !> @brief Abstract base class for ascii list loaders
32  !!
33  !! Abstract class with types and routines common to Ascii list
34  !! based loaders.
35  !!
36  !<
37  type, abstract, extends(asciidynamicpkgloadbasetype) :: listinputbasetype
38  integer(I4B) :: ts_active
39  type(timeseriesmanagertype), pointer :: tsmanager => null()
40  type(structarraytype), pointer :: structarray => null()
41  contains
42  procedure :: base_init
43  procedure :: base_destroy
44  procedure :: df
45  procedure :: ad
46  procedure :: reset
47  end type listinputbasetype
48 
49  !> @brief Boundary package list loader.
50  !!
51  !! Creates boundary input context for a package,
52  !! (e.g. CHD or MAW) and updates that context in
53  !! read and prepare (RP) routines.
54  !!
55  !<
57  integer(I4B) :: iboundname
58  type(boundinputcontexttype) :: bound_context
59  contains
60  procedure :: ainit => bndlist_init
61  procedure :: rp => bndlist_rp
62  procedure :: destroy => bndlist_destroy
63  procedure :: ts_link_bnd => bndlist_ts_link_bnd
64  procedure :: ts_link_aux => bndlist_ts_link_aux
65  procedure :: ts_link => bndlist_ts_link
66  procedure :: ts_update => bndlist_ts_update
67  procedure :: create_structarray => bndlist_create_structarray
68  end type boundlistinputtype
69 
70 contains
71 
72  subroutine bndlist_init(this, mf6_input, component_name, component_input_name, &
73  input_name, iperblock, parser, iout)
76  class(boundlistinputtype), intent(inout) :: this
77  type(modflowinputtype), intent(in) :: mf6_input
78  character(len=*), intent(in) :: component_name
79  character(len=*), intent(in) :: component_input_name
80  character(len=*), intent(in) :: input_name
81  integer(I4B), intent(in) :: iperblock
82  type(blockparsertype), pointer, intent(inout) :: parser
83  integer(I4B), intent(in) :: iout
84  type(loadmf6filetype) :: loader
85  character(len=LINELENGTH) :: blockname
86  integer(I4B) :: iblk
87  !
88  ! -- initialize scalars
89  this%iboundname = 0
90  !
91  ! -- initialize base class
92  call this%base_init(mf6_input, component_name, component_input_name, &
93  input_name, iperblock, parser, loader, iout)
94  !
95  ! -- initialize package input context
96  call this%bound_context%create(mf6_input, this%readasarrays)
97  !
98  ! -- load blocks after OPTIONS and DIMENSIONS
99  do iblk = 1, size(this%mf6_input%block_dfns)
100  !
101  ! -- log block header via loader or directly here?
102  !
103  ! -- set blockname
104  blockname = this%mf6_input%block_dfns(iblk)%blockname
105  !
106  ! -- base_init loads OPTIONS and DIMENSIONS blocks if defined
107  if (blockname == 'OPTIONS' .or. blockname == 'DIMENSIONS') cycle
108  if (blockname == 'PERIOD') exit
109  !
110  ! -- load block
111  call loader%load_block(iblk)
112  !
113  if (this%mf6_input%block_dfns(iblk)%aggregate) then
114  if (this%mf6_input%block_dfns(iblk)%timeseries) then
115  if (this%ts_active > 0) then
116  call this%ts_update(loader%structarray)
117  end if
118  end if
119  end if
120  !
121  end do
122  !
123  call loader%finalize()
124  !
125  ! -- store in scope SA cols for list input
126  call this%bound_context%bound_params(this%param_names, this%nparam, &
127  this%input_name, create=.false.)
128  !
129  ! -- construct and set up the struct array object
130  call this%create_structarray()
131  !
132  ! -- finalize input context setup
133  call this%bound_context%allocate_arrays()
134  !
135  ! -- return
136  return
137  end subroutine bndlist_init
138 
139  subroutine bndlist_rp(this, parser)
140  ! -- modules
145  ! -- dummy
146  class(boundlistinputtype), intent(inout) :: this
147  type(blockparsertype), pointer, intent(inout) :: parser
148  ! -- local
149  integer(I4B) :: ibinary
150  integer(I4B) :: oc_inunit
151  logical(LGP) :: ts_active
152  !
153  call this%reset()
154  !
155  ibinary = read_control_record(parser, oc_inunit, this%iout)
156  !
157  ! -- log lst file header
158  call idm_log_header(this%mf6_input%component_name, &
159  this%mf6_input%subcomponent_name, this%iout)
160  !
161  if (ibinary == 1) then
162  !
163  this%bound_context%nbound = &
164  this%structarray%read_from_binary(oc_inunit, this%iout)
165  !
166  call parser%terminateblock()
167  !
168  close (oc_inunit)
169  !
170  else
171  !
172  ts_active = (this%ts_active /= 0)
173  !
174  this%bound_context%nbound = &
175  this%structarray%read_from_parser(parser, ts_active, this%iout)
176  end if
177  !
178  ! update ts links
179  if (this%ts_active /= 0) then
180  call this%ts_update(this%structarray)
181  end if
182  !
183  ! -- close logging statement
184  call idm_log_close(this%mf6_input%component_name, &
185  this%mf6_input%subcomponent_name, this%iout)
186  !
187  ! -- return
188  return
189  end subroutine bndlist_rp
190 
191  subroutine bndlist_destroy(this)
192  ! -- modules
193  class(boundlistinputtype), intent(inout) :: this !< BoundListInputType
194  !
195  call this%base_destroy()
196  call this%bound_context%destroy()
197  !
198  ! -- return
199  return
200  end subroutine bndlist_destroy
201 
202  subroutine bndlist_ts_link_bnd(this, structvector, ts_strloc)
203  ! -- modules
207  ! -- dummy
208  class(boundlistinputtype), intent(inout) :: this
209  type(structvectortype), pointer, intent(in) :: structvector
210  type(tsstringloctype), pointer, intent(in) :: ts_strloc
211  ! -- local
212  real(DP), pointer :: bndElem
213  type(timeserieslinktype), pointer :: tsLinkBnd
214  type(structvectortype), pointer :: sv_bound
215  character(len=LENBOUNDNAME) :: boundname
216  !
217  nullify (tslinkbnd)
218  !
219  ! -- set bound element
220  bndelem => structvector%dbl1d(ts_strloc%row)
221  !
222  ! -- set link
223  call read_value_or_time_series(ts_strloc%token, ts_strloc%row, &
224  ts_strloc%structarray_col, bndelem, &
225  this%mf6_input%subcomponent_name, &
226  'BND', this%tsmanager, &
227  this%bound_context%iprpak, tslinkbnd)
228  !
229  if (associated(tslinkbnd)) then
230  !
231  ! -- set variable name
232  tslinkbnd%Text = structvector%idt%mf6varname
233  !
234  ! -- set boundname if provided
235  if (this%bound_context%inamedbound > 0) then
236  sv_bound => this%structarray%get(this%iboundname)
237  boundname = sv_bound%charstr1d(ts_strloc%row)
238  tslinkbnd%BndName = boundname
239  end if
240  end if
241  !
242  ! -- return
243  return
244  end subroutine bndlist_ts_link_bnd
245 
246  subroutine bndlist_ts_link_aux(this, structvector, ts_strloc)
247  ! -- modules
251  ! -- dummy
252  class(boundlistinputtype), intent(inout) :: this
253  type(structvectortype), pointer, intent(in) :: structvector
254  type(tsstringloctype), pointer, intent(in) :: ts_strloc
255  ! -- local
256  real(DP), pointer :: bndElem
257  type(timeserieslinktype), pointer :: tsLinkAux
258  type(structvectortype), pointer :: sv_bound
259  character(len=LENBOUNDNAME) :: boundname
260  !
261  nullify (tslinkaux)
262  !
263  ! -- set bound element
264  bndelem => structvector%dbl2d(ts_strloc%col, ts_strloc%row)
265  !
266  ! -- set link
267  call read_value_or_time_series(ts_strloc%token, ts_strloc%row, &
268  ts_strloc%structarray_col, bndelem, &
269  this%mf6_input%subcomponent_name, &
270  'AUX', this%tsmanager, &
271  this%bound_context%iprpak, tslinkaux)
272 
273  if (associated(tslinkaux)) then
274  !
275  ! -- set variable name
276  tslinkaux%Text = this%bound_context%auxname_cst(ts_strloc%col)
277  !
278  ! -- set boundname if provided
279  if (this%bound_context%inamedbound > 0) then
280  sv_bound => this%structarray%get(this%iboundname)
281  boundname = sv_bound%charstr1d(ts_strloc%row)
282  tslinkaux%BndName = boundname
283  end if
284  !
285  end if
286  !
287  ! -- return
288  return
289  end subroutine bndlist_ts_link_aux
290 
291  subroutine bndlist_ts_update(this, structarray)
292  ! -- modules
295  ! -- dummy
296  class(boundlistinputtype), intent(inout) :: this
297  type(structarraytype), pointer, intent(inout) :: structarray
298  ! -- local
299  integer(I4B) :: n, m
300  type(tsstringloctype), pointer :: ts_strloc
301  type(structvectortype), pointer :: sv
302  !
303  do m = 1, structarray%count()
304 
305  sv => structarray%get(m)
306 
307  if (sv%idt%timeseries) then
308  !
309  do n = 1, sv%ts_strlocs%count()
310  ts_strloc => sv%get_ts_strloc(n)
311  call this%ts_link(sv, ts_strloc)
312  end do
313  !
314  call sv%clear()
315  end if
316  end do
317  !
318  ! -- return
319  return
320  end subroutine bndlist_ts_update
321 
322  subroutine bndlist_ts_link(this, structvector, ts_strloc)
323  ! -- modules
325  ! -- dummy
326  class(boundlistinputtype), intent(inout) :: this
327  type(structvectortype), pointer, intent(in) :: structvector
328  type(tsstringloctype), pointer, intent(in) :: ts_strloc
329  ! -- local
330  !
331  select case (structvector%memtype)
332  case (2) ! -- dbl1d
333  !
334  call this%ts_link_bnd(structvector, ts_strloc)
335  !
336  case (6) ! -- dbl2d
337  !
338  call this%ts_link_aux(structvector, ts_strloc)
339  !
340  case default
341  end select
342  !
343  ! -- return
344  return
345  end subroutine bndlist_ts_link
346 
347  subroutine bndlist_create_structarray(this)
348  ! -- modules
351  ! -- dummy
352  class(boundlistinputtype), intent(inout) :: this
353  ! -- local
354  type(inputparamdefinitiontype), pointer :: idt
355  integer(I4B) :: icol
356  !
357  ! -- construct and set up the struct array object
358  this%structarray => constructstructarray(this%mf6_input, this%nparam, &
359  this%bound_context%maxbound, 0, &
360  this%mf6_input%mempath, &
361  this%mf6_input%component_mempath)
362  !
363  ! -- set up struct array
364  do icol = 1, this%nparam
365  !
366  idt => get_param_definition_type(this%mf6_input%param_dfns, &
367  this%mf6_input%component_type, &
368  this%mf6_input%subcomponent_type, &
369  'PERIOD', &
370  this%param_names(icol), this%input_name)
371  !
372  ! -- allocate variable in memory manager
373  call this%structarray%mem_create_vector(icol, idt)
374  !
375  ! -- store boundname index when found
376  if (idt%mf6varname == 'BOUNDNAME') this%iboundname = icol
377  !
378  end do
379  !
380  ! -- return
381  return
382  end subroutine bndlist_create_structarray
383 
384  subroutine base_init(this, mf6_input, component_name, component_input_name, &
385  input_name, iperblock, parser, loader, iout)
389  use memorymanagermodule, only: get_isize
391  class(listinputbasetype), intent(inout) :: this
392  type(modflowinputtype), intent(in) :: mf6_input
393  character(len=*), intent(in) :: component_name
394  character(len=*), intent(in) :: component_input_name
395  character(len=*), intent(in) :: input_name
396  integer(I4B), intent(in) :: iperblock
397  type(blockparsertype), intent(inout) :: parser
398  type(loadmf6filetype), intent(inout) :: loader
399  integer(I4B), intent(in) :: iout
400  type(characterstringtype), dimension(:), pointer, &
401  contiguous :: ts_fnames
402  character(len=LINELENGTH) :: fname
403  integer(I4B) :: ts6_size, n
404  character(len=LINELENGTH) :: blockname
405  integer(I4B) :: iblk
406  !
407  ! -- init loader
408  call this%DynamicPkgLoadType%init(mf6_input, component_name, &
409  component_input_name, input_name, &
410  iperblock, iout)
411  !
412  ! -- initialize
413  this%ts_active = 0
414  !
415  ! -- initialize static loader
416  call loader%init(parser, mf6_input, this%input_name, iout)
417  !
418  ! -- load OPTIONS and DIMENSIONS blocks
419  do iblk = 1, size(this%mf6_input%block_dfns)
420  !
421  ! -- set blockname
422  blockname = this%mf6_input%block_dfns(iblk)%blockname
423  !
424  ! -- step 1 loads OPTIONS and DIMENSIONS blocks if defined
425  if (blockname /= 'OPTIONS' .and. blockname /= 'DIMENSIONS') exit
426  !
427  ! -- load block
428  call loader%load_block(iblk)
429  !
430  end do
431  !
432  ! -- create tsmanager
433  allocate (this%tsmanager)
434  call tsmanager_cr(this%tsmanager, iout)
435  !
436  ! -- determine if TS6 files were provided in OPTIONS block
437  call get_isize('TS6_FILENAME', this%mf6_input%mempath, ts6_size)
438  !
439  if (ts6_size > 0) then
440  !
441  this%ts_active = 1
442  call mem_setptr(ts_fnames, 'TS6_FILENAME', this%mf6_input%mempath)
443  !
444  do n = 1, size(ts_fnames)
445  fname = ts_fnames(n)
446  call this%tsmanager%add_tsfile(fname, getunit())
447  end do
448  !
449  end if
450  !
451  ! -- define TS manager
452  call this%tsmanager%tsmanager_df()
453  !
454  ! -- return
455  return
456  end subroutine base_init
457 
458  subroutine base_destroy(this)
459  ! -- modules
460  class(listinputbasetype), intent(inout) :: this !< ListInputType
461  !
462  deallocate (this%tsmanager)
463  !
464  ! -- deallocate StructArray
465  call destructstructarray(this%structarray)
466  !
467  ! -- return
468  return
469  end subroutine base_destroy
470 
471  subroutine df(this)
472  ! -- modules
473  ! -- dummy
474  class(listinputbasetype), intent(inout) :: this !< ListInputType
475  !
476  ! -- define tsmanager
477  !call this%tsmanager%tsmanager_df()
478  !
479  ! -- return
480  return
481  end subroutine df
482 
483  subroutine ad(this)
484  ! -- modules
485  class(listinputbasetype), intent(inout) :: this !< ListInputType
486  !
487  ! -- advance timeseries
488  call this%tsmanager%ad()
489  !
490  ! -- return
491  return
492  end subroutine ad
493 
494  subroutine reset(this)
495  ! -- modules
496  class(listinputbasetype), intent(inout) :: this !< ListInputType
497  !
498  ! -- reset tsmanager
499  call this%tsmanager%reset(this%mf6_input%subcomponent_name)
500  !
501  ! -- return
502  return
503  end subroutine reset
504 
505 end module mf6filelistinputmodule
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:44
integer(i4b), parameter lencomponentname
maximum length of a component name
Definition: Constants.f90:18
integer(i4b), parameter lentimeseriesname
maximum length of a time series name
Definition: Constants.f90:41
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:34
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:35
integer(i4b), parameter izero
integer constant zero
Definition: Constants.f90:50
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:26
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.
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:57
subroutine, public idm_log_header(component, subcomponent, iout)
@ brief log a header message
Definition: IdmLogger.f90:44
This module contains the InputDefinitionModule.
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
This module defines variable data types.
Definition: kind.f90:8
This module contains the LoadMf6FileModule.
Definition: LoadMf6File.f90:8
integer(i4b) function, public read_control_record(parser, oc_inunit, iout)
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains the Mf6FileListInputModule.
subroutine bndlist_destroy(this)
subroutine bndlist_init(this, mf6_input, component_name, component_input_name, input_name, iperblock, parser, iout)
subroutine bndlist_ts_link_bnd(this, structvector, ts_strloc)
subroutine bndlist_ts_link(this, structvector, ts_strloc)
subroutine bndlist_ts_link_aux(this, structvector, ts_strloc)
subroutine bndlist_rp(this, parser)
subroutine bndlist_ts_update(this, structarray)
subroutine bndlist_create_structarray(this)
subroutine base_destroy(this)
subroutine base_init(this, mf6_input, component_name, component_input_name, input_name, iperblock, parser, loader, iout)
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
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
This module contains the StructArrayModule.
Definition: StructArray.f90:8
type(structarraytype) function, pointer, public constructstructarray(mf6_input, ncol, nrow, blocknum, mempath, component_mempath)
constructor for a struct_array
Definition: StructArray.f90:74
subroutine, public destructstructarray(struct_array)
destructor for a struct_array
This module contains the StructVectorModule.
Definition: StructVector.f90:7
subroutine, public tsmanager_cr(this, iout, removeTsLinksOnCompletion, extendTsToEndOfSimulation)
Create the tsmanager.
subroutine, public read_value_or_time_series(textInput, ii, jj, bndElem, pkgName, auxOrBnd, tsManager, iprpak, tsLink)
Call this subroutine if the time-series link is available or needed.
base abstract type for ascii source dynamic load
derived type for boundary package input context
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:47
Abstract base class for ascii list loaders.
derived type for storing input definition for a file
type for structured array
Definition: StructArray.f90:37
derived type for generic vector
derived type which describes time series string field