MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
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 584 of file tsp-mvt.f90.

585  ! -- modules
587  ! -- dummy
588  class(TspMvtType) :: this
589  !
590  ! -- Allocate scalars in NumericalPackageType
591  call this%NumericalPackageType%allocate_scalars()
592  !
593  ! -- Allocate
594  call mem_allocate(this%maxpackages, 'MAXPACKAGES', this%memoryPath)
595  call mem_allocate(this%ibudgetout, 'IBUDGETOUT', this%memoryPath)
596  call mem_allocate(this%ibudcsv, 'IBUDCSV', this%memoryPath)
597  !
598  ! -- Initialize
599  this%maxpackages = 0
600  this%ibudgetout = 0
601  this%ibudcsv = 0
602  !
603  ! -- Return
604  return

◆ mvt_ar()

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

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

175  ! -- dummy
176  class(TspMvtType) :: this
177  !
178  ! -- Setup the output table
179  call this%mvt_setup_outputtab()
180  !
181  ! -- Return
182  return

◆ 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 410 of file tsp-mvt.f90.

411  ! -- dummy
412  class(TspMvtType) :: this
413  real(DP), dimension(:), contiguous, intent(in) :: cnew1
414  real(DP), dimension(:), contiguous, intent(in) :: cnew2
415  !
416  ! -- Fill the budget object
417  call this%mvt_fill_budobj(cnew1, cnew2)
418  !
419  ! -- Return
420  return

◆ 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 382 of file tsp-mvt.f90.

383  ! -- dummy
384  class(TspMvtType) :: this
385  integer(I4B), intent(in) :: kiter
386  integer(I4B), intent(in) :: iend
387  integer(I4B), intent(in) :: icnvgmod
388  character(len=LENPAKLOC), intent(inout) :: cpak
389  real(DP), intent(inout) :: dpak
390  ! -- formats
391  character(len=*), parameter :: fmtmvrcnvg = &
392  "(/,1x,'MOVER PACKAGE REQUIRES AT LEAST TWO OUTER ITERATIONS. CONVERGE &
393  &FLAG HAS BEEN RESET TO FALSE.')"
394  !
395  ! -- If there are active movers, then at least 2 outers required
396  if (associated(this%mvrbudobj)) then
397  if (icnvgmod == 1 .and. kiter == 1) then
398  dpak = dnodata
399  cpak = trim(this%packName)
400  write (this%iout, fmtmvrcnvg)
401  end if
402  end if
403  !
404  ! -- Return
405  return

◆ 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
125  !
126  ! -- Return
127  return
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 536 of file tsp-mvt.f90.

537  ! -- modules
539  ! -- dummy
540  class(TspMvtType) :: this
541  !
542  ! -- Deallocate arrays if package was active
543  if (this%inunit > 0) then
544  !
545  ! -- Character array
546  deallocate (this%paknames)
547  !
548  ! -- Budget object
549  call this%budget%budget_da()
550  deallocate (this%budget)
551  !
552  ! -- Budobj
553  call this%budobj%budgetobject_da()
554  deallocate (this%budobj)
555  nullify (this%budobj)
556  !
557  ! -- Output table object
558  if (associated(this%outputtab)) then
559  call this%outputtab%table_da()
560  deallocate (this%outputtab)
561  nullify (this%outputtab)
562  end if
563  end if
564  !
565  ! -- Scalars
566  this%fmi1 => null()
567  this%fmi1 => null()
568  this%mvrbudobj => null()
569  call mem_deallocate(this%maxpackages)
570  call mem_deallocate(this%ibudgetout)
571  call mem_deallocate(this%ibudcsv)
572  !
573  ! -- Deallocate scalars in NumericalPackageType
574  call this%NumericalPackageType%da()
575  !
576  ! -- Return
577  return

◆ mvt_df()

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

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

133  ! -- dummy
134  class(TspMvtType) :: this
135  class(DisBaseType), pointer, intent(in) :: dis
136  ! -- formats
137  character(len=*), parameter :: fmtmvt = &
138  "(1x,/1x,'MVT -- MOVER TRANSPORT PACKAGE, VERSION 1, 4/15/2020', &
139  &' INPUT READ FROM UNIT ', i0, //)"
140  !
141  ! -- Set pointer to dis
142  this%dis => dis
143  !
144  ! -- Print a message identifying the MVT package.
145  write (this%iout, fmtmvt) this%inunit
146  !
147  ! -- Initialize block parser
148  call this%parser%Initialize(this%inunit, this%iout)
149  !
150  ! -- Initialize the budget table writer
151  call budget_cr(this%budget, this%memoryPath)
152  !
153  ! -- Read mvt options
154  call this%read_options()
155  !
156  ! -- Return
157  return
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 223 of file tsp-mvt.f90.

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

◆ 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 742 of file tsp-mvt.f90.

743  ! -- dummy
744  class(TspMvtType) :: this
745  real(DP), intent(in), dimension(:), contiguous, target :: cnew1
746  real(DP), intent(in), dimension(:), contiguous, target :: cnew2
747  ! -- local
748  type(TspFmiType), pointer :: fmi_pr
749  type(TspFmiType), pointer :: fmi_rc
750  real(DP), dimension(:), contiguous, pointer :: cnew
751  integer(I4B) :: nbudterm
752  integer(I4B) :: nlist
753  integer(I4B) :: ipr
754  integer(I4B) :: irc
755  integer(I4B) :: i
756  integer(I4B) :: j
757  integer(I4B) :: n1, n2
758  integer(I4B) :: igwtnode
759  real(DP) :: cp
760  real(DP) :: q
761  real(DP) :: rate
762  !
763  ! -- Go through the water mover budget terms and set up the transport
764  ! mover budget terms
765  nbudterm = this%mvrbudobj%nbudterm
766  do i = 1, nbudterm
767  nlist = this%mvrbudobj%budterm(i)%nlist
768  call this%set_fmi_pr_rc(i, fmi_pr, fmi_rc)
769  cnew => cnew1
770  if (associated(fmi_pr, this%fmi2)) then
771  cnew => cnew2
772  end if
773  call fmi_pr%get_package_index(this%mvrbudobj%budterm(i)%text2id1, ipr)
774  call fmi_rc%get_package_index(this%mvrbudobj%budterm(i)%text2id2, irc)
775  call this%budobj%budterm(i)%reset(nlist)
776  do j = 1, nlist
777  n1 = this%mvrbudobj%budterm(i)%id1(j)
778  n2 = this%mvrbudobj%budterm(i)%id2(j)
779  q = this%mvrbudobj%budterm(i)%flow(j)
780  cp = dzero
781  if (fmi_pr%iatp(ipr) /= 0) then
782  cp = fmi_pr%datp(ipr)%concpack(n1)
783  else
784  ! -- Must be a regular stress package
785  igwtnode = fmi_pr%gwfpackages(ipr)%nodelist(n1)
786  !cdl todo: need to set cnew to model 1; right now it is coming in as argument
787  cp = cnew(igwtnode)
788  end if
789  !
790  ! -- Calculate solute mover rate
791  rate = dzero
792  if (fmi_rc%iatp(irc) /= 0) then
793  rate = -q * cp * this%eqnsclfac
794  end if
795  !
796  ! -- Add the rate to the budterm
797  call this%budobj%budterm(i)%update_term(n1, n2, rate)
798  end do
799  end do
800  !
801  ! --Terms are filled, now accumulate them for this time step
802  call this%budobj%accumulate_terms()
803  !
804  ! -- Return
805  return

◆ mvt_ot_bdsummary()

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

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

470  ! -- modules
471  use tdismodule, only: kstp, kper, delt, totim
472  ! -- dummy
473  class(TspMvtType) :: this
474  integer(I4B), intent(in) :: ibudfl
475  ! -- locals
476  integer(I4B) :: i, j, n
477  real(DP), allocatable, dimension(:) :: ratin, ratout
478  !
479  ! -- Allocate and initialize ratin/ratout
480  allocate (ratin(this%maxpackages), ratout(this%maxpackages))
481  do j = 1, this%maxpackages
482  ratin(j) = dzero
483  ratout(j) = dzero
484  end do
485  !
486  ! -- Accumulate the rates
487  do i = 1, this%maxpackages
488  do j = 1, this%budobj%nbudterm
489  do n = 1, this%budobj%budterm(j)%nlist
490  !
491  ! -- Provider is inflow to mover
492  if (this%paknames(i) == this%budobj%budterm(j)%text2id1) then
493  ratin(i) = ratin(i) + this%budobj%budterm(j)%flow(n)
494  end if
495  !
496  ! -- Receiver is outflow from mover
497  if (this%paknames(i) == this%budobj%budterm(j)%text2id2) then
498  ratout(i) = ratout(i) + this%budobj%budterm(j)%flow(n)
499  end if
500  end do
501  end do
502  end do
503  !
504  ! -- Send rates to budget object
505  call this%budget%reset()
506  do j = 1, this%maxpackages
507  call this%budget%addentry(ratin(j), ratout(j), delt, this%paknames(j))
508  end do
509  !
510  ! -- Write the budget
511  call this%budget%finalize_step(delt)
512  if (ibudfl /= 0) then
513  call this%budget%budget_ot(kstp, kper, this%iout)
514  end if
515  !
516  ! -- Write budget csv
517  call this%budget%writecsv(totim)
518  !
519  ! -- Deallocate
520  deallocate (ratin, ratout)
521  !
522  ! -- Output mvr budget
523  ! Not using budobj write_table here because it would result
524  ! in a table that has one entry. A custom table looks
525  ! better here with a row for each package.
526  !call this%budobj%write_budtable(kstp, kper, this%iout)
527  !
528  ! -- Return
529  return
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 452 of file tsp-mvt.f90.

453  ! -- dummy
454  class(TspMvtType) :: this
455  integer(I4B), intent(in) :: icbcfl
456  integer(I4B), intent(in) :: ibudfl
457  !
458  ! -- Print the mover flow table
459  if (ibudfl /= 0 .and. this%iprflow /= 0) then
460  call this%mvt_print_outputtab()
461  end if
462  !
463  ! -- Return
464  return

◆ 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 425 of file tsp-mvt.f90.

426  ! -- modules
427  use tdismodule, only: kstp, kper, delt, pertim, totim
428  ! -- dummy
429  class(TspMvttype) :: this
430  integer(I4B), intent(in) :: icbcfl
431  integer(I4B), intent(in) :: ibudfl
432  ! -- locals
433  integer(I4B) :: ibinun
434  !
435  ! -- Save the mover flows from the budobj to a mover binary file
436  ibinun = 0
437  if (this%ibudgetout /= 0) then
438  ibinun = this%ibudgetout
439  end if
440  if (icbcfl == 0) ibinun = 0
441  if (ibinun > 0) then
442  call this%budobj%save_flows(this%dis, ibinun, kstp, kper, delt, &
443  pertim, totim, this%iout)
444  end if
445  !
446  ! -- Return
447  return
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 907 of file tsp-mvt.f90.

908  ! -- module
909  use tdismodule, only: kstp, kper
910  ! -- dummy
911  class(TspMvttype), intent(inout) :: this
912  ! -- local
913  character(len=LINELENGTH) :: title
914  character(len=LENMODELNAME + LENPACKAGENAME + 1) :: cloc1, cloc2
915  integer(I4B) :: i
916  integer(I4B) :: n
917  integer(I4B) :: inum
918  integer(I4B) :: ntabrows
919  integer(I4B) :: nlist
920  !
921  ! -- Determine number of table rows
922  ntabrows = 0
923  do i = 1, this%budobj%nbudterm
924  nlist = this%budobj%budterm(i)%nlist
925  ntabrows = ntabrows + nlist
926  end do
927  !
928  ! -- Set table kstp and kper
929  call this%outputtab%set_kstpkper(kstp, kper)
930  !
931  ! -- Add terms and print the table
932  title = 'TRANSPORT MOVER PACKAGE ('//trim(this%packName)// &
933  ') FLOW RATES'
934  call this%outputtab%set_title(title)
935  call this%outputtab%set_maxbound(ntabrows)
936  !
937  ! -- Process each table row
938  inum = 1
939  do i = 1, this%budobj%nbudterm
940  nlist = this%budobj%budterm(i)%nlist
941  do n = 1, nlist
942  cloc1 = trim(adjustl(this%budobj%budterm(i)%text1id1))//' '// &
943  trim(adjustl(this%budobj%budterm(i)%text2id1))
944  cloc2 = trim(adjustl(this%budobj%budterm(i)%text1id2))//' '// &
945  trim(adjustl(this%budobj%budterm(i)%text2id2))
946  call this%outputtab%add_term(inum)
947  call this%outputtab%add_term(cloc1)
948  call this%outputtab%add_term(this%budobj%budterm(i)%id1(n))
949  call this%outputtab%add_term(-this%mvrbudobj%budterm(i)%flow(n))
950  call this%outputtab%add_term(this%budobj%budterm(i)%flow(n))
951  call this%outputtab%add_term(cloc2)
952  call this%outputtab%add_term(this%budobj%budterm(i)%id2(n))
953  inum = inum + 1
954  end do
955  end do
956  !
957  ! -- Return
958  return

◆ mvt_rp()

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

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

188  ! -- modules
189  use tdismodule, only: kper, kstp
190  ! -- dummy
191  class(TspMvtType) :: this
192  !
193  ! -- At this point, the mvrbudobj is available to set up the mvt budobj
194  if (kper * kstp == 1) then
195  !
196  ! -- If mvt is for a single model then point to fmi1
197  !cdl todo: this needs to be called from GwtGwtExg somehow for the 2 model case
198  if (associated(this%fmi1, this%fmi2)) then
199  call this%set_pointer_mvrbudobj(this%fmi1%mvrbudobj)
200  end if
201  !
202  ! -- Set up the mvt budobject
203  call this%mvt_scan_mvrbudobj()
204  call this%mvt_setup_budobj()
205  !
206  ! -- Define the budget object to be the size of maxpackages
207  call this%budget%budget_df(this%maxpackages, 'TRANSPORT MOVER', bddim='M')
208  call this%budget%set_ibudcsv(this%ibudcsv)
209  end if
210  !
211  ! -- Return
212  return

◆ 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 813 of file tsp-mvt.f90.

814  class(TspMvtType) :: this
815  integer(I4B) :: nbudterm
816  integer(I4B) :: maxpackages
817  integer(I4B) :: i, j
818  integer(I4B) :: ipos
819  logical :: found
820  !
821  ! -- Calculate maxpackages, which is the the square of nbudterm
822  nbudterm = this%mvrbudobj%nbudterm
823  do i = 1, nbudterm
824  if (i * i == nbudterm) then
825  maxpackages = i
826  exit
827  end if
828  end do
829  this%maxpackages = maxpackages
830  !
831  ! -- Allocate paknames
832  allocate (this%paknames(this%maxpackages))
833  do i = 1, this%maxpackages
834  this%paknames(i) = ''
835  end do
836  !
837  ! -- Scan through mvrbudobj and create unique paknames
838  ipos = 1
839  do i = 1, nbudterm
840  found = .false.
841  do j = 1, ipos
842  if (this%mvrbudobj%budterm(i)%text2id1 == this%paknames(j)) then
843  found = .true.
844  exit
845  end if
846  end do
847  if (.not. found) then
848  this%paknames(ipos) = this%mvrbudobj%budterm(i)%text2id1
849  ipos = ipos + 1
850  end if
851  end do
852  !
853  ! -- Return
854  return

◆ mvt_setup_budobj()

subroutine tspmvtmodule::mvt_setup_budobj ( class(tspmvttype this)

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

692  ! -- modules
693  use constantsmodule, only: lenbudtxt
694  ! -- dummy
695  class(TspMvtType) :: this
696  ! -- local
697  integer(I4B) :: nbudterm
698  integer(I4B) :: ncv
699  integer(I4B) :: maxlist
700  integer(I4B) :: i
701  integer(I4B) :: naux
702  character(len=LENMODELNAME) :: modelname1, modelname2
703  character(len=LENPACKAGENAME) :: packagename1, packagename2
704  character(len=LENBUDTXT) :: text
705  !
706  ! -- Assign terms to set up the mover budget object
707  nbudterm = this%mvrbudobj%nbudterm
708  ncv = 0
709  naux = 0
710  if (this%depvartype == 'CONCENTRATION') then
711  text = ' MVT-FLOW'
712  else
713  text = ' MVE-FLOW'
714  end if
715  !
716  ! -- Set up budobj
717  call this%budobj%budgetobject_df(ncv, nbudterm, 0, 0, bddim_opt='M')
718  !
719  ! -- Go through the water mover budget terms and set up the transport
720  ! mover budget terms
721  do i = 1, nbudterm
722  modelname1 = this%mvrbudobj%budterm(i)%text1id1
723  packagename1 = this%mvrbudobj%budterm(i)%text2id1
724  modelname2 = this%mvrbudobj%budterm(i)%text1id2
725  packagename2 = this%mvrbudobj%budterm(i)%text2id2
726  maxlist = this%mvrbudobj%budterm(i)%maxlist
727  call this%budobj%budterm(i)%initialize(text, &
728  modelname1, &
729  packagename1, &
730  modelname2, &
731  packagename2, &
732  maxlist, .false., .false., &
733  naux)
734  end do
735  !
736  ! -- Return
737  return
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:36

◆ mvt_setup_outputtab()

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

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

860  ! -- dummy
861  class(TspMvtType), intent(inout) :: this
862  ! -- local
863  character(len=LINELENGTH) :: title
864  character(len=LINELENGTH) :: text
865  integer(I4B) :: ntabcol
866  integer(I4B) :: maxrow
867  integer(I4B) :: ilen
868  !
869  ! -- Allocate and initialize the output table
870  if (this%iprflow /= 0) then
871  !
872  ! -- Dimension table
873  ntabcol = 7
874  maxrow = 0
875  !
876  ! -- Initialize the output table object
877  title = 'TRANSPORT MOVER PACKAGE ('//trim(this%packName)// &
878  ') FLOW RATES'
879  call table_cr(this%outputtab, this%packName, title)
880  call this%outputtab%table_df(maxrow, ntabcol, this%iout, &
881  transient=.true.)
882  text = 'NUMBER'
883  call this%outputtab%initialize_column(text, 10, alignment=tabcenter)
884  text = 'PROVIDER LOCATION'
885  ilen = lenmodelname + lenpackagename + 1
886  call this%outputtab%initialize_column(text, ilen)
887  text = 'PROVIDER ID'
888  call this%outputtab%initialize_column(text, 10)
889  text = 'PROVIDER FLOW RATE'
890  call this%outputtab%initialize_column(text, 10)
891  text = 'PROVIDER TRANSPORT RATE'
892  call this%outputtab%initialize_column(text, 10)
893  text = 'RECEIVER LOCATION'
894  ilen = lenmodelname + lenpackagename + 1
895  call this%outputtab%initialize_column(text, ilen)
896  text = 'RECEIVER ID'
897  call this%outputtab%initialize_column(text, 10)
898  !
899  end if
900  !
901  ! -- Return
902  return
Here is the call graph for this function:

◆ read_options()

subroutine tspmvtmodule::read_options ( class(tspmvttype this)

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

610  ! -- modules
611  use openspecmodule, only: access, form
613  ! -- dummy
614  class(TspMvtType) :: this
615  ! -- local
616  character(len=LINELENGTH) :: errmsg, keyword
617  character(len=MAXCHARLEN) :: fname
618  integer(I4B) :: ierr
619  logical :: isfound, endOfBlock
620  ! -- formats
621  character(len=*), parameter :: fmtflow = &
622  "(4x, a, 1x, a, 1x, ' WILL BE SAVED TO FILE: ', a, &
623  &/4x, 'OPENED ON UNIT: ', I0)"
624  character(len=*), parameter :: fmtflow2 = &
625  &"(4x, 'FLOWS WILL BE SAVED TO BUDGET FILE')"
626  !
627  ! -- Get options block
628  call this%parser%GetBlock('OPTIONS', isfound, ierr, blockrequired=.false., &
629  supportopenclose=.true.)
630  !
631  ! -- Parse options block if detected
632  if (isfound) then
633  write (this%iout, '(1x,a)') 'PROCESSING MVT OPTIONS'
634  do
635  call this%parser%GetNextLine(endofblock)
636  if (endofblock) exit
637  call this%parser%GetStringCaps(keyword)
638  select case (keyword)
639  case ('SAVE_FLOWS')
640  this%ipakcb = -1
641  write (this%iout, fmtflow2)
642  case ('PRINT_INPUT')
643  this%iprpak = 1
644  write (this%iout, '(4x,a)') 'MVT INPUT WILL BE PRINTED.'
645  case ('PRINT_FLOWS')
646  this%iprflow = 1
647  write (this%iout, '(4x,a)') &
648  'MVT FLOWS WILL BE PRINTED TO LISTING FILE.'
649  case ('BUDGET')
650  call this%parser%GetStringCaps(keyword)
651  if (keyword == 'FILEOUT') then
652  call this%parser%GetString(fname)
653  this%ibudgetout = getunit()
654  call openfile(this%ibudgetout, this%iout, fname, 'DATA(BINARY)', &
655  form, access, 'REPLACE')
656  write (this%iout, fmtflow) 'MVT', 'BUDGET', trim(adjustl(fname)), &
657  this%ibudgetout
658  else
659  call store_error('Optional BUDGET keyword must &
660  &be followed by FILEOUT')
661  end if
662  case ('BUDGETCSV')
663  call this%parser%GetStringCaps(keyword)
664  if (keyword == 'FILEOUT') then
665  call this%parser%GetString(fname)
666  this%ibudcsv = getunit()
667  call openfile(this%ibudcsv, this%iout, fname, 'CSV', &
668  filstat_opt='REPLACE')
669  write (this%iout, fmtflow) 'MVT', 'BUDGET CSV', &
670  trim(adjustl(fname)), this%ibudcsv
671  else
672  call store_error('Optional BUDGETCSV keyword must be followed by &
673  &FILEOUT')
674  end if
675  case default
676  write (errmsg, '(a,a)') 'Unknown MVT option: ', &
677  trim(keyword)
678  call store_error(errmsg)
679  call this%parser%StoreErrorUnit()
680  end select
681  end do
682  write (this%iout, '(1x,a)') 'END OF MVT OPTIONS'
683  end if
684  !
685  ! -- Return
686  return
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 319 of file tsp-mvt.f90.

320  ! -- dummy
321  class(TspMvtType) :: this
322  integer(I4B), intent(in) :: ibudterm
323  type(TspFmiType), pointer :: fmi_pr
324  type(TspFmiType), pointer :: fmi_rc
325  !
326  fmi_pr => null()
327  fmi_rc => null()
328  if (this%gwfmodelname1 == '' .and. this%gwfmodelname2 == '') then
329  fmi_pr => this%fmi1
330  fmi_rc => this%fmi1
331  else
332  ! -- Modelname for provider is this%mvrbudobj%budterm(i)%text1id1
333  if (this%mvrbudobj%budterm(ibudterm)%text1id1 == this%gwfmodelname1) then
334  ! -- Model 1 is the provider
335  fmi_pr => this%fmi1
336  else if (this%mvrbudobj%budterm(ibudterm)%text1id1 == &
337  this%gwfmodelname2) then
338  ! -- Model 2 is the provider
339  fmi_pr => this%fmi2
340  else
341  ! -- Must be an error
342  !cdl todo: programming error
343  print *, this%mvrbudobj%budterm(ibudterm)%text1id1
344  print *, this%gwfmodelname1
345  print *, this%gwfmodelname2
346  stop "error in set_fmi_pr_rc"
347  end if
348  !
349  ! -- Modelname for receiver is this%mvrbudobj%budterm(i)%text1id2
350  if (this%mvrbudobj%budterm(ibudterm)%text1id2 == this%gwfmodelname1) then
351  ! -- Model 1 is the receiver
352  fmi_rc => this%fmi1
353  else if (this%mvrbudobj%budterm(ibudterm)%text1id2 == &
354  this%gwfmodelname2) then
355  ! -- Model 2 is the receiver
356  fmi_rc => this%fmi2
357  else
358  ! -- Must be an error
359  !cdl todo: programming error
360  print *, this%mvrbudobj%budterm(ibudterm)%text1id2
361  print *, this%gwfmodelname1
362  print *, this%gwfmodelname2
363  stop "error in set_fmi_pr_rc"
364  end if
365  end if
366  !
367  if (.not. associated(fmi_pr)) then
368  print *, 'Could not find FMI Package...'
369  stop "error in set_fmi_pr_rc"
370  end if
371  if (.not. associated(fmi_rc)) then
372  print *, 'Could not find FMI Package...'
373  stop "error in set_fmi_pr_rc"
374  end if
375  !
376  ! -- Return
377  return

◆ 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 166 of file tsp-mvt.f90.

167  class(TspMvtType) :: this
168  type(BudgetObjectType), intent(in), target :: mvrbudobj
169  this%mvrbudobj => mvrbudobj