MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
prt-prp.f90
Go to the documentation of this file.
2  use kindmodule, only: dp, i4b, lgp
5  mnormal
6  use bndmodule, only: bndtype
8  use tablemodule, only: tabletype, table_cr
14  use prtfmimodule, only: prtfmitype
25 
26  implicit none
27 
28  private
29  public :: prtprptype
30  public :: prp_create
31 
32  character(len=LENFTYPE) :: ftype = 'PRP'
33  character(len=16) :: text = ' PRP'
34 
35  !> @brief Particle release point (PRP) package
36  type, extends(bndtype) :: prtprptype
37  type(prtfmitype), pointer :: fmi => null() !< flow model interface
38  type(particlestoretype), pointer :: particles => null() !< particle store
39  type(trackfilecontroltype), pointer :: trackfilectl => null() !< track file control
40  integer(I4B), pointer :: nreleasepts => null() !< number of release points
41  integer(I4B), pointer :: nparticles => null() !< number of particles released
42  integer(I4B), pointer :: istopweaksink => null() !< weak sink option: 0 = no stop, 1 = stop
43  integer(I4B), pointer :: istopzone => null() !< optional stop zone number: 0 = no stop zone
44  integer(I4B), pointer :: idrape => null() !< drape option: 0 = do not drape, 1 = drape to topmost active cell
45  integer(I4B), pointer :: itrkout => null() !< binary track file
46  integer(I4B), pointer :: itrkhdr => null() !< track header file
47  integer(I4B), pointer :: itrkcsv => null() !< CSV track file
48  integer(I4B), pointer :: irlstls => null() !< release time file
49  logical(LGP), pointer :: localz => null() !< compute z coordinates local to the cell
50  logical(LGP), pointer :: rlsall => null() !< release in all time step
51  logical(LGP), pointer :: rlsfirst => null() !< release in first time step
52  logical(LGP), pointer :: rlstimelist => null() !< use global release time
53  real(dp), pointer :: offset => null() !< release time offset
54  real(dp), pointer :: stoptime => null() !< stop time for all release points
55  real(dp), pointer :: stoptraveltime => null() !< stop travel time for all points
56  integer(I4B), pointer, contiguous :: rlskstp(:) !< time steps selected for release
57  integer(I4B), pointer, contiguous :: rptnode(:) => null() !< release point reduced nns
58  integer(I4B), pointer, contiguous :: rptzone(:) => null() !< release point zone numbers
59  real(dp), pointer, contiguous :: rptx(:) => null() !< release point x coordinates
60  real(dp), pointer, contiguous :: rpty(:) => null() !< release point y coordinates
61  real(dp), pointer, contiguous :: rptz(:) => null() !< release point z coordinates
62  real(dp), pointer, contiguous :: locz(:) => null() !< release point local z coordinates
63  real(dp), pointer, contiguous :: rptmass(:) => null() !< total mass released from point
64  character(len=LENBOUNDNAME), pointer, contiguous :: rptname(:) => null() !< release point names
65  type(timeselecttype), pointer :: releasetimes
66 
67  contains
68  procedure :: prp_allocate_arrays
69  procedure :: prp_allocate_scalars
70  procedure :: bnd_ar => prp_ar
71  procedure :: bnd_ad => prp_ad
72  procedure :: bnd_rp => prp_rp
73  procedure :: bnd_cq_simrate => prp_cq_simrate
74  procedure :: bnd_da => prp_da
75  procedure :: define_listlabel
76  procedure :: prp_set_pointers
77  procedure :: bnd_options => prp_options
78  procedure :: read_dimensions => prp_read_dimensions
79  procedure :: prp_read_packagedata
80  procedure, public :: bnd_obs_supported => prp_obs_supported
81  procedure, public :: bnd_df_obs => prp_df_obs
82  end type prtprptype
83 
84 contains
85 
86  !> @brief Create a new particle release point package
87  subroutine prp_create(packobj, id, ibcnum, inunit, iout, namemodel, &
88  pakname, mempath, fmi)
89  ! -- dummy
90  class(bndtype), pointer :: packobj
91  integer(I4B), intent(in) :: id
92  integer(I4B), intent(in) :: ibcnum
93  integer(I4B), intent(in) :: inunit
94  integer(I4B), intent(in) :: iout
95  character(len=*), intent(in) :: namemodel
96  character(len=*), intent(in) :: pakname
97  character(len=*), intent(in) :: mempath
98  type(prtfmitype), pointer :: fmi
99  ! -- local
100  type(prtprptype), pointer :: prpobj
101  ! -- formats
102  character(len=*), parameter :: fmtheader = &
103  "(1x, /1x, 'PRP -- PARTICLE RELEASE POINT PACKAGE', &
104  &' INPUT READ FROM MEMPATH: ', A, /)"
105 
106  ! -- allocate the object and assign values to object variables
107  allocate (prpobj)
108  packobj => prpobj
109 
110  ! -- create name and memory path
111  call packobj%set_names(ibcnum, namemodel, pakname, ftype, mempath)
112  prpobj%text = text
113 
114  ! -- allocate scalars
115  call prpobj%prp_allocate_scalars()
116 
117  ! -- initialize package
118  call packobj%pack_initialize()
119 
120  packobj%inunit = inunit
121  packobj%iout = iout
122  packobj%id = id
123  packobj%ibcnum = ibcnum
124  packobj%ncolbnd = 4
125  packobj%iscloc = 1
126 
127  ! -- store pointer to flow model interface
128  prpobj%fmi => fmi
129 
130  ! -- if prp is enabled, print a message identifying it
131  if (inunit > 0) write (iout, fmtheader) mempath
132  end subroutine prp_create
133 
134  !> @brief Deallocate memory
135  subroutine prp_da(this)
136  class(prtprptype) :: this
137 
138  ! -- deallocate parent
139  call this%BndType%bnd_da()
140 
141  ! -- deallocate scalars
142  call mem_deallocate(this%rlsall)
143  call mem_deallocate(this%rlsfirst)
144  call mem_deallocate(this%rlstimelist)
145  call mem_deallocate(this%localz)
146  call mem_deallocate(this%offset)
147  call mem_deallocate(this%stoptime)
148  call mem_deallocate(this%stoptraveltime)
149  call mem_deallocate(this%istopweaksink)
150  call mem_deallocate(this%istopzone)
151  call mem_deallocate(this%idrape)
152  call mem_deallocate(this%nreleasepts)
153  call mem_deallocate(this%nparticles)
154  call mem_deallocate(this%itrkout)
155  call mem_deallocate(this%itrkhdr)
156  call mem_deallocate(this%itrkcsv)
157  call mem_deallocate(this%irlstls)
158 
159  ! -- deallocate arrays
160  call mem_deallocate(this%rptx)
161  call mem_deallocate(this%rpty)
162  call mem_deallocate(this%rptz)
163  call mem_deallocate(this%locz)
164  call mem_deallocate(this%rptnode)
165  call mem_deallocate(this%rptmass)
166  call mem_deallocate(this%rlskstp)
167  call mem_deallocate(this%rptname, 'RPTNAME', this%memoryPath)
168 
169  ! -- deallocate particle store
170  call this%particles%destroy(this%memoryPath)
171  deallocate (this%particles)
172 
173  ! -- deallocate release time selection
174  call this%releasetimes%destroy()
175  deallocate (this%releasetimes)
176  end subroutine prp_da
177 
178  !> @ brief Set pointers to model variables
179  subroutine prp_set_pointers(this, ibound, izone, trackfilectl)
180  ! -- dummy variables
181  class(prtprptype) :: this
182  integer(I4B), dimension(:), pointer, contiguous :: ibound
183  integer(I4B), dimension(:), pointer, contiguous :: izone
184  type(trackfilecontroltype), pointer :: trackfilectl
185 
186  this%ibound => ibound
187  this%rptzone => izone
188  this%trackfilectl => trackfilectl
189  end subroutine prp_set_pointers
190 
191  !> @brief Allocate arrays
192  subroutine prp_allocate_arrays(this, nodelist, auxvar)
193  ! -- dummy
194  class(prtprptype) :: this
195  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
196  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
197  ! -- local
198  integer(I4B) :: nps
199 
200  ! -- Allocate particle store, starting with the number
201  ! of release points (arrays resized if/when needed)
202  call create_particle_store(this%particles, this%nreleasepts, this%memoryPath)
203 
204  ! -- Allocate arrays
205  call mem_allocate(this%rptx, this%nreleasepts, 'RPTX', this%memoryPath)
206  call mem_allocate(this%rpty, this%nreleasepts, 'RPTY', this%memoryPath)
207  call mem_allocate(this%rptz, this%nreleasepts, 'RPTZ', this%memoryPath)
208  call mem_allocate(this%locz, this%nreleasepts, 'LOCZ', this%memoryPath)
209  call mem_allocate(this%rptmass, this%nreleasepts, 'RPTMASS', this%memoryPath)
210  call mem_allocate(this%rptnode, this%nreleasepts, 'RPTNODER', &
211  this%memoryPath)
212  call mem_allocate(this%rlskstp, 1, 'RLSKSTP', this%memoryPath)
213  call mem_allocate(this%rptname, lenboundname, this%nreleasepts, &
214  'RPTNAME', this%memoryPath)
215 
216  ! -- Initialize arrays
217  this%rlskstp(1) = 1 ! single release in first time step by default
218  do nps = 1, this%nreleasepts
219  this%rptmass(nps) = dzero
220  end do
221  end subroutine prp_allocate_arrays
222 
223  !> @brief Allocate scalars
224  subroutine prp_allocate_scalars(this)
225  class(prtprptype) :: this
226 
227  ! -- Allocate release time selection
228  allocate (this%releasetimes)
229  call this%releasetimes%init()
230 
231  ! -- call standard BndType allocate scalars
232  call this%BndType%allocate_scalars()
233 
234  ! -- Allocate scalars for this type
235  call mem_allocate(this%rlsall, 'RLSALL', this%memoryPath)
236  call mem_allocate(this%rlsfirst, 'RLSFIRST', this%memoryPath)
237  call mem_allocate(this%rlstimelist, 'RELEASETIME', this%memoryPath)
238  call mem_allocate(this%localz, 'LOCALZ', this%memoryPath)
239  call mem_allocate(this%offset, 'OFFSET', this%memoryPath)
240  call mem_allocate(this%stoptime, 'STOPTIME', this%memoryPath)
241  call mem_allocate(this%stoptraveltime, 'STOPTRAVELTIME', this%memoryPath)
242  call mem_allocate(this%istopweaksink, 'ISTOPWEAKSINK', this%memoryPath)
243  call mem_allocate(this%istopzone, 'ISTOPZONE', this%memoryPath)
244  call mem_allocate(this%idrape, 'IDRAPE', this%memoryPath)
245  call mem_allocate(this%nreleasepts, 'NRELEASEPTS', this%memoryPath)
246  call mem_allocate(this%nparticles, 'NPART', this%memoryPath)
247  call mem_allocate(this%itrkout, 'ITRKOUT', this%memoryPath)
248  call mem_allocate(this%itrkhdr, 'ITRKHDR', this%memoryPath)
249  call mem_allocate(this%itrkcsv, 'ITRKCSV', this%memoryPath)
250  call mem_allocate(this%irlstls, 'IRLSTLS', this%memoryPath)
251 
252  ! -- Set values
253  this%rlsall = .false.
254  this%rlsfirst = .false.
255  this%rlstimelist = .false.
256  this%localz = .false.
257  this%offset = dzero
258  this%stoptime = huge(1d0)
259  this%stoptraveltime = huge(1d0)
260  this%istopweaksink = 0
261  this%istopzone = 0
262  this%idrape = 0
263  this%nreleasepts = 0
264  this%nparticles = 0
265  this%itrkout = 0
266  this%itrkhdr = 0
267  this%itrkcsv = 0
268  this%irlstls = 0
269  end subroutine prp_allocate_scalars
270 
271  !> @ brief Allocate and read period data
272  subroutine prp_ar(this)
273  ! -- dummy variables
274  class(prtprptype), intent(inout) :: this
275  ! -- local variables
276  integer(I4B) :: n
277 
278  call this%obs%obs_ar()
279  call this%BndType%allocate_arrays()
280  if (this%inamedbound /= 0) then
281  do n = 1, this%nreleasepts
282  this%boundname(n) = this%rptname(n)
283  end do
284  end if
285  do n = 1, this%nreleasepts
286  this%nodelist(n) = this%rptnode(n)
287  end do
288  ! if (this%imover /= 0) then
289  ! allocate(this%pakmvrobj)
290  ! call this%pakmvrobj%ar(this%maxbound, this%maxbound, this%memoryPath)
291  ! endif
292  end subroutine prp_ar
293 
294  !> @brief Advance a time step and release particles if appropriate.
295  !!
296  !! Releases may be scheduled via a global RELEASETIME, or within a
297  !! stress period via ALL, FIRST, FREQUENCY or STEPS (with optional
298  !! FRACTION). If no release option is specified, a single release
299  !! is conducted at the first moment of the first time step of the
300  !! first stress period.
301  !<
302  subroutine prp_ad(this)
303  ! -- modules
304  use tdismodule, only: totimc, delt, kstp
305  use dismodule, only: distype
306  use disvmodule, only: disvtype
307  ! -- dummy
308  class(prtprptype) :: this
309  ! -- local
310  character(len=LINELENGTH) :: errmsg
311  integer(I4B) :: ic, icu, nps, nts, nrel, &
312  nreleasets, np, irow, icol, ilay, icpl
313  real(DP) :: x, y, z, trelease, tend, top, bot, hds
314  real(DP), allocatable :: polyverts(:, :)
315  type(particletype), pointer :: particle
316 
317  ! -- Check if there's a release to make
318  if (.not. ( &
319  ! all time steps?
320  this%rlsall .or. &
321  ! first time step?
322  (this%rlsfirst .and. kstp == 1) .or. &
323  ! specified time steps?
324  any(this%rlskstp == kstp) .or. &
325  ! specified release times?
326  this%rlstimelist)) return
327 
328  if (this%rlstimelist) then
329  nreleasets = size(this%releasetimes%times)
330  else
331  nreleasets = 1
332  end if
333  nrel = this%nreleasepts * nreleasets
334 
335  ! -- Reset mass release for time step
336  do nps = 1, this%nreleasepts
337  this%rptmass(nps) = dzero
338  end do
339 
340  ! -- Resize particle store if another set
341  ! of particles will exceed its capacity
342  if ((this%nparticles + nrel) > size(this%particles%irpt)) &
343  call this%particles%resize( &
344  size(this%particles%irpt) + nrel, &
345  this%memoryPath)
346 
347  ! -- Release a particle from each point...
348  do nps = 1, this%nreleasepts
349  ic = this%rptnode(nps)
350  icu = this%dis%get_nodeuser(ic)
351  ! -- ...for each release time in the current time step
352  tsloop: do nts = 1, nreleasets
353  if (this%rlstimelist) then
354  trelease = this%releasetimes%times(nts)
355  tend = totimc + delt
356  if (trelease < totimc .or. trelease >= tend) cycle tsloop
357  else
358  trelease = totimc + this%offset * delt
359  end if
360 
361  np = this%nparticles + 1
362  this%nparticles = np
363 
364  ! -- Check release point is within the specified cell
365  ! and not above/below grid top/bottom respectively
366  x = this%rptx(nps)
367  y = this%rpty(nps)
368  z = this%rptz(nps)
369  call this%dis%get_polyverts(ic, polyverts)
370  if (.not. point_in_polygon(x, y, polyverts)) then
371  write (errmsg, '(a,g0,a,g0,a,i0)') &
372  'Error: release point (x=', x, ', y=', y, ') is not in cell ', icu
373  call store_error(errmsg, terminate=.false.)
374  call store_error_unit(this%inunit, terminate=.true.)
375  end if
376  if (z > maxval(this%dis%top)) then
377  write (errmsg, '(a,g0,a,g0,a,i0)') &
378  'Error: release point (z=', z, ') is above grid top ', &
379  maxval(this%dis%top)
380  call store_error(errmsg, terminate=.false.)
381  call store_error_unit(this%inunit, terminate=.true.)
382  else if (z < minval(this%dis%bot)) then
383  write (errmsg, '(a,g0,a,g0,a,i0)') &
384  'Error: release point (z=', z, ') is below grid bottom ', &
385  minval(this%dis%bot)
386  call store_error(errmsg, terminate=.false.)
387  call store_error_unit(this%inunit, terminate=.true.)
388  end if
389 
390  ! -- Initialize particle and add it to particle store
391  ! -- Todo: branch depending on exchange PRP or a normal PRP.
392  ! if exchange PRP, particle identity properties should be
393  ! passed in (e.g. imdl, iprp, irpt, trelease, name).
394  ! if normal PRP, imdl and iprp should be set from pointers
395  ! provided to PRP by PRT model; irpt and trelease as below.
396  allocate (particle)
397  call create_particle(particle)
398  if (size(this%boundname) /= 0) then
399  particle%name = this%boundname(nps)
400  else
401  particle%name = ''
402  end if
403  particle%irpt = nps
404  particle%istopweaksink = this%istopweaksink
405  particle%istopzone = this%istopzone
406  particle%icu = icu
407  select type (dis => this%dis)
408  type is (distype)
409  call get_ijk(icu, dis%nrow, dis%ncol, dis%nlay, irow, icol, ilay)
410  type is (disvtype)
411  call get_jk(icu, dis%ncpl, dis%nlay, icpl, ilay)
412  end select
413  particle%ilay = ilay
414  particle%izone = this%rptzone(ic)
415  particle%istatus = 0
416  ! Handle inactive cells
417  if (this%ibound(ic) == 0) then
418  ! -- If drape option activated, release in highest active
419  ! cell vertically below release point.
420  if (this%idrape /= 0) &
421  call this%dis%highest_active(ic, this%ibound)
422  ! -- If returned cell is inactive, do not release particle
423  if (this%ibound(ic) == 0) &
424  particle%istatus = 8 ! permanently unreleased
425  end if
426  particle%x = x
427  particle%y = y
428  if (this%localz) then
429  top = this%fmi%dis%top(ic)
430  bot = this%fmi%dis%bot(ic)
431  hds = this%fmi%gwfhead(ic)
432  particle%z = bot + this%rptz(nps) * (hds - bot)
433  else
434  particle%z = this%rptz(nps)
435  end if
436  particle%trelease = trelease
437  ! Set stopping time to earlier of times specified by STOPTIME and STOPTRAVELTIME
438  if (this%stoptraveltime == huge(1d0)) then
439  particle%tstop = this%stoptime
440  else
441  particle%tstop = particle%trelease + this%stoptraveltime
442  if (this%stoptime < particle%tstop) particle%tstop = this%stoptime
443  end if
444  particle%ttrack = particle%trelease
445  particle%idomain(1) = 0
446  particle%iboundary(1) = 0
447  particle%idomain(2) = ic
448  particle%iboundary(2) = 0
449  particle%idomain(3) = 0
450  particle%iboundary(3) = 0
451  call this%particles%load_from_particle(particle, np)
452 
453  ! -- Accumulate mass release from this point
454  this%rptmass(nps) = this%rptmass(nps) + done
455  end do tsloop
456  end do
457  end subroutine prp_ad
458 
459  !> @ brief Read and prepare period data for particle input
460  subroutine prp_rp(this)
461  ! -- modules
462  use tdismodule, only: kper, nper, nstp
463  use inputoutputmodule, only: urword
464  ! -- dummy variables
465  class(prtprptype), intent(inout) :: this
466  ! -- local variables
467  integer(I4B) :: ierr
468  integer(I4B) :: n, i
469  integer(I4B) :: lloc, istart, istop, ival
470  real(DP) :: dval
471  logical(LGP) :: isfound
472  logical(LGP) :: endOfBlock
473  logical(LGP) :: use_last
474  logical(LGP) :: noperiodblocks
475  character(len=LINELENGTH) :: keyword
476  character(len=:), allocatable :: line
477  ! -- formats
478  character(len=*), parameter :: fmtblkerr = &
479  "('Looking for BEGIN PERIOD iper. &
480  &Found ', a, ' instead.')"
481  character(len=*), parameter :: fmt_steps = &
482  "(6x,'TIME STEP(S) ',50(I0,' '))" ! kluge 50 (similar to STEPS in OC)?
483  character(len=*), parameter :: fmt_freq = &
484  "(6x,'EVERY ',I0,' TIME STEP(S)')"
485  character(len=*), parameter :: fmt_fracs = &
486  "(6x,50(f10.3,' '))"
487 
488  ! -- Set ionper to the stress period number for which a new block of data
489  ! will be read.
490  if (this%inunit == 0) return
491 
492  ! -- get stress period data
493  noperiodblocks = .false.
494  if (this%ionper < kper) then
495  ! -- get period block
496  call this%parser%GetBlock('PERIOD', isfound, ierr, &
497  supportopenclose=.true., &
498  blockrequired=.false.)
499  if (isfound) then
500  ! -- read ionper and check for increasing period numbers
501  call this%read_check_ionper()
502  else
503  ! -- PERIOD block not found
504  if (ierr < 0) then
505  if (kper == 1) then
506  ! -- End of file found; no period data for the simulation.
507  noperiodblocks = .true.
508  else
509  ! -- End of file found; no more period data.
510  this%ionper = nper + 1
511  end if
512  else
513  ! -- Found invalid block
514  call this%parser%GetCurrentLine(line)
515  write (errmsg, fmtblkerr) adjustl(trim(line))
516  call store_error(errmsg, terminate=.true.)
517  end if
518  end if
519  end if
520 
521  ! -- If no period data for the simulation default to single
522  ! release at beginning of first period's first time step.
523  ! Otherwise read release timing settings from the period
524  ! data block of the package input file.
525  if (noperiodblocks) then
526  if (kper == 1) then
527  call mem_reallocate(this%rlskstp, 1, &
528  "RLSKSTP", this%memoryPath)
529  this%rlsfirst = .true.
530  use_last = .false.
531  end if
532  ! -- If the current stress period matches the
533  ! block we are reading continue parsing it
534  else if (this%ionper == kper) then
535  use_last = .false.
536  recordloop: do
537  call this%parser%GetNextLine(endofblock)
538  if (endofblock) exit
539  call this%parser%GetStringCaps(keyword)
540  select case (keyword)
541  case ('ALL')
542  this%rlsall = .true.
543  case ('STEPS')
544  call mem_reallocate(this%rlskstp, 0, &
545  "RLSKSTP", this%memoryPath)
546  call this%parser%GetRemainingLine(line)
547  lloc = 1
548  stepslistsearch: do
549  call urword(line, lloc, istart, istop, 2, ival, dval, -1, 0)
550  if (ival > 0) then
551  n = size(this%rlskstp)
552  call mem_reallocate(this%rlskstp, n + 1, &
553  'RLSKSTP', this%memoryPath)
554  this%rlskstp(n + 1) = ival
555  cycle stepslistsearch
556  end if
557  exit stepslistsearch
558  end do stepslistsearch
559  case ('FIRST')
560  this%rlsfirst = .true.
561  case ('FREQUENCY')
562  ival = this%parser%GetInteger()
563  if (ival < 0) then
564  errmsg = "FREQUENCY must be non-negative"
565  call store_error(errmsg)
566  call this%parser%StoreErrorUnit(terminate=.true.)
567  end if
568  do i = 1, nstp(this%ionper)
569  if (mod(i, ival) == 0) then
570  n = size(this%rlskstp)
571  call mem_reallocate(this%rlskstp, n + 1, &
572  'RLSKSTP', this%memoryPath)
573  this%rlskstp(n + 1) = i
574  end if
575  end do
576  case ('FRACTION')
577  dval = this%parser%GetDouble()
578  this%offset = dval
579  case default
580  write (errmsg, '(2a)') &
581  'Looking for ALL, STEPS, FIRST, FREQUENCY, or FRACTION. Found: ', &
582  trim(adjustl(keyword))
583  call store_error(errmsg, terminate=.true.)
584  end select
585  end do recordloop
586  else
587  ! -- else repeat period settings
588  use_last = .true.
589  end if
590 
591  ! -- write settings to list file
592  if (.not. any(this%rlskstp > 0)) then
593  write (this%iout, "(1x,/1x,a)") 'NO PARTICLE RELEASES IN THIS STRESS '// &
594  'PERIOD'
595  else if (use_last) then
596  write (this%iout, "(1x,/1x,a)") 'REUSING PARTICLE RELEASE SETTINGS '// &
597  'FROM LAST STRESS PERIOD'
598  else
599  ! -- write particle release setting
600  write (this%iout, "(1x,/1x,a)", advance='no') 'PARTICLE RELEASE:'
601  if (any(this%rlskstp > 0)) then
602  n = size(this%rlskstp)
603  if (n > 0) write (this%iout, fmt_steps, advance='no') this%rlskstp
604  end if
605  write (this%iout, "(1x,a)", advance='no') 'AT OFFSET'
606  write (this%iout, fmt_fracs) (/this%offset/)
607  write (this%iout, '(A)')
608  end if
609  end subroutine prp_rp
610 
611  !> @ brief Calculate flow between package and model.
612  subroutine prp_cq_simrate(this, hnew, flowja, imover)
613  ! -- modules
614  use tdismodule, only: delt
615  ! -- dummy variables
616  class(prtprptype) :: this
617  real(DP), dimension(:), intent(in) :: hnew !< todo: mass concentration?
618  real(DP), dimension(:), intent(inout) :: flowja !< flow between package and model
619  integer(I4B), intent(in) :: imover !< flag indicating if the mover package is active
620  ! -- local variables
621  integer(I4B) :: i
622  integer(I4B) :: node
623  integer(I4B) :: idiag
624  real(DP) :: rrate
625 
626  ! -- If no boundaries, skip flow calculations.
627  if (this%nbound <= 0) return
628 
629  ! -- Loop through each boundary calculating flow.
630  do i = 1, this%nbound
631  node = this%nodelist(i)
632  rrate = dzero
633  ! -- If cell is no-flow or constant-head, then ignore it.
634  ! todo: think about condition(s) under which to ignore cell
635  if (node > 0) then
636  idiag = this%dis%con%ia(node)
637  ! todo: think about condition(s) under which to ignore cell
638  ! -- Calculate the flow rate into the cell.
639  rrate = this%rptmass(i) * (done / delt) ! reciprocal of tstp length
640  flowja(idiag) = flowja(idiag) + rrate
641  end if
642 
643  ! -- Save simulated value to simvals array.
644  this%simvals(i) = rrate
645  end do
646  end subroutine prp_cq_simrate
647 
648  !> @ brief Define list heading written with PRINT_INPUT option
649  subroutine define_listlabel(this) ! kluge note: update for PRT?
650  class(prtprptype), intent(inout) :: this
651 
652  ! -- create the header list label
653  this%listlabel = trim(this%filtyp)//' NO.'
654  if (this%dis%ndim == 3) then
655  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
656  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'ROW'
657  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'COL'
658  elseif (this%dis%ndim == 2) then
659  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'LAYER'
660  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'CELL2D'
661  else
662  write (this%listlabel, '(a, a7)') trim(this%listlabel), 'NODE'
663  end if
664  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'STRESS RATE'
665  if (this%inamedbound == 1) then
666  write (this%listlabel, '(a, a16)') trim(this%listlabel), 'BOUNDARY NAME'
667  end if
668  end subroutine define_listlabel
669 
670  !> @brief Indicates whether observations are supported.
671  logical function prp_obs_supported(this)
672  class(prtprptype) :: this
673  prp_obs_supported = .true.
674  end function prp_obs_supported
675 
676  !> @brief Store supported observations
677  subroutine prp_df_obs(this)
678  ! -- dummy
679  class(prtprptype) :: this
680  ! -- local
681  integer(I4B) :: indx
682  call this%obs%StoreObsType('prp', .true., indx)
683  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
684 
685  ! -- Store obs type and assign procedure pointer
686  ! for to-mvr observation type.
687  call this%obs%StoreObsType('to-mvr', .true., indx)
688  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
689  end subroutine prp_df_obs
690 
691  !> @brief Set options specific to PrtPrpType
692  subroutine prp_options(this, option, found)
693  use openspecmodule, only: access, form
694  use constantsmodule, only: maxcharlen, dzero
697  ! -- dummy
698  class(prtprptype), intent(inout) :: this
699  character(len=*), intent(inout) :: option
700  logical, intent(inout) :: found
701  ! -- locals
702  real(DP) :: dval
703  integer(I4B) :: i, ios, nlines
704  logical(LGP) :: success
705  character(len=MAXCHARLEN) :: fname
706  character(len=MAXCHARLEN) :: keyword
707  character(len=:), allocatable :: line
708  ! -- formats
709  character(len=*), parameter :: fmttrkbin = &
710  "(4x, 'PARTICLE TRACKS WILL BE SAVED TO BINARY FILE: ', a, /4x, &
711  &'OPENED ON UNIT: ', I0)"
712  character(len=*), parameter :: fmttrkcsv = &
713  "(4x, 'PARTICLE TRACKS WILL BE SAVED TO CSV FILE: ', a, /4x, &
714  &'OPENED ON UNIT: ', I0)"
715 
716  select case (option)
717  case ('STOPTIME')
718  this%stoptime = this%parser%GetDouble()
719  found = .true.
720  case ('STOPTRAVELTIME')
721  this%stoptraveltime = this%parser%GetDouble()
722  found = .true.
723  case ('STOP_AT_WEAK_SINK')
724  this%istopweaksink = 1
725  found = .true.
726  case ('ISTOPZONE')
727  this%istopzone = this%parser%GetInteger()
728  found = .true.
729  case ('DRAPE')
730  this%idrape = 1
731  found = .true.
732  case ('RELEASE_TIMES')
733  rtloop: do
734  success = .false.
735  call this%parser%TryGetDouble(dval, success)
736  if (.not. success) exit rtloop
737  call this%releasetimes%expand()
738  this%releasetimes%times(size(this%releasetimes%times)) = dval
739  end do rtloop
740  if (.not. this%releasetimes%increasing()) then
741  errmsg = "RELEASE TIMES MUST STRICTLY INCREASE"
742  call store_error(errmsg)
743  call this%parser%StoreErrorUnit(terminate=.true.)
744  end if
745  this%rlstimelist = .true.
746  found = .true.
747  case ('RELEASE_TIMESFILE')
748  call this%parser%GetString(fname)
749  call openfile(this%irlstls, this%iout, fname, 'TLS')
750  nlines = 0
751  rtfloop: do
752  read (this%irlstls, '(A)', iostat=ios) line
753  if (ios /= 0) exit rtfloop
754  nlines = nlines + 1
755  end do rtfloop
756  call this%releasetimes%expand(nlines)
757  rewind(this%irlstls)
758  allocate (character(len=LINELENGTH) :: line)
759  do i = 1, nlines
760  read (this%irlstls, '(A)') line
761  read (line, '(f30.0)') dval
762  this%releasetimes%times(i) = dval
763  end do
764  if (.not. this%releasetimes%increasing()) then
765  errmsg = "RELEASE TIMES MUST STRICTLY INCREASE"
766  call store_error(errmsg)
767  call this%parser%StoreErrorUnit(terminate=.true.)
768  end if
769  this%rlstimelist = .true.
770  found = .true.
771  case ('TRACK')
772  call this%parser%GetStringCaps(keyword)
773  if (keyword == 'FILEOUT') then
774  ! parse filename
775  call this%parser%GetString(fname)
776  ! open binary output file
777  this%itrkout = getunit()
778  call openfile(this%itrkout, this%iout, fname, 'DATA(BINARY)', &
779  form, access, filstat_opt='REPLACE', &
780  mode_opt=mnormal)
781  write (this%iout, fmttrkbin) trim(adjustl(fname)), this%itrkout
782  ! open and write ascii header spec file
783  this%itrkhdr = getunit()
784  fname = trim(fname)//'.hdr'
785  call openfile(this%itrkhdr, this%iout, fname, 'CSV', &
786  filstat_opt='REPLACE', mode_opt=mnormal)
787  write (this%itrkhdr, '(a,/,a)') trackheader, trackdtypes
788  else
789  call store_error('OPTIONAL TRACK KEYWORD MUST BE '// &
790  'FOLLOWED BY FILEOUT')
791  end if
792  found = .true.
793  case ('TRACKCSV')
794  call this%parser%GetStringCaps(keyword)
795  if (keyword == 'FILEOUT') then
796  ! parse filename
797  call this%parser%GetString(fname)
798  ! open CSV output file and write headers
799  this%itrkcsv = getunit()
800  call openfile(this%itrkcsv, this%iout, fname, 'CSV', &
801  filstat_opt='REPLACE')
802  write (this%iout, fmttrkcsv) trim(adjustl(fname)), this%itrkcsv
803  write (this%itrkcsv, '(a)') trackheader
804  else
805  call store_error('OPTIONAL TRACKCSV KEYWORD MUST BE &
806  &FOLLOWED BY FILEOUT')
807  end if
808  found = .true.
809  case ('LOCAL_Z')
810  this%localz = .true.
811  found = .true.
812  case default
813  found = .false.
814  end select
815  end subroutine prp_options
816 
817  !> @brief Read the packagedata for this package
818  subroutine prp_read_packagedata(this)
819  ! -- dummy
820  class(prtprptype), intent(inout) :: this
821  ! -- local
822  character(len=LINELENGTH) :: cellid
823  character(len=LENBOUNDNAME) :: bndName, bndNameTemp
824  character(len=9) :: cno
825  logical :: isfound
826  logical :: endOfBlock
827  integer(I4B) :: ival
828  integer(I4B) :: n
829  integer(I4B) :: ierr
830  character(len=LENBOUNDNAME), dimension(:), allocatable :: nametxt
831  integer(I4B), dimension(:), allocatable :: nboundchk
832  integer(I4B), dimension(:), allocatable :: noder
833  real(DP), dimension(:), allocatable :: x
834  real(DP), dimension(:), allocatable :: y
835  real(DP), dimension(:), allocatable :: z
836  real(DP), dimension(:), allocatable :: tstop
837  ! -- format
838  character(len=*), parameter :: fmttend = &
839  "('end time (', G0, ') must be greater than or equal to the &
840  &begin time (', G0, ').')"
841 
842  ! -- allocate and initialize temporary variables
843  allocate (noder(this%nreleasepts))
844  allocate (x(this%nreleasepts))
845  allocate (y(this%nreleasepts))
846  allocate (z(this%nreleasepts))
847  allocate (tstop(this%nreleasepts))
848  allocate (nametxt(this%nreleasepts))
849  allocate (nboundchk(this%nreleasepts))
850 
851  ! -- initialize temporary variables
852  do n = 1, this%nreleasepts
853  nboundchk(n) = 0
854  end do
855 
856  ! -- read particle release point data
857  ! -- get particle release points block
858  call this%parser%GetBlock('PACKAGEDATA', isfound, ierr, &
859  supportopenclose=.true.)
860 
861  ! -- parse block if detected
862  if (isfound) then
863  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%packName)) &
864  //' PACKAGEDATA'
865  do
866  call this%parser%GetNextLine(endofblock)
867  if (endofblock) exit
868  ival = this%parser%GetInteger()
869  n = ival
870 
871  if (n < 1 .or. n > this%nreleasepts) then
872  write (errmsg, '(a,1x,i0,a)') &
873  'Release point number must be greater than 0 and less than ', &
874  'or equal to', this%nreleasepts, '.'
875  call store_error(errmsg)
876  cycle
877  end if
878 
879  ! -- increment nboundchk
880  nboundchk(n) = nboundchk(n) + 1
881 
882  ! -- node number
883  call this%parser%GetCellid(this%dis%ndim, cellid)
884  noder(n) = this%dis%noder_from_cellid(cellid, this%inunit, this%iout)
885 
886  ! -- x, y, z coordinates
887  x(n) = this%parser%GetDouble()
888  y(n) = this%parser%GetDouble()
889  z(n) = this%parser%GetDouble()
890 
891  if (this%localz .and. (z(n) < 0 .or. z(n) > 1)) then
892  call store_error('Local z coordinate must fall in the interval [0, 1]')
893  cycle
894  end if
895 
896  ! -- set default boundname
897  write (cno, '(i9.9)') n
898  bndname = 'PRP'//cno
899 
900  ! -- read boundnames from file, if provided
901  if (this%inamedbound /= 0) then
902  call this%parser%GetStringCaps(bndnametemp)
903  if (bndnametemp /= '') &
904  bndname = bndnametemp
905  else
906  bndname = ''
907  end if
908 
909  ! -- store temp boundnames
910  nametxt(n) = bndname
911  end do
912 
913  write (this%iout, '(1x,a)') &
914  'END OF '//trim(adjustl(this%packName))//' PACKAGEDATA'
915 
916  ! -- check for duplicate or missing particle release points
917  do n = 1, this%nreleasepts
918  if (nboundchk(n) == 0) then
919  write (errmsg, '(a,a,1x,i0,a)') 'No data specified for particle ', &
920  'release point', n, '.'
921  call store_error(errmsg)
922  else if (nboundchk(n) > 1) then
923  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a)') &
924  'Data for particle release point', n, 'specified', nboundchk(n), &
925  'times.'
926  call store_error(errmsg)
927  end if
928  end do
929  else
930  call store_error('Required packagedata block not found.')
931  end if
932 
933  ! -- terminate if any errors were detected
934  if (count_errors() > 0) then
935  call this%parser%StoreErrorUnit()
936  end if
937 
938  ! -- fill particle release point data with data stored in temporary local arrays
939  do n = 1, this%nreleasepts
940  this%rptnode(n) = noder(n)
941  this%rptx(n) = x(n)
942  this%rpty(n) = y(n)
943  this%rptz(n) = z(n)
944  this%rptname(n) = nametxt(n)
945  end do
946 
947  ! -- deallocate local storage
948  deallocate (noder)
949  deallocate (x)
950  deallocate (y)
951  deallocate (z)
952  deallocate (tstop)
953  deallocate (nametxt)
954  deallocate (nboundchk)
955  end subroutine prp_read_packagedata
956 
957  !> @brief Read package dimensions
958  subroutine prp_read_dimensions(this)
959  ! -- dummy
960  class(prtprptype), intent(inout) :: this
961  ! -- local
962  character(len=LINELENGTH) :: errmsg, keyword
963  integer(I4B) :: ierr
964  logical :: isfound, endOfBlock
965 
966  ! -- get dimension block
967  call this%parser%GetBlock('DIMENSIONS', isfound, ierr, &
968  supportopenclose=.true.)
969 
970  ! -- parse dimension block if detected
971  if (isfound) then
972  write (this%iout, '(1x,a)') 'PROCESSING PARTICLE INPUT DIMENSIONS'
973  do
974  call this%parser%GetNextLine(endofblock)
975  if (endofblock) exit
976  call this%parser%GetStringCaps(keyword)
977  select case (keyword)
978  case ('NRELEASEPTS')
979  this%nreleasepts = this%parser%GetInteger()
980  case default
981  write (errmsg, &
982  '(4x,a,a)') '****ERROR. UNKNOWN PARTICLE INPUT DIMENSION: ', &
983  trim(keyword)
984  call store_error(errmsg)
985  call this%parser%StoreErrorUnit()
986  end select
987  end do
988  write (this%iout, '(1x,a)') 'END OF PARTICLE INPUT DIMENSIONS'
989  else
990  call store_error('ERROR. REQUIRED DIMENSIONS BLOCK NOT FOUND.')
991  end if
992 
993  ! -- set maxbound and nbound to nreleasepts
994  this%maxbound = this%nreleasepts
995  this%nbound = this%nreleasepts
996 
997  ! -- allocate arrays for prp package
998  call this%prp_allocate_arrays()
999 
1000  ! -- read packagedata
1001  call this%prp_read_packagedata()
1002  end subroutine prp_read_dimensions
1003 
1004 end module prtprpmodule
This module contains block parser methods.
Definition: BlockParser.f90:7
This module contains the base boundary package.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:44
@ tabcenter
centered table column
Definition: Constants.f90:171
@ tableft
left justified table column
Definition: Constants.f90:170
@ mnormal
normal output mode
Definition: Constants.f90:205
integer(i4b), parameter lenpakloc
maximum length of a package location
Definition: Constants.f90:49
real(dp), parameter dem1
real constant 1e-1
Definition: Constants.f90:102
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:38
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:35
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:64
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:46
real(dp), parameter done
real constant 1
Definition: Constants.f90:75
Definition: Dis.f90:1
logical function, public point_in_polygon(x, y, poly)
Check if a point is within a polygon.
Definition: GeomUtil.f90:25
subroutine, public get_ijk(nodenumber, nrow, ncol, nlay, irow, icol, ilay)
Get row, column and layer indices from node number and grid dimensions. If nodenumber is invalid,...
Definition: GeomUtil.f90:98
subroutine, public get_jk(nodenumber, ncpl, nlay, icpl, ilay)
Get layer index and within-layer node index from node number and grid dimensions. If nodenumber is in...
Definition: GeomUtil.f90:126
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
This module contains the derived type ObsType.
Definition: Obs.f90:127
subroutine, public defaultobsidprocessor(obsrv, dis, inunitobs, iout)
@ brief Process IDstring provided for each observation
Definition: Obs.f90:249
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
subroutine, public create_particle_store(this, np, mempath)
Create a new particle store.
Definition: Particle.f90:109
subroutine, public create_particle(particle)
Create a new particle.
Definition: Particle.f90:101
subroutine prp_allocate_arrays(this, nodelist, auxvar)
Allocate arrays.
Definition: prt-prp.f90:193
subroutine prp_rp(this)
@ brief Read and prepare period data for particle input
Definition: prt-prp.f90:461
subroutine prp_cq_simrate(this, hnew, flowja, imover)
@ brief Calculate flow between package and model.
Definition: prt-prp.f90:613
subroutine prp_read_dimensions(this)
Read package dimensions.
Definition: prt-prp.f90:959
character(len=lenftype) ftype
Definition: prt-prp.f90:32
subroutine prp_df_obs(this)
Store supported observations.
Definition: prt-prp.f90:678
subroutine define_listlabel(this)
@ brief Define list heading written with PRINT_INPUT option
Definition: prt-prp.f90:650
subroutine prp_ad(this)
Advance a time step and release particles if appropriate.
Definition: prt-prp.f90:303
subroutine prp_set_pointers(this, ibound, izone, trackfilectl)
@ brief Set pointers to model variables
Definition: prt-prp.f90:180
subroutine prp_allocate_scalars(this)
Allocate scalars.
Definition: prt-prp.f90:225
subroutine prp_da(this)
Deallocate memory.
Definition: prt-prp.f90:136
character(len=16) text
Definition: prt-prp.f90:33
logical function prp_obs_supported(this)
Indicates whether observations are supported.
Definition: prt-prp.f90:672
subroutine, public prp_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath, fmi)
Create a new particle release point package.
Definition: prt-prp.f90:89
subroutine prp_ar(this)
@ brief Allocate and read period data
Definition: prt-prp.f90:273
subroutine prp_read_packagedata(this)
Read the packagedata for this package.
Definition: prt-prp.f90:819
subroutine prp_options(this, option, found)
Set options specific to PrtPrpType.
Definition: prt-prp.f90:693
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_warning(msg, substring)
Store warning message.
Definition: Sim.f90:236
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
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
character(len=maxcharlen) warnmsg
warning message string
subroutine, public table_cr(this, name, title)
Definition: Table.f90:85
integer(i4b), dimension(:), pointer, public, contiguous nstp
number of time steps in each stress period
Definition: tdis.f90:39
real(dp), pointer, public totimc
simulation time at start of time step
Definition: tdis.f90:33
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
Specify times for some event(s) to occur.
Definition: TimeSelect.f90:2
type(timeserieslinktype) function, pointer, public gettimeserieslinkfromlist(list, indx)
Get time series link from a list.
character(len= *), parameter, public trackheader
Definition: TrackData.f90:56
character(len= *), parameter, public trackdtypes
Definition: TrackData.f90:61
@ brief BndType
Structured grid discretization.
Definition: Dis.f90:23
Vertex grid discretization.
Definition: Disv.f90:24
Structure of arrays to store particles.
Definition: Particle.f90:69
A particle tracked by the PRT model.
Definition: Particle.f90:31
Particle release point (PRP) package.
Definition: prt-prp.f90:36
Represents a series of instants at which some event should occur.
Definition: TimeSelect.f90:18
Manages particle track (i.e. pathline) files.
Definition: TrackData.f90:38