MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
Message.f90
Go to the documentation of this file.
1 !> @brief Store and issue logging messages to output units.
3 
4  use kindmodule, only: lgp, i4b, dp
8  use simvariablesmodule, only: istdout
9 
10  implicit none
11  public :: messagestype
12  public :: write_message
13  public :: write_message_counter
14  public :: write_message_centered
15 
16  !> @brief Container for related messages.
17  !!
18  !! A maximum capacity can be configured. Message storage
19  !! is dynamically resized up to the configured capacity.
20  !<
21  type :: messagestype
22  integer(I4B) :: num_messages = 0 !< number of messages currently stored
23  integer(I4B) :: max_messages = 1000 !< default max message storage capacity
24  integer(I4B) :: max_exceeded = 0 !< number of messages in excess of maximum
25  integer(I4B) :: exp_messages = 100 !< number of slots to expand message array
26  character(len=MAXCHARLEN), allocatable, dimension(:) :: messages !< message array
27  contains
28  procedure :: init
29  procedure :: count
30  procedure :: set_max
31  procedure :: store
32  procedure :: write_all
33  procedure :: deallocate
34  end type messagestype
35 
36 contains
37 
38  !> @brief Initialize message storage.
39  subroutine init(this)
40  class(messagestype) :: this !< MessageType object
41 
42  this%num_messages = 0
43  this%max_messages = 1000
44  this%max_exceeded = 0
45  this%exp_messages = 100
46  end subroutine init
47 
48  !> @brief Return the number of messages currently stored.
49  function count(this) result(nmessage)
50  class(messagestype) :: this !< MessageType object
51  integer(I4B) :: nmessage
52 
53  if (allocated(this%messages)) then
54  nmessage = this%num_messages
55  else
56  nmessage = 0
57  end if
58  end function count
59 
60  !> @brief Set the maximum number of messages.
61  subroutine set_max(this, imax)
62  class(messagestype) :: this !< MessageType object
63  integer(I4B), intent(in) :: imax !< maximum number of messages that will be stored
64 
65  this%max_messages = imax
66  end subroutine set_max
67 
68  !> @brief Add a message to storage.
69  !!
70  !! An optional string may be provided to filter out duplicate messages.
71  !! If any stored messages contain the string the message is not stored.
72  !<
73  subroutine store(this, msg, substring)
74  ! -- dummy variables
75  class(messagestype) :: this !< MessageType object
76  character(len=*), intent(in) :: msg !< message
77  character(len=*), intent(in), optional :: substring !< duplicate pattern
78  ! -- local variables
79  logical(LGP) :: inc_array
80  integer(I4B) :: i, n
81 
82  ! -- resize message array if needed
83  inc_array = .true.
84  if (allocated(this%messages)) then
85  if (this%num_messages < size(this%messages)) then
86  inc_array = .false.
87  end if
88  end if
89  if (inc_array) then
90  call expandarray(this%messages, increment=this%exp_messages)
91  this%exp_messages = int(this%exp_messages * 1.1)
92  end if
93 
94  ! -- don't store duplicate messages
95  if (present(substring)) then
96  do i = 1, this%num_messages
97  if (index(this%messages(i), substring) > 0) return
98  end do
99  end if
100 
101  ! -- store message and update count unless
102  ! at capacity, then update excess count
103  n = this%num_messages + 1
104  if (n <= this%max_messages) then
105  this%num_messages = n
106  this%messages(n) = msg
107  else
108  this%max_exceeded = this%max_exceeded + 1
109  end if
110  end subroutine store
111 
112  !> @brief Write all stored messages to standard output.
113  !!
114  !! An optional title to precede the messages may be provided.
115  !! The title is printed on a separate line. An arbitrary kind
116  !! may be specified, e.g. 'note', 'warning' or 'error. A file
117  !! unit can also be specified to write in addition to stdout.
118  !<
119  subroutine write_all(this, title, kind, iunit)
120  ! -- dummy variables
121  class(messagestype) :: this !< MessageType object
122  character(len=*), intent(in), optional :: title !< message title
123  character(len=*), intent(in), optional :: kind !< message kind
124  integer(I4B), intent(in), optional :: iunit !< file unit
125  ! -- local
126  character(len=LINELENGTH) :: ltitle
127  character(len=LINELENGTH) :: lkind
128  character(len=LINELENGTH) :: errmsg
129  character(len=LINELENGTH) :: cerr
130  integer(I4B) :: iu
131  integer(I4B) :: i
132  integer(I4B) :: isize
133  integer(I4B) :: iwidth
134  ! -- formats
135  character(len=*), parameter :: stdfmt = "(/,A,/)"
136 
137  ! -- process optional variables
138  if (present(title)) then
139  ltitle = title
140  else
141  ltitle = ''
142  end if
143  if (present(kind)) then
144  lkind = kind
145  else
146  lkind = ''
147  end if
148  if (present(iunit)) then
149  iu = iunit
150  else
151  iu = 0
152  end if
153 
154  ! -- write messages, if any
155  if (allocated(this%messages)) then
156  isize = this%num_messages
157  if (isize > 0) then
158  ! -- calculate the maximum width of the prepended string
159  ! for the counter
160  write (cerr, '(i0)') isize
161  iwidth = len_trim(cerr) + 1
162 
163  ! -- write title for message
164  if (trim(ltitle) /= '') then
165  if (iu > 0) &
166  call write_message(iunit=iu, text=ltitle, fmt=stdfmt)
167  call write_message(text=ltitle, fmt=stdfmt)
168  end if
169 
170  ! -- write each message
171  do i = 1, isize
172  if (iu > 0) &
173  call write_message_counter( &
174  iunit=iu, &
175  text=this%messages(i), &
176  icount=i, &
177  iwidth=iwidth)
178  call write_message_counter( &
179  text=this%messages(i), &
180  icount=i, &
181  iwidth=iwidth)
182  end do
183 
184  ! -- write the number of additional messages
185  if (this%max_exceeded > 0) then
186  write (errmsg, '(i0,3(1x,a))') &
187  this%max_exceeded, 'additional', trim(kind), &
188  'detected but not printed.'
189  if (iu > 0) &
190  call write_message(iunit=iu, text=trim(errmsg), fmt='(/,1x,a)')
191  call write_message(text=trim(errmsg), fmt='(/,1x,a)')
192  end if
193  end if
194  end if
195  end subroutine write_all
196 
197  !> @ brief Deallocate message storage.
198  subroutine deallocate (this)
199  class(messagestype) :: this
200  if (allocated(this%messages)) deallocate (this%messages)
201  end subroutine deallocate
202 
203  !> @brief Write a message to an output unit.
204  !!
205  !! Use `advance` to toggle advancing output. Use `skipbefore/after` to
206  !! configure the number of whitespace lines before/after the message.
207  !<
208  subroutine write_message(text, iunit, fmt, &
209  skipbefore, skipafter, advance)
210  ! -- dummy
211  character(len=*), intent(in) :: text !< message to write
212  integer(I4B), intent(in), optional :: iunit !< output unit to write the message to
213  character(len=*), intent(in), optional :: fmt !< format to write the message (default='(a)')
214  integer(I4B), intent(in), optional :: skipbefore !< number of empty lines before message (default=0)
215  integer(I4B), intent(in), optional :: skipafter !< number of empty lines after message (default=0)
216  logical(LGP), intent(in), optional :: advance !< whether to use advancing output (default is .true.)
217  ! -- local
218  character(len=3) :: cadvance
219  integer(I4B) :: i
220  integer(I4B) :: ilen
221  integer(I4B) :: iu
222  character(len=LENHUGELINE) :: simfmt
223  character(len=*), parameter :: stdfmt = '(a)'
224  character(len=*), parameter :: emptyfmt = '()'
225 
226  if (present(iunit)) then
227  iu = iunit
228  else
229  iu = istdout
230  end if
231 
232  ! -- get message length
233  ilen = len_trim(text)
234 
235  ! -- process optional arguments
236  if (present(fmt)) then
237  simfmt = fmt
238  else
239  if (ilen > 0) then
240  simfmt = stdfmt
241  else
242  simfmt = emptyfmt
243  end if
244  end if
245  if (present(advance)) then
246  if (advance) then
247  cadvance = 'YES'
248  else
249  cadvance = 'NO'
250  end if
251  else
252  cadvance = 'YES'
253  end if
254 
255  ! -- write empty line before message, if enabled
256  if (present(skipbefore)) then
257  do i = 1, skipbefore
258  write (iu, *)
259  end do
260  end if
261 
262  ! -- write message if it isn't empty
263  if (ilen > 0) then
264  write (iu, trim(simfmt), advance=cadvance) text(1:ilen)
265  else
266  write (iu, trim(simfmt), advance=cadvance)
267  end if
268 
269  ! -- write empty line after message, if enabled
270  if (present(skipafter)) then
271  do i = 1, skipafter
272  write (iu, *)
273  end do
274  end if
275  end subroutine write_message
276 
277  !> @brief Write a message with configurable indentation and numbering.
278  !!
279  !! The message may exceed 78 characters in length. Messages longer than
280  !! 78 characters are written across multiple lines. After icount lines,
281  !! subsequent lines are indented and numbered. Use skipbefore/after to
282  !! configure the number of empty lines before/after the message.
283  !<
284  subroutine write_message_counter(text, iunit, icount, iwidth, &
285  skipbefore, skipafter)
286  ! -- dummy
287  character(len=*), intent(in) :: text !< message to be written
288  integer(I4B), intent(in), optional :: iunit !< the unit number to which the message is written
289  integer(I4B), intent(in), optional :: icount !< counter to prepended to the message
290  integer(I4B), intent(in), optional :: iwidth !< maximum width of the prepended counter
291  integer(I4B), intent(in), optional :: skipbefore !< optional number of empty lines before message (default=0)
292  integer(I4B), intent(in), optional :: skipafter !< optional number of empty lines after message (default=0)
293  ! -- local
294  integer(I4B), parameter :: len_line = 78
295  character(len=LENHUGELINE) :: amessage
296  character(len=len_line) :: line
297  character(len=16) :: cfmt
298  character(len=10) :: counter
299  character(len=5) :: fmt_first
300  character(len=20) :: fmt_cont
301  logical(LGP) :: include_counter
302  integer(I4B) :: isb
303  integer(I4B) :: isa
304  integer(I4B) :: jend
305  integer(I4B) :: len_str1
306  integer(I4B) :: len_str2
307  integer(I4B) :: len_message
308  integer(I4B) :: i
309  integer(I4B) :: j
310  integer(I4B) :: iu
311 
312  if (present(iunit)) then
313  iu = iunit
314  else
315  iu = istdout
316  end if
317 
318  ! -- abort if message is empty
319  if (len_trim(text) < 1) return
320 
321  ! -- initialize local variables
322  amessage = text
323  counter = ''
324  fmt_first = '(A)'
325  fmt_cont = '(A)'
326  len_str1 = 0
327  len_str2 = len_line
328  include_counter = .false.
329  j = 0
330 
331  ! -- process optional arguments
332  if (present(skipbefore)) then
333  isb = skipbefore
334  else
335  isb = 0
336  end if
337  if (present(skipafter)) then
338  isa = skipafter
339  else
340  isa = 0
341  end if
342 
343  ! -- create the counter to prepend to the start of the message,
344  ! formats, and variables used to create strings
345  if (present(iwidth) .and. present(icount)) then
346  include_counter = .true.
347 
348  ! -- write counter
349  write (cfmt, '(A,I0,A)') '(1x,i', iwidth, ',".",1x)'
350  write (counter, cfmt) icount
351 
352  ! -- calculate the length of the first and second string on a line
353  len_str1 = len(trim(counter)) + 1
354  len_str2 = len_line - len_str1
355 
356  ! -- write format for the continuation lines
357  write (fmt_cont, '(a,i0,a)') &
358  '(', len(trim(counter)) + 1, 'x,a)'
359  end if
360 
361  ! -- calculate the length of the message
362  len_message = len_trim(amessage)
363 
364  ! -- parse the message into multiple lines
365 5 continue
366  jend = j + len_str2
367  if (jend >= len_message) go to 100
368  do i = jend, j + 1, -1
369  if (amessage(i:i) .eq. ' ') then
370  if (j == 0) then
371  if (include_counter) then
372  line = counter(1:len_str1)//amessage(j + 1:i)
373  else
374  line = amessage(j + 1:i)
375  end if
376  call write_message(text=line, iunit=iu, &
377  fmt=fmt_first, &
378  skipbefore=isb)
379  else
380  line = adjustl(amessage(j + 1:i))
381  call write_message(text=line, iunit=iu, &
382  fmt=fmt_cont)
383  end if
384  j = i
385  go to 5
386  end if
387  end do
388  if (j == 0) then
389  if (include_counter) then
390  line = counter(1:len_str1)//amessage(j + 1:jend)
391  else
392  line = amessage(j + 1:jend)
393  end if
394  call write_message(text=line, iunit=iu, &
395  fmt=fmt_first, &
396  skipbefore=isb)
397  else
398  line = amessage(j + 1:jend)
399  call write_message(text=line, iunit=iu, &
400  fmt=fmt_cont)
401  end if
402  j = jend
403  go to 5
404 
405  ! -- last piece of amessage to write to a line
406 100 continue
407  jend = len_message
408  if (j == 0) then
409  if (include_counter) then
410  line = counter(1:len_str1)//amessage(j + 1:jend)
411  else
412  line = amessage(j + 1:jend)
413  end if
414  call write_message(text=line, iunit=iu, &
415  fmt=fmt_first, &
416  skipbefore=isb, skipafter=isa)
417  else
418  line = amessage(j + 1:jend)
419  call write_message(text=line, iunit=iu, fmt=fmt_cont, &
420  skipafter=isa)
421  end if
422  end subroutine write_message_counter
423 
424  !> @brief Write horizontally centered text, left-padding as needed.
425  subroutine write_message_centered(text, linelen, iunit)
426  ! -- dummy
427  character(len=*), intent(in) :: text !< message to write to iunit
428  integer(I4B), intent(in) :: linelen !< length of line to center text in
429  integer(I4B), intent(in), optional :: iunit !< output unit to write text
430  ! -- local
431  character(len=linelen) :: line
432  character(len=linelen) :: blank
433  integer(I4B) :: iu
434  integer(I4B) :: len_message
435  integer(I4B) :: jend
436  integer(I4B) :: ipad
437  integer(I4B) :: i
438  integer(I4B) :: j
439 
440  if (present(iunit)) then
441  iu = iunit
442  else
443  iu = istdout
444  end if
445 
446  ! -- initialize local variables
447  blank = ''
448  len_message = len_trim(adjustl(text))
449  j = 0
450 
451  ! -- parse the amessage into multiple lines
452  outer: do while (.true.)
453  jend = j + linelen
454 
455  ! last line
456  if (jend >= len_message) then
457  jend = len_message
458  line = text(j + 1:jend)
459  ipad = ((linelen - len_trim(line)) / 2)
460  call write_message(text=blank(1:ipad)//line, iunit=iunit)
461  exit outer
462  end if
463 
464  do i = jend, j + 1, -1
465  if (text(i:i) .eq. ' ') then
466  line = text(j + 1:i)
467  ipad = ((linelen - len_trim(line)) / 2)
468  call write_message(text=blank(1:ipad)//line, iunit=iunit)
469  j = i
470  cycle outer
471  end if
472  end do
473 
474  line = text(j + 1:jend)
475  ipad = ((linelen - len_trim(line)) / 2)
476  call write_message(text=blank(1:ipad)//line, iunit=iunit)
477  j = jend
478  end do outer
479  end subroutine write_message_centered
480 
481 end module messagemodule
subroutine init()
Definition: GridSorting.f90:24
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 lenhugeline
maximum length of a huge line
Definition: Constants.f90:16
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:46
@ vsummary
write summary output
Definition: Constants.f90:187
real(dp), parameter done
real constant 1
Definition: Constants.f90:75
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_centered(text, linelen, iunit)
Write horizontally centered text, left-padding as needed.
Definition: Message.f90:426
subroutine, public write_message(text, iunit, fmt, skipbefore, skipafter, advance)
Write a message to an output unit.
Definition: Message.f90:210
subroutine store(this, msg, substring)
Add a message to storage.
Definition: Message.f90:74
subroutine write_all(this, title, kind, iunit)
Write all stored messages to standard output.
Definition: Message.f90:120
subroutine deallocate(this)
@ brief Deallocate message storage.
Definition: Message.f90:199
subroutine, public write_message_counter(text, iunit, icount, iwidth, skipbefore, skipafter)
Write a message with configurable indentation and numbering.
Definition: Message.f90:286
subroutine set_max(this, imax)
Set the maximum number of messages.
Definition: Message.f90:62
integer(i4b) function count(this)
Return the number of messages currently stored.
Definition: Message.f90:50
This module contains simulation variables.
Definition: SimVariables.f90:9
integer(i4b) istdout
unit number for stdout
Container for related messages.
Definition: Message.f90:21