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