MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
LoadContext.f90
Go to the documentation of this file.
1 !> @brief This module contains the LoadContextModule
2 !!
3 !! This module creates a load context for IDM generic
4 !! loaders (ListLoadType, LayerArrayLoadType, GridArrayLoadType)
5 !! that supports consistent package side access. It also
6 !! determines in scope parameters for the generic dynamic
7 !! loaders and all structarray based static loads.
8 !!
9 !<
11 
12  use kindmodule, only: dp, i4b, lgp
15  use simvariablesmodule, only: errmsg
20 
21  implicit none
22  private
23  public :: loadcontexttype
24  public :: readstatevartype
25  public :: rsv_name
26 
27  enum, bind(C)
28  enumerator :: load_undef = 0 !< undefined load type
29  enumerator :: list = 1 !< list (structarray) based load
30  enumerator :: layerarray = 2 !< readasarrays load
31  enumerator :: gridarray = 3 !< readarraygrid load
32  end enum
33 
34  enum, bind(C)
35  enumerator :: context_undef = 0 !< undefined context type
36  enumerator :: root = 1 !< root context type
37  enumerator :: sim = 2 !< sim context type
38  enumerator :: model = 3 !< model context type
39  enumerator :: modelpkg = 4 !< model package context type
40  enumerator :: stresspkg = 5 !< model stress package context type
41  enumerator :: exchange = 6 !< exchange context type
42  end enum
43 
44  !> @brief Pointer type for read state variable
45  !<
47  integer(I4B), pointer :: invar
48  end type readstatevartype
49 
50  interface setptr
51  module procedure setptr_int, setptr_charstr1d, &
53  end interface setptr
54 
55  !> @brief derived type for boundary package input context
56  !!
57  !! Input Load Context for generic dynamic loaders and
58  !! StructArray based static loads
59  !!
60  !<
62  character(len=LENVARNAME) :: blockname !< load block name
63  character(len=LENVARNAME) :: named_bound !< name of dimensions relevant to load
64  integer(I4B), pointer :: naux => null() !< number of auxiliary variables
65  integer(I4B), pointer :: maxbound => null() !< value associated with named_bound
66  integer(I4B), pointer :: boundnames => null() !< are bound names optioned
67  integer(I4B), pointer :: iprpak => null() ! print input option
68  integer(I4B), pointer :: nbound => null() !< number of bounds in period
69  integer(I4B), pointer :: ncpl => null() !< ncpl associated with model shape
70  integer(I4B), pointer :: nodes => null() !< nodes associated with model shape
71  integer(I4B) :: loadtype !< enum load type
72  integer(I4B) :: ctxtype !< enum context type
73  logical(LGP) :: readarray !< is this an array based load
74  type(characterstringtype), dimension(:), pointer, &
75  contiguous :: auxname_cst => null() !< array of auxiliary names
76  type(characterstringtype), dimension(:), pointer, &
77  contiguous :: boundname_cst => null() !< array of bound names
78  real(dp), dimension(:, :), pointer, &
79  contiguous :: auxvar => null() !< auxiliary variable array
80  integer(I4B), dimension(:), pointer, contiguous :: mshape => null() !< model shape
81  character(len=LINELENGTH), dimension(:), allocatable :: params !< in scope param tags
82  type(modflowinputtype) :: mf6_input !< description of input
83  contains
84  procedure :: init
85  procedure :: allocate_scalars
86  procedure :: allocate_arrays
87  procedure :: allocate_param
88  procedure :: tags
89  procedure :: in_scope
90  procedure :: set_params
91  procedure :: rsv_alloc
92  procedure :: destroy
93  end type loadcontexttype
94 
95 contains
96 
97  !> @brief init loader context object
98  !<
99  subroutine init(this, mf6_input, blockname, named_bound)
100  use inputoutputmodule, only: upcase
102  class(loadcontexttype) :: this
103  type(modflowinputtype), intent(in) :: mf6_input
104  character(len=*), optional, intent(in) :: blockname
105  character(len=*), optional, intent(in) :: named_bound
106  type(inputparamdefinitiontype), pointer :: idt
107  integer(I4B) :: n
108 
109  this%mf6_input = mf6_input
110  this%readarray = .false.
111  this%loadtype = load_undef
112  this%ctxtype = context_undef
113 
114  select case (mf6_input%load_scope)
115  case ('ROOT')
116  this%ctxtype = root
117  case ('SIM')
118  if (mf6_input%subcomponent_type == 'NAM') then
119  this%ctxtype = model
120  else if (mf6_input%subcomponent_type == 'TDIS' .or. &
121  mf6_input%subcomponent_type == 'HPC') then
122  this%ctxtype = sim
123  else if (mf6_input%component_type == 'EXG') then
124  this%ctxtype = exchange
125  end if
126  case ('MODEL')
127  if (mf6_input%subcomponent_type == 'OC' .or. &
128  mf6_input%subcomponent_type == 'STO') then
129  this%ctxtype = modelpkg
130  else
131  this%ctxtype = stresspkg
132  end if
133  case default
134  end select
135 
136  if (this%ctxtype == context_undef) then
137  errmsg = 'LoadContext unidentified context for mempath: '// &
138  trim(mf6_input%mempath)
139  call store_error(errmsg, .true.)
140  end if
141 
142  if (present(blockname)) then
143  this%blockname = blockname
144  call upcase(this%blockname)
145  else
146  this%blockname = 'PERIOD'
147  end if
148 
149  if (present(named_bound)) then
150  this%named_bound = named_bound
151  call upcase(this%named_bound)
152  else
153  this%named_bound = 'MAXBOUND'
154  end if
155 
156  ! determine if list based load
157  do n = 1, size(mf6_input%block_dfns)
158  if (mf6_input%block_dfns(n)%blockname == this%blockname) then
159  if (mf6_input%block_dfns(n)%aggregate) then
160  this%loadtype = list
161  end if
162  end if
163  end do
164 
165  ! determine if array based load
166  if (this%loadtype == load_undef) then
167  do n = 1, size(mf6_input%param_dfns)
168  idt => mf6_input%param_dfns(n)
169  if (idt%blockname == 'OPTIONS') then
170  select case (idt%tagname)
171  case ('READASARRAYS')
172  this%loadtype = layerarray
173  this%readarray = .true.
174  case ('READARRAYGRID')
175  this%loadtype = gridarray
176  this%readarray = .true.
177  case default
178  ! no-op
179  end select
180  end if
181  end do
182  end if
183 
184  ! set in scope params for load
185  call this%set_params()
186 
187  ! allocate load context scalars
188  call this%allocate_scalars()
189  end subroutine init
190 
191  !> @brief allocate scalars
192  !<
193  subroutine allocate_scalars(this)
195  class(loadcontexttype) :: this
196 
197  if (this%ctxtype == exchange .or. &
198  this%ctxtype == modelpkg .or. &
199  this%ctxtype == stresspkg) then
200 
201  call setptr(this%nbound, 'NBOUND', this%mf6_input%mempath)
202  call setval(this%naux, 'NAUX', this%mf6_input%mempath)
203  call setval(this%ncpl, 'NCPL', this%mf6_input%mempath)
204  call setval(this%nodes, 'NODES', this%mf6_input%mempath)
205  call setval(this%maxbound, this%named_bound, this%mf6_input%mempath)
206  call setval(this%boundnames, 'BOUNDNAMES', this%mf6_input%mempath)
207  call setval(this%iprpak, 'IPRPAK', this%mf6_input%mempath)
208 
209  ! reset nbound
210  this%nbound = 0
211  end if
212 
213  if (this%ctxtype == stresspkg .and. &
214  this%blockname == 'PERIOD') then
215  call mem_setptr(this%mshape, 'MODEL_SHAPE', &
216  this%mf6_input%component_mempath)
217 
218  if (this%ncpl == 0) then
219  if (size(this%mshape) == 2) then
220  this%ncpl = this%mshape(2)
221  else if (size(this%mshape) == 3) then
222  this%ncpl = this%mshape(2) * this%mshape(3)
223  end if
224  end if
225 
226  if (this%nodes == 0) this%nodes = product(this%mshape)
227  end if
228  end subroutine allocate_scalars
229 
230  !> @brief allocate arrays
231  !!
232  !! call this routine after input parameters have been allocated,
233  !! e.g. after load_params() with create has been called for array
234  !! based loaders or after all mem_create_vector() calls have
235  !! been made for list based load.
236  !!
237  !<
238  subroutine allocate_arrays(this)
240  class(loadcontexttype) :: this
241  integer(I4B), dimension(:, :), pointer, contiguous :: cellid
242  integer(I4B), dimension(:), pointer, contiguous :: nodeulist
243 
244  if (this%ctxtype == stresspkg .and. &
245  this%blockname == 'PERIOD') then
246  ! allocate cellid if this is not list input
247  if (this%readarray) then
248  call mem_allocate(cellid, 0, 0, 'CELLID', this%mf6_input%mempath)
249  end if
250 
251  ! allocate nodeulist
252  if (this%loadtype /= gridarray) then
253  call mem_allocate(nodeulist, 0, 'NODEULIST', this%mf6_input%mempath)
254  end if
255 
256  ! set pointers to arrays
257  call setptr(this%auxname_cst, 'AUXILIARY', &
258  this%mf6_input%mempath, lenauxname)
259  call setptr(this%boundname_cst, 'BOUNDNAME', &
260  this%mf6_input%mempath, lenboundname)
261  call setptr(this%auxvar, this%mf6_input%mempath)
262 
263  else if (this%ctxtype == exchange) then
264  ! set pointers to arrays
265  call setptr(this%auxname_cst, 'AUXILIARY', &
266  this%mf6_input%mempath, lenauxname)
267  call setptr(this%boundname_cst, 'BOUNDNAME', &
268  this%mf6_input%mempath, lenboundname)
269  call setptr(this%auxvar, this%mf6_input%mempath)
270  end if
271  end subroutine allocate_arrays
272 
273  !> @brief allocate a package dynamic input parameter
274  !<
275  subroutine allocate_param(this, idt)
277  class(loadcontexttype) :: this
278  type(inputparamdefinitiontype), pointer :: idt
279  integer(I4B) :: dimsize
280 
281  ! initialize
282  dimsize = 0
283 
284  if (this%readarray) then
285  select case (idt%shape)
286  case ('NCPL', 'NAUX NCPL')
287  dimsize = this%ncpl
288  case ('NODES', 'NAUX NODES')
289  dimsize = this%maxbound
290  case default
291  end select
292  end if
293 
294  select case (idt%datatype)
295  case ('INTEGER')
296  if (this%loadtype == list) then
297  call allocate_int1d(this%maxbound, idt%mf6varname, &
298  this%mf6_input%mempath)
299  end if
300  case ('DOUBLE')
301  if (this%loadtype == list) then
302  call allocate_dbl1d(this%maxbound, idt%mf6varname, &
303  this%mf6_input%mempath)
304  end if
305  case ('STRING')
306  if (this%loadtype == list) then
307  call allocate_charstr1d(lenboundname, this%maxbound, idt%mf6varname, &
308  this%mf6_input%mempath)
309  end if
310  case ('INTEGER1D')
311  if (this%loadtype == list) then
312  if (idt%shape == 'NCELLDIM') then
313  call allocate_int2d(size(this%mshape), this%maxbound, &
314  idt%mf6varname, this%mf6_input%mempath)
315  end if
316  else if (this%readarray) then
317  call allocate_int1d(dimsize, idt%mf6varname, &
318  this%mf6_input%mempath)
319  end if
320  case ('DOUBLE1D')
321  if (idt%shape == 'NAUX') then
322  call allocate_dbl2d(this%naux, this%maxbound, &
323  idt%mf6varname, this%mf6_input%mempath)
324  else if (this%readarray) then
325  call allocate_dbl1d(dimsize, idt%mf6varname, &
326  this%mf6_input%mempath)
327  end if
328  case ('DOUBLE2D')
329  if (this%readarray) then
330  call allocate_dbl2d(this%naux, dimsize, idt%mf6varname, &
331  this%mf6_input%mempath)
332  end if
333  case default
334  end select
335  end subroutine allocate_param
336 
337  !> @brief get in scope package params
338  !!
339  !! set input array to tagnames of in scope params, optionally
340  !! allocate the parameters based on datatype.
341  !!
342  !<
343  subroutine tags(this, params, nparam, input_name, create)
344  use devfeaturemodule, only: dev_feature
345  use simvariablesmodule, only: iout
347  class(loadcontexttype) :: this
348  character(len=LINELENGTH), dimension(:), allocatable, &
349  intent(inout) :: params
350  integer(I4B), intent(inout) :: nparam
351  character(len=*), intent(in) :: input_name
352  logical(LGP), optional, intent(in) :: create
353  type(inputparamdefinitiontype), pointer :: idt
354  character(len=LINELENGTH) :: dev_msg
355  logical(LGP) :: allocate_params
356  integer(I4B) :: n
357 
358  ! initialize allocate_params
359  allocate_params = .false.
360 
361  ! override default if provided
362  if (present(create)) then
363  allocate_params = create
364  end if
365 
366  if (allocated(params)) deallocate (params)
367  nparam = size(this%params)
368  allocate (params(nparam))
369  do n = 1, nparam
370  idt => &
371  get_param_definition_type(this%mf6_input%param_dfns, &
372  this%mf6_input%component_type, &
373  this%mf6_input%subcomponent_type, &
374  this%blockname, this%params(n), '')
375 
376  ! check if input param is prerelease
377  if (idt%prerelease) then
378  dev_msg = 'Input tag "'//trim(idt%tagname)// &
379  &'" read from file "'//trim(input_name)// &
380  &'" is still under development. Install the &
381  &nightly build or compile from source with IDEVELOPMODE = 1.'
382  call dev_feature(dev_msg, iout)
383  end if
384 
385  params(n) = this%params(n)
386  if (allocate_params) call this%allocate_param(idt)
387  end do
388  end subroutine tags
389 
390  !> @brief establish if input parameter is in scope for package load
391  !<
392  function in_scope(this, mf6_input, blockname, tagname)
395  class(loadcontexttype) :: this
396  type(modflowinputtype), intent(in) :: mf6_input
397  character(len=*), intent(in) :: blockname
398  character(len=*), intent(in) :: tagname
399  logical(LGP) :: in_scope
400  type(inputparamdefinitiontype), pointer :: idt
401  character(len=LENVARNAME) :: checkname
402  character(len=LINELENGTH) :: datatype
403  integer(I4B) :: isize, checksize
404  integer(I4B), pointer :: intptr
405 
406  idt => &
407  get_param_definition_type(mf6_input%param_dfns, &
408  mf6_input%component_type, &
409  mf6_input%subcomponent_type, &
410  blockname, tagname, '')
411  if (idt%required) then
412  in_scope = .true.
413  return
414  else
415  in_scope = .false.
416  datatype = idt_datatype(idt)
417  if (datatype == 'KEYSTRING' .or. &
418  datatype == 'RECARRAY' .or. &
419  datatype == 'RECORD') return
420  end if
421 
422  ! initialize
423  checkname = ''
424  checksize = 0
425 
426  if (tagname == 'AUXVAR' .or. &
427  tagname == 'AUX') then
428  checkname = 'NAUX'
429  else if (tagname == 'BOUNDNAME') then
430  checkname = 'BOUNDNAMES'
431  else if (tagname == 'I'//trim(mf6_input%subcomponent_type(1:3))) then
432  if (this%loadtype == layerarray) in_scope = .true.
433  else
434  select case (mf6_input%subcomponent_type)
435  case ('EVT')
436  if (tagname == 'PXDP' .or. tagname == 'PETM') then
437  checkname = 'NSEG'
438  checksize = 1
439  else if (tagname == 'PETM0') then
440  checkname = 'SURFRATESPEC'
441  end if
442  case ('MVR', 'MVT', 'MVE')
443  if (tagname == 'MNAME' .or. &
444  tagname == 'MNAME1' .or. &
445  tagname == 'MNAME2') then
446  checkname = 'MODELNAMES'
447  end if
448  case ('NAM')
449  in_scope = .true.
450  case ('SSM')
451  if (tagname == 'MIXED') in_scope = .true.
452  case default
453  errmsg = 'LoadContext in_scope needs new check for: '// &
454  trim(idt%tagname)
455  call store_error(errmsg, .true.)
456  end select
457  end if
458 
459  ! apply checks
460  if (.not. in_scope) then
461  call get_isize(checkname, mf6_input%mempath, isize)
462  if (isize > 0) then
463  call mem_setptr(intptr, checkname, mf6_input%mempath)
464  if (intptr > checksize) in_scope = .true.
465  end if
466  end if
467  end function in_scope
468 
469  !> @brief set set of in scope parameters for package
470  !<
471  subroutine set_params(this)
476  class(loadcontexttype) :: this
477  type(inputparamdefinitiontype), pointer :: idt, aidt
478  character(len=LINELENGTH), dimension(:), allocatable :: tags
479  character(len=LINELENGTH), dimension(:), allocatable :: cols
480  integer(I4B) :: keepcnt, iparam, nparam
481  logical(LGP) :: keep
482 
483  ! initialize
484  keepcnt = 0
485 
486  if (this%loadtype == list) then
487  ! get aggregate param definition for period block
488  aidt => &
489  get_aggregate_definition_type(this%mf6_input%aggregate_dfns, &
490  this%mf6_input%component_type, &
491  this%mf6_input%subcomponent_type, &
492  this%blockname)
493  ! split recarray definition
494  call idt_parse_rectype(aidt, cols, nparam)
495  else
496  nparam = size(this%mf6_input%param_dfns)
497  end if
498 
499  ! allocate dfn input params
500  do iparam = 1, nparam
501  if (this%loadtype == list) then
502  idt => get_param_definition_type(this%mf6_input%param_dfns, &
503  this%mf6_input%component_type, &
504  this%mf6_input%subcomponent_type, &
505  this%blockname, cols(iparam), '')
506  else
507  idt => this%mf6_input%param_dfns(iparam)
508  end if
509 
510  if (idt%blockname /= this%blockname) then
511  keep = .false.
512  else
513  keep = this%in_scope(this%mf6_input, this%blockname, idt%tagname)
514  end if
515 
516  if (keep) then
517  keepcnt = keepcnt + 1
518  call expandarray(tags)
519  tags(keepcnt) = trim(idt%tagname)
520  end if
521  end do
522 
523  ! update nparam
524  nparam = keepcnt
525 
526  ! allocate filtcols
527  allocate (this%params(nparam))
528 
529  ! set filtcols
530  do iparam = 1, nparam
531  this%params(iparam) = trim(tags(iparam))
532  end do
533 
534  ! cleanup
535  if (allocated(tags)) deallocate (tags)
536  end subroutine set_params
537 
538  !> @brief allocate a read state variable
539  !!
540  !! Create and set a read state variable, e.g. 'INRECHARGE',
541  !! which are updated per iper load as follows:
542  !! -1: unset, not in use
543  !! 0: not read in most recent period block
544  !! 1: numeric input read in most recent period block
545  !! 2: time series input read in most recent period block
546  !!
547  !<
548  function rsv_alloc(this, mf6varname) result(varname)
549  use constantsmodule, only: lenvarname
551  class(loadcontexttype) :: this
552  character(len=*), intent(in) :: mf6varname
553  character(len=LENVARNAME) :: varname
554  integer(I4B), pointer :: intvar
555  varname = rsv_name(mf6varname)
556  call mem_allocate(intvar, varname, this%mf6_input%mempath)
557  intvar = -1
558  end function rsv_alloc
559 
560  !> @brief destroy input context object
561  !<
562  subroutine destroy(this)
563  class(loadcontexttype) :: this
564 
565  if (this%ctxtype == exchange .or. &
566  this%ctxtype == stresspkg) then
567  ! deallocate local
568  deallocate (this%naux)
569  deallocate (this%ncpl)
570  deallocate (this%nodes)
571  deallocate (this%maxbound)
572  deallocate (this%boundnames)
573  deallocate (this%iprpak)
574  end if
575 
576  ! nullify
577  nullify (this%naux)
578  nullify (this%nbound)
579  nullify (this%ncpl)
580  nullify (this%nodes)
581  nullify (this%maxbound)
582  nullify (this%boundnames)
583  nullify (this%iprpak)
584  nullify (this%auxname_cst)
585  nullify (this%boundname_cst)
586  nullify (this%auxvar)
587  nullify (this%mshape)
588  end subroutine destroy
589 
590  !> @brief create read state variable name
591  !<
592  function rsv_name(mf6varname) result(varname)
593  use constantsmodule, only: lenvarname
594  character(len=*), intent(in) :: mf6varname
595  character(len=LENVARNAME) :: varname
596  integer(I4B) :: ilen
597  character(len=2) :: prefix = 'IN'
598  ilen = len_trim(mf6varname)
599  if (ilen > (lenvarname - len(prefix))) then
600  varname = prefix//mf6varname(1:(lenvarname - len(prefix)))
601  else
602  varname = prefix//trim(mf6varname)
603  end if
604  end function rsv_name
605 
606  !> @brief allocate character string type array
607  !<
608  subroutine allocate_charstr1d(strlen, nrow, varname, mempath)
610  integer(I4B), intent(in) :: strlen !< string number of characters
611  integer(I4B), intent(in) :: nrow !< integer array number of rows
612  character(len=*), intent(in) :: varname !< variable name
613  character(len=*), intent(in) :: mempath !< variable mempath
614  type(characterstringtype), dimension(:), pointer, &
615  contiguous :: charstr1d
616  integer(I4B) :: n
617  call mem_allocate(charstr1d, strlen, nrow, varname, mempath)
618  do n = 1, nrow
619  charstr1d(n) = ''
620  end do
621  end subroutine allocate_charstr1d
622 
623  !> @brief allocate int1d
624  !<
625  subroutine allocate_int1d(nrow, varname, mempath)
627  integer(I4B), intent(in) :: nrow !< integer array number of rows
628  character(len=*), intent(in) :: varname !< variable name
629  character(len=*), intent(in) :: mempath !< variable mempath
630  integer(I4B), dimension(:), pointer, contiguous :: int1d
631  integer(I4B) :: n
632  call mem_allocate(int1d, nrow, varname, mempath)
633  do n = 1, nrow
634  int1d(n) = izero
635  end do
636  end subroutine allocate_int1d
637 
638  !> @brief allocate int2d
639  !<
640  subroutine allocate_int2d(ncol, nrow, varname, mempath)
642  integer(I4B), intent(in) :: ncol !< integer array number of cols
643  integer(I4B), intent(in) :: nrow !< integer array number of rows
644  character(len=*), intent(in) :: varname !< variable name
645  character(len=*), intent(in) :: mempath !< variable mempath
646  integer(I4B), dimension(:, :), pointer, contiguous :: int2d
647  integer(I4B) :: n, m
648  call mem_allocate(int2d, ncol, nrow, varname, mempath)
649  do m = 1, nrow
650  do n = 1, ncol
651  int2d(n, m) = izero
652  end do
653  end do
654  end subroutine allocate_int2d
655 
656  !> @brief allocate dbl1d
657  !<
658  subroutine allocate_dbl1d(nrow, varname, mempath)
660  integer(I4B), intent(in) :: nrow !< integer array number of rows
661  character(len=*), intent(in) :: varname !< variable name
662  character(len=*), intent(in) :: mempath !< variable mempath
663  real(DP), dimension(:), pointer, contiguous :: dbl1d
664  integer(I4B) :: n
665  call mem_allocate(dbl1d, nrow, varname, mempath)
666  do n = 1, nrow
667  dbl1d(n) = dzero
668  end do
669  end subroutine allocate_dbl1d
670 
671  !> @brief allocate dbl2d
672  !<
673  subroutine allocate_dbl2d(ncol, nrow, varname, mempath)
675  integer(I4B), intent(in) :: ncol !< integer array number of cols
676  integer(I4B), intent(in) :: nrow !< integer array number of rows
677  character(len=*), intent(in) :: varname !< variable name
678  character(len=*), intent(in) :: mempath !< variable mempath
679  real(DP), dimension(:, :), pointer, contiguous :: dbl2d
680  integer(I4B) :: n, m
681  call mem_allocate(dbl2d, ncol, nrow, varname, mempath)
682  do m = 1, nrow
683  do n = 1, ncol
684  dbl2d(n, m) = dzero
685  end do
686  end do
687  end subroutine allocate_dbl2d
688 
689  !> @brief allocate intptr and update from input contextset intptr to varname
690  !!
691  !<
692  subroutine setval(intptr, varname, mempath)
694  integer(I4B), pointer, intent(inout) :: intptr
695  character(len=*), intent(in) :: varname
696  character(len=*), intent(in) :: mempath
697  logical(LGP) :: found
698  allocate (intptr)
699  intptr = 0
700  call mem_set_value(intptr, varname, mempath, found)
701  end subroutine setval
702 
703  !> @brief set intptr to varname
704  !!
705  !<
706  subroutine setptr_int(intptr, varname, mempath)
708  integer(I4B), pointer, intent(inout) :: intptr
709  character(len=*), intent(in) :: varname
710  character(len=*), intent(in) :: mempath
711  integer(I4B) :: isize
712  call get_isize(varname, mempath, isize)
713  if (isize > -1) then
714  call mem_setptr(intptr, varname, mempath)
715  else
716  call mem_allocate(intptr, varname, mempath)
717  intptr = 0
718  end if
719  end subroutine setptr_int
720 
721  !> @brief set charstr1d pointer to varname
722  !<
723  subroutine setptr_charstr1d(charstr1d, varname, mempath, strlen)
725  type(characterstringtype), dimension(:), pointer, &
726  contiguous, intent(inout) :: charstr1d
727  character(len=*), intent(in) :: varname
728  character(len=*), intent(in) :: mempath
729  integer(I4B), intent(in) :: strlen
730  integer(I4B) :: isize
731  call get_isize(varname, mempath, isize)
732  if (isize > -1) then
733  call mem_setptr(charstr1d, varname, mempath)
734  else
735  call mem_allocate(charstr1d, strlen, 0, varname, mempath)
736  end if
737  end subroutine setptr_charstr1d
738 
739  !> @brief set auxvar pointer
740  !!
741  !<
742  subroutine setptr_auxvar(auxvar, mempath)
744  real(DP), dimension(:, :), pointer, &
745  contiguous, intent(inout) :: auxvar
746  character(len=*), intent(in) :: mempath
747  integer(I4B) :: isize
748  call get_isize('AUXVAR', mempath, isize)
749  if (isize > -1) then
750  call mem_setptr(auxvar, 'AUXVAR', mempath)
751  else
752  call mem_allocate(auxvar, 0, 0, 'AUXVAR', mempath)
753  end if
754  end subroutine setptr_auxvar
755 
756 end module loadcontextmodule
subroutine init()
Definition: GridSorting.f90:24
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 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 lenboundname
maximum length of a bound name
Definition: Constants.f90:36
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.
type(inputparamdefinitiontype) function, pointer, public get_aggregate_definition_type(input_definition_types, component_type, subcomponent_type, blockname)
Return aggregate definition.
subroutine, public idt_parse_rectype(idt, cols, ncol)
allocate and set RECARRAY, KEYSTRING or RECORD param list
character(len=linelength) function, public idt_datatype(idt)
return input definition type datatype
Disable development features in release mode.
Definition: DevFeature.f90:2
subroutine, public dev_feature(errmsg, iunit)
Terminate if in release mode (guard development features)
Definition: DevFeature.f90:21
This module contains the InputDefinitionModule.
subroutine, public upcase(word)
Convert to upper case.
This module defines variable data types.
Definition: kind.f90:8
This module contains the LoadContextModule.
Definition: LoadContext.f90:10
subroutine set_params(this)
set set of in scope parameters for package
subroutine allocate_dbl2d(ncol, nrow, varname, mempath)
allocate dbl2d
subroutine tags(this, params, nparam, input_name, create)
get in scope package params
subroutine setptr_auxvar(auxvar, mempath)
set auxvar pointer
subroutine allocate_charstr1d(strlen, nrow, varname, mempath)
allocate character string type array
subroutine allocate_int1d(nrow, varname, mempath)
allocate int1d
@ load_undef
undefined load type
Definition: LoadContext.f90:28
@ gridarray
readarraygrid load
Definition: LoadContext.f90:31
@ layerarray
readasarrays load
Definition: LoadContext.f90:30
@ list
list (structarray) based load
Definition: LoadContext.f90:29
subroutine allocate_dbl1d(nrow, varname, mempath)
allocate dbl1d
@ stresspkg
model stress package context type
Definition: LoadContext.f90:40
@ exchange
exchange context type
Definition: LoadContext.f90:41
@ model
model context type
Definition: LoadContext.f90:38
@ root
root context type
Definition: LoadContext.f90:36
@ modelpkg
model package context type
Definition: LoadContext.f90:39
@ sim
sim context type
Definition: LoadContext.f90:37
@ context_undef
undefined context type
Definition: LoadContext.f90:35
subroutine setval(intptr, varname, mempath)
allocate intptr and update from input contextset intptr to varname
subroutine allocate_scalars(this)
allocate scalars
subroutine allocate_param(this, idt)
allocate a package dynamic input parameter
subroutine allocate_arrays(this)
allocate arrays
subroutine setptr_int(intptr, varname, mempath)
set intptr to varname
subroutine allocate_int2d(ncol, nrow, varname, mempath)
allocate int2d
subroutine destroy(this)
destroy input context object
character(len=lenvarname) function, public rsv_name(mf6varname)
create read state variable name
logical(lgp) function in_scope(this, mf6_input, blockname, tagname)
establish if input parameter is in scope for package load
character(len=lenvarname) function rsv_alloc(this, mf6varname)
allocate a read state variable
subroutine setptr_charstr1d(charstr1d, varname, mempath, strlen)
set charstr1d pointer to varname
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains the ModelPackageInputsModule.
logical(lgp) function, public supported_model(ctype)
is this a supported MODFLOW 6 model type
This module contains the ModflowInputModule.
Definition: ModflowInput.f90:9
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
integer(i4b) iout
file unit number for simulation output
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
derived type for boundary package input context
Definition: LoadContext.f90:61
Pointer type for read state variable.
Definition: LoadContext.f90:46
derived type for storing input definition for a file