MODFLOW 6  version 6.7.0.dev0
USGS Modular Hydrologic Model
IdmLoad.f90
Go to the documentation of this file.
1 !> @brief This module contains the IdmLoadModule
2 !!
3 !! This module contains routines for managing static
4 !! and dynamic input loading for supported sources.
5 !!
6 !<
8 
9  use kindmodule, only: dp, i4b, lgp
10  use simvariablesmodule, only: errmsg
14  use listmodule, only: listtype
21 
22  implicit none
23  private
24  public :: simnam_load
25  public :: simtdis_load
26  public :: load_models
27  public :: load_exchanges
28  public :: idm_df
29  public :: idm_rp
30  public :: idm_ad
31  public :: idm_da
32 
33 contains
34 
35  !> @brief advance package dynamic data for period steps
36  !<
37  subroutine idm_df()
39  class(modeldynamicpkgstype), pointer :: model_dynamic_input
40  integer(I4B) :: n
41  do n = 1, model_dynamic_pkgs%Count()
42  model_dynamic_input => getdynamicmodelfromlist(model_dynamic_pkgs, n)
43  call model_dynamic_input%df()
44  end do
45  end subroutine idm_df
46 
47  !> @brief load package dynamic data for period
48  !<
49  subroutine idm_rp()
51  class(modeldynamicpkgstype), pointer :: model_dynamic_input
52  integer(I4B) :: n
53  do n = 1, model_dynamic_pkgs%Count()
54  model_dynamic_input => getdynamicmodelfromlist(model_dynamic_pkgs, n)
55  call model_dynamic_input%rp()
56  end do
57  end subroutine idm_rp
58 
59  !> @brief advance package dynamic data for period steps
60  !<
61  subroutine idm_ad()
63  class(modeldynamicpkgstype), pointer :: model_dynamic_input
64  integer(I4B) :: n
65  do n = 1, model_dynamic_pkgs%Count()
66  model_dynamic_input => getdynamicmodelfromlist(model_dynamic_pkgs, n)
67  call model_dynamic_input%ad()
68  end do
69  end subroutine idm_ad
70 
71  !> @brief idm deallocate routine
72  !<
73  subroutine idm_da(iout)
79  integer(I4B), intent(in) :: iout
80  type(characterstringtype), dimension(:), contiguous, &
81  pointer :: mempaths
82  character(len=LENCOMPONENTNAME) :: exg_comp, exg_subcomp
83  character(len=LENMEMPATH) :: input_mempath, mempath
84  integer(I4B) :: n
85 
86  ! deallocate dynamic loaders
87  call dynamic_da(iout)
88 
89  ! deallocate EXG mempaths
90  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
91  call mem_setptr(mempaths, 'EXGMEMPATHS', input_mempath)
92  do n = 1, size(mempaths)
93  mempath = mempaths(n)
94  if (mempath /= '') then
95  call split_mem_path(mempath, exg_comp, exg_subcomp)
96  call memorystore_remove(exg_comp, exg_subcomp, idm_context)
97  end if
98  end do
99 
100  ! deallocate input context SIM paths
101  call memorystore_remove('UTL', 'HPC', idm_context)
102  call memorystore_remove('SIM', 'TDIS', idm_context)
103  call memorystore_remove('SIM', 'NAM', idm_context)
104  call memorystore_remove(component='SIM', context=idm_context)
105  end subroutine idm_da
106 
107  !> @brief load an integrated model package from supported source
108  !<
109  recursive subroutine input_load(component_type, subcomponent_type, modelname, &
110  pkgname, pkgtype, filename, modelfname, &
111  nc_vars, iout)
115  character(len=*), intent(in) :: component_type
116  character(len=*), intent(in) :: subcomponent_type
117  character(len=*), intent(in) :: pkgname
118  character(len=*), intent(in) :: pkgtype
119  character(len=*), intent(in) :: filename
120  character(len=*), intent(in) :: modelname
121  character(len=*), intent(in) :: modelfname
122  type(ncfilevarstype), pointer, intent(in) :: nc_vars
123  integer(I4B), intent(in) :: iout
124  class(staticpkgloadbasetype), pointer :: static_loader
125  class(dynamicpkgloadbasetype), pointer :: dynamic_loader
126  class(modeldynamicpkgstype), pointer :: dynamic_pkgs
127  integer(I4B) :: n
128 
129  ! create model package loader
130  static_loader => &
131  create_input_loader(component_type, subcomponent_type, modelname, pkgname, &
132  pkgtype, filename, modelfname, nc_vars)
133 
134  ! load static input and set dynamic loader
135  dynamic_loader => static_loader%load(iout)
136 
137  if (associated(dynamic_loader)) then
138  ! set pointer to model dynamic packages list
139  dynamic_pkgs => &
140  dynamic_model_pkgs(static_loader%mf6_input%component_type, modelname, &
141  static_loader%component_input_name, nc_vars%nc_fname, &
142  nc_vars%ncid, iout)
143  ! add dynamic pkg loader to list
144  call dynamic_pkgs%add(dynamic_loader)
145  end if
146 
147  ! create subpackage list
148  call static_loader%create_subpkg_list()
149 
150  ! load idm integrated subpackages
151  do n = 1, static_loader%subpkg_list%pnum
152  ! load subpackage
153  call input_load(static_loader%subpkg_list%component_types(n), &
154  static_loader%subpkg_list%subcomponent_types(n), &
155  static_loader%mf6_input%component_name, &
156  static_loader%subpkg_list%subcomponent_types(n), &
157  static_loader%subpkg_list%pkgtypes(n), &
158  static_loader%subpkg_list%filenames(n), &
159  modelfname, nc_vars, iout)
160  end do
161 
162  ! cleanup
163  call static_loader%destroy()
164  deallocate (static_loader)
165  end subroutine input_load
166 
167  !> @brief load integrated model package files
168  !<
169  subroutine load_model_pkgs(model_pkg_inputs, iout)
174  type(modelpackageinputstype), intent(inout) :: model_pkg_inputs
175  integer(i4B), intent(in) :: iout
176  type(ncfilevarstype), pointer :: nc_vars
177  integer(I4B) :: itype, ipkg
178 
179  nc_vars => netcdf_context(model_pkg_inputs%modeltype, &
180  model_pkg_inputs%component_type, &
181  model_pkg_inputs%modelname, &
182  model_pkg_inputs%modelfname, iout)
183  ! load package instances by type
184  do itype = 1, size(model_pkg_inputs%pkglist)
185  ! load package instances
186  do ipkg = 1, model_pkg_inputs%pkglist(itype)%pnum
187  if (idm_integrated(model_pkg_inputs%component_type, &
188  model_pkg_inputs%pkglist(itype)%subcomponent_type)) &
189  then
190  ! only load if model pkg can read from input context
191  call input_load(model_pkg_inputs%component_type, &
192  model_pkg_inputs%pkglist(itype)%subcomponent_type, &
193  model_pkg_inputs%modelname, &
194  model_pkg_inputs%pkglist(itype)%pkgnames(ipkg), &
195  model_pkg_inputs%pkglist(itype)%pkgtype, &
196  model_pkg_inputs%pkglist(itype)%filenames(ipkg), &
197  model_pkg_inputs%modelfname, nc_vars, iout)
198  else
199  ! open input file for package parser
200  model_pkg_inputs%pkglist(itype)%inunits(ipkg) = &
201  open_source_file(model_pkg_inputs%pkglist(itype)%pkgtype, &
202  model_pkg_inputs%pkglist(itype)%filenames(ipkg), &
203  model_pkg_inputs%modelfname, iout)
204  end if
205  end do
206  end do
207 
208  ! cleanup
209  call nc_vars%destroy()
210  deallocate (nc_vars)
211  nullify (nc_vars)
212  end subroutine load_model_pkgs
213 
214  !> @brief load model namfiles and model package files
215  !<
216  subroutine load_models(iout)
225  integer(I4B), intent(in) :: iout
226  type(distributedsimtype), pointer :: ds
227  integer(I4B), dimension(:), pointer :: model_loadmask
228  character(len=LENMEMPATH) :: input_mempath
229  type(characterstringtype), dimension(:), contiguous, &
230  pointer :: mtypes !< model types
231  type(characterstringtype), dimension(:), contiguous, &
232  pointer :: mfnames !< model file names
233  type(characterstringtype), dimension(:), contiguous, &
234  pointer :: mnames !< model names
235  character(len=LINELENGTH) :: mtype, mfname
236  character(len=LENMODELNAME) :: mname
237  type(modelpackageinputstype), allocatable :: model_pkg_inputs
238  integer(I4B) :: n
239 
240  ! get model mask
241  ds => get_dsim()
242  model_loadmask => ds%get_load_mask()
243 
244  ! set input memory path
245  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
246 
247  ! set pointers to input context model attribute arrays
248  call mem_setptr(mtypes, 'MTYPE', input_mempath)
249  call mem_setptr(mfnames, 'MFNAME', input_mempath)
250  call mem_setptr(mnames, 'MNAME', input_mempath)
251 
252  do n = 1, size(mtypes)
253  ! attributes for this model
254  mtype = mtypes(n)
255  mfname = mfnames(n)
256  call inlen_check(mnames(n), mname, lenmodelname, 'MODELNAME')
257 
258  ! terminate if errors were detected
259  if (count_errors() > 0) then
261  end if
262 
263  ! load specified model inputs
264  if (model_loadmask(n) > 0) then
265  ! load model nam file
266  call load_modelnam(mtype, mfname, mname, iout)
267  ! create description of model packages
268  allocate (model_pkg_inputs)
269  call model_pkg_inputs%init(mtype, mfname, mname, iout)
270  ! load packages
271  call load_model_pkgs(model_pkg_inputs, iout)
272  ! publish pkg info to input context
273  call model_pkg_inputs%memload()
274  ! cleanup
275  call model_pkg_inputs%destroy()
276  deallocate (model_pkg_inputs)
277  end if
278  end do
279  end subroutine load_models
280 
281  !> @brief load exchange files
282  !<
283  subroutine load_exchanges(iout)
293  integer(I4B), intent(in) :: iout
294  type(distributedsimtype), pointer :: ds
295  integer(I4B), dimension(:), pointer :: model_loadmask
296  type(characterstringtype), dimension(:), contiguous, &
297  pointer :: etypes !< exg types
298  type(characterstringtype), dimension(:), contiguous, &
299  pointer :: efiles !< exg file names
300  type(characterstringtype), dimension(:), contiguous, &
301  pointer :: emnames_a !< model a names
302  type(characterstringtype), dimension(:), contiguous, &
303  pointer :: emnames_b !< model b names
304  type(characterstringtype), dimension(:), contiguous, &
305  pointer :: emempaths !< exg mempaths
306  type(characterstringtype), dimension(:), contiguous, &
307  pointer :: mtypes !< model types
308  type(characterstringtype), dimension(:), contiguous, &
309  pointer :: mfnames !< model file names
310  type(characterstringtype), dimension(:), contiguous, &
311  pointer :: mnames !< model names
312  character(len=LENMEMPATH) :: input_mempath, mempath
313  integer(I4B), pointer :: exgid, ncelldim
314  character(len=LINELENGTH) :: exgtype, efname, mfname
315  character(len=LENMODELNAME) :: mname1, mname2, mname
316  character(len=LENCOMPONENTNAME) :: sc_type, sc_name, mtype
317  class(staticpkgloadbasetype), pointer :: static_loader
318  class(dynamicpkgloadbasetype), pointer :: dynamic_loader
319  integer(I4B) :: n, m1_idx, m2_idx, irem, isize
320 
321  ! get model mask
322  ds => get_dsim()
323  model_loadmask => ds%get_load_mask()
324 
325  ! set input memory path
326  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
327 
328  ! set pointers to input context exg and model attribute arrays
329  call mem_setptr(etypes, 'EXGTYPE', input_mempath)
330  call mem_setptr(efiles, 'EXGFILE', input_mempath)
331  call mem_setptr(emnames_a, 'EXGMNAMEA', input_mempath)
332  call mem_setptr(emnames_b, 'EXGMNAMEB', input_mempath)
333  call mem_setptr(mtypes, 'MTYPE', input_mempath)
334  call mem_setptr(mfnames, 'MFNAME', input_mempath)
335  call mem_setptr(mnames, 'MNAME', input_mempath)
336 
337  ! allocate mempaths array for exchanges
338  call mem_allocate(emempaths, lenmempath, size(etypes), 'EXGMEMPATHS', &
339  input_mempath)
340 
341  ! load exchanges for local models
342  do n = 1, size(etypes)
343  ! attributes for this exchange
344  exgtype = etypes(n)
345  efname = efiles(n)
346  call inlen_check(emnames_a(n), mname1, lenmodelname, 'MODELNAME')
347  call inlen_check(emnames_b(n), mname2, lenmodelname, 'MODELNAME')
348 
349  ! initialize mempath as no path
350  emempaths(n) = ''
351  irem = 0
352 
353  ! set indexes for exchange model names
354  m1_idx = ifind_charstr(mnames, mname1)
355  m2_idx = ifind_charstr(mnames, mname2)
356 
357  if (m1_idx <= 0 .or. m2_idx <= 0) then
358  errmsg = 'Exchange has invalid (unrecognized) model name(s):'
359  if (m1_idx <= 0) errmsg = trim(errmsg)//' '//trim(mname1)
360  if (m2_idx <= 0) errmsg = trim(errmsg)//' '//trim(mname2)
361  call store_error(errmsg)
362  end if
363 
364  ! terminate if errors were detected
365  if (count_errors() > 0) then
367  end if
368 
369  ! load the exchange input if either model local
370  if (model_loadmask(m1_idx) > 0 .or. model_loadmask(m2_idx) > 0) then
371  ! set index if either model is remote
372  if (model_loadmask(m1_idx) == 0) then
373  irem = m1_idx
374  else if (model_loadmask(m2_idx) == 0) then
375  irem = m2_idx
376  end if
377 
378  ! allocate and set remote model NCELLDIM
379  if (irem > 0) then
380  mtype = mtypes(irem)
381  mfname = mfnames(irem)
382  mname = mnames(irem)
383  mempath = create_mem_path(component=mname, context=idm_context)
384  call get_isize('NCELLDIM', mempath, isize)
385  if (isize < 0) then
386  call mem_allocate(ncelldim, 'NCELLDIM', mempath)
387  ncelldim = remote_model_ndim(mtype, mfname)
388  else
389  call mem_setptr(ncelldim, 'NCELLDIM', mempath)
390  end if
391  else
392  nullify (ncelldim)
393  end if
394 
395  ! set subcomponent strings
396  sc_type = trim(idm_subcomponent_type('EXG', exgtype))
397  write (sc_name, '(a,i0)') trim(sc_type)//'_', n
398 
399  ! create and set exchange mempath
400  mempath = create_mem_path('EXG', sc_name, idm_context)
401  emempaths(n) = mempath
402 
403  ! allocate and set exgid
404  call mem_allocate(exgid, 'EXGID', mempath)
405  exgid = n
406 
407  ! create exchange loader
408  static_loader => create_input_loader('EXG', sc_type, 'EXG', sc_name, &
409  exgtype, efname, simfile)
410  ! load static input
411  dynamic_loader => static_loader%load(iout)
412 
413  if (associated(dynamic_loader)) then
414  errmsg = 'IDM unimplemented. Dynamic Exchanges not supported.'
415  call store_error(errmsg)
416  call store_error_filename(efname)
417  else
418  call static_loader%destroy()
419  deallocate (static_loader)
420  end if
421  end if
422  end do
423 
424  ! clean up temporary NCELLDIM for remote models
425  do n = 1, size(mnames)
426  if (model_loadmask(n) == 0) then
427  mname = mnames(n)
428  mempath = create_mem_path(component=mname, context=idm_context)
429  call get_isize('NCELLDIM', mempath, isize)
430  if (isize > 0) then
431  call mem_setptr(ncelldim, 'NCELLDIM', mempath)
432  call mem_deallocate(ncelldim)
433  end if
434  end if
435  end do
436  end subroutine load_exchanges
437 
438  !> @brief MODFLOW 6 mfsim.nam input load routine
439  !<
440  subroutine simnam_load(paramlog)
441  use sourceloadmodule, only: load_simnam
442  integer(I4B), intent(inout) :: paramlog
443  ! load sim nam file
444  call load_simnam()
445  ! allocate any unallocated simnam params
446  call simnam_allocate()
447  ! read and set input parameter logging keyword
448  paramlog = input_param_log()
449  ! memload summary info
450  call simnam_load_dim()
451  end subroutine simnam_load
452 
453  !> @brief MODFLOW 6 tdis input load routine
454  !<
455  subroutine simtdis_load()
456  use sourceloadmodule, only: load_simtdis
457  ! load sim tdis file
458  call load_simtdis()
459  end subroutine simtdis_load
460 
461  !> @brief retrieve list of model dynamic loaders
462  !<
463  function dynamic_model_pkgs(modeltype, modelname, modelfname, nc_fname, &
464  ncid, iout) result(model_dynamic_input)
466  character(len=*), intent(in) :: modeltype
467  character(len=*), intent(in) :: modelname
468  character(len=*), intent(in) :: modelfname
469  character(len=*), intent(in) :: nc_fname
470  integer(I4B), intent(in) :: ncid
471  integer(I4B), intent(in) :: iout
472  class(modeldynamicpkgstype), pointer :: model_dynamic_input
473  class(modeldynamicpkgstype), pointer :: temp
474  integer(I4B) :: id
475 
476  ! initialize
477  nullify (model_dynamic_input)
478 
479  ! assign model loader object if found
480  do id = 1, model_dynamic_pkgs%Count()
481  temp => getdynamicmodelfromlist(model_dynamic_pkgs, id)
482  if (temp%modelname == modelname) then
483  model_dynamic_input => temp
484  exit
485  end if
486  end do
487 
488  ! create if not found
489  if (.not. associated(model_dynamic_input)) then
490  allocate (model_dynamic_input)
491  call model_dynamic_input%init(modeltype, modelname, modelfname, &
492  nc_fname, ncid, iout)
493  call adddynamicmodeltolist(model_dynamic_pkgs, model_dynamic_input)
494  end if
495  end function dynamic_model_pkgs
496 
497  !> @brief deallocate all model dynamic loader collections
498  !<
499  subroutine dynamic_da(iout)
501  use sourceloadmodule, only: nc_close
502  integer(I4B), intent(in) :: iout
503  class(modeldynamicpkgstype), pointer :: model_dynamic_input
504  integer(I4B) :: n
505  do n = 1, model_dynamic_pkgs%Count()
506  model_dynamic_input => getdynamicmodelfromlist(model_dynamic_pkgs, n)
507  call nc_close(model_dynamic_input%ncid, model_dynamic_input%nc_fname)
508  call model_dynamic_input%destroy()
509  deallocate (model_dynamic_input)
510  nullify (model_dynamic_input)
511  end do
512  call model_dynamic_pkgs%Clear()
513  end subroutine dynamic_da
514 
515  !> @brief return sim input context PRINT_INPUT value
516  !<
517  function input_param_log() result(paramlog)
521  character(len=LENMEMPATH) :: simnam_mempath
522  integer(I4B) :: paramlog
523  integer(I4B), pointer :: p
524  ! read and set input value of PRINT_INPUT
525  simnam_mempath = create_mem_path('SIM', 'NAM', idm_context)
526  call mem_setptr(p, 'PRINT_INPUT', simnam_mempath)
527  paramlog = p
528  end function input_param_log
529 
530  !> @brief load simulation summary info to input context
531  !<
532  subroutine simnam_load_dim()
537  character(len=LENMEMPATH) :: sim_mempath, simnam_mempath
538  type(characterstringtype), dimension(:), contiguous, &
539  pointer :: mtypes !< model types
540  type(characterstringtype), dimension(:), contiguous, &
541  pointer :: etypes !< model types
542  integer(I4B), pointer :: nummodels
543  integer(I4B), pointer :: numexchanges
544 
545  ! initialize
546  nullify (nummodels)
547  nullify (numexchanges)
548 
549  ! set memory paths
550  sim_mempath = create_mem_path(component='SIM', context=idm_context)
551  simnam_mempath = create_mem_path('SIM', 'NAM', idm_context)
552 
553  ! set pointers to loaded simnam arrays
554  call mem_setptr(mtypes, 'MTYPE', simnam_mempath)
555  call mem_setptr(etypes, 'EXGTYPE', simnam_mempath)
556 
557  ! allocate variables
558  call mem_allocate(nummodels, 'NUMMODELS', sim_mempath)
559  call mem_allocate(numexchanges, 'NUMEXCHANGES', sim_mempath)
560 
561  ! set values
562  nummodels = size(mtypes)
563  numexchanges = size(etypes)
564  end subroutine simnam_load_dim
565 
566  !> @brief set sim nam input context default integer value
567  !<
568  subroutine allocate_simnam_int(input_mempath, idt)
571  character(len=LENMEMPATH), intent(in) :: input_mempath
572  type(inputparamdefinitiontype), pointer, intent(in) :: idt
573  integer(I4B), pointer :: intvar
574 
575  ! allocate and set default
576  call mem_allocate(intvar, idt%mf6varname, input_mempath)
577 
578  select case (idt%mf6varname)
579  case ('CONTINUE')
580  intvar = isimcontinue
581  case ('NOCHECK')
582  intvar = isimcheck
583  case ('MAXERRORS')
584  intvar = 1000 !< MessageType max_message
585  case ('MXITER')
586  intvar = 1
587  case ('PRINT_INPUT')
588  intvar = 0
589  case default
590  write (errmsg, '(a,a)') &
591  'Idm SIMNAM Load default value setting '&
592  &'is unhandled for this variable: ', &
593  trim(idt%mf6varname)
594  call store_error(errmsg)
596  end select
597  end subroutine allocate_simnam_int
598 
599  !> @brief MODFLOW 6 mfsim.nam parameter allocate and set
600  !<
601  subroutine allocate_simnam_param(input_mempath, idt)
602  use simvariablesmodule, only: simfile
606  character(len=LENMEMPATH), intent(in) :: input_mempath
607  type(inputparamdefinitiontype), pointer, intent(in) :: idt
608  character(len=LINELENGTH), pointer :: cstr
609  type(characterstringtype), dimension(:), &
610  pointer, contiguous :: acharstr1d
611 
612  select case (idt_datatype(idt))
613  case ('KEYWORD', 'INTEGER')
614  if (idt%in_record) then
615  ! no-op
616  else
617  ! allocate and set default
618  call allocate_simnam_int(input_mempath, idt)
619  end if
620  case ('STRING')
621  ! did this param originate from sim namfile RECARRAY type
622  if (idt%in_record) then
623  ! allocate 0 size CharacterStringType array
624  call mem_allocate(acharstr1d, linelength, 0, idt%mf6varname, &
625  input_mempath)
626  else
627  ! allocate empty string
628  call mem_allocate(cstr, linelength, idt%mf6varname, input_mempath)
629  cstr = ''
630  end if
631  case ('RECORD')
632  ! no-op
633  case default
634  write (errmsg, '(a,a)') &
635  'IdmLoad allocate simnam param unhandled datatype: ', &
636  trim(idt%datatype)
637  call store_error(errmsg)
639  end select
640  end subroutine allocate_simnam_param
641 
642  !> @brief MODFLOW 6 mfsim.nam input context parameter allocation
643  !<
644  subroutine simnam_allocate()
649  character(len=LENMEMPATH) :: input_mempath
650  type(modflowinputtype) :: mf6_input
651  type(inputparamdefinitiontype), pointer :: idt
652  integer(I4B) :: iparam, isize
653 
654  ! set memory path
655  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
656  ! create description of input
657  mf6_input = getmodflowinput('NAM6', 'SIM', 'NAM', 'SIM', 'NAM')
658 
659  ! allocate sim namfile parameters if not in input context
660  do iparam = 1, size(mf6_input%param_dfns)
661  ! assign param definition pointer
662  idt => mf6_input%param_dfns(iparam)
663  ! check if variable is already allocated
664  call get_isize(idt%mf6varname, input_mempath, isize)
665  if (isize < 0) then
666  ! allocate and set parameter
667  call allocate_simnam_param(input_mempath, idt)
668  end if
669  end do
670  end subroutine simnam_allocate
671 
672 end module idmloadmodule
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 lencomponentname
maximum length of a component name
Definition: Constants.f90:18
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:22
integer(i4b), parameter lenexchangename
maximum length of the exchange name
Definition: Constants.f90:24
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
This module contains the DefinitionSelectModule.
character(len=linelength) function, public idt_datatype(idt)
return input definition type datatype
class(distributedsimtype) function, pointer, public get_dsim()
Get pointer to the distributed simulation object.
logical function, public idm_integrated(component, subcomponent)
This module contains the IdmLoadModule.
Definition: IdmLoad.f90:7
subroutine, public simnam_load(paramlog)
MODFLOW 6 mfsim.nam input load routine.
Definition: IdmLoad.f90:441
integer(i4b) function input_param_log()
return sim input context PRINT_INPUT value
Definition: IdmLoad.f90:518
subroutine load_model_pkgs(model_pkg_inputs, iout)
load integrated model package files
Definition: IdmLoad.f90:170
subroutine, public idm_da(iout)
idm deallocate routine
Definition: IdmLoad.f90:74
subroutine, public idm_df()
advance package dynamic data for period steps
Definition: IdmLoad.f90:38
subroutine, public simtdis_load()
MODFLOW 6 tdis input load routine.
Definition: IdmLoad.f90:456
subroutine, public idm_rp()
load package dynamic data for period
Definition: IdmLoad.f90:50
subroutine, public idm_ad()
advance package dynamic data for period steps
Definition: IdmLoad.f90:62
recursive subroutine input_load(component_type, subcomponent_type, modelname, pkgname, pkgtype, filename, modelfname, nc_vars, iout)
load an integrated model package from supported source
Definition: IdmLoad.f90:112
subroutine simnam_load_dim()
load simulation summary info to input context
Definition: IdmLoad.f90:533
subroutine allocate_simnam_int(input_mempath, idt)
set sim nam input context default integer value
Definition: IdmLoad.f90:569
subroutine, public load_models(iout)
load model namfiles and model package files
Definition: IdmLoad.f90:217
subroutine dynamic_da(iout)
deallocate all model dynamic loader collections
Definition: IdmLoad.f90:500
subroutine, public load_exchanges(iout)
load exchange files
Definition: IdmLoad.f90:284
subroutine simnam_allocate()
MODFLOW 6 mfsim.nam input context parameter allocation.
Definition: IdmLoad.f90:645
class(modeldynamicpkgstype) function, pointer dynamic_model_pkgs(modeltype, modelname, modelfname, nc_fname, ncid, iout)
retrieve list of model dynamic loaders
Definition: IdmLoad.f90:465
subroutine allocate_simnam_param(input_mempath, idt)
MODFLOW 6 mfsim.nam parameter allocate and set.
Definition: IdmLoad.f90:602
This module contains the InputDefinitionModule.
This module contains the InputLoadTypeModule.
class(modeldynamicpkgstype) function, pointer, public getdynamicmodelfromlist(list, idx)
get model dynamic packages object from list
subroutine, public adddynamicmodeltolist(list, model_dynamic)
add model dynamic packages object to list
type(listtype), public model_dynamic_pkgs
This module defines variable data types.
Definition: kind.f90:8
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine split_mem_path(mem_path, component, subcomponent)
Split the memory path into component(s)
subroutine, public memorystore_remove(component, subcomponent, context)
subroutine, public get_isize(name, mem_path, isize)
@ brief Get the number of elements for this variable
This module contains the ModelPackageInputsModule.
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 the NCFileVarsModule.
Definition: NCFileVars.f90:7
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_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
character(len=linelength) idm_context
integer(i4b) isimcheck
simulation input check flag (1) to check input, (0) to ignore checks
integer(i4b) isimcontinue
simulation continue flag (1) to continue if isimcnvg = 0, (0) to terminate
character(len=linelength) simfile
simulation name file
This module contains the SourceCommonModule.
Definition: SourceCommon.f90:7
character(len=lencomponentname) function, public idm_subcomponent_type(component, subcomponent)
component from package or model type
subroutine, public inlen_check(input_name, mf6_name, maxlen, name_type)
store an error for input exceeding internal name length
character(len=lencomponentname) function, public idm_component_type(component)
component from package or model type
integer(i4b) function, public ifind_charstr(array, str)
This module contains the SourceLoadModule.
Definition: SourceLoad.F90:8
subroutine, public load_simnam()
Definition: SourceLoad.F90:149
integer(i4b) function, public open_source_file(pkgtype, filename, modelfname, iout)
Definition: SourceLoad.F90:102
subroutine, public load_simtdis()
Definition: SourceLoad.F90:181
type(ncfilevarstype) function, pointer, public netcdf_context(modeltype, component_type, modelname, modelfname, iout)
create model netcdf context
Definition: SourceLoad.F90:359
subroutine, public nc_close(ncid, nc_fname)
close an open netcdf file
Definition: SourceLoad.F90:343
integer(i4b) function, public remote_model_ndim(mtype, mfname)
Definition: SourceLoad.F90:225
class(staticpkgloadbasetype) function, pointer, public create_input_loader(component_type, subcomponent_type, component_name, subcomponent_name, input_type, input_fname, component_fname, nc_vars)
factory function to create and setup model package static loader
Definition: SourceLoad.F90:37
subroutine, public load_modelnam(mtype, mfname, mname, iout)
Definition: SourceLoad.F90:125
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
Base abstract type for dynamic input loader.
type for storing a dynamic package load list
Base abstract type for static input loader.
A generic heterogeneous doubly-linked list.
Definition: List.f90:14
derived type for model package inputs type
derived type for storing input definition for a file
Type describing modflow6 input variables in model NetCDF file.
Definition: NCFileVars.f90:48