MODFLOW 6  version 6.6.0.dev0
USGS Modular Hydrologic Model
gwf-mvr.f90
Go to the documentation of this file.
1 !GWF Water Mover Module
2 !This module contains a derived type, called GwfMvrType, that
3 !is attached to the GWF model. The water mover can be used to move water
4 !between packages. The mover requires that mover-aware packages have access
5 !to four arrays: qtformvr, qformvr, qtomvr, and qfrommvr. These arrays are
6 !stored and managed by a separate PackageMoverType object. qformvr is a
7 !vector of volumetric flow rates available for the mover. The package
8 !must fill the vector (dimensioned by number of reaches) with the available
9 !water. qtomvr is a vector containing how much water was actually moved
10 !by the mover. The package should use this value in the budgeting part
11 !to track how much water was actually provided to the mover. Lastly,
12 !the qfrommvr is a vector that contains volumetric rates for how much
13 !water was provided by the mover as a source of water to the package.
14 !
15 !The mover is designed so that a reach can provide water to more than one
16 !receiving reaches. The available water will be consumed in order of
17 !the movers listed in the package. The mover is also designed so that
18 !a receiver can receive water from more than one provider.
19 !
20 ! 1. The mover is instantiated as a model member:
21 !
22 ! type(GwfMvrType), pointer :: mvr => null()
23 !
24 ! Mover aware packages have access to the following vectors of mover
25 ! information, which are stored in the PackageMoverType object:
26 !
27 ! qtformvr(nproviders) -- total available unconsumed water for mover
28 ! qformvr(nproviders) -- currently available consumed water (changes during fc)
29 ! qtomvr(nproviders) -- actual amount of water sent to mover
30 ! qfrommvr(nreceivers) -- actual amount of water received from mover
31 !
32 ! integer(I4B), pointer :: imover => null()
33 ! real(DP), dimension(:), pointer, contiguous :: qtformvr => null()
34 ! real(DP), dimension(:), pointer, contiguous :: qformvr => null()
35 ! real(DP), dimension(:), pointer, contiguous :: qtomvr => null()
36 ! real(DP), dimension(:), pointer, contiguous :: qfrommvr => null()
37 !
38 ! Note qtformvr is filled as a positive number to indicate that it is
39 ! water available to be moved. If qtformvr is negative, then
40 ! no water will be moved for that reach. qformvr is also the available
41 ! water, but this value decreases as the mover object consumes water from
42 ! it.
43 !
44 ! 2. In gwf_cr create the mover package by calling the CR subroutine:
45 !
46 ! call mvr_cr(this%mvr, this%name, this%inmvr, this%iout)
47 !
48 ! 3. In gwf_ar call the AR method for the mover:
49 !
50 ! if(this%inmvr > 0) call this%mvr%mvr_ar()
51 !
52 ! Mover aware packages allocate the four vectors. The first three
53 ! (qtformvr, qformvr, qtomvr) are allocated to the number of providers
54 ! and the last one (qfrommvr) is allocated to the number of receivers.
55 !
56 ! 4. In gwf_rp call the RP method for the mover. This reads the
57 ! movers active for the current period.
58 !
59 ! if(this%inmvr > 0) call this%mvr%mvr_rp()
60 !
61 ! 5. In gwf_ad call the AD method for the mover. This saves qtomvr from the
62 ! the last time step.
63 !
64 ! if(this%inmvr > 0) call this%mvr%mvr_ad()
65 !
66 ! Mover aware packages then set:
67 ! qtomvr(:) = 0.
68 ! qformvr(:) = 0.
69 !
70 ! 6. In gwf_cf call the CF routine. Mover aware packages set:
71 ! qtformvr(:) = qformvr(:)
72 ! qfrommvr(:) = 0.
73 ! qtomvr(:) = 0.
74 !
75 ! 7. The FC method for the mover is called. This method calculates the
76 ! amount of water to move based on the amount of water available from the
77 ! previous iteration. This call updates the values in the qtomvr and
78 ! qfrommvr vectors inside the packages. This is done by the mover package
79 ! using pointers to the appropriate reach locations in qtomvr and qfrommvr.
80 !
81 ! if(this%inmvr > 0) call this%mvr%mvr_fc() ! called from gwf%gwf_fc()
82 !
83 ! a. Mover aware packages first set qformvr(:) = 0.
84 ! b. Mover aware packages that are receivers (MAW, SFR, LAK, UZF) add
85 ! qfrommvr terms to their individual control volume equations as a
86 ! source of water.
87 ! c. Mover aware packages calculate qformvr as amount of water available
88 ! to be moved (these qformvr terms are used in the next iteration
89 ! by this%mvr%mvr_fc() to calculate how much water is actually moved)
90 !
91 ! 8. The BD method for the mover is called. This method writes the moved
92 ! water rates if requested.
93 !
94 ! if(this%inmvr > 0) call this%mvr%mvr_bd()
95 !
96 ! Mover aware packages account for qtomvr and qfrommvr terms in their
97 ! individual budget routines.
98 !
99 ! 9. The OT method for the mover is called. This method outputs a mover
100 ! budget table.
101 !
102 ! if(this%inmvr > 0) call this%mvr%mvr_ot()
103 !
105  use kindmodule, only: dp, i4b, lgp
109  linelength
110  use mvrmodule, only: mvrtype
111  use budgetmodule, only: budgettype, budget_cr
117  use basedismodule, only: disbasetype
118  use inputoutputmodule, only: urword
119  use tablemodule, only: tabletype, table_cr
120 
121  implicit none
122  private
123  public :: gwfmvrtype, mvr_cr
124 
126  logical(LGP), pointer :: reset_mapped_id ! flag to indicate mapped ids must be reset; true when movers change
127  integer(I4B), pointer :: ibudgetout => null() !< binary budget output file
128  integer(I4B), pointer :: ibudcsv => null() !< unit number for csv budget output file
129  integer(I4B), pointer :: maxmvr => null() !< max number of movers to be specified
130  integer(I4B), pointer :: maxpackages => null() !< max number of packages to be specified
131  integer(I4B), pointer :: maxcomb => null() !< max number of combination of packages
132  integer(I4B), pointer :: nmvr => null() !< number of movers for current stress period
133  integer(I4B), pointer :: iexgmvr => null() !< indicate mover is for an exchange (not for a single model)
134  integer(I4B), pointer :: imodelnames => null() !< indicate package input file has model names in it
135  integer(I4B), dimension(:), pointer, contiguous :: ientries => null() !< number of entries for each combination
136  character(len=LENMEMPATH), &
137  dimension(:), pointer, contiguous :: pckmempaths !< memory paths of all packages used in this mover
138  character(len=LENPACKAGENAME), &
139  dimension(:), pointer, contiguous :: paknames => null() !< array of package names
140  type(mvrtype), dimension(:), pointer, contiguous :: mvr => null() !< array of movers
141  type(gwfmvrperioddatatype), pointer :: gwfmvrperioddata => null() !< input data object
142  type(budgettype), pointer :: budget => null() !< mover budget object (used to write table)
143  type(budgetobjecttype), pointer :: budobj => null() !< new budget container (used to write binary file)
145  dimension(:), pointer, contiguous :: pakmovers => null() !< pointer to package mover objects
146  !
147  ! -- table objects
148  type(tabletype), pointer :: outputtab => null()
149  logical(LGP) :: suppress_fileout = .false. !< flag to disable output file (budget, budget csv)
150 
151  contains
152  procedure :: mvr_init
153  procedure :: mvr_ar
154  procedure :: mvr_rp
155  procedure :: mvr_ad
156  procedure :: mvr_fc
157  procedure :: mvr_cc
158  procedure :: mvr_bd
159  procedure :: mvr_bdsav
160  procedure :: mvr_ot_saveflow
161  procedure :: mvr_ot_printflow
162  procedure :: mvr_ot_bdsummary
163  procedure :: mvr_da
164  procedure :: read_options
165  procedure :: check_options
166  procedure :: read_dimensions
167  procedure :: read_packages
168  procedure :: check_packages
169  procedure :: assign_packagemovers
170  procedure :: initialize_movers
171  procedure :: fill_budobj
172  procedure :: allocate_scalars
173  procedure :: allocate_arrays
174  procedure, private :: mvr_setup_budobj
175  procedure, private :: mvr_setup_outputtab
176  procedure, private :: mvr_print_outputtab
177  procedure, private :: set_mapped_id
178 
179  end type gwfmvrtype
180 
181 contains
182 
183  !> @brief Create a new mvr object
184  !<
185  subroutine mvr_cr(mvrobj, name_parent, inunit, iout, dis, iexgmvr)
186  ! -- dummy
187  type(gwfmvrtype), pointer :: mvrobj
188  character(len=*), intent(in) :: name_parent
189  integer(I4B), intent(in) :: inunit
190  integer(I4B), intent(in) :: iout
191  class(disbasetype), pointer, intent(in) :: dis
192  integer(I4B), optional :: iexgmvr
193  !
194  ! -- Create the object
195  allocate (mvrobj)
196  !
197  ! -- Init
198  call mvrobj%mvr_init(name_parent, inunit, iout, dis, iexgmvr)
199  end subroutine mvr_cr
200 
201  subroutine mvr_init(this, name_parent, inunit, iout, dis, iexgmvr)
202  class(gwfmvrtype) :: this
203  character(len=*), intent(in) :: name_parent
204  integer(I4B), intent(in) :: inunit
205  integer(I4B), intent(in) :: iout
206  class(disbasetype), pointer, intent(in) :: dis
207  integer(I4B), optional :: iexgmvr
208  !
209  ! -- create name and memory paths. name_parent will either be model name or the
210  ! exchange name.
211  call this%set_names(1, name_parent, 'MVR', 'MVR')
212  !
213  ! -- Allocate scalars
214  call this%allocate_scalars()
215  !
216  ! -- Set pointer to dis
217  this%dis => dis
218  !
219  ! -- Set variables
220  this%inunit = inunit
221  this%iout = iout
222  !
223  ! -- Set iexgmvr
224  if (present(iexgmvr)) this%iexgmvr = iexgmvr
225  !
226  ! -- Create the budget object
227  if (inunit > 0) then
228  call budget_cr(this%budget, this%memoryPath)
229  !
230  ! -- Initialize block parser
231  call this%parser%Initialize(this%inunit, this%iout)
232  end if
233  !
234  ! -- instantiate the budget object
235  call budgetobject_cr(this%budobj, 'WATER MOVER')
236  end subroutine mvr_init
237 
238  !> @brief Allocate and read water mover information
239  !<
240  subroutine mvr_ar(this)
241  ! -- dummy
242  class(gwfmvrtype) :: this
243  !
244  ! -- Print a message identifying the water mover package.
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)
248  !
249  ! -- Read and check options
250  call this%read_options()
251  call this%check_options()
252  !
253  ! -- Read options
254  call this%read_dimensions()
255  !
256  ! -- Allocate arrays
257  call this%allocate_arrays()
258  !
259  ! -- Read and check package names
260  call this%read_packages()
261  call this%check_packages()
262  !
263  ! -- Define the budget object to be the size of package names
264  call this%budget%budget_df(this%maxpackages, 'WATER MOVER')
265  call this%budget%set_ibudcsv(this%ibudcsv)
266  !
267  ! -- setup the budget object
268  call this%mvr_setup_budobj()
269  end subroutine mvr_ar
270 
271  !> @brief Read and Prepare
272  !!
273  !! Read itmp and read new boundaries if itmp > 0
274  !<
275  subroutine mvr_rp(this)
276  ! -- modules
277  use constantsmodule, only: linelength
278  use tdismodule, only: kper, nper
280  use arrayhandlersmodule, only: ifind
281  ! -- dummy
282  class(gwfmvrtype), intent(inout) :: this
283  ! -- local
284  integer(I4B) :: i, ierr, nlist, ipos
285  integer(I4B) :: ii, jj
286  logical :: isfound
287  character(len=LINELENGTH) :: line, errmsg
288  character(len=LENMODELNAME) :: mname
289  ! -- formats
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,')')"
297  !
298  ! -- Set ionper to the stress period number for which a new block of data
299  ! will be read.
300  if (this%inunit == 0) return
301  !
302  ! -- get stress period data
303  if (this%ionper < kper) then
304  !
305  ! -- get period block
306  call this%parser%GetBlock('PERIOD', isfound, ierr, &
307  supportopenclose=.true., &
308  blockrequired=.false.)
309  if (isfound) then
310  !
311  ! -- read ionper and check for increasing period numbers
312  call this%read_check_ionper()
313  else
314  !
315  ! -- PERIOD block not found
316  if (ierr < 0) then
317  ! -- End of file found; data applies for remainder of simulation.
318  this%ionper = nper + 1
319  else
320  ! -- Found invalid block
321  call this%parser%GetCurrentLine(line)
322  write (errmsg, fmtblkerr) adjustl(trim(line))
323  call store_error(errmsg)
324  call this%parser%StoreErrorUnit()
325  end if
326  end if
327  end if
328  !
329  ! -- read data if ionper == kper
330  if (this%ionper == kper) then
331  write (this%iout, '(/,2x,a,i0)') 'READING WATER MOVERS FOR PERIOD ', kper
332  nlist = -1
333  i = 1
334  this%reset_mapped_id = .true.
335  !
336  ! -- set mname to '' if this is an exchange mover, or to the model name
337  if (this%iexgmvr == 0) then
338  mname = this%name_model
339  else
340  mname = ''
341  end if
342  !
343  ! -- Assign a pointer to the package mover object. The pointer assignment
344  ! will happen only the first time
345  call this%assign_packagemovers()
346  !
347  ! -- Call the period data input reader
348  call this%gwfmvrperioddata%read_from_parser(this%parser, nlist, mname)
349  !
350  ! -- Process the input data into the individual mover objects
351  call this%initialize_movers(nlist)
352  !
353  ! -- assign the pointers
354  do i = 1, nlist
355  call this%mvr(i)%prepare(this%parser%iuactive, &
356  this%pckMemPaths, &
357  this%pakmovers)
358  if (this%iprpak == 1) call this%mvr(i)%echo(this%iout)
359  end do
360  write (this%iout, '(/,1x,a,1x,i6,/)') 'END OF DATA FOR PERIOD', kper
361  !
362  ! -- Set the number of movers for this period to nlist
363  this%nmvr = nlist
364  write (this%iout, '(4x, i0, a, i0)') this%nmvr, &
365  ' MOVERS READ FOR PERIOD ', kper
366  !
367  ! -- Check to make sure all providers and receivers are properly stored
368  do i = 1, this%nmvr
369  ipos = ifind(this%pckMemPaths, this%mvr(i)%mem_path_src)
370  if (ipos < 1) then
371  write (errmsg, '(a,a,a)') 'Provider ', &
372  trim(this%mvr(i)%mem_path_src), ' not listed in packages block.'
373  call store_error(errmsg)
374  end if
375  ipos = ifind(this%pckMemPaths, this%mvr(i)%mem_path_tgt)
376  if (ipos < 1) then
377  write (errmsg, '(a,a,a)') 'Receiver ', &
378  trim(this%mvr(i)%mem_path_tgt), ' not listed in packages block.'
379  call store_error(errmsg)
380  end if
381  end do
382  if (count_errors() > 0) then
383  call this%parser%StoreErrorUnit()
384  end if
385  !
386  ! -- reset ientries
387  do i = 1, this%maxcomb
388  this%ientries(i) = 0
389  end do
390  !
391  ! --
392  do i = 1, this%nmvr
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
397  end do
398  else
399  write (this%iout, fmtlsp) 'MVR'
400  !
401  end if
402  end subroutine mvr_rp
403 
404  subroutine initialize_movers(this, nr_active_movers)
405  class(gwfmvrtype) :: this
406  integer(I4B) :: nr_active_movers
407  ! local
408  integer(I4B) :: i
409 
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))
419  end do
420 
421  end subroutine initialize_movers
422 
423  subroutine mvr_ad(this)
424  ! -- dummy
425  class(gwfmvrtype) :: this
426  ! -- locals
427  integer(I4B) :: i
428  !
429  do i = 1, this%nmvr
430  call this%mvr(i)%advance()
431  end do
432  end subroutine mvr_ad
433 
434  !> @brief Calculate qfrommvr as a function of qtomvr
435  !<
436  subroutine mvr_fc(this)
437  class(gwfmvrtype) :: this
438  ! local
439  integer(I4B) :: i
440 
441  do i = 1, this%nmvr
442  call this%mvr(i)%update_provider()
443  call this%mvr(i)%update_receiver()
444  end do
445 
446  end subroutine mvr_fc
447 
448  !> @brief Extra convergence check for mover
449  !<
450  subroutine mvr_cc(this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
451  ! -- dummy
452  class(gwfmvrtype) :: this
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
460  ! -- formats
461  character(len=*), parameter :: fmtmvrcnvg = &
462  "(/,1x,'MOVER PACKAGE REQUIRES AT LEAST TWO OUTER ITERATIONS. CONVERGE &
463  &FLAG HAS BEEN RESET TO FALSE.')"
464  !
465  ! -- If there are active movers, then at least 2 outers required
466  if (this%nmvr > 0) then
467  if (icnvgmod == 1 .and. kiter == 1) then
468  dpak = dnodata
469  cpak = trim(this%packName)
470  write (this%iout, fmtmvrcnvg)
471  end if
472  end if
473  end subroutine mvr_cc
474 
475  !> @brief Fill the mover budget object
476  !<
477  subroutine mvr_bd(this)
478  ! -- dummy
479  class(gwfmvrtype) :: this
480  ! -- locals
481  ! -- formats
482  !
483  ! -- set the feature maps; for performance reasons,
484  ! this should only be called for the first time
485  ! step of a stress period in which a new set of
486  ! movers was provided in a period block.
487  if (this%reset_mapped_id) then
488  call this%set_mapped_id()
489  this%reset_mapped_id = .false.
490  end if
491  !
492  ! -- fill the budget object
493  call this%fill_budobj()
494  end subroutine mvr_bd
495 
496  !> @brief Write mover terms
497  !<
498  subroutine mvr_bdsav(this, icbcfl, ibudfl, isuppress_output)
499  ! -- modules
500  use tdismodule, only: kstp, kper, delt, pertim, totim
501  ! -- dummy
502  class(gwfmvrtype) :: this
503  integer(I4B), intent(in) :: icbcfl
504  integer(I4B), intent(in) :: ibudfl
505  integer(I4B), intent(in) :: isuppress_output
506  ! -- locals
507  integer(I4B) :: ibinun
508  ! -- formats
509  character(len=*), parameter :: fmttkk = &
510  "(1X,/1X,A,' PERIOD ',I0,' STEP ',I0)"
511  !
512  ! -- Print the mover flow table
513  if (ibudfl /= 0 .and. this%iprflow /= 0 .and. isuppress_output == 0) then
514  call this%mvr_print_outputtab()
515  end if
516  !
517  ! -- Save the mover flows from the budobj to a mover binary file
518  ibinun = 0
519  if (this%ibudgetout /= 0) then
520  ibinun = this%ibudgetout
521  end if
522  if (icbcfl == 0) ibinun = 0
523  if (isuppress_output /= 0) ibinun = 0
524  if (ibinun > 0) then
525  call this%budobj%save_flows(this%dis, ibinun, kstp, kper, delt, &
526  pertim, totim, this%iout)
527  end if
528  end subroutine mvr_bdsav
529 
530  !> @brief Write mover terms
531  !<
532  subroutine mvr_ot_saveflow(this, icbcfl, ibudfl)
533  ! -- modules
534  use tdismodule, only: kstp, kper, delt, pertim, totim
535  ! -- dummy
536  class(gwfmvrtype) :: this
537  integer(I4B), intent(in) :: icbcfl
538  integer(I4B), intent(in) :: ibudfl
539  ! -- locals
540  integer(I4B) :: ibinun
541  !
542  ! -- Save the mover flows from the budobj to a mover binary file
543  ibinun = 0
544  if (this%ibudgetout /= 0) then
545  ibinun = this%ibudgetout
546  end if
547  if (icbcfl == 0) ibinun = 0
548  if (ibinun > 0) then
549  call this%budobj%save_flows(this%dis, ibinun, kstp, kper, delt, &
550  pertim, totim, this%iout)
551  end if
552  end subroutine mvr_ot_saveflow
553 
554  !> @brief Print mover flow table
555  !<
556  subroutine mvr_ot_printflow(this, icbcfl, ibudfl)
557  ! -- dummy
558  class(gwfmvrtype) :: this
559  integer(I4B), intent(in) :: icbcfl
560  integer(I4B), intent(in) :: ibudfl
561  !
562  ! -- Print the mover flow table
563  if (ibudfl /= 0 .and. this%iprflow /= 0) then
564  call this%mvr_print_outputtab()
565  end if
566  end subroutine mvr_ot_printflow
567 
568  !> @brief Write mover budget to listing file
569  !<
570  subroutine mvr_ot_bdsummary(this, ibudfl)
571  ! -- modules
572  use tdismodule, only: kstp, kper, delt, totim
573  ! -- dummy
574  class(gwfmvrtype) :: this
575  integer(I4B), intent(in) :: ibudfl
576  ! -- locals
577  character(len=LENMEMPATH) :: pckMemPath
578  integer(I4B) :: i, j
579  real(DP), allocatable, dimension(:) :: ratin, ratout
580  !
581  ! -- Allocate and initialize ratin/ratout
582  allocate (ratin(this%maxpackages), ratout(this%maxpackages))
583  do j = 1, this%maxpackages
584  ratin(j) = dzero
585  ratout(j) = dzero
586  end do
587  !
588  ! -- Accumulate the rates
589  do i = 1, this%nmvr
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
593  end if
594  if (this%pckMemPaths(j) == this%mvr(i)%mem_path_tgt) then
595  ratout(j) = ratout(j) + this%mvr(i)%qpactual
596  end if
597  end do
598  end do
599  !
600  ! -- Send rates to budget object
601  call this%budget%reset()
602  do j = 1, this%maxpackages
603  if ((this%iexgmvr) == 1) then
604  pckmempath = this%pckMemPaths(j)
605  else
606  pckmempath = this%paknames(j)
607  end if
608  call this%budget%addentry(ratin(j), ratout(j), delt, pckmempath)
609  end do
610  !
611  ! -- Write the budget
612  call this%budget%finalize_step(delt)
613  if (ibudfl /= 0) then
614  call this%budget%budget_ot(kstp, kper, this%iout)
615  end if
616  !
617  ! -- Write budget csv
618  call this%budget%writecsv(totim)
619  !
620  ! -- Deallocate
621  deallocate (ratin, ratout)
622  !
623  ! -- Output mvr budget
624  ! Not using budobj write_table here because it would result
625  ! in a table that has one entry. A custom table looks
626  ! better here with a row for each package.
627  !call this%budobj%write_budtable(kstp, kper, this%iout)
628  end subroutine mvr_ot_bdsummary
629 
630  !> @brief Deallocate
631  !<
632  subroutine mvr_da(this)
633  ! -- modules
634  use constantsmodule, only: done
636  ! -- dummy
637  class(gwfmvrtype) :: this
638  !
639  ! -- Arrays
640  if (this%inunit > 0) then
641  call mem_deallocate(this%ientries)
642  deallocate (this%mvr)
643  deallocate (this%pckMemPaths)
644  deallocate (this%paknames)
645  deallocate (this%pakmovers)
646  !
647  ! -- allocate the perioddata object
648  call this%gwfmvrperioddata%destroy()
649  deallocate (this%gwfmvrperioddata)
650  nullify (this%gwfmvrperioddata)
651  !
652  ! -- budget object
653  call this%budget%budget_da()
654  deallocate (this%budget)
655  !
656  ! -- budobj
657  call this%budobj%budgetobject_da()
658  deallocate (this%budobj)
659  nullify (this%budobj)
660  !
661  ! -- output table object
662  if (associated(this%outputtab)) then
663  call this%outputtab%table_da()
664  deallocate (this%outputtab)
665  nullify (this%outputtab)
666  end if
667  end if
668  !
669  ! -- Scalars
670  call mem_deallocate(this%reset_mapped_id)
671  call mem_deallocate(this%ibudgetout)
672  call mem_deallocate(this%ibudcsv)
673  call mem_deallocate(this%maxmvr)
674  call mem_deallocate(this%maxpackages)
675  call mem_deallocate(this%maxcomb)
676  call mem_deallocate(this%nmvr)
677  call mem_deallocate(this%iexgmvr)
678  call mem_deallocate(this%imodelnames)
679  !
680  ! -- deallocate scalars in NumericalPackageType
681  call this%NumericalPackageType%da()
682  end subroutine mvr_da
683 
684  !> @brief Read options specified in the input options block
685  !<
686  subroutine read_options(this)
687  ! -- modules
688  use constantsmodule, only: linelength, dzero, done
689  use openspecmodule, only: access, form
692  ! -- dummy
693  class(gwfmvrtype) :: this
694  ! -- local
695  character(len=LINELENGTH) :: errmsg
696  character(len=MAXCHARLEN) :: fname, keyword
697  integer(I4B) :: ierr
698  logical :: isfound, endOfBlock
699  ! -- formats
700  character(len=*), parameter :: fmtmvrbin = &
701  "(4x, 'MVR ', 1x, a, 1x, ' WILL BE SAVED TO FILE: ', a, /4x, 'OPENED ON &
702  &UNIT: ', I0)"
703  !
704  ! -- get options block
705  call this%parser%GetBlock('OPTIONS', isfound, ierr, &
706  supportopenclose=.true., blockrequired=.false.)
707  !
708  ! -- parse options block if detected
709  if (isfound) then
710  write (this%iout, '(1x,a)') 'PROCESSING MVR OPTIONS'
711  do
712  call this%parser%GetNextLine(endofblock)
713  if (endofblock) exit
714  call this%parser%GetStringCaps(keyword)
715  select case (keyword)
716  case ('BUDGET')
717  if (this%suppress_fileout) cycle
718  call this%parser%GetStringCaps(keyword)
719  if (keyword == 'FILEOUT') then
720  call this%parser%GetString(fname)
721  this%ibudgetout = getunit()
722  call openfile(this%ibudgetout, this%iout, fname, 'DATA(BINARY)', &
723  form, access, 'REPLACE')
724  write (this%iout, fmtmvrbin) 'BUDGET', trim(adjustl(fname)), &
725  this%ibudgetout
726  else
727  call store_error('OPTIONAL BUDGET KEYWORD MUST &
728  &BE FOLLOWED BY FILEOUT')
729  end if
730  case ('BUDGETCSV')
731  if (this%suppress_fileout) cycle
732  call this%parser%GetStringCaps(keyword)
733  if (keyword == 'FILEOUT') then
734  call this%parser%GetString(fname)
735  this%ibudcsv = getunit()
736  call openfile(this%ibudcsv, this%iout, fname, 'CSV', &
737  filstat_opt='REPLACE')
738  write (this%iout, fmtmvrbin) 'BUDGET CSV', trim(adjustl(fname)), &
739  this%ibudcsv
740  else
741  call store_error('OPTIONAL BUDGETCSV KEYWORD MUST BE FOLLOWED BY &
742  &FILEOUT')
743  end if
744  case ('PRINT_INPUT')
745  this%iprpak = 1
746  write (this%iout, '(4x,a)') 'WATER MOVER INPUT '// &
747  'WILL BE PRINTED TO LIST FILE.'
748  case ('PRINT_FLOWS')
749  this%iprflow = 1
750  write (this%iout, '(4x,a)') 'LISTS OF WATER MOVER FLOWS '// &
751  'WILL BE PRINTED TO LIST FILE.'
752  case ('MODELNAMES')
753  this%imodelnames = 1
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.'
760  call store_error(errmsg)
761  call this%parser%StoreErrorUnit()
762  end if
763  case default
764  write (errmsg, '(a,a)') 'Unknown MVR option: ', trim(keyword)
765  call store_error(errmsg)
766  call this%parser%StoreErrorUnit()
767  end select
768  end do
769  write (this%iout, '(1x,a)') 'END OF MVR OPTIONS'
770  end if
771  end subroutine read_options
772 
773  !> @brief Check MODELNAMES option set correctly
774  !<
775  subroutine check_options(this)
776  ! -- modules
777  use constantsmodule, only: linelength
779  ! -- dummy
780  class(gwfmvrtype) :: this
781  ! -- local
782  character(len=LINELENGTH) :: errmsg
783  !
784  ! -- Check if not exchange mover but model names are specified
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.'
789  call store_error(errmsg)
790  call this%parser%StoreErrorUnit()
791  end if
792  !
793  ! -- Check if exchange mover but model names not specified
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.'
798  call store_error(errmsg)
799  call this%parser%StoreErrorUnit()
800  end if
801  end subroutine check_options
802 
803  !> @brief Read the dimensions for this package
804  !<
805  subroutine read_dimensions(this)
806  ! -- modules
807  use constantsmodule, only: linelength
809  ! -- dummy
810  class(gwfmvrtype), intent(inout) :: this
811  ! -- local
812  character(len=LINELENGTH) :: errmsg, keyword
813  integer(I4B) :: ierr
814  logical :: isfound, endOfBlock
815  integer(I4B) :: i
816  integer(I4B) :: j
817  !
818  ! -- get dimensions block
819  call this%parser%GetBlock('DIMENSIONS', isfound, ierr, &
820  supportopenclose=.true.)
821  !
822  ! -- parse dimensions block if detected
823  if (isfound) then
824  write (this%iout, '(/1x,a)') 'PROCESSING MVR DIMENSIONS'
825  do
826  call this%parser%GetNextLine(endofblock)
827  if (endofblock) exit
828  call this%parser%GetStringCaps(keyword)
829  select case (keyword)
830  case ('MAXMVR')
831  this%maxmvr = this%parser%GetInteger()
832  write (this%iout, '(4x,a,i0)') 'MAXMVR = ', this%maxmvr
833  case ('MAXPACKAGES')
834  this%maxpackages = this%parser%GetInteger()
835  write (this%iout, '(4x,a,i0)') 'MAXPACKAGES = ', this%maxpackages
836  case default
837  write (errmsg, '(a,a)') &
838  'Unknown MVR dimension: ', trim(keyword)
839  call store_error(errmsg)
840  call this%parser%StoreErrorUnit()
841  end select
842  end do
843  write (this%iout, '(1x,a)') 'END OF MVR DIMENSIONS'
844  else
845  call store_error('Required DIMENSIONS block not found.')
846  call this%parser%StoreErrorUnit()
847  end if
848  !
849  ! -- calculate maximum number of combinations
850  this%maxcomb = 0
851  do i = 1, this%maxpackages
852  do j = 1, this%maxpackages
853  this%maxcomb = this%maxcomb + 1
854  end do
855  end do
856  !
857  ! -- verify dimensions were set
858  if (this%maxmvr < 0) then
859  write (errmsg, '(a)') &
860  'MAXMVR was not specified or was specified incorrectly.'
861  call store_error(errmsg)
862  call this%parser%StoreErrorUnit()
863  end if
864  if (this%maxpackages < 0) then
865  write (errmsg, '(a)') &
866  'MAXPACKAGES was not specified or was specified incorrectly.'
867  call store_error(errmsg)
868  call this%parser%StoreErrorUnit()
869  end if
870  end subroutine read_dimensions
871 
872  !> @brief Read the packages that will be managed by this mover
873  !<
874  subroutine read_packages(this)
875  ! -- modules
876  use constantsmodule, only: linelength
879  ! -- dummy
880  class(gwfmvrtype), intent(inout) :: this
881  ! -- local
882  character(len=LINELENGTH) :: errmsg, word, word1, word2
883  integer(I4B) :: lloc, ierr
884  integer(I4B) :: npak
885  logical :: isfound, endOfBlock
886  !
887  ! -- get packages block
888  call this%parser%GetBlock('PACKAGES', isfound, ierr, &
889  supportopenclose=.true.)
890  !
891  ! -- parse packages block
892  if (isfound) then
893  write (this%iout, '(/1x,a)') 'PROCESSING MVR PACKAGES'
894  npak = 0
895  do
896  call this%parser%GetNextLine(endofblock)
897  if (endofblock) exit
898  call this%parser%GetStringCaps(word1)
899  lloc = 1
900  npak = npak + 1
901  if (npak > this%maxpackages) then
902  call store_error('ERROR. MAXPACKAGES NOT SET LARGE ENOUGH.')
903  call this%parser%StoreErrorUnit()
904  end if
905  if (this%iexgmvr == 0) then
906  this%pckMemPaths(npak) = create_mem_path(this%name_model, word1)
907  word = word1
908  else
909  call this%parser%GetStringCaps(word2)
910  this%pckMemPaths(npak) = create_mem_path(word1, word2)
911  word = word2
912  end if
913  this%paknames(npak) = trim(word)
914  write (this%iout, '(3x,a,a)') 'INCLUDING PACKAGE: ', &
915  trim(this%pckMemPaths(npak))
916  end do
917  write (this%iout, '(1x,a)') 'END OF MVR PACKAGES'
918  else
919  call store_error('ERROR. REQUIRED PACKAGES BLOCK NOT FOUND.')
920  call this%parser%StoreErrorUnit()
921  end if
922  !
923  ! -- Check to make sure npak = this%maxpackages
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, ').'
928  call store_error(errmsg)
929  call this%parser%StoreErrorUnit()
930  end if
931  end subroutine read_packages
932 
933  !> @brief Check to make sure packages have mover activated
934  !<
935  subroutine check_packages(this)
936  ! -- modules
937  use constantsmodule, only: linelength
940  ! -- dummy
941  class(gwfmvrtype), intent(inout) :: this
942  ! -- local
943  character(len=LINELENGTH) :: errmsg
944  integer(I4B) :: i
945  integer(I4B), pointer :: imover_ptr
946  !
947  ! -- Check to make sure mover is activated for each package
948  do i = 1, size(this%pckMemPaths)
949  imover_ptr => null()
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.'
956  call store_error(errmsg)
957  end if
958  end do
959  !
960  ! -- Terminate if errors detected.
961  if (count_errors() > 0) then
962  call this%parser%StoreErrorUnit()
963  end if
964  end subroutine check_packages
965 
966  !> @brief Assign pointer to each package's packagemover object
967  !<
968  subroutine assign_packagemovers(this)
969  ! -- modules
971  ! -- dummy
972  class(gwfmvrtype), intent(inout) :: this
973  ! -- local
974  integer(I4B) :: i
975  !
976  ! -- Assign the package mover pointer if it hasn't been assigned yet
977  do i = 1, size(this%pckMemPaths)
978  if (this%pakmovers(i)%memoryPath == '') then
979  call set_packagemover_pointer(this%pakmovers(i), &
980  trim(this%pckMemPaths(i)))
981  end if
982  end do
983  end subroutine assign_packagemovers
984 
985  !> @brief Allocate package scalars
986  !<
987  subroutine allocate_scalars(this)
988  ! -- modules
989  use constantsmodule, only: done
991  ! -- dummy
992  class(gwfmvrtype) :: this
993  !
994  ! -- allocate scalars in NumericalPackageType
995  call this%NumericalPackageType%allocate_scalars()
996  !
997  ! -- Allocate
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)
1004  call mem_allocate(this%nmvr, 'NMVR', this%memoryPath)
1005  call mem_allocate(this%iexgmvr, 'IEXGMVR', this%memoryPath)
1006  call mem_allocate(this%imodelnames, 'IMODELNAMES', this%memoryPath)
1007  !
1008  ! -- Initialize
1009  this%reset_mapped_id = .false.
1010  this%ibudgetout = 0
1011  this%ibudcsv = 0
1012  this%maxmvr = -1
1013  this%maxpackages = -1
1014  this%maxcomb = 0
1015  this%nmvr = 0
1016  this%iexgmvr = 0
1017  this%imodelnames = 0
1018  !
1019  ! -- allocate the period data input object
1020  allocate (this%gwfmvrperioddata)
1021  end subroutine allocate_scalars
1022 
1023  !> @brief Allocate package arrays
1024  !<
1025  subroutine allocate_arrays(this)
1026  ! -- modules
1028  use constantsmodule, only: dzero
1030  ! -- dummy
1031  class(gwfmvrtype) :: this
1032  ! -- local
1033  integer(I4B) :: i
1034  !
1035  ! -- Allocate
1036  allocate (this%mvr(this%maxmvr))
1037  allocate (this%pckMemPaths(this%maxpackages))
1038  allocate (this%paknames(this%maxpackages))
1039  allocate (this%pakmovers(this%maxpackages))
1040  !
1041  ! -- nullify the pakmovers
1042  do i = 1, this%maxpackages
1043  call nulllify_packagemover_pointer(this%pakmovers(i))
1044  end do
1045  !
1046  ! -- allocate the perioddata object
1047  call this%gwfmvrperioddata%construct(this%maxmvr, this%memoryPath)
1048  !
1049  !
1050  ! -- allocate the object and assign values to object variables
1051  call mem_allocate(this%ientries, this%maxcomb, 'IENTRIES', this%memoryPath)
1052  !
1053  ! -- initialize ientries
1054  do i = 1, this%maxcomb
1055  this%ientries(i) = 0
1056  end do
1057  !
1058  ! -- setup the output table
1059  call this%mvr_setup_outputtab()
1060  end subroutine allocate_arrays
1061 
1062  !> @brief Set up the budget object that stores all the mvr flows
1063  !<
1064  subroutine mvr_setup_budobj(this)
1065  ! -- modules
1066  use constantsmodule, only: lenbudtxt
1068  ! -- dummy
1069  class(gwfmvrtype) :: this
1070  ! -- local
1071  integer(I4B) :: nbudterm
1072  integer(I4B) :: ncv
1073  integer(I4B) :: i
1074  integer(I4B) :: j
1075  integer(I4B) :: naux
1076  character(len=LENMODELNAME) :: modelname1, modelname2
1077  character(len=LENPACKAGENAME) :: packagename1, packagename2
1078  integer(I4B) :: maxlist
1079  integer(I4B) :: idx
1080  character(len=LENBUDTXT) :: text
1081  !
1082  ! -- Determine the number of mover budget terms. These are fixed for
1083  ! the simulation and cannot change. A separate term is required
1084  ! for each possible provider/receiver combination.
1085  nbudterm = 0
1086  do i = 1, this%maxpackages
1087  do j = 1, this%maxpackages
1088  nbudterm = nbudterm + 1
1089  end do
1090  end do
1091  !
1092  ! -- Number of control volumes is set to be 0, because there aren't
1093  ! any for the mover
1094  ncv = 0
1095  !
1096  ! -- set up budobj
1097  call this%budobj%budgetobject_df(ncv, nbudterm, 0, 0)
1098  idx = 0
1099  !
1100  ! -- Go through and set up each budget term
1101  text = ' MOVER-FLOW'
1102  maxlist = this%maxmvr
1103  naux = 0
1104  do i = 1, this%maxpackages
1105 
1106  call split_mem_path(this%pckMemPaths(i), modelname1, packagename1)
1107 
1108  do j = 1, this%maxpackages
1109 
1110  idx = idx + 1
1111  call split_mem_path(this%pckMemPaths(j), modelname2, packagename2)
1112  call this%budobj%budterm(idx)%initialize(text, &
1113  modelname1, &
1114  packagename1, &
1115  modelname2, &
1116  packagename2, &
1117  maxlist, .false., .false., &
1118  naux)
1119  end do
1120  end do
1121  end subroutine mvr_setup_budobj
1122 
1123  !> @brief Fill budget object
1124  !<
1125  subroutine fill_budobj(this)
1126  ! -- modules
1127  ! -- dummy
1128  class(gwfmvrtype) :: this
1129  ! -- local
1130  integer(I4B) :: idx
1131  integer(I4B) :: i
1132  integer(I4B) :: j
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
1140  real(DP) :: rval
1141  character(len=LENMODELNAME) :: modelname1, modelname2
1142  character(len=LENPACKAGENAME) :: packagename1, packagename2
1143  character(len=LENMEMPATH) :: pckMemPathsDummy
1144  real(DP) :: q
1145  !
1146  ! -- initialize counter
1147  idx = 0
1148 
1149  do i = 1, this%maxpackages
1150  ! -- Retrieve modelname1 and packagename1
1151  lloc = 1
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
1159  ! -- Retrieve modelname2 and packagename2
1160  lloc = 1
1161  call urword(this%pckMemPaths(j), lloc, istart, istop, 1, ival, rval, &
1162  -1, -1)
1163  pckmempathsdummy = this%pckMemPaths(j)
1164  modelname2 = pckmempathsdummy(istart:istop)
1165  call urword(this%pckMemPaths(j), lloc, istart, istop, 1, ival, rval, &
1166  -1, -1)
1167  pckmempathsdummy = this%pckMemPaths(j)
1168  packagename2 = pckmempathsdummy(istart:istop)
1169  ipos = (i - 1) * this%maxpackages + j
1170  nitems = this%ientries(ipos)
1171  !
1172  ! -- nitems is the number of mover connections for this
1173  ! model-package / model-package combination. Cycle if none.
1174  idx = idx + 1
1175  call this%budobj%budterm(idx)%reset(nitems)
1176  if (nitems < 1) cycle
1177  do n = 1, this%nmvr
1178  !
1179  ! -- pname1 is provider, pname2 is receiver
1180  ! flow is always negative because it is coming from provider
1181  if (this%pckMemPaths(i) == this%mvr(n)%mem_path_src) then
1182  if (this%pckMemPaths(j) == this%mvr(n)%mem_path_tgt) then
1183  !
1184  ! -- set q to qpactual
1185  q = -this%mvr(n)%qpactual
1186  !
1187  ! -- use mapped index (needed for lake to map outlet to lake number)
1188  n1 = this%mvr(n)%iRchNrSrcMapped
1189  !
1190  ! -- set receiver id to irch2
1191  n2 = this%mvr(n)%iRchNrTgt
1192  !
1193  ! -- check record into budget object
1194  call this%budobj%budterm(idx)%update_term(n1, n2, q)
1195  end if
1196  end if
1197  end do
1198  end do
1199  end do
1200  !
1201  ! --Terms are filled, now accumulate them for this time step
1202  call this%budobj%accumulate_terms()
1203  end subroutine fill_budobj
1204 
1205  !> @brief Set up output table
1206  !<
1207  subroutine mvr_setup_outputtab(this)
1208  ! -- dummy
1209  class(gwfmvrtype), intent(inout) :: this
1210  ! -- local
1211  character(len=LINELENGTH) :: title
1212  character(len=LINELENGTH) :: text
1213  integer(I4B) :: ntabcol
1214  integer(I4B) :: ilen
1215  !
1216  ! -- allocate and initialize the output table
1217  if (this%iprflow /= 0) then
1218  !
1219  ! -- dimension table
1220  ntabcol = 7
1221  !
1222  ! -- initialize the output table object
1223  title = 'WATER MOVER PACKAGE ('//trim(this%packName)// &
1224  ') FLOW RATES'
1225  call table_cr(this%outputtab, this%packName, title)
1226  call this%outputtab%table_df(this%maxmvr, ntabcol, this%iout, &
1227  transient=.true.)
1228  text = 'NUMBER'
1229  call this%outputtab%initialize_column(text, 10, alignment=tabcenter)
1230  text = 'PROVIDER LOCATION'
1231  ilen = lenmodelname + lenpackagename + 1
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'
1240  ilen = lenmodelname + lenpackagename + 1
1241  call this%outputtab%initialize_column(text, ilen)
1242  text = 'RECEIVER ID'
1243  call this%outputtab%initialize_column(text, 10)
1244  !
1245  end if
1246  end subroutine mvr_setup_outputtab
1247 
1248  !> @brief Set up output table
1249  !<
1250  subroutine mvr_print_outputtab(this)
1251  ! -- module
1252  use tdismodule, only: kstp, kper
1253  ! -- dummy
1254  class(gwfmvrtype), intent(inout) :: this
1255  ! -- local
1256  character(len=LINELENGTH) :: title
1257  integer(I4B) :: i
1258  !
1259  ! -- set table kstp and kper
1260  call this%outputtab%set_kstpkper(kstp, kper)
1261  !
1262  ! -- Add terms and print the table
1263  title = 'WATER MOVER PACKAGE ('//trim(this%packName)// &
1264  ') FLOW RATES'
1265  call this%outputtab%set_title(title)
1266  call this%outputtab%set_maxbound(this%nmvr)
1267  do i = 1, 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)
1275  end do
1276  end subroutine mvr_print_outputtab
1277 
1278  !> @brief Set mapped id
1279  !!
1280  !! For the budget output, we don't write outlet number,
1281  !! instead we write the lake number. Normally the receiver
1282  !! number is the same as the feature number provided by the
1283  !! user. For moving water from a lake, the user specifies the
1284  !! outlet number, not the lake number, in the mover package.
1285  !! The iRchNrSrcMapped variable contains the lake number, not
1286  !! the outlet number, and is written to the budget files. For
1287  !! other packages, the iRchNrSrcMapped value is simply the well
1288  !! number, the stream reach, or the uzf cell number.
1289  !! This routine needs to be called each time a new set of movers
1290  !! is read. It can't be called from within mvr_rp because the
1291  !! iprmap isn't updated by lake until lak_rp, which is called
1292  !! after mvr_rp.
1293  !<
1294  subroutine set_mapped_id(this)
1295  ! -- dummy
1296  class(gwfmvrtype) :: this
1297  ! -- locals
1298  integer(I4B) :: i, mapped_id
1299  class(packagemovertype), pointer :: pkg_mvr
1300  ! -- formats
1301  !
1302  ! -- set the feature maps
1303  allocate (pkg_mvr)
1304  do i = 1, this%nmvr
1305  call set_packagemover_pointer(pkg_mvr, this%mvr(i)%mem_path_src)
1306  mapped_id = pkg_mvr%iprmap(this%mvr(i)%iRchNrSrc)
1307  this%mvr(i)%iRchNrSrcMapped = mapped_id
1308  end do
1309  deallocate (pkg_mvr)
1310  end subroutine set_mapped_id
1311 
1312 end module
This module contains block parser methods.
Definition: BlockParser.f90:7
This module contains the BudgetModule.
Definition: Budget.f90:20
subroutine, public budget_cr(this, name_model)
@ brief Create a new budget object
Definition: Budget.f90:84
subroutine, public budgetobject_cr(this, name)
Create a new budget object.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
@ tabcenter
centered table column
Definition: Constants.f90:172
integer(i4b), parameter lenmodelname
maximum length of the model name
Definition: Constants.f90:22
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
real(dp), parameter dnodata
real no data constant
Definition: Constants.f90:95
integer(i4b), parameter lenpakloc
maximum length of a package location
Definition: Constants.f90:50
integer(i4b), parameter lenauxname
maximum length of a aux variable
Definition: Constants.f90:35
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:47
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:37
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine, public mvr_cr(mvrobj, name_parent, inunit, iout, dis, iexgmvr)
Create a new mvr object.
Definition: gwf-mvr.f90:186
subroutine mvr_da(this)
Deallocate.
Definition: gwf-mvr.f90:633
subroutine allocate_scalars(this)
Allocate package scalars.
Definition: gwf-mvr.f90:988
subroutine mvr_bdsav(this, icbcfl, ibudfl, isuppress_output)
Write mover terms.
Definition: gwf-mvr.f90:499
subroutine initialize_movers(this, nr_active_movers)
Definition: gwf-mvr.f90:405
subroutine fill_budobj(this)
Fill budget object.
Definition: gwf-mvr.f90:1126
subroutine check_packages(this)
Check to make sure packages have mover activated.
Definition: gwf-mvr.f90:936
subroutine mvr_init(this, name_parent, inunit, iout, dis, iexgmvr)
Definition: gwf-mvr.f90:202
subroutine mvr_setup_budobj(this)
Set up the budget object that stores all the mvr flows.
Definition: gwf-mvr.f90:1065
subroutine mvr_bd(this)
Fill the mover budget object.
Definition: gwf-mvr.f90:478
subroutine read_options(this)
Read options specified in the input options block.
Definition: gwf-mvr.f90:687
subroutine assign_packagemovers(this)
Assign pointer to each package's packagemover object.
Definition: gwf-mvr.f90:969
subroutine mvr_ot_printflow(this, icbcfl, ibudfl)
Print mover flow table.
Definition: gwf-mvr.f90:557
subroutine mvr_setup_outputtab(this)
Set up output table.
Definition: gwf-mvr.f90:1208
subroutine read_dimensions(this)
Read the dimensions for this package.
Definition: gwf-mvr.f90:806
subroutine mvr_fc(this)
Calculate qfrommvr as a function of qtomvr.
Definition: gwf-mvr.f90:437
subroutine mvr_rp(this)
Read and Prepare.
Definition: gwf-mvr.f90:276
subroutine mvr_ad(this)
Definition: gwf-mvr.f90:424
subroutine mvr_ot_saveflow(this, icbcfl, ibudfl)
Write mover terms.
Definition: gwf-mvr.f90:533
subroutine mvr_cc(this, innertot, kiter, iend, icnvgmod, cpak, ipak, dpak)
Extra convergence check for mover.
Definition: gwf-mvr.f90:451
subroutine mvr_ot_bdsummary(this, ibudfl)
Write mover budget to listing file.
Definition: gwf-mvr.f90:571
subroutine mvr_print_outputtab(this)
Set up output table.
Definition: gwf-mvr.f90:1251
subroutine mvr_ar(this)
Allocate and read water mover information.
Definition: gwf-mvr.f90:241
subroutine allocate_arrays(this)
Allocate package arrays.
Definition: gwf-mvr.f90:1026
subroutine set_mapped_id(this)
Set mapped id.
Definition: gwf-mvr.f90:1295
subroutine read_packages(this)
Read the packages that will be managed by this mover.
Definition: gwf-mvr.f90:875
subroutine check_options(this)
Check MODELNAMES option set correctly.
Definition: gwf-mvr.f90:776
This module contains the GwfMvrPeriodDataModule Module.
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
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This module defines variable data types.
Definition: kind.f90:8
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.
Definition: Mover.f90:7
This module contains the base numerical package type.
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
subroutine, public nulllify_packagemover_pointer(packagemover)
subroutine, public set_packagemover_pointer(packagemover, memPath)
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
subroutine, public table_cr(this, name, title)
Definition: Table.f90:87
real(dp), pointer, public pertim
time relative to start of stress period
Definition: tdis.f90:30
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
integer(i4b), pointer, public nper
number of stress period
Definition: tdis.f90:21
Derived type for the Budget object.
Definition: Budget.f90:39
Derived type for GwfMvrPeriodDataType.
Derived type for MvrType.
Definition: Mover.f90:29