MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
Sim.f90
Go to the documentation of this file.
1 !> @brief This module contains simulation methods
2 !!
3 !! This module contains simulation methods for storing warning and error
4 !! messages and notes. This module also has methods for counting warnings,
5 !! errors, and notes in addition to stopping the simulation. The module does
6 !! not have any dependencies on models, exchanges, or solutions in a
7 !! simulation.
8 !!
9 !<
10 module simmodule
11 
12  use kindmodule, only: dp, i4b
13  use errorutilmodule, only: pstop
14  use definedmacros, only: get_os
16  done, &
17  iustart, iulast, &
18  vsummary, vall, vdebug, &
19  oswin, osundef
21  iforcestop, iunext, &
22  warnmsg
24 
25  implicit none
26 
27  private
28  public :: count_errors
29  public :: store_error
30  public :: ustop
31  public :: converge_reset
32  public :: converge_check
33  public :: initial_message
34  public :: final_message
35  public :: store_warning
36  public :: deprecation_warning
37  public :: store_note
38  public :: count_warnings
39  public :: count_notes
40  public :: store_error_unit
41  public :: store_error_filename
42  public :: maxerrors
43 
48 
49 contains
50 
51  !> @brief Return number of errors
52  !!
53  !! Function to return the number of errors messages that have been stored.
54  !!
55  !! @return ncount number of error messages stored
56  !!
57  !<
58  function count_errors() result(ncount)
59  integer(I4B) :: ncount
60  ncount = sim_errors%count()
61  end function count_errors
62 
63  !> @brief Return number of warnings
64  !!
65  !! Function to return the number of warning messages that have been stored.
66  !!
67  !! @return ncount number of warning messages stored
68  !!
69  !<
70  function count_warnings() result(ncount)
71  integer(I4B) :: ncount
72  ncount = sim_warnings%count()
73  end function count_warnings
74 
75  !> @brief Return the number of notes stored.
76  !<
77  function count_notes() result(ncount)
78  integer(I4B) :: ncount
79  ncount = sim_notes%count()
80  end function count_notes
81 
82  !> @brief Set the maximum number of errors to be stored.
83  !<
84  subroutine maxerrors(imax)
85  integer(I4B), intent(in) :: imax !< maximum number of error messages that will be stored
86  call sim_errors%set_max(imax)
87  end subroutine maxerrors
88 
89  !> @brief Store an error message.
90  !<
91  subroutine store_error(msg, terminate)
92  ! -- dummy variable
93  character(len=*), intent(in) :: msg !< error message
94  logical, optional, intent(in) :: terminate !< boolean indicating if the simulation should be terminated
95  ! -- local variables
96  logical :: lterminate
97  !
98  ! -- process optional variables
99  if (present(terminate)) then
100  lterminate = terminate
101  else
102  lterminate = .false.
103  end if
104  !
105  ! -- store error
106  call sim_errors%store(msg)
107  !
108  ! -- terminate the simulation
109  if (lterminate) then
110  call ustop()
111  end if
112 
113  end subroutine store_error
114 
115  !> @brief Get the file name
116  !!
117  !! Subroutine to get the file name from the unit number for a open file.
118  !! If the INQUIRE function returns the full path (for example, the INTEL
119  !! compiler) then the returned file name (fname) is limited to the filename
120  !! without the path.
121  !!
122  !<
123  subroutine get_filename(iunit, fname)
124  ! -- dummy variables
125  integer(I4B), intent(in) :: iunit !< open file unit number
126  character(len=*), intent(inout) :: fname !< file name attached to the open file unit number
127  ! -- local variables
128  integer(I4B) :: ipos
129  integer(I4B) :: ios
130  integer(I4B) :: ilen
131  !
132  ! -- get file name from unit number
133  inquire (unit=iunit, name=fname)
134  !
135  ! -- determine the operating system
136  ios = get_os()
137  !
138  ! -- extract filename from full path, if present
139  ! forward slash on linux, unix, and osx
140  if (ios /= oswin) then
141  ipos = index(fname, '/', back=.true.)
142  end if
143  !
144  ! -- check for backslash on windows or undefined os and
145  ! forward slashes were not found
146  if (ios == oswin .or. ios == osundef) then
147  if (ipos < 1) then
148  ipos = index(fname, '\', back=.true.)
149  end if
150  end if
151  !
152  ! -- exclude the path from the file name
153  if (ipos > 0) then
154  ilen = len_trim(fname)
155  write (fname, '(a)') fname(ipos + 1:ilen)//' '
156  end if
157 
158  end subroutine get_filename
159 
160  !> @brief Store the file unit number
161  !!
162  !! Subroutine to convert the unit number for a open file to a file name
163  !! and indicate that there is an error reading from the file. By default,
164  !! the simulation is terminated when this subroutine is called.
165  !!
166  !<
167  subroutine store_error_unit(iunit, terminate)
168  ! -- dummy variables
169  integer(I4B), intent(in) :: iunit !< open file unit number
170  logical, optional, intent(in) :: terminate !< boolean indicating if the simulation should be terminated
171  ! -- local variables
172  logical :: lterminate
173  character(len=LINELENGTH) :: fname
174  character(len=LINELENGTH) :: errmsg
175  !
176  ! -- process optional variables
177  if (present(terminate)) then
178  lterminate = terminate
179  else
180  lterminate = .true.
181  end if
182  !
183  ! -- store error unit
184  inquire (unit=iunit, name=fname)
185  write (errmsg, '(3a)') &
186  "Error occurred while reading file '", trim(adjustl(fname)), "'"
187  call sim_uniterrors%store(errmsg)
188  !
189  ! -- terminate the simulation
190  if (lterminate) then
191  call ustop()
192  end if
193 
194  end subroutine store_error_unit
195 
196  !> @brief Store the erroring file name
197  !!
198  !! Subroutine to store the file name issuing an error. By default,
199  !! the simulation is terminated when this subroutine is called
200  !!
201  !<
202  subroutine store_error_filename(filename, terminate)
203  ! -- dummy variables
204  character(len=*), intent(in) :: filename !< erroring file name
205  logical, optional, intent(in) :: terminate !< boolean indicating if the simulation should be terminated
206  ! -- local variables
207  logical :: lterminate
208  character(len=LINELENGTH) :: errmsg
209  !
210  ! -- process optional variables
211  if (present(terminate)) then
212  lterminate = terminate
213  else
214  lterminate = .true.
215  end if
216  !
217  ! -- store error unit
218  write (errmsg, '(3a)') &
219  "ERROR OCCURRED WHILE READING FILE '", trim(adjustl(filename)), "'"
220  call sim_uniterrors%store(errmsg)
221  !
222  ! -- terminate the simulation
223  if (lterminate) then
224  call ustop()
225  end if
226 
227  end subroutine store_error_filename
228 
229  !> @brief Store warning message
230  !!
231  !! Subroutine to store a warning message for printing at the end of
232  !! the simulation.
233  !!
234  !<
235  subroutine store_warning(msg, substring)
236  ! -- dummy variables
237  character(len=*), intent(in) :: msg !< warning message
238  character(len=*), intent(in), optional :: substring !< optional string that can be used
239  !! to prevent storing duplicate messages
240  !
241  ! -- store warning
242  if (present(substring)) then
243  call sim_warnings%store(msg, substring)
244  else
245  call sim_warnings%store(msg)
246  end if
247  !
248  ! -- return
249  return
250  end subroutine store_warning
251 
252  !> @brief Store deprecation warning message
253  !!
254  !! Subroutine to store a warning message for deprecated variables
255  !! and printing at the end of simulation.
256  !!
257  !<
258  subroutine deprecation_warning(cblock, cvar, cver, endmsg, iunit)
259  ! -- modules
261  ! -- dummy variables
262  character(len=*), intent(in) :: cblock !< block name
263  character(len=*), intent(in) :: cvar !< variable name
264  character(len=*), intent(in) :: cver !< version when variable was deprecated
265  character(len=*), intent(in), optional :: endmsg !< optional user defined message to append
266  !! at the end of the deprecation warning
267  integer(I4B), intent(in), optional :: iunit !< optional input file unit number with
268  !! the deprecated variable
269  ! -- local variables
270  character(len=MAXCHARLEN) :: message
271  character(len=LINELENGTH) :: fname
272  !
273  ! -- build message
274  write (message, '(a)') &
275  trim(cblock)//" BLOCK VARIABLE '"//trim(cvar)//"'"
276  if (present(iunit)) then
277  call get_filename(iunit, fname)
278  write (message, '(a,1x,3a)') &
279  trim(message), "IN FILE '", trim(fname), "'"
280  end if
281  write (message, '(a)') &
282  trim(message)//' WAS DEPRECATED IN VERSION '//trim(cver)//'.'
283  if (present(endmsg)) then
284  write (message, '(a,1x,2a)') trim(message), trim(endmsg), '.'
285  end if
286  !
287  ! -- store warning
288  call sim_warnings%store(message)
289 
290  end subroutine deprecation_warning
291 
292  !> @brief Store note
293  !!
294  !! Subroutine to store a note for printing at the end of the simulation.
295  !!
296  !<
297  subroutine store_note(note)
298  ! -- modules
300  ! -- dummy variables
301  character(len=*), intent(in) :: note !< note
302  !
303  ! -- store note
304  call sim_notes%store(note)
305 
306  end subroutine store_note
307 
308  !> @brief Stop the simulation.
309  !!
310  !! Subroutine to stop the simulations with option to print message
311  !! before stopping with the active error code.
312  !!
313  !<
314  subroutine ustop(stopmess, ioutlocal)
315  ! -- dummy variables
316  character, optional, intent(in) :: stopmess * (*) !< optional message to print before
317  !! stopping the simulation
318  integer(I4B), optional, intent(in) :: ioutlocal !< optional output file to
319  !! final message to
320  !
321  ! -- print the final message
322  call print_final_message(stopmess, ioutlocal)
323  !
324  ! -- terminate with the appropriate error code
325  call pstop(ireturnerr)
326 
327  end subroutine ustop
328 
329  !> @brief Print the final messages
330  !!
331  !! Subroutine to print the notes, warnings, errors and the final message (if passed).
332  !! The subroutine also closes all open files.
333  !!
334  !<
335  subroutine print_final_message(stopmess, ioutlocal)
336  ! -- dummy variables
337  character, optional, intent(in) :: stopmess * (*) !< optional message to print before
338  !! stopping the simulation
339  integer(I4B), optional, intent(in) :: ioutlocal !< optional output file to
340  !! final message to
341  ! -- local variables
342  character(len=*), parameter :: fmt = '(1x,a)'
343  character(len=*), parameter :: msg = 'Stopping due to error(s)'
344  !
345  ! -- print the accumulated messages
346  if (isim_level >= vall) then
347  call sim_notes%write_all('NOTES:', 'note(s)', &
348  iunit=iout)
349  call sim_warnings%write_all('WARNING REPORT:', 'warning(s)', &
350  iunit=iout)
351  end if
352  call sim_errors%write_all('ERROR REPORT:', 'error(s)', iunit=iout)
353  call sim_uniterrors%write_all('UNIT ERROR REPORT:', &
354  'file unit error(s)', iunit=iout)
355  !
356  ! -- write a stop message, if one is passed
357  if (present(stopmess)) then
358  if (stopmess .ne. ' ') then
359  call write_message(stopmess, fmt=fmt, iunit=iout)
360  call write_message(stopmess, fmt=fmt)
361  if (present(ioutlocal)) then
362  if (ioutlocal > 0 .and. ioutlocal /= iout) then
363  write (ioutlocal, fmt) trim(stopmess)
364  close (ioutlocal)
365  end if
366  end if
367  end if
368  end if
369  !
370  ! -- write console buffer output to stdout
371  flush (istdout)
372  !
373  ! -- determine if an error condition has occurred
374  if (sim_errors%count() > 0) then
375  ireturnerr = 2
376  if (present(ioutlocal)) then
377  if (ioutlocal > 0 .and. ioutlocal /= iout) write (ioutlocal, fmt) msg
378  end if
379  end if
380  !
381  ! -- close all open files
382  call sim_closefiles()
383 
384  end subroutine print_final_message
385 
386  !> @brief Reset the simulation convergence flag
387  !!
388  !! Subroutine to reset the simulation convergence flag.
389  !!
390  !<
391  subroutine converge_reset()
392  use simvariablesmodule, only: isimcnvg
393  isimcnvg = 1
394  end subroutine converge_reset
395 
396  !> @brief Simulation convergence check
397  !!
398  !! Subroutine to check simulation convergence. If the continue option is
399  !! set the simulation convergence flag is set to True if the simulation
400  !! did not actually converge for a time step and the non-convergence counter
401  !! is incremented.
402  !!
403  !<
404  subroutine converge_check(hasConverged)
405  ! -- modules
407  ! -- dummy variables
408  logical, intent(inout) :: hasconverged !< boolean indicting if the
409  !! simulation is considered converged
410  ! -- format
411  character(len=*), parameter :: fmtfail = &
412  "(1x, 'Simulation convergence failure.', &
413  &' Simulation will terminate after output and deallocation.')"
414  !
415  ! -- Initialize hasConverged to True
416  hasconverged = .true.
417  !
418  ! -- Count number of failures
419  if (isimcnvg == 0) then
421  end if
422  !
423  ! -- Continue if 'CONTINUE' specified in simulation control file
424  if (isimcontinue == 1) then
425  if (isimcnvg == 0) then
426  isimcnvg = 1
427  end if
428  end if
429  !
430  ! -- save simulation failure message
431  if (isimcnvg == 0) then
432  call write_message('', fmt=fmtfail, iunit=iout)
433  hasconverged = .false.
434  end if
435 
436  end subroutine converge_check
437 
438  !> @brief Print the header and initializes messaging
439  !!
440  !! Subroutine that prints the initial message and initializes the notes,
441  !! warning messages, unit errors, and error messages.
442  !!
443  !<
444  subroutine initial_message()
445  ! -- modules
448  !
449  ! -- initialize message lists
450  call sim_errors%init()
451  call sim_uniterrors%init()
452  call sim_warnings%init()
453  call sim_notes%init()
454  !
455  ! -- Write banner to screen (unit stdout)
456  call write_listfile_header(istdout, write_kind_info=.false., &
457  write_sys_command=.false.)
458  !
459  call write_message(' MODFLOW runs in '//trim(simulation_mode)//' mode', &
460  skipafter=1)
461  !
462  if (simulation_mode == 'PARALLEL' .and. nr_procs == 1) then
463  call store_warning('Running parallel MODFLOW on only 1 process')
464  end if
465  !
466  end subroutine initial_message
467 
468  !> @brief Create final message
469  !!
470  !! Subroutine that creates the appropriate final message and
471  !! terminates the program with an error message, if necessary.
472  !!
473  !<
474  subroutine final_message()
475  ! -- modules
478  ! -- formats
479  character(len=*), parameter :: fmtnocnvg = &
480  &"(1x, 'Simulation convergence failure occurred ', i0, ' time(s).')"
481  !
482  ! -- Write message if nonconvergence occurred in at least one timestep
483  if (numnoconverge > 0) then
484  write (warnmsg, fmtnocnvg) numnoconverge
485  if (isimcontinue == 0) then
486  call sim_errors%store(warnmsg)
487  else
488  call sim_warnings%store(warnmsg)
489  end if
490  end if
491  !
492  ! -- write final message
493  if (isimcnvg == 0) then
494  call print_final_message('Premature termination of simulation.', iout)
495  else
496  call print_final_message('Normal termination of simulation.', iout)
497  end if
498  !
499  ! -- If the simulation did not converge and the continue
500  ! option was not set, then set the return code to 1. The
501  ! purpose of setting the returncode this way is that the
502  ! program will terminate without a stop code if the simulation
503  ! reached the end and the continue flag was set, even if the
504  ! the simulation did not converge.
505  if (isimcnvg == 0 .and. isimcontinue == 0) then
506  ireturnerr = 1
507  end if
508  !
509  ! -- destroy messages
510  call sim_errors%deallocate()
511  call sim_uniterrors%deallocate()
512  call sim_warnings%deallocate()
513  call sim_notes%deallocate()
514  !
515  ! -- return or halt
516  if (iforcestop == 1) then
517  call pstop(ireturnerr)
518  end if
519 
520  end subroutine final_message
521 
522  !> @brief Close all open files
523  !!
524  !! Subroutine that closes all open files at the end of the simulation.
525  !!
526  !<
527  subroutine sim_closefiles()
528  ! -- local variables
529  integer(I4B) :: i
530  logical :: opened
531  character(len=7) :: output_file
532  !
533  ! -- close all open file units
534  do i = iustart, iunext - 1
535  !
536  ! -- determine if file unit i is open
537  inquire (unit=i, opened=opened)
538  !
539  ! -- skip file units that are no longer open
540  if (.not. opened) then
541  cycle
542  end if
543  !
544  ! -- flush the file if it can be written to
545  inquire (unit=i, write=output_file)
546  if (trim(adjustl(output_file)) == 'YES') then
547  flush (i)
548  end if
549  !
550  ! -- close file unit i
551  close (i)
552  end do
553 
554  end subroutine sim_closefiles
555 
556 end module simmodule
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 iulast
maximum file unit number (this allows for 9000 open files)
Definition: Constants.f90:57
integer(i4b), parameter iustart
starting file unit number
Definition: Constants.f90:56
@ osundef
unknown operating system
Definition: Constants.f90:195
@ oswin
Windows operating system.
Definition: Constants.f90:198
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:46
@ vsummary
write summary output
Definition: Constants.f90:187
@ vdebug
write debug output
Definition: Constants.f90:189
@ vall
write all simulation notes and warnings
Definition: Constants.f90:188
real(dp), parameter done
real constant 1
Definition: Constants.f90:75
integer(i4b) function, public get_os()
Get operating system.
Definition: defmacro.F90:17
subroutine pstop(status, message)
Stop the program, optionally specifying an error status code.
Definition: ErrorUtil.f90:24
This module defines variable data types.
Definition: kind.f90:8
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
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public ustop(stopmess, ioutlocal)
Stop the simulation.
Definition: Sim.f90:315
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
type(messagestype) sim_uniterrors
Definition: Sim.f90:45
subroutine, public converge_reset()
Reset the simulation convergence flag.
Definition: Sim.f90:392
subroutine, public initial_message()
Print the header and initializes messaging.
Definition: Sim.f90:445
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine sim_closefiles()
Close all open files.
Definition: Sim.f90:528
integer(i4b) function, public count_notes()
Return the number of notes stored.
Definition: Sim.f90:78
integer(i4b) function, public count_warnings()
Return number of warnings.
Definition: Sim.f90:71
subroutine, public final_message()
Create final message.
Definition: Sim.f90:475
subroutine, public deprecation_warning(cblock, cvar, cver, endmsg, iunit)
Store deprecation warning message.
Definition: Sim.f90:259
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
Definition: Sim.f90:203
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
subroutine get_filename(iunit, fname)
Get the file name.
Definition: Sim.f90:124
type(messagestype) sim_warnings
Definition: Sim.f90:46
subroutine print_final_message(stopmess, ioutlocal)
Print the final messages.
Definition: Sim.f90:336
type(messagestype) sim_notes
Definition: Sim.f90:47
type(messagestype) sim_errors
Definition: Sim.f90:44
subroutine, public store_note(note)
Store note.
Definition: Sim.f90:298
subroutine, public converge_check(hasConverged)
Simulation convergence check.
Definition: Sim.f90:405
This module contains simulation variables.
Definition: SimVariables.f90:9
integer(i4b) iforcestop
forced stop flag (1) forces a call to ustop(..) when the simulation has ended, (0) doesn't
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) isim_level
simulation output level
integer(i4b) ireturnerr
return code for program (0) successful, (1) non-convergence, (2) error
character(len=maxcharlen) warnmsg
warning message string
integer(i4b) numnoconverge
number of times the simulation did not converge
integer(i4b) iout
file unit number for simulation output
integer(i4b) iunext
next file unit number to assign
integer(i4b) istdout
unit number for stdout
integer(i4b) isimcnvg
simulation convergence flag (1) if all objects have converged, (0) otherwise
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
Container for related messages.
Definition: Message.f90:21