MODFLOW 6  version 6.7.0.dev1
USGS Modular Hydrologic Model
prt-prp.f90
Go to the documentation of this file.
2  use kindmodule, only: dp, i4b, lgp
6  use bndmodule, only: bndtype
8  use tablemodule, only: tabletype, table_cr
14  use prtfmimodule, only: prtfmitype
25  use dismodule, only: distype
26  use disvmodule, only: disvtype
27  use errorutilmodule, only: pstop
28  use mathutilmodule, only: arange, is_close
30 
31  implicit none
32 
33  private
34  public :: prtprptype
35  public :: prp_create
36 
37  character(len=LENFTYPE) :: ftype = 'PRP'
38  character(len=16) :: text = ' PRP'
39 
40  !> @brief Particle release point (PRP) package
41  type, extends(bndtype) :: prtprptype
42  type(prtfmitype), pointer :: fmi => null() !< flow model interface
43  type(particlestoretype), pointer :: particles => null() !< particle store
44  type(trackcontroltype), pointer :: trackctl => null() !< track control
45  type(releasescheduletype), pointer :: schedule !< particle release schedule
46  integer(I4B), pointer :: nreleasepoints => null() !< number of release points
47  integer(I4B), pointer :: nreleasetimes => null() !< number of user-specified particle release times
48  integer(I4B), pointer :: nparticles => null() !< number of particles released
49  integer(I4B), pointer :: istopweaksink => null() !< weak sink option: 0 = no stop, 1 = stop
50  integer(I4B), pointer :: istopzone => null() !< optional stop zone number: 0 = no stop zone
51  integer(I4B), pointer :: idrape => null() !< drape option: 0 = do not drape, 1 = drape to topmost active cell
52  integer(I4B), pointer :: idrymeth => null() !< dry tracking method: 0 = drop, 1 = stop, 2 = stay
53  integer(I4B), pointer :: itrkout => null() !< binary track file
54  integer(I4B), pointer :: itrkhdr => null() !< track header file
55  integer(I4B), pointer :: itrkcsv => null() !< CSV track file
56  integer(I4B), pointer :: irlstls => null() !< release time file
57  integer(I4B), pointer :: ilocalz => null() !< compute z coordinates local to the cell
58  integer(I4B), pointer :: iextend => null() !< extend tracking beyond simulation's end
59  integer(I4B), pointer :: ifrctrn => null() !< force ternary solution for quad grids
60  integer(I4B), pointer :: iexmeth => null() !< method for iterative solution of particle exit location and time in generalized Pollock's method
61  real(dp), pointer :: extol => null() !< tolerance for iterative solution of particle exit location and time in generalized Pollock's method
62  real(dp), pointer :: rttol => null() !< tolerance for coincident particle release times
63  real(dp), pointer :: rtfreq => null() !< frequency for regularly spaced release times
64  real(dp), pointer :: offset => null() !< release time offset
65  real(dp), pointer :: stoptime => null() !< stop time for all release points
66  real(dp), pointer :: stoptraveltime => null() !< stop travel time for all points
67  integer(I4B), pointer, contiguous :: rptnode(:) => null() !< release point reduced nns
68  integer(I4B), pointer, contiguous :: rptzone(:) => null() !< release point zone numbers
69  real(dp), pointer, contiguous :: rptx(:) => null() !< release point x coordinates
70  real(dp), pointer, contiguous :: rpty(:) => null() !< release point y coordinates
71  real(dp), pointer, contiguous :: rptz(:) => null() !< release point z coordinates
72  real(dp), pointer, contiguous :: rptm(:) => null() !< total mass released from point
73  character(len=LENBOUNDNAME), pointer, contiguous :: rptname(:) => null() !< release point names
74  contains
75  procedure :: prp_allocate_arrays
76  procedure :: prp_allocate_scalars
77  procedure :: bnd_ar => prp_ar
78  procedure :: bnd_ad => prp_ad
79  procedure :: bnd_rp => prp_rp
80  procedure :: bnd_cq_simrate => prp_cq_simrate
81  procedure :: bnd_da => prp_da
82  procedure :: define_listlabel
83  procedure :: prp_set_pointers
84  procedure :: bnd_options => prp_options
85  procedure :: read_dimensions => prp_read_dimensions
86  procedure :: prp_read_packagedata
87  procedure :: prp_read_releasetimes
89  procedure :: release
90  procedure :: log_release
92  procedure :: initialize_particle
93  procedure, public :: bnd_obs_supported => prp_obs_supported
94  procedure, public :: bnd_df_obs => prp_df_obs
95  end type prtprptype
96 
97 contains
98 
99  !> @brief Create a new particle release point package
100  subroutine prp_create(packobj, id, ibcnum, inunit, iout, namemodel, &
101  pakname, fmi)
102  ! dummy
103  class(bndtype), pointer :: packobj
104  integer(I4B), intent(in) :: id
105  integer(I4B), intent(in) :: ibcnum
106  integer(I4B), intent(in) :: inunit
107  integer(I4B), intent(in) :: iout
108  character(len=*), intent(in) :: namemodel
109  character(len=*), intent(in) :: pakname
110  type(prtfmitype), pointer :: fmi
111  ! local
112  type(prtprptype), pointer :: prpobj
113  ! formats
114  character(len=*), parameter :: fmtheader = &
115  "(1x, /1x, 'PRP PARTICLE RELEASE POINT PACKAGE', &
116  &' INPUT READ FROM UNIT ', i0, /)"
117 
118  ! allocate the object and assign values to object variables
119  allocate (prpobj)
120  packobj => prpobj
121 
122  ! create name and memory path
123  call packobj%set_names(ibcnum, namemodel, pakname, ftype)
124  prpobj%text = text
125 
126  ! allocate scalars
127  call prpobj%prp_allocate_scalars()
128 
129  ! initialize package
130  call packobj%pack_initialize()
131 
132  packobj%inunit = inunit
133  packobj%iout = iout
134  packobj%id = id
135  packobj%ibcnum = ibcnum
136  packobj%ncolbnd = 4
137  packobj%iscloc = 1
138 
139  ! store pointer to flow model interface
140  prpobj%fmi => fmi
141 
142  ! if prp is enabled, print a message identifying it
143  if (inunit > 0) write (iout, fmtheader) inunit
144  end subroutine prp_create
145 
146  !> @brief Deallocate memory
147  subroutine prp_da(this)
148  class(prtprptype) :: this
149 
150  ! Deallocate parent
151  call this%BndType%bnd_da()
152 
153  ! Deallocate scalars
154  call mem_deallocate(this%ilocalz)
155  call mem_deallocate(this%iextend)
156  call mem_deallocate(this%offset)
157  call mem_deallocate(this%stoptime)
158  call mem_deallocate(this%stoptraveltime)
159  call mem_deallocate(this%istopweaksink)
160  call mem_deallocate(this%istopzone)
161  call mem_deallocate(this%idrape)
162  call mem_deallocate(this%idrymeth)
163  call mem_deallocate(this%nreleasepoints)
164  call mem_deallocate(this%nreleasetimes)
165  call mem_deallocate(this%nparticles)
166  call mem_deallocate(this%itrkout)
167  call mem_deallocate(this%itrkhdr)
168  call mem_deallocate(this%itrkcsv)
169  call mem_deallocate(this%irlstls)
170  call mem_deallocate(this%ifrctrn)
171  call mem_deallocate(this%iexmeth)
172  call mem_deallocate(this%extol)
173  call mem_deallocate(this%rttol)
174  call mem_deallocate(this%rtfreq)
175 
176  ! Deallocate arrays
177  call mem_deallocate(this%rptx)
178  call mem_deallocate(this%rpty)
179  call mem_deallocate(this%rptz)
180  call mem_deallocate(this%rptnode)
181  call mem_deallocate(this%rptm)
182  call mem_deallocate(this%rptname, 'RPTNAME', this%memoryPath)
183 
184  ! Deallocate objects
185  call this%particles%destroy(this%memoryPath)
186  call this%schedule%deallocate()
187  deallocate (this%particles)
188  deallocate (this%schedule)
189  end subroutine prp_da
190 
191  !> @ brief Set pointers to model variables
192  subroutine prp_set_pointers(this, ibound, izone, trackctl)
193  class(prtprptype) :: this
194  integer(I4B), dimension(:), pointer, contiguous :: ibound
195  integer(I4B), dimension(:), pointer, contiguous :: izone
196  type(trackcontroltype), pointer :: trackctl
197 
198  this%ibound => ibound
199  this%rptzone => izone
200  this%trackctl => trackctl
201  end subroutine prp_set_pointers
202 
203  !> @brief Allocate arrays
204  subroutine prp_allocate_arrays(this, nodelist, auxvar)
205  ! dummy
206  class(prtprptype) :: this
207  integer(I4B), dimension(:), pointer, contiguous, optional :: nodelist
208  real(DP), dimension(:, :), pointer, contiguous, optional :: auxvar
209  ! local
210  integer(I4B) :: nps
211 
212  ! Allocate particle store, starting with the number
213  ! of release points (arrays resized if/when needed)
214  call create_particle_store( &
215  this%particles, &
216  this%nreleasepoints, &
217  this%memoryPath)
218 
219  ! Allocate arrays
220  call mem_allocate(this%rptx, this%nreleasepoints, 'RPTX', this%memoryPath)
221  call mem_allocate(this%rpty, this%nreleasepoints, 'RPTY', this%memoryPath)
222  call mem_allocate(this%rptz, this%nreleasepoints, 'RPTZ', this%memoryPath)
223  call mem_allocate(this%rptm, this%nreleasepoints, 'RPTMASS', this%memoryPath)
224  call mem_allocate(this%rptnode, this%nreleasepoints, 'RPTNODER', &
225  this%memoryPath)
226  call mem_allocate(this%rptname, lenboundname, this%nreleasepoints, &
227  'RPTNAME', this%memoryPath)
228 
229  ! Initialize arrays
230  do nps = 1, this%nreleasepoints
231  this%rptm(nps) = dzero
232  end do
233  end subroutine prp_allocate_arrays
234 
235  !> @brief Allocate scalars
236  subroutine prp_allocate_scalars(this)
237  class(prtprptype) :: this
238 
239  ! Allocate parent's scalars
240  call this%BndType%allocate_scalars()
241 
242  ! Allocate scalars for this type
243  call mem_allocate(this%ilocalz, 'ILOCALZ', this%memoryPath)
244  call mem_allocate(this%iextend, 'IEXTEND', this%memoryPath)
245  call mem_allocate(this%offset, 'OFFSET', this%memoryPath)
246  call mem_allocate(this%stoptime, 'STOPTIME', this%memoryPath)
247  call mem_allocate(this%stoptraveltime, 'STOPTRAVELTIME', this%memoryPath)
248  call mem_allocate(this%istopweaksink, 'ISTOPWEAKSINK', this%memoryPath)
249  call mem_allocate(this%istopzone, 'ISTOPZONE', this%memoryPath)
250  call mem_allocate(this%idrape, 'IDRAPE', this%memoryPath)
251  call mem_allocate(this%idrymeth, 'IDRYMETH', this%memoryPath)
252  call mem_allocate(this%nreleasepoints, 'NRELEASEPOINTS', this%memoryPath)
253  call mem_allocate(this%nreleasetimes, 'NRELEASETIMES', this%memoryPath)
254  call mem_allocate(this%nparticles, 'NPARTICLES', this%memoryPath)
255  call mem_allocate(this%itrkout, 'ITRKOUT', this%memoryPath)
256  call mem_allocate(this%itrkhdr, 'ITRKHDR', this%memoryPath)
257  call mem_allocate(this%itrkcsv, 'ITRKCSV', this%memoryPath)
258  call mem_allocate(this%irlstls, 'IRLSTLS', this%memoryPath)
259  call mem_allocate(this%ifrctrn, 'IFRCTRN', this%memoryPath)
260  call mem_allocate(this%iexmeth, 'IEXMETH', this%memoryPath)
261  call mem_allocate(this%extol, 'EXTOL', this%memoryPath)
262  call mem_allocate(this%rttol, 'RTTOL', this%memoryPath)
263  call mem_allocate(this%rtfreq, 'RTFREQ', this%memoryPath)
264 
265  ! Set values
266  this%ilocalz = 0
267  this%iextend = 0
268  this%offset = dzero
269  this%stoptime = huge(1d0)
270  this%stoptraveltime = huge(1d0)
271  this%istopweaksink = 0
272  this%istopzone = 0
273  this%idrape = 0
274  this%idrymeth = 0
275  this%nreleasepoints = 0
276  this%nreleasetimes = 0
277  this%nparticles = 0
278  this%itrkout = 0
279  this%itrkhdr = 0
280  this%itrkcsv = 0
281  this%irlstls = 0
282  this%ifrctrn = 0
283  this%iexmeth = 0
284  this%extol = dem5
285  this%rttol = dsame * dep9
286  this%rtfreq = dzero
287 
288  end subroutine prp_allocate_scalars
289 
290  !> @ brief Allocate and read period data
291  subroutine prp_ar(this)
292  ! dummy variables
293  class(prtprptype), intent(inout) :: this
294  ! local variables
295  integer(I4B) :: n
296 
297  call this%obs%obs_ar()
298  call this%BndType%allocate_arrays()
299  if (this%inamedbound /= 0) then
300  do n = 1, this%nreleasepoints
301  this%boundname(n) = this%rptname(n)
302  end do
303  end if
304  do n = 1, this%nreleasepoints
305  this%nodelist(n) = this%rptnode(n)
306  end do
307  end subroutine prp_ar
308 
309  !> @brief Advance a time step and release particles if scheduled.
310  subroutine prp_ad(this)
311  use tdismodule, only: totalsimtime
312  class(prtprptype) :: this
313  integer(I4B) :: ip, it
314  real(DP) :: t
315 
316  ! Notes
317  ! -----
318  ! Each release point can be thought of as
319  ! a gumball machine with infinite supply:
320  ! a point can release an arbitrary number
321  ! of particles, but only one at any time.
322  ! Coincident release times are merged to
323  ! a single time by the release scheduler.
324 
325  ! Reset mass accumulators for this time step.
326  do ip = 1, this%nreleasepoints
327  this%rptm(ip) = dzero
328  end do
329 
330  ! Advance the release schedule and check if
331  ! any releases will be made this time step.
332  call this%schedule%advance()
333  if (.not. this%schedule%any()) return
334 
335  ! Log the schedule to the list file.
336  call this%log_release()
337 
338  ! Expand the particle store. We know from the
339  ! schedule how many particles will be released.
340  call this%particles%resize( &
341  this%particles%num_stored() + &
342  (this%nreleasepoints * this%schedule%count()), &
343  this%memoryPath)
344 
345  ! Release a particle from each point for
346  ! each release time in the current step.
347  do ip = 1, this%nreleasepoints
348  do it = 1, this%schedule%count()
349  t = this%schedule%times(it)
350  ! Skip the release time if it's before the simulation
351  ! starts, or if no `extend_tracking`, after it ends.
352  if (t < dzero) then
353  write (warnmsg, '(a,g0,a)') &
354  'Skipping negative release time (t=', t, ').'
355  call store_warning(warnmsg)
356  cycle
357  else if (t > totalsimtime .and. this%iextend == 0) then
358  write (warnmsg, '(a,g0,a)') &
359  'Skipping release time falling after the end of the &
360  &simulation (t=', t, '). Enable EXTEND_TRACKING to &
361  &release particles after the simulation end time.'
362  call store_warning(warnmsg)
363  cycle
364  end if
365  call this%release(ip, t)
366  end do
367  end do
368  end subroutine prp_ad
369 
370  !> @brief Log the release scheduled for this time step.
371  subroutine log_release(this)
372  class(prtprptype), intent(inout) :: this !< prp
373  if (this%iprpak > 0) then
374  write (this%iout, "(1x,/1x,a,1x,i0)") &
375  'PARTICLE RELEASE FOR PRP', this%ibcnum
376  call this%schedule%log(this%iout)
377  end if
378  end subroutine log_release
379 
380  !> @brief Verify that the release point is in the cell.
381  !!
382  !! Terminate with an error if the release point lies outside the
383  !! given cell, or if the point is above or below the grid top or
384  !! bottom, respectively.
385  !<
386  subroutine validate_release_point(this, ic, x, y, z)
387  class(prtprptype), intent(inout) :: this !< this instance
388  integer(I4B), intent(in) :: ic !< cell index
389  real(DP), intent(in) :: x, y, z !< release point
390  ! local
391  real(DP), allocatable :: polyverts(:, :)
392 
393  call this%fmi%dis%get_polyverts(ic, polyverts)
394  if (.not. point_in_polygon(x, y, polyverts)) then
395  write (errmsg, '(a,g0,a,g0,a,i0)') &
396  'Error: release point (x=', x, ', y=', y, ') is not in cell ', &
397  this%dis%get_nodeuser(ic)
398  call store_error(errmsg, terminate=.false.)
399  call store_error_unit(this%inunit, terminate=.true.)
400  end if
401  if (z > maxval(this%dis%top)) then
402  write (errmsg, '(a,g0,a,g0,a,i0)') &
403  'Error: release point (z=', z, ') is above grid top ', &
404  maxval(this%dis%top)
405  call store_error(errmsg, terminate=.false.)
406  call store_error_unit(this%inunit, terminate=.true.)
407  else if (z < minval(this%dis%bot)) then
408  write (errmsg, '(a,g0,a,g0,a,i0)') &
409  'Error: release point (z=', z, ') is below grid bottom ', &
410  minval(this%dis%bot)
411  call store_error(errmsg, terminate=.false.)
412  call store_error_unit(this%inunit, terminate=.true.)
413  end if
414  deallocate (polyverts)
415  end subroutine validate_release_point
416 
417  !> Release a particle at the specified time.
418  !!
419  !! Releasing a particle entails validating the particle's
420  !! coordinates and settings, transforming its coordinates
421  !! if needed, initializing the particle's initial tracking
422  !! time to the given release time, storing the particle in
423  !! the particle store (from which the PRT model will later
424  !! retrieve it, apply the tracking method, and check it in
425  !! again), and accumulating the particle's mass (the total
426  !! mass released from each release point is calculated for
427  !! budget reporting).
428  !<
429  subroutine release(this, ip, trelease)
430  ! dummy
431  class(prtprptype), intent(inout) :: this !< this instance
432  integer(I4B), intent(in) :: ip !< particle index
433  real(DP), intent(in) :: trelease !< release time
434  ! local
435  integer(I4B) :: np
436  type(particletype), pointer :: particle
437 
438  call this%initialize_particle(particle, ip, trelease)
439  np = this%nparticles + 1
440  this%nparticles = np
441  call this%particles%put(particle, np)
442  deallocate (particle)
443  this%rptm(ip) = this%rptm(ip) + done ! TODO configurable mass
444 
445  end subroutine release
446 
447  subroutine initialize_particle(this, particle, ip, trelease)
449  class(prtprptype), intent(inout) :: this !< this instance
450  type(particletype), pointer, intent(inout) :: particle !< the particle
451  integer(I4B), intent(in) :: ip !< particle index
452  real(DP), intent(in) :: trelease !< release time
453  ! local
454  integer(I4B) :: irow, icol, ilay, icpl
455  integer(I4B) :: ic, icu, ic_old
456  real(DP) :: x, y, z
457  real(DP) :: top, bot, hds
458 
459  ic = this%rptnode(ip)
460  icu = this%dis%get_nodeuser(ic)
461 
462  call create_particle(particle)
463 
464  if (size(this%boundname) /= 0) then
465  particle%name = this%boundname(ip)
466  else
467  particle%name = ''
468  end if
469 
470  particle%irpt = ip
471  particle%istopweaksink = this%istopweaksink
472  particle%istopzone = this%istopzone
473  particle%idrymeth = this%idrymeth
474  particle%icu = icu
475 
476  select type (dis => this%dis)
477  type is (distype)
478  call get_ijk(icu, dis%nrow, dis%ncol, dis%nlay, irow, icol, ilay)
479  type is (disvtype)
480  call get_jk(icu, dis%ncpl, dis%nlay, icpl, ilay)
481  end select
482  particle%ilay = ilay
483  particle%izone = this%rptzone(ic)
484  particle%istatus = 0 ! status 0 until tracking starts
485  ! If the cell is inactive, either drape the particle
486  ! to the top-most active cell beneath it if drape is
487  ! enabled, or else terminate permanently unreleased.
488  if (this%ibound(ic) == 0) then
489  ic_old = ic
490  if (this%idrape > 0) then
491  call this%dis%highest_active(ic, this%ibound)
492  if (ic == ic_old .or. this%ibound(ic) == 0) then
493  ! negative unreleased status signals to the
494  ! tracking method that we haven't yet saved
495  ! a termination record, it needs to do so.
496  particle%istatus = -1 * term_unreleased
497  end if
498  else
499  particle%istatus = -1 * term_unreleased
500  end if
501  end if
502 
503  ! Load coordinates and transform if needed
504  x = this%rptx(ip)
505  y = this%rpty(ip)
506  if (this%ilocalz > 0) then
507  top = this%fmi%dis%top(ic)
508  bot = this%fmi%dis%bot(ic)
509  hds = this%fmi%gwfhead(ic)
510  z = bot + this%rptz(ip) * (hds - bot)
511  else
512  z = this%rptz(ip)
513  end if
514 
515  call this%validate_release_point(ic, x, y, z)
516 
517  particle%x = x
518  particle%y = y
519  particle%z = z
520  particle%trelease = trelease
521 
522  ! Set stop time to earlier of STOPTIME and STOPTRAVELTIME
523  if (this%stoptraveltime == huge(1d0)) then
524  particle%tstop = this%stoptime
525  else
526  particle%tstop = particle%trelease + this%stoptraveltime
527  if (this%stoptime < particle%tstop) particle%tstop = this%stoptime
528  end if
529 
530  particle%ttrack = particle%trelease
531  particle%idomain(1) = 0
532  particle%iboundary(1) = 0
533  particle%idomain(2) = ic
534  particle%iboundary(2) = 0
535  particle%idomain(3) = 0
536  particle%iboundary(3) = 0
537  particle%ifrctrn = this%ifrctrn
538  particle%iexmeth = this%iexmeth
539  particle%iextend = this%iextend
540  particle%extol = this%extol
541  end subroutine initialize_particle
542 
543  !> @ brief Read and prepare period data for particle input
544  subroutine prp_rp(this)
545  ! modules
546  use tdismodule, only: kper, nper
547  use inputoutputmodule, only: urword
548  ! dummy variables
549  class(prtprptype), intent(inout) :: this
550  ! local variables
551  integer(I4B) :: ierr
552  logical(LGP) :: is_found
553  logical(LGP) :: end_of_block
554  logical(LGP) :: no_blocks
555  character(len=LINELENGTH) :: line
556  character(len=LINELENGTH), allocatable :: lines(:)
557  ! formats
558  character(len=*), parameter :: fmtblkerr = &
559  "('Looking for BEGIN PERIOD iper. &
560  &Found ', a, ' instead.')"
561  character(len=*), parameter :: fmt_steps = &
562  "(6x,'TIME STEP(S) ',50(I0,' '))" ! 50 limit is similar to STEPS in OC
563  character(len=*), parameter :: fmt_freq = &
564  "(6x,'EVERY ',I0,' TIME STEP(S)')"
565  character(len=*), parameter :: fmt_fracs = &
566  "(6x,50(f10.3,' '))"
567 
568  ! Set ionper to the stress period number for which a new block of data
569  ! will be read.
570  if (this%inunit == 0) return
571 
572  ! get stress period data
573  no_blocks = .false.
574  if (this%ionper < kper) then
575  ! get period block
576  call this%parser%GetBlock('PERIOD', is_found, ierr, &
577  supportopenclose=.true., &
578  blockrequired=.false.)
579  if (is_found) then
580  ! read ionper and check for increasing period numbers
581  call this%read_check_ionper()
582  else
583  ! PERIOD block not found
584  if (ierr < 0) then
585  if (kper == 1) then
586  ! End of file found; no period data for the simulation.
587  no_blocks = .true.
588  else
589  ! End of file found; no more period data.
590  this%ionper = nper + 1
591  end if
592  else
593  ! Found invalid block
594  call this%parser%GetCurrentLine(line)
595  write (errmsg, fmtblkerr) adjustl(trim(line))
596  call store_error(errmsg, terminate=.true.)
597  end if
598  end if
599  end if
600 
601  ! If the user hasn't provided any release settings (neither
602  ! explicit release times, release time frequency, or period
603  ! block release settings), default to a single release at the
604  ! start of the first period's first time step.
605  if (no_blocks .and. &
606  kper == 1 .and. &
607  size(this%schedule%time_select%times) == 0) then
608  allocate (lines(1))
609  line = "FIRST"
610  lines(1) = line
611  call this%schedule%advance(lines=lines)
612  else if (this%ionper == kper) then
613  ! If the current stress period matches the
614  ! block we are reading, parse the setting
615  ! and register it with the schedule.
616  allocate (lines(0))
617  recordloop: do
618  call this%parser%GetNextLine(end_of_block)
619  if (end_of_block) exit recordloop
620  call this%parser%GetCurrentLine(line)
621  call expandarray(lines)
622  lines(size(lines)) = line
623  end do recordloop
624  if (size(lines) > 0) &
625  call this%schedule%advance(lines=lines)
626  deallocate (lines)
627  end if
628 
629  end subroutine prp_rp
630 
631  !> @ brief Calculate flow between package and model.
632  subroutine prp_cq_simrate(this, hnew, flowja, imover)
633  ! modules
634  use tdismodule, only: delt
635  ! dummy variables
636  class(prtprptype) :: this
637  real(DP), dimension(:), intent(in) :: hnew
638  real(DP), dimension(:), intent(inout) :: flowja !< flow between package and model
639  integer(I4B), intent(in) :: imover !< flag indicating if the mover package is active
640  ! local variables
641  integer(I4B) :: i
642  integer(I4B) :: node
643  integer(I4B) :: idiag
644  real(DP) :: rrate
645 
646  ! If no boundaries, skip flow calculations.
647  if (this%nbound <= 0) return
648 
649  ! Loop through each boundary calculating flow.
650  do i = 1, this%nbound
651  node = this%nodelist(i)
652  rrate = dzero
653  ! If cell is no-flow or constant-head, then ignore it.
654  if (node > 0) then
655  ! Calculate the flow rate into the cell.
656  idiag = this%dis%con%ia(node)
657  rrate = this%rptm(i) * (done / delt) ! reciprocal of tstp length
658  flowja(idiag) = flowja(idiag) + rrate
659  end if
660 
661  ! Save simulated value to simvals array.
662  this%simvals(i) = rrate
663  end do
664  end subroutine prp_cq_simrate
665 
666  subroutine define_listlabel(this)
667  class(prtprptype), intent(inout) :: this
668  ! not implemented, not used
669  end subroutine define_listlabel
670 
671  !> @brief Indicates whether observations are supported.
672  logical function prp_obs_supported(this)
673  class(prtprptype) :: this
674  prp_obs_supported = .true.
675  end function prp_obs_supported
676 
677  !> @brief Store supported observations
678  subroutine prp_df_obs(this)
679  ! dummy
680  class(prtprptype) :: this
681  ! local
682  integer(I4B) :: indx
683  call this%obs%StoreObsType('prp', .true., indx)
684  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
685 
686  ! Store obs type and assign procedure pointer
687  ! for to-mvr observation type.
688  call this%obs%StoreObsType('to-mvr', .true., indx)
689  this%obs%obsData(indx)%ProcessIdPtr => defaultobsidprocessor
690  end subroutine prp_df_obs
691 
692  !> @brief Set options specific to PrtPrpType
693  subroutine prp_options(this, option, found)
694  use openspecmodule, only: access, form
695  use constantsmodule, only: maxcharlen, dzero
698  ! dummy
699  class(prtprptype), intent(inout) :: this
700  character(len=*), intent(inout) :: option
701  logical(LGP), intent(inout) :: found
702  ! locals
703  character(len=MAXCHARLEN) :: fname
704  character(len=MAXCHARLEN) :: keyword
705  ! formats
706  character(len=*), parameter :: fmttrkbin = &
707  "(4x, 'PARTICLE TRACKS WILL BE SAVED TO BINARY FILE: ', a, /4x, &
708  &'OPENED ON UNIT: ', I0)"
709  character(len=*), parameter :: fmttrkcsv = &
710  "(4x, 'PARTICLE TRACKS WILL BE SAVED TO CSV FILE: ', a, /4x, &
711  &'OPENED ON UNIT: ', I0)"
712 
713  select case (option)
714  case ('STOPTIME')
715  this%stoptime = this%parser%GetDouble()
716  found = .true.
717  case ('STOPTRAVELTIME')
718  this%stoptraveltime = this%parser%GetDouble()
719  found = .true.
720  case ('STOP_AT_WEAK_SINK')
721  this%istopweaksink = 1
722  found = .true.
723  case ('ISTOPZONE')
724  this%istopzone = this%parser%GetInteger()
725  found = .true.
726  case ('DRAPE')
727  this%idrape = 1
728  found = .true.
729  case ('DRY_TRACKING_METHOD')
730  call this%parser%GetStringCaps(keyword)
731  select case (keyword)
732  case ('DROP')
733  this%idrymeth = 0
734  case ('STOP')
735  this%idrymeth = 1
736  case ('STAY')
737  this%idrymeth = 2
738  case default
739  write (errmsg, '(a, a)') &
740  'Unknown dry tracking method: ', trim(keyword)
741  call store_error(errmsg)
742  write (errmsg, '(a, a)') &
743  'DRY must be "DROP", "STOP" or "STAY"'
744  call store_error(errmsg)
745  call this%parser%StoreErrorUnit()
746  end select
747  found = .true.
748  case ('TRACK')
749  call this%parser%GetStringCaps(keyword)
750  if (keyword == 'FILEOUT') then
751  ! parse filename
752  call this%parser%GetString(fname)
753  ! open binary output file
754  this%itrkout = getunit()
755  call openfile(this%itrkout, this%iout, fname, 'DATA(BINARY)', &
756  form, access, filstat_opt='REPLACE', &
757  mode_opt=mnormal)
758  write (this%iout, fmttrkbin) trim(adjustl(fname)), this%itrkout
759  ! open and write ascii header spec file
760  this%itrkhdr = getunit()
761  fname = trim(fname)//'.hdr'
762  call openfile(this%itrkhdr, this%iout, fname, 'CSV', &
763  filstat_opt='REPLACE', mode_opt=mnormal)
764  write (this%itrkhdr, '(a,/,a)') trackheader, trackdtypes
765  else
766  call store_error('OPTIONAL TRACK KEYWORD MUST BE '// &
767  'FOLLOWED BY FILEOUT')
768  end if
769  found = .true.
770  case ('TRACKCSV')
771  call this%parser%GetStringCaps(keyword)
772  if (keyword == 'FILEOUT') then
773  ! parse filename
774  call this%parser%GetString(fname)
775  ! open CSV output file and write headers
776  this%itrkcsv = getunit()
777  call openfile(this%itrkcsv, this%iout, fname, 'CSV', &
778  filstat_opt='REPLACE')
779  write (this%iout, fmttrkcsv) trim(adjustl(fname)), this%itrkcsv
780  write (this%itrkcsv, '(a)') trackheader
781  else
782  call store_error('OPTIONAL TRACKCSV KEYWORD MUST BE &
783  &FOLLOWED BY FILEOUT')
784  end if
785  found = .true.
786  case ('LOCAL_Z')
787  this%ilocalz = 1
788  found = .true.
789  case ('EXTEND_TRACKING')
790  this%iextend = 1
791  found = .true.
792  case ('EXIT_SOLVE_TOLERANCE')
793  this%extol = this%parser%GetDouble()
794  if (this%extol <= dzero) &
795  call store_error('EXIT_SOLVE_TOLERANCE MUST BE POSITIVE')
796  found = .true.
797  case ('RELEASE_TIME_TOLERANCE')
798  this%rttol = this%parser%GetDouble()
799  if (this%rttol <= dzero) &
800  call store_error('RELEASE_TIME_TOLERANCE MUST BE POSITIVE')
801  found = .true.
802  case ('RELEASE_TIME_FREQUENCY')
803  this%rtfreq = this%parser%GetDouble()
804  if (this%rtfreq <= dzero) &
805  call store_error('RELEASE_TIME_FREQUENCY MUST BE POSITIVE')
806  found = .true.
807  case ('DEV_FORCETERNARY')
808  call this%parser%DevOpt()
809  this%ifrctrn = 1
810  write (this%iout, '(4x,a)') &
811  'TRACKING WILL BE DONE USING THE TERNARY METHOD REGARDLESS OF CELL TYPE'
812  found = .true.
813  case ('DEV_EXIT_SOLVE_METHOD')
814  call this%parser%DevOpt()
815  this%iexmeth = this%parser%GetInteger()
816  if (.not. (this%iexmeth /= 1 .or. this%iexmeth /= 2)) &
817  call store_error('DEV_EXIT_SOLVE_METHOD MUST BE &
818  &1 (BRENT) OR 2 (CHANDRUPATLA)')
819  found = .true.
820  case default
821  found = .false.
822  end select
823 
824  ! Catch unrecognized options
825  if (.not. found) then
826  errmsg = "UNKNOWN PRP OPTION '"//trim(keyword)//"'."
827  call store_error(errmsg)
828  call this%parser%StoreErrorUnit()
829  end if
830 
831  ! Create release schedule now that we know
832  ! the coincident release time tolerance
833  this%schedule => create_release_schedule(tol=this%rttol)
834 
835  end subroutine prp_options
836 
837  !> @brief Read package dimensions
838  subroutine prp_read_dimensions(this)
839  ! dummy
840  class(prtprptype), intent(inout) :: this
841  ! local
842  character(len=LINELENGTH) :: errmsg, keyword
843  integer(I4B) :: ierr
844  logical :: isfound, endOfBlock
845 
846  ! get dimension block
847  call this%parser%GetBlock('DIMENSIONS', isfound, ierr, &
848  supportopenclose=.true.)
849 
850  ! parse dimension block if detected
851  if (isfound) then
852  write (this%iout, '(1x,a)') 'PROCESSING PARTICLE INPUT DIMENSIONS'
853  do
854  call this%parser%GetNextLine(endofblock)
855  if (endofblock) exit
856  call this%parser%GetStringCaps(keyword)
857  select case (keyword)
858  case ('NRELEASEPTS')
859  this%nreleasepoints = this%parser%GetInteger()
860  case ('NRELEASETIMES')
861  this%nreleasetimes = this%parser%GetInteger()
862  case default
863  write (errmsg, &
864  '(4x,a,a)') '****ERROR. UNKNOWN PARTICLE INPUT DIMENSION: ', &
865  trim(keyword)
866  call store_error(errmsg)
867  call this%parser%StoreErrorUnit()
868  end select
869  end do
870  write (this%iout, '(1x,a)') 'END OF PARTICLE INPUT DIMENSIONS'
871  else
872  call store_error('ERROR. REQUIRED DIMENSIONS BLOCK NOT FOUND.')
873  end if
874 
875  ! set maxbound and nbound to nreleasepts
876  this%maxbound = this%nreleasepoints
877  this%nbound = this%nreleasepoints
878 
879  ! allocate arrays for prp package
880  call this%prp_allocate_arrays()
881 
882  ! read packagedata and releasetimes blocks
883  call this%prp_read_packagedata()
884  call this%prp_read_releasetimes()
885  call this%prp_load_releasetimefrequency()
886  end subroutine prp_read_dimensions
887 
888  !> @brief Load package data (release points).
889  subroutine prp_read_packagedata(this)
890  ! dummy
891  class(prtprptype), intent(inout) :: this
892  ! local
893  character(len=LINELENGTH) :: cellid
894  character(len=LENBOUNDNAME) :: bndName, bndNameTemp
895  character(len=9) :: cno
896  logical :: isfound
897  logical :: endOfBlock
898  integer(I4B) :: ival
899  integer(I4B) :: n
900  integer(I4B) :: ierr
901  character(len=LENBOUNDNAME), dimension(:), allocatable :: nametxt
902  integer(I4B), dimension(:), allocatable :: nboundchk
903  integer(I4B), dimension(:), allocatable :: noder
904  real(DP), dimension(:), allocatable :: x
905  real(DP), dimension(:), allocatable :: y
906  real(DP), dimension(:), allocatable :: z
907  real(DP), dimension(:), allocatable :: tstop
908  ! format
909  character(len=*), parameter :: fmttend = &
910  "('end time (', G0, ') must be greater than or equal to the &
911  &begin time (', G0, ').')"
912 
913  ! allocate temporary variables
914  allocate (noder(this%nreleasepoints))
915  allocate (x(this%nreleasepoints))
916  allocate (y(this%nreleasepoints))
917  allocate (z(this%nreleasepoints))
918  allocate (tstop(this%nreleasepoints))
919  allocate (nametxt(this%nreleasepoints))
920  allocate (nboundchk(this%nreleasepoints))
921 
922  ! initialize temporary variables
923  do n = 1, this%nreleasepoints
924  nboundchk(n) = 0
925  end do
926 
927  ! read particle release point data
928  ! get particle release points block
929  call this%parser%GetBlock('PACKAGEDATA', isfound, ierr, &
930  supportopenclose=.true.)
931 
932  ! parse block if detected
933  if (isfound) then
934  write (this%iout, '(/1x,a)') 'PROCESSING '//trim(adjustl(this%packName)) &
935  //' PACKAGEDATA'
936  do
937  call this%parser%GetNextLine(endofblock)
938  if (endofblock) exit
939  ival = this%parser%GetInteger()
940  n = ival
941 
942  if (n < 1 .or. n > this%nreleasepoints) then
943  write (errmsg, '(a,i0,a,i0,a)') &
944  'Expected ', this%nreleasepoints, ' release points. &
945  &Points must be numbered from 1 to ', this%nreleasepoints, '.'
946  call store_error(errmsg)
947  cycle
948  end if
949 
950  ! increment nboundchk
951  nboundchk(n) = nboundchk(n) + 1
952 
953  ! node number
954  call this%parser%GetCellid(this%dis%ndim, cellid)
955  noder(n) = this%dis%noder_from_cellid(cellid, this%inunit, this%iout)
956 
957  ! x, y, z coordinates
958  x(n) = this%parser%GetDouble()
959  y(n) = this%parser%GetDouble()
960  z(n) = this%parser%GetDouble()
961 
962  if (this%ilocalz > 0 .and. (z(n) < 0 .or. z(n) > 1)) then
963  call store_error('Local z coordinate must fall in the interval [0, 1]')
964  cycle
965  end if
966 
967  ! set default boundname
968  write (cno, '(i9.9)') n
969  bndname = 'PRP'//cno
970 
971  ! read boundnames from file, if provided
972  if (this%inamedbound /= 0) then
973  call this%parser%GetStringCaps(bndnametemp)
974  if (bndnametemp /= '') &
975  bndname = bndnametemp
976  else
977  bndname = ''
978  end if
979 
980  ! store temp boundnames
981  nametxt(n) = bndname
982  end do
983 
984  write (this%iout, '(1x,a)') &
985  'END OF '//trim(adjustl(this%packName))//' PACKAGEDATA'
986 
987  ! check for duplicate or missing particle release points
988  do n = 1, this%nreleasepoints
989  if (nboundchk(n) == 0) then
990  write (errmsg, '(a,a,1x,i0,a)') 'No data specified for particle ', &
991  'release point', n, '.'
992  call store_error(errmsg)
993  else if (nboundchk(n) > 1) then
994  write (errmsg, '(a,1x,i0,1x,a,1x,i0,1x,a)') &
995  'Data for particle release point', n, 'specified', nboundchk(n), &
996  'times.'
997  call store_error(errmsg)
998  end if
999  end do
1000  else
1001  call store_error('Required packagedata block not found.')
1002  end if
1003 
1004  ! terminate if any errors were detected
1005  if (count_errors() > 0) then
1006  call this%parser%StoreErrorUnit()
1007  end if
1008 
1009  ! fill particle release point data with data stored in temporary local arrays
1010  do n = 1, this%nreleasepoints
1011  this%rptnode(n) = noder(n)
1012  this%rptx(n) = x(n)
1013  this%rpty(n) = y(n)
1014  this%rptz(n) = z(n)
1015  this%rptname(n) = nametxt(n)
1016  end do
1017 
1018  ! deallocate local storage
1019  deallocate (noder)
1020  deallocate (x)
1021  deallocate (y)
1022  deallocate (z)
1023  deallocate (tstop)
1024  deallocate (nametxt)
1025  deallocate (nboundchk)
1026  end subroutine prp_read_packagedata
1027 
1028  !> @brief Load explicitly specified release times.
1029  subroutine prp_read_releasetimes(this)
1030  ! dummy
1031  class(prtprptype), intent(inout) :: this
1032  ! local
1033  integer(I4B) :: i, ierr
1034  logical(LGP) :: eob, found, success
1035  real(DP) :: t
1036  real(DP), allocatable :: times(:)
1037 
1038  ! get releasetimes block
1039  call this%parser%GetBlock('RELEASETIMES', found, ierr, &
1040  supportopenclose=.true., &
1041  blockrequired=.false.)
1042 
1043  ! raise an error if releasetimes has a dimension
1044  ! but no block was found, otherwise return early
1045  if (.not. found) then
1046  if (this%nreleasetimes <= 0) return
1047  write (errmsg, '(a, i0)') &
1048  "Expected RELEASETIMES with length ", this%nreleasetimes
1049  call store_error(errmsg)
1050  call this%parser%StoreErrorUnit(terminate=.true.)
1051  end if
1052 
1053  ! allocate times array
1054  allocate (times(this%nreleasetimes))
1055 
1056  ! read times from the block
1057  write (this%iout, '(/1x,a)') &
1058  'PROCESSING '//trim(adjustl(this%text))//' RELEASETIMES'
1059  do i = 1, this%nreleasetimes
1060  call this%parser%GetNextLine(eob)
1061  if (eob) exit
1062  call this%parser%TryGetDouble(t, success)
1063  if (.not. success) then
1064  errmsg = "Failed to read double precision value"
1065  call store_error(errmsg)
1066  call this%parser%StoreErrorUnit(terminate=.true.)
1067  end if
1068  times(i) = t
1069  end do
1070 
1071  ! register times with the release schedule
1072  call this%schedule%time_select%extend(times)
1073 
1074  ! make sure times strictly increase
1075  if (.not. this%schedule%time_select%increasing()) then
1076  errmsg = "Release times must strictly increase"
1077  call store_error(errmsg)
1078  call this%parser%StoreErrorUnit(terminate=.true.)
1079  end if
1080 
1081  ! deallocate
1082  deallocate (times)
1083 
1084  end subroutine prp_read_releasetimes
1085 
1086  !> @brief Load regularly spaced release times if configured.
1088  ! modules
1089  use tdismodule, only: totalsimtime
1090  ! dummy
1091  class(prtprptype), intent(inout) :: this
1092  ! local
1093  real(DP), allocatable :: times(:)
1094 
1095  ! check if a release time frequency is configured
1096  if (this%rtfreq <= dzero) return
1097 
1098  ! create array of regularly-spaced release times
1099  times = arange( &
1100  start=dzero, &
1101  stop=totalsimtime, &
1102  step=this%rtfreq)
1103 
1104  ! register times with release schedule
1105  call this%schedule%time_select%extend(times)
1106 
1107  ! make sure times strictly increase
1108  if (.not. this%schedule%time_select%increasing()) then
1109  errmsg = "Release times must strictly increase"
1110  call store_error(errmsg)
1111  call this%parser%StoreErrorUnit(terminate=.true.)
1112  end if
1113 
1114  ! deallocate
1115  deallocate (times)
1116 
1117  end subroutine prp_load_releasetimefrequency
1118 
1119 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
real(dp), parameter dsame
real constant for values that are considered the same based on machine precision
Definition: Constants.f90:122
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
@ tabcenter
centered table column
Definition: Constants.f90:172
@ tableft
left justified table column
Definition: Constants.f90:171
@ mnormal
normal output mode
Definition: Constants.f90:206
real(dp), parameter dep3
real constant 1000
Definition: Constants.f90:88
integer(i4b), parameter lenpakloc
maximum length of a package location
Definition: Constants.f90:50
real(dp), parameter dem1
real constant 1e-1
Definition: Constants.f90:103
real(dp), parameter dep9
real constant 1e9
Definition: Constants.f90:90
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
Definition: Constants.f90:39
integer(i4b), parameter lenboundname
maximum length of a bound name
Definition: Constants.f90:36
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter dem5
real constant 1e-5
Definition: Constants.f90:108
integer(i4b), parameter maxcharlen
maximum length of char string
Definition: Constants.f90:47
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
Definition: Dis.f90:1
subroutine pstop(status, message)
Stop the program, optionally specifying an error status code.
Definition: ErrorUtil.f90:24
logical function, public point_in_polygon(x, y, poly)
Check if a point is within a polygon.
Definition: GeomUtil.f90:27
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:100
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:128
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
pure real(dp) function, dimension(:), allocatable, public arange(start, stop, step)
Return reals separated by the given step over the given interval.
Definition: MathUtil.f90:384
pure logical function, public is_close(a, b, rtol, atol, symmetric)
Check if a real value is approximately equal to another.
Definition: MathUtil.f90:46
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:246
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
subroutine create_particle_store(store, np, mempath)
Allocate particle store.
Definition: Particle.f90:172
@ term_unreleased
terminated permanently unreleased
Definition: Particle.f90:38
subroutine create_particle(particle)
Create a new particle.
Definition: Particle.f90:164
subroutine prp_set_pointers(this, ibound, izone, trackctl)
@ brief Set pointers to model variables
Definition: prt-prp.f90:193
subroutine prp_allocate_arrays(this, nodelist, auxvar)
Allocate arrays.
Definition: prt-prp.f90:205
subroutine prp_rp(this)
@ brief Read and prepare period data for particle input
Definition: prt-prp.f90:545
subroutine prp_load_releasetimefrequency(this)
Load regularly spaced release times if configured.
Definition: prt-prp.f90:1088
subroutine prp_cq_simrate(this, hnew, flowja, imover)
@ brief Calculate flow between package and model.
Definition: prt-prp.f90:633
subroutine prp_read_dimensions(this)
Read package dimensions.
Definition: prt-prp.f90:839
character(len=lenftype) ftype
Definition: prt-prp.f90:37
subroutine prp_read_releasetimes(this)
Load explicitly specified release times.
Definition: prt-prp.f90:1030
subroutine prp_df_obs(this)
Store supported observations.
Definition: prt-prp.f90:679
subroutine, public prp_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi)
Create a new particle release point package.
Definition: prt-prp.f90:102
subroutine define_listlabel(this)
Definition: prt-prp.f90:667
subroutine log_release(this)
Log the release scheduled for this time step.
Definition: prt-prp.f90:372
subroutine prp_ad(this)
Advance a time step and release particles if scheduled.
Definition: prt-prp.f90:311
subroutine prp_allocate_scalars(this)
Allocate scalars.
Definition: prt-prp.f90:237
subroutine initialize_particle(this, particle, ip, trelease)
Definition: prt-prp.f90:448
subroutine prp_da(this)
Deallocate memory.
Definition: prt-prp.f90:148
character(len=16) text
Definition: prt-prp.f90:38
logical function prp_obs_supported(this)
Indicates whether observations are supported.
Definition: prt-prp.f90:673
subroutine prp_ar(this)
@ brief Allocate and read period data
Definition: prt-prp.f90:292
subroutine release(this, ip, trelease)
Release a particle at the specified time.
Definition: prt-prp.f90:430
subroutine prp_read_packagedata(this)
Load package data (release points).
Definition: prt-prp.f90:890
subroutine validate_release_point(this, ic, x, y, z)
Verify that the release point is in the cell.
Definition: prt-prp.f90:387
subroutine prp_options(this, option, found)
Set options specific to PrtPrpType.
Definition: prt-prp.f90:694
Particle release scheduling.
type(releasescheduletype) function, pointer, public create_release_schedule(tol)
Create a new release schedule object.
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:87
real(dp), pointer, public totalsimtime
time at end of simulation
Definition: tdis.f90:37
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
type(timeserieslinktype) function, pointer, public gettimeserieslinkfromlist(list, indx)
Get time series link from a list.
character(len= *), parameter, public trackdtypes
Definition: TrackFile.f90:39
character(len= *), parameter, public trackheader
Definition: TrackFile.f90:35
@ 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:123
Particle tracked by the PRT model.
Definition: Particle.f90:78
Particle release point (PRP) package.
Definition: prt-prp.f90:41
Particle release scheduling utility.
Manages particle track (i.e. pathline) files.