28 subroutine openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, &
29 filstat_opt, mode_opt)
34 integer(I4B),
intent(inout) :: iu
35 integer(I4B),
intent(in) :: iout
36 character(len=*),
intent(in) :: fname
37 character(len=*),
intent(in) :: ftype
38 character(len=*),
intent(in),
optional :: fmtarg_opt
39 character(len=*),
intent(in),
optional :: accarg_opt
40 character(len=*),
intent(in),
optional :: filstat_opt
41 integer(I4B),
intent(in),
optional :: mode_opt
43 character(len=20) :: fmtarg
44 character(len=20) :: accarg
45 character(len=20) :: filstat
46 character(len=20) :: filact
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,/)"
59 if (
present(mode_opt))
then
68 write (iout, fmtmsg2) trim(fname)
78 if (
present(fmtarg_opt))
then
82 if (
present(accarg_opt))
then
86 if (
present(filstat_opt))
then
90 if (filstat ==
'OLD')
then
97 iflen = len_trim(fname)
105 inquire (file=fname(1:iflen), number=iuop)
109 open (unit=iu, file=fname(1:iflen), form=fmtarg, access=accarg, &
110 status=filstat,
action=filact, iostat=ivar)
115 write (
errmsg,
'(3a,1x,i0,a)') &
116 'Could not open "', fname(1:iflen),
'" on unit', iu,
'.'
118 write (
errmsg,
'(a,1x,a,1x,i0,a)') &
119 trim(
errmsg),
'File already open on unit', iuop,
'.'
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().'
138 write (iout, fmtmsg) fname(1:iflen), ftype, iu, filstat, fmtarg, &
152 integer(I4B),
intent(inout) :: iu
158 inquire (unit=i, opened=opened)
159 if (.not. opened)
exit
175 integer(I4B) :: iunit
189 integer(I4B),
intent(inout) :: iounit
190 integer(I4B),
intent(in) :: errunit
191 character(len=*),
intent(in) :: description
193 write (
errmsg,
'(a,1x,i0)') &
194 trim(description)//
' already assigned at unit: ', iounit
208 character(len=*),
intent(inout) :: word
211 integer(I4B) :: idiff
216 idiff = ichar(
'a') - ichar(
'A')
220 IF (word(k:k) >=
'a' .and. word(k:k) <=
'z') &
221 word(k:k) = char(ichar(word(k:k)) - idiff)
232 character(len=*) :: word
234 integer(I4B) :: idiff, k, l
238 idiff = ichar(
'a') - ichar(
'A')
242 if (word(k:k) >=
'A' .and. word(k:k) <=
'Z')
then
243 word(k:k) = char(ichar(word(k:k)) + idiff)
256 character(len=LINELENGTH),
intent(inout) :: name
257 integer(I4B),
intent(in) :: proc_id
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
267 ipos0 = index(name_local,
".", back=.true.)
268 ipos1 = len_trim(name)
270 write (extension_local,
'(a)') name(ipos0:ipos1)
275 write (name_processor,
'(a,a,i0,a)') &
276 name(1:ipos0 - 1),
'.p', proc_id, trim(adjustl(extension_local))
277 name = name_processor
286 subroutine uwword(line, icol, ilen, ncode, c, n, r, fmt, alignment, sep)
289 character(len=*),
intent(inout) :: line
290 integer(I4B),
intent(inout) :: icol
291 integer(I4B),
intent(in) :: ilen
292 integer(I4B),
intent(in) :: ncode
293 character(len=*),
intent(in) :: c
294 integer(I4B),
intent(in) :: n
295 real(dp),
intent(in) :: r
296 character(len=*),
optional,
intent(in) :: fmt
297 integer(I4B),
optional,
intent(in) :: alignment
298 character(len=*),
optional,
intent(in) :: sep
300 character(len=16) :: cfmt
301 character(len=16) :: cffmt
302 character(len=ILEN) :: cval
303 integer(I4B) :: ialign
305 integer(I4B) :: ispace
306 integer(I4B) :: istop
308 integer(I4B) :: ireal
315 if (
present(fmt))
then
320 write (cfmt,
'(a,I0,a)')
'(a', ilen,
')'
322 write (cfmt,
'(a,I0,a)')
'(I', ilen,
')'
326 write (cfmt,
'(a,I0,a,I0,a)')
'(1PG', ilen,
'.', i,
')'
332 write (cffmt,
'(a,I0,a)')
'(a', ilen,
')'
334 if (
present(alignment))
then
347 else if (ncode ==
tabreal)
then
352 if (len_trim(adjustl(cval)) > ilen)
then
355 cval = trim(adjustl(cval))
359 ispace = (ilen - i) / 2
362 cval =
' '//trim(adjustl(cval))
364 cval = trim(adjustl(cval))
367 cval = repeat(
' ', ispace)//trim(cval)
369 else if (ialign ==
tableft)
then
370 cval = trim(adjustl(cval))
372 cval =
' '//trim(adjustl(cval))
382 istop = icol + ilen - 1
385 write (line(icol:istop), cffmt) cval
389 if (
present(sep))
then
392 write (line(icol:istop),
'(a)') sep
424 subroutine urword(line, icol, istart, istop, ncode, n, r, iout, in)
426 character(len=*) :: line
427 integer(I4B),
intent(inout) :: icol
428 integer(I4B),
intent(inout) :: istart
429 integer(I4B),
intent(inout) :: istop
430 integer(I4B),
intent(in) :: ncode
431 integer(I4B),
intent(inout) :: n
432 real(dp),
intent(inout) :: r
433 integer(I4B),
intent(in) :: iout
434 integer(I4B),
intent(in) :: in
436 character(len=20) string
438 character(len=1) charend
439 character(len=200) :: msg
440 character(len=linelength) :: msg_line
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:')"
459 line(linlen:linlen) =
' '
463 if (icol < 1 .or. icol > linlen)
go to 100
468 if (line(i:i) /=
' ' .and. line(i:i) /=
',' .and. &
469 line(i:i) /= tab)
go to 20
477 20
if (line(i:i) == char(34) .or. line(i:i) == char(39))
then
478 if (line(i:i) == char(34))
then
484 if (i <= linlen)
then
486 if (line(j:j) == charend)
go to 40
493 if (line(j:j) ==
' ' .or. line(j:j) ==
',' .or. &
494 line(j:j) == tab)
go to 40
512 idiff = ichar(
'a') - ichar(
'A')
514 if (line(k:k) >=
'a' .and. line(k:k) <=
'z') &
515 line(k:k) = char(ichar(line(k:k)) - idiff)
521 100
if (ncode == 2 .or. ncode == 3)
then
522 l = istop - istart + 1
524 if (istart > linlen)
then
527 if (ncode == 2) n = 0
528 if (ncode == 3) r =
dzero
530 if (ncode == 2)
read (line(istart:istop), *, err=200) n
531 if (ncode == 3)
read (line(istart:istop), *, err=200) r
537 200
if (ncode == 3)
then
538 string =
'a real number'
541 string =
'an integer'
549 line(linlen + 1:linlen + 1) =
'E'
553 else if (iout > 0)
then
555 write (msg_line, fmtmsgout1) in, line(istart:istop), string(1:l)
557 write (msg_line, fmtmsgout2) line(istart:istop), string(1:l)
565 write (msg_line, fmtmsgout1) in, line(istart:istop), string(1:l)
567 write (msg_line, fmtmsgout2) line(istart:istop), string(1:l)
576 write (msg, fmtmsgout3) in, line(istart:istop), trim(string)
578 write (msg, fmtmsgout4) line(istart:istop), trim(string)
588 subroutine ulstlb(iout, label, caux, ncaux, naux)
590 character(len=*) :: label
591 character(len=16) :: caux(ncaux)
593 character(len=400) buf
595 character(len=1) dash(400)
598 character(len=*),
parameter :: fmtmsgout1 =
"(1x, a)"
599 character(len=*),
parameter :: fmtmsgout2 =
"(1x, 400a)"
605 nbuf = len(label) + 9
610 buf(n1:nbuf) = caux(i)
615 write (iout, fmtmsgout1) buf(1:nbuf)
618 write (iout, fmtmsgout2) (dash(j), j=1, nbuf)
626 subroutine ubdsv4(kstp, kper, text, naux, auxtxt, ibdchn, &
627 & ncol, nrow, nlay, nlist, iout, delt, pertim, totim)
629 character(len=16) :: text
630 character(len=16),
dimension(:) :: auxtxt
631 real(dp),
intent(in) :: delt, pertim, totim
633 character(len=*),
parameter :: fmt = &
634 &
"(1X,'UBDSV4 SAVING ',A16,' ON UNIT',I7,' AT TIME STEP',I7,"// &
635 &
"', STRESS PERIOD',I7)"
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)
649 subroutine ubdsvb(ibdchn, icrl, q, val, nvl, naux, laux)
651 real(dp),
dimension(nvl) :: val
657 write (ibdchn) icrl, q, (val(n), n=laux, n2)
659 write (ibdchn) icrl, q
672 subroutine ucolno(nlbl1, nlbl2, nspace, ncpl, ndig, iout)
674 character(len=1) :: dot, space, dg, bf
675 dimension :: bf(1000), dg(10)
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/
'.',
' '/
681 character(len=*),
parameter :: fmtmsgout1 =
"(1x)"
682 character(len=*),
parameter :: fmtmsgout2 =
"(1x, 1000a1)"
686 if (iout <= 0)
return
687 write (iout, fmtmsgout1)
689 nlbl = nlbl2 - nlbl1 + 1
692 if (nlbl < ncpl) n = ncpl
693 ntot = nspace + n * ndig
695 if (ntot > 1000)
go to 50
696 nwrap = (nlbl - 1) / ncpl + 1
712 if (j2 > nlbl2) j2 = nlbl2
720 if (i2 == 0)
go to 30
722 i2 = i2 - i3 * 10 + 1
724 if (i3 == 0)
go to 30
726 i3 = i3 - i4 * 10 + 1
728 if (i4 == 0)
go to 30
733 bf(nbf - 3) = dg(i4 + 1)
738 write (iout, fmtmsgout2) (bf(i), i=1, nbf)
744 if (ntot > 1000) ntot = 1000
745 write (iout, fmtmsgout2) (dot, i=1, ntot)
750 subroutine ulaprw(buf, text, kstp, kper, ncol, nrow, ilay, iprn, iout)
752 character(len=16) :: text
753 real(dp),
dimension(ncol, nrow) :: buf
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)))"
804 if (iout <= 0)
return
807 write (iout, fmtmsgout1) text, ilay, kstp, kper
808 else if (ilay < 0)
then
809 write (iout, fmtmsgout2) text, kstp, kper
814 if (ip < 1 .or. ip > 21) ip = 12
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)
833 write (iout, fmtg10) i, (buf(j, i), j=1, ncol)
837 write (iout, fmtg13) i, (buf(j, i), j=1, ncol)
841 write (iout, fmtf7pt1) i, (buf(j, i), j=1, ncol)
845 write (iout, fmtf7pt2) i, (buf(j, i), j=1, ncol)
849 write (iout, fmtf7pt3) i, (buf(j, i), j=1, ncol)
853 write (iout, fmtf7pt4) i, (buf(j, i), j=1, ncol)
857 write (iout, fmtf5pt0) i, (buf(j, i), j=1, ncol)
861 write (iout, fmtf5pt1) i, (buf(j, i), j=1, ncol)
865 write (iout, fmtf5pt2) i, (buf(j, i), j=1, ncol)
869 write (iout, fmtf5pt3) i, (buf(j, i), j=1, ncol)
873 write (iout, fmtf5pt4) i, (buf(j, i), j=1, ncol)
877 write (iout, fmtg11) i, (buf(j, i), j=1, ncol)
881 write (iout, fmtf6pt0) i, (buf(j, i), j=1, ncol)
885 write (iout, fmtf6pt1) i, (buf(j, i), j=1, ncol)
889 write (iout, fmtf6pt2) i, (buf(j, i), j=1, ncol)
893 write (iout, fmtf6pt3) i, (buf(j, i), j=1, ncol)
897 write (iout, fmtf6pt4) i, (buf(j, i), j=1, ncol)
901 write (iout, fmtf6pt5) i, (buf(j, i), j=1, ncol)
905 write (iout, fmtg12) i, (buf(j, i), j=1, ncol)
909 write (iout, fmtg11pt4) i, (buf(j, i), j=1, ncol)
913 write (iout, fmtg9pt2) i, (buf(j, i), j=1, ncol)
924 subroutine ulasav(buf, text, kstp, kper, pertim, totim, ncol, nrow, &
927 character(len=16) :: text
928 real(dp),
dimension(ncol, nrow) :: buf
929 real(dp) :: pertim, totim
932 write (ichn) kstp, kper, pertim, totim, text, ncol, nrow, ilay
936 write (ichn) ((buf(ic, ir), ic=1, ncol), ir=1, nrow)
945 subroutine ubdsv1(kstp, kper, text, ibdchn, buff, ncol, nrow, nlay, iout, &
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
962 character(len=*),
parameter :: fmt = &
963 &
"(1X,'UBDSV1 SAVING ',A16,' ON UNIT',I7,' AT TIME STEP',I7,"// &
964 &
"', STRESS PERIOD',I7)"
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
981 subroutine ubdsv06(kstp, kper, text, modelnam1, paknam1, modelnam2, paknam2, &
982 ibdchn, naux, auxtxt, ncol, nrow, nlay, nlist, iout, &
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
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)"
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
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
1043 write (ibdchn) n, q, (aux(nn), nn=1, naux)
1053 subroutine ubdsvd(ibdchn, n, n2, q, naux, aux)
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
1067 write (ibdchn) n, n2, q, (aux(nn), nn=1, naux)
1069 write (ibdchn) n, n2, q
1078 character(len=*),
intent(in) :: word1, word2
1080 character(len=200) :: upword1, upword2
1093 character(len=*),
intent(in) :: str
1094 integer,
intent(in) :: width
1096 character(len=max(len_trim(str), width)) :: res
1106 character(len=LINELENGTH) :: line
1107 character(len=100) :: fname, ac, act, fm, frm, seq, unf
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)"
1115 inquire (unit=iu, name=fname, access=ac, action=act, formatted=fm, &
1116 sequential=seq, unformatted=unf, form=frm)
1119 write (line, fmta) iu, trim(fname), trim(ac), trim(act)
1121 write (line, fmtb) trim(fm), trim(seq), trim(unf), trim(frm)
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
1142 integer(I4B) :: i, idum, istart, istop, linelen, lloc
1146 if (
allocated(words))
then
1153 allocate (words(nwords))
1158 call urword(line, lloc, istart, istop, 0, idum, rdum, 0, 0)
1159 words(i) = line(istart:istop)
1165 subroutine ulaprufw(ncol, nrow, kstp, kper, ilay, iout, buf, text, userfmt, &
1166 nvalues, nwidth, editdesc)
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
1176 integer(I4B) :: i, j, nspaces
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('-'))"
1185 if (iout <= 0)
return
1188 write (iout, fmtmsgout1) trim(text), ilay, kstp, kper
1189 else if (ilay < 0)
then
1190 write (iout, fmtmsgout2) trim(text), kstp, kper
1195 if (editdesc ==
'F') nspaces = 3
1196 call ucolno(1, ncol, nspaces, nvalues, nwidth + 1, iout)
1200 write (iout, userfmt) i, (buf(j, i), j=1, ncol)
1223 integer(I4B),
intent(in) :: iu
1224 logical,
intent(out) :: eof
1225 character(len=:),
allocatable :: astring
1227 integer(I4B) :: isize, istat
1228 character(len=256) :: buffer
1229 character(len=1000) :: ermsg, fname
1230 character(len=7) :: fmtd
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.')"
1245 read (iu,
'(a)', advance=
'NO', iostat=istat, size=isize,
end=99) buffer
1249 ermsg =
'Programming error in call to read_line: '// &
1250 'Attempt to read from unit number <= 0'
1252 inquire (unit=iu, opened=lop, name=fname, formatted=fmtd)
1254 write (ermsg, fmterrmsg1) iu
1255 elseif (fmtd ==
'NO' .or. fmtd ==
'UNKNOWN')
then
1256 write (ermsg, fmterrmsg2) trim(fname)
1258 write (ermsg, fmterrmsg3) trim(fname), iu
1264 astring = astring//buffer(:isize)
1281 character(len=*),
intent(in) :: pathname
1282 character(len=*),
intent(out) :: filename
1284 integer(I4B) :: i, istart, istop, lenpath
1285 character(len=1) :: fs =
'/'
1286 character(len=1) :: bs =
'\'
1289 lenpath = len_trim(pathname)
1292 loop:
do i = lenpath, 1, -1
1293 if (pathname(i:i) == fs .or. pathname(i:i) == bs)
then
1294 if (i == istop)
then
1302 if (istop >= istart)
then
1303 filename = pathname(istart:istop)
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
1322 integer(I4B) :: istat, ndum, ncode = 0
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
1331 idnum = namedboundflag
1332 bndname = line(istart:istop)
1339 subroutine urdaux(naux, inunit, iout, lloc, istart, istop, auxname, line, text)
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
1356 integer(I4B) :: n, linelen
1357 integer(I4B) :: iauxlen
1362 write (errmsg,
'(a)')
'Auxiliary variables already specified. '// &
1363 &
'Auxiliary variables must be specified on one line in the '// &
1365 call store_error(errmsg)
1366 call store_error_unit(inunit)
1369 call urword(line, lloc, istart, istop, 1, n, rval, iout, inunit)
1370 if (istart >= linelen)
exit auxloop
1371 iauxlen = istop - istart + 1
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&
1378 call store_error(errmsg)
1379 call store_error_unit(inunit)
1383 auxname(naux) = line(istart:istop)
1385 write (iout,
"(4X,'AUXILIARY ',a,' VARIABLE: ',A)") &
1386 trim(adjustl(text)), auxname(naux)
1409 subroutine print_format(linein, cdatafmp, editdesc, nvaluesp, nwidthp, inunit)
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
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
1427 call parseline(line, nwords, words, inunit)
1431 if (editdesc ==
'I') isint = .true.
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 &
1439 call store_error(trim(ermsg))
1440 call store_error_unit(inunit)
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
1449 read (words(2), *, iostat=ierr) nvaluesp
1452 read (words(4), *, iostat=ierr) nwidthp
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)
1467 if (.not. isint)
then
1469 if (nwords >= 5)
then
1470 if (.not.
same_word(words(5),
'DIGITS')) ierr = 1
1472 read (words(6), *, iostat=ierr) ndigits
1483 if (i <= nwords)
then
1485 select case (words(i))
1486 case (
'EXPONENTIAL')
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)
1510 call store_error(ermsg)
1511 call store_error(line)
1512 call store_error_unit(inunit)
1516 select case (editdesc)
1521 case (
'E',
'G',
'S')
1531 integer(I4B),
intent(in) :: nvalsp, nwidp, ndig
1532 character(len=*),
intent(inout) :: outfmt
1533 logical,
intent(in),
optional :: prowcolnum
1535 character(len=8) :: cvalues, cwidth, cdigits
1536 character(len=60) :: ufmt
1537 logical :: prowcolnumlocal
1539 character(len=*),
parameter :: fmtndig =
"(i8)"
1541 if (
present(prowcolnum))
then
1542 prowcolnumlocal = prowcolnum
1544 prowcolnumlocal = .true.
1548 write (cdigits, fmtndig) ndig
1549 cdigits = adjustl(cdigits)
1552 write (cvalues, fmtndig) nvalsp
1553 cvalues = adjustl(cvalues)
1554 write (cwidth, fmtndig) nwidp
1555 cwidth = adjustl(cwidth)
1556 if (prowcolnumlocal)
then
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)//
')))'
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
1587 character(len=8) :: cvalues, cwidth, cdigits
1588 character(len=60) :: ufmt
1589 logical :: prowcolnumlocal
1591 character(len=*),
parameter :: fmtndig =
"(i8)"
1593 if (
present(prowcolnum))
then
1594 prowcolnumlocal = prowcolnum
1596 prowcolnumlocal = .true.
1600 write (cdigits, fmtndig) ndig
1601 cdigits = adjustl(cdigits)
1603 write (cwidth, fmtndig) nwidp
1604 cwidth = adjustl(cwidth)
1606 write (cvalues, fmtndig) (nvalsp - 1)
1607 cvalues = adjustl(cvalues)
1608 if (prowcolnumlocal)
then
1609 ufmt =
'(1x,i3,2x,1p,'//editdesc
1611 ufmt =
'(6x,1p,'//editdesc
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)//
')'
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)//
')))'
1645 integer(I4B),
intent(in) :: nvalsp, nwidp
1646 character(len=*),
intent(inout) :: outfmt
1647 logical,
intent(in),
optional :: prowcolnum
1649 character(len=8) :: cvalues, cwidth
1650 character(len=60) :: ufmt
1651 logical :: prowcolnumlocal
1653 character(len=*),
parameter :: fmtndig =
"(i8)"
1655 if (
present(prowcolnum))
then
1656 prowcolnumlocal = prowcolnum
1658 prowcolnumlocal = .true.
1662 write (cvalues, fmtndig) nvalsp
1663 cvalues = adjustl(cvalues)
1664 write (cwidth, fmtndig) nwidp
1665 cwidth = adjustl(cwidth)
1666 if (prowcolnumlocal)
then
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)//
')))'
1688 character(len=*),
intent(in) :: line
1690 integer(I4B) :: linelen
1691 integer(I4B) :: lloc
1692 integer(I4B) :: istart
1693 integer(I4B) :: istop
1694 integer(I4B) :: idum
1704 call urword(line, lloc, istart, istop, 0, idum, rdum, 0, 0)
1705 if (istart == linelen)
exit
1718 integer(I4B),
intent(in) :: iu
1719 integer(I4B),
intent(in) :: offset
1720 integer(I4B),
intent(in) :: whence
1721 integer(I4B),
intent(inout) :: status
1723 integer(I8B) :: ipos
1725 inquire (unit=iu, size=ipos)
1727 select case (whence)
1735 inquire (unit=iu, pos=ipos)
1736 ipos = ipos + offset
1740 inquire (unit=iu, size=ipos)
1741 ipos = ipos + offset
1745 write (iu, pos=ipos, iostat=status)
1746 inquire (unit=iu, pos=ipos)
1756 use,
intrinsic :: iso_fortran_env, only: iostat_end
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
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
1774 if (ierr == iostat_end)
then
1779 elseif (ierr /= 0)
then
1782 write (errmsg, *)
'u9rdcom: Could not read from unit: ', iin
1783 call store_error(errmsg, terminate=.true.)
1785 if (len_trim(line) < 1)
then
1796 allocate (
character(len=lsize) :: linetemp)
1798 if (line(j:j) /=
' ' .and. line(j:j) /=
',' .and. &
1799 line(j:j) /= char(9))
then
1805 linetemp(:) = line(istart:)
1806 line(:) = linetemp(:)
1807 deallocate (linetemp)
1811 select case (line(1:1))
1822 if (line(1:2) == comment) iscomment = .true.
1823 if (len_trim(line) < 1) iscomment = .true.
1828 if (.not. iscomment)
then
1835 if (line(i:i) /=
' ')
then
1840 write (iout,
'(1x,a)') line(1:i)
1854 integer(I4B),
intent(in) :: lun
1855 character(len=:),
intent(out),
allocatable :: line
1856 integer(I4B),
intent(out) :: iostat
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)
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(:)
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) =
' '
1885 else if (iostat == 0)
then
1886 linesize = len(line)
1887 deallocate (linetemp)
1888 allocate (
character(len=linesize) :: linetemp)
1889 linetemp(:) = line(:)
1891 allocate (
character(len=linesize + size_read) :: line)
1892 line(:) = linetemp(:)
1893 line(linesize + 1:) = buffer(:size_read)
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.'
1907 if (line(i:i) .eq. lf)
then
1908 write (errmsg,
'(a)') &
1909 'get_line: Found an isolated Line Feed.'
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.)
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
@ tabcenter
centered table column
@ tabright
right justified table column
@ tableft
left justified table column
@ tabucstring
upper case string table data
@ tabstring
string table data
@ tabinteger
integer table data
integer(i4b), parameter iulast
maximum file unit number (this allows for 9000 open files)
integer(i4b), parameter namedboundflag
named bound flag
integer(i4b), parameter iustart
starting file unit number
integer(i4b), parameter lenbigline
maximum length of a big line
integer(i4b), parameter lenauxname
maximum length of a aux variable
integer(i4b), parameter lenboundname
maximum length of a bound name
real(dp), parameter dzero
real constant zero
integer(i4b), parameter maxcharlen
maximum length of char string
This module defines variable data types.
Store and issue logging messages to output units.
subroutine, public write_message(text, iunit, fmt, skipbefore, skipafter, advance)
Write a message to an output unit.
character(len=20), dimension(2) action
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
integer(i4b) iunext
next file unit number to assign
integer(i4b) isim_mode
simulation mode