MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
tspmvtmodule Module Reference

Data Types

type  tspmvttype
 

Functions/Subroutines

subroutine, public mvt_cr (mvt, name_model, inunit, iout, fmi1, eqnsclfac, depvartype, gwfmodelname1, gwfmodelname2, fmi2)
 Create a new mover transport object. More...
 
subroutine mvt_df (this, dis)
 Define mover transport object. More...
 
subroutine set_pointer_mvrbudobj (this, mvrbudobj)
 @ brief Set pointer to mvrbudobj More...
 
subroutine mvt_ar (this)
 Allocate and read mover-for-transport information. More...
 
subroutine mvt_rp (this)
 Read and prepare mover transport object. More...
 
subroutine mvt_fc (this, cnew1, cnew2)
 Calculate coefficients and fill amat and rhs. More...
 
subroutine set_fmi_pr_rc (this, ibudterm, fmi_pr, fmi_rc)
 @ brief Set the fmi_pr and fmi_rc pointers More...
 
subroutine mvt_cc (this, kiter, iend, icnvgmod, cpak, dpak)
 Extra convergence check for mover. More...
 
subroutine mvt_bd (this, cnew1, cnew2)
 Write mover terms to listing file. More...
 
subroutine mvt_ot_saveflow (this, icbcfl, ibudfl)
 Write mover budget terms. More...
 
subroutine mvt_ot_printflow (this, icbcfl, ibudfl)
 Print mover flow table. More...
 
subroutine mvt_ot_bdsummary (this, ibudfl)
 Write mover budget to listing file. More...
 
subroutine mvt_da (this)
 @ brief Deallocate memory More...
 
subroutine allocate_scalars (this)
 @ brief Allocate scalar variables for package More...
 
subroutine read_options (this)
 Read mover-for-transport options block. More...
 
subroutine mvt_setup_budobj (this)
 Set up the budget object that stores all the mvr flows. More...
 
subroutine mvt_fill_budobj (this, cnew1, cnew2)
 Copy mover-for-transport flow terms into thisbudobj. More...
 
subroutine mvt_scan_mvrbudobj (this)
 Determine max number of packages in use. More...
 
subroutine mvt_setup_outputtab (this)
 Set up the mover-for-transport output table. More...
 
subroutine mvt_print_outputtab (this)
 Set up mover-for-transport output table. More...
 

Function/Subroutine Documentation

◆ allocate_scalars()

subroutine tspmvtmodule::allocate_scalars ( class(tspmvttype this)

Method to allocate scalar variables for the MVT package.

Definition at line 548 of file tsp-mvt.f90.

549  ! -- modules
551  ! -- dummy
552  class(TspMvtType) :: this
553  !
554  ! -- Allocate scalars in NumericalPackageType
555  call this%NumericalPackageType%allocate_scalars()
556  !
557  ! -- Allocate
558  call mem_allocate(this%maxpackages, 'MAXPACKAGES', this%memoryPath)
559  call mem_allocate(this%ibudgetout, 'IBUDGETOUT', this%memoryPath)
560  call mem_allocate(this%ibudcsv, 'IBUDCSV', this%memoryPath)
561  !
562  ! -- Initialize
563  this%maxpackages = 0
564  this%ibudgetout = 0
565  this%ibudcsv = 0

◆ mvt_ar()

subroutine tspmvtmodule::mvt_ar ( class(tspmvttype this)
private

Definition at line 168 of file tsp-mvt.f90.

169  ! -- dummy
170  class(TspMvtType) :: this
171  !
172  ! -- Setup the output table
173  call this%mvt_setup_outputtab()

◆ mvt_bd()

subroutine tspmvtmodule::mvt_bd ( class(tspmvttype this,
real(dp), dimension(:), intent(in), contiguous  cnew1,
real(dp), dimension(:), intent(in), contiguous  cnew2 
)
private

Definition at line 389 of file tsp-mvt.f90.

390  ! -- dummy
391  class(TspMvtType) :: this
392  real(DP), dimension(:), contiguous, intent(in) :: cnew1
393  real(DP), dimension(:), contiguous, intent(in) :: cnew2
394  !
395  ! -- Fill the budget object
396  call this%mvt_fill_budobj(cnew1, cnew2)

◆ mvt_cc()

subroutine tspmvtmodule::mvt_cc ( class(tspmvttype this,
integer(i4b), intent(in)  kiter,
integer(i4b), intent(in)  iend,
integer(i4b), intent(in)  icnvgmod,
character(len=lenpakloc), intent(inout)  cpak,
real(dp), intent(inout)  dpak 
)
private

Definition at line 364 of file tsp-mvt.f90.

365  ! -- dummy
366  class(TspMvtType) :: this
367  integer(I4B), intent(in) :: kiter
368  integer(I4B), intent(in) :: iend
369  integer(I4B), intent(in) :: icnvgmod
370  character(len=LENPAKLOC), intent(inout) :: cpak
371  real(DP), intent(inout) :: dpak
372  ! -- formats
373  character(len=*), parameter :: fmtmvrcnvg = &
374  "(/,1x,'MOVER PACKAGE REQUIRES AT LEAST TWO OUTER ITERATIONS. CONVERGE &
375  &FLAG HAS BEEN RESET TO FALSE.')"
376  !
377  ! -- If there are active movers, then at least 2 outers required
378  if (associated(this%mvrbudobj)) then
379  if (icnvgmod == 1 .and. kiter == 1) then
380  dpak = dnodata
381  cpak = trim(this%packName)
382  write (this%iout, fmtmvrcnvg)
383  end if
384  end if

◆ mvt_cr()

subroutine, public tspmvtmodule::mvt_cr ( type(tspmvttype), pointer  mvt,
character(len=*), intent(in)  name_model,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout,
type(tspfmitype), intent(in), target  fmi1,
real(dp), intent(in), pointer  eqnsclfac,
character(len=lenvarname), intent(in)  depvartype,
character(len=*), intent(in), optional  gwfmodelname1,
character(len=*), intent(in), optional  gwfmodelname2,
type(tspfmitype), intent(in), optional, target  fmi2 
)
Parameters
[in]eqnsclfacgoverning equation scale factor
[in]depvartypedependent variable type ('concentration' or 'temperature')

Definition at line 73 of file tsp-mvt.f90.

75  ! -- dummy
76  type(TspMvtType), pointer :: mvt
77  character(len=*), intent(in) :: name_model
78  integer(I4B), intent(in) :: inunit
79  integer(I4B), intent(in) :: iout
80  type(TspFmiType), intent(in), target :: fmi1
81  real(DP), intent(in), pointer :: eqnsclfac !< governing equation scale factor
82  character(len=LENVARNAME), intent(in) :: depvartype !< dependent variable type ('concentration' or 'temperature')
83  character(len=*), intent(in), optional :: gwfmodelname1
84  character(len=*), intent(in), optional :: gwfmodelname2
85  type(TspFmiType), intent(in), target, optional :: fmi2
86  !
87  ! -- Create the object
88  allocate (mvt)
89  !
90  ! -- Create name and memory path
91  call mvt%set_names(1, name_model, 'MVT', 'MVT')
92  !
93  ! -- Allocate scalars
94  call mvt%allocate_scalars()
95  !
96  mvt%inunit = inunit
97  mvt%iout = iout
98  !
99  ! -- Assume that this MVT is owned by a GWT Model
100  mvt%fmi1 => fmi1
101  mvt%fmi2 => fmi1
102  !
103  ! -- Set pointers
104  if (present(fmi2)) then
105  mvt%fmi2 => fmi2
106  end if
107  !
108  ! -- Set model names
109  if (present(gwfmodelname1)) then
110  mvt%gwfmodelname1 = gwfmodelname1
111  end if
112  if (present(gwfmodelname2)) then
113  mvt%gwfmodelname2 = gwfmodelname2
114  end if
115  !
116  ! -- Create the budget object
117  call budgetobject_cr(mvt%budobj, 'TRANSPORT MOVER')
118  !
119  ! -- Store pointer to governing equation scale factor
120  mvt%eqnsclfac => eqnsclfac
121  !
122  ! -- Store pointer to labels associated with the current model so that the
123  ! package has access to the corresponding dependent variable type
124  mvt%depvartype = depvartype
Here is the call graph for this function:
Here is the caller graph for this function:

◆ mvt_da()

subroutine tspmvtmodule::mvt_da ( class(tspmvttype this)

Method to deallocate memory for the package.

Definition at line 503 of file tsp-mvt.f90.

504  ! -- modules
506  ! -- dummy
507  class(TspMvtType) :: this
508  !
509  ! -- Deallocate arrays if package was active
510  if (this%inunit > 0) then
511  !
512  ! -- Character array
513  deallocate (this%paknames)
514  !
515  ! -- Budget object
516  call this%budget%budget_da()
517  deallocate (this%budget)
518  !
519  ! -- Budobj
520  call this%budobj%budgetobject_da()
521  deallocate (this%budobj)
522  nullify (this%budobj)
523  !
524  ! -- Output table object
525  if (associated(this%outputtab)) then
526  call this%outputtab%table_da()
527  deallocate (this%outputtab)
528  nullify (this%outputtab)
529  end if
530  end if
531  !
532  ! -- Scalars
533  this%fmi1 => null()
534  this%fmi1 => null()
535  this%mvrbudobj => null()
536  call mem_deallocate(this%maxpackages)
537  call mem_deallocate(this%ibudgetout)
538  call mem_deallocate(this%ibudcsv)
539  !
540  ! -- Deallocate scalars in NumericalPackageType
541  call this%NumericalPackageType%da()

◆ mvt_df()

subroutine tspmvtmodule::mvt_df ( class(tspmvttype this,
class(disbasetype), intent(in), pointer  dis 
)
private

Definition at line 129 of file tsp-mvt.f90.

130  ! -- dummy
131  class(TspMvtType) :: this
132  class(DisBaseType), pointer, intent(in) :: dis
133  ! -- formats
134  character(len=*), parameter :: fmtmvt = &
135  "(1x,/1x,'MVT -- MOVER TRANSPORT PACKAGE, VERSION 1, 4/15/2020', &
136  &' INPUT READ FROM UNIT ', i0, //)"
137  !
138  ! -- Set pointer to dis
139  this%dis => dis
140  !
141  ! -- Print a message identifying the MVT package.
142  write (this%iout, fmtmvt) this%inunit
143  !
144  ! -- Initialize block parser
145  call this%parser%Initialize(this%inunit, this%iout)
146  !
147  ! -- Initialize the budget table writer
148  call budget_cr(this%budget, this%memoryPath)
149  !
150  ! -- Read mvt options
151  call this%read_options()
Here is the call graph for this function:

◆ mvt_fc()

subroutine tspmvtmodule::mvt_fc ( class(tspmvttype this,
real(dp), dimension(:), intent(in), target, contiguous  cnew1,
real(dp), dimension(:), intent(in), target, contiguous  cnew2 
)

The mvt package adds the mass flow rate to the provider qmfrommvr array. The advanced packages know enough to subtract any mass that is leaving, so the mvt just adds mass coming in from elsewhere. Because the movers change by stress period, their solute effects must be added to the right- hand side of the transport matrix equations.

Definition at line 211 of file tsp-mvt.f90.

212  ! -- dummy
213  class(TspMvtType) :: this
214  real(DP), intent(in), dimension(:), contiguous, target :: cnew1
215  real(DP), intent(in), dimension(:), contiguous, target :: cnew2
216  ! -- local
217  integer(I4B) :: i, n
218  integer(I4B) :: id1, id2, nlist
219  integer(I4B) :: ipr, irc
220  integer(I4B) :: igwtnode
221  integer(I4B) :: nbudterm
222  real(DP) :: q, cp
223  real(DP), dimension(:), pointer :: concpak
224  real(DP), dimension(:), contiguous, pointer :: cnew
225  type(TspFmiType), pointer :: fmi_pr !< pointer to provider model fmi package
226  type(TspFmiType), pointer :: fmi_rc !< pointer to receiver model fmi package
227  !
228  ! -- Add mover QC terms to the receiver packages
229  nbudterm = this%mvrbudobj%nbudterm
230  do i = 1, nbudterm
231  nlist = this%mvrbudobj%budterm(i)%nlist
232  if (nlist > 0) then
233  !
234  ! -- Set pointers to the fmi packages for the provider and the receiver
235  call this%set_fmi_pr_rc(i, fmi_pr, fmi_rc)
236  !
237  ! -- Set a pointer to the GWT model concentration (or temperature)
238  ! associated with the provider
239  cnew => cnew1
240  if (associated(fmi_pr, this%fmi2)) then
241  cnew => cnew2
242  end if
243  !
244  !-- Get the package index for the provider
245  call fmi_pr%get_package_index(this%mvrbudobj%budterm(i)%text2id1, ipr)
246  !
247  ! -- Get the package index for the receiver
248  call fmi_rc%get_package_index(this%mvrbudobj%budterm(i)%text2id2, irc)
249  !
250  ! -- If provider is an advanced package, then set a pointer to its simulated concentration
251  if (fmi_pr%iatp(ipr) /= 0) then
252  concpak => fmi_pr%datp(ipr)%concpack
253  end if
254  !
255  ! -- Process flows for each entry in the list and add mass to receivers
256  do n = 1, nlist
257  !
258  ! -- lak/sfr/maw/uzf id1 (provider) and id2 (receiver)
259  id1 = this%mvrbudobj%budterm(i)%id1(n)
260  id2 = this%mvrbudobj%budterm(i)%id2(n)
261  !
262  ! -- Obtain mover flow rate from the mover flow budget object
263  q = this%mvrbudobj%budterm(i)%flow(n)
264  !
265  ! -- Assign concentration of the provider
266  cp = dzero
267  if (fmi_pr%iatp(ipr) /= 0) then
268  !
269  ! -- Provider package is being represented by an APT (SFT, LKT, MWT, UZT,
270  ! SFE, LKE, MWE, UZE) so set the dependent variable (concentration or
271  ! temperature) to the simulated dependent variable of the APT.
272  cp = concpak(id1)
273  else
274  !
275  ! -- Provider is a regular stress package (WEL, DRN, RIV, etc.) or the
276  ! provider is an advanced stress package but is not represented with
277  ! SFT, LKT, MWT, or UZT, so use the GWT cell concentration
278  igwtnode = fmi_pr%gwfpackages(ipr)%nodelist(id1)
279  cp = cnew(igwtnode)
280  !
281  end if
282  !
283  ! -- Add the mover rate times the provider concentration into the receiver
284  ! make sure these are accumulated since multiple providers can move
285  ! water into the same receiver
286  if (fmi_rc%iatp(irc) /= 0) then
287  fmi_rc%datp(irc)%qmfrommvr(id2) = fmi_rc%datp(irc)%qmfrommvr(id2) - &
288  q * cp * this%eqnsclfac
289  end if
290  end do
291  end if
292  end do

◆ mvt_fill_budobj()

subroutine tspmvtmodule::mvt_fill_budobj ( class(tspmvttype this,
real(dp), dimension(:), intent(in), target, contiguous  cnew1,
real(dp), dimension(:), intent(in), target, contiguous  cnew2 
)

Definition at line 697 of file tsp-mvt.f90.

698  ! -- dummy
699  class(TspMvtType) :: this
700  real(DP), intent(in), dimension(:), contiguous, target :: cnew1
701  real(DP), intent(in), dimension(:), contiguous, target :: cnew2
702  ! -- local
703  type(TspFmiType), pointer :: fmi_pr
704  type(TspFmiType), pointer :: fmi_rc
705  real(DP), dimension(:), contiguous, pointer :: cnew
706  integer(I4B) :: nbudterm
707  integer(I4B) :: nlist
708  integer(I4B) :: ipr
709  integer(I4B) :: irc
710  integer(I4B) :: i
711  integer(I4B) :: j
712  integer(I4B) :: n1, n2
713  integer(I4B) :: igwtnode
714  real(DP) :: cp
715  real(DP) :: q
716  real(DP) :: rate
717  !
718  ! -- Go through the water mover budget terms and set up the transport
719  ! mover budget terms
720  nbudterm = this%mvrbudobj%nbudterm
721  do i = 1, nbudterm
722  nlist = this%mvrbudobj%budterm(i)%nlist
723  call this%set_fmi_pr_rc(i, fmi_pr, fmi_rc)
724  cnew => cnew1
725  if (associated(fmi_pr, this%fmi2)) then
726  cnew => cnew2
727  end if
728  call fmi_pr%get_package_index(this%mvrbudobj%budterm(i)%text2id1, ipr)
729  call fmi_rc%get_package_index(this%mvrbudobj%budterm(i)%text2id2, irc)
730  call this%budobj%budterm(i)%reset(nlist)
731  do j = 1, nlist
732  n1 = this%mvrbudobj%budterm(i)%id1(j)
733  n2 = this%mvrbudobj%budterm(i)%id2(j)
734  q = this%mvrbudobj%budterm(i)%flow(j)
735  cp = dzero
736  if (fmi_pr%iatp(ipr) /= 0) then
737  cp = fmi_pr%datp(ipr)%concpack(n1)
738  else
739  ! -- Must be a regular stress package
740  igwtnode = fmi_pr%gwfpackages(ipr)%nodelist(n1)
741  !cdl todo: need to set cnew to model 1; right now it is coming in as argument
742  cp = cnew(igwtnode)
743  end if
744  !
745  ! -- Calculate solute mover rate
746  rate = dzero
747  if (fmi_rc%iatp(irc) /= 0) then
748  rate = -q * cp * this%eqnsclfac
749  end if
750  !
751  ! -- Add the rate to the budterm
752  call this%budobj%budterm(i)%update_term(n1, n2, rate)
753  end do
754  end do
755  !
756  ! --Terms are filled, now accumulate them for this time step
757  call this%budobj%accumulate_terms()

◆ mvt_ot_bdsummary()

subroutine tspmvtmodule::mvt_ot_bdsummary ( class(tspmvttype this,
integer(i4b), intent(in)  ibudfl 
)
private

Definition at line 439 of file tsp-mvt.f90.

440  ! -- modules
441  use tdismodule, only: kstp, kper, delt, totim
442  ! -- dummy
443  class(TspMvtType) :: this
444  integer(I4B), intent(in) :: ibudfl
445  ! -- locals
446  integer(I4B) :: i, j, n
447  real(DP), allocatable, dimension(:) :: ratin, ratout
448  !
449  ! -- Allocate and initialize ratin/ratout
450  allocate (ratin(this%maxpackages), ratout(this%maxpackages))
451  do j = 1, this%maxpackages
452  ratin(j) = dzero
453  ratout(j) = dzero
454  end do
455  !
456  ! -- Accumulate the rates
457  do i = 1, this%maxpackages
458  do j = 1, this%budobj%nbudterm
459  do n = 1, this%budobj%budterm(j)%nlist
460  !
461  ! -- Provider is inflow to mover
462  if (this%paknames(i) == this%budobj%budterm(j)%text2id1) then
463  ratin(i) = ratin(i) + this%budobj%budterm(j)%flow(n)
464  end if
465  !
466  ! -- Receiver is outflow from mover
467  if (this%paknames(i) == this%budobj%budterm(j)%text2id2) then
468  ratout(i) = ratout(i) + this%budobj%budterm(j)%flow(n)
469  end if
470  end do
471  end do
472  end do
473  !
474  ! -- Send rates to budget object
475  call this%budget%reset()
476  do j = 1, this%maxpackages
477  call this%budget%addentry(ratin(j), ratout(j), delt, this%paknames(j))
478  end do
479  !
480  ! -- Write the budget
481  call this%budget%finalize_step(delt)
482  if (ibudfl /= 0) then
483  call this%budget%budget_ot(kstp, kper, this%iout)
484  end if
485  !
486  ! -- Write budget csv
487  call this%budget%writecsv(totim)
488  !
489  ! -- Deallocate
490  deallocate (ratin, ratout)
491  !
492  ! -- Output mvr budget
493  ! Not using budobj write_table here because it would result
494  ! in a table that has one entry. A custom table looks
495  ! better here with a row for each package.
496  !call this%budobj%write_budtable(kstp, kper, this%iout)
real(dp), pointer, public totim
time relative to start of simulation
Definition: tdis.f90:32
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
real(dp), pointer, public delt
length of the current time step
Definition: tdis.f90:29

◆ mvt_ot_printflow()

subroutine tspmvtmodule::mvt_ot_printflow ( class(tspmvttype this,
integer(i4b), intent(in)  icbcfl,
integer(i4b), intent(in)  ibudfl 
)

Definition at line 425 of file tsp-mvt.f90.

426  ! -- dummy
427  class(TspMvtType) :: this
428  integer(I4B), intent(in) :: icbcfl
429  integer(I4B), intent(in) :: ibudfl
430  !
431  ! -- Print the mover flow table
432  if (ibudfl /= 0 .and. this%iprflow /= 0) then
433  call this%mvt_print_outputtab()
434  end if

◆ mvt_ot_saveflow()

subroutine tspmvtmodule::mvt_ot_saveflow ( class(tspmvttype this,
integer(i4b), intent(in)  icbcfl,
integer(i4b), intent(in)  ibudfl 
)
private

Definition at line 401 of file tsp-mvt.f90.

402  ! -- modules
403  use tdismodule, only: kstp, kper, delt, pertim, totim
404  ! -- dummy
405  class(TspMvttype) :: this
406  integer(I4B), intent(in) :: icbcfl
407  integer(I4B), intent(in) :: ibudfl
408  ! -- locals
409  integer(I4B) :: ibinun
410  !
411  ! -- Save the mover flows from the budobj to a mover binary file
412  ibinun = 0
413  if (this%ibudgetout /= 0) then
414  ibinun = this%ibudgetout
415  end if
416  if (icbcfl == 0) ibinun = 0
417  if (ibinun > 0) then
418  call this%budobj%save_flows(this%dis, ibinun, kstp, kper, delt, &
419  pertim, totim, this%iout)
420  end if
real(dp), pointer, public pertim
time relative to start of stress period
Definition: tdis.f90:30

◆ mvt_print_outputtab()

subroutine tspmvtmodule::mvt_print_outputtab ( class(tspmvttype), intent(inout)  this)
private

Definition at line 853 of file tsp-mvt.f90.

854  ! -- module
855  use tdismodule, only: kstp, kper
856  ! -- dummy
857  class(TspMvttype), intent(inout) :: this
858  ! -- local
859  character(len=LINELENGTH) :: title
860  character(len=LENMODELNAME + LENPACKAGENAME + 1) :: cloc1, cloc2
861  integer(I4B) :: i
862  integer(I4B) :: n
863  integer(I4B) :: inum
864  integer(I4B) :: ntabrows
865  integer(I4B) :: nlist
866  !
867  ! -- Determine number of table rows
868  ntabrows = 0
869  do i = 1, this%budobj%nbudterm
870  nlist = this%budobj%budterm(i)%nlist
871  ntabrows = ntabrows + nlist
872  end do
873  !
874  ! -- Set table kstp and kper
875  call this%outputtab%set_kstpkper(kstp, kper)
876  !
877  ! -- Add terms and print the table
878  title = 'TRANSPORT MOVER PACKAGE ('//trim(this%packName)// &
879  ') FLOW RATES'
880  call this%outputtab%set_title(title)
881  call this%outputtab%set_maxbound(ntabrows)
882  !
883  ! -- Process each table row
884  inum = 1
885  do i = 1, this%budobj%nbudterm
886  nlist = this%budobj%budterm(i)%nlist
887  do n = 1, nlist
888  cloc1 = trim(adjustl(this%budobj%budterm(i)%text1id1))//' '// &
889  trim(adjustl(this%budobj%budterm(i)%text2id1))
890  cloc2 = trim(adjustl(this%budobj%budterm(i)%text1id2))//' '// &
891  trim(adjustl(this%budobj%budterm(i)%text2id2))
892  call this%outputtab%add_term(inum)
893  call this%outputtab%add_term(cloc1)
894  call this%outputtab%add_term(this%budobj%budterm(i)%id1(n))
895  call this%outputtab%add_term(-this%mvrbudobj%budterm(i)%flow(n))
896  call this%outputtab%add_term(this%budobj%budterm(i)%flow(n))
897  call this%outputtab%add_term(cloc2)
898  call this%outputtab%add_term(this%budobj%budterm(i)%id2(n))
899  inum = inum + 1
900  end do
901  end do

◆ mvt_rp()

subroutine tspmvtmodule::mvt_rp ( class(tspmvttype this)
private

Definition at line 178 of file tsp-mvt.f90.

179  ! -- modules
180  use tdismodule, only: kper, kstp
181  ! -- dummy
182  class(TspMvtType) :: this
183  !
184  ! -- At this point, the mvrbudobj is available to set up the mvt budobj
185  if (kper * kstp == 1) then
186  !
187  ! -- If mvt is for a single model then point to fmi1
188  !cdl todo: this needs to be called from GwtGwtExg somehow for the 2 model case
189  if (associated(this%fmi1, this%fmi2)) then
190  call this%set_pointer_mvrbudobj(this%fmi1%mvrbudobj)
191  end if
192  !
193  ! -- Set up the mvt budobject
194  call this%mvt_scan_mvrbudobj()
195  call this%mvt_setup_budobj()
196  !
197  ! -- Define the budget object to be the size of maxpackages
198  call this%budget%budget_df(this%maxpackages, 'TRANSPORT MOVER', bddim='M')
199  call this%budget%set_ibudcsv(this%ibudcsv)
200  end if

◆ mvt_scan_mvrbudobj()

subroutine tspmvtmodule::mvt_scan_mvrbudobj ( class(tspmvttype this)
private

Scan through the gwf water mover budget object and determine the maximum number of packages and unique package names

Definition at line 765 of file tsp-mvt.f90.

766  class(TspMvtType) :: this
767  integer(I4B) :: nbudterm
768  integer(I4B) :: maxpackages
769  integer(I4B) :: i, j
770  integer(I4B) :: ipos
771  logical :: found
772  !
773  ! -- Calculate maxpackages, which is the the square of nbudterm
774  nbudterm = this%mvrbudobj%nbudterm
775  do i = 1, nbudterm
776  if (i * i == nbudterm) then
777  maxpackages = i
778  exit
779  end if
780  end do
781  this%maxpackages = maxpackages
782  !
783  ! -- Allocate paknames
784  allocate (this%paknames(this%maxpackages))
785  do i = 1, this%maxpackages
786  this%paknames(i) = ''
787  end do
788  !
789  ! -- Scan through mvrbudobj and create unique paknames
790  ipos = 1
791  do i = 1, nbudterm
792  found = .false.
793  do j = 1, ipos
794  if (this%mvrbudobj%budterm(i)%text2id1 == this%paknames(j)) then
795  found = .true.
796  exit
797  end if
798  end do
799  if (.not. found) then
800  this%paknames(ipos) = this%mvrbudobj%budterm(i)%text2id1
801  ipos = ipos + 1
802  end if
803  end do

◆ mvt_setup_budobj()

subroutine tspmvtmodule::mvt_setup_budobj ( class(tspmvttype this)

Definition at line 649 of file tsp-mvt.f90.

650  ! -- modules
651  use constantsmodule, only: lenbudtxt
652  ! -- dummy
653  class(TspMvtType) :: this
654  ! -- local
655  integer(I4B) :: nbudterm
656  integer(I4B) :: ncv
657  integer(I4B) :: maxlist
658  integer(I4B) :: i
659  integer(I4B) :: naux
660  character(len=LENMODELNAME) :: modelname1, modelname2
661  character(len=LENPACKAGENAME) :: packagename1, packagename2
662  character(len=LENBUDTXT) :: text
663  !
664  ! -- Assign terms to set up the mover budget object
665  nbudterm = this%mvrbudobj%nbudterm
666  ncv = 0
667  naux = 0
668  if (this%depvartype == 'CONCENTRATION') then
669  text = ' MVT-FLOW'
670  else
671  text = ' MVE-FLOW'
672  end if
673  !
674  ! -- Set up budobj
675  call this%budobj%budgetobject_df(ncv, nbudterm, 0, 0, bddim_opt='M')
676  !
677  ! -- Go through the water mover budget terms and set up the transport
678  ! mover budget terms
679  do i = 1, nbudterm
680  modelname1 = this%mvrbudobj%budterm(i)%text1id1
681  packagename1 = this%mvrbudobj%budterm(i)%text2id1
682  modelname2 = this%mvrbudobj%budterm(i)%text1id2
683  packagename2 = this%mvrbudobj%budterm(i)%text2id2
684  maxlist = this%mvrbudobj%budterm(i)%maxlist
685  call this%budobj%budterm(i)%initialize(text, &
686  modelname1, &
687  packagename1, &
688  modelname2, &
689  packagename2, &
690  maxlist, .false., .false., &
691  naux)
692  end do
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:37

◆ mvt_setup_outputtab()

subroutine tspmvtmodule::mvt_setup_outputtab ( class(tspmvttype), intent(inout)  this)
private

Definition at line 808 of file tsp-mvt.f90.

809  ! -- dummy
810  class(TspMvtType), intent(inout) :: this
811  ! -- local
812  character(len=LINELENGTH) :: title
813  character(len=LINELENGTH) :: text
814  integer(I4B) :: ntabcol
815  integer(I4B) :: maxrow
816  integer(I4B) :: ilen
817  !
818  ! -- Allocate and initialize the output table
819  if (this%iprflow /= 0) then
820  !
821  ! -- Dimension table
822  ntabcol = 7
823  maxrow = 0
824  !
825  ! -- Initialize the output table object
826  title = 'TRANSPORT MOVER PACKAGE ('//trim(this%packName)// &
827  ') FLOW RATES'
828  call table_cr(this%outputtab, this%packName, title)
829  call this%outputtab%table_df(maxrow, ntabcol, this%iout, &
830  transient=.true.)
831  text = 'NUMBER'
832  call this%outputtab%initialize_column(text, 10, alignment=tabcenter)
833  text = 'PROVIDER LOCATION'
834  ilen = lenmodelname + lenpackagename + 1
835  call this%outputtab%initialize_column(text, ilen)
836  text = 'PROVIDER ID'
837  call this%outputtab%initialize_column(text, 10)
838  text = 'PROVIDER FLOW RATE'
839  call this%outputtab%initialize_column(text, 10)
840  text = 'PROVIDER TRANSPORT RATE'
841  call this%outputtab%initialize_column(text, 10)
842  text = 'RECEIVER LOCATION'
843  ilen = lenmodelname + lenpackagename + 1
844  call this%outputtab%initialize_column(text, ilen)
845  text = 'RECEIVER ID'
846  call this%outputtab%initialize_column(text, 10)
847  !
848  end if
Here is the call graph for this function:

◆ read_options()

subroutine tspmvtmodule::read_options ( class(tspmvttype this)

Definition at line 570 of file tsp-mvt.f90.

571  ! -- modules
572  use openspecmodule, only: access, form
574  ! -- dummy
575  class(TspMvtType) :: this
576  ! -- local
577  character(len=LINELENGTH) :: errmsg, keyword
578  character(len=MAXCHARLEN) :: fname
579  integer(I4B) :: ierr
580  logical :: isfound, endOfBlock
581  ! -- formats
582  character(len=*), parameter :: fmtflow = &
583  "(4x, a, 1x, a, 1x, ' WILL BE SAVED TO FILE: ', a, &
584  &/4x, 'OPENED ON UNIT: ', I0)"
585  character(len=*), parameter :: fmtflow2 = &
586  &"(4x, 'FLOWS WILL BE SAVED TO BUDGET FILE')"
587  !
588  ! -- Get options block
589  call this%parser%GetBlock('OPTIONS', isfound, ierr, blockrequired=.false., &
590  supportopenclose=.true.)
591  !
592  ! -- Parse options block if detected
593  if (isfound) then
594  write (this%iout, '(1x,a)') 'PROCESSING MVT OPTIONS'
595  do
596  call this%parser%GetNextLine(endofblock)
597  if (endofblock) exit
598  call this%parser%GetStringCaps(keyword)
599  select case (keyword)
600  case ('SAVE_FLOWS')
601  this%ipakcb = -1
602  write (this%iout, fmtflow2)
603  case ('PRINT_INPUT')
604  this%iprpak = 1
605  write (this%iout, '(4x,a)') 'MVT INPUT WILL BE PRINTED.'
606  case ('PRINT_FLOWS')
607  this%iprflow = 1
608  write (this%iout, '(4x,a)') &
609  'MVT FLOWS WILL BE PRINTED TO LISTING FILE.'
610  case ('BUDGET')
611  call this%parser%GetStringCaps(keyword)
612  if (keyword == 'FILEOUT') then
613  call this%parser%GetString(fname)
614  this%ibudgetout = getunit()
615  call openfile(this%ibudgetout, this%iout, fname, 'DATA(BINARY)', &
616  form, access, 'REPLACE')
617  write (this%iout, fmtflow) 'MVT', 'BUDGET', trim(adjustl(fname)), &
618  this%ibudgetout
619  else
620  call store_error('Optional BUDGET keyword must &
621  &be followed by FILEOUT')
622  end if
623  case ('BUDGETCSV')
624  call this%parser%GetStringCaps(keyword)
625  if (keyword == 'FILEOUT') then
626  call this%parser%GetString(fname)
627  this%ibudcsv = getunit()
628  call openfile(this%ibudcsv, this%iout, fname, 'CSV', &
629  filstat_opt='REPLACE')
630  write (this%iout, fmtflow) 'MVT', 'BUDGET CSV', &
631  trim(adjustl(fname)), this%ibudcsv
632  else
633  call store_error('Optional BUDGETCSV keyword must be followed by &
634  &FILEOUT')
635  end if
636  case default
637  write (errmsg, '(a,a)') 'Unknown MVT option: ', &
638  trim(keyword)
639  call store_error(errmsg)
640  call this%parser%StoreErrorUnit()
641  end select
642  end do
643  write (this%iout, '(1x,a)') 'END OF MVT OPTIONS'
644  end if
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
Here is the call graph for this function:

◆ set_fmi_pr_rc()

subroutine tspmvtmodule::set_fmi_pr_rc ( class(tspmvttype this,
integer(i4b), intent(in)  ibudterm,
type(tspfmitype), pointer  fmi_pr,
type(tspfmitype), pointer  fmi_rc 
)
private

The fmi_pr and fmi_rc arguments are pointers to the provider and receiver FMI Packages. If this MVT Package is owned by a single GWT model, then these pointers are both set to the FMI Package of this GWT model's FMI package. If this MVT package is owned by a GWTGWT exchange, then the fmi_pr and fmi_rc pointers may be assigned to FMI Packages in different models.

Definition at line 304 of file tsp-mvt.f90.

305  ! -- dummy
306  class(TspMvtType) :: this
307  integer(I4B), intent(in) :: ibudterm
308  type(TspFmiType), pointer :: fmi_pr
309  type(TspFmiType), pointer :: fmi_rc
310  !
311  fmi_pr => null()
312  fmi_rc => null()
313  if (this%gwfmodelname1 == '' .and. this%gwfmodelname2 == '') then
314  fmi_pr => this%fmi1
315  fmi_rc => this%fmi1
316  else
317  ! -- Modelname for provider is this%mvrbudobj%budterm(i)%text1id1
318  if (this%mvrbudobj%budterm(ibudterm)%text1id1 == this%gwfmodelname1) then
319  ! -- Model 1 is the provider
320  fmi_pr => this%fmi1
321  else if (this%mvrbudobj%budterm(ibudterm)%text1id1 == &
322  this%gwfmodelname2) then
323  ! -- Model 2 is the provider
324  fmi_pr => this%fmi2
325  else
326  ! -- Must be an error
327  !cdl todo: programming error
328  print *, this%mvrbudobj%budterm(ibudterm)%text1id1
329  print *, this%gwfmodelname1
330  print *, this%gwfmodelname2
331  stop "error in set_fmi_pr_rc"
332  end if
333  !
334  ! -- Modelname for receiver is this%mvrbudobj%budterm(i)%text1id2
335  if (this%mvrbudobj%budterm(ibudterm)%text1id2 == this%gwfmodelname1) then
336  ! -- Model 1 is the receiver
337  fmi_rc => this%fmi1
338  else if (this%mvrbudobj%budterm(ibudterm)%text1id2 == &
339  this%gwfmodelname2) then
340  ! -- Model 2 is the receiver
341  fmi_rc => this%fmi2
342  else
343  ! -- Must be an error
344  !cdl todo: programming error
345  print *, this%mvrbudobj%budterm(ibudterm)%text1id2
346  print *, this%gwfmodelname1
347  print *, this%gwfmodelname2
348  stop "error in set_fmi_pr_rc"
349  end if
350  end if
351  !
352  if (.not. associated(fmi_pr)) then
353  print *, 'Could not find FMI Package...'
354  stop "error in set_fmi_pr_rc"
355  end if
356  if (.not. associated(fmi_rc)) then
357  print *, 'Could not find FMI Package...'
358  stop "error in set_fmi_pr_rc"
359  end if

◆ set_pointer_mvrbudobj()

subroutine tspmvtmodule::set_pointer_mvrbudobj ( class(tspmvttype this,
type(budgetobjecttype), intent(in), target  mvrbudobj 
)
private

Store a pointer to mvrbudobj, which contains the simulated water mover flows from either a gwf model MVR package or from a gwf-gwf exchange MVR package.

Definition at line 160 of file tsp-mvt.f90.

161  class(TspMvtType) :: this
162  type(BudgetObjectType), intent(in), target :: mvrbudobj
163  this%mvrbudobj => mvrbudobj