MODFLOW 6  version 6.7.0.dev1
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_inputs%Count()
42  model_dynamic_input => getdynamicmodelfromlist(model_inputs, 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_inputs%Count()
54  model_dynamic_input => getdynamicmodelfromlist(model_inputs, 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_inputs%Count()
66  model_dynamic_input => getdynamicmodelfromlist(model_inputs, 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_model
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  ! set pointer to model dynamic packages list
138  dynamic_model => &
139  dynamic_models(static_loader%mf6_input%component_type, modelname, &
140  static_loader%component_input_name, nc_vars%nc_fname, &
141  nc_vars%ncid, iout)
142 
143  if (associated(dynamic_loader)) then
144  ! add dynamic pkg loader to list
145  call dynamic_model%add(dynamic_loader)
146  end if
147 
148  ! create subpackage list
149  call static_loader%create_subpkg_list()
150 
151  ! load idm integrated subpackages
152  do n = 1, static_loader%subpkg_list%pnum
153  ! load subpackage
154  call input_load(static_loader%subpkg_list%component_types(n), &
155  static_loader%subpkg_list%subcomponent_types(n), &
156  static_loader%mf6_input%component_name, &
157  static_loader%subpkg_list%subcomponent_types(n), &
158  static_loader%subpkg_list%pkgtypes(n), &
159  static_loader%subpkg_list%filenames(n), &
160  modelfname, nc_vars, iout)
161  end do
162 
163  ! cleanup
164  call static_loader%destroy()
165  deallocate (static_loader)
166  end subroutine input_load
167 
168  !> @brief load integrated model package files
169  !<
170  subroutine load_model_pkgs(model_pkg_inputs, iout)
175  type(modelpackageinputstype), intent(inout) :: model_pkg_inputs
176  integer(i4B), intent(in) :: iout
177  type(ncfilevarstype), pointer :: nc_vars
178  integer(I4B) :: itype, ipkg
179 
180  nc_vars => netcdf_context(model_pkg_inputs%modeltype, &
181  model_pkg_inputs%component_type, &
182  model_pkg_inputs%modelname, &
183  model_pkg_inputs%modelfname, iout)
184  ! load package instances by type
185  do itype = 1, size(model_pkg_inputs%pkglist)
186  ! load package instances
187  do ipkg = 1, model_pkg_inputs%pkglist(itype)%pnum
188  if (idm_integrated(model_pkg_inputs%component_type, &
189  model_pkg_inputs%pkglist(itype)%subcomponent_type)) &
190  then
191  ! only load if model pkg can read from input context
192  call input_load(model_pkg_inputs%component_type, &
193  model_pkg_inputs%pkglist(itype)%subcomponent_type, &
194  model_pkg_inputs%modelname, &
195  model_pkg_inputs%pkglist(itype)%pkgnames(ipkg), &
196  model_pkg_inputs%pkglist(itype)%pkgtype, &
197  model_pkg_inputs%pkglist(itype)%filenames(ipkg), &
198  model_pkg_inputs%modelfname, nc_vars, iout)
199  else
200  ! open input file for package parser
201  model_pkg_inputs%pkglist(itype)%inunits(ipkg) = &
202  open_source_file(model_pkg_inputs%pkglist(itype)%pkgtype, &
203  model_pkg_inputs%pkglist(itype)%filenames(ipkg), &
204  model_pkg_inputs%modelfname, iout)
205  end if
206  end do
207  end do
208 
209  ! cleanup
210  call nc_vars%destroy()
211  deallocate (nc_vars)
212  nullify (nc_vars)
213  end subroutine load_model_pkgs
214 
215  !> @brief load model namfiles and model package files
216  !<
217  subroutine load_models(iout)
226  integer(I4B), intent(in) :: iout
227  type(distributedsimtype), pointer :: ds
228  integer(I4B), dimension(:), pointer :: model_loadmask
229  character(len=LENMEMPATH) :: input_mempath
230  type(characterstringtype), dimension(:), contiguous, &
231  pointer :: mtypes !< model types
232  type(characterstringtype), dimension(:), contiguous, &
233  pointer :: mfnames !< model file names
234  type(characterstringtype), dimension(:), contiguous, &
235  pointer :: mnames !< model names
236  character(len=LINELENGTH) :: mtype, mfname
237  character(len=LENMODELNAME) :: mname
238  type(modelpackageinputstype), allocatable :: model_pkg_inputs
239  integer(I4B) :: n
240 
241  ! get model mask
242  ds => get_dsim()
243  model_loadmask => ds%get_load_mask()
244 
245  ! set input memory path
246  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
247 
248  ! set pointers to input context model attribute arrays
249  call mem_setptr(mtypes, 'MTYPE', input_mempath)
250  call mem_setptr(mfnames, 'MFNAME', input_mempath)
251  call mem_setptr(mnames, 'MNAME', input_mempath)
252 
253  do n = 1, size(mtypes)
254  ! attributes for this model
255  mtype = mtypes(n)
256  mfname = mfnames(n)
257  call inlen_check(mnames(n), mname, lenmodelname, 'MODELNAME')
258 
259  ! terminate if errors were detected
260  if (count_errors() > 0) then
262  end if
263 
264  ! load specified model inputs
265  if (model_loadmask(n) > 0) then
266  ! load model nam file
267  call load_modelnam(mtype, mfname, mname, iout)
268  ! create description of model packages
269  allocate (model_pkg_inputs)
270  call model_pkg_inputs%init(mtype, mfname, mname, iout)
271  ! load packages
272  call load_model_pkgs(model_pkg_inputs, iout)
273  ! publish pkg info to input context
274  call model_pkg_inputs%memload()
275  ! cleanup
276  call model_pkg_inputs%destroy()
277  deallocate (model_pkg_inputs)
278  end if
279  end do
280  end subroutine load_models
281 
282  !> @brief load exchange files
283  !<
284  subroutine load_exchanges(iout)
294  integer(I4B), intent(in) :: iout
295  type(distributedsimtype), pointer :: ds
296  integer(I4B), dimension(:), pointer :: model_loadmask
297  type(characterstringtype), dimension(:), contiguous, &
298  pointer :: etypes !< exg types
299  type(characterstringtype), dimension(:), contiguous, &
300  pointer :: efiles !< exg file names
301  type(characterstringtype), dimension(:), contiguous, &
302  pointer :: emnames_a !< model a names
303  type(characterstringtype), dimension(:), contiguous, &
304  pointer :: emnames_b !< model b names
305  type(characterstringtype), dimension(:), contiguous, &
306  pointer :: emempaths !< exg mempaths
307  type(characterstringtype), dimension(:), contiguous, &
308  pointer :: mtypes !< model types
309  type(characterstringtype), dimension(:), contiguous, &
310  pointer :: mfnames !< model file names
311  type(characterstringtype), dimension(:), contiguous, &
312  pointer :: mnames !< model names
313  character(len=LENMEMPATH) :: input_mempath, mempath
314  integer(I4B), pointer :: exgid, ncelldim
315  character(len=LINELENGTH) :: exgtype, efname, mfname
316  character(len=LENMODELNAME) :: mname1, mname2, mname
317  character(len=LENCOMPONENTNAME) :: sc_type, sc_name, mtype
318  class(staticpkgloadbasetype), pointer :: static_loader
319  class(dynamicpkgloadbasetype), pointer :: dynamic_loader
320  integer(I4B) :: n, m1_idx, m2_idx, irem, isize
321 
322  ! get model mask
323  ds => get_dsim()
324  model_loadmask => ds%get_load_mask()
325 
326  ! set input memory path
327  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
328 
329  ! set pointers to input context exg and model attribute arrays
330  call mem_setptr(etypes, 'EXGTYPE', input_mempath)
331  call mem_setptr(efiles, 'EXGFILE', input_mempath)
332  call mem_setptr(emnames_a, 'EXGMNAMEA', input_mempath)
333  call mem_setptr(emnames_b, 'EXGMNAMEB', input_mempath)
334  call mem_setptr(mtypes, 'MTYPE', input_mempath)
335  call mem_setptr(mfnames, 'MFNAME', input_mempath)
336  call mem_setptr(mnames, 'MNAME', input_mempath)
337 
338  ! allocate mempaths array for exchanges
339  call mem_allocate(emempaths, lenmempath, size(etypes), 'EXGMEMPATHS', &
340  input_mempath)
341 
342  ! load exchanges for local models
343  do n = 1, size(etypes)
344  ! attributes for this exchange
345  exgtype = etypes(n)
346  efname = efiles(n)
347  call inlen_check(emnames_a(n), mname1, lenmodelname, 'MODELNAME')
348  call inlen_check(emnames_b(n), mname2, lenmodelname, 'MODELNAME')
349 
350  ! initialize mempath as no path
351  emempaths(n) = ''
352  irem = 0
353 
354  ! set indexes for exchange model names
355  m1_idx = ifind_charstr(mnames, mname1)
356  m2_idx = ifind_charstr(mnames, mname2)
357 
358  if (m1_idx <= 0 .or. m2_idx <= 0) then
359  errmsg = 'Exchange has invalid (unrecognized) model name(s):'
360  if (m1_idx <= 0) errmsg = trim(errmsg)//' '//trim(mname1)
361  if (m2_idx <= 0) errmsg = trim(errmsg)//' '//trim(mname2)
362  call store_error(errmsg)
363  end if
364 
365  ! terminate if errors were detected
366  if (count_errors() > 0) then
368  end if
369 
370  ! load the exchange input if either model local
371  if (model_loadmask(m1_idx) > 0 .or. model_loadmask(m2_idx) > 0) then
372  ! set index if either model is remote
373  if (model_loadmask(m1_idx) == 0) then
374  irem = m1_idx
375  else if (model_loadmask(m2_idx) == 0) then
376  irem = m2_idx
377  end if
378 
379  ! allocate and set remote model NCELLDIM
380  if (irem > 0) then
381  mtype = mtypes(irem)
382  mfname = mfnames(irem)
383  mname = mnames(irem)
384  mempath = create_mem_path(component=mname, context=idm_context)
385  call get_isize('NCELLDIM', mempath, isize)
386  if (isize < 0) then
387  call mem_allocate(ncelldim, 'NCELLDIM', mempath)
388  ncelldim = remote_model_ndim(mtype, mfname)
389  else
390  call mem_setptr(ncelldim, 'NCELLDIM', mempath)
391  end if
392  else
393  nullify (ncelldim)
394  end if
395 
396  ! set subcomponent strings
397  sc_type = trim(idm_subcomponent_type('EXG', exgtype))
398  write (sc_name, '(a,i0)') trim(sc_type)//'_', n
399 
400  ! create and set exchange mempath
401  mempath = create_mem_path('EXG', sc_name, idm_context)
402  emempaths(n) = mempath
403 
404  ! allocate and set exgid
405  call mem_allocate(exgid, 'EXGID', mempath)
406  exgid = n
407 
408  ! create exchange loader
409  static_loader => create_input_loader('EXG', sc_type, 'EXG', sc_name, &
410  exgtype, efname, simfile)
411  ! load static input
412  dynamic_loader => static_loader%load(iout)
413 
414  if (associated(dynamic_loader)) then
415  errmsg = 'IDM unimplemented. Dynamic Exchanges not supported.'
416  call store_error(errmsg)
417  call store_error_filename(efname)
418  else
419  call static_loader%destroy()
420  deallocate (static_loader)
421  end if
422  end if
423  end do
424 
425  ! clean up temporary NCELLDIM for remote models
426  do n = 1, size(mnames)
427  if (model_loadmask(n) == 0) then
428  mname = mnames(n)
429  mempath = create_mem_path(component=mname, context=idm_context)
430  call get_isize('NCELLDIM', mempath, isize)
431  if (isize > 0) then
432  call mem_setptr(ncelldim, 'NCELLDIM', mempath)
433  call mem_deallocate(ncelldim)
434  end if
435  end if
436  end do
437  end subroutine load_exchanges
438 
439  !> @brief MODFLOW 6 mfsim.nam input load routine
440  !<
441  subroutine simnam_load(paramlog)
442  use sourceloadmodule, only: load_simnam
443  integer(I4B), intent(inout) :: paramlog
444  ! load sim nam file
445  call load_simnam()
446  ! allocate any unallocated simnam params
447  call simnam_allocate()
448  ! read and set input parameter logging keyword
449  paramlog = input_param_log()
450  ! memload summary info
451  call simnam_load_dim()
452  end subroutine simnam_load
453 
454  !> @brief MODFLOW 6 tdis input load routine
455  !<
456  subroutine simtdis_load()
457  use sourceloadmodule, only: load_simtdis
458  ! load sim tdis file
459  call load_simtdis()
460  end subroutine simtdis_load
461 
462  !> @brief retrieve list of model dynamic loaders
463  !<
464  function dynamic_models(modeltype, modelname, modelfname, nc_fname, &
465  ncid, iout) result(model_dynamic_input)
467  character(len=*), intent(in) :: modeltype
468  character(len=*), intent(in) :: modelname
469  character(len=*), intent(in) :: modelfname
470  character(len=*), intent(in) :: nc_fname
471  integer(I4B), intent(in) :: ncid
472  integer(I4B), intent(in) :: iout
473  class(modeldynamicpkgstype), pointer :: model_dynamic_input
474  class(modeldynamicpkgstype), pointer :: temp
475  integer(I4B) :: id
476 
477  ! initialize
478  nullify (model_dynamic_input)
479 
480  ! assign model loader object if found
481  do id = 1, model_inputs%Count()
482  temp => getdynamicmodelfromlist(model_inputs, id)
483  if (temp%modelname == modelname) then
484  model_dynamic_input => temp
485  exit
486  end if
487  end do
488 
489  ! create if not found
490  if (.not. associated(model_dynamic_input)) then
491  allocate (model_dynamic_input)
492  call model_dynamic_input%init(modeltype, modelname, modelfname, &
493  nc_fname, ncid, iout)
494  call adddynamicmodeltolist(model_inputs, model_dynamic_input)
495  end if
496  end function dynamic_models
497 
498  !> @brief deallocate all model dynamic loader collections
499  !<
500  subroutine dynamic_da(iout)
502  use sourceloadmodule, only: nc_close
503  integer(I4B), intent(in) :: iout
504  class(modeldynamicpkgstype), pointer :: model_dynamic_input
505  integer(I4B) :: n
506  do n = 1, model_inputs%Count()
507  model_dynamic_input => getdynamicmodelfromlist(model_inputs, n)
508  call nc_close(model_dynamic_input%ncid, model_dynamic_input%nc_fname)
509  call model_dynamic_input%destroy()
510  deallocate (model_dynamic_input)
511  nullify (model_dynamic_input)
512  end do
513  call model_inputs%Clear()
514  end subroutine dynamic_da
515 
516  !> @brief return sim input context PRINT_INPUT value
517  !<
518  function input_param_log() result(paramlog)
522  character(len=LENMEMPATH) :: simnam_mempath
523  integer(I4B) :: paramlog
524  integer(I4B), pointer :: p
525  ! read and set input value of PRINT_INPUT
526  simnam_mempath = create_mem_path('SIM', 'NAM', idm_context)
527  call mem_setptr(p, 'PRINT_INPUT', simnam_mempath)
528  paramlog = p
529  end function input_param_log
530 
531  !> @brief load simulation summary info to input context
532  !<
533  subroutine simnam_load_dim()
538  character(len=LENMEMPATH) :: sim_mempath, simnam_mempath
539  type(characterstringtype), dimension(:), contiguous, &
540  pointer :: mtypes !< model types
541  type(characterstringtype), dimension(:), contiguous, &
542  pointer :: etypes !< model types
543  integer(I4B), pointer :: nummodels
544  integer(I4B), pointer :: numexchanges
545 
546  ! initialize
547  nullify (nummodels)
548  nullify (numexchanges)
549 
550  ! set memory paths
551  sim_mempath = create_mem_path(component='SIM', context=idm_context)
552  simnam_mempath = create_mem_path('SIM', 'NAM', idm_context)
553 
554  ! set pointers to loaded simnam arrays
555  call mem_setptr(mtypes, 'MTYPE', simnam_mempath)
556  call mem_setptr(etypes, 'EXGTYPE', simnam_mempath)
557 
558  ! allocate variables
559  call mem_allocate(nummodels, 'NUMMODELS', sim_mempath)
560  call mem_allocate(numexchanges, 'NUMEXCHANGES', sim_mempath)
561 
562  ! set values
563  nummodels = size(mtypes)
564  numexchanges = size(etypes)
565  end subroutine simnam_load_dim
566 
567  !> @brief set sim nam input context default integer value
568  !<
569  subroutine allocate_simnam_int(input_mempath, idt)
572  character(len=LENMEMPATH), intent(in) :: input_mempath
573  type(inputparamdefinitiontype), pointer, intent(in) :: idt
574  integer(I4B), pointer :: intvar
575 
576  ! allocate and set default
577  call mem_allocate(intvar, idt%mf6varname, input_mempath)
578 
579  select case (idt%mf6varname)
580  case ('CONTINUE')
581  intvar = isimcontinue
582  case ('NOCHECK')
583  intvar = isimcheck
584  case ('MAXERRORS')
585  intvar = 1000 !< MessageType max_message
586  case ('MXITER')
587  intvar = 1
588  case ('PRINT_INPUT')
589  intvar = 0
590  case default
591  write (errmsg, '(a,a)') &
592  'Idm SIMNAM Load default value setting '&
593  &'is unhandled for this variable: ', &
594  trim(idt%mf6varname)
595  call store_error(errmsg)
597  end select
598  end subroutine allocate_simnam_int
599 
600  !> @brief MODFLOW 6 mfsim.nam parameter allocate and set
601  !<
602  subroutine allocate_simnam_param(input_mempath, idt)
603  use simvariablesmodule, only: simfile
607  character(len=LENMEMPATH), intent(in) :: input_mempath
608  type(inputparamdefinitiontype), pointer, intent(in) :: idt
609  character(len=LINELENGTH), pointer :: cstr
610  type(characterstringtype), dimension(:), &
611  pointer, contiguous :: acharstr1d
612 
613  select case (idt_datatype(idt))
614  case ('KEYWORD', 'INTEGER')
615  if (idt%in_record) then
616  ! no-op
617  else
618  ! allocate and set default
619  call allocate_simnam_int(input_mempath, idt)
620  end if
621  case ('STRING')
622  ! did this param originate from sim namfile RECARRAY type
623  if (idt%in_record) then
624  ! allocate 0 size CharacterStringType array
625  call mem_allocate(acharstr1d, linelength, 0, idt%mf6varname, &
626  input_mempath)
627  else
628  ! allocate empty string
629  call mem_allocate(cstr, linelength, idt%mf6varname, input_mempath)
630  cstr = ''
631  end if
632  case ('RECORD')
633  ! no-op
634  case default
635  write (errmsg, '(a,a)') &
636  'IdmLoad allocate simnam param unhandled datatype: ', &
637  trim(idt%datatype)
638  call store_error(errmsg)
640  end select
641  end subroutine allocate_simnam_param
642 
643  !> @brief MODFLOW 6 mfsim.nam input context parameter allocation
644  !<
645  subroutine simnam_allocate()
650  character(len=LENMEMPATH) :: input_mempath
651  type(modflowinputtype) :: mf6_input
652  type(inputparamdefinitiontype), pointer :: idt
653  integer(I4B) :: iparam, isize
654 
655  ! set memory path
656  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
657  ! create description of input
658  mf6_input = getmodflowinput('NAM6', 'SIM', 'NAM', 'SIM', 'NAM')
659 
660  ! allocate sim namfile parameters if not in input context
661  do iparam = 1, size(mf6_input%param_dfns)
662  ! assign param definition pointer
663  idt => mf6_input%param_dfns(iparam)
664  ! check if variable is already allocated
665  call get_isize(idt%mf6varname, input_mempath, isize)
666  if (isize < 0) then
667  ! allocate and set parameter
668  call allocate_simnam_param(input_mempath, idt)
669  end if
670  end do
671  end subroutine simnam_allocate
672 
673 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:442
integer(i4b) function input_param_log()
return sim input context PRINT_INPUT value
Definition: IdmLoad.f90:519
subroutine load_model_pkgs(model_pkg_inputs, iout)
load integrated model package files
Definition: IdmLoad.f90:171
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:457
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:534
class(modeldynamicpkgstype) function, pointer dynamic_models(modeltype, modelname, modelfname, nc_fname, ncid, iout)
retrieve list of model dynamic loaders
Definition: IdmLoad.f90:466
subroutine allocate_simnam_int(input_mempath, idt)
set sim nam input context default integer value
Definition: IdmLoad.f90:570
subroutine, public load_models(iout)
load model namfiles and model package files
Definition: IdmLoad.f90:218
subroutine dynamic_da(iout)
deallocate all model dynamic loader collections
Definition: IdmLoad.f90:501
subroutine, public load_exchanges(iout)
load exchange files
Definition: IdmLoad.f90:285
subroutine simnam_allocate()
MODFLOW 6 mfsim.nam input context parameter allocation.
Definition: IdmLoad.f90:646
subroutine allocate_simnam_param(input_mempath, idt)
MODFLOW 6 mfsim.nam parameter allocate and set.
Definition: IdmLoad.f90:603
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
type(listtype), public model_inputs
subroutine, public adddynamicmodeltolist(list, model_dynamic)
add model dynamic packages object to list
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