25 character(len=LENPACKAGENAME) :: text =
''
26 logical,
pointer :: flows_from_file => null()
27 type(
listtype),
pointer :: gwfbndlist => null()
28 integer(I4B),
pointer :: iflowsupdated => null()
29 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound => null()
30 real(dp),
dimension(:),
pointer,
contiguous :: gwfflowja => null()
31 real(dp),
dimension(:, :),
pointer,
contiguous :: gwfspdis => null()
32 real(dp),
dimension(:),
pointer,
contiguous :: gwfhead => null()
33 real(dp),
dimension(:),
pointer,
contiguous :: gwfsat => null()
34 integer(I4B),
dimension(:),
pointer,
contiguous :: ibdgwfsat0 => null()
35 integer(I4B),
pointer :: idryinactive => null()
36 real(dp),
dimension(:),
pointer,
contiguous :: gwfstrgss => null()
37 real(dp),
dimension(:),
pointer,
contiguous :: gwfstrgsy => null()
38 integer(I4B),
dimension(:),
pointer,
contiguous :: gwfceltyp => null()
39 integer(I4B),
pointer :: igwfspdis => null()
40 integer(I4B),
pointer :: igwfstrgss => null()
41 integer(I4B),
pointer :: igwfstrgsy => null()
42 integer(I4B),
pointer :: igwfceltyp => null()
43 integer(I4B),
pointer :: iubud => null()
44 integer(I4B),
pointer :: iuhds => null()
45 integer(I4B),
pointer :: iumvr => null()
46 integer(I4B),
pointer :: iugrb => null()
47 integer(I4B),
pointer :: nflowpack => null()
48 integer(I4B),
dimension(:),
pointer,
contiguous :: igwfmvrterm => null()
54 character(len=16),
dimension(:),
allocatable :: flowpacknamearray
55 character(len=LENVARNAME) :: depvartype =
''
85 subroutine fmi_df(this, dis, idryinactive)
90 integer(I4B),
intent(in) :: idryinactive
92 character(len=*),
parameter :: fmtfmi = &
93 "(1x,/1x,'FMI -- FLOW MODEL INTERFACE, VERSION 2, 8/17/2023', &
94 &' INPUT READ FROM MEMPATH: ', A, //)"
95 character(len=*),
parameter :: fmtfmi0 = &
96 "(1x,/1x,'FMI -- FLOW MODEL INTERFACE,'&
97 &' VERSION 2, 8/17/2023')"
100 if (this%iout > 0)
then
101 if (this%inunit /= 0)
then
102 write (this%iout, fmtfmi) this%input_mempath
104 write (this%iout, fmtfmi0)
105 if (this%flows_from_file)
then
106 write (this%iout,
'(a)')
' FLOWS ARE ASSUMED TO BE ZERO.'
108 write (this%iout,
'(a)')
' FLOWS PROVIDED BY A GWF MODEL IN THIS &
118 if (this%inunit /= 0)
then
119 call this%source_options()
123 if (this%inunit /= 0 .and. this%flows_from_file)
then
124 call this%source_packagedata()
125 call this%initialize_gwfterms_from_bfr()
129 if (.not. this%flows_from_file)
then
130 call this%initialize_gwfterms_from_gwfbndlist()
136 this%idryinactive = idryinactive
145 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound
148 this%ibound => ibound
151 call this%allocate_arrays(this%dis%nodes)
164 call this%deallocate_gwfpackages()
167 deallocate (this%gwfpackages)
168 deallocate (this%flowpacknamearray)
172 if (this%flows_from_file)
then
199 call this%NumericalPackageType%da()
213 call this%NumericalPackageType%allocate_scalars()
216 call mem_allocate(this%flows_from_file,
'FLOWS_FROM_FILE', this%memoryPath)
217 call mem_allocate(this%iflowsupdated,
'IFLOWSUPDATED', this%memoryPath)
218 call mem_allocate(this%igwfspdis,
'IGWFSPDIS', this%memoryPath)
219 call mem_allocate(this%igwfstrgss,
'IGWFSTRGSS', this%memoryPath)
220 call mem_allocate(this%igwfstrgsy,
'IGWFSTRGSY', this%memoryPath)
221 call mem_allocate(this%igwfceltyp,
'IGWFCELTYP', this%memoryPath)
226 call mem_allocate(this%nflowpack,
'NFLOWPACK', this%memoryPath)
227 call mem_allocate(this%idryinactive,
"IDRYINACTIVE", this%memoryPath)
231 this%flows_from_file = .true.
232 this%iflowsupdated = 1
242 this%idryinactive = 1
253 integer(I4B),
intent(in) :: nodes
259 call mem_allocate(this%ibdgwfsat0, nodes,
'IBDGWFSAT0', this%memoryPath)
261 this%ibdgwfsat0(n) = 1
266 if (this%flows_from_file)
then
268 'GWFFLOWJA', this%memoryPath)
269 call mem_allocate(this%gwfsat, nodes,
'GWFSAT', this%memoryPath)
270 call mem_allocate(this%gwfhead, nodes,
'GWFHEAD', this%memoryPath)
271 call mem_allocate(this%gwfspdis, 3, nodes,
'GWFSPDIS', this%memoryPath)
273 this%gwfsat(n) = done
274 this%gwfhead(n) =
dzero
275 this%gwfspdis(:, n) =
dzero
277 do n = 1,
size(this%gwfflowja)
278 this%gwfflowja(n) =
dzero
282 if (this%igwfstrgss == 0)
then
283 call mem_allocate(this%gwfstrgss, 1,
'GWFSTRGSS', this%memoryPath)
285 call mem_allocate(this%gwfstrgss, nodes,
'GWFSTRGSS', this%memoryPath)
287 if (this%igwfstrgsy == 0)
then
288 call mem_allocate(this%gwfstrgsy, 1,
'GWFSTRGSY', this%memoryPath)
290 call mem_allocate(this%gwfstrgsy, nodes,
'GWFSTRGSY', this%memoryPath)
292 do n = 1,
size(this%gwfstrgss)
293 this%gwfstrgss(n) =
dzero
295 do n = 1,
size(this%gwfstrgsy)
296 this%gwfstrgsy(n) =
dzero
304 if (this%igwfceltyp == 0) &
305 call mem_allocate(this%gwfceltyp, nodes,
'GWFCELTYP', this%memoryPath)
309 if (this%inunit == 0)
call this%allocate_gwfpackages(this%nflowpack)
321 logical(LGP) :: found_ipakcb
322 character(len=*),
parameter :: fmtisvflow = &
323 "(4x,'CELL-BY-CELL FLOW INFORMATION WILL BE SAVED TO BINARY FILE &
324 &WHENEVER ICBCFL IS NOT ZERO AND FLOW IMBALANCE CORRECTION ACTIVE.')"
327 call mem_set_value(this%ipakcb,
'SAVE_FLOWS', this%input_mempath, &
330 write (this%iout,
'(1x,a)')
'PROCESSING FMI OPTIONS'
332 if (found_ipakcb)
then
334 write (this%iout, fmtisvflow)
337 write (this%iout,
'(1x,a)')
'END OF FMI OPTIONS'
359 character(len=LINELENGTH) :: flowtype, fileop, fname
360 integer(I4B) :: inunit, n
361 logical(LGP) :: exist
363 call mem_setptr(flowtypes,
'FLOWTYPE', this%input_mempath)
364 call mem_setptr(fileops,
'FILEIN', this%input_mempath)
365 call mem_setptr(fnames,
'FNAME', this%input_mempath)
367 write (this%iout,
'(1x,a)')
'PROCESSING FMI PACKAGEDATA'
369 do n = 1,
size(flowtypes)
370 flowtype = flowtypes(n)
374 inquire (file=trim(fname), exist=exist)
375 if (.not. exist)
then
376 call store_error(
'Could not find file '//trim(fname))
380 if (fileop /=
'FILEIN')
then
381 call store_error(
'Unexpected packagedata input keyword read: "' &
382 //trim(fileop)//
'".')
386 select case (flowtype)
389 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
392 call this%initialize_bfr()
395 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
398 call this%initialize_hfr()
401 call openfile(inunit, this%iout, fname,
'DATA(BINARY)',
form, &
406 call this%mvrbudobj%fill_from_bfr(this%dis, this%iout)
409 call openfile(inunit, this%iout, fname,
'DATA(BINARY)', &
412 call this%read_grid()
414 write (
errmsg,
'(a,3(1x,a))') &
415 'UNKNOWN', trim(adjustl(this%text)),
'PACKAGEDATA:', trim(flowtype)
420 write (this%iout,
'(1x,a)')
'END OF FMI PACKAGEDATA'
440 integer(I4B) :: user_nodes
441 integer(I4B),
allocatable :: idomain1d(:), idomain2d(:, :), idomain3d(:, :, :)
443 character(len=*),
parameter :: fmticterr = &
444 &
"('Error in ',a,': Binary grid file does not contain ICELLTYPE.')"
445 character(len=*),
parameter :: fmtdiserr = &
446 "('Error in ',a,': Models do not have the same discretization. &
447 &GWF model has ', i0, ' user nodes, this model has ', i0, '. &
448 &Ensure discretization packages, including IDOMAIN, are identical.')"
449 character(len=*),
parameter :: fmtidomerr = &
450 "('Error in ',a,': models do not have the same discretization. &
451 &Models have different IDOMAIN arrays. &
452 &Ensure discretization packages, including IDOMAIN, are identical.')"
454 call this%gfr%initialize(this%iugrb)
457 if (.not. this%gfr%has_variable(
"ICELLTYPE"))
then
458 write (
errmsg, fmticterr) trim(this%text)
463 'GWFCELTYP', this%memoryPath)
464 call this%gfr%read_int_1d_into(
"ICELLTYPE", this%gwfceltyp)
467 select case (this%gfr%grid_type)
469 select type (dis => this%dis)
471 user_nodes = this%gfr%read_int(
"NCELLS")
472 if (user_nodes /= this%dis%nodesuser)
then
473 write (
errmsg, fmtdiserr) &
474 trim(this%text), user_nodes, this%dis%nodesuser
477 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
478 idomain3d = reshape(idomain1d, [ &
479 this%gfr%read_int(
"NCOL"), &
480 this%gfr%read_int(
"NROW"), &
481 this%gfr%read_int(
"NLAY") &
483 if (.not. all(dis%idomain == idomain3d))
then
484 write (
errmsg, fmtidomerr) trim(this%text)
489 select type (dis => this%dis)
491 user_nodes = this%gfr%read_int(
"NCELLS")
492 if (user_nodes /= this%dis%nodesuser)
then
493 write (
errmsg, fmtdiserr) &
494 trim(this%text), user_nodes, this%dis%nodesuser
497 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
498 idomain2d = reshape(idomain1d, [ &
499 this%gfr%read_int(
"NCPL"), &
500 this%gfr%read_int(
"NLAY") &
502 if (.not. all(dis%idomain == idomain2d))
then
503 write (
errmsg, fmtidomerr) trim(this%text)
508 select type (dis => this%dis)
510 user_nodes = this%gfr%read_int(
"NODES")
511 if (user_nodes /= this%dis%nodesuser)
then
512 write (
errmsg, fmtdiserr) &
513 trim(this%text), user_nodes, this%dis%nodesuser
516 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
517 if (.not. all(dis%idomain == idomain1d))
then
518 write (
errmsg, fmtidomerr) trim(this%text)
523 select type (dis => this%dis)
525 user_nodes = this%gfr%read_int(
"NCELLS")
526 if (user_nodes /= this%dis%nodesuser)
then
527 write (
errmsg, fmtdiserr) &
528 trim(this%text), user_nodes, this%dis%nodesuser
531 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
532 idomain2d = reshape(idomain1d, [ &
533 this%gfr%read_int(
"NCOL"), &
534 this%gfr%read_int(
"NROW") &
536 if (.not. all(dis%idomain == idomain2d))
then
537 write (
errmsg, fmtidomerr) trim(this%text)
542 select type (dis => this%dis)
544 user_nodes = this%gfr%read_int(
"NODES")
545 if (user_nodes /= this%dis%nodesuser)
then
546 write (
errmsg, fmtdiserr) &
547 trim(this%text), user_nodes, this%dis%nodesuser
550 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
551 if (.not. all(dis%idomain == idomain1d))
then
552 write (
errmsg, fmtidomerr) trim(this%text)
557 select type (dis => this%dis)
559 user_nodes = this%gfr%read_int(
"NCELLS")
560 if (user_nodes /= this%dis%nodesuser)
then
561 write (
errmsg, fmtdiserr) &
562 trim(this%text), user_nodes, this%dis%nodesuser
565 idomain1d = this%gfr%read_int_1d(
"IDOMAIN")
566 if (.not. all(dis%idomain == idomain1d))
then
567 write (
errmsg, fmtidomerr) trim(this%text)
573 if (
allocated(idomain3d))
deallocate (idomain3d)
574 if (
allocated(idomain2d))
deallocate (idomain2d)
575 if (
allocated(idomain1d))
deallocate (idomain1d)
577 call this%gfr%finalize()
583 integer(I4B) :: ncrbud
584 call this%bfr%initialize(this%iubud, this%iout, ncrbud)
603 integer(I4B) :: nu, nr
604 integer(I4B) :: ip, i
607 character(len=*),
parameter :: fmtkstpkper = &
608 "(1x,/1x,'FMI READING BUDGET TERMS &
609 &FOR KSTP ', i0, ' KPER ', i0)"
610 character(len=*),
parameter :: fmtbudkstpkper = &
611 "(1x,/1x, 'FMI SETTING BUDGET TERMS &
612 &FOR KSTP ', i0, ' AND KPER ', &
613 &i0, ' TO BUDGET FILE TERMS FROM &
614 &KSTP ', i0, ' AND KPER ', i0)"
622 if (this%bfr%header%kstp == 1)
then
623 if (this%bfr%endoffile)
then
625 else if (this%bfr%headernext%kper ==
kper + 1)
then
628 else if (this%bfr%endoffile)
then
629 write (
errmsg,
'(4x,a)')
'REACHED END OF GWF BUDGET &
630 &FILE BEFORE READING SUFFICIENT BUDGET INFORMATION FOR THIS &
641 write (this%iout, fmtkstpkper)
kstp,
kper
646 do n = 1, this%bfr%nbudterms
647 call this%bfr%read_record(success, this%iout)
648 if (.not. success)
then
649 write (
errmsg,
'(4x,a)')
'GWF BUDGET READ NOT SUCCESSFUL'
655 if (
kper /= this%bfr%header%kper)
then
656 write (
errmsg,
'(4x,a)')
'PERIOD NUMBER IN BUDGET FILE &
657 &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
658 &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN &
659 &STRESS PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL &
660 &TIME STEPS ONE-FOR-ONE IN THAT STRESS PERIOD.'
666 if (this%bfr%header%kstp > 1 .and. (
kstp /= this%bfr%header%kstp))
then
667 write (
errmsg,
'(4x,a)')
'TIME STEP NUMBER IN BUDGET FILE &
668 &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
669 &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN STRESS &
670 &PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
671 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
678 select type (h => this%bfr%header)
680 select case (trim(adjustl(h%budtxt)))
681 case (
'FLOW-JA-FACE')
685 do ipos = 1,
size(this%bfr%flowja)
686 this%gwfflowja(ipos) = this%bfr%flowja(ipos)
690 nu = this%bfr%nodesrc(i)
691 nr = this%dis%get_nodenumber(nu, 0)
693 this%gwfspdis(1, nr) = this%bfr%auxvar(1, i)
694 this%gwfspdis(2, nr) = this%bfr%auxvar(2, i)
695 this%gwfspdis(3, nr) = this%bfr%auxvar(3, i)
699 nu = this%bfr%nodesrc(i)
700 nr = this%dis%get_nodenumber(nu, 0)
702 this%gwfsat(nr) = this%bfr%auxvar(1, i)
705 do nu = 1, this%dis%nodesuser
706 nr = this%dis%get_nodenumber(nu, 0)
708 this%gwfstrgss(nr) = this%bfr%flow(nu)
711 do nu = 1, this%dis%nodesuser
712 nr = this%dis%get_nodenumber(nu, 0)
714 this%gwfstrgsy(nr) = this%bfr%flow(nu)
717 call this%gwfpackages(ip)%copy_values( &
722 do i = 1, this%gwfpackages(ip)%nbound
723 nu = this%gwfpackages(ip)%nodelist(i)
724 nr = this%dis%get_nodenumber(nu, 0)
725 this%gwfpackages(ip)%nodelist(i) = nr
734 write (this%iout, fmtbudkstpkper)
kstp,
kper, &
735 this%bfr%header%kstp, this%bfr%header%kper
738 this%iflowsupdated = 0
745 call this%bfr%finalize()
751 call this%hfr%initialize(this%iuhds, this%iout)
761 integer(I4B) :: nu, nr, i, ilay
766 character(len=*),
parameter :: fmtkstpkper = &
767 "(1x,/1x,'FMI READING HEAD FOR &
768 &KSTP ', i0, ' KPER ', i0)"
769 character(len=*),
parameter :: fmthdskstpkper = &
770 "(1x,/1x, 'FMI SETTING HEAD FOR KSTP ', i0, ' AND KPER ', &
771 &i0, ' TO BINARY FILE HEADS FROM KSTP ', i0, ' AND KPER ', i0)"
779 if (this%hfr%header%kstp == 1)
then
780 if (this%hfr%endoffile)
then
782 else if (this%hfr%headernext%kper ==
kper + 1)
then
785 else if (this%hfr%endoffile)
then
786 write (
errmsg,
'(4x,a)')
'REACHED END OF GWF HEAD &
787 &FILE BEFORE READING SUFFICIENT HEAD INFORMATION FOR THIS &
798 write (this%iout, fmtkstpkper)
kstp,
kper
801 do ilay = 1, this%hfr%nlay
804 call this%hfr%read_record(success, this%iout)
805 if (.not. success)
then
806 write (
errmsg,
'(4x,a)')
'GWF HEAD READ NOT SUCCESSFUL'
812 if (
kper /= this%hfr%header%kper)
then
813 write (
errmsg,
'(4x,a)')
'PERIOD NUMBER IN HEAD FILE &
814 &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
815 &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
816 &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
817 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
823 if (this%hfr%header%kstp > 1 .and. (
kstp /= this%hfr%header%kstp))
then
824 write (
errmsg,
'(4x,a)')
'TIME STEP NUMBER IN HEAD FILE &
825 &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
826 &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
827 &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
828 &ONE-FOR-ONE IN THAT STRESS PERIOD.'
835 ncpl =
size(this%hfr%head)
837 nu = (ilay - 1) * ncpl + i
838 nr = this%dis%get_nodenumber(nu, 0)
839 val = this%hfr%head(i)
840 if (nr > 0) this%gwfhead(nr) = val
844 write (this%iout, fmthdskstpkper)
kstp,
kper, &
845 this%hfr%header%kstp, this%hfr%header%kper
864 integer(I4B) :: nflowpack
865 integer(I4B) :: i, ip
867 logical :: found_flowja
868 logical :: found_dataspdis
869 logical :: found_datasat
870 logical :: found_stoss
871 logical :: found_stosy
872 integer(I4B),
dimension(:),
allocatable :: imap
875 allocate (imap(this%bfr%nbudterms))
878 found_flowja = .false.
879 found_dataspdis = .false.
880 found_datasat = .false.
881 found_stoss = .false.
882 found_stosy = .false.
883 do i = 1, this%bfr%nbudterms
884 select case (trim(adjustl(this%bfr%budtxtarray(i))))
885 case (
'FLOW-JA-FACE')
886 found_flowja = .true.
888 found_dataspdis = .true.
891 found_datasat = .true.
899 nflowpack = nflowpack + 1
905 call this%allocate_gwfpackages(nflowpack)
910 do i = 1, this%bfr%nbudterms
911 if (imap(i) == 0) cycle
912 call this%gwfpackages(ip)%set_name(this%bfr%dstpackagenamearray(i), &
913 this%bfr%budtxtarray(i))
914 naux = this%bfr%nauxarray(i)
915 call this%gwfpackages(ip)%set_auxname(naux, this%bfr%auxtxtarray(1:naux, i))
923 if (imap(i) == 1)
then
924 this%flowpacknamearray(ip) = this%bfr%dstpackagenamearray(i)
930 if (.not. found_dataspdis)
then
931 write (
errmsg,
'(4x,a)')
'SPECIFIC DISCHARGE NOT FOUND IN &
932 &BUDGET FILE. SAVE_SPECIFIC_DISCHARGE AND &
933 &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
936 if (.not. found_datasat)
then
937 write (
errmsg,
'(4x,a)')
'SATURATION NOT FOUND IN &
938 &BUDGET FILE. SAVE_SATURATION AND &
939 &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
942 if (.not. found_flowja)
then
943 write (
errmsg,
'(4x,a)')
'FLOWJA NOT FOUND IN &
944 &BUDGET FILE. SAVE_FLOWS MUST &
945 &BE ACTIVATED IN THE NPF PACKAGE.'
960 integer(I4B) :: ngwfpack
961 integer(I4B) :: ngwfterms
963 integer(I4B) :: imover
964 integer(I4B) :: ntomvr
965 integer(I4B) :: iterm
966 character(len=LENPACKAGENAME) :: budtxt
967 class(
bndtype),
pointer :: packobj => null()
970 ngwfpack = this%gwfbndlist%Count()
978 imover = packobj%imover
979 if (packobj%isadvpak /= 0) imover = 0
980 if (imover /= 0)
then
987 ngwfterms = ngwfpack + ntomvr
988 call this%allocate_gwfpackages(ngwfterms)
996 budtxt = adjustl(packobj%text)
997 call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
998 this%flowpacknamearray(iterm) = packobj%packName
1003 imover = packobj%imover
1004 if (packobj%isadvpak /= 0) imover = 0
1005 if (imover /= 0)
then
1006 budtxt = trim(adjustl(packobj%text))//
'-TO-MVR'
1007 call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
1008 this%flowpacknamearray(iterm) = packobj%packName
1009 this%igwfmvrterm(iterm) = 1
1027 integer(I4B),
intent(in) :: ngwfterms
1030 character(len=LENMEMPATH) :: memPath
1033 allocate (this%gwfpackages(ngwfterms))
1034 allocate (this%flowpacknamearray(ngwfterms))
1037 call mem_allocate(this%igwfmvrterm, ngwfterms,
'IGWFMVRTERM', this%memoryPath)
1040 this%nflowpack = ngwfterms
1041 do n = 1, this%nflowpack
1042 this%igwfmvrterm(n) = 0
1043 this%flowpacknamearray(n) =
''
1047 write (mempath,
'(a, i0)') trim(this%memoryPath)//
'-FT', n
1048 call this%gwfpackages(n)%initialize(mempath)
1057 do n = 1, this%nflowpack
1058 call this%gwfpackages(n)%da()
1066 character(len=*),
intent(in) :: name
1067 integer(I4B),
intent(inout) :: idx
1073 do ip = 1,
size(this%flowpacknamearray)
1074 if (this%flowpacknamearray(ip) == name)
then
1080 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 read_grid(this)
Read/validate flow model grid.
subroutine deallocate_gwfpackages(this)
Deallocate memory in the gwfpackages array.
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 source_options(this)
@ brief Source input options for package
subroutine fmi_da(this)
Deallocate variables.
subroutine source_packagedata(this)
@ brief Source input options for package
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_filename(filename, terminate)
Store the erroring file name.
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
This class is used to store a single deferred-length character string. It was designed to work in an ...
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.