MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
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%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  !
96  if (tas6_size > 0) then
97  !
98  this%tas_active = 1
99  !
100  call mem_setptr(tas_fnames, 'TAS6_FILENAME', this%mf6_input%mempath)
101  !
102  ! -- add files to tasmanager
103  do n = 1, size(tas_fnames)
104  fname = tas_fnames(n)
105  call this%tasmanager%add_tasfile(fname)
106  end do
107  !
108  end if
109  !
110  ! -- initialize input context memory
111  call this%bound_context%create(mf6_input, this%readasarrays)
112  !
113  ! -- allocate dfn params
114  call this%params_alloc()
115  !
116  ! -- allocate memory for storing TAS strings
117  call this%tas_arrays_alloc()
118  !
119  ! -- return
120  return
121  end subroutine bndgrid_init
122 
123  subroutine bndgrid_df(this)
124  ! -- modules
125  ! -- dummy
126  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
127  !
128  call this%tasmanager%tasmanager_df()
129  !
130  ! -- return
131  return
132  end subroutine bndgrid_df
133 
134  subroutine bndgrid_ad(this)
135  ! -- modules
136  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
137  !
138  call this%tasmanager%ad()
139  !
140  ! -- return
141  return
142  end subroutine bndgrid_ad
143 
144  subroutine bndgrid_rp(this, parser)
145  ! -- modules
150  use arrayhandlersmodule, only: ifind
153  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
154  type(blockparsertype), pointer, intent(inout) :: parser
155  ! -- local
156  logical(LGP) :: endOfBlock
157  character(len=LINELENGTH) :: keyword, param_tag
158  type(inputparamdefinitiontype), pointer :: idt
159  integer(I4B) :: iaux, iparam
160  character(len=LENTIMESERIESNAME) :: tas_name
161  !
162  ! -- reset for this period
163  call this%reset()
164  !
165  ! -- log lst file header
166  call idm_log_header(this%mf6_input%component_name, &
167  this%mf6_input%subcomponent_name, this%iout)
168  !
169  ! -- read array block
170  do
171  ! -- initialize
172  iaux = 0
173  !
174  ! -- read next line
175  call parser%GetNextLine(endofblock)
176  if (endofblock) exit
177  !
178  ! -- read param_tag
179  call parser%GetStringCaps(param_tag)
180  !
181  ! -- is param tag an auxvar?
182  iaux = ifind_charstr(this%bound_context%auxname_cst, param_tag)
183  !
184  ! -- any auvxar corresponds to the definition tag 'AUX'
185  if (iaux > 0) param_tag = 'AUX'
186  !
187  ! -- set input definition
188  idt => get_param_definition_type(this%mf6_input%param_dfns, &
189  this%mf6_input%component_type, &
190  this%mf6_input%subcomponent_type, &
191  'PERIOD', param_tag, this%input_name)
192  !
193  ! -- look for TAS keyword if tas is active
194  if (this%tas_active /= 0) then
195  call parser%GetStringCaps(keyword)
196  !
197  if (keyword == 'TIMEARRAYSERIES') then
198  call parser%GetStringCaps(tas_name)
199  !
200  if (param_tag == 'AUX') then
201  this%aux_tasnames(iaux) = tas_name
202  else
203  iparam = ifind(this%param_names, param_tag)
204  this%param_tasnames(iparam) = tas_name
205  this%param_reads(iparam)%invar = 2
206  end if
207  !
208  ! -- log variable
209  call idm_log_var(param_tag, this%mf6_input%mempath, this%iout, .true.)
210  !
211  ! -- cycle to next input param
212  cycle
213  end if
214  !
215  end if
216  !
217  ! -- read and load the parameter
218  call this%param_load(parser, idt%datatype, idt%mf6varname, idt%tagname, &
219  idt%shape, this%mf6_input%mempath, iaux)
220  !
221  end do
222  !
223  !
224  if (this%tas_active /= 0) then
225  call this%tas_links_create(parser%iuactive)
226  end if
227  !
228  ! -- log lst file header
229  call idm_log_close(this%mf6_input%component_name, &
230  this%mf6_input%subcomponent_name, this%iout)
231  !
232  ! -- return
233  return
234  end subroutine bndgrid_rp
235 
236  subroutine bndgrid_destroy(this)
237  ! -- modules
238  class(boundgridinputtype), intent(inout) :: this !< Mf6FileGridInputType
239  !
240  deallocate (this%tasmanager)
241  !
242  ! -- return
243  return
244  end subroutine bndgrid_destroy
245 
246  subroutine bndgrid_reset(this)
247  ! -- modules
248  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
249  integer(I4B) :: n, m
250  !
251  if (this%tas_active /= 0) then
252  !
253  ! -- reset tasmanager
254  call this%tasmanager%reset(this%mf6_input%subcomponent_name)
255  !
256  ! -- reinitialize tas name arrays
257  call this%init_charstr1d('AUXTASNAME', this%input_name)
258  call this%init_charstr1d('PARAMTASNAME', this%input_name)
259  end if
260  !
261  do n = 1, this%nparam
262  ! -- reset read state
263  this%param_reads(n)%invar = 0
264  end do
265  !
266  ! -- explicitly reset auxvar array each period
267  do m = 1, this%bound_context%ncpl
268  do n = 1, this%bound_context%naux
269  this%bound_context%auxvar(n, m) = dzero
270  end do
271  end do
272  !
273  ! -- return
274  return
275  end subroutine bndgrid_reset
276 
277  subroutine init_charstr1d(this, varname, input_name)
278  ! -- modules
280  ! -- dummy
281  class(boundgridinputtype) :: this
282  character(len=*), intent(in) :: varname
283  character(len=*), intent(in) :: input_name
284  ! -- local
285  type(characterstringtype), dimension(:), pointer, &
286  contiguous :: charstr1d
287  integer(I4B) :: n
288  !
289  call mem_setptr(charstr1d, varname, this%mf6_input%mempath)
290  do n = 1, size(charstr1d)
291  charstr1d(n) = ''
292  end do
293  end subroutine init_charstr1d
294 
295  subroutine bndgrid_params_alloc(this)
296  ! -- modules
297  ! -- dummy
298  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
299  character(len=LENVARNAME) :: rs_varname
300  integer(I4B), pointer :: intvar
301  integer(I4B) :: iparam
302  !
303  ! -- set in scope param names
304  call this%bound_context%bound_params(this%param_names, this%nparam, &
305  this%input_name)
306  !
307  call this%bound_context%allocate_arrays()
308  !
309  ! -- allocate and set param_reads pointer array
310  allocate (this%param_reads(this%nparam))
311  !
312  ! store read state variable pointers
313  do iparam = 1, this%nparam
314  ! -- allocate and store name of read state variable
315  rs_varname = this%bound_context%rsv_alloc(this%param_names(iparam))
316  call mem_setptr(intvar, rs_varname, this%mf6_input%mempath)
317  this%param_reads(iparam)%invar => intvar
318  this%param_reads(iparam)%invar = 0
319  end do
320  !
321  ! -- return
322  return
323  end subroutine bndgrid_params_alloc
324 
325  subroutine bndgrid_param_load(this, parser, datatype, varname, &
326  tagname, shapestr, mempath, iaux)
327  ! -- modules
329  use arrayhandlersmodule, only: ifind
335  use idmloggermodule, only: idm_log_var
336  ! -- dummy
337  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
338  type(blockparsertype), intent(in) :: parser
339  character(len=*), intent(in) :: datatype
340  character(len=*), intent(in) :: varname
341  character(len=*), intent(in) :: tagname
342  character(len=*), intent(in) :: shapestr
343  character(len=*), intent(in) :: mempath
344  integer(I4B), intent(in) :: iaux
345  ! -- local
346  integer(I4B), dimension(:), pointer, contiguous :: int1d
347  real(DP), dimension(:), pointer, contiguous :: dbl1d
348  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
349  integer(I4B) :: iparam, n
350  !
351  select case (datatype)
352  case ('INTEGER1D')
353  !
354  call mem_setptr(int1d, varname, mempath)
355  call read_int1d(parser, int1d, varname)
356  call idm_log_var(int1d, tagname, mempath, this%iout)
357  !
358  case ('DOUBLE1D')
359  !
360  call mem_setptr(dbl1d, varname, mempath)
361  call read_dbl1d(parser, dbl1d, varname)
362  call idm_log_var(dbl1d, tagname, mempath, this%iout)
363  !
364  case ('DOUBLE2D')
365  !
366  call mem_setptr(dbl2d, varname, mempath)
367  allocate (dbl1d(this%bound_context%ncpl))
368  call read_dbl1d(parser, dbl1d, varname)
369  do n = 1, this%bound_context%ncpl
370  dbl2d(iaux, n) = dbl1d(n)
371  end do
372  call idm_log_var(dbl1d, tagname, mempath, this%iout)
373  deallocate (dbl1d)
374  !
375  case default
376  !
377  errmsg = 'IDM unimplemented. Mf6FileGridInput::param_load &
378  &datatype='//trim(datatype)
379  call store_error(errmsg)
380  call store_error_filename(this%input_name)
381  !
382  end select
383  !
384  iparam = ifind(this%param_names, varname)
385  !
386  ! -- if param is tracked set read state
387  if (iparam > 0) then
388  this%param_reads(iparam)%invar = 1
389  end if
390  !
391  ! -- return
392  return
393  end subroutine bndgrid_param_load
394 
395  subroutine bndgrid_tas_arrays_alloc(this)
396  ! -- modules
398  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
399  !
400  ! -- count params other than AUX
401  if (this%tas_active /= 0) then
402  !
403  call mem_allocate(this%aux_tasnames, lentimeseriesname, &
404  this%bound_context%naux, 'AUXTASNAME', &
405  this%mf6_input%mempath)
406  call mem_allocate(this%param_tasnames, lentimeseriesname, this%nparam, &
407  'PARAMTASNAME', this%mf6_input%mempath)
408  !
409  call this%init_charstr1d('AUXTASNAME', this%input_name)
410  call this%init_charstr1d('PARAMTASNAME', this%input_name)
411  !
412  else
413  !
414  call mem_allocate(this%aux_tasnames, lentimeseriesname, 0, &
415  'AUXTASNAME', this%mf6_input%mempath)
416  call mem_allocate(this%param_tasnames, lentimeseriesname, 0, &
417  'PARAMTASNAME', this%mf6_input%mempath)
418  !
419  end if
420  !
421  ! -- return
422  return
423  end subroutine bndgrid_tas_arrays_alloc
424 
425  ! FLUX and SFAC are handled in model context
426  subroutine bndgrid_tas_links_create(this, inunit)
427  ! -- modules
430  ! -- dummy
431  class(boundgridinputtype), intent(inout) :: this !< BoundGridInputType
432  integer(I4B), intent(in) :: inunit
433  ! -- local
434  type(inputparamdefinitiontype), pointer :: idt
435  ! -- non-contiguous because a slice of bound is passed
436  real(DP), dimension(:), pointer :: auxArrayPtr, bndArrayPtr
437  real(DP), dimension(:), pointer, contiguous :: bound
438  integer(I4B), dimension(:), pointer, contiguous :: nodelist
439  character(len=LENTIMESERIESNAME) :: tas_name
440  character(len=LENAUXNAME) :: aux_name
441  logical :: convertFlux
442  integer(I4B) :: n
443  !
444  ! -- initialize
445  nullify (auxarrayptr)
446  nullify (bndarrayptr)
447  nullify (nodelist)
448  convertflux = .false.
449  !
450  ! Create AUX Time Array Series links
451  do n = 1, this%bound_context%naux
452  tas_name = this%aux_tasnames(n)
453  !
454  if (tas_name /= '') then
455  ! -- set auxvar pointer
456  auxarrayptr => this%bound_context%auxvar(n, :)
457  aux_name = this%bound_context%auxname_cst(n)
458  call this%tasmanager%MakeTasLink(this%mf6_input%subcomponent_name, &
459  auxarrayptr, this%bound_context%iprpak, &
460  tas_name, aux_name, convertflux, &
461  nodelist, inunit)
462  end if
463  end do
464  !
465  ! Create BND Time Array Series links
466  do n = 1, this%nparam
467  ! -- assign param definition pointer
468  idt => get_param_definition_type(this%mf6_input%param_dfns, &
469  this%mf6_input%component_type, &
470  this%mf6_input%subcomponent_type, &
471  'PERIOD', this%param_names(n), &
472  this%input_name)
473  !
474  if (idt%timeseries) then
475  if (this%param_reads(n)%invar == 2) then
476  tas_name = this%param_tasnames(n)
477  call mem_setptr(bound, idt%mf6varname, this%mf6_input%mempath)
478  ! -- set bound pointer
479  bndarrayptr => bound(:)
480  call this%tasmanager%MakeTasLink(this%mf6_input%subcomponent_name, &
481  bndarrayptr, &
482  this%bound_context%iprpak, &
483  tas_name, idt%mf6varname, &
484  convertflux, nodelist, inunit)
485  end if
486  end if
487  end do
488  !
489  ! -- return
490  return
491  end subroutine bndgrid_tas_links_create
492 
493 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:44
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 izero
integer constant zero
Definition: Constants.f90:50
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
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:57
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
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_param_load(this, parser, datatype, varname, tagname, shapestr, mempath, iaux)
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_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)
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:47
Ascii grid based dynamic loader type.
derived type for storing input definition for a file