23 character(len=LENPACKAGENAME) :: text =
''
24 logical,
pointer :: flows_from_file => null()
25 type(
listtype),
pointer :: gwfbndlist => null()
26 integer(I4B),
pointer :: iflowsupdated => null()
27 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound => null()
28 real(dp),
dimension(:),
pointer,
contiguous :: gwfflowja => null()
29 real(dp),
dimension(:, :),
pointer,
contiguous :: gwfspdis => null()
30 real(dp),
dimension(:),
pointer,
contiguous :: gwfhead => null()
31 real(dp),
dimension(:),
pointer,
contiguous :: gwfsat => null()
32 integer(I4B),
dimension(:),
pointer,
contiguous :: ibdgwfsat0 => null()
33 integer(I4B),
pointer :: idryinactive => null()
34 real(dp),
dimension(:),
pointer,
contiguous :: gwfstrgss => null()
35 real(dp),
dimension(:),
pointer,
contiguous :: gwfstrgsy => null()
36 integer(I4B),
pointer :: igwfstrgss => null()
37 integer(I4B),
pointer :: igwfstrgsy => null()
38 integer(I4B),
pointer :: iubud => null()
39 integer(I4B),
pointer :: iuhds => null()
40 integer(I4B),
pointer :: iumvr => null()
41 integer(I4B),
pointer :: iugrb => null()
42 integer(I4B),
pointer :: nflowpack => null()
43 integer(I4B),
dimension(:),
pointer,
contiguous :: igwfmvrterm => null()
49 character(len=16),
dimension(:),
allocatable :: flowpacknamearray
50 character(len=LENVARNAME) :: depvartype =
''
79 subroutine fmi_df(this, dis, idryinactive)
85 integer(I4B),
intent(in) :: idryinactive
87 character(len=*),
parameter :: fmtfmi = &
88 "(1x,/1x,'FMI -- FLOW MODEL INTERFACE, VERSION 2, 8/17/2023', &
89 &' INPUT READ FROM UNIT ', i0, //)"
90 character(len=*),
parameter :: fmtfmi0 = &
91 "(1x,/1x,'FMI -- FLOW MODEL INTERFACE,'&
92 &' VERSION 2, 8/17/2023')"
95 if (this%iout > 0)
then
96 if (this%inunit /= 0)
then
97 write (this%iout, fmtfmi) this%inunit
99 write (this%iout, fmtfmi0)
100 if (this%flows_from_file)
then
101 write (this%iout,
'(a)')
' FLOWS ARE ASSUMED TO BE ZERO.'
103 write (this%iout,
'(a)')
' FLOWS PROVIDED BY A GWF MODEL IN THIS &
113 if (this%inunit /= 0)
then
114 call this%read_options()
118 if (this%inunit /= 0 .and. this%flows_from_file)
then
119 call this%read_packagedata()
120 call this%initialize_gwfterms_from_bfr()
124 if (.not. this%flows_from_file)
then
125 call this%initialize_gwfterms_from_gwfbndlist()
131 this%idryinactive = idryinactive
141 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound
144 this%ibound => ibound
147 call this%allocate_arrays(this%dis%nodes)
160 call this%deallocate_gwfpackages()
163 deallocate (this%gwfpackages)
164 deallocate (this%flowpacknamearray)
168 if (this%flows_from_file)
then
192 call this%NumericalPackageType%da()
205 call this%NumericalPackageType%allocate_scalars()
208 call mem_allocate(this%flows_from_file,
'FLOWS_FROM_FILE', this%memoryPath)
209 call mem_allocate(this%iflowsupdated,
'IFLOWSUPDATED', this%memoryPath)
210 call mem_allocate(this%igwfstrgss,
'IGWFSTRGSS', this%memoryPath)
211 call mem_allocate(this%igwfstrgsy,
'IGWFSTRGSY', this%memoryPath)
216 call mem_allocate(this%nflowpack,
'NFLOWPACK', this%memoryPath)
217 call mem_allocate(this%idryinactive,
"IDRYINACTIVE", this%memoryPath)
221 this%flows_from_file = .true.
222 this%iflowsupdated = 1
230 this%idryinactive = 1
241 integer(I4B),
intent(in) :: nodes
247 call mem_allocate(this%ibdgwfsat0, nodes,
'IBDGWFSAT0', this%memoryPath)
249 this%ibdgwfsat0(n) = 1
254 if (this%flows_from_file)
then
256 'GWFFLOWJA', this%memoryPath)
257 call mem_allocate(this%gwfsat, nodes,
'GWFSAT', this%memoryPath)
258 call mem_allocate(this%gwfhead, nodes,
'GWFHEAD', this%memoryPath)
259 call mem_allocate(this%gwfspdis, 3, nodes,
'GWFSPDIS', this%memoryPath)
261 this%gwfsat(n) = done
262 this%gwfhead(n) =
dzero
263 this%gwfspdis(:, n) =
dzero
265 do n = 1,
size(this%gwfflowja)
266 this%gwfflowja(n) =
dzero
270 if (this%igwfstrgss == 0)
then
271 call mem_allocate(this%gwfstrgss, 1,
'GWFSTRGSS', this%memoryPath)
273 call mem_allocate(this%gwfstrgss, nodes,
'GWFSTRGSS', this%memoryPath)
275 if (this%igwfstrgsy == 0)
then
276 call mem_allocate(this%gwfstrgsy, 1,
'GWFSTRGSY', this%memoryPath)
278 call mem_allocate(this%gwfstrgsy, nodes,
'GWFSTRGSY', this%memoryPath)
280 do n = 1,
size(this%gwfstrgss)
281 this%gwfstrgss(n) =
dzero
283 do n = 1,
size(this%gwfstrgsy)
284 this%gwfstrgsy(n) =
dzero
289 if (this%inunit == 0)
call this%allocate_gwfpackages(this%nflowpack)
303 character(len=LINELENGTH) :: keyword
305 logical :: isfound, endOfBlock
308 call this%parser%GetBlock(
'OPTIONS', isfound, ierr, blockrequired=.false., &
309 supportopenclose=.true.)
313 write (this%iout,
'(1x,a)')
'PROCESSING FMI OPTIONS'
315 call this%parser%GetNextLine(endofblock)
317 call this%parser%GetStringCaps(keyword)
318 select case (keyword)
322 write (
errmsg,
'(a,3(1x,a))') &
323 'UNKNOWN', trim(adjustl(this%text)),
'OPTION:', trim(keyword)
325 call this%parser%StoreErrorUnit()
328 write (this%iout,
'(1x,a)')
'END OF FMI OPTIONS'
349 character(len=LINELENGTH) :: keyword, fname
351 integer(I4B) :: inunit
353 integer(I4B) :: nodes
354 logical :: isfound, endOfBlock
355 logical :: blockrequired
357 integer(I4B),
allocatable :: idomain1d(:), idomain2d(:, :), idomain3d(:, :, :)
359 character(len=*),
parameter :: fmtdiserr = &
360 "('Models do not have the same discretization&
362 & GWF model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
363 & This model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
364 & Ensure discretization packages, including IDOMAIN, are identical.')"
365 character(len=*),
parameter :: fmtidomerr = &
366 "('Models do not have the same discretization&
368 & Models have different IDOMAIN arrays.&
369 & Ensure discretization packages, including IDOMAIN, are identical.')"
373 blockrequired = .true.
376 call this%parser%GetBlock(
'PACKAGEDATA', isfound, ierr, &
377 blockrequired=blockrequired, &
378 supportopenclose=.true.)
382 write (this%iout,
'(1x,a)')
'PROCESSING FMI PACKAGEDATA'
384 call this%parser%GetNextLine(endofblock)
386 call this%parser%GetStringCaps(keyword)
387 select case (keyword)
389 call this%parser%GetStringCaps(keyword)
390 if (keyword /=
'FILEIN')
then
391 call store_error(
'GWFBUDGET KEYWORD MUST BE FOLLOWED BY '// &
392 '"FILEIN" then by filename.')
393 call this%parser%StoreErrorUnit()
395 call this%parser%GetString(fname)
397 inquire (file=trim(fname), exist=exist)
398 if (.not. exist)
then
399 call store_error(
'Could not find file '//trim(fname))
400 call this%parser%StoreErrorUnit()
402 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
405 call this%initialize_bfr()
407 call this%parser%GetStringCaps(keyword)
408 if (keyword /=
'FILEIN')
then
409 call store_error(
'GWFHEAD KEYWORD MUST BE FOLLOWED BY '// &
410 '"FILEIN" then by filename.')
411 call this%parser%StoreErrorUnit()
413 call this%parser%GetString(fname)
414 inquire (file=trim(fname), exist=exist)
415 if (.not. exist)
then
416 call store_error(
'Could not find file '//trim(fname))
417 call this%parser%StoreErrorUnit()
420 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
423 call this%initialize_hfr()
425 call this%parser%GetStringCaps(keyword)
426 if (keyword /=
'FILEIN')
then
427 call store_error(
'GWFMOVER KEYWORD MUST BE FOLLOWED BY '// &
428 '"FILEIN" then by filename.')
429 call this%parser%StoreErrorUnit()
431 call this%parser%GetString(fname)
433 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
438 call this%mvrbudobj%fill_from_bfr(this%dis, this%iout)
440 call this%parser%GetStringCaps(keyword)
441 if (keyword /=
'FILEIN')
then
442 call store_error(
'GWFGRID KEYWORD MUST BE FOLLOWED BY '// &
443 '"FILEIN" then by filename.')
444 call this%parser%StoreErrorUnit()
446 call this%parser%GetString(fname)
448 call openfile(inunit, this%iout, fname,
'DATA(BINARY)', &
451 call this%gfr%initialize(this%iugrb)
454 select case (this%gfr%grid_type)
456 select type (dis => this%dis)
458 nodes = this%gfr%read_int(
"NCELLS")
459 if (nodes /= this%dis%nodes)
then
460 write (
errmsg, fmtdiserr) trim(this%text)
463 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
464 idomain3d = reshape(idomain1d, [ &
465 this%gfr%read_int(
"NCOL"), &
466 this%gfr%read_int(
"NROW"), &
467 this%gfr%read_int(
"NLAY") &
469 if (.not. all(dis%idomain == idomain3d))
then
470 write (
errmsg, fmtidomerr) trim(this%text)
475 select type (dis => this%dis)
477 nodes = this%gfr%read_int(
"NCELLS")
478 if (nodes /= this%dis%nodes)
then
479 write (
errmsg, fmtdiserr) trim(this%text)
482 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
483 idomain2d = reshape(idomain1d, [ &
484 this%gfr%read_int(
"NCPL"), &
485 this%gfr%read_int(
"NLAY") &
487 if (.not. all(dis%idomain == idomain2d))
then
488 write (
errmsg, fmtidomerr) trim(this%text)
493 select type (dis => this%dis)
495 nodes = this%gfr%read_int(
"NODES")
496 if (nodes /= this%dis%nodes)
then
497 write (
errmsg, fmtdiserr) trim(this%text)
500 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
501 if (.not. all(dis%idomain == idomain1d))
then
502 write (
errmsg, fmtidomerr) trim(this%text)
507 select type (dis => this%dis)
509 nodes = this%gfr%read_int(
"NCELLS")
510 if (nodes /= this%dis%nodes)
then
511 write (
errmsg, fmtdiserr) trim(this%text)
514 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
515 idomain2d = reshape(idomain1d, [ &
516 this%gfr%read_int(
"NCOL"), &
517 this%gfr%read_int(
"NROW") &
519 if (.not. all(dis%idomain == idomain2d))
then
520 write (
errmsg, fmtidomerr) trim(this%text)
525 select type (dis => this%dis)
527 nodes = this%gfr%read_int(
"NODES")
528 if (nodes /= this%dis%nodes)
then
529 write (
errmsg, fmtdiserr) trim(this%text)
532 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
533 if (.not. all(dis%idomain == idomain1d))
then
534 write (
errmsg, fmtidomerr) trim(this%text)
539 select type (dis => this%dis)
541 nodes = this%gfr%read_int(
"NCELLS")
542 if (nodes /= this%dis%nodes)
then
543 write (
errmsg, fmtdiserr) trim(this%text)
546 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
547 if (.not. all(dis%idomain == idomain1d))
then
548 write (
errmsg, fmtidomerr) trim(this%text)
554 if (
allocated(idomain3d))
deallocate (idomain3d)
555 if (
allocated(idomain2d))
deallocate (idomain2d)
556 if (
allocated(idomain1d))
deallocate (idomain1d)
558 call this%gfr%finalize()
560 write (
errmsg,
'(a,3(1x,a))') &
561 'UNKNOWN', trim(adjustl(this%text)),
'PACKAGEDATA:', trim(keyword)
565 write (this%iout,
'(1x,a)')
'END OF FMI PACKAGEDATA'
572 integer(I4B) :: ncrbud
573 call this%bfr%initialize(this%iubud, this%iout, ncrbud)
592 integer(I4B) :: nu, nr
593 integer(I4B) :: ip, i
596 character(len=*),
parameter :: fmtkstpkper = &
597 "(1x,/1x,'FMI READING BUDGET TERMS &
598 &FOR KSTP ', i0, ' KPER ', i0)"
599 character(len=*),
parameter :: fmtbudkstpkper = &
600 "(1x,/1x, 'FMI SETTING BUDGET TERMS &
601 &FOR KSTP ', i0, ' AND KPER ', &
602 &i0, ' TO BUDGET FILE TERMS FROM &
603 &KSTP ', i0, ' AND KPER ', i0)"
611 if (this%bfr%kstp == 1)
then
612 if (this%bfr%kpernext ==
kper + 1)
then
614 else if (this%bfr%endoffile)
then
617 else if (this%bfr%endoffile)
then
618 write (
errmsg,
'(4x,a)')
'REACHED END OF GWF BUDGET &
619 &FILE BEFORE READING SUFFICIENT BUDGET INFORMATION FOR THIS &
630 write (this%iout, fmtkstpkper)
kstp,
kper
635 do n = 1, this%bfr%nbudterms
636 call this%bfr%read_record(success, this%iout)
637 if (.not. success)
then
638 write (
errmsg,
'(4x,a)')
'GWF BUDGET READ NOT SUCCESSFUL'
644 if (
kper /= this%bfr%kper)
then
645 write (
errmsg,
'(4x,a)')
'PERIOD NUMBER IN BUDGET FILE &
646 &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
647 &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN &
648 &STRESS PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL &
649 &TIME STEPS ONE-FOR-ONE IN THAT STRESS PERIOD.'
655 if (this%bfr%kstp > 1 .and. (
kstp /= this%bfr%kstp))
then
656 write (
errmsg,
'(4x,a)')
'TIME STEP NUMBER IN BUDGET FILE &
657 &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
658 &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN STRESS &
659 &PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
660 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
667 select case (trim(adjustl(this%bfr%budtxt)))
668 case (
'FLOW-JA-FACE')
672 do ipos = 1,
size(this%bfr%flowja)
673 this%gwfflowja(ipos) = this%bfr%flowja(ipos)
676 do i = 1, this%bfr%nlist
677 nu = this%bfr%nodesrc(i)
678 nr = this%dis%get_nodenumber(nu, 0)
680 this%gwfspdis(1, nr) = this%bfr%auxvar(1, i)
681 this%gwfspdis(2, nr) = this%bfr%auxvar(2, i)
682 this%gwfspdis(3, nr) = this%bfr%auxvar(3, i)
685 do i = 1, this%bfr%nlist
686 nu = this%bfr%nodesrc(i)
687 nr = this%dis%get_nodenumber(nu, 0)
689 this%gwfsat(nr) = this%bfr%auxvar(1, i)
692 do nu = 1, this%dis%nodesuser
693 nr = this%dis%get_nodenumber(nu, 0)
695 this%gwfstrgss(nr) = this%bfr%flow(nu)
698 do nu = 1, this%dis%nodesuser
699 nr = this%dis%get_nodenumber(nu, 0)
701 this%gwfstrgsy(nr) = this%bfr%flow(nu)
704 call this%gwfpackages(ip)%copy_values( &
709 do i = 1, this%gwfpackages(ip)%nbound
710 nu = this%gwfpackages(ip)%nodelist(i)
711 nr = this%dis%get_nodenumber(nu, 0)
712 this%gwfpackages(ip)%nodelist(i) = nr
720 write (this%iout, fmtbudkstpkper)
kstp,
kper, this%bfr%kstp, this%bfr%kper
723 this%iflowsupdated = 0
730 call this%bfr%finalize()
736 call this%hfr%initialize(this%iuhds, this%iout)
746 integer(I4B) :: nu, nr, i, ilay
751 character(len=*),
parameter :: fmtkstpkper = &
752 "(1x,/1x,'FMI READING HEAD FOR &
753 &KSTP ', i0, ' KPER ', i0)"
754 character(len=*),
parameter :: fmthdskstpkper = &
755 "(1x,/1x, 'FMI SETTING HEAD FOR KSTP ', i0, ' AND KPER ', &
756 &i0, ' TO BINARY FILE HEADS FROM KSTP ', i0, ' AND KPER ', i0)"
764 if (this%hfr%kstp == 1)
then
765 if (this%hfr%kpernext ==
kper + 1)
then
767 else if (this%hfr%endoffile)
then
770 else if (this%hfr%endoffile)
then
771 write (
errmsg,
'(4x,a)')
'REACHED END OF GWF HEAD &
772 &FILE BEFORE READING SUFFICIENT HEAD INFORMATION FOR THIS &
783 write (this%iout, fmtkstpkper)
kstp,
kper
786 do ilay = 1, this%hfr%nlay
789 call this%hfr%read_record(success, this%iout)
790 if (.not. success)
then
791 write (
errmsg,
'(4x,a)')
'GWF HEAD READ NOT SUCCESSFUL'
797 if (
kper /= this%hfr%kper)
then
798 write (
errmsg,
'(4x,a)')
'PERIOD NUMBER IN HEAD FILE &
799 &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
800 &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
801 &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
802 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
808 if (this%hfr%kstp > 1 .and. (
kstp /= this%hfr%kstp))
then
809 write (
errmsg,
'(4x,a)')
'TIME STEP NUMBER IN HEAD FILE &
810 &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
811 &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
812 &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
813 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
820 ncpl =
size(this%hfr%head)
822 nu = (ilay - 1) * ncpl + i
823 nr = this%dis%get_nodenumber(nu, 0)
824 val = this%hfr%head(i)
825 if (nr > 0) this%gwfhead(nr) = val
829 write (this%iout, fmthdskstpkper)
kstp,
kper, this%hfr%kstp, this%hfr%kper
851 integer(I4B) :: nflowpack
852 integer(I4B) :: i, ip
854 logical :: found_flowja
855 logical :: found_dataspdis
856 logical :: found_datasat
857 logical :: found_stoss
858 logical :: found_stosy
859 integer(I4B),
dimension(:),
allocatable :: imap
862 allocate (imap(this%bfr%nbudterms))
865 found_flowja = .false.
866 found_dataspdis = .false.
867 found_datasat = .false.
868 found_stoss = .false.
869 found_stosy = .false.
870 do i = 1, this%bfr%nbudterms
871 select case (trim(adjustl(this%bfr%budtxtarray(i))))
872 case (
'FLOW-JA-FACE')
873 found_flowja = .true.
875 found_dataspdis = .true.
877 found_datasat = .true.
885 nflowpack = nflowpack + 1
891 call this%allocate_gwfpackages(nflowpack)
896 do i = 1, this%bfr%nbudterms
897 if (imap(i) == 0) cycle
898 call this%gwfpackages(ip)%set_name(this%bfr%dstpackagenamearray(i), &
899 this%bfr%budtxtarray(i))
900 naux = this%bfr%nauxarray(i)
901 call this%gwfpackages(ip)%set_auxname(naux, this%bfr%auxtxtarray(1:naux, i))
909 if (imap(i) == 1)
then
910 this%flowpacknamearray(ip) = this%bfr%dstpackagenamearray(i)
916 if (.not. found_dataspdis)
then
917 write (
errmsg,
'(4x,a)')
'SPECIFIC DISCHARGE NOT FOUND IN &
918 &BUDGET FILE. SAVE_SPECIFIC_DISCHARGE AND &
919 &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
922 if (.not. found_datasat)
then
923 write (
errmsg,
'(4x,a)')
'SATURATION NOT FOUND IN &
924 &BUDGET FILE. SAVE_SATURATION AND &
925 &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
928 if (.not. found_flowja)
then
929 write (
errmsg,
'(4x,a)')
'FLOWJA NOT FOUND IN &
930 &BUDGET FILE. SAVE_FLOWS MUST &
931 &BE ACTIVATED IN THE NPF PACKAGE.'
935 call this%parser%StoreErrorUnit()
946 integer(I4B) :: ngwfpack
947 integer(I4B) :: ngwfterms
949 integer(I4B) :: imover
950 integer(I4B) :: ntomvr
951 integer(I4B) :: iterm
952 character(len=LENPACKAGENAME) :: budtxt
953 class(
bndtype),
pointer :: packobj => null()
956 ngwfpack = this%gwfbndlist%Count()
964 imover = packobj%imover
965 if (packobj%isadvpak /= 0) imover = 0
966 if (imover /= 0)
then
973 ngwfterms = ngwfpack + ntomvr
974 call this%allocate_gwfpackages(ngwfterms)
982 budtxt = adjustl(packobj%text)
983 call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
984 this%flowpacknamearray(iterm) = packobj%packName
989 imover = packobj%imover
990 if (packobj%isadvpak /= 0) imover = 0
991 if (imover /= 0)
then
992 budtxt = trim(adjustl(packobj%text))//
'-TO-MVR'
993 call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
994 this%flowpacknamearray(iterm) = packobj%packName
995 this%igwfmvrterm(iterm) = 1
1013 integer(I4B),
intent(in) :: ngwfterms
1016 character(len=LENMEMPATH) :: memPath
1019 allocate (this%gwfpackages(ngwfterms))
1020 allocate (this%flowpacknamearray(ngwfterms))
1023 call mem_allocate(this%igwfmvrterm, ngwfterms,
'IGWFMVRTERM', this%memoryPath)
1026 this%nflowpack = ngwfterms
1027 do n = 1, this%nflowpack
1028 this%igwfmvrterm(n) = 0
1029 this%flowpacknamearray(n) =
''
1033 write (mempath,
'(a, i0)') trim(this%memoryPath)//
'-FT', n
1034 call this%gwfpackages(n)%initialize(mempath)
1043 do n = 1, this%nflowpack
1044 call this%gwfpackages(n)%da()
1052 character(len=*),
intent(in) :: name
1053 integer(I4B),
intent(inout) :: idx
1059 do ip = 1,
size(this%flowpacknamearray)
1060 if (this%flowpacknamearray(ip) == name)
then
1066 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
Structured grid discretization.
Structured grid discretization.
Unstructured grid discretization.
Vertex grid discretization.
Vertex grid discretization.
A generic heterogeneous doubly-linked list.
Derived type for storing flows.