MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
SimulationCreate.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b, lgp, write_kindinfo
23  use listmodule, only: listtype
24 
25  implicit none
26  private
27  public :: simulation_cr
28  public :: simulation_da
29 
30 contains
31 
32  !> @brief Read the simulation name file and initialize the models, exchanges
33  !<
34  subroutine simulation_cr()
35  ! -- modules
36  ! -- local
37  !
38  ! -- Source simulation nam input context and create objects
40  end subroutine simulation_cr
41 
42  !> @brief Deallocate simulation variables
43  !<
44  subroutine simulation_da()
45  ! -- modules
48  ! -- local
49  type(distributedsimtype), pointer :: ds
50 
51  ! -- variables
52  ds => get_dsim()
53  call ds%destroy()
54  !
55  deallocate (model_names)
56  deallocate (model_loc_idx)
57  end subroutine simulation_da
58 
59  !> @brief Source the simulation name file
60  !!
61  !! Source from the simulation nam input context to initialize the models,
62  !! exchanges, solutions, solutions groups. Then add the exchanges to
63  !! the appropriate solutions.
64  !!
65  !<
66  subroutine source_simulation_nam()
67  ! -- dummy
68  ! -- local
69  !
70  ! -- Process OPTIONS block in namfile
71  call options_create()
72  !
73  ! -- Process TIMING block in namfile
74  call timing_create()
75  !
76  ! -- Process MODELS block in namfile
77  call models_create()
78  !
79  ! -- Process EXCHANGES block in namfile
80  call exchanges_create()
81  !
82  ! -- Process SOLUTION_GROUPS blocks in namfile
84  !
85  ! -- Go through each model and make sure that it has been assigned to
86  ! a solution.
88  !
89  ! -- Go through each solution and assign exchanges accordingly
90  call assign_exchanges()
91  end subroutine source_simulation_nam
92 
93  !> @brief Set the simulation options
94  !<
95  subroutine options_create()
96  ! -- modules
102  ! -- dummy
103  ! -- locals
104  character(len=LENMEMPATH) :: input_mempath
105  integer(I4B), pointer :: simcontinue, nocheck, maxerror
106  character(len=:), pointer :: prmem
107  character(len=LINELENGTH) :: errmsg
108  !
109  ! -- set input memory path
110  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
111  !
112  ! -- set pointers to input context option params
113  call mem_setptr(simcontinue, 'CONTINUE', input_mempath)
114  call mem_setptr(nocheck, 'NOCHECK', input_mempath)
115  call mem_setptr(prmem, 'PRMEM', input_mempath)
116  call mem_setptr(maxerror, 'MAXERRORS', input_mempath)
117  !
118  ! -- update sim options
119  isimcontinue = simcontinue
120  isimcheck = nocheck
121  call maxerrors(maxerror)
122  !
123  if (prmem /= '') then
124  errmsg = ''
125  call mem_set_print_option(iout, prmem, errmsg)
126  if (errmsg /= '') then
127  call store_error(errmsg, .true.)
128  end if
129  end if
130  !
131  ! -- log values to list file
132  if (iout > 0) then
133  write (iout, '(/1x,a)') 'READING SIMULATION OPTIONS'
134  !
135  if (isimcontinue == 1) then
136  write (iout, '(4x, a)') &
137  'SIMULATION WILL CONTINUE EVEN IF THERE IS NONCONVERGENCE.'
138  end if
139  !
140  if (isimcheck == 0) then
141  write (iout, '(4x, a)') &
142  'MODEL DATA WILL NOT BE CHECKED FOR ERRORS.'
143  end if
144  !
145  write (iout, '(4x, a, i0)') &
146  'MAXIMUM NUMBER OF ERRORS THAT WILL BE STORED IS ', maxerror
147  !
148  if (prmem /= '') then
149  write (iout, '(4x, a, a, a)') &
150  'MEMORY_PRINT_OPTION SET TO "', trim(prmem), '".'
151  end if
152  !
153  write (iout, '(1x,a)') 'END OF SIMULATION OPTIONS'
154  end if
155  end subroutine options_create
156 
157  !> @brief Set the timing module to be used for the simulation
158  !<
159  subroutine timing_create()
160  ! -- modules
164  use tdismodule, only: tdis_cr
165  ! -- dummy
166  ! -- locals
167  character(len=LENMEMPATH) :: input_mempath
168  character(len=LENMEMPATH) :: tdis_input_mempath
169  character(len=:), pointer :: tdis6
170  logical :: terminate = .true.
171  !
172  ! -- set input memory path
173  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
174  tdis_input_mempath = create_mem_path('SIM', 'TDIS', idm_context)
175  !
176  write (iout, '(/1x,a)') 'READING SIMULATION TIMING'
177  !
178  ! -- set pointers to input context timing params
179  call mem_setptr(tdis6, 'TDIS6', input_mempath)
180  !
181  ! -- create timing
182  if (tdis6 /= '') then
183  call tdis_cr(tdis6, tdis_input_mempath)
184  else
185  call store_error('TIMING block variable TDIS6 is unset'// &
186  ' in simulation control input.', terminate)
187  end if
188  !
189  write (iout, '(1x,a)') 'END OF SIMULATION TIMING'
190  end subroutine timing_create
191 
192  !> @brief Set the models to be used for the simulation
193  !<
194  subroutine models_create()
195  ! -- modules
200  use chfmodule, only: chf_cr
201  use gwfmodule, only: gwf_cr
202  use gwtmodule, only: gwt_cr
203  use gwemodule, only: gwe_cr
204  use olfmodule, only: olf_cr
205  use prtmodule, only: prt_cr
210  ! use VirtualPrtModelModule, only: add_virtual_prt_model
211  use constantsmodule, only: lenmodelname
212  ! -- dummy
213  ! -- locals
214  type(distributedsimtype), pointer :: ds
215  character(len=LENMEMPATH) :: input_mempath
216  type(characterstringtype), dimension(:), contiguous, &
217  pointer :: mtypes !< model types
218  type(characterstringtype), dimension(:), contiguous, &
219  pointer :: mfnames !< model file names
220  type(characterstringtype), dimension(:), contiguous, &
221  pointer :: mnames !< model names
222  integer(I4B) :: im
223  class(numericalmodeltype), pointer :: num_model
224  character(len=LINELENGTH) :: model_type
225  character(len=LINELENGTH) :: fname, model_name
226  integer(I4B) :: n, nr_models_glob
227  integer(I4B), dimension(:), pointer :: model_ranks => null()
228  logical :: terminate = .true.
229  !
230  ! -- set input memory path
231  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
232  !
233  ! -- set pointers to input context model attribute arrays
234  call mem_setptr(mtypes, 'MTYPE', input_mempath)
235  call mem_setptr(mfnames, 'MFNAME', input_mempath)
236  call mem_setptr(mnames, 'MNAME', input_mempath)
237  !
238  ! -- allocate global arrays
239  nr_models_glob = size(mnames)
240  allocate (model_names(nr_models_glob))
241  allocate (model_loc_idx(nr_models_glob))
242  !
243  ! -- get model-to-cpu assignment (in serial all to rank 0)
244  ds => get_dsim()
245  model_ranks => ds%get_load_balance()
246  !
247  ! -- open model logging block
248  write (iout, '(/1x,a)') 'READING SIMULATION MODELS'
249  !
250  ! -- create models
251  im = 0
252  do n = 1, size(mtypes)
253  !
254  ! -- attributes for this model
255  model_type = mtypes(n)
256  fname = mfnames(n)
257  model_name = mnames(n)
258  !
259  call check_model_name(model_type, model_name)
260  !
261  ! increment global model id
262  model_names(n) = model_name(1:lenmodelname)
263  model_loc_idx(n) = -1
264  num_model => null()
265  !
266  ! -- add a new (local or global) model
267  select case (model_type)
268  case ('GWF6')
269  if (model_ranks(n) == proc_id) then
270  im = im + 1
271  write (iout, '(4x,2a,i0,a)') trim(model_type), ' model ', &
272  n, ' will be created'
273  call gwf_cr(fname, n, model_names(n))
274  num_model => getnumericalmodelfromlist(basemodellist, im)
275  model_loc_idx(n) = im
276  end if
277  call add_virtual_gwf_model(n, model_names(n), num_model)
278  case ('GWT6')
279  if (model_ranks(n) == proc_id) then
280  im = im + 1
281  write (iout, '(4x,2a,i0,a)') trim(model_type), ' model ', &
282  n, ' will be created'
283  call gwt_cr(fname, n, model_names(n))
284  num_model => getnumericalmodelfromlist(basemodellist, im)
285  model_loc_idx(n) = im
286  end if
287  call add_virtual_gwt_model(n, model_names(n), num_model)
288  case ('GWE6')
289  if (model_ranks(n) == proc_id) then
290  im = im + 1
291  write (iout, '(4x,2a,i0,a)') trim(model_type), ' model ', &
292  n, ' will be created'
293  call gwe_cr(fname, n, model_names(n))
294  num_model => getnumericalmodelfromlist(basemodellist, im)
295  model_loc_idx(n) = im
296  end if
297  call add_virtual_gwe_model(n, model_names(n), num_model)
298  case ('CHF6')
299  if (model_ranks(n) == proc_id) then
300  im = im + 1
301  write (iout, '(4x,2a,i0,a)') trim(model_type), " model ", &
302  n, " will be created"
303  call chf_cr(fname, n, model_names(n))
304  call dev_feature('CHF is still under development, install the &
305  &nightly build or compile from source with IDEVELOPMODE = 1.')
306  num_model => getnumericalmodelfromlist(basemodellist, im)
307  model_loc_idx(n) = im
308  end if
309  case ('OLF6')
310  if (model_ranks(n) == proc_id) then
311  im = im + 1
312  write (iout, '(4x,2a,i0,a)') trim(model_type), " model ", &
313  n, " will be created"
314  call olf_cr(fname, n, model_names(n))
315  call dev_feature('OLF is still under development, install the &
316  &nightly build or compile from source with IDEVELOPMODE = 1.')
317  num_model => getnumericalmodelfromlist(basemodellist, im)
318  model_loc_idx(n) = im
319  end if
320  case ('PRT6')
321  im = im + 1
322  write (iout, '(4x,2a,i0,a)') trim(model_type), ' model ', &
323  n, ' will be created'
324  call prt_cr(fname, n, model_names(n))
325  num_model => getnumericalmodelfromlist(basemodellist, im)
326  model_loc_idx(n) = im
327  case default
328  write (errmsg, '(a,a)') &
329  'Unknown simulation model type: ', trim(model_type)
330  call store_error(errmsg, terminate)
331  end select
332  end do
333  !
334  ! -- close model logging block
335  write (iout, '(1x,a)') 'END OF SIMULATION MODELS'
336  !
337  ! -- sanity check
338  if (simulation_mode == 'PARALLEL' .and. im == 0) then
339  write (errmsg, '(a, i0)') &
340  'No MODELS assigned to process ', proc_id
341  call store_error(errmsg, terminate)
342  end if
343  end subroutine models_create
344 
345  !> @brief Set the exchanges to be used for the simulation
346  !<
347  subroutine exchanges_create()
348  ! -- modules
363  ! use VirtualPrtExchangeModule, only: add_virtual_prt_exchange
364  ! -- dummy
365  ! -- locals
366  character(len=LENMEMPATH) :: input_mempath
367  type(characterstringtype), dimension(:), contiguous, &
368  pointer :: etypes !< exg types
369  type(characterstringtype), dimension(:), contiguous, &
370  pointer :: efiles !< exg file names
371  type(characterstringtype), dimension(:), contiguous, &
372  pointer :: emnames_a !< model a names
373  type(characterstringtype), dimension(:), contiguous, &
374  pointer :: emnames_b !< model b names
375  type(characterstringtype), dimension(:), contiguous, &
376  pointer :: emempaths
377  character(len=LINELENGTH) :: exgtype
378  integer(I4B) :: exg_id
379  integer(I4B) :: m1_id, m2_id
380  character(len=LINELENGTH) :: fname, name1, name2
381  character(len=LENEXCHANGENAME) :: exg_name
382  character(len=LENMEMPATH) :: exg_mempath
383  integer(I4B) :: n
384  character(len=LINELENGTH) :: errmsg
385  logical(LGP) :: terminate = .true.
386  logical(LGP) :: both_remote, both_local
387  ! -- formats
388  character(len=*), parameter :: fmtmerr = "('Error in simulation control ', &
389  &'file. Could not find model: ', a)"
390  !
391  ! -- set input memory path
392  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
393  !
394  ! -- set pointers to input context exchange attribute arrays
395  call mem_setptr(etypes, 'EXGTYPE', input_mempath)
396  call mem_setptr(efiles, 'EXGFILE', input_mempath)
397  call mem_setptr(emnames_a, 'EXGMNAMEA', input_mempath)
398  call mem_setptr(emnames_b, 'EXGMNAMEB', input_mempath)
399  call mem_setptr(emempaths, 'EXGMEMPATHS', input_mempath)
400  !
401  ! -- open exchange logging block
402  write (iout, '(/1x,a)') 'READING SIMULATION EXCHANGES'
403  !
404  ! -- initialize
405  exg_id = 0
406  !
407  ! -- create exchanges
408  do n = 1, size(etypes)
409  !
410  ! -- attributes for this exchange
411  exgtype = etypes(n)
412  fname = efiles(n)
413  name1 = emnames_a(n)
414  name2 = emnames_b(n)
415  exg_mempath = emempaths(n)
416 
417  exg_id = exg_id + 1
418 
419  ! find model index in list
420  m1_id = ifind(model_names, name1)
421  if (m1_id < 0) then
422  write (errmsg, fmtmerr) trim(name1)
423  call store_error(errmsg, terminate)
424  end if
425  m2_id = ifind(model_names, name2)
426  if (m2_id < 0) then
427  write (errmsg, fmtmerr) trim(name2)
428  call store_error(errmsg, terminate)
429  end if
430 
431  ! both models on other process? then don't create it here...
432  both_remote = (model_loc_idx(m1_id) == -1 .and. &
433  model_loc_idx(m2_id) == -1)
434  both_local = (model_loc_idx(m1_id) > 0 .and. &
435  model_loc_idx(m2_id) > 0)
436  if (.not. both_remote) then
437  write (iout, '(4x,a,a,i0,a,i0,a,i0)') trim(exgtype), ' exchange ', &
438  exg_id, ' will be created to connect model ', m1_id, &
439  ' with model ', m2_id
440  end if
441 
442  select case (exgtype)
443  case ('CHF6-GWF6')
444  write (exg_name, '(a,i0)') 'CHF-GWF_', exg_id
445  if (both_local) then
446  call chfgwf_cr(fname, exg_name, exg_id, m1_id, m2_id, exg_mempath)
447  end if
448  case ('GWF6-GWF6')
449  write (exg_name, '(a,i0)') 'GWF-GWF_', exg_id
450  if (.not. both_remote) then
451  call gwfexchange_create(fname, exg_name, exg_id, m1_id, m2_id, &
452  exg_mempath)
453  end if
454  call add_virtual_gwf_exchange(exg_name, exg_id, m1_id, m2_id)
455  case ('GWF6-GWT6')
456  if (both_local) then
457  call gwfgwt_cr(fname, exg_id, m1_id, m2_id)
458  end if
459  case ('GWF6-GWE6')
460  if (both_local) then
461  call gwfgwe_cr(fname, exg_id, m1_id, m2_id)
462  end if
463  case ('GWF6-PRT6')
464  call gwfprt_cr(fname, exg_id, m1_id, m2_id)
465  case ('GWT6-GWT6')
466  write (exg_name, '(a,i0)') 'GWT-GWT_', exg_id
467  if (.not. both_remote) then
468  call gwtexchange_create(fname, exg_name, exg_id, m1_id, m2_id, &
469  exg_mempath)
470  end if
471  call add_virtual_gwt_exchange(exg_name, exg_id, m1_id, m2_id)
472  case ('GWE6-GWE6')
473  write (exg_name, '(a,i0)') 'GWE-GWE_', exg_id
474  if (.not. both_remote) then
475  call gweexchange_create(fname, exg_name, exg_id, m1_id, m2_id, &
476  exg_mempath)
477  end if
478  call add_virtual_gwe_exchange(exg_name, exg_id, m1_id, m2_id)
479  case ('OLF6-GWF6')
480  write (exg_name, '(a,i0)') 'OLF-GWF_', exg_id
481  if (both_local) then
482  call olfgwf_cr(fname, exg_name, exg_id, m1_id, m2_id, exg_mempath)
483  end if
484  case default
485  write (errmsg, '(a,a)') &
486  'Unknown simulation exchange type: ', trim(exgtype)
487  call store_error(errmsg, terminate)
488  end select
489  end do
490  !
491  ! -- close exchange logging block
492  write (iout, '(1x,a)') 'END OF SIMULATION EXCHANGES'
493  end subroutine exchanges_create
494 
495  !> @brief Check a solution_group to be used for the simulation
496  !<
497  subroutine solution_group_check(sgp, sgid, isgpsoln)
498  ! -- modules
499  ! -- dummy
500  type(solutiongrouptype), pointer, intent(inout) :: sgp
501  integer(I4B), intent(in) :: sgid
502  integer(I4B), intent(in) :: isgpsoln
503  ! -- local
504  character(len=LINELENGTH) :: errmsg
505  logical :: terminate = .true.
506  ! -- formats
507  character(len=*), parameter :: fmterrmxiter = &
508  "('MXITER is set to ', i0, ' but there is only one solution', &
509  &' in SOLUTION GROUP ', i0, '. Set MXITER to 1 in simulation control', &
510  &' file.')"
511  !
512  ! -- error check completed group
513  if (sgid > 0) then
514  !
515  ! -- Make sure there is a solution in this solution group
516  if (isgpsoln == 0) then
517  write (errmsg, '(a,i0)') &
518  'There are no solutions for solution group ', sgid
519  call store_error(errmsg, terminate)
520  end if
521  !
522  ! -- If there is only one solution then mxiter should be 1.
523  if (isgpsoln == 1 .and. sgp%mxiter > 1) then
524  write (errmsg, fmterrmxiter) sgp%mxiter, isgpsoln
525  call store_error(errmsg, terminate)
526  end if
527  end if
528  end subroutine solution_group_check
529 
530  !> @brief Set the solution_groups to be used for the simulation
531  !<
533  ! -- modules
541  use basemodelmodule, only: basemodeltype
544  ! -- dummy
545  ! -- local
546  character(len=LENMEMPATH) :: input_mempath
547  type(characterstringtype), dimension(:), contiguous, &
548  pointer :: slntype
549  type(characterstringtype), dimension(:), contiguous, &
550  pointer :: slnfname
551  type(characterstringtype), dimension(:), contiguous, &
552  pointer :: slnmnames
553  integer(I4B), dimension(:), contiguous, pointer :: blocknum
554  character(len=LINELENGTH) :: stype, fname
555  character(len=:), allocatable :: mnames
556  type(solutiongrouptype), pointer :: sgp
557  class(basesolutiontype), pointer :: sp
558  class(basemodeltype), pointer :: mp
559  integer(I4B) :: isoln
560  integer(I4B) :: isgpsoln
561  integer(I4B) :: sgid
562  integer(I4B) :: glo_mid
563  integer(I4B) :: loc_idx
564  integer(I4B) :: i, j, istat, mxiter
565  integer(I4B) :: nwords
566  character(len=LENMODELNAME), dimension(:), allocatable :: words
567  character(len=:), allocatable :: parse_str
568  character(len=LINELENGTH) :: errmsg
569  logical :: terminate = .true.
570  !
571  ! -- set memory path
572  input_mempath = create_mem_path('SIM', 'NAM', idm_context)
573  !
574  ! -- set pointers to input context solution attribute arrays
575  call mem_setptr(slntype, 'SLNTYPE', input_mempath)
576  call mem_setptr(slnfname, 'SLNFNAME', input_mempath)
577  call mem_setptr(slnmnames, 'SLNMNAMES', input_mempath)
578  call mem_setptr(blocknum, 'SOLUTIONGROUPNUM', input_mempath)
579  !
580  ! -- open solution group logging block
581  write (iout, '(/1x,a)') 'READING SOLUTIONGROUP'
582  !
583  ! -- initialize
584  sgid = 0 ! integer id of soln group, tracks with blocknum
585  isoln = 0 ! cumulative solution number
586  !
587  ! -- create solution groups
588  do i = 1, size(blocknum)
589  !
590  ! -- allocate slnmnames string
591  allocate (character(slnmnames(i)%strlen()) :: mnames)
592  !
593  ! -- attributes for this solution
594  stype = slntype(i)
595  fname = slnfname(i)
596  mnames = slnmnames(i)
597 
598  if (blocknum(i) /= sgid) then
599  !
600  ! -- check for new soln group
601  if (blocknum(i) == sgid + 1) then
602  !
603  ! -- error check completed group
604  call solution_group_check(sgp, sgid, isgpsoln)
605  !
606  ! -- reinitialize
607  nullify (sgp)
608  isgpsoln = 0 ! solution counter for this solution group
609  !
610  ! -- set sgid
611  sgid = blocknum(i)
612  !
613  ! -- create new soln group and add to global list
614  call solutiongroup_create(sgp, sgid)
615  call addsolutiongrouptolist(solutiongrouplist, sgp)
616  else
617  write (errmsg, '(a,i0,a,i0,a)') &
618  'Solution group blocks are not listed consecutively. Found ', &
619  blocknum(i), ' when looking for ', sgid + 1, '.'
620  call store_error(errmsg, terminate)
621  end if
622  end if
623  !
624  ! --
625  select case (stype)
626  !
627  case ('MXITER')
628  read (fname, *, iostat=istat) mxiter
629  if (istat == 0) then
630  sgp%mxiter = mxiter
631  end if
632  case ('IMS6')
633  !
634  ! -- increment solution counters
635  isoln = isoln + 1
636  isgpsoln = isgpsoln + 1
637  !
638  ! -- create soln and add to group
639  sp => create_ims_solution(simulation_mode, fname, isoln)
640  call sgp%add_solution(isoln, sp)
641  !
642  ! -- parse model names
643  parse_str = trim(mnames)//' '
644  call parseline(parse_str, nwords, words)
645  !
646  ! -- Find each model id and get model
647  do j = 1, nwords
648  call upcase(words(j))
649  glo_mid = ifind(model_names, words(j))
650  if (glo_mid == -1) then
651  write (errmsg, '(a,a)') 'Invalid model name: ', trim(words(j))
652  call store_error(errmsg, terminate)
653  end if
654  !
655  loc_idx = model_loc_idx(glo_mid)
656  if (loc_idx == -1) then
657  if (simulation_mode == 'PARALLEL') then
658  ! this is still ok
659  cycle
660  end if
661  end if
662  !
663  mp => getbasemodelfromlist(basemodellist, loc_idx)
664  !
665  ! -- Add the model to the solution
666  call sp%add_model(mp)
667  mp%idsoln = isoln
668  end do
669  case ('EMS6')
670  !
671  ! -- increment solution counters
672  isoln = isoln + 1
673  isgpsoln = isgpsoln + 1
674  !
675  ! -- create soln and add to group
676  sp => create_ems_solution(simulation_mode, fname, isoln)
677  call sgp%add_solution(isoln, sp)
678  !
679  ! -- parse model names
680  parse_str = trim(mnames)//' '
681  call parseline(parse_str, nwords, words)
682  !
683  ! -- Find each model id and get model
684  do j = 1, nwords
685  call upcase(words(j))
686  glo_mid = ifind(model_names, words(j))
687  if (glo_mid == -1) then
688  write (errmsg, '(a,a)') 'Invalid model name: ', trim(words(j))
689  call store_error(errmsg, terminate)
690  end if
691  !
692  loc_idx = model_loc_idx(glo_mid)
693  if (loc_idx == -1) then
694  if (simulation_mode == 'PARALLEL') then
695  ! this is still ok
696  cycle
697  end if
698  end if
699  !
700  mp => getbasemodelfromlist(basemodellist, loc_idx)
701  !
702  ! -- Add the model to the solution
703  call sp%add_model(mp)
704  mp%idsoln = isoln
705  end do
706  case default
707  end select
708  !
709  ! -- clean up
710  deallocate (mnames)
711  end do
712  !
713  ! -- error check final group
714  call solution_group_check(sgp, sgid, isgpsoln)
715  !
716  ! -- close exchange logging block
717  write (iout, '(1x,a)') 'END OF SOLUTIONGROUP'
718  !
719  ! -- Check and make sure at least one solution group was found
720  if (solutiongrouplist%Count() == 0) then
721  call store_error('There are no solution groups.', terminate)
722  end if
723  end subroutine solution_groups_create
724 
725  !> @brief Check for dangling models, and break with
726  !! error when found
727  !<
729  character(len=LINELENGTH) :: errmsg
730  class(basemodeltype), pointer :: mp
731  integer(I4B) :: im
732 
733  do im = 1, basemodellist%Count()
735  if (mp%idsoln == 0) then
736  write (errmsg, '(a,a)') &
737  'Model was not assigned to a solution: ', mp%name
738  call store_error(errmsg)
739  end if
740  end do
741  if (count_errors() > 0) then
742  call store_error_filename('mfsim.nam')
743  end if
744 
745  end subroutine check_model_assignment
746 
747  !> @brief Assign exchanges to solutions
748  !!
749  !! This assigns NumericalExchanges to NumericalSolutions,
750  !! based on the link between the models in the solution and
751  !! those exchanges. The BaseExchange%connects_model() function
752  !! should be overridden to indicate if such a link exists.
753  !<
754  subroutine assign_exchanges()
755  ! -- local
756  class(basesolutiontype), pointer :: sp
757  class(baseexchangetype), pointer :: ep
758  class(basemodeltype), pointer :: mp
759  type(listtype), pointer :: models_in_solution
760  integer(I4B) :: is, ie, im
761 
762  do is = 1, basesolutionlist%Count()
764  !
765  ! -- now loop over exchanges
766  do ie = 1, baseexchangelist%Count()
768  !
769  ! -- and add when it affects (any model in) the solution matrix
770  models_in_solution => sp%get_models()
771  do im = 1, models_in_solution%Count()
772  mp => getbasemodelfromlist(models_in_solution, im)
773  if (ep%connects_model(mp)) then
774  !
775  ! -- add to solution (and only once)
776  call sp%add_exchange(ep)
777  exit
778  end if
779  end do
780  end do
781  end do
782  end subroutine assign_exchanges
783 
784  !> @brief Check that the model name is valid
785  !<
786  subroutine check_model_name(mtype, mname)
787  ! -- dummy
788  character(len=*), intent(in) :: mtype
789  character(len=*), intent(inout) :: mname
790  ! -- local
791  integer :: ilen
792  integer :: i
793  character(len=LINELENGTH) :: errmsg
794  logical :: terminate = .true.
795 
796  ilen = len_trim(mname)
797  if (ilen > lenmodelname) then
798  write (errmsg, '(a,a)') 'Invalid model name: ', trim(mname)
799  call store_error(errmsg)
800  write (errmsg, '(a,i0,a,i0)') &
801  'Name length of ', ilen, ' exceeds maximum length of ', &
803  call store_error(errmsg, terminate)
804  end if
805  do i = 1, ilen
806  if (mname(i:i) == ' ') then
807  write (errmsg, '(a,a)') 'Invalid model name: ', trim(mname)
808  call store_error(errmsg)
809  write (errmsg, '(a)') &
810  'Model name cannot have spaces within it.'
811  call store_error(errmsg, terminate)
812  end if
813  end do
814  end subroutine check_model_name
815 
816 end module simulationcreatemodule
class(baseexchangetype) function, pointer, public getbaseexchangefromlist(list, idx)
Retrieve a specific BaseExchangeType object from a list.
class(basemodeltype) function, pointer, public getbasemodelfromlist(list, idx)
Definition: BaseModel.f90:172
subroutine, public addbasesolutiontolist(list, solution)
class(basesolutiontype) function, pointer, public getbasesolutionfromlist(list, idx)
This module contains the ChfGwfExchangeModule Module.
Definition: exg-chfgwf.f90:6
subroutine, public chfgwf_cr(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create CHF GWF exchange
Definition: exg-chfgwf.f90:41
Channel Flow (CHF) Module.
Definition: chf.f90:3
subroutine, public chf_cr(filename, id, modelname)
Create a new surface water flow model object.
Definition: chf.f90:55
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 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 lenpackagetype
maximum length of a package type (DIS6, SFR6, CSUB6, etc.)
Definition: Constants.f90:38
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
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
class(distributedsimtype) function, pointer, public get_dsim()
Get pointer to the distributed simulation object.
This module contains the GweGweExchangeModule Module.
Definition: exg-gwegwe.f90:10
subroutine, public gweexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create GWT GWT exchange
Definition: exg-gwegwe.f90:111
Definition: gwe.f90:3
subroutine, public gwe_cr(filename, id, modelname)
Create a new groundwater energy transport model object.
Definition: gwe.f90:96
subroutine, public gwfgwe_cr(filename, id, m1_id, m2_id)
Create a new GWF to GWE exchange object.
Definition: exg-gwfgwe.f90:47
This module contains the GwfGwfExchangeModule Module.
Definition: exg-gwfgwf.f90:10
subroutine, public gwfexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create GWF GWF exchange
Definition: exg-gwfgwf.f90:122
subroutine, public gwfgwt_cr(filename, id, m1_id, m2_id)
Create a new GWF to GWT exchange object.
Definition: exg-gwfgwt.f90:49
Definition: gwf.f90:1
subroutine, public gwf_cr(filename, id, modelname)
Create a new groundwater flow model object.
Definition: gwf.f90:138
subroutine, public gwfprt_cr(filename, id, m1id, m2id)
Create a new GWF to PRT exchange object.
Definition: exg-gwfprt.f90:40
This module contains the GwtGwtExchangeModule Module.
Definition: exg-gwtgwt.f90:10
subroutine, public gwtexchange_create(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create GWT GWT exchange
Definition: exg-gwtgwt.f90:110
Definition: gwt.f90:8
subroutine, public gwt_cr(filename, id, modelname)
Create a new groundwater transport model object.
Definition: gwt.f90:101
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public parseline(line, nwords, words, inunit, filename)
Parse a line into words.
subroutine, public upcase(word)
Convert to upper case.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This module defines variable data types.
Definition: kind.f90:8
subroutine, public write_kindinfo(iout)
Write variable data types.
Definition: kind.f90:27
type(listtype), public basemodellist
Definition: mf6lists.f90:16
type(listtype), public baseexchangelist
Definition: mf6lists.f90:25
type(listtype), public solutiongrouplist
Definition: mf6lists.f90:22
type(listtype), public basesolutionlist
Definition: mf6lists.f90:19
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine, public mem_set_print_option(iout, keyword, error_msg)
Set the memory print option.
class(numericalmodeltype) function, pointer, public getnumericalmodelfromlist(list, idx)
This module contains the OlfGwfExchangeModule Module.
Definition: exg-olfgwf.f90:6
subroutine, public olfgwf_cr(filename, name, id, m1_id, m2_id, input_mempath)
@ brief Create OLF GWF exchange
Definition: exg-olfgwf.f90:41
Channel Flow (OLF) Module.
Definition: olf.f90:3
subroutine, public olf_cr(filename, id, modelname)
Create a new overland flow model object.
Definition: olf.f90:55
Definition: prt.f90:1
subroutine, public prt_cr(filename, id, modelname)
Create a new particle tracking model object.
Definition: prt.f90:119
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public maxerrors(imax)
Set the maximum number of errors to be stored.
Definition: Sim.f90:85
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
subroutine models_create()
Set the models to be used for the simulation.
subroutine check_model_assignment()
Check for dangling models, and break with error when found.
subroutine, public simulation_da()
Deallocate simulation variables.
subroutine options_create()
Set the simulation options.
subroutine check_model_name(mtype, mname)
Check that the model name is valid.
subroutine source_simulation_nam()
Source the simulation name file.
subroutine solution_groups_create()
Set the solution_groups to be used for the simulation.
subroutine timing_create()
Set the timing module to be used for the simulation.
subroutine exchanges_create()
Set the exchanges to be used for the simulation.
subroutine assign_exchanges()
Assign exchanges to solutions.
subroutine solution_group_check(sgp, sgid, isgpsoln)
Check a solution_group to be used for the simulation.
subroutine, public simulation_cr()
Read the simulation name file and initialize the models, exchanges.
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) simulation_mode
integer(i4b) nr_procs
integer(i4b), dimension(:), allocatable model_loc_idx
equals the local index into the basemodel list (-1 when not available)
integer(i4b) iout
file unit number for simulation output
character(len=lenmodelname), dimension(:), allocatable model_names
all model names in the (global) simulation
integer(i4b) proc_id
class(basesolutiontype) function, pointer, public create_ims_solution(sim_mode, filename, sol_id)
Create an IMS solution of type NumericalSolution for serial runs or its sub-type ParallelSolution for...
class(basesolutiontype) function, pointer, public create_ems_solution(sim_mode, filename, sol_id)
Create an EMS solution of type ExplicitSolution for serial runs or its sub-type ParallelSolution for.
subroutine, public solutiongroup_create(sgp, id)
Create a new solution group.
subroutine, public addsolutiongrouptolist(list, solutiongroup)
subroutine, public tdis_cr(fname, inmempath)
Create temporal discretization.
Definition: tdis.f90:50
This module contains version information.
Definition: version.f90:7
subroutine write_listfile_header(iout, cmodel_type, write_sys_command, write_kind_info)
@ brief Write program header
Definition: version.f90:98
subroutine, public add_virtual_gwe_exchange(name, exchange_id, model1_id, model2_id)
Add a virtual GWE-GWE exchange to the simulation.
subroutine, public add_virtual_gwe_model(model_id, model_name, model)
subroutine, public add_virtual_gwf_exchange(name, exchange_id, model1_id, model2_id)
Add a virtual GWF-GWF exchange to the simulation.
subroutine, public add_virtual_gwf_model(model_id, model_name, model)
Add virtual GWF model.
subroutine, public add_virtual_gwt_exchange(name, exchange_id, model1_id, model2_id)
Add a virtual GWT-GWT exchange to the simulation.
subroutine, public add_virtual_gwt_model(model_id, model_name, model)
Highest level model type. All models extend this parent type.
Definition: BaseModel.f90:13
This class is used to store a single deferred-length character string. It was designed to work in an ...
Definition: CharString.f90:23
A generic heterogeneous doubly-linked list.
Definition: List.f90:14