MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
mf6core.f90
Go to the documentation of this file.
1 !> @brief Core MODFLOW 6 module
2 !!
3 !! This module contains the core components for MODFLOW 6. This module
4 !! is used by the stand-alone executable and the share object versions
5 !! of MODFLOW 6.
6 !!
7 !<
9  use kindmodule, only: i4b, lgp
20  use simstagesmodule
21  use profilermodule
22  implicit none
23 
24  class(runcontroltype), pointer :: run_ctrl => null() !< the run controller for this simulation
25 
26 contains
27 
28  !> @brief Main controller
29  !!
30  !! This subroutine is the main controller for MODFLOW 6.
31  !!
32  !<
33  subroutine mf6run
34  ! -- modules
36  use tdismodule, only: endofsimulation
37  ! -- local
38  logical(LGP) :: hasConverged
39  !
40  ! -- parse any command line arguments
42  !
43  ! initialize simulation
44  call mf6initialize()
45  !
46  ! -- time loop
47  do while (.not. endofsimulation)
48 
49  ! perform a time step
50  hasconverged = mf6update()
51 
52  ! if not converged, break
53  if (.not. hasconverged) exit
54 
55  end do
56  !
57  ! -- finalize simulation
58  call mf6finalize()
59 
60  end subroutine mf6run
61 
62  !> @brief Initialize a simulation
63  !!
64  !! This subroutine initializes a MODFLOW 6 simulation. The subroutine:
65  !! - creates the simulation
66  !! - defines
67  !! - allocates and reads static data
68  !!
69  !<
70  subroutine mf6initialize()
71  ! -- modules
74  use sourceloadmodule, only: export_cr
75 
76  call g_prof%pre_init()
77 
78  ! -- get the run controller for sequential or parallel builds
80  call run_ctrl%start()
81 
82  ! -- print info and start timer
83  call print_info()
84 
85  ! -- create mfsim.lst
86  call create_lstfile()
87 
88  ! -- load input context
89  call static_input_load()
90 
91  ! init timer and start
92  call g_prof%initialize()
93  call g_prof%start("Initialize", g_prof%tmr_init)
94 
95  ! -- create
96  call simulation_cr()
97 
98  ! -- define
99  call simulation_df()
100 
101  ! -- allocate and read
102  call simulation_ar()
103 
104  ! -- create model exports
105  call export_cr()
106 
107  ! -- stop the timer
108  call g_prof%stop(g_prof%tmr_init)
109 
110  end subroutine mf6initialize
111 
112  !> @brief Run a time step
113  !!
114  !! This function runs a single time step to completion.
115  !!
116  !! @return hasConverged boolean indicating if convergence was achieved for the time step
117  !!
118  !<
119  function mf6update() result(hasConverged)
120  logical(LGP) :: hasconverged
121  ! start timer
122  call g_prof%start("Update", g_prof%tmr_update)
123  !
124  ! -- prepare timestep
125  call mf6preparetimestep()
126  !
127  ! -- do timestep
128  call mf6dotimestep()
129  !
130  ! -- after timestep
131  hasconverged = mf6finalizetimestep()
132 
133  ! stop timer
134  call g_prof%stop(g_prof%tmr_update)
135 
136  end function mf6update
137 
138  !> @brief Finalize the simulation
139  !!
140  !! This subroutine finalizes a simulation. Steps include:
141  !! - final processing
142  !! - deallocate memory
143  !!
144  !<
145  subroutine mf6finalize()
146  ! -- modules
147  use, intrinsic :: iso_fortran_env, only: output_unit
148  use listsmodule, only: lists_da
150  use tdismodule, only: tdis_da
151  use idmloadmodule, only: idm_da
152  use sourceloadmodule, only: export_da
153  use simvariablesmodule, only: iout
154  ! -- local variables
155  integer(I4B) :: im
156  integer(I4B) :: ic
157  integer(I4B) :: is
158  integer(I4B) :: isg
159  class(solutiongrouptype), pointer :: sgp => null()
160  class(basesolutiontype), pointer :: sp => null()
161  class(basemodeltype), pointer :: mp => null()
162  class(baseexchangetype), pointer :: ep => null()
163  class(spatialmodelconnectiontype), pointer :: mc => null()
164  integer(I4B) :: tmr_dealloc
165 
166  ! start timer
167  call g_prof%start("Finalize", g_prof%tmr_finalize)
168 
169  !
170  ! -- FINAL PROCESSING (FP)
171  ! -- Final processing for each model
172  do im = 1, basemodellist%Count()
173  mp => getbasemodelfromlist(basemodellist, im)
174  call mp%model_fp()
175  end do
176  !
177  ! -- Final processing for each exchange
178  do ic = 1, baseexchangelist%Count()
179  ep => getbaseexchangefromlist(baseexchangelist, ic)
180  call ep%exg_fp()
181  end do
182  !
183  ! -- Final processing for each solution
184  do is = 1, basesolutionlist%Count()
185  sp => getbasesolutionfromlist(basesolutionlist, is)
186  call sp%sln_fp()
187  end do
188 
189  ! start timer for deallocation
190  tmr_dealloc = -1
191  call g_prof%start("Deallocate", tmr_dealloc)
192 
193  !
194  ! -- DEALLOCATE (DA)
195  ! -- Deallocate tdis
196  call tdis_da()
197  !
198  ! -- Deallocate for each model
199  do im = 1, basemodellist%Count()
200  mp => getbasemodelfromlist(basemodellist, im)
201  call mp%model_da()
202  deallocate (mp)
203  end do
204  !
205  ! -- Deallocate for each exchange
206  do ic = 1, baseexchangelist%Count()
207  ep => getbaseexchangefromlist(baseexchangelist, ic)
208  call ep%exg_da()
209  deallocate (ep)
210  end do
211  !
212  ! -- Deallocate for each connection
213  do ic = 1, baseconnectionlist%Count()
214  mc => get_smc_from_list(baseconnectionlist, ic)
215  call mc%exg_da()
216  deallocate (mc)
217  end do
218  !
219  ! -- Deallocate for each solution
220  do is = 1, basesolutionlist%Count()
221  sp => getbasesolutionfromlist(basesolutionlist, is)
222  call sp%sln_da()
223  deallocate (sp)
224  end do
225  !
226  ! -- Deallocate solution group and simulation variables
227  do isg = 1, solutiongrouplist%Count()
228  sgp => getsolutiongroupfromlist(solutiongrouplist, isg)
229  call sgp%sgp_da()
230  deallocate (sgp)
231  end do
232  !
233  call idm_da(iout)
234  call export_da()
235  call simulation_da()
236  call lists_da()
237 
238  ! stop timer
239  call g_prof%stop(tmr_dealloc)
240 
241  ! finish gently (No calls after this)
242  ! timer is stopped inside because this call does not return
243  call run_ctrl%finish()
244 
245  end subroutine mf6finalize
246 
247  !> @brief print initial message
248  !<
249  subroutine print_info()
250  use simmodule, only: initial_message
251  use timermodule, only: print_start_time
252 
253  ! print initial message
254  call initial_message()
255 
256  ! get start time
257  call print_start_time()
258 
259  end subroutine print_info
260 
261  !> @brief Set up mfsim list file output logging
262  !!
263  !! This subroutine creates the mfsim list file
264  !! and writes the header.
265  !!
266  !<
267  subroutine create_lstfile()
268  use constantsmodule, only: linelength
271  use messagemodule, only: write_message
273  character(len=LINELENGTH) :: line
274  !
275  ! -- Open simulation list file
276  iout = getunit()
277  !
278  if (nr_procs > 1) then
280  end if
281  !
282  call openfile(iout, 0, simlstfile, 'LIST', filstat_opt='REPLACE')
283  !
284  ! -- write simlstfile to stdout
285  write (line, '(2(1x,A))') 'Writing simulation list file:', &
286  trim(adjustl(simlstfile))
287  !
288  call write_message(line)
290  end subroutine create_lstfile
291 
292  !> @brief Create simulation input context
293  !!
294  !! This subroutine creates the simulation input context
295  !!
296  !<
297  subroutine static_input_load()
298  ! -- modules
299  use constantsmodule, only: lenmempath
300  use simvariablesmodule, only: iout
301  use idmloadmodule, only: simnam_load, simtdis_load, &
305  use simvariablesmodule, only: iparamlog
306  !
307  ! -- load simnam input context
308  call simnam_load(iparamlog)
309  !
310  ! -- load tdis to input context
311  call simtdis_load()
312  !
313  ! -- load in scope models
314  call load_models(iout)
315  !
316  ! -- load in scope exchanges
317  call load_exchanges(iout)
318  end subroutine static_input_load
319 
320  !> @brief Define the simulation
321  !!
322  !! This subroutine defined the simulation. Steps include:
323  !! - define each model
324  !! - define each solution
325  !!
326  !<
327  subroutine simulation_df()
328  ! -- modules
329  use idmloadmodule, only: idm_df
330  ! -- local variables
331  integer(I4B) :: im
332  integer(I4B) :: ic
333  integer(I4B) :: is
334  class(basesolutiontype), pointer :: sp => null()
335  class(basemodeltype), pointer :: mp => null()
336  class(baseexchangetype), pointer :: ep => null()
337  class(spatialmodelconnectiontype), pointer :: mc => null()
338 
339  ! -- init virtual data environment
340  call run_ctrl%at_stage(stg_bfr_mdl_df)
341 
342  ! -- Define each model
343  do im = 1, basemodellist%Count()
345  call mp%model_df()
346  end do
347  !
348  ! -- synchronize
349  call run_ctrl%at_stage(stg_aft_mdl_df)
350  !
351  ! -- Define each exchange
352  do ic = 1, baseexchangelist%Count()
354  call ep%exg_df()
355  end do
356  !
357  ! -- synchronize
358  call run_ctrl%at_stage(stg_aft_exg_df)
359  !
360  ! -- when needed, this is where the interface models are
361  ! created and added to the numerical solutions
362  call connections_cr()
363  !
364  ! -- synchronize
365  call run_ctrl%at_stage(stg_aft_con_cr)
366  !
367  ! -- synchronize
368  call run_ctrl%at_stage(stg_bfr_con_df)
369  !
370  ! -- Define each connection
371  do ic = 1, baseconnectionlist%Count()
373  call mc%exg_df()
374  end do
375  !
376  ! -- synchronize
377  call run_ctrl%at_stage(stg_aft_con_df)
378  !
379  ! -- Define each solution
380  do is = 1, basesolutionlist%Count()
382  call sp%sln_df()
383  end do
384 
385  ! idm df
386  call idm_df()
387 
388  end subroutine simulation_df
389 
390  !> @brief Simulation allocate and read
391  !!
392  !! This subroutine allocates and reads static data for the simulation.
393  !! Steps include:
394  !! - allocate and read for each model
395  !! - allocate and read for each exchange
396  !! - allocate and read for each solution
397  !!
398  !<
399  subroutine simulation_ar()
401  ! -- local variables
402  integer(I4B) :: im
403  integer(I4B) :: ic
404  integer(I4B) :: is
405  class(basesolutiontype), pointer :: sp => null()
406  class(basemodeltype), pointer :: mp => null()
407  class(baseexchangetype), pointer :: ep => null()
408  class(spatialmodelconnectiontype), pointer :: mc => null()
409 
410  ! -- Allocate and read each model
411  do im = 1, basemodellist%Count()
413  call mp%model_ar()
414  end do
415  !
416  ! -- Allocate and read each exchange
417  do ic = 1, baseexchangelist%Count()
419  call ep%exg_ar()
420  end do
421  !
422  ! -- Synchronize
423  call run_ctrl%at_stage(stg_bfr_con_ar)
424  !
425  ! -- Allocate and read all model connections
426  do ic = 1, baseconnectionlist%Count()
428  call mc%exg_ar()
429  end do
430  !
431  ! -- Synchronize
432  call run_ctrl%at_stage(stg_aft_con_ar)
433  !
434  ! -- Allocate and read each solution
435  do is = 1, basesolutionlist%Count()
437  call sp%sln_ar()
438  end do
439  !
440  end subroutine simulation_ar
441 
442  !> @brief Create the model connections from the exchanges
443  !!
444  !! This will upgrade the numerical exchanges in the solution,
445  !! whenever the configuration requires this, to Connection
446  !! objects. Currently we anticipate:
447  !!
448  !! GWF-GWF => GwfGwfConnection
449  !! GWT-GWT => GwtGwtConecction
450  !<
451  subroutine connections_cr()
453  use simvariablesmodule, only: iout
454  use versionmodule, only: idevelopmode
455  integer(I4B) :: isol
456  type(connectionbuildertype) :: connectionBuilder
457  class(basesolutiontype), pointer :: sol => null()
458  integer(I4B) :: status
459  character(len=16) :: envvar
460 
461  write (iout, '(/a)') 'PROCESSING MODEL CONNECTIONS'
462 
463  if (baseexchangelist%Count() == 0) then
464  ! if this is not a coupled simulation in any way,
465  ! then we will not need model connections
466  return
467  end if
468 
469  if (idevelopmode == 1) then
470  call get_environment_variable('DEV_ALWAYS_USE_IFMOD', &
471  value=envvar, status=status)
472  if (status == 0 .and. envvar == '1') then
473  connectionbuilder%dev_always_ifmod = .true.
474  write (iout, '(/a)') "Development option: forcing interface model"
475  end if
476  end if
477 
478  do isol = 1, basesolutionlist%Count()
480  call connectionbuilder%processSolution(sol)
481  end do
482 
483  write (iout, '(a)') 'END OF MODEL CONNECTIONS'
484  end subroutine connections_cr
485 
486  !> @brief Read and prepare time step
487  !!
488  !! This subroutine reads and prepares period data for the simulation.
489  !! Steps include:
490  !! - read and prepare for each model
491  !! - read and prepare for each exchange
492  !! - reset convergence flag
493  !! - calculate maximum time step for each model
494  !! - calculate maximum time step for each exchange
495  !! - calculate maximum time step for each solution
496  !! - set time discretization timestep using smallest maximum timestep
497  !!
498  !<
499  subroutine mf6preparetimestep()
500  ! -- modules
501  use kindmodule, only: i4b
504  kstp, kper
509  use simmodule, only: converge_reset
510  use simvariablesmodule, only: isim_mode
511  use idmloadmodule, only: idm_rp
513  ! -- local variables
514  class(basemodeltype), pointer :: mp => null()
515  class(baseexchangetype), pointer :: ep => null()
516  class(spatialmodelconnectiontype), pointer :: mc => null()
517  class(basesolutiontype), pointer :: sp => null()
518  character(len=LINELENGTH) :: line
519  character(len=LINELENGTH) :: fmt
520  integer(I4B) :: im
521  integer(I4B) :: ie
522  integer(I4B) :: ic
523  integer(I4B) :: is
524 
525  ! start timer
526  call g_prof%start("Prepare time step", g_prof%tmr_prep_tstp)
527 
528  !
529  ! -- initialize fmt
530  fmt = "(/,a,/)"
531  !
532  ! -- period update
533  call tdis_set_counters()
534  !
535  ! -- set base line
536  write (line, '(a,i0,a,i0,a)') &
537  'start timestep kper="', kper, '" kstp="', kstp, '" mode="'
538  !
539  ! -- evaluate simulation mode
540  select case (isim_mode)
541  case (mvalidate)
542  line = trim(line)//'validate"'
543  case (mnormal)
544  line = trim(line)//'normal"'
545  end select
546 
547  ! -- load dynamic input
548  call idm_rp()
549 
550  ! -- Read and prepare each model
551  do im = 1, basemodellist%Count()
553  call mp%model_message(line, fmt=fmt)
554  call mp%model_rp()
555  end do
556  !
557  ! -- Synchronize
558  call run_ctrl%at_stage(stg_bfr_exg_rp)
559  !
560  ! -- Read and prepare each exchange
561  do ie = 1, baseexchangelist%Count()
563  call ep%exg_rp()
564  end do
565  !
566  ! -- Read and prepare each connection
567  do ic = 1, baseconnectionlist%Count()
568  mc => get_smc_from_list(baseconnectionlist, ic)
569  call mc%exg_rp()
570  end do
571  !
572  ! -- Synchronize
573  call run_ctrl%at_stage(stg_aft_con_rp)
574  !
575  ! -- reset simulation convergence flag
576  call converge_reset()
577  !
578  ! -- time update for each model
579  do im = 1, basemodellist%Count()
581  call mp%model_dt()
582  end do
583  !
584  ! -- time update for each exchange
585  do ie = 1, baseexchangelist%Count()
587  call ep%exg_dt()
588  end do
589  !
590  ! -- time update for each connection
591  do ic = 1, baseconnectionlist%Count()
592  mc => get_smc_from_list(baseconnectionlist, ic)
593  call mc%exg_dt()
594  end do
595  !
596  ! -- time update for each solution
597  do is = 1, basesolutionlist%Count()
598  sp => getbasesolutionfromlist(basesolutionlist, is)
599  call sp%sln_dt()
600  end do
601  !
602  ! -- update exports
603  call export_post_prepare()
604  !
605  ! -- set time step
606  call tdis_set_timestep()
607 
608  ! stop timer
609  call g_prof%stop(g_prof%tmr_prep_tstp)
610 
611  end subroutine mf6preparetimestep
612 
613  !> @brief Run time step
614  !!
615  !! This subroutine runs a single time step for the simulation.
616  !! Steps include:
617  !! - formulate the system of equations for each model and exchange
618  !! - solve each solution
619  !!
620  !<
621  subroutine mf6dotimestep()
622  ! -- modules
623  use kindmodule, only: i4b
624  use listsmodule, only: solutiongrouplist
627  use idmloadmodule, only: idm_ad
628  ! -- local variables
629  class(solutiongrouptype), pointer :: sgp => null()
630  integer(I4B) :: isg
631  logical :: finishedTrying
632 
633  ! start timer
634  call g_prof%start("Do time step", g_prof%tmr_do_tstp)
635 
636  ! -- By default, the solution groups will be solved once, and
637  ! may fail. But if adaptive stepping is active, then
638  ! the solution groups may be solved over and over with
639  ! progressively smaller time steps to see if convergence
640  ! can be obtained.
641  ifailedstepretry = 0
642  retryloop: do
643 
644  ! -- idm advance
645  call idm_ad()
646 
647  do isg = 1, solutiongrouplist%Count()
649  call sgp%sgp_ca()
650  end do
651 
652  call sim_step_retry(finishedtrying)
653  if (finishedtrying) exit retryloop
655 
656  end do retryloop
657 
658  ! stop timer
659  call g_prof%stop(g_prof%tmr_do_tstp)
660 
661  end subroutine mf6dotimestep
662 
663  !> @brief Rerun time step
664  !!
665  !! This subroutine reruns a single time step for the simulation when
666  !! the adaptive time step option is used.
667  !!
668  !<
669  subroutine sim_step_retry(finishedTrying)
670  ! -- modules
671  use kindmodule, only: dp
673  use simmodule, only: converge_reset
674  use tdismodule, only: kstp, kper, delt, tdis_delt_reset
676  ! -- dummy variables
677  logical, intent(out) :: finishedTrying !< boolean that indicates if no
678  ! additional reruns of the time step are required
679  !
680  ! -- Check with ats to reset delt and keep trying
681  finishedtrying = .true.
682  call ats_reset_delt(kstp, kper, laststepfailed, delt, finishedtrying)
683  !
684  if (.not. finishedtrying) then
685  !
686  ! -- Reset delt, which requires updating pertim, totim
687  ! and end of period and simulation indicators
688  call tdis_delt_reset(delt)
689  !
690  ! -- Reset state of the simulation convergence flag
691  call converge_reset()
692 
693  end if
694  end subroutine sim_step_retry
695 
696  !> @brief Finalize time step
697  !!
698  !! This function finalizes a single time step for the simulation
699  !! and writes output for the time step. Steps include:
700  !! - write output for each model
701  !! - write output for each exchange
702  !! - write output for each solutions
703  !! - perform a final convergence check and whether the simulation
704  !! can continue if convergence was not achieved
705  !!
706  !! @return hasConverged boolean indicating if convergence was achieved for the time step
707  !!
708  !<
709  function mf6finalizetimestep() result(hasConverged)
710  ! -- modules
711  use kindmodule, only: i4b
717  use simmodule, only: converge_check
718  use simvariablesmodule, only: isim_mode
720  ! -- return variable
721  logical(LGP) :: hasconverged
722  ! -- local variables
723  class(basesolutiontype), pointer :: sp => null()
724  class(basemodeltype), pointer :: mp => null()
725  class(baseexchangetype), pointer :: ep => null()
726  class(spatialmodelconnectiontype), pointer :: mc => null()
727  character(len=LINELENGTH) :: line
728  character(len=LINELENGTH) :: fmt
729  integer(I4B) :: im
730  integer(I4B) :: ix
731  integer(I4B) :: ic
732  integer(I4B) :: is
733  !
734  ! -- initialize format and line
735  fmt = "(/,a,/)"
736  line = 'end timestep'
737 
738  ! start timer
739  call g_prof%start("Finalize time step", g_prof%tmr_final_tstp)
740 
741  !
742  ! -- evaluate simulation mode
743  select case (isim_mode)
744  case (mvalidate)
745  !
746  ! -- Write final message for timestep for each model
747  do im = 1, basemodellist%Count()
749  call mp%model_message(line, fmt=fmt)
750  end do
751  case (mnormal)
752 
753  call g_prof%start("Write output", g_prof%tmr_output)
754  !
755  ! -- Write output and final message for timestep for each model
756  do im = 1, basemodellist%Count()
758  call mp%model_ot()
759  call mp%model_message(line, fmt=fmt)
760  end do
761  !
762  ! -- Write output for each exchange
763  do ix = 1, baseexchangelist%Count()
765  call ep%exg_ot()
766  end do
767  !
768  ! -- Write output for each connection
769  do ic = 1, baseconnectionlist%Count()
770  mc => get_smc_from_list(baseconnectionlist, ic)
771  call mc%exg_ot()
772  end do
773  !
774  ! -- Write output for each solution
775  do is = 1, basesolutionlist%Count()
777  call sp%sln_ot()
778  end do
779  !
780  ! -- update exports
781  call g_prof%start("NetCDF export", g_prof%tmr_nc_export)
782  call export_post_step()
783  call g_prof%stop(g_prof%tmr_nc_export)
784 
785  call g_prof%stop(g_prof%tmr_output)
786  end select
787  !
788  ! -- Check if we're done
789  call converge_check(hasconverged)
790 
791  ! stop timer
792  call g_prof%stop(g_prof%tmr_final_tstp)
793 
794  end function mf6finalizetimestep
795 
796 end module mf6coremodule
subroutine, public ats_reset_delt(kstp, kper, lastStepFailed, delt, finishedTrying)
@ brief Reset time step because failure has occurred
Definition: ats.f90:606
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
class(basesolutiontype) function, pointer, public getbasesolutionfromlist(list, idx)
subroutine, public getcommandlinearguments()
Get command line arguments.
Definition: comarg.f90:29
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
@ mvalidate
validation mode - do not run time steps
Definition: Constants.f90:205
@ mnormal
normal output mode
Definition: Constants.f90:206
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
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
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
subroutine, public load_models(iout)
load model namfiles and model package files
Definition: IdmLoad.f90:218
subroutine, public load_exchanges(iout)
load exchange files
Definition: IdmLoad.f90:285
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public append_processor_id(name, proc_id)
Append processor id to a string.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
This module defines variable data types.
Definition: kind.f90:8
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 baseconnectionlist
Definition: mf6lists.f90:28
type(listtype), public basesolutionlist
Definition: mf6lists.f90:19
subroutine, public lists_da()
Definition: mf6lists.f90:34
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
Store and issue logging messages to output units.
Definition: Message.f90:2
subroutine, public write_message(text, iunit, fmt, skipbefore, skipafter, advance)
Write a message to an output unit.
Definition: Message.f90:210
Core MODFLOW 6 module.
Definition: mf6core.f90:8
subroutine mf6dotimestep()
Run time step.
Definition: mf6core.f90:622
subroutine mf6run
Main controller.
Definition: mf6core.f90:34
subroutine static_input_load()
Create simulation input context.
Definition: mf6core.f90:298
subroutine mf6preparetimestep()
Read and prepare time step.
Definition: mf6core.f90:500
subroutine simulation_df()
Define the simulation.
Definition: mf6core.f90:328
subroutine simulation_ar()
Simulation allocate and read.
Definition: mf6core.f90:400
class(runcontroltype), pointer run_ctrl
the run controller for this simulation
Definition: mf6core.f90:24
logical(lgp) function mf6update()
Run a time step.
Definition: mf6core.f90:120
subroutine sim_step_retry(finishedTrying)
Rerun time step.
Definition: mf6core.f90:670
subroutine mf6initialize()
Initialize a simulation.
Definition: mf6core.f90:71
logical(lgp) function mf6finalizetimestep()
Finalize time step.
Definition: mf6core.f90:710
subroutine create_lstfile()
Set up mfsim list file output logging.
Definition: mf6core.f90:268
subroutine connections_cr()
Create the model connections from the exchanges.
Definition: mf6core.f90:452
subroutine mf6finalize()
Finalize the simulation.
Definition: mf6core.f90:146
subroutine print_info()
print initial message
Definition: mf6core.f90:250
type(profilertype), public g_prof
the global timer object (to reduce trivial lines of code)
Definition: Profiler.f90:70
class(runcontroltype) function, pointer, public create_run_control()
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public converge_reset()
Reset the simulation convergence flag.
Definition: Sim.f90:389
subroutine, public initial_message()
Print the header and initializes messaging.
Definition: Sim.f90:442
subroutine, public converge_check(hasConverged)
Simulation convergence check.
Definition: Sim.f90:402
integer(i4b), parameter, public stg_aft_con_ar
afterr connection allocate read
Definition: SimStages.f90:18
integer(i4b), parameter, public stg_aft_con_df
after connection define
Definition: SimStages.f90:15
integer(i4b), parameter, public stg_aft_mdl_df
after model define
Definition: SimStages.f90:11
integer(i4b), parameter, public stg_bfr_mdl_df
before model define
Definition: SimStages.f90:10
integer(i4b), parameter, public stg_aft_exg_df
after exchange define
Definition: SimStages.f90:12
integer(i4b), parameter, public stg_aft_con_cr
after connection create
Definition: SimStages.f90:13
integer(i4b), parameter, public stg_bfr_exg_rp
before exchange read prepare
Definition: SimStages.f90:19
integer(i4b), parameter, public stg_bfr_con_ar
before connection allocate read
Definition: SimStages.f90:17
integer(i4b), parameter, public stg_aft_con_rp
after connection read prepare
Definition: SimStages.f90:20
integer(i4b), parameter, public stg_bfr_con_df
before connection define
Definition: SimStages.f90:14
subroutine, public simulation_da()
Deallocate simulation variables.
subroutine, public simulation_cr()
Read the simulation name file and initialize the models, exchanges.
This module contains simulation variables.
Definition: SimVariables.f90:9
integer(i4b) ifailedstepretry
current retry for this time step
integer(i4b) nr_procs
integer(i4b) laststepfailed
flag indicating if the last step failed (1) if last step failed; (0) otherwise (set in converge_check...
integer(i4b) iout
file unit number for simulation output
integer(i4b) iparamlog
input (idm) parameter logging to simulation listing file
character(len=linelength) simlstfile
simulation listing file name
integer(i4b) proc_id
integer(i4b) isim_mode
simulation mode
class(solutiongrouptype) function, pointer, public getsolutiongroupfromlist(list, idx)
This module contains the SourceLoadModule.
Definition: SourceLoad.F90:8
subroutine, public export_da()
deallocate model export objects and list
Definition: SourceLoad.F90:340
subroutine, public export_cr()
create model exports list
Definition: SourceLoad.F90:305
subroutine, public export_post_prepare()
model exports post prepare step actions
Definition: SourceLoad.F90:326
subroutine, public export_post_step()
model exports post step actions
Definition: SourceLoad.F90:333
class(spatialmodelconnectiontype) function, pointer, public get_smc_from_list(list, idx)
Get the connection from a list.
logical(lgp), pointer, public endofsimulation
flag indicating end of simulation
Definition: tdis.f90:28
subroutine, public tdis_set_timestep()
Set time step length.
Definition: tdis.f90:153
subroutine, public tdis_set_counters()
Set kstp and kper.
Definition: tdis.f90:91
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
subroutine, public tdis_da()
Deallocate memory.
Definition: tdis.f90:345
subroutine, public tdis_delt_reset(deltnew)
Reset delt and update timing variables and indicators.
Definition: tdis.f90:213
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29
subroutine, public print_start_time()
Start simulation timer.
Definition: Timer.f90:19
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
integer(i4b), parameter idevelopmode
Definition: version.f90:19
Highest level model type. All models extend this parent type.
Definition: BaseModel.f90:13
Class to manage spatial connection of a model to one or more models of the same type....