MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
InputOutput.f90
Go to the documentation of this file.
1 ! -- MODFLOW 6 utility routines.
2 !
4 
5  use kindmodule, only: dp, i4b, i8b
12  use messagemodule, only: write_message
13  private
17  linear_interpolate, lowcase, read_line, getfilefrompath, &
21 
22 contains
23 
24  !> @brief Open a file
25  !!
26  !! Subroutine to open a file using the specified arguments
27  !<
28  subroutine openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, &
29  filstat_opt, mode_opt)
30  ! -- modules
31  use openspecmodule, only: action
32  implicit none
33  ! -- dummy
34  integer(I4B), intent(inout) :: iu !< unit number
35  integer(I4B), intent(in) :: iout !< output unit number to write a message (iout=0 does not print)
36  character(len=*), intent(in) :: fname !< name of the file
37  character(len=*), intent(in) :: ftype !< file type (e.g. WEL)
38  character(len=*), intent(in), optional :: fmtarg_opt !< file format, default is 'formatted'
39  character(len=*), intent(in), optional :: accarg_opt !< file access, default is 'sequential'
40  character(len=*), intent(in), optional :: filstat_opt !< file status, default is 'old'. Use 'REPLACE' for output file.
41  integer(I4B), intent(in), optional :: mode_opt !< simulation mode that is evaluated to determine if the file should be opened
42  ! -- local
43  character(len=20) :: fmtarg
44  character(len=20) :: accarg
45  character(len=20) :: filstat
46  character(len=20) :: filact
47  integer(I4B) :: imode
48  integer(I4B) :: iflen
49  integer(I4B) :: ivar
50  integer(I4B) :: iuop
51  ! -- formats
52  character(len=*), parameter :: fmtmsg = &
53  "(1x,/1x,'OPENED ',a,/1x,'FILE TYPE:',a,' UNIT ',I4,3x,'STATUS:',a,/ &
54  & 1x,'FORMAT:',a,3x,'ACCESS:',a/1x,'ACTION:',a/)"
55  character(len=*), parameter :: fmtmsg2 = &
56  "(1x,/1x,'DID NOT OPEN ',a,/)"
57  !
58  ! -- Process mode_opt
59  if (present(mode_opt)) then
60  imode = mode_opt
61  else
62  imode = isim_mode
63  end if
64  !
65  ! -- Evaluate if the file should be opened
66  if (isim_mode < imode) then
67  if (iout > 0) then
68  write (iout, fmtmsg2) trim(fname)
69  end if
70  else
71  !
72  ! -- Default is to read an existing text file
73  fmtarg = 'FORMATTED'
74  accarg = 'SEQUENTIAL'
75  filstat = 'OLD'
76  !
77  ! -- Override defaults
78  if (present(fmtarg_opt)) then
79  fmtarg = fmtarg_opt
80  call upcase(fmtarg)
81  end if
82  if (present(accarg_opt)) then
83  accarg = accarg_opt
84  call upcase(accarg)
85  end if
86  if (present(filstat_opt)) then
87  filstat = filstat_opt
88  call upcase(filstat)
89  end if
90  if (filstat == 'OLD') then
91  filact = action(1)
92  else
93  filact = action(2)
94  end if
95  !
96  ! -- size of fname
97  iflen = len_trim(fname)
98  !
99  ! -- Get a free unit number
100  if (iu <= 0) then
101  call freeunitnumber(iu)
102  end if
103  !
104  ! -- Check to see if file is already open, if not then open the file
105  inquire (file=fname(1:iflen), number=iuop)
106  if (iuop > 0) then
107  ivar = -1
108  else
109  open (unit=iu, file=fname(1:iflen), form=fmtarg, access=accarg, &
110  status=filstat, action=filact, iostat=ivar)
111  end if
112  !
113  ! -- Check for an error
114  if (ivar /= 0) then
115  write (errmsg, '(3a,1x,i0,a)') &
116  'Could not open "', fname(1:iflen), '" on unit', iu, '.'
117  if (iuop > 0) then
118  write (errmsg, '(a,1x,a,1x,i0,a)') &
119  trim(errmsg), 'File already open on unit', iuop, '.'
120  end if
121  write (errmsg, '(a,1x,a,1x,a,a)') &
122  trim(errmsg), 'Specified file status', trim(filstat), '.'
123  write (errmsg, '(a,1x,a,1x,a,a)') &
124  trim(errmsg), 'Specified file format', trim(fmtarg), '.'
125  write (errmsg, '(a,1x,a,1x,a,a)') &
126  trim(errmsg), 'Specified file access', trim(accarg), '.'
127  write (errmsg, '(a,1x,a,1x,a,a)') &
128  trim(errmsg), 'Specified file action', trim(filact), '.'
129  write (errmsg, '(a,1x,a,1x,i0,a)') &
130  trim(errmsg), 'IOSTAT error number', ivar, '.'
131  write (errmsg, '(a,1x,a)') &
132  trim(errmsg), 'STOP EXECUTION in subroutine openfile().'
133  call store_error(errmsg, terminate=.true.)
134  end if
135  !
136  ! -- Write a message
137  if (iout > 0) then
138  write (iout, fmtmsg) fname(1:iflen), ftype, iu, filstat, fmtarg, &
139  accarg, filact
140  end if
141  end if
142  end subroutine openfile
143 
144  !> @brief Assign a free unopened unit number
145  !!
146  !! Subroutine to assign a free unopened unit number to the iu dummy argument
147  !<
148  subroutine freeunitnumber(iu)
149  ! -- modules
150  implicit none
151  ! -- dummy
152  integer(I4B), intent(inout) :: iu !< next free file unit number
153  ! -- local
154  integer(I4B) :: i
155  logical :: opened
156  !
157  do i = iunext, iulast
158  inquire (unit=i, opened=opened)
159  if (.not. opened) exit
160  end do
161  iu = i
162  iunext = iu + 1
163  end subroutine freeunitnumber
164 
165  !> @brief Get a free unit number
166  !!
167  !! Function to get a free unit number that hasn't been used
168  !<
169  function getunit()
170  ! -- modules
171  implicit none
172  ! -- return
173  integer(I4B) :: getunit !< free unit number
174  ! -- local
175  integer(I4B) :: iunit
176  !
177  ! -- code
178  call freeunitnumber(iunit)
179  getunit = iunit
180  end function getunit
181 
182  !> @ brief assign io unit number
183  !!
184  !! Generic method to assign io unit number to unassigned integer
185  !! variable (initialized less than or equal to 0). Assigns a valid
186  !! number if unassigned, otherwise sets a terminating error.
187  !<
188  subroutine assign_iounit(iounit, errunit, description)
189  integer(I4B), intent(inout) :: iounit !< iounit variable
190  integer(I4B), intent(in) :: errunit !< input file inunit for error assignment
191  character(len=*), intent(in) :: description !< usage description for iounit
192  if (iounit > 0) then
193  write (errmsg, '(a,1x,i0)') &
194  trim(description)//' already assigned at unit: ', iounit
195  call store_error(errmsg)
196  call store_error_unit(errunit)
197  end if
198  iounit = getunit()
199  end subroutine assign_iounit
200 
201  !> @brief Convert to upper case
202  !!
203  !! Subroutine to convert a character string to upper case.
204  !<
205  subroutine upcase(word)
206  implicit none
207  ! -- dummy
208  character(len=*), intent(inout) :: word !< word to convert to upper case
209  ! -- local
210  integer(I4B) :: l
211  integer(I4B) :: idiff
212  integer(I4B) :: k
213  !
214  ! -- Compute the difference between lowercase and uppercase.
215  l = len(word)
216  idiff = ichar('a') - ichar('A')
217  !
218  ! -- Loop through the string and convert any lowercase characters.
219  do k = 1, l
220  IF (word(k:k) >= 'a' .and. word(k:k) <= 'z') &
221  word(k:k) = char(ichar(word(k:k)) - idiff)
222  end do
223  end subroutine upcase
224 
225  !> @brief Convert to lower case
226  !!
227  !! Subroutine to convert a character string to lower case.
228  !<
229  subroutine lowcase(word)
230  implicit none
231  ! -- dummy
232  character(len=*) :: word
233  ! -- local
234  integer(I4B) :: idiff, k, l
235  !
236  ! -- Compute the difference between lowercase and uppercase.
237  l = len(word)
238  idiff = ichar('a') - ichar('A')
239  !
240  ! -- Loop through the string and convert any uppercase characters.
241  do k = 1, l
242  if (word(k:k) >= 'A' .and. word(k:k) <= 'Z') then
243  word(k:k) = char(ichar(word(k:k)) + idiff)
244  end if
245  end do
246  end subroutine lowcase
247 
248  !> @brief Append processor id to a string
249  !!
250  !! Subroutine to append the processor id to a string before the file extension
251  !! (extension is the string after the last '.' in the string. If there is
252  !! no '.' in the string the processor id is appended to the end of the string.
253  !<
254  subroutine append_processor_id(name, proc_id)
255  ! -- dummy
256  character(len=LINELENGTH), intent(inout) :: name !< file name
257  integer(I4B), intent(in) :: proc_id !< processor id
258  ! -- local
259  character(len=LINELENGTH) :: name_local
260  character(len=LINELENGTH) :: name_processor
261  character(len=LINELENGTH) :: extension_local
262  integer(I4B) :: ipos0
263  integer(I4B) :: ipos1
264  !
265  name_local = name
266  call lowcase(name_local)
267  ipos0 = index(name_local, ".", back=.true.)
268  ipos1 = len_trim(name)
269  if (ipos0 > 0) then
270  write (extension_local, '(a)') name(ipos0:ipos1)
271  else
272  ipos0 = ipos1
273  extension_local = ''
274  end if
275  write (name_processor, '(a,a,i0,a)') &
276  name(1:ipos0 - 1), '.p', proc_id, trim(adjustl(extension_local))
277  name = name_processor
278  end subroutine append_processor_id
279 
280  !> @brief Create a formatted line
281  !!
282  !! Subroutine to create a formatted line with specified alignment and column
283  !! separators. Like URWORD, UWWORD works with strings, integers, and floats.
284  !! Can pass an optional format statement, alignment, and column separator.
285  !<
286  subroutine uwword(line, icol, ilen, ncode, c, n, r, fmt, alignment, sep)
287  implicit none
288  ! -- dummy
289  character(len=*), intent(inout) :: line !< line
290  integer(I4B), intent(inout) :: icol !< column to write to line
291  integer(I4B), intent(in) :: ilen !< current length of line
292  integer(I4B), intent(in) :: ncode !< code for data type to write
293  character(len=*), intent(in) :: c !< character data type
294  integer(I4B), intent(in) :: n !< integer data type
295  real(dp), intent(in) :: r !< float data type
296  character(len=*), optional, intent(in) :: fmt !< format statement
297  integer(I4B), optional, intent(in) :: alignment !< alignment specifier
298  character(len=*), optional, intent(in) :: sep !< column separator
299  ! -- local
300  character(len=16) :: cfmt
301  character(len=16) :: cffmt
302  character(len=ILEN) :: cval
303  integer(I4B) :: ialign
304  integer(I4B) :: i
305  integer(I4B) :: ispace
306  integer(I4B) :: istop
307  integer(I4B) :: ipad
308  integer(I4B) :: ireal
309  !
310  ! -- initialize locals
311  ipad = 0
312  ireal = 0
313  !
314  ! -- process dummy variables
315  if (present(fmt)) then
316  cfmt = fmt
317  else
318  select case (ncode)
319  case (tabstring, tabucstring)
320  write (cfmt, '(a,I0,a)') '(a', ilen, ')'
321  case (tabinteger)
322  write (cfmt, '(a,I0,a)') '(I', ilen, ')'
323  case (tabreal)
324  ireal = 1
325  i = ilen - 7
326  write (cfmt, '(a,I0,a,I0,a)') '(1PG', ilen, '.', i, ')'
327  if (r >= dzero) then
328  ipad = 1
329  end if
330  end select
331  end if
332  write (cffmt, '(a,I0,a)') '(a', ilen, ')'
333  !
334  if (present(alignment)) then
335  ialign = alignment
336  else
337  ialign = tabright
338  end if
339  !
340  if (ncode == tabstring .or. ncode == tabucstring) then
341  cval = c
342  if (ncode == tabucstring) then
343  call upcase(cval)
344  end if
345  else if (ncode == tabinteger) then
346  write (cval, cfmt) n
347  else if (ncode == tabreal) then
348  write (cval, cfmt) r
349  end if
350  !
351  ! -- Apply alignment to cval
352  if (len_trim(adjustl(cval)) > ilen) then
353  cval = adjustl(cval)
354  else
355  cval = trim(adjustl(cval))
356  end if
357  if (ialign == tabcenter) then
358  i = len_trim(cval)
359  ispace = (ilen - i) / 2
360  if (ireal > 0) then
361  if (ipad > 0) then
362  cval = ' '//trim(adjustl(cval))
363  else
364  cval = trim(adjustl(cval))
365  end if
366  else
367  cval = repeat(' ', ispace)//trim(cval)
368  end if
369  else if (ialign == tableft) then
370  cval = trim(adjustl(cval))
371  if (ipad > 0) then
372  cval = ' '//trim(adjustl(cval))
373  end if
374  else
375  cval = adjustr(cval)
376  end if
377  if (ncode == tabucstring) then
378  call upcase(cval)
379  end if
380  !
381  ! -- Increment istop to the end of the column
382  istop = icol + ilen - 1
383  !
384  ! -- Write final string to line
385  write (line(icol:istop), cffmt) cval
386  !
387  icol = istop + 1
388  !
389  if (present(sep)) then
390  i = len(sep)
391  istop = icol + i
392  write (line(icol:istop), '(a)') sep
393  icol = istop
394  end if
395  end subroutine uwword
396 
397  !> @brief Extract a word from a string
398  !!
399  !! Subroutine to extract a word from a line of text, and optionally
400  !! convert the word to a number. The last character in the line is
401  !! set to blank so that if any problems occur with finding a word,
402  !! istart and istop will point to this blank character. Thus, a word
403  !! will always be returned unless there is a numeric conversion error.
404  !! Be sure that the last character in line is not an important character
405  !! because it will always be set to blank.
406  !!
407  !! A word starts with the first character that is not a space or
408  !! comma, and ends when a subsequent character that is a space
409  !! or comma. Note that these parsing rules do not treat two
410  !! commas separated by one or more spaces as a null word.
411  !!
412  !! For a word that begins with "'" or '"', the word starts with
413  !! the character after the quote and ends with the character preceding
414  !! a subsequent quote. Thus, a quoted word can include spaces and commas.
415  !! The quoted word cannot contain a quote character of the same type
416  !! within the word but can contain a different quote character. For
417  !! example, "WORD'S" or 'WORD"S'.
418  !!
419  !! Number conversion error is written to unit iout if iout is positive;
420  !! error is written to default output if iout is 0; no error message is
421  !! written if iout is negative.
422  !!
423  !<
424  subroutine urword(line, icol, istart, istop, ncode, n, r, iout, in)
425  ! -- dummy
426  character(len=*) :: line !< line to parse
427  integer(I4B), intent(inout) :: icol !< current column in line
428  integer(I4B), intent(inout) :: istart !< starting character position of the word
429  integer(I4B), intent(inout) :: istop !< ending character position of the word
430  integer(I4B), intent(in) :: ncode !< word conversion flag (1) upper case, (2) integer, (3) real number
431  integer(I4B), intent(inout) :: n !< integer data type
432  real(dp), intent(inout) :: r !< float data type
433  integer(I4B), intent(in) :: iout !< output listing file unit
434  integer(I4B), intent(in) :: in !< input file unit number
435  ! -- local
436  character(len=20) string
437  character(len=1) tab
438  character(len=1) charend
439  character(len=200) :: msg
440  character(len=linelength) :: msg_line
441  ! -- formats
442  character(len=*), parameter :: fmtmsgout1 = &
443  "(1X,'FILE UNIT ',I4,' : ERROR CONVERTING ""',A, &
444  & '"" TO ',A,' IN LINE:')"
445  character(len=*), parameter :: fmtmsgout2 = "(1x, &
446  & 'KEYBOARD INPUT : ERROR CONVERTING ""',a,'"" TO ',a,' IN LINE:')"
447  character(len=*), parameter :: fmtmsgout3 = "('File unit ', &
448  & I0,': Error converting ""',a,'"" to ',A,' in following line:')"
449  character(len=*), parameter :: fmtmsgout4 = &
450  "('Keyboard input: Error converting ""',a, &
451  & '"" to ',A,' in following line:')"
452  !
453  tab = char(9)
454  !
455  ! -- Set last char in LINE to blank and set ISTART and ISTOP to point
456  ! to this blank as a default situation when no word is found. If
457  ! starting location in LINE is out of bounds, do not look for a word.
458  linlen = len(line)
459  line(linlen:linlen) = ' '
460  istart = linlen
461  istop = linlen
462  linlen = linlen - 1
463  if (icol < 1 .or. icol > linlen) go to 100
464  !
465  ! -- Find start of word, which is indicated by first character that
466  ! is not a blank, a comma, or a tab.
467  do i = icol, linlen
468  if (line(i:i) /= ' ' .and. line(i:i) /= ',' .and. &
469  line(i:i) /= tab) go to 20
470  end do
471  icol = linlen + 1
472  go to 100
473  !
474  ! -- Found start of word. Look for end.
475  ! When word is quoted, only a quote can terminate it.
476  ! search for a single (char(39)) or double (char(34)) quote
477 20 if (line(i:i) == char(34) .or. line(i:i) == char(39)) then
478  if (line(i:i) == char(34)) then
479  charend = char(34)
480  else
481  charend = char(39)
482  end if
483  i = i + 1
484  if (i <= linlen) then
485  do j = i, linlen
486  if (line(j:j) == charend) go to 40
487  end do
488  end if
489  !
490  ! -- When word is not quoted, space, comma, or tab will terminate.
491  else
492  do j = i, linlen
493  if (line(j:j) == ' ' .or. line(j:j) == ',' .or. &
494  line(j:j) == tab) go to 40
495  end do
496  end if
497  !
498  ! -- End of line without finding end of word; set end of word to
499  ! end of line.
500  j = linlen + 1
501  !
502  ! -- Found end of word; set J to point to last character in WORD and
503  ! set ICOL to point to location for scanning for another word.
504 40 icol = j + 1
505  j = j - 1
506  if (j < i) go to 100
507  istart = i
508  istop = j
509  !
510  ! -- Convert word to upper case and RETURN if NCODE is 1.
511  if (ncode == 1) then
512  idiff = ichar('a') - ichar('A')
513  do k = istart, istop
514  if (line(k:k) >= 'a' .and. line(k:k) <= 'z') &
515  line(k:k) = char(ichar(line(k:k)) - idiff)
516  end do
517  return
518  end if
519  !
520  ! -- Convert word to a number if requested.
521 100 if (ncode == 2 .or. ncode == 3) then
522  l = istop - istart + 1
523  if (l < 1) go to 200
524  if (istart > linlen) then
525  ! support legacy urword behavior to return a zero value when
526  ! no more data is on the line
527  if (ncode == 2) n = 0
528  if (ncode == 3) r = dzero
529  else
530  if (ncode == 2) read (line(istart:istop), *, err=200) n
531  if (ncode == 3) read (line(istart:istop), *, err=200) r
532  end if
533  end if
534  return
535  !
536  ! -- Number conversion error.
537 200 if (ncode == 3) then
538  string = 'a real number'
539  l = 13
540  else
541  string = 'an integer'
542  l = 10
543  end if
544  !
545  ! -- If output unit is negative, set last character of string to 'E'.
546  if (iout < 0) then
547  n = 0
548  r = 0.
549  line(linlen + 1:linlen + 1) = 'E'
550  return
551  !
552  ! -- If output unit is positive; write a message to output unit.
553  else if (iout > 0) then
554  if (in > 0) then
555  write (msg_line, fmtmsgout1) in, line(istart:istop), string(1:l)
556  else
557  write (msg_line, fmtmsgout2) line(istart:istop), string(1:l)
558  end if
559  call write_message(msg_line, iunit=iout, skipbefore=1)
560  call write_message(line, iunit=iout, fmt='(1x,a)')
561  !
562  ! -- If output unit is 0; write a message to default output.
563  else
564  if (in > 0) then
565  write (msg_line, fmtmsgout1) in, line(istart:istop), string(1:l)
566  else
567  write (msg_line, fmtmsgout2) line(istart:istop), string(1:l)
568  end if
569  call write_message(msg_line, iunit=iout, skipbefore=1)
570  call write_message(line, iunit=iout, fmt='(1x,a)')
571  end if
572  !
573  ! -- STOP after storing error message.
574  call lowcase(string)
575  if (in > 0) then
576  write (msg, fmtmsgout3) in, line(istart:istop), trim(string)
577  else
578  write (msg, fmtmsgout4) line(istart:istop), trim(string)
579  end if
580  !
581  call store_error(msg)
582  call store_error(trim(line))
583  call store_error_unit(in)
584  end subroutine urword
585 
586  !> @brief Print a label for a list
587  !<
588  subroutine ulstlb(iout, label, caux, ncaux, naux)
589  ! -- dummy
590  character(len=*) :: label
591  character(len=16) :: caux(ncaux)
592  ! -- local
593  character(len=400) buf
594  ! -- constant
595  character(len=1) dash(400)
596  data dash/400*'-'/
597  ! -- formats
598  character(len=*), parameter :: fmtmsgout1 = "(1x, a)"
599  character(len=*), parameter :: fmtmsgout2 = "(1x, 400a)"
600  !
601  ! -- Construct the complete label in BUF. Start with BUF=LABEL.
602  buf = label
603  !
604  ! -- Add auxiliary data names if there are any.
605  nbuf = len(label) + 9
606  if (naux > 0) then
607  do i = 1, naux
608  n1 = nbuf + 1
609  nbuf = nbuf + 16
610  buf(n1:nbuf) = caux(i)
611  end do
612  end if
613  !
614  ! -- Write the label.
615  write (iout, fmtmsgout1) buf(1:nbuf)
616  !
617  ! -- Add a line of dashes.
618  write (iout, fmtmsgout2) (dash(j), j=1, nbuf)
619  end subroutine ulstlb
620 
621  !> @brief Write header records for cell-by-cell flow terms for one component
622  !! of flow plus auxiliary data using a list structure
623  !!
624  !! Each item in the list is written by module UBDSVB
625  !<
626  subroutine ubdsv4(kstp, kper, text, naux, auxtxt, ibdchn, &
627  & ncol, nrow, nlay, nlist, iout, delt, pertim, totim)
628  ! -- dummy
629  character(len=16) :: text
630  character(len=16), dimension(:) :: auxtxt
631  real(dp), intent(in) :: delt, pertim, totim
632  ! -- formats
633  character(len=*), parameter :: fmt = &
634  & "(1X,'UBDSV4 SAVING ',A16,' ON UNIT',I7,' AT TIME STEP',I7,"// &
635  & "', STRESS PERIOD',I7)"
636  !
637  ! -- Write unformatted records identifying data
638  if (iout > 0) write (iout, fmt) text, ibdchn, kstp, kper
639  write (ibdchn) kstp, kper, text, ncol, nrow, -nlay
640  write (ibdchn) 5, delt, pertim, totim
641  write (ibdchn) naux + 1
642  if (naux > 0) write (ibdchn) (auxtxt(n), n=1, naux)
643  write (ibdchn) nlist
644  end subroutine ubdsv4
645 
646  !> @brief Write one value of cell-by-cell flow plus auxiliary data using a
647  !! list structure
648  !<
649  subroutine ubdsvb(ibdchn, icrl, q, val, nvl, naux, laux)
650  ! -- dummy
651  real(dp), dimension(nvl) :: val
652  real(dp) :: q
653  !
654  ! -- Write cell number and flow rate
655  IF (naux > 0) then
656  n2 = laux + naux - 1
657  write (ibdchn) icrl, q, (val(n), n=laux, n2)
658  else
659  write (ibdchn) icrl, q
660  end if
661  end subroutine ubdsvb
662 
663  !> @brief Output column numbers above a matrix printout
664  !!
665  !! nlbl1 is the start column label (number)
666  !! nlbl2 is the stop column label (number)
667  !! nspace is number of blank spaces to leave at start of line
668  !! ncpl is number of column numbers per line
669  !! ndig is number of characters in each column field
670  !! iout is output channel
671  !<
672  subroutine ucolno(nlbl1, nlbl2, nspace, ncpl, ndig, iout)
673  ! -- local
674  character(len=1) :: dot, space, dg, bf
675  dimension :: bf(1000), dg(10)
676  ! -- constants
677  data dg(1), dg(2), dg(3), dg(4), dg(5), dg(6), dg(7), dg(8), dg(9), dg(10)/ &
678  & '0', '1', '2', '3', '4', '5', '6', '7', '8', '9'/
679  data dot, space/'.', ' '/
680  ! -- formats
681  character(len=*), parameter :: fmtmsgout1 = "(1x)"
682  character(len=*), parameter :: fmtmsgout2 = "(1x, 1000a1)"
683  !
684  ! -- Calculate # of columns to be printed (nlbl), width
685  ! of a line (ntot), number of lines (nwrap).
686  if (iout <= 0) return
687  write (iout, fmtmsgout1)
688  !
689  nlbl = nlbl2 - nlbl1 + 1
690  n = nlbl
691  !
692  if (nlbl < ncpl) n = ncpl
693  ntot = nspace + n * ndig
694  !
695  if (ntot > 1000) go to 50
696  nwrap = (nlbl - 1) / ncpl + 1
697  j1 = nlbl1 - ncpl
698  j2 = nlbl1 - 1
699  !
700  ! -- Build and print each line
701  do n = 1, nwrap
702  !
703  ! -- Clear the buffer (BF)
704  do i = 1, 1000
705  bf(i) = space
706  end do
707  nbf = nspace
708  !
709  ! -- Determine first (j1) and last (j2) column # for this line.
710  j1 = j1 + ncpl
711  j2 = j2 + ncpl
712  if (j2 > nlbl2) j2 = nlbl2
713  !
714  ! -- Load the column #'s into the buffer.
715  do j = j1, j2
716  nbf = nbf + ndig
717  i2 = j / 10
718  i1 = j - i2 * 10 + 1
719  bf(nbf) = dg(i1)
720  if (i2 == 0) go to 30
721  i3 = i2 / 10
722  i2 = i2 - i3 * 10 + 1
723  bf(nbf - 1) = dg(i2)
724  if (i3 == 0) go to 30
725  i4 = i3 / 10
726  i3 = i3 - i4 * 10 + 1
727  bf(nbf - 2) = dg(i3)
728  if (i4 == 0) go to 30
729  if (i4 > 9) then
730  ! -- If more than 4 digits, use "X" for 4th digit.
731  bf(nbf - 3) = 'X'
732  else
733  bf(nbf - 3) = dg(i4 + 1)
734  end if
735 30 end do
736  !
737  ! -- Print the contents of the buffer (i.e. print the line).
738  write (iout, fmtmsgout2) (bf(i), i=1, nbf)
739  !
740  end do
741  !
742  ! -- Print a line of dots (for aesthetic purposes only).
743 50 ntot = ntot
744  if (ntot > 1000) ntot = 1000
745  write (iout, fmtmsgout2) (dot, i=1, ntot)
746  end subroutine ucolno
747 
748  !> @brief Print 1 layer array
749  !<
750  subroutine ulaprw(buf, text, kstp, kper, ncol, nrow, ilay, iprn, iout)
751  ! -- dummy
752  character(len=16) :: text
753  real(dp), dimension(ncol, nrow) :: buf
754  ! -- formats
755  character(len=*), parameter :: fmtmsgout1 = &
756  & "('1', /2x, a, ' IN LAYER ',I3,' AT END OF TIME STEP ',I3, &
757  & ' IN STRESS PERIOD ',I4/2x,75('-'))"
758  character(len=*), parameter :: fmtmsgout2 = &
759  & "('1',/1x,A,' FOR CROSS SECTION AT END OF TIME STEP',I3, &
760  & ' IN STRESS PERIOD ',I4/1x,79('-'))"
761  character(len=*), parameter :: fmtg10 = &
762  & "(1X,I3,2X,1PG10.3,10(1X,G10.3):/(5X,11(1X,G10.3)))"
763  character(len=*), parameter :: fmtg13 = &
764  & "(1x,I3,2x,1PG13.6,8(1x,G13.6):/(5x,9(1x,G13.6)))"
765  character(len=*), parameter :: fmtf7pt1 = &
766  & "(1x,I3,1x,15(1x,F7.1):/(5x,15(1x,F7.1)))"
767  character(len=*), parameter :: fmtf7pt2 = &
768  & "(1x,I3,1x,15(1x,F7.2):/(5x,15(1x,F7.2)))"
769  character(len=*), parameter :: fmtf7pt3 = &
770  & "(1x,I3,1x,15(1x,F7.3):/(5x,15(1x,F7.3)))"
771  character(len=*), parameter :: fmtf7pt4 = &
772  & "(1x,I3,1x,15(1x,F7.4):/(5x,15(1x,F7.4)))"
773  character(len=*), parameter :: fmtf5pt0 = &
774  & "(1x,I3,1x,20(1x,F5.0):/(5x,20(1x,F5.0)))"
775  character(len=*), parameter :: fmtf5pt1 = &
776  & "(1x,I3,1x,20(1x,F5.1):/(5x,20(1x,F5.1)))"
777  character(len=*), parameter :: fmtf5pt2 = &
778  & "(1x,I3,1x,20(1x,F5.2):/(5x,20(1x,F5.2)))"
779  character(len=*), parameter :: fmtf5pt3 = &
780  & "(1x,I3,1x,20(1x,F5.3):/(5x,20(1x,F5.3)))"
781  character(len=*), parameter :: fmtf5pt4 = &
782  & "(1x,I3,1x,20(1x,F5.4):/(5x,20(1x,F5.4)))"
783  character(len=*), parameter :: fmtg11 = &
784  & "(1x,I3,2x,1PG11.4,9(1x,G11.4):/(5x,10(1x,G11.4)))"
785  character(len=*), parameter :: fmtf6pt0 = &
786  & "(1x,I3,1x,10(1x,F6.0):/(5X,10(1x,F6.0)))"
787  character(len=*), parameter :: fmtf6pt1 = &
788  & "(1x,I3,1x,10(1x,F6.1):/(5x,10(1x,F6.1)))"
789  character(len=*), parameter :: fmtf6pt2 = &
790  & "(1x,I3,1x,10(1x,F6.2):/(5x,10(1x,F6.2)))"
791  character(len=*), parameter :: fmtf6pt3 = &
792  & "(1x,I3,1x,10(1x,F6.3):/(5x,10(1x,F6.3)))"
793  character(len=*), parameter :: fmtf6pt4 = &
794  & "(1x,I3,1x,10(1x,F6.4):/(5x,10(1x,F6.4)))"
795  character(len=*), parameter :: fmtf6pt5 = &
796  & "(1x,I3,1x,10(1x,F6.5):/(5x,10(1x,F6.5)))"
797  character(len=*), parameter :: fmtg12 = &
798  & "(1x,I3,2x,1PG12.5,4(1x,G12.5):/(5x,5(1x,G12.5)))"
799  character(len=*), parameter :: fmtg11pt4 = &
800  & "(1x,I3,2x,1PG11.4,5(1x,G11.4):/(5x,6(1x,G11.4)))"
801  character(len=*), parameter :: fmtg9pt2 = &
802  & "(1x,I3,2x,1PG9.2,6(1x,G9.2):/(5x,7(1x,G9.2)))"
803  !
804  if (iout <= 0) return
805  ! -- Print a header depending on ilay
806  if (ilay > 0) then
807  write (iout, fmtmsgout1) text, ilay, kstp, kper
808  else if (ilay < 0) then
809  write (iout, fmtmsgout2) text, kstp, kper
810  end if
811  !
812  ! -- Make sure the format code (ip or iprn) is between 1 and 21
813  ip = iprn
814  if (ip < 1 .or. ip > 21) ip = 12
815  !
816  ! -- Call the utility module ucolno to print column numbers.
817  if (ip == 1) call ucolno(1, ncol, 0, 11, 11, iout)
818  if (ip == 2) call ucolno(1, ncol, 0, 9, 14, iout)
819  if (ip >= 3 .and. ip <= 6) call ucolno(1, ncol, 3, 15, 8, iout)
820  if (ip >= 7 .and. ip <= 11) call ucolno(1, ncol, 3, 20, 6, iout)
821  if (ip == 12) call ucolno(1, ncol, 0, 10, 12, iout)
822  if (ip >= 13 .and. ip <= 18) call ucolno(1, ncol, 3, 10, 7, iout)
823  if (ip == 19) call ucolno(1, ncol, 0, 5, 13, iout)
824  if (ip == 20) call ucolno(1, ncol, 0, 6, 12, iout)
825  if (ip == 21) call ucolno(1, ncol, 0, 7, 10, iout)
826  !
827  ! -- Loop through the rows printing each one in its entirety.
828  do i = 1, nrow
829  select case (ip)
830  !
831  case (1)
832  ! -- format 11G10.3
833  write (iout, fmtg10) i, (buf(j, i), j=1, ncol)
834  !
835  case (2)
836  ! -- format 9G13.6
837  write (iout, fmtg13) i, (buf(j, i), j=1, ncol)
838  !
839  case (3)
840  ! -- format 15F7.1
841  write (iout, fmtf7pt1) i, (buf(j, i), j=1, ncol)
842  !
843  case (4)
844  ! -- format 15F7.2
845  write (iout, fmtf7pt2) i, (buf(j, i), j=1, ncol)
846  !
847  case (5)
848  ! -- format 15F7.3
849  write (iout, fmtf7pt3) i, (buf(j, i), j=1, ncol)
850  !
851  case (6)
852  ! -- format 15F7.4
853  write (iout, fmtf7pt4) i, (buf(j, i), j=1, ncol)
854  !
855  case (7)
856  ! -- format 20F5.0
857  write (iout, fmtf5pt0) i, (buf(j, i), j=1, ncol)
858  !
859  case (8)
860  ! -- format 20F5.1
861  write (iout, fmtf5pt1) i, (buf(j, i), j=1, ncol)
862  !
863  case (9)
864  ! -- format 20F5.2
865  write (iout, fmtf5pt2) i, (buf(j, i), j=1, ncol)
866  !
867  case (10)
868  ! -- format 20F5.3
869  write (iout, fmtf5pt3) i, (buf(j, i), j=1, ncol)
870  !
871  case (11)
872  ! -- format 20F5.4
873  write (iout, fmtf5pt4) i, (buf(j, i), j=1, ncol)
874  !
875  case (12)
876  ! -- format 10G11.4
877  write (iout, fmtg11) i, (buf(j, i), j=1, ncol)
878  !
879  case (13)
880  ! -- format 10F6.0
881  write (iout, fmtf6pt0) i, (buf(j, i), j=1, ncol)
882  !
883  case (14)
884  ! -- format 10F6.1
885  write (iout, fmtf6pt1) i, (buf(j, i), j=1, ncol)
886  !
887  case (15)
888  ! -- format 10F6.2
889  write (iout, fmtf6pt2) i, (buf(j, i), j=1, ncol)
890  !
891  case (16)
892  ! -- format 10F6.3
893  write (iout, fmtf6pt3) i, (buf(j, i), j=1, ncol)
894  !
895  case (17)
896  ! -- format 10F6.4
897  write (iout, fmtf6pt4) i, (buf(j, i), j=1, ncol)
898  !
899  case (18)
900  ! -- format 10F6.5
901  write (iout, fmtf6pt5) i, (buf(j, i), j=1, ncol)
902  !
903  case (19)
904  ! -- format 5G12.5
905  write (iout, fmtg12) i, (buf(j, i), j=1, ncol)
906  !
907  case (20)
908  ! -- format 6G11.4
909  write (iout, fmtg11pt4) i, (buf(j, i), j=1, ncol)
910  !
911  case (21)
912  ! -- format 7G9.2
913  write (iout, fmtg9pt2) i, (buf(j, i), j=1, ncol)
914  !
915  end select
916  end do
917  !
918  ! -- Flush file
919  flush (iout)
920  end subroutine ulaprw
921 
922  !> @brief Save 1 layer array on disk
923  !<
924  subroutine ulasav(buf, text, kstp, kper, pertim, totim, ncol, nrow, &
925  ilay, ichn)
926  ! -- dummy
927  character(len=16) :: text
928  real(dp), dimension(ncol, nrow) :: buf
929  real(dp) :: pertim, totim
930  !
931  ! -- Write an unformatted record containing identifying information
932  write (ichn) kstp, kper, pertim, totim, text, ncol, nrow, ilay
933  !
934  ! -- Write an unformatted record containing array values. The array is
935  ! dimensioned (ncol,nrow)
936  write (ichn) ((buf(ic, ir), ic=1, ncol), ir=1, nrow)
937  !
938  ! -- flush file
939  flush (ichn)
940  end subroutine ulasav
941 
942  !> @brief Record cell-by-cell flow terms for one component of flow as a 3-D
943  !! array with extra record to indicate delt, pertim, and totim
944  !<
945  subroutine ubdsv1(kstp, kper, text, ibdchn, buff, ncol, nrow, nlay, iout, &
946  delt, pertim, totim)
947  implicit none
948  ! -- dummy
949  integer(I4B), intent(in) :: kstp
950  integer(I4B), intent(in) :: kper
951  character(len=*), intent(in) :: text
952  integer(I4B), intent(in) :: ibdchn
953  real(dp), dimension(:), intent(in) :: buff
954  integer(I4B), intent(in) :: ncol
955  integer(I4B), intent(in) :: nrow
956  integer(I4B), intent(in) :: nlay
957  integer(I4B), intent(in) :: iout
958  real(dp), intent(in) :: delt
959  real(dp), intent(in) :: pertim
960  real(dp), intent(in) :: totim
961  ! -- format
962  character(len=*), parameter :: fmt = &
963  & "(1X,'UBDSV1 SAVING ',A16,' ON UNIT',I7,' AT TIME STEP',I7,"// &
964  & "', STRESS PERIOD',I7)"
965  !
966  ! -- Write records
967  if (iout > 0) write (iout, fmt) text, ibdchn, kstp, kper
968  write (ibdchn) kstp, kper, text, ncol, nrow, -nlay
969  write (ibdchn) 1, delt, pertim, totim
970  write (ibdchn) buff
971  !
972  ! -- flush file
973  flush (ibdchn)
974  end subroutine ubdsv1
975 
976  !> @brief Write header records for cell-by-cell flow terms for one component
977  !! of flow.
978  !!
979  !! Each item in the list is written by module ubdsvc
980  !<
981  subroutine ubdsv06(kstp, kper, text, modelnam1, paknam1, modelnam2, paknam2, &
982  ibdchn, naux, auxtxt, ncol, nrow, nlay, nlist, iout, &
983  delt, pertim, totim)
984  implicit none
985  ! -- dummy
986  integer(I4B), intent(in) :: kstp
987  integer(I4B), intent(in) :: kper
988  character(len=*), intent(in) :: text
989  character(len=*), intent(in) :: modelnam1
990  character(len=*), intent(in) :: paknam1
991  character(len=*), intent(in) :: modelnam2
992  character(len=*), intent(in) :: paknam2
993  integer(I4B), intent(in) :: naux
994  character(len=16), dimension(:), intent(in) :: auxtxt
995  integer(I4B), intent(in) :: ibdchn
996  integer(I4B), intent(in) :: ncol
997  integer(I4B), intent(in) :: nrow
998  integer(I4B), intent(in) :: nlay
999  integer(I4B), intent(in) :: nlist
1000  integer(I4B), intent(in) :: iout
1001  real(dp), intent(in) :: delt
1002  real(dp), intent(in) :: pertim
1003  real(dp), intent(in) :: totim
1004  ! -- local
1005  integer(I4B) :: n
1006  ! -- format
1007  character(len=*), parameter :: fmt = &
1008  & "(1X,'UBDSV06 SAVING ',A16,' IN MODEL ',A16,' PACKAGE ',A16,"// &
1009  & "'CONNECTED TO MODEL ',A16,' PACKAGE ',A16,"// &
1010  & "' ON UNIT',I7,' AT TIME STEP',I7,', STRESS PERIOD',I7)"
1011  !
1012  ! -- Write unformatted records identifying data.
1013  if (iout > 0) write (iout, fmt) text, modelnam1, paknam1, modelnam2, &
1014  paknam2, ibdchn, kstp, kper
1015  write (ibdchn) kstp, kper, text, ncol, nrow, -nlay
1016  write (ibdchn) 6, delt, pertim, totim
1017  write (ibdchn) modelnam1
1018  write (ibdchn) paknam1
1019  write (ibdchn) modelnam2
1020  write (ibdchn) paknam2
1021  write (ibdchn) naux + 1
1022  if (naux > 0) write (ibdchn) (auxtxt(n), n=1, naux)
1023  write (ibdchn) nlist
1024  end subroutine ubdsv06
1025 
1026  !> @brief Write one value of cell-by-cell flow using a list structure.
1027  !!
1028  !! From node (n) and to node (n2) are written to the file
1029  !<
1030  subroutine ubdsvc(ibdchn, n, q, naux, aux)
1031  implicit none
1032  ! -- dummy
1033  integer(I4B), intent(in) :: ibdchn
1034  integer(I4B), intent(in) :: n
1035  real(dp), intent(in) :: q
1036  integer(I4B), intent(in) :: naux
1037  real(dp), dimension(naux), intent(in) :: aux
1038  ! -- local
1039  integer(I4B) :: nn
1040  !
1041  ! -- Write record
1042  if (naux > 0) then
1043  write (ibdchn) n, q, (aux(nn), nn=1, naux)
1044  else
1045  write (ibdchn) n, q
1046  end if
1047  end subroutine ubdsvc
1048 
1049  !> @brief Write one value of cell-by-cell flow using a list structure.
1050  !!
1051  !! From node (n) and to node (n2) are written to the file
1052  !<
1053  subroutine ubdsvd(ibdchn, n, n2, q, naux, aux)
1054  implicit none
1055  ! -- dummy
1056  integer(I4B), intent(in) :: ibdchn
1057  integer(I4B), intent(in) :: n
1058  integer(I4B), intent(in) :: n2
1059  real(dp), intent(in) :: q
1060  integer(I4B), intent(in) :: naux
1061  real(dp), dimension(naux), intent(in) :: aux
1062  ! -- local
1063  integer(I4B) :: nn
1064  !
1065  ! -- Write record
1066  if (naux > 0) then
1067  write (ibdchn) n, n2, q, (aux(nn), nn=1, naux)
1068  else
1069  write (ibdchn) n, n2, q
1070  end if
1071  end subroutine ubdsvd
1072 
1073  !> @brief Perform a case-insensitive comparison of two words
1074  !<
1075  logical function same_word(word1, word2)
1076  implicit none
1077  ! -- dummy
1078  character(len=*), intent(in) :: word1, word2
1079  ! -- local
1080  character(len=200) :: upword1, upword2
1081  !
1082  upword1 = word1
1083  call upcase(upword1)
1084  upword2 = word2
1085  call upcase(upword2)
1086  same_word = (upword1 == upword2)
1087  end function same_word
1088 
1089  !> @brief Function for string manipulation
1090  !<
1091  function str_pad_left(str, width) result(res)
1092  ! -- local
1093  character(len=*), intent(in) :: str
1094  integer, intent(in) :: width
1095  ! -- Return
1096  character(len=max(len_trim(str), width)) :: res
1097  !
1098  res = str
1099  res = adjustr(res)
1100  end function
1101 
1102  subroutine unitinquire(iu)
1103  ! -- dummy
1104  integer(I4B) :: iu
1105  ! -- local
1106  character(len=LINELENGTH) :: line
1107  character(len=100) :: fname, ac, act, fm, frm, seq, unf
1108  ! -- format
1109  character(len=*), parameter :: fmta = &
1110  &"('unit:',i4,' name:',a,' access:',a,' action:',a)"
1111  character(len=*), parameter :: fmtb = &
1112  &"(' formatted:',a,' sequential:',a,' unformatted:',a,' form:',a)"
1113  !
1114  ! -- set strings using inquire statement
1115  inquire (unit=iu, name=fname, access=ac, action=act, formatted=fm, &
1116  sequential=seq, unformatted=unf, form=frm)
1117  !
1118  ! -- write the results of the inquire statement
1119  write (line, fmta) iu, trim(fname), trim(ac), trim(act)
1120  call write_message(line)
1121  write (line, fmtb) trim(fm), trim(seq), trim(unf), trim(frm)
1122  call write_message(line)
1123  end subroutine unitinquire
1124 
1125  !> @brief Parse a line into words.
1126  !!
1127  !! Blanks and commas are recognized as delimiters. Multiple blanks between
1128  !! words is OK, but multiple commas between words is treated as an error.
1129  !! Quotation marks are not recognized as delimiters.
1130  !<
1131  subroutine parseline(line, nwords, words, inunit, filename)
1132  ! -- modules
1133  use constantsmodule, only: linelength
1134  implicit none
1135  ! -- dummy
1136  character(len=*), intent(in) :: line
1137  integer(I4B), intent(inout) :: nwords
1138  character(len=*), allocatable, dimension(:), intent(inout) :: words
1139  integer(I4B), intent(in), optional :: inunit
1140  character(len=*), intent(in), optional :: filename
1141  ! -- local
1142  integer(I4B) :: i, idum, istart, istop, linelen, lloc
1143  real(dp) :: rdum
1144  !
1145  nwords = 0
1146  if (allocated(words)) then
1147  deallocate (words)
1148  end if
1149  linelen = len(line)
1150  !
1151  ! -- get the number of words in a line and allocate words array
1152  nwords = get_nwords(line)
1153  allocate (words(nwords))
1154  !
1155  ! -- Populate words array and return
1156  lloc = 1
1157  do i = 1, nwords
1158  call urword(line, lloc, istart, istop, 0, idum, rdum, 0, 0)
1159  words(i) = line(istart:istop)
1160  end do
1161  end subroutine parseline
1162 
1163  !> @brief Print 1 layer array with user formatting in wrap format
1164  !<
1165  subroutine ulaprufw(ncol, nrow, kstp, kper, ilay, iout, buf, text, userfmt, &
1166  nvalues, nwidth, editdesc)
1167  implicit none
1168  ! -- dummy
1169  integer(I4B), intent(in) :: ncol, nrow, kstp, kper, ilay, iout
1170  real(dp), dimension(ncol, nrow), intent(in) :: buf
1171  character(len=*), intent(in) :: text
1172  character(len=*), intent(in) :: userfmt
1173  integer(I4B), intent(in) :: nvalues, nwidth
1174  character(len=1), intent(in) :: editdesc
1175  ! -- local
1176  integer(I4B) :: i, j, nspaces
1177  ! -- formats
1178  character(len=*), parameter :: fmtmsgout1 = &
1179  "('1',/2X,A,' IN LAYER ',I3,' AT END OF TIME STEP ',I3, &
1180 & ' IN STRESS PERIOD ',I4/2X,75('-'))"
1181  character(len=*), parameter :: fmtmsgout2 = &
1182  "('1',/1X,A,' FOR CROSS SECTION AT END OF TIME STEP',I3, &
1183 & ' IN STRESS PERIOD ',I4/1X,79('-'))"
1184  !
1185  if (iout <= 0) return
1186  ! -- Print a header depending on ILAY
1187  if (ilay > 0) then
1188  write (iout, fmtmsgout1) trim(text), ilay, kstp, kper
1189  else if (ilay < 0) then
1190  write (iout, fmtmsgout2) trim(text), kstp, kper
1191  end if
1192  !
1193  ! -- Print column numbers.
1194  nspaces = 0
1195  if (editdesc == 'F') nspaces = 3
1196  call ucolno(1, ncol, nspaces, nvalues, nwidth + 1, iout)
1197  !
1198  ! -- Loop through the rows, printing each one in its entirety.
1199  do i = 1, nrow
1200  write (iout, userfmt) i, (buf(j, i), j=1, ncol)
1201  end do
1202  !
1203  ! -- flush file
1204  flush (iout)
1205  end subroutine ulaprufw
1206 
1207  !> @brief This function reads a line of arbitrary length and returns it.
1208  !!
1209  !! The returned string can be stored in a deferred-length character variable,
1210  !! for example:
1211  !!
1212  !! integer(I4B) :: iu
1213  !! character(len=:), allocatable :: my_string
1214  !! logical :: eof
1215  !! iu = 8
1216  !! open(iu,file='my_file')
1217  !! my_string = read_line(iu, eof)
1218  !<
1219  function read_line(iu, eof) result(astring)
1220  !
1221  implicit none
1222  ! -- dummy
1223  integer(I4B), intent(in) :: iu
1224  logical, intent(out) :: eof
1225  character(len=:), allocatable :: astring
1226  ! -- local
1227  integer(I4B) :: isize, istat
1228  character(len=256) :: buffer
1229  character(len=1000) :: ermsg, fname
1230  character(len=7) :: fmtd
1231  logical :: lop
1232  ! -- formats
1233  character(len=*), parameter :: fmterrmsg1 = &
1234  & "('Error in read_line: File ',i0,' is not open.')"
1235  character(len=*), parameter :: fmterrmsg2 = &
1236  & "('Error in read_line: Attempting to read text ' // &
1237  & 'from unformatted file: ""',a,'""')"
1238  character(len=*), parameter :: fmterrmsg3 = &
1239  & "('Error reading from file ""',a,'"" opened on unit ',i0, &
1240  & ' in read_line.')"
1241  !
1242  astring = ''
1243  eof = .false.
1244  do
1245  read (iu, '(a)', advance='NO', iostat=istat, size=isize, end=99) buffer
1246  if (istat > 0) then
1247  ! Determine error if possible, report it, and stop.
1248  if (iu <= 0) then
1249  ermsg = 'Programming error in call to read_line: '// &
1250  'Attempt to read from unit number <= 0'
1251  else
1252  inquire (unit=iu, opened=lop, name=fname, formatted=fmtd)
1253  if (.not. lop) then
1254  write (ermsg, fmterrmsg1) iu
1255  elseif (fmtd == 'NO' .or. fmtd == 'UNKNOWN') then
1256  write (ermsg, fmterrmsg2) trim(fname)
1257  else
1258  write (ermsg, fmterrmsg3) trim(fname), iu
1259  end if
1260  end if
1261  call store_error(ermsg)
1262  call store_error_unit(iu)
1263  end if
1264  astring = astring//buffer(:isize)
1265  ! -- An end-of-record condition stops the loop.
1266  if (istat < 0) then
1267  return
1268  end if
1269  end do
1270  !
1271  return
1272 99 continue
1273  !
1274  ! An end-of-file condition returns an empty string.
1275  eof = .true.
1276  end function read_line
1277 
1278  subroutine getfilefrompath(pathname, filename)
1279  implicit none
1280  ! -- dummy
1281  character(len=*), intent(in) :: pathname
1282  character(len=*), intent(out) :: filename
1283  ! -- local
1284  integer(I4B) :: i, istart, istop, lenpath
1285  character(len=1) :: fs = '/'
1286  character(len=1) :: bs = '\'
1287  !
1288  filename = ''
1289  lenpath = len_trim(pathname)
1290  istart = 1
1291  istop = lenpath
1292  loop: do i = lenpath, 1, -1
1293  if (pathname(i:i) == fs .or. pathname(i:i) == bs) then
1294  if (i == istop) then
1295  istop = istop - 1
1296  else
1297  istart = i + 1
1298  exit loop
1299  end if
1300  end if
1301  end do loop
1302  if (istop >= istart) then
1303  filename = pathname(istart:istop)
1304  end if
1305  end subroutine getfilefrompath
1306 
1307  !> @brief Starting at position icol, define string as line(istart:istop).
1308  !!
1309  !! If string can be interpreted as an integer(I4B), return integer in idnum
1310  !! argument. If token is not an integer(I4B), assume it is a boundary name,
1311  !! return NAMEDBOUNDFLAG in idnum, convert string to uppercase and return it
1312  !! in bndname.
1313  !<
1314  subroutine extract_idnum_or_bndname(line, icol, istart, istop, idnum, bndname)
1315  implicit none
1316  ! -- dummy
1317  character(len=*), intent(inout) :: line
1318  integer(I4B), intent(inout) :: icol, istart, istop
1319  integer(I4B), intent(out) :: idnum
1320  character(len=LENBOUNDNAME), intent(out) :: bndname
1321  ! -- local
1322  integer(I4B) :: istat, ndum, ncode = 0
1323  real(dp) :: rdum
1324  !
1325  call urword(line, icol, istart, istop, ncode, ndum, rdum, 0, 0)
1326  read (line(istart:istop), *, iostat=istat) ndum
1327  if (istat == 0) then
1328  idnum = ndum
1329  bndname = ''
1330  else
1331  idnum = namedboundflag
1332  bndname = line(istart:istop)
1333  call upcase(bndname)
1334  end if
1335  end subroutine extract_idnum_or_bndname
1336 
1337  !> @brief Read auxiliary variables from an input line
1338  !<
1339  subroutine urdaux(naux, inunit, iout, lloc, istart, istop, auxname, line, text)
1340  ! -- modules
1341  use arrayhandlersmodule, only: expandarray
1342  use constantsmodule, only: lenauxname
1343  ! -- implicit
1344  implicit none
1345  ! -- dummy
1346  integer(I4B), intent(inout) :: naux
1347  integer(I4B), intent(in) :: inunit
1348  integer(I4B), intent(in) :: iout
1349  integer(I4B), intent(inout) :: lloc
1350  integer(I4B), intent(inout) :: istart
1351  integer(I4B), intent(inout) :: istop
1352  character(len=LENAUXNAME), allocatable, dimension(:), intent(inout) :: auxname
1353  character(len=*), intent(inout) :: line
1354  character(len=*), intent(in) :: text
1355  ! -- local
1356  integer(I4B) :: n, linelen
1357  integer(I4B) :: iauxlen
1358  real(dp) :: rval
1359  !
1360  linelen = len(line)
1361  if (naux > 0) then
1362  write (errmsg, '(a)') 'Auxiliary variables already specified. '// &
1363  & 'Auxiliary variables must be specified on one line in the '// &
1364  & 'options block.'
1365  call store_error(errmsg)
1366  call store_error_unit(inunit)
1367  end if
1368  auxloop: do
1369  call urword(line, lloc, istart, istop, 1, n, rval, iout, inunit)
1370  if (istart >= linelen) exit auxloop
1371  iauxlen = istop - istart + 1
1372  if (iauxlen > lenauxname) then
1373  write (errmsg, '(a, a, a, i0, a, i0, a)') &
1374  'Found auxiliary variable (', line(istart:istop), &
1375  ') with a name of size ', iauxlen, &
1376  '. Auxiliary variable names must be len than or equal&
1377  & to ', lenauxname, ' characters.'
1378  call store_error(errmsg)
1379  call store_error_unit(inunit)
1380  end if
1381  naux = naux + 1
1382  call expandarray(auxname)
1383  auxname(naux) = line(istart:istop)
1384  if (iout > 0) then
1385  write (iout, "(4X,'AUXILIARY ',a,' VARIABLE: ',A)") &
1386  trim(adjustl(text)), auxname(naux)
1387  end if
1388  end do auxloop
1389  end subroutine urdaux
1390 
1391  !> @brief Define the print or save format
1392  !!
1393  !! Define cdatafmp as a Fortran output format based on user input. Also define
1394  !! nvalues, nwidth, and editdesc.
1395  !!
1396  !! Syntax for linein:
1397  !! COLUMNS nval WIDTH nwid [DIGITS ndig [options]]
1398  !!
1399  !! Where:
1400  !! nval = Number of values per line.
1401  !! nwid = Number of character places to be used for each value.
1402  !! ndig = Number of digits to the right of the decimal point (required
1403  !! for real array).
1404  !! options are:
1405  !! editoption: One of [EXPONENTIAL, FIXED, GENERAL, SCIENTIFIC]
1406  !! A default value should be passed in for editdesc as G, I, E, F, or S.
1407  !! If I is passed in, then the fortran format will be for an integer variable.
1408  !<
1409  subroutine print_format(linein, cdatafmp, editdesc, nvaluesp, nwidthp, inunit)
1410  ! -- dummy
1411  character(len=*), intent(in) :: linein
1412  character(len=*), intent(inout) :: cdatafmp
1413  character(len=*), intent(inout) :: editdesc
1414  integer(I4B), intent(inout) :: nvaluesp
1415  integer(I4B), intent(inout) :: nwidthp
1416  integer(I4B), intent(in) :: inunit
1417  ! -- local
1418  character(len=len(linein)) :: line
1419  character(len=20), dimension(:), allocatable :: words
1420  character(len=100) :: ermsg
1421  integer(I4B) :: ndigits = 0, nwords = 0
1422  integer(I4B) :: i, ierr
1423  logical :: isint
1424  !
1425  ! -- Parse line and initialize values
1426  line(:) = linein(:)
1427  call parseline(line, nwords, words, inunit)
1428  ierr = 0
1429  i = 0
1430  isint = .false.
1431  if (editdesc == 'I') isint = .true.
1432  !
1433  ! -- Check array name
1434  if (nwords < 1) then
1435  ermsg = 'Could not build PRINT_FORMAT from line'//trim(line)
1436  call store_error(trim(ermsg))
1437  ermsg = 'Syntax is: COLUMNS <columns> WIDTH <width> DIGITS &
1438  &<digits> <format>'
1439  call store_error(trim(ermsg))
1440  call store_error_unit(inunit)
1441  end if
1442  !
1443  ermsg = 'Error setting PRINT_FORMAT. Syntax is incorrect in line:'
1444  if (nwords >= 4) then
1445  if (.not. same_word(words(1), 'COLUMNS')) ierr = 1
1446  if (.not. same_word(words(3), 'WIDTH')) ierr = 1
1447  ! -- Read nvalues and nwidth
1448  if (ierr == 0) then
1449  read (words(2), *, iostat=ierr) nvaluesp
1450  end if
1451  if (ierr == 0) then
1452  read (words(4), *, iostat=ierr) nwidthp
1453  end if
1454  else
1455  ierr = 1
1456  end if
1457  if (ierr /= 0) then
1458  call store_error(ermsg)
1459  call store_error(line)
1460  ermsg = 'Syntax is: COLUMNS <columns> WIDTH <width> &
1461  &DIGITS <digits> <format>'
1462  call store_error(trim(ermsg))
1463  call store_error_unit(inunit)
1464  end if
1465  i = 4
1466  !
1467  if (.not. isint) then
1468  ! -- Check for DIGITS specification
1469  if (nwords >= 5) then
1470  if (.not. same_word(words(5), 'DIGITS')) ierr = 1
1471  ! -- Read ndigits
1472  read (words(6), *, iostat=ierr) ndigits
1473  else
1474  ierr = 1
1475  end if
1476  i = i + 2
1477  end if
1478  !
1479  ! -- Check for EXPONENTIAL | FIXED | GENERAL | SCIENTIFIC option.
1480  ! -- Check for LABEL, WRAP, and STRIP options.
1481  do
1482  i = i + 1
1483  if (i <= nwords) then
1484  call upcase(words(i))
1485  select case (words(i))
1486  case ('EXPONENTIAL')
1487  editdesc = 'E'
1488  if (isint) ierr = 1
1489  case ('FIXED')
1490  editdesc = 'F'
1491  if (isint) ierr = 1
1492  case ('GENERAL')
1493  editdesc = 'G'
1494  if (isint) ierr = 1
1495  case ('SCIENTIFIC')
1496  editdesc = 'S'
1497  if (isint) ierr = 1
1498  case default
1499  ermsg = 'Error in format specification. Unrecognized option: '//words(i)
1500  call store_error(ermsg)
1501  ermsg = 'Valid values are EXPONENTIAL, FIXED, GENERAL, or SCIENTIFIC.'
1502  call store_error(ermsg)
1503  call store_error_unit(inunit)
1504  end select
1505  else
1506  exit
1507  end if
1508  end do
1509  if (ierr /= 0) then
1510  call store_error(ermsg)
1511  call store_error(line)
1512  call store_error_unit(inunit)
1513  end if
1514  !
1515  ! -- Build the output format.
1516  select case (editdesc)
1517  case ('I')
1518  call buildintformat(nvaluesp, nwidthp, cdatafmp)
1519  case ('F')
1520  call buildfixedformat(nvaluesp, nwidthp, ndigits, cdatafmp)
1521  case ('E', 'G', 'S')
1522  call buildfloatformat(nvaluesp, nwidthp, ndigits, editdesc, cdatafmp)
1523  end select
1524  end subroutine print_format
1525 
1526  !> @brief Build a fixed format for printing or saving a real array
1527  !<
1528  subroutine buildfixedformat(nvalsp, nwidp, ndig, outfmt, prowcolnum)
1529  implicit none
1530  ! -- dummy
1531  integer(I4B), intent(in) :: nvalsp, nwidp, ndig
1532  character(len=*), intent(inout) :: outfmt
1533  logical, intent(in), optional :: prowcolnum ! default true
1534  ! -- local
1535  character(len=8) :: cvalues, cwidth, cdigits
1536  character(len=60) :: ufmt
1537  logical :: prowcolnumlocal
1538  ! -- formats
1539  character(len=*), parameter :: fmtndig = "(i8)"
1540  !
1541  if (present(prowcolnum)) then
1542  prowcolnumlocal = prowcolnum
1543  else
1544  prowcolnumlocal = .true.
1545  end if
1546  !
1547  ! -- Convert integers to characters and left-adjust
1548  write (cdigits, fmtndig) ndig
1549  cdigits = adjustl(cdigits)
1550  !
1551  ! -- Build format for printing to the list file in wrap format
1552  write (cvalues, fmtndig) nvalsp
1553  cvalues = adjustl(cvalues)
1554  write (cwidth, fmtndig) nwidp
1555  cwidth = adjustl(cwidth)
1556  if (prowcolnumlocal) then
1557  ufmt = '(1x,i3,1x,'
1558  else
1559  ufmt = '(5x,'
1560  end if
1561  !
1562  ufmt = trim(ufmt)//cvalues
1563  ufmt = trim(ufmt)//'(1x,f'
1564  ufmt = trim(ufmt)//cwidth
1565  ufmt = trim(ufmt)//'.'
1566  ufmt = trim(ufmt)//cdigits
1567  ufmt = trim(ufmt)//'):/(5x,'
1568  ufmt = trim(ufmt)//cvalues
1569  ufmt = trim(ufmt)//'(1x,f'
1570  ufmt = trim(ufmt)//cwidth
1571  ufmt = trim(ufmt)//'.'
1572  ufmt = trim(ufmt)//cdigits
1573  ufmt = trim(ufmt)//')))'
1574  outfmt = ufmt
1575  end subroutine buildfixedformat
1576 
1577  !> @brief Build a floating-point format for printing or saving a real array
1578  !<
1579  subroutine buildfloatformat(nvalsp, nwidp, ndig, editdesc, outfmt, prowcolnum)
1580  implicit none
1581  ! -- dummy
1582  integer(I4B), intent(in) :: nvalsp, nwidp, ndig
1583  character(len=*), intent(in) :: editdesc
1584  character(len=*), intent(inout) :: outfmt
1585  logical, intent(in), optional :: prowcolnum ! default true
1586  ! -- local
1587  character(len=8) :: cvalues, cwidth, cdigits
1588  character(len=60) :: ufmt
1589  logical :: prowcolnumlocal
1590  ! -- formats
1591  character(len=*), parameter :: fmtndig = "(i8)"
1592  !
1593  if (present(prowcolnum)) then
1594  prowcolnumlocal = prowcolnum
1595  else
1596  prowcolnumlocal = .true.
1597  end if
1598  !
1599  ! -- Build the format
1600  write (cdigits, fmtndig) ndig
1601  cdigits = adjustl(cdigits)
1602  ! -- Convert integers to characters and left-adjust
1603  write (cwidth, fmtndig) nwidp
1604  cwidth = adjustl(cwidth)
1605  ! -- Build format for printing to the list file
1606  write (cvalues, fmtndig) (nvalsp - 1)
1607  cvalues = adjustl(cvalues)
1608  if (prowcolnumlocal) then
1609  ufmt = '(1x,i3,2x,1p,'//editdesc
1610  else
1611  ufmt = '(6x,1p,'//editdesc
1612  end if
1613  ufmt = trim(ufmt)//cwidth
1614  ufmt = trim(ufmt)//'.'
1615  ufmt = trim(ufmt)//cdigits
1616  if (nvalsp > 1) then
1617  ufmt = trim(ufmt)//','
1618  ufmt = trim(ufmt)//cvalues
1619  ufmt = trim(ufmt)//'(1x,'
1620  ufmt = trim(ufmt)//editdesc
1621  ufmt = trim(ufmt)//cwidth
1622  ufmt = trim(ufmt)//'.'
1623  ufmt = trim(ufmt)//cdigits
1624  ufmt = trim(ufmt)//')'
1625  end if
1626  !
1627  ufmt = trim(ufmt)//':/(5x,'
1628  write (cvalues, fmtndig) nvalsp
1629  cvalues = adjustl(cvalues)
1630  ufmt = trim(ufmt)//cvalues
1631  ufmt = trim(ufmt)//'(1x,'
1632  ufmt = trim(ufmt)//editdesc
1633  ufmt = trim(ufmt)//cwidth
1634  ufmt = trim(ufmt)//'.'
1635  ufmt = trim(ufmt)//cdigits
1636  ufmt = trim(ufmt)//')))'
1637  outfmt = ufmt
1638  end subroutine buildfloatformat
1639 
1640  !> @brief Build a format for printing or saving an integer array
1641  !<
1642  subroutine buildintformat(nvalsp, nwidp, outfmt, prowcolnum)
1643  implicit none
1644  ! -- dummy
1645  integer(I4B), intent(in) :: nvalsp, nwidp
1646  character(len=*), intent(inout) :: outfmt
1647  logical, intent(in), optional :: prowcolnum ! default true
1648  ! -- local
1649  character(len=8) :: cvalues, cwidth
1650  character(len=60) :: ufmt
1651  logical :: prowcolnumlocal
1652  ! -- formats
1653  character(len=*), parameter :: fmtndig = "(i8)"
1654  !
1655  if (present(prowcolnum)) then
1656  prowcolnumlocal = prowcolnum
1657  else
1658  prowcolnumlocal = .true.
1659  end if
1660  !
1661  ! -- Build format for printing to the list file in wrap format
1662  write (cvalues, fmtndig) nvalsp
1663  cvalues = adjustl(cvalues)
1664  write (cwidth, fmtndig) nwidp
1665  cwidth = adjustl(cwidth)
1666  if (prowcolnumlocal) then
1667  ufmt = '(1x,i3,1x,'
1668  else
1669  ufmt = '(5x,'
1670  end if
1671  ufmt = trim(ufmt)//cvalues
1672  ufmt = trim(ufmt)//'(1x,i'
1673  ufmt = trim(ufmt)//cwidth
1674  ufmt = trim(ufmt)//'):/(5x,'
1675  ufmt = trim(ufmt)//cvalues
1676  ufmt = trim(ufmt)//'(1x,i'
1677  ufmt = trim(ufmt)//cwidth
1678  ufmt = trim(ufmt)//')))'
1679  outfmt = ufmt
1680  end subroutine buildintformat
1681 
1682  !> @brief Get the number of words in a string
1683  !<
1684  function get_nwords(line)
1685  ! -- return
1686  integer(I4B) :: get_nwords !< number of words in a string
1687  ! -- dummy
1688  character(len=*), intent(in) :: line !< line
1689  ! -- local
1690  integer(I4B) :: linelen
1691  integer(I4B) :: lloc
1692  integer(I4B) :: istart
1693  integer(I4B) :: istop
1694  integer(I4B) :: idum
1695  real(dp) :: rdum
1696  !
1697  ! -- initialize variables
1698  get_nwords = 0
1699  linelen = len(line)
1700  !
1701  ! -- Count words in line and allocate words array
1702  lloc = 1
1703  do
1704  call urword(line, lloc, istart, istop, 0, idum, rdum, 0, 0)
1705  if (istart == linelen) exit
1706  get_nwords = get_nwords + 1
1707  end do
1708  end function get_nwords
1709 
1710  !> @brief Move the file pointer.
1711  !!
1712  !! Patterned after fseek, which is not supported as part of the fortran
1713  !! standard. For this subroutine to work the file must have been opened with
1714  !! access='stream' and action='readwrite'.
1715  !<
1716  subroutine fseek_stream(iu, offset, whence, status)
1717  ! -- dummy
1718  integer(I4B), intent(in) :: iu
1719  integer(I4B), intent(in) :: offset
1720  integer(I4B), intent(in) :: whence
1721  integer(I4B), intent(inout) :: status
1722  ! -- local
1723  integer(I8B) :: ipos
1724  !
1725  inquire (unit=iu, size=ipos)
1726  !
1727  select case (whence)
1728  case (0)
1729  !
1730  ! -- whence = 0, offset is relative to start of file
1731  ipos = 0 + offset
1732  case (1)
1733  !
1734  ! -- whence = 1, offset is relative to current pointer position
1735  inquire (unit=iu, pos=ipos)
1736  ipos = ipos + offset
1737  case (2)
1738  !
1739  ! -- whence = 2, offset is relative to end of file
1740  inquire (unit=iu, size=ipos)
1741  ipos = ipos + offset
1742  end select
1743  !
1744  ! -- position the file pointer to ipos
1745  write (iu, pos=ipos, iostat=status)
1746  inquire (unit=iu, pos=ipos)
1747  end subroutine fseek_stream
1748 
1749  !> @brief Read until non-comment line found and then return line.
1750  !!
1751  !! Different from u8rdcom in that line is a deferred length character string,
1752  !! which allows any length lines to be read using the get_line subroutine.
1753  !<
1754  subroutine u9rdcom(iin, iout, line, ierr)
1755  ! -- module
1756  use, intrinsic :: iso_fortran_env, only: iostat_end
1757  implicit none
1758  ! -- dummy
1759  integer(I4B), intent(in) :: iin
1760  integer(I4B), intent(in) :: iout
1761  character(len=:), allocatable, intent(inout) :: line
1762  integer(I4B), intent(out) :: ierr
1763  ! -- local
1764  character(len=:), allocatable :: linetemp
1765  character(len=2), parameter :: comment = '//'
1766  character(len=1), parameter :: tab = char(9)
1767  logical :: iscomment
1768  integer(I4B) :: i, j, l, istart, lsize
1769  !
1770  !readerrmsg = ''
1771  line = comment
1772  pcomments: do
1773  call get_line(iin, line, ierr)
1774  if (ierr == iostat_end) then
1775  ! -- End of file reached. Return with ierr = IOSTAT_END
1776  ! and line as an empty string
1777  line = ' '
1778  exit pcomments
1779  elseif (ierr /= 0) then
1780  ! -- Other error...report it
1781  call unitinquire(iin)
1782  write (errmsg, *) 'u9rdcom: Could not read from unit: ', iin
1783  call store_error(errmsg, terminate=.true.)
1784  end if
1785  if (len_trim(line) < 1) then
1786  line = comment
1787  cycle
1788  end if
1789  !
1790  ! -- Ensure that any initial tab characters are treated as spaces
1791  cleartabs: do
1792  !
1793  ! -- adjustl manually to avoid stack overflow
1794  lsize = len(line)
1795  istart = 1
1796  allocate (character(len=lsize) :: linetemp)
1797  do j = 1, lsize
1798  if (line(j:j) /= ' ' .and. line(j:j) /= ',' .and. &
1799  line(j:j) /= char(9)) then
1800  istart = j
1801  exit
1802  end if
1803  end do
1804  linetemp(:) = ' '
1805  linetemp(:) = line(istart:)
1806  line(:) = linetemp(:)
1807  deallocate (linetemp)
1808  !
1809  ! -- check for comment
1810  iscomment = .false.
1811  select case (line(1:1))
1812  case ('#')
1813  iscomment = .true.
1814  exit cleartabs
1815  case ('!')
1816  iscomment = .true.
1817  exit cleartabs
1818  case (tab)
1819  line(1:1) = ' '
1820  cycle cleartabs
1821  case default
1822  if (line(1:2) == comment) iscomment = .true.
1823  if (len_trim(line) < 1) iscomment = .true.
1824  exit cleartabs
1825  end select
1826  end do cleartabs
1827  !
1828  if (.not. iscomment) then
1829  exit pcomments
1830  else
1831  if (iout > 0) then
1832  !find the last non-blank character.
1833  l = len(line)
1834  do i = l, 1, -1
1835  if (line(i:i) /= ' ') then
1836  exit
1837  end if
1838  end do
1839  ! -- print the line up to the last non-blank character.
1840  write (iout, '(1x,a)') line(1:i)
1841  end if
1842  end if
1843  end do pcomments
1844  end subroutine u9rdcom
1845 
1846  !> @brief Read an unlimited length line from unit number lun into a deferred-
1847  !! length character string (line).
1848  !!
1849  !! Tack on a single space to the end so that routines like URWORD continue to
1850  !! function as before.
1851  !<
1852  subroutine get_line(lun, line, iostat)
1853  ! -- dummy
1854  integer(I4B), intent(in) :: lun
1855  character(len=:), intent(out), allocatable :: line
1856  integer(I4B), intent(out) :: iostat
1857  ! -- local
1858  integer(I4B), parameter :: buffer_len = maxcharlen
1859  character(len=buffer_len) :: buffer
1860  character(len=:), allocatable :: linetemp
1861  integer(I4B) :: size_read, linesize
1862  character(len=1), parameter :: cr = char(13)
1863  character(len=1), parameter :: lf = char(10)
1864  !
1865  ! -- initialize
1866  line = ''
1867  linetemp = ''
1868  !
1869  ! -- process
1870  do
1871  read (lun, '(A)', iostat=iostat, advance='no', size=size_read) buffer
1872  if (is_iostat_eor(iostat)) then
1873  linesize = len(line)
1874  deallocate (linetemp)
1875  allocate (character(len=linesize) :: linetemp)
1876  linetemp(:) = line(:)
1877  deallocate (line)
1878  allocate (character(len=linesize + size_read + 1) :: line)
1879  line(:) = linetemp(:)
1880  line(linesize + 1:) = buffer(:size_read)
1881  linesize = len(line)
1882  line(linesize:linesize) = ' '
1883  iostat = 0
1884  exit
1885  else if (iostat == 0) then
1886  linesize = len(line)
1887  deallocate (linetemp)
1888  allocate (character(len=linesize) :: linetemp)
1889  linetemp(:) = line(:)
1890  deallocate (line)
1891  allocate (character(len=linesize + size_read) :: line)
1892  line(:) = linetemp(:)
1893  line(linesize + 1:) = buffer(:size_read)
1894  else
1895  exit
1896  end if
1897  end do
1898  !
1899  ! -- look for undetected end-of-record with isolated CR or LF
1900  linesize = len(line)
1901  crlfcheck: do i = 1, linesize
1902  if (line(i:i) .eq. cr .or. line(i:i) .eq. lf) then
1903  if (line(i:i) .eq. cr) then
1904  write (errmsg, '(a)') &
1905  'get_line: Found an isolated Carriage Return.'
1906  end if
1907  if (line(i:i) .eq. lf) then
1908  write (errmsg, '(a)') &
1909  'get_line: Found an isolated Line Feed.'
1910  end if
1911  write (errmsg, '(a,1x,a,a)') trim(errmsg), &
1912  'Replace with Carriage Return and Line Feed to', &
1913  ' read as two separate lines.'
1914  write (errmsg, '(a,1x,5a)') trim(errmsg), &
1915  'Line: "', line(1:i - 1), '|', line(i + 1:linesize), '"'
1916  call store_error(errmsg, terminate=.false.)
1917  call store_error_unit(lun, terminate=.true.)
1918  end if
1919  end do crlfcheck
1920  end subroutine get_line
1921 
1922 end module inputoutputmodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
@ tabcenter
centered table column
Definition: Constants.f90:172
@ tabright
right justified table column
Definition: Constants.f90:173
@ tableft
left justified table column
Definition: Constants.f90:171
@ tabucstring
upper case string table data
Definition: Constants.f90:180
@ tabstring
string table data
Definition: Constants.f90:179
@ tabreal
real table data
Definition: Constants.f90:182
@ tabinteger
integer table data
Definition: Constants.f90:181
integer(i4b), parameter iulast
maximum file unit number (this allows for 9000 open files)
Definition: Constants.f90:58
integer(i4b), parameter namedboundflag
named bound flag
Definition: Constants.f90:49
integer(i4b), parameter iustart
starting file unit number
Definition: Constants.f90:57
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
integer(i4b), parameter lenauxname
maximum length of a aux variable
Definition: Constants.f90:35
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:36
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:47
subroutine, public buildintformat(nvalsp, nwidp, outfmt, prowcolnum)
Build a format for printing or saving an integer array.
subroutine, public assign_iounit(iounit, errunit, description)
@ brief assign io unit number
subroutine, public urdaux(naux, inunit, iout, lloc, istart, istop, auxname, line, text)
Read auxiliary variables from an input line.
logical function, public same_word(word1, word2)
Perform a case-insensitive comparison of two words.
subroutine, public getfilefrompath(pathname, filename)
subroutine, public ubdsvc(ibdchn, n, q, naux, aux)
Write one value of cell-by-cell flow using a list structure.
subroutine, public extract_idnum_or_bndname(line, icol, istart, istop, idnum, bndname)
Starting at position icol, define string as line(istart:istop).
subroutine, public ucolno(nlbl1, nlbl2, nspace, ncpl, ndig, iout)
Output column numbers above a matrix printout.
subroutine, public ubdsv1(kstp, kper, text, ibdchn, buff, ncol, nrow, nlay, iout, delt, pertim, totim)
Record cell-by-cell flow terms for one component of flow as a 3-D array with extra record to indicate...
subroutine, public ubdsv4(kstp, kper, text, naux, auxtxt, ibdchn, ncol, nrow, nlay, nlist, iout, delt, pertim, totim)
Write header records for cell-by-cell flow terms for one component of flow plus auxiliary data using ...
subroutine, public ubdsvb(ibdchn, icrl, q, val, nvl, naux, laux)
Write one value of cell-by-cell flow plus auxiliary data using a list structure.
integer(i4b) function, public getunit()
Get a free unit number.
subroutine get_line(lun, line, iostat)
Read an unlimited length line from unit number lun into a deferred- length character string (line).
subroutine, public lowcase(word)
Convert to lower case.
subroutine, public ulaprw(buf, text, kstp, kper, ncol, nrow, ilay, iprn, iout)
Print 1 layer array.
subroutine, public parseline(line, nwords, words, inunit, filename)
Parse a line into words.
subroutine, public buildfixedformat(nvalsp, nwidp, ndig, outfmt, prowcolnum)
Build a fixed format for printing or saving a real array.
subroutine, public buildfloatformat(nvalsp, nwidp, ndig, editdesc, outfmt, prowcolnum)
Build a floating-point format for printing or saving a real array.
subroutine, public upcase(word)
Convert to upper case.
integer(i4b) function, public get_nwords(line)
Get the number of words in a string.
subroutine, public u9rdcom(iin, iout, line, ierr)
Read until non-comment line found and then return line.
subroutine, public fseek_stream(iu, offset, whence, status)
Move the file pointer.
character(len=max(len_trim(str), width)) function, public str_pad_left(str, width)
Function for string manipulation.
subroutine, public print_format(linein, cdatafmp, editdesc, nvaluesp, nwidthp, inunit)
Define the print or save format.
subroutine, public ubdsvd(ibdchn, n, n2, q, naux, aux)
Write one value of cell-by-cell flow using a list structure.
subroutine, public ulstlb(iout, label, caux, ncaux, naux)
Print a label for a list.
character(len=:) function, allocatable, public read_line(iu, eof)
This function reads a line of arbitrary length and returns it.
subroutine, public append_processor_id(name, proc_id)
Append processor id to a string.
subroutine, public ulaprufw(ncol, nrow, kstp, kper, ilay, iout, buf, text, userfmt, nvalues, nwidth, editdesc)
Print 1 layer array with user formatting in wrap format.
subroutine freeunitnumber(iu)
Assign a free unopened unit number.
subroutine, public ubdsv06(kstp, kper, text, modelnam1, paknam1, modelnam2, paknam2, ibdchn, naux, auxtxt, ncol, nrow, nlay, nlist, iout, delt, pertim, totim)
Write header records for cell-by-cell flow terms for one component of flow.
subroutine, public ulasav(buf, text, kstp, kper, pertim, totim, ncol, nrow, ilay, ichn)
Save 1 layer array on disk.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
subroutine, public unitinquire(iu)
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
subroutine, public uwword(line, icol, ilen, ncode, c, n, r, fmt, alignment, sep)
Create a formatted line.
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
character(len=20), dimension(2) action
Definition: OpenSpec.f90:7
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
integer(i4b) iunext
next file unit number to assign
integer(i4b) isim_mode
simulation mode