22 character(len=LENPACKAGENAME) :: text =
''
23 logical,
pointer :: flows_from_file => null()
24 type(
listtype),
pointer :: gwfbndlist => null()
25 integer(I4B),
pointer :: iflowsupdated => null()
26 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound => null()
27 real(dp),
dimension(:),
pointer,
contiguous :: gwfflowja => null()
28 real(dp),
dimension(:, :),
pointer,
contiguous :: gwfspdis => null()
29 real(dp),
dimension(:),
pointer,
contiguous :: gwfhead => null()
30 real(dp),
dimension(:),
pointer,
contiguous :: gwfsat => null()
31 integer(I4B),
dimension(:),
pointer,
contiguous :: ibdgwfsat0 => null()
32 integer(I4B),
pointer :: idryinactive => null()
33 real(dp),
dimension(:),
pointer,
contiguous :: gwfstrgss => null()
34 real(dp),
dimension(:),
pointer,
contiguous :: gwfstrgsy => null()
35 integer(I4B),
pointer :: igwfstrgss => null()
36 integer(I4B),
pointer :: igwfstrgsy => null()
37 integer(I4B),
pointer :: iubud => null()
38 integer(I4B),
pointer :: iuhds => null()
39 integer(I4B),
pointer :: iumvr => null()
40 integer(I4B),
pointer :: nflowpack => null()
41 integer(I4B),
dimension(:),
pointer,
contiguous :: igwfmvrterm => null()
46 character(len=16),
dimension(:),
allocatable :: flowpacknamearray
47 character(len=LENVARNAME) :: depvartype =
''
76 subroutine fmi_df(this, dis, idryinactive)
82 integer(I4B),
intent(in) :: idryinactive
84 character(len=*),
parameter :: fmtfmi = &
85 "(1x,/1x,'FMI -- FLOW MODEL INTERFACE, VERSION 2, 8/17/2023', &
86 &' INPUT READ FROM UNIT ', i0, //)"
87 character(len=*),
parameter :: fmtfmi0 = &
88 "(1x,/1x,'FMI -- FLOW MODEL INTERFACE,'&
89 &' VERSION 2, 8/17/2023')"
92 if (this%iout > 0)
then
93 if (this%inunit /= 0)
then
94 write (this%iout, fmtfmi) this%inunit
96 write (this%iout, fmtfmi0)
97 if (this%flows_from_file)
then
98 write (this%iout,
'(a)')
' FLOWS ARE ASSUMED TO BE ZERO.'
100 write (this%iout,
'(a)')
' FLOWS PROVIDED BY A GWF MODEL IN THIS &
110 if (this%inunit /= 0)
then
111 call this%read_options()
115 if (this%inunit /= 0 .and. this%flows_from_file)
then
116 call this%read_packagedata()
117 call this%initialize_gwfterms_from_bfr()
121 if (.not. this%flows_from_file)
then
122 call this%initialize_gwfterms_from_gwfbndlist()
128 this%idryinactive = idryinactive
138 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound
141 this%ibound => ibound
144 call this%allocate_arrays(this%dis%nodes)
157 call this%deallocate_gwfpackages()
160 deallocate (this%gwfpackages)
161 deallocate (this%flowpacknamearray)
165 if (this%flows_from_file)
then
188 call this%NumericalPackageType%da()
201 call this%NumericalPackageType%allocate_scalars()
204 call mem_allocate(this%flows_from_file,
'FLOWS_FROM_FILE', this%memoryPath)
205 call mem_allocate(this%iflowsupdated,
'IFLOWSUPDATED', this%memoryPath)
206 call mem_allocate(this%igwfstrgss,
'IGWFSTRGSS', this%memoryPath)
207 call mem_allocate(this%igwfstrgsy,
'IGWFSTRGSY', this%memoryPath)
211 call mem_allocate(this%nflowpack,
'NFLOWPACK', this%memoryPath)
212 call mem_allocate(this%idryinactive,
"IDRYINACTIVE", this%memoryPath)
216 this%flows_from_file = .true.
217 this%iflowsupdated = 1
224 this%idryinactive = 1
235 integer(I4B),
intent(in) :: nodes
241 call mem_allocate(this%ibdgwfsat0, nodes,
'IBDGWFSAT0', this%memoryPath)
243 this%ibdgwfsat0(n) = 1
248 if (this%flows_from_file)
then
250 'GWFFLOWJA', this%memoryPath)
251 call mem_allocate(this%gwfsat, nodes,
'GWFSAT', this%memoryPath)
252 call mem_allocate(this%gwfhead, nodes,
'GWFHEAD', this%memoryPath)
253 call mem_allocate(this%gwfspdis, 3, nodes,
'GWFSPDIS', this%memoryPath)
255 this%gwfsat(n) = done
256 this%gwfhead(n) =
dzero
257 this%gwfspdis(:, n) =
dzero
259 do n = 1,
size(this%gwfflowja)
260 this%gwfflowja(n) =
dzero
264 if (this%igwfstrgss == 0)
then
265 call mem_allocate(this%gwfstrgss, 1,
'GWFSTRGSS', this%memoryPath)
267 call mem_allocate(this%gwfstrgss, nodes,
'GWFSTRGSS', this%memoryPath)
269 if (this%igwfstrgsy == 0)
then
270 call mem_allocate(this%gwfstrgsy, 1,
'GWFSTRGSY', this%memoryPath)
272 call mem_allocate(this%gwfstrgsy, nodes,
'GWFSTRGSY', this%memoryPath)
274 do n = 1,
size(this%gwfstrgss)
275 this%gwfstrgss(n) =
dzero
277 do n = 1,
size(this%gwfstrgsy)
278 this%gwfstrgsy(n) =
dzero
283 if (this%inunit == 0)
call this%allocate_gwfpackages(this%nflowpack)
297 character(len=LINELENGTH) :: keyword
299 logical :: isfound, endOfBlock
302 call this%parser%GetBlock(
'OPTIONS', isfound, ierr, blockrequired=.false., &
303 supportopenclose=.true.)
307 write (this%iout,
'(1x,a)')
'PROCESSING FMI OPTIONS'
309 call this%parser%GetNextLine(endofblock)
311 call this%parser%GetStringCaps(keyword)
312 select case (keyword)
316 write (
errmsg,
'(a,3(1x,a))') &
317 'UNKNOWN', trim(adjustl(this%text)),
'OPTION:', trim(keyword)
319 call this%parser%StoreErrorUnit()
322 write (this%iout,
'(1x,a)')
'END OF FMI OPTIONS'
337 character(len=LINELENGTH) :: keyword, fname
339 integer(I4B) :: inunit
341 logical :: isfound, endOfBlock
342 logical :: blockrequired
347 blockrequired = .true.
350 call this%parser%GetBlock(
'PACKAGEDATA', isfound, ierr, &
351 blockrequired=blockrequired, &
352 supportopenclose=.true.)
356 write (this%iout,
'(1x,a)')
'PROCESSING FMI PACKAGEDATA'
358 call this%parser%GetNextLine(endofblock)
360 call this%parser%GetStringCaps(keyword)
361 select case (keyword)
363 call this%parser%GetStringCaps(keyword)
364 if (keyword /=
'FILEIN')
then
365 call store_error(
'GWFBUDGET KEYWORD MUST BE FOLLOWED BY '// &
366 '"FILEIN" then by filename.')
367 call this%parser%StoreErrorUnit()
369 call this%parser%GetString(fname)
371 inquire (file=trim(fname), exist=exist)
372 if (.not. exist)
then
373 call store_error(
'Could not find file '//trim(fname))
374 call this%parser%StoreErrorUnit()
376 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
379 call this%initialize_bfr()
381 call this%parser%GetStringCaps(keyword)
382 if (keyword /=
'FILEIN')
then
383 call store_error(
'GWFHEAD KEYWORD MUST BE FOLLOWED BY '// &
384 '"FILEIN" then by filename.')
385 call this%parser%StoreErrorUnit()
387 call this%parser%GetString(fname)
388 inquire (file=trim(fname), exist=exist)
389 if (.not. exist)
then
390 call store_error(
'Could not find file '//trim(fname))
391 call this%parser%StoreErrorUnit()
394 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
397 call this%initialize_hfr()
399 call this%parser%GetStringCaps(keyword)
400 if (keyword /=
'FILEIN')
then
401 call store_error(
'GWFMOVER KEYWORD MUST BE FOLLOWED BY '// &
402 '"FILEIN" then by filename.')
403 call this%parser%StoreErrorUnit()
405 call this%parser%GetString(fname)
407 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
412 call this%mvrbudobj%fill_from_bfr(this%dis, this%iout)
414 write (
errmsg,
'(a,3(1x,a))') &
415 'UNKNOWN', trim(adjustl(this%text)),
'PACKAGEDATA:', trim(keyword)
419 write (this%iout,
'(1x,a)')
'END OF FMI PACKAGEDATA'
429 integer(I4B) :: ncrbud
432 call this%bfr%initialize(this%iubud, this%iout, ncrbud)
453 integer(I4B) :: nu, nr
454 integer(I4B) :: ip, i
457 character(len=*),
parameter :: fmtkstpkper = &
458 "(1x,/1x,'FMI READING BUDGET TERMS &
459 &FOR KSTP ', i0, ' KPER ', i0)"
460 character(len=*),
parameter :: fmtbudkstpkper = &
461 "(1x,/1x, 'FMI SETTING BUDGET TERMS &
462 &FOR KSTP ', i0, ' AND KPER ', &
463 &i0, ' TO BUDGET FILE TERMS FROM &
464 &KSTP ', i0, ' AND KPER ', i0)"
472 if (this%bfr%kstp == 1)
then
473 if (this%bfr%kpernext ==
kper + 1)
then
475 else if (this%bfr%endoffile)
then
478 else if (this%bfr%endoffile)
then
479 write (
errmsg,
'(4x,a)')
'REACHED END OF GWF BUDGET &
480 &FILE BEFORE READING SUFFICIENT BUDGET INFORMATION FOR THIS &
491 write (this%iout, fmtkstpkper)
kstp,
kper
496 do n = 1, this%bfr%nbudterms
497 call this%bfr%read_record(success, this%iout)
498 if (.not. success)
then
499 write (
errmsg,
'(4x,a)')
'GWF BUDGET READ NOT SUCCESSFUL'
505 if (
kper /= this%bfr%kper)
then
506 write (
errmsg,
'(4x,a)')
'PERIOD NUMBER IN BUDGET FILE &
507 &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
508 &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN &
509 &STRESS PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL &
510 &TIME STEPS ONE-FOR-ONE IN THAT STRESS PERIOD.'
516 if (this%bfr%kstp > 1 .and. (
kstp /= this%bfr%kstp))
then
517 write (
errmsg,
'(4x,a)')
'TIME STEP NUMBER IN BUDGET FILE &
518 &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
519 &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN STRESS &
520 &PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
521 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
528 select case (trim(adjustl(this%bfr%budtxt)))
529 case (
'FLOW-JA-FACE')
533 do ipos = 1,
size(this%bfr%flowja)
534 this%gwfflowja(ipos) = this%bfr%flowja(ipos)
537 do i = 1, this%bfr%nlist
538 nu = this%bfr%nodesrc(i)
539 nr = this%dis%get_nodenumber(nu, 0)
541 this%gwfspdis(1, nr) = this%bfr%auxvar(1, i)
542 this%gwfspdis(2, nr) = this%bfr%auxvar(2, i)
543 this%gwfspdis(3, nr) = this%bfr%auxvar(3, i)
546 do i = 1, this%bfr%nlist
547 nu = this%bfr%nodesrc(i)
548 nr = this%dis%get_nodenumber(nu, 0)
550 this%gwfsat(nr) = this%bfr%auxvar(1, i)
553 do nu = 1, this%dis%nodesuser
554 nr = this%dis%get_nodenumber(nu, 0)
556 this%gwfstrgss(nr) = this%bfr%flow(nu)
559 do nu = 1, this%dis%nodesuser
560 nr = this%dis%get_nodenumber(nu, 0)
562 this%gwfstrgsy(nr) = this%bfr%flow(nu)
565 call this%gwfpackages(ip)%copy_values( &
570 do i = 1, this%gwfpackages(ip)%nbound
571 nu = this%gwfpackages(ip)%nodelist(i)
572 nr = this%dis%get_nodenumber(nu, 0)
573 this%gwfpackages(ip)%nodelist(i) = nr
581 write (this%iout, fmtbudkstpkper)
kstp,
kper, this%bfr%kstp, this%bfr%kper
584 this%iflowsupdated = 0
596 call this%bfr%finalize()
608 call this%hfr%initialize(this%iuhds, this%iout)
620 integer(I4B) :: nu, nr, i, ilay
625 character(len=*),
parameter :: fmtkstpkper = &
626 "(1x,/1x,'FMI READING HEAD FOR &
627 &KSTP ', i0, ' KPER ', i0)"
628 character(len=*),
parameter :: fmthdskstpkper = &
629 "(1x,/1x, 'FMI SETTING HEAD FOR KSTP ', i0, ' AND KPER ', &
630 &i0, ' TO BINARY FILE HEADS FROM KSTP ', i0, ' AND KPER ', i0)"
638 if (this%hfr%kstp == 1)
then
639 if (this%hfr%kpernext ==
kper + 1)
then
641 else if (this%hfr%endoffile)
then
644 else if (this%hfr%endoffile)
then
645 write (
errmsg,
'(4x,a)')
'REACHED END OF GWF HEAD &
646 &FILE BEFORE READING SUFFICIENT HEAD INFORMATION FOR THIS &
657 write (this%iout, fmtkstpkper)
kstp,
kper
660 do ilay = 1, this%hfr%nlay
663 call this%hfr%read_record(success, this%iout)
664 if (.not. success)
then
665 write (
errmsg,
'(4x,a)')
'GWF HEAD READ NOT SUCCESSFUL'
671 if (
kper /= this%hfr%kper)
then
672 write (
errmsg,
'(4x,a)')
'PERIOD NUMBER IN HEAD FILE &
673 &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
674 &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
675 &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
676 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
682 if (this%hfr%kstp > 1 .and. (
kstp /= this%hfr%kstp))
then
683 write (
errmsg,
'(4x,a)')
'TIME STEP NUMBER IN HEAD FILE &
684 &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
685 &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
686 &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
687 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
694 ncpl =
size(this%hfr%head)
696 nu = (ilay - 1) * ncpl + i
697 nr = this%dis%get_nodenumber(nu, 0)
698 val = this%hfr%head(i)
699 if (nr > 0) this%gwfhead(nr) = val
703 write (this%iout, fmthdskstpkper)
kstp,
kper, this%hfr%kstp, this%hfr%kper
732 integer(I4B) :: nflowpack
733 integer(I4B) :: i, ip
735 logical :: found_flowja
736 logical :: found_dataspdis
737 logical :: found_datasat
738 logical :: found_stoss
739 logical :: found_stosy
740 integer(I4B),
dimension(:),
allocatable :: imap
743 allocate (imap(this%bfr%nbudterms))
746 found_flowja = .false.
747 found_dataspdis = .false.
748 found_datasat = .false.
749 found_stoss = .false.
750 found_stosy = .false.
751 do i = 1, this%bfr%nbudterms
752 select case (trim(adjustl(this%bfr%budtxtarray(i))))
753 case (
'FLOW-JA-FACE')
754 found_flowja = .true.
756 found_dataspdis = .true.
758 found_datasat = .true.
766 nflowpack = nflowpack + 1
772 call this%allocate_gwfpackages(nflowpack)
777 do i = 1, this%bfr%nbudterms
778 if (imap(i) == 0) cycle
779 call this%gwfpackages(ip)%set_name(this%bfr%dstpackagenamearray(i), &
780 this%bfr%budtxtarray(i))
781 naux = this%bfr%nauxarray(i)
782 call this%gwfpackages(ip)%set_auxname(naux, this%bfr%auxtxtarray(1:naux, i))
790 if (imap(i) == 1)
then
791 this%flowpacknamearray(ip) = this%bfr%dstpackagenamearray(i)
797 if (.not. found_dataspdis)
then
798 write (
errmsg,
'(4x,a)')
'SPECIFIC DISCHARGE NOT FOUND IN &
799 &BUDGET FILE. SAVE_SPECIFIC_DISCHARGE AND &
800 &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
803 if (.not. found_datasat)
then
804 write (
errmsg,
'(4x,a)')
'SATURATION NOT FOUND IN &
805 &BUDGET FILE. SAVE_SATURATION AND &
806 &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
809 if (.not. found_flowja)
then
810 write (
errmsg,
'(4x,a)')
'FLOWJA NOT FOUND IN &
811 &BUDGET FILE. SAVE_FLOWS MUST &
812 &BE ACTIVATED IN THE NPF PACKAGE.'
816 call this%parser%StoreErrorUnit()
828 integer(I4B) :: ngwfpack
829 integer(I4B) :: ngwfterms
831 integer(I4B) :: imover
832 integer(I4B) :: ntomvr
833 integer(I4B) :: iterm
834 character(len=LENPACKAGENAME) :: budtxt
835 class(
bndtype),
pointer :: packobj => null()
838 ngwfpack = this%gwfbndlist%Count()
846 imover = packobj%imover
847 if (packobj%isadvpak /= 0) imover = 0
848 if (imover /= 0)
then
855 ngwfterms = ngwfpack + ntomvr
856 call this%allocate_gwfpackages(ngwfterms)
864 budtxt = adjustl(packobj%text)
865 call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
866 this%flowpacknamearray(iterm) = packobj%packName
871 imover = packobj%imover
872 if (packobj%isadvpak /= 0) imover = 0
873 if (imover /= 0)
then
874 budtxt = trim(adjustl(packobj%text))//
'-TO-MVR'
875 call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
876 this%flowpacknamearray(iterm) = packobj%packName
877 this%igwfmvrterm(iterm) = 1
895 integer(I4B),
intent(in) :: ngwfterms
898 character(len=LENMEMPATH) :: memPath
901 allocate (this%gwfpackages(ngwfterms))
902 allocate (this%flowpacknamearray(ngwfterms))
905 call mem_allocate(this%igwfmvrterm, ngwfterms,
'IGWFMVRTERM', this%memoryPath)
908 this%nflowpack = ngwfterms
909 do n = 1, this%nflowpack
910 this%igwfmvrterm(n) = 0
911 this%flowpacknamearray(n) =
''
915 write (mempath,
'(a, i0)') trim(this%memoryPath)//
'-FT', n
916 call this%gwfpackages(n)%initialize(mempath)
930 do n = 1, this%nflowpack
931 call this%gwfpackages(n)%da()
940 character(len=*),
intent(in) :: name
941 integer(I4B),
intent(inout) :: idx
947 do ip = 1,
size(this%flowpacknamearray)
948 if (this%flowpacknamearray(ip) == name)
then
954 call store_error(
'Error in get_package_index. Could not find '//name, &
This module contains the base boundary package.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
subroutine, public budgetobject_cr_bfr(this, name, ibinun, iout, colconv1, colconv2)
Create a new budget object from a binary flow file.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lenpackagename
maximum length of the package name
integer(i4b), parameter lenvarname
maximum length of a variable name
real(dp), parameter dhalf
real constant 1/2
real(dp), parameter dem6
real constant 1e-6
real(dp), parameter dzero
real constant zero
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
integer(i4b), parameter lenmempath
maximum length of the memory path
real(dp), parameter done
real constant 1
subroutine allocate_scalars(this)
Allocate scalars.
subroutine fmi_ar(this, ibound)
Allocate the package.
subroutine allocate_gwfpackages(this, ngwfterms)
Allocate budget packages.
subroutine deallocate_gwfpackages(this)
Deallocate memory in the gwfpackages array.
subroutine read_options(this)
Read options from input file.
subroutine finalize_hfr(this)
Finalize the head file reader.
subroutine fmi_df(this, dis, idryinactive)
Define the flow model interface.
subroutine get_package_index(this, name, idx)
Find the package index for the package with the given name.
subroutine advance_bfr(this)
Advance the budget file reader.
subroutine initialize_gwfterms_from_gwfbndlist(this)
Initialize gwf terms from a GWF exchange.
subroutine initialize_hfr(this)
Initialize the head file reader.
subroutine fmi_da(this)
Deallocate variables.
subroutine read_packagedata(this)
Read packagedata block from input file.
subroutine advance_hfr(this)
Advance the head file reader.
subroutine initialize_gwfterms_from_bfr(this)
Initialize gwf terms from budget file.
subroutine finalize_bfr(this)
Finalize the budget file reader.
subroutine allocate_arrays(this, nodes)
Allocate arrays.
subroutine initialize_bfr(this)
Initialize the budget file reader.
This module defines variable data types.
This module contains the base numerical package type.
This module contains the PackageBudgetModule Module.
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
integer(i4b) function, public count_errors()
Return number of errors.
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), pointer, public kstp
current time step number
integer(i4b), pointer, public kper
current stress period number
A generic heterogeneous doubly-linked list.
Derived type for storing flows.