126 logical(LGP),
pointer :: reset_mapped_id
127 integer(I4B),
pointer :: ibudgetout => null()
128 integer(I4B),
pointer :: ibudcsv => null()
129 integer(I4B),
pointer :: maxmvr => null()
130 integer(I4B),
pointer :: maxpackages => null()
131 integer(I4B),
pointer :: maxcomb => null()
132 integer(I4B),
pointer :: nmvr => null()
133 integer(I4B),
pointer :: iexgmvr => null()
134 integer(I4B),
pointer :: imodelnames => null()
135 integer(I4B),
dimension(:),
pointer,
contiguous :: ientries => null()
136 character(len=LENMEMPATH), &
137 dimension(:),
pointer,
contiguous :: pckmempaths
138 character(len=LENPACKAGENAME), &
139 dimension(:),
pointer,
contiguous :: paknames => null()
140 type(
mvrtype),
dimension(:),
pointer,
contiguous :: mvr => null()
145 dimension(:),
pointer,
contiguous :: pakmovers => null()
149 logical(LGP) :: suppress_fileout = .false.
185 subroutine mvr_cr(mvrobj, name_parent, inunit, iout, dis, iexgmvr)
188 character(len=*),
intent(in) :: name_parent
189 integer(I4B),
intent(in) :: inunit
190 integer(I4B),
intent(in) :: iout
192 integer(I4B),
optional :: iexgmvr
198 call mvrobj%mvr_init(name_parent, inunit, iout, dis, iexgmvr)
201 subroutine mvr_init(this, name_parent, inunit, iout, dis, iexgmvr)
203 character(len=*),
intent(in) :: name_parent
204 integer(I4B),
intent(in) :: inunit
205 integer(I4B),
intent(in) :: iout
207 integer(I4B),
optional :: iexgmvr
211 call this%set_names(1, name_parent,
'MVR',
'MVR')
214 call this%allocate_scalars()
224 if (
present(iexgmvr)) this%iexgmvr = iexgmvr
228 call budget_cr(this%budget, this%memoryPath)
231 call this%parser%Initialize(this%inunit, this%iout)
245 write (this%iout, 1) this%inunit
246 1
format(1x, /1x,
'MVR -- WATER MOVER PACKAGE, VERSION 8, 1/29/2016', &
247 ' INPUT READ FROM UNIT ', i0)
250 call this%read_options()
251 call this%check_options()
254 call this%read_dimensions()
257 call this%allocate_arrays()
260 call this%read_packages()
261 call this%check_packages()
264 call this%budget%budget_df(this%maxpackages,
'WATER MOVER')
265 call this%budget%set_ibudcsv(this%ibudcsv)
268 call this%mvr_setup_budobj()
284 integer(I4B) :: i, ierr, nlist, ipos
285 integer(I4B) :: ii, jj
287 character(len=LINELENGTH) :: line, errmsg
288 character(len=LENMODELNAME) :: mname
290 character(len=*),
parameter :: fmtblkerr = &
291 &
"('Error. Looking for BEGIN PERIOD iper. Found ', a, ' instead.')"
292 character(len=*),
parameter :: fmtlsp = &
293 &
"(1X,/1X,'REUSING ',A,'S FROM LAST STRESS PERIOD')"
294 character(len=*),
parameter :: fmtnbd = &
295 "(1X,/1X,'THE NUMBER OF ACTIVE ',A,'S (',I6, &
296 &') IS GREATER THAN MAXIMUM(',I6,')')"
300 if (this%inunit == 0)
return
303 if (this%ionper <
kper)
then
306 call this%parser%GetBlock(
'PERIOD', isfound, ierr, &
307 supportopenclose=.true., &
308 blockrequired=.false.)
312 call this%read_check_ionper()
318 this%ionper =
nper + 1
321 call this%parser%GetCurrentLine(line)
322 write (errmsg, fmtblkerr) adjustl(trim(line))
324 call this%parser%StoreErrorUnit()
330 if (this%ionper ==
kper)
then
331 write (this%iout,
'(/,2x,a,i0)')
'READING WATER MOVERS FOR PERIOD ',
kper
334 this%reset_mapped_id = .true.
337 if (this%iexgmvr == 0)
then
338 mname = this%name_model
345 call this%assign_packagemovers()
348 call this%gwfmvrperioddata%read_from_parser(this%parser, nlist, mname)
351 call this%initialize_movers(nlist)
355 call this%mvr(i)%prepare(this%parser%iuactive, &
358 if (this%iprpak == 1)
call this%mvr(i)%echo(this%iout)
360 write (this%iout,
'(/,1x,a,1x,i6,/)')
'END OF DATA FOR PERIOD',
kper
364 write (this%iout,
'(4x, i0, a, i0)') this%nmvr, &
365 ' MOVERS READ FOR PERIOD ',
kper
369 ipos =
ifind(this%pckMemPaths, this%mvr(i)%mem_path_src)
371 write (errmsg,
'(a,a,a)')
'Provider ', &
372 trim(this%mvr(i)%mem_path_src),
' not listed in packages block.'
375 ipos =
ifind(this%pckMemPaths, this%mvr(i)%mem_path_tgt)
377 write (errmsg,
'(a,a,a)')
'Receiver ', &
378 trim(this%mvr(i)%mem_path_tgt),
' not listed in packages block.'
383 call this%parser%StoreErrorUnit()
387 do i = 1, this%maxcomb
393 ii =
ifind(this%pckMemPaths, this%mvr(i)%mem_path_src)
394 jj =
ifind(this%pckMemPaths, this%mvr(i)%mem_path_tgt)
395 ipos = (ii - 1) * this%maxpackages + jj
396 this%ientries(ipos) = this%ientries(ipos) + 1
399 write (this%iout, fmtlsp)
'MVR'
406 integer(I4B) :: nr_active_movers
410 do i = 1, nr_active_movers
411 call this%mvr(i)%set_values(this%gwfmvrperioddata%mname1(i), &
412 this%gwfmvrperioddata%pname1(i), &
413 this%gwfmvrperioddata%id1(i), &
414 this%gwfmvrperioddata%mname2(i), &
415 this%gwfmvrperioddata%pname2(i), &
416 this%gwfmvrperioddata%id2(i), &
417 this%gwfmvrperioddata%imvrtype(i), &
418 this%gwfmvrperioddata%value(i))
430 call this%mvr(i)%advance()
442 call this%mvr(i)%update_provider()
443 call this%mvr(i)%update_receiver()
450 subroutine mvr_cc(this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
453 integer(I4B),
intent(in) :: innertot
454 integer(I4B),
intent(in) :: kiter
455 integer(I4B),
intent(in) :: iend
456 integer(I4B),
intent(in) :: icnvgmod
457 character(len=LENPAKLOC),
intent(inout) :: cpak
458 integer(I4B),
intent(inout) :: ipak
459 real(DP),
intent(inout) :: dpak
461 character(len=*),
parameter :: fmtmvrcnvg = &
462 "(/,1x,'MOVER PACKAGE REQUIRES AT LEAST TWO OUTER ITERATIONS. CONVERGE &
463 &FLAG HAS BEEN RESET TO FALSE.')"
466 if (this%nmvr > 0)
then
467 if (icnvgmod == 1 .and. kiter == 1)
then
469 cpak = trim(this%packName)
470 write (this%iout, fmtmvrcnvg)
487 if (this%reset_mapped_id)
then
488 call this%set_mapped_id()
489 this%reset_mapped_id = .false.
493 call this%fill_budobj()
498 subroutine mvr_bdsav(this, icbcfl, ibudfl, isuppress_output)
503 integer(I4B),
intent(in) :: icbcfl
504 integer(I4B),
intent(in) :: ibudfl
505 integer(I4B),
intent(in) :: isuppress_output
507 integer(I4B) :: ibinun
509 character(len=*),
parameter :: fmttkk = &
510 "(1X,/1X,A,' PERIOD ',I0,' STEP ',I0)"
513 if (ibudfl /= 0 .and. this%iprflow /= 0 .and. isuppress_output == 0)
then
514 call this%mvr_print_outputtab()
519 if (this%ibudgetout /= 0)
then
520 ibinun = this%ibudgetout
522 if (icbcfl == 0) ibinun = 0
523 if (isuppress_output /= 0) ibinun = 0
525 call this%budobj%save_flows(this%dis, ibinun,
kstp,
kper,
delt, &
537 integer(I4B),
intent(in) :: icbcfl
538 integer(I4B),
intent(in) :: ibudfl
540 integer(I4B) :: ibinun
544 if (this%ibudgetout /= 0)
then
545 ibinun = this%ibudgetout
547 if (icbcfl == 0) ibinun = 0
549 call this%budobj%save_flows(this%dis, ibinun,
kstp,
kper,
delt, &
559 integer(I4B),
intent(in) :: icbcfl
560 integer(I4B),
intent(in) :: ibudfl
563 if (ibudfl /= 0 .and. this%iprflow /= 0)
then
564 call this%mvr_print_outputtab()
575 integer(I4B),
intent(in) :: ibudfl
577 character(len=LENMEMPATH) :: pckMemPath
579 real(DP),
allocatable,
dimension(:) :: ratin, ratout
582 allocate (ratin(this%maxpackages), ratout(this%maxpackages))
583 do j = 1, this%maxpackages
590 do j = 1, this%maxpackages
591 if (this%pckMemPaths(j) == this%mvr(i)%mem_path_src)
then
592 ratin(j) = ratin(j) + this%mvr(i)%qpactual
594 if (this%pckMemPaths(j) == this%mvr(i)%mem_path_tgt)
then
595 ratout(j) = ratout(j) + this%mvr(i)%qpactual
601 call this%budget%reset()
602 do j = 1, this%maxpackages
603 if ((this%iexgmvr) == 1)
then
604 pckmempath = this%pckMemPaths(j)
606 pckmempath = this%paknames(j)
608 call this%budget%addentry(ratin(j), ratout(j),
delt, pckmempath)
612 call this%budget%finalize_step(
delt)
613 if (ibudfl /= 0)
then
614 call this%budget%budget_ot(
kstp,
kper, this%iout)
618 call this%budget%writecsv(
totim)
621 deallocate (ratin, ratout)
640 if (this%inunit > 0)
then
642 deallocate (this%mvr)
643 deallocate (this%pckMemPaths)
644 deallocate (this%paknames)
645 deallocate (this%pakmovers)
648 call this%gwfmvrperioddata%destroy()
649 deallocate (this%gwfmvrperioddata)
650 nullify (this%gwfmvrperioddata)
653 call this%budget%budget_da()
654 deallocate (this%budget)
657 call this%budobj%budgetobject_da()
658 deallocate (this%budobj)
659 nullify (this%budobj)
662 if (
associated(this%outputtab))
then
663 call this%outputtab%table_da()
664 deallocate (this%outputtab)
665 nullify (this%outputtab)
681 call this%NumericalPackageType%da()
695 character(len=LINELENGTH) :: errmsg
696 character(len=MAXCHARLEN) :: fname, keyword
698 logical :: isfound, endOfBlock
700 character(len=*),
parameter :: fmtmvrbin = &
701 "(4x, 'MVR ', 1x, a, 1x, ' WILL BE SAVED TO FILE: ', a, /4x, 'OPENED ON &
705 call this%parser%GetBlock(
'OPTIONS', isfound, ierr, &
706 supportopenclose=.true., blockrequired=.false.)
710 write (this%iout,
'(1x,a)')
'PROCESSING MVR OPTIONS'
712 call this%parser%GetNextLine(endofblock)
714 call this%parser%GetStringCaps(keyword)
715 select case (keyword)
717 if (this%suppress_fileout) cycle
718 call this%parser%GetStringCaps(keyword)
719 if (keyword ==
'FILEOUT')
then
720 call this%parser%GetString(fname)
722 call openfile(this%ibudgetout, this%iout, fname,
'DATA(BINARY)', &
724 write (this%iout, fmtmvrbin)
'BUDGET', trim(adjustl(fname)), &
728 &BE FOLLOWED BY FILEOUT')
731 if (this%suppress_fileout) cycle
732 call this%parser%GetStringCaps(keyword)
733 if (keyword ==
'FILEOUT')
then
734 call this%parser%GetString(fname)
736 call openfile(this%ibudcsv, this%iout, fname,
'CSV', &
737 filstat_opt=
'REPLACE')
738 write (this%iout, fmtmvrbin)
'BUDGET CSV', trim(adjustl(fname)), &
741 call store_error(
'OPTIONAL BUDGETCSV KEYWORD MUST BE FOLLOWED BY &
746 write (this%iout,
'(4x,a)')
'WATER MOVER INPUT '// &
747 'WILL BE PRINTED TO LIST FILE.'
750 write (this%iout,
'(4x,a)')
'LISTS OF WATER MOVER FLOWS '// &
751 'WILL BE PRINTED TO LIST FILE.'
754 write (this%iout,
'(4x,a)')
'ALL PACKAGE NAMES ARE PRECEDED '// &
755 'BY THE NAME OF THE MODEL CONTAINING THE PACKAGE.'
756 if (this%iexgmvr == 0)
then
757 write (errmsg,
'(a,a)') &
758 'MODELNAMES cannot be specified unless the '// &
759 'mover package is for an exchange.'
761 call this%parser%StoreErrorUnit()
764 write (errmsg,
'(a,a)')
'Unknown MVR option: ', trim(keyword)
766 call this%parser%StoreErrorUnit()
769 write (this%iout,
'(1x,a)')
'END OF MVR OPTIONS'
782 character(len=LINELENGTH) :: errmsg
785 if (this%iexgmvr == 0 .and. this%imodelnames == 1)
then
786 write (errmsg,
'(a,a)') &
787 'MODELNAMES cannot be specified unless the '// &
788 'mover package is for an exchange.'
790 call this%parser%StoreErrorUnit()
794 if (this%iexgmvr /= 0 .and. this%imodelnames == 0)
then
795 write (errmsg,
'(a,a)') &
796 'MODELNAMES option must be specified because '// &
797 'mover package is for an exchange.'
799 call this%parser%StoreErrorUnit()
812 character(len=LINELENGTH) :: errmsg, keyword
814 logical :: isfound, endOfBlock
819 call this%parser%GetBlock(
'DIMENSIONS', isfound, ierr, &
820 supportopenclose=.true.)
824 write (this%iout,
'(/1x,a)')
'PROCESSING MVR DIMENSIONS'
826 call this%parser%GetNextLine(endofblock)
828 call this%parser%GetStringCaps(keyword)
829 select case (keyword)
831 this%maxmvr = this%parser%GetInteger()
832 write (this%iout,
'(4x,a,i0)')
'MAXMVR = ', this%maxmvr
834 this%maxpackages = this%parser%GetInteger()
835 write (this%iout,
'(4x,a,i0)')
'MAXPACKAGES = ', this%maxpackages
837 write (errmsg,
'(a,a)') &
838 'Unknown MVR dimension: ', trim(keyword)
840 call this%parser%StoreErrorUnit()
843 write (this%iout,
'(1x,a)')
'END OF MVR DIMENSIONS'
845 call store_error(
'Required DIMENSIONS block not found.')
846 call this%parser%StoreErrorUnit()
851 do i = 1, this%maxpackages
852 do j = 1, this%maxpackages
853 this%maxcomb = this%maxcomb + 1
858 if (this%maxmvr < 0)
then
859 write (errmsg,
'(a)') &
860 'MAXMVR was not specified or was specified incorrectly.'
862 call this%parser%StoreErrorUnit()
864 if (this%maxpackages < 0)
then
865 write (errmsg,
'(a)') &
866 'MAXPACKAGES was not specified or was specified incorrectly.'
868 call this%parser%StoreErrorUnit()
882 character(len=LINELENGTH) :: errmsg, word, word1, word2
883 integer(I4B) :: lloc, ierr
885 logical :: isfound, endOfBlock
888 call this%parser%GetBlock(
'PACKAGES', isfound, ierr, &
889 supportopenclose=.true.)
893 write (this%iout,
'(/1x,a)')
'PROCESSING MVR PACKAGES'
896 call this%parser%GetNextLine(endofblock)
898 call this%parser%GetStringCaps(word1)
901 if (npak > this%maxpackages)
then
902 call store_error(
'ERROR. MAXPACKAGES NOT SET LARGE ENOUGH.')
903 call this%parser%StoreErrorUnit()
905 if (this%iexgmvr == 0)
then
909 call this%parser%GetStringCaps(word2)
913 this%paknames(npak) = trim(word)
914 write (this%iout,
'(3x,a,a)')
'INCLUDING PACKAGE: ', &
915 trim(this%pckMemPaths(npak))
917 write (this%iout,
'(1x,a)')
'END OF MVR PACKAGES'
919 call store_error(
'ERROR. REQUIRED PACKAGES BLOCK NOT FOUND.')
920 call this%parser%StoreErrorUnit()
924 if (npak /= this%maxpackages)
then
925 write (errmsg,
'(a, i0, a, i0, a)') &
926 'ERROR. NUMBER OF PACKAGES (', npak,
') DOES NOT EQUAL '// &
927 'MAXPACKAGES (', this%maxpackages,
').'
929 call this%parser%StoreErrorUnit()
943 character(len=LINELENGTH) :: errmsg
945 integer(I4B),
pointer :: imover_ptr
948 do i = 1,
size(this%pckMemPaths)
950 call mem_setptr(imover_ptr,
'IMOVER', trim(this%pckMemPaths(i)))
951 if (imover_ptr == 0)
then
952 write (errmsg,
'(a, a, a)') &
953 'ERROR. MODEL AND PACKAGE "', &
954 trim(this%pckMemPaths(i)), &
955 '" DOES NOT HAVE MOVER SPECIFIED IN OPTIONS BLOCK.'
962 call this%parser%StoreErrorUnit()
977 do i = 1,
size(this%pckMemPaths)
978 if (this%pakmovers(i)%memoryPath ==
'')
then
980 trim(this%pckMemPaths(i)))
995 call this%NumericalPackageType%allocate_scalars()
998 call mem_allocate(this%reset_mapped_id,
'RESET_MAPPED_ID', this%memoryPath)
999 call mem_allocate(this%ibudgetout,
'IBUDGETOUT', this%memoryPath)
1000 call mem_allocate(this%ibudcsv,
'IBUDCSV', this%memoryPath)
1001 call mem_allocate(this%maxmvr,
'MAXMVR', this%memoryPath)
1002 call mem_allocate(this%maxpackages,
'MAXPACKAGES', this%memoryPath)
1003 call mem_allocate(this%maxcomb,
'MAXCOMB', this%memoryPath)
1005 call mem_allocate(this%iexgmvr,
'IEXGMVR', this%memoryPath)
1006 call mem_allocate(this%imodelnames,
'IMODELNAMES', this%memoryPath)
1009 this%reset_mapped_id = .false.
1013 this%maxpackages = -1
1017 this%imodelnames = 0
1020 allocate (this%gwfmvrperioddata)
1036 allocate (this%mvr(this%maxmvr))
1037 allocate (this%pckMemPaths(this%maxpackages))
1038 allocate (this%paknames(this%maxpackages))
1039 allocate (this%pakmovers(this%maxpackages))
1042 do i = 1, this%maxpackages
1047 call this%gwfmvrperioddata%construct(this%maxmvr, this%memoryPath)
1051 call mem_allocate(this%ientries, this%maxcomb,
'IENTRIES', this%memoryPath)
1054 do i = 1, this%maxcomb
1055 this%ientries(i) = 0
1059 call this%mvr_setup_outputtab()
1071 integer(I4B) :: nbudterm
1075 integer(I4B) :: naux
1076 character(len=LENMODELNAME) :: modelname1, modelname2
1077 character(len=LENPACKAGENAME) :: packagename1, packagename2
1078 integer(I4B) :: maxlist
1080 character(len=LENBUDTXT) :: text
1086 do i = 1, this%maxpackages
1087 do j = 1, this%maxpackages
1088 nbudterm = nbudterm + 1
1097 call this%budobj%budgetobject_df(ncv, nbudterm, 0, 0)
1101 text =
' MOVER-FLOW'
1102 maxlist = this%maxmvr
1104 do i = 1, this%maxpackages
1106 call split_mem_path(this%pckMemPaths(i), modelname1, packagename1)
1108 do j = 1, this%maxpackages
1111 call split_mem_path(this%pckMemPaths(j), modelname2, packagename2)
1112 call this%budobj%budterm(idx)%initialize(text, &
1117 maxlist, .false., .false., &
1133 integer(I4B) :: n, n1, n2
1134 integer(I4B) :: ipos
1135 integer(I4B) :: ival
1136 integer(I4B) :: nitems
1137 integer(I4B) :: lloc
1138 integer(I4B) :: istart
1139 integer(I4B) :: istop
1141 character(len=LENMODELNAME) :: modelname1, modelname2
1142 character(len=LENPACKAGENAME) :: packagename1, packagename2
1143 character(len=LENMEMPATH) :: pckMemPathsDummy
1149 do i = 1, this%maxpackages
1152 call urword(this%pckMemPaths(i), lloc, istart, istop, 1, ival, rval, -1, -1)
1153 pckmempathsdummy = this%pckMemPaths(i)
1154 modelname1 = pckmempathsdummy(istart:istop)
1155 call urword(this%pckMemPaths(i), lloc, istart, istop, 1, ival, rval, -1, -1)
1156 pckmempathsdummy = this%pckMemPaths(i)
1157 packagename1 = pckmempathsdummy(istart:istop)
1158 do j = 1, this%maxpackages
1161 call urword(this%pckMemPaths(j), lloc, istart, istop, 1, ival, rval, &
1163 pckmempathsdummy = this%pckMemPaths(j)
1164 modelname2 = pckmempathsdummy(istart:istop)
1165 call urword(this%pckMemPaths(j), lloc, istart, istop, 1, ival, rval, &
1167 pckmempathsdummy = this%pckMemPaths(j)
1168 packagename2 = pckmempathsdummy(istart:istop)
1169 ipos = (i - 1) * this%maxpackages + j
1170 nitems = this%ientries(ipos)
1175 call this%budobj%budterm(idx)%reset(nitems)
1176 if (nitems < 1) cycle
1181 if (this%pckMemPaths(i) == this%mvr(n)%mem_path_src)
then
1182 if (this%pckMemPaths(j) == this%mvr(n)%mem_path_tgt)
then
1185 q = -this%mvr(n)%qpactual
1188 n1 = this%mvr(n)%iRchNrSrcMapped
1191 n2 = this%mvr(n)%iRchNrTgt
1194 call this%budobj%budterm(idx)%update_term(n1, n2, q)
1202 call this%budobj%accumulate_terms()
1211 character(len=LINELENGTH) :: title
1212 character(len=LINELENGTH) :: text
1213 integer(I4B) :: ntabcol
1214 integer(I4B) :: ilen
1217 if (this%iprflow /= 0)
then
1223 title =
'WATER MOVER PACKAGE ('//trim(this%packName)// &
1225 call table_cr(this%outputtab, this%packName, title)
1226 call this%outputtab%table_df(this%maxmvr, ntabcol, this%iout, &
1229 call this%outputtab%initialize_column(text, 10, alignment=
tabcenter)
1230 text =
'PROVIDER LOCATION'
1232 call this%outputtab%initialize_column(text, ilen)
1233 text =
'PROVIDER ID'
1234 call this%outputtab%initialize_column(text, 10)
1235 text =
'AVAILABLE RATE'
1236 call this%outputtab%initialize_column(text, 10)
1237 text =
'PROVIDED RATE'
1238 call this%outputtab%initialize_column(text, 10)
1239 text =
'RECEIVER LOCATION'
1241 call this%outputtab%initialize_column(text, ilen)
1242 text =
'RECEIVER ID'
1243 call this%outputtab%initialize_column(text, 10)
1256 character(len=LINELENGTH) :: title
1260 call this%outputtab%set_kstpkper(
kstp,
kper)
1263 title =
'WATER MOVER PACKAGE ('//trim(this%packName)// &
1265 call this%outputtab%set_title(title)
1266 call this%outputtab%set_maxbound(this%nmvr)
1268 call this%outputtab%add_term(i)
1269 call this%outputtab%add_term(this%mvr(i)%mem_path_src)
1270 call this%outputtab%add_term(this%mvr(i)%iRchNrSrc)
1271 call this%outputtab%add_term(this%mvr(i)%qavailable)
1272 call this%outputtab%add_term(this%mvr(i)%qpactual)
1273 call this%outputtab%add_term(this%mvr(i)%mem_path_tgt)
1274 call this%outputtab%add_term(this%mvr(i)%iRchNrTgt)
1298 integer(I4B) :: i, mapped_id
1306 mapped_id = pkg_mvr%iprmap(this%mvr(i)%iRchNrSrc)
1307 this%mvr(i)%iRchNrSrcMapped = mapped_id
1309 deallocate (pkg_mvr)
This module contains block parser methods.
This module contains the BudgetModule.
subroutine, public budget_cr(this, name_model)
@ brief Create a new budget object
subroutine, public budgetobject_cr(this, name)
Create a new budget object.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
@ tabcenter
centered table column
integer(i4b), parameter lenmodelname
maximum length of the model name
integer(i4b), parameter lenpackagename
maximum length of the package name
real(dp), parameter dnodata
real no data constant
integer(i4b), parameter lenpakloc
maximum length of a package location
integer(i4b), parameter lenauxname
maximum length of a aux variable
real(dp), parameter dzero
real constant zero
integer(i4b), parameter maxcharlen
maximum length of char string
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, public mvr_cr(mvrobj, name_parent, inunit, iout, dis, iexgmvr)
Create a new mvr object.
subroutine mvr_da(this)
Deallocate.
subroutine allocate_scalars(this)
Allocate package scalars.
subroutine mvr_bdsav(this, icbcfl, ibudfl, isuppress_output)
Write mover terms.
subroutine initialize_movers(this, nr_active_movers)
subroutine fill_budobj(this)
Fill budget object.
subroutine check_packages(this)
Check to make sure packages have mover activated.
subroutine mvr_init(this, name_parent, inunit, iout, dis, iexgmvr)
subroutine mvr_setup_budobj(this)
Set up the budget object that stores all the mvr flows.
subroutine mvr_bd(this)
Fill the mover budget object.
subroutine read_options(this)
Read options specified in the input options block.
subroutine assign_packagemovers(this)
Assign pointer to each package's packagemover object.
subroutine mvr_ot_printflow(this, icbcfl, ibudfl)
Print mover flow table.
subroutine mvr_setup_outputtab(this)
Set up output table.
subroutine read_dimensions(this)
Read the dimensions for this package.
subroutine mvr_fc(this)
Calculate qfrommvr as a function of qtomvr.
subroutine mvr_rp(this)
Read and Prepare.
subroutine mvr_ot_saveflow(this, icbcfl, ibudfl)
Write mover terms.
subroutine mvr_cc(this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
Extra convergence check for mover.
subroutine mvr_ot_bdsummary(this, ibudfl)
Write mover budget to listing file.
subroutine mvr_print_outputtab(this)
Set up output table.
subroutine mvr_ar(this)
Allocate and read water mover information.
subroutine allocate_arrays(this)
Allocate package arrays.
subroutine set_mapped_id(this)
Set mapped id.
subroutine read_packages(this)
Read the packages that will be managed by this mover.
subroutine check_options(this)
Check MODELNAMES option set correctly.
This module contains the GwfMvrPeriodDataModule Module.
This module defines variable data types.
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine split_mem_path(mem_path, component, subcomponent)
Split the memory path into component(s)
This module contains the MvrModule Module.
This module contains the base numerical package type.
subroutine, public nulllify_packagemover_pointer(packagemover)
subroutine, public set_packagemover_pointer(packagemover, memPath)
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.
subroutine, public table_cr(this, name, title)
real(dp), pointer, public pertim
time relative to start of stress period
real(dp), pointer, public totim
time relative to start of simulation
integer(i4b), pointer, public kstp
current time step number
integer(i4b), pointer, public kper
current stress period number
real(dp), pointer, public delt
length of the current time step
integer(i4b), pointer, public nper
number of stress period
Derived type for the Budget object.
Derived type for GwfMvrPeriodDataType.
Derived type for MvrType.