37 character(len=LENFTYPE) ::
ftype =
'PRP'
38 character(len=16) ::
text =
' PRP'
46 integer(I4B),
pointer :: nreleasepoints => null()
47 integer(I4B),
pointer :: nreleasetimes => null()
48 integer(I4B),
pointer :: nparticles => null()
49 integer(I4B),
pointer :: istopweaksink => null()
50 integer(I4B),
pointer :: istopzone => null()
51 integer(I4B),
pointer :: idrape => null()
52 integer(I4B),
pointer :: idrymeth => null()
53 integer(I4B),
pointer :: itrkout => null()
54 integer(I4B),
pointer :: itrkhdr => null()
55 integer(I4B),
pointer :: itrkcsv => null()
56 integer(I4B),
pointer :: irlstls => null()
57 integer(I4B),
pointer :: ilocalz => null()
58 integer(I4B),
pointer :: iextend => null()
59 integer(I4B),
pointer :: ifrctrn => null()
60 integer(I4B),
pointer :: iexmeth => null()
61 real(dp),
pointer :: extol => null()
62 real(dp),
pointer :: rttol => null()
63 real(dp),
pointer :: rtfreq => null()
64 real(dp),
pointer :: offset => null()
65 real(dp),
pointer :: stoptime => null()
66 real(dp),
pointer :: stoptraveltime => null()
67 integer(I4B),
pointer,
contiguous :: rptnode(:) => null()
68 integer(I4B),
pointer,
contiguous :: rptzone(:) => null()
69 real(dp),
pointer,
contiguous :: rptx(:) => null()
70 real(dp),
pointer,
contiguous :: rpty(:) => null()
71 real(dp),
pointer,
contiguous :: rptz(:) => null()
72 real(dp),
pointer,
contiguous :: rptm(:) => null()
73 character(len=LENBOUNDNAME),
pointer,
contiguous :: rptname(:) => null()
100 subroutine prp_create(packobj, id, ibcnum, inunit, iout, namemodel, &
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
114 character(len=*),
parameter :: fmtheader = &
115 "(1x, /1x, 'PRP PARTICLE RELEASE POINT PACKAGE', &
116 &' INPUT READ FROM UNIT ', i0, /)"
123 call packobj%set_names(ibcnum, namemodel, pakname,
ftype)
127 call prpobj%prp_allocate_scalars()
130 call packobj%pack_initialize()
132 packobj%inunit = inunit
135 packobj%ibcnum = ibcnum
143 if (inunit > 0)
write (iout, fmtheader) inunit
151 call this%BndType%bnd_da()
185 call this%particles%deallocate(this%memoryPath)
186 call this%schedule%deallocate()
187 deallocate (this%particles)
188 deallocate (this%schedule)
194 integer(I4B),
dimension(:),
pointer,
contiguous :: ibound
195 integer(I4B),
dimension(:),
pointer,
contiguous :: izone
198 this%ibound => ibound
199 this%rptzone => izone
200 this%trackctl => trackctl
207 integer(I4B),
dimension(:),
pointer,
contiguous,
optional :: nodelist
208 real(DP),
dimension(:, :),
pointer,
contiguous,
optional :: auxvar
216 this%nreleasepoints, &
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', &
227 'RPTNAME', this%memoryPath)
230 do nps = 1, this%nreleasepoints
231 this%rptm(nps) =
dzero
240 call this%BndType%allocate_scalars()
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)
263 call mem_allocate(this%rtfreq,
'RTFREQ', this%memoryPath)
269 this%stoptime = huge(1d0)
270 this%stoptraveltime = huge(1d0)
271 this%istopweaksink = 0
275 this%nreleasepoints = 0
276 this%nreleasetimes = 0
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)
304 do n = 1, this%nreleasepoints
305 this%nodelist(n) = this%rptnode(n)
312 integer(I4B) :: ip, it
324 do ip = 1, this%nreleasepoints
325 this%rptm(ip) =
dzero
330 call this%schedule%advance()
331 if (.not. this%schedule%any())
return
334 call this%log_release()
338 call this%particles%resize( &
339 this%particles%num_stored() + &
340 (this%nreleasepoints * this%schedule%count()), &
345 do ip = 1, this%nreleasepoints
346 do it = 1, this%schedule%count()
347 call this%release(ip, this%schedule%times(it))
355 if (this%iprpak > 0)
then
356 write (this%iout,
"(1x,/1x,a,1x,i0)") &
357 'PARTICLE RELEASE FOR PRP', this%ibcnum
358 call this%schedule%log(this%iout)
370 integer(I4B),
intent(in) :: ic
371 real(DP),
intent(in) :: x, y, z
373 real(DP),
allocatable :: polyverts(:, :)
375 call this%fmi%dis%get_polyverts(ic, polyverts)
377 write (
errmsg,
'(a,g0,a,g0,a,i0)') &
378 'Error: release point (x=', x,
', y=', y,
') is not in cell ', &
379 this%dis%get_nodeuser(ic)
383 if (z > maxval(this%dis%top))
then
384 write (
errmsg,
'(a,g0,a,g0,a,i0)') &
385 'Error: release point (z=', z,
') is above grid top ', &
389 else if (z < minval(this%dis%bot))
then
390 write (
errmsg,
'(a,g0,a,g0,a,i0)') &
391 'Error: release point (z=', z,
') is below grid bottom ', &
396 deallocate (polyverts)
414 integer(I4B),
intent(in) :: ip
415 real(DP),
intent(in) :: trelease
420 call this%initialize_particle(particle, ip, trelease)
423 np = this%nparticles + 1
427 call this%particles%save_particle(particle, np)
428 deallocate (particle)
431 this%rptm(ip) = this%rptm(ip) +
done
438 integer(I4B),
intent(in) :: ip
439 real(DP),
intent(in) :: trelease
441 integer(I4B) :: irow, icol, ilay, icpl
442 integer(I4B) :: ic, icu, ic_old
444 real(DP) :: top, bot, hds
446 ic = this%rptnode(ip)
447 icu = this%dis%get_nodeuser(ic)
451 if (
size(this%boundname) /= 0)
then
452 particle%name = this%boundname(ip)
458 particle%istopweaksink = this%istopweaksink
459 particle%istopzone = this%istopzone
460 particle%idrymeth = this%idrymeth
463 select type (dis => this%dis)
465 call get_ijk(icu, dis%nrow, dis%ncol, dis%nlay, irow, icol, ilay)
467 call get_jk(icu, dis%ncpl, dis%nlay, icpl, ilay)
470 particle%izone = this%rptzone(ic)
476 if (this%ibound(ic) == 0)
then
478 if (this%idrape > 0)
then
479 call this%dis%highest_active(ic, this%ibound)
480 if (ic == ic_old .or. this%ibound(ic) == 0) &
490 if (this%ilocalz > 0)
then
491 top = this%fmi%dis%top(ic)
492 bot = this%fmi%dis%bot(ic)
493 hds = this%fmi%gwfhead(ic)
494 z = bot + this%rptz(ip) * (hds - bot)
499 call this%validate_release_point(ic, x, y, z)
504 particle%trelease = trelease
507 if (this%stoptraveltime == huge(1d0))
then
508 particle%tstop = this%stoptime
510 particle%tstop = particle%trelease + this%stoptraveltime
511 if (this%stoptime < particle%tstop) particle%tstop = this%stoptime
514 particle%ttrack = particle%trelease
515 particle%idomain(1) = 0
516 particle%iboundary(1) = 0
517 particle%idomain(2) = ic
518 particle%iboundary(2) = 0
519 particle%idomain(3) = 0
520 particle%iboundary(3) = 0
521 particle%ifrctrn = this%ifrctrn
522 particle%iexmeth = this%iexmeth
523 particle%iextend = this%iextend
524 particle%extol = this%extol
536 logical(LGP) :: is_found
537 logical(LGP) :: end_of_block
538 logical(LGP) :: no_blocks
539 character(len=LINELENGTH) :: line
540 character(len=LINELENGTH),
allocatable :: lines(:)
542 character(len=*),
parameter :: fmtblkerr = &
543 "('Looking for BEGIN PERIOD iper. &
544 &Found ', a, ' instead.')"
545 character(len=*),
parameter :: fmt_steps = &
546 "(6x,'TIME STEP(S) ',50(I0,' '))"
547 character(len=*),
parameter :: fmt_freq = &
548 "(6x,'EVERY ',I0,' TIME STEP(S)')"
549 character(len=*),
parameter :: fmt_fracs = &
554 if (this%inunit == 0)
return
558 if (this%ionper <
kper)
then
560 call this%parser%GetBlock(
'PERIOD', is_found, ierr, &
561 supportopenclose=.true., &
562 blockrequired=.false.)
565 call this%read_check_ionper()
574 this%ionper =
nper + 1
578 call this%parser%GetCurrentLine(line)
579 write (
errmsg, fmtblkerr) adjustl(trim(line))
589 if (no_blocks .and. &
591 size(this%schedule%time_select%times) == 0)
then
595 call this%schedule%advance(lines=lines)
596 else if (this%ionper ==
kper)
then
602 call this%parser%GetNextLine(end_of_block)
603 if (end_of_block)
exit recordloop
604 call this%parser%GetCurrentLine(line)
606 lines(
size(lines)) = line
608 if (
size(lines) > 0) &
609 call this%schedule%advance(lines=lines)
621 real(DP),
dimension(:),
intent(in) :: hnew
622 real(DP),
dimension(:),
intent(inout) :: flowja
623 integer(I4B),
intent(in) :: imover
627 integer(I4B) :: idiag
631 if (this%nbound <= 0)
return
634 do i = 1, this%nbound
635 node = this%nodelist(i)
640 idiag = this%dis%con%ia(node)
641 rrate = this%rptm(i) * (
done /
delt)
642 flowja(idiag) = flowja(idiag) + rrate
646 this%simvals(i) = rrate
667 call this%obs%StoreObsType(
'prp', .true., indx)
672 call this%obs%StoreObsType(
'to-mvr', .true., indx)
684 character(len=*),
intent(inout) :: option
685 logical(LGP),
intent(inout) :: found
687 character(len=MAXCHARLEN) :: fname
688 character(len=MAXCHARLEN) :: keyword
690 character(len=*),
parameter :: fmttrkbin = &
691 "(4x, 'PARTICLE TRACKS WILL BE SAVED TO BINARY FILE: ', a, /4x, &
692 &'OPENED ON UNIT: ', I0)"
693 character(len=*),
parameter :: fmttrkcsv = &
694 "(4x, 'PARTICLE TRACKS WILL BE SAVED TO CSV FILE: ', a, /4x, &
695 &'OPENED ON UNIT: ', I0)"
699 this%stoptime = this%parser%GetDouble()
701 case (
'STOPTRAVELTIME')
702 this%stoptraveltime = this%parser%GetDouble()
704 case (
'STOP_AT_WEAK_SINK')
705 this%istopweaksink = 1
708 this%istopzone = this%parser%GetInteger()
713 case (
'DRY_TRACKING_METHOD')
714 call this%parser%GetStringCaps(keyword)
715 select case (keyword)
723 write (
errmsg,
'(a, a)') &
724 'Unknown dry tracking method: ', trim(keyword)
726 write (
errmsg,
'(a, a)') &
727 'DRY must be "DROP", "STOP" or "STAY"'
729 call this%parser%StoreErrorUnit()
733 call this%parser%GetStringCaps(keyword)
734 if (keyword ==
'FILEOUT')
then
736 call this%parser%GetString(fname)
739 call openfile(this%itrkout, this%iout, fname,
'DATA(BINARY)', &
742 write (this%iout, fmttrkbin) trim(adjustl(fname)), this%itrkout
745 fname = trim(fname)//
'.hdr'
746 call openfile(this%itrkhdr, this%iout, fname,
'CSV', &
747 filstat_opt=
'REPLACE', mode_opt=mnormal)
750 call store_error(
'OPTIONAL TRACK KEYWORD MUST BE '// &
751 'FOLLOWED BY FILEOUT')
755 call this%parser%GetStringCaps(keyword)
756 if (keyword ==
'FILEOUT')
then
758 call this%parser%GetString(fname)
761 call openfile(this%itrkcsv, this%iout, fname,
'CSV', &
762 filstat_opt=
'REPLACE')
763 write (this%iout, fmttrkcsv) trim(adjustl(fname)), this%itrkcsv
766 call store_error(
'OPTIONAL TRACKCSV KEYWORD MUST BE &
767 &FOLLOWED BY FILEOUT')
773 case (
'EXTEND_TRACKING')
776 case (
'EXIT_SOLVE_TOLERANCE')
777 this%extol = this%parser%GetDouble()
778 if (this%extol <=
dzero) &
779 call store_error(
'EXIT_SOLVE_TOLERANCE MUST BE POSITIVE')
781 case (
'RELEASE_TIME_TOLERANCE')
782 this%rttol = this%parser%GetDouble()
783 if (this%rttol <=
dzero) &
784 call store_error(
'RELEASE_TIME_TOLERANCE MUST BE POSITIVE')
786 case (
'RELEASE_TIME_FREQUENCY')
787 this%rtfreq = this%parser%GetDouble()
788 if (this%rtfreq <=
dzero) &
789 call store_error(
'RELEASE_TIME_FREQUENCY MUST BE POSITIVE')
791 case (
'DEV_FORCETERNARY')
792 call this%parser%DevOpt()
794 write (this%iout,
'(4x,a)') &
795 'TRACKING WILL BE DONE USING THE TERNARY METHOD REGARDLESS OF CELL TYPE'
797 case (
'DEV_EXIT_SOLVE_METHOD')
798 call this%parser%DevOpt()
799 this%iexmeth = this%parser%GetInteger()
800 if (.not. (this%iexmeth /= 1 .or. this%iexmeth /= 2)) &
802 &1 (BRENT) OR 2 (CHANDRUPATLA)')
809 if (.not. found)
then
810 errmsg =
"UNKNOWN PRP OPTION '"//trim(keyword)//
"'."
812 call this%parser%StoreErrorUnit()
826 character(len=LINELENGTH) :: errmsg, keyword
828 logical :: isfound, endOfBlock
831 call this%parser%GetBlock(
'DIMENSIONS', isfound, ierr, &
832 supportopenclose=.true.)
836 write (this%iout,
'(1x,a)')
'PROCESSING PARTICLE INPUT DIMENSIONS'
838 call this%parser%GetNextLine(endofblock)
840 call this%parser%GetStringCaps(keyword)
841 select case (keyword)
843 this%nreleasepoints = this%parser%GetInteger()
844 case (
'NRELEASETIMES')
845 this%nreleasetimes = this%parser%GetInteger()
848 '(4x,a,a)')
'****ERROR. UNKNOWN PARTICLE INPUT DIMENSION: ', &
851 call this%parser%StoreErrorUnit()
854 write (this%iout,
'(1x,a)')
'END OF PARTICLE INPUT DIMENSIONS'
856 call store_error(
'ERROR. REQUIRED DIMENSIONS BLOCK NOT FOUND.')
860 this%maxbound = this%nreleasepoints
861 this%nbound = this%nreleasepoints
864 call this%prp_allocate_arrays()
867 call this%prp_read_packagedata()
868 call this%prp_read_releasetimes()
869 call this%prp_load_releasetimefrequency()
877 character(len=LINELENGTH) :: cellid
878 character(len=LENBOUNDNAME) :: bndName, bndNameTemp
879 character(len=9) :: cno
881 logical :: endOfBlock
885 character(len=LENBOUNDNAME),
dimension(:),
allocatable :: nametxt
886 integer(I4B),
dimension(:),
allocatable :: nboundchk
887 integer(I4B),
dimension(:),
allocatable :: noder
888 real(DP),
dimension(:),
allocatable :: x
889 real(DP),
dimension(:),
allocatable :: y
890 real(DP),
dimension(:),
allocatable :: z
891 real(DP),
dimension(:),
allocatable :: tstop
893 character(len=*),
parameter :: fmttend = &
894 "('end time (', G0, ') must be greater than or equal to the &
895 &begin time (', G0, ').')"
898 allocate (noder(this%nreleasepoints))
899 allocate (x(this%nreleasepoints))
900 allocate (y(this%nreleasepoints))
901 allocate (z(this%nreleasepoints))
902 allocate (tstop(this%nreleasepoints))
903 allocate (nametxt(this%nreleasepoints))
904 allocate (nboundchk(this%nreleasepoints))
907 do n = 1, this%nreleasepoints
913 call this%parser%GetBlock(
'PACKAGEDATA', isfound, ierr, &
914 supportopenclose=.true.)
918 write (this%iout,
'(/1x,a)')
'PROCESSING '//trim(adjustl(this%packName)) &
921 call this%parser%GetNextLine(endofblock)
923 ival = this%parser%GetInteger()
926 if (n < 1 .or. n > this%nreleasepoints)
then
927 write (
errmsg,
'(a,1x,i0,a)') &
928 'Release point number must be greater than 0 and less than', &
929 'or equal to', this%nreleasepoints,
'.'
935 nboundchk(n) = nboundchk(n) + 1
938 call this%parser%GetCellid(this%dis%ndim, cellid)
939 noder(n) = this%dis%noder_from_cellid(cellid, this%inunit, this%iout)
942 x(n) = this%parser%GetDouble()
943 y(n) = this%parser%GetDouble()
944 z(n) = this%parser%GetDouble()
946 if (this%ilocalz > 0 .and. (z(n) < 0 .or. z(n) > 1))
then
947 call store_error(
'Local z coordinate must fall in the interval [0, 1]')
952 write (cno,
'(i9.9)') n
956 if (this%inamedbound /= 0)
then
957 call this%parser%GetStringCaps(bndnametemp)
958 if (bndnametemp /=
'') &
959 bndname = bndnametemp
968 write (this%iout,
'(1x,a)') &
969 'END OF '//trim(adjustl(this%packName))//
' PACKAGEDATA'
972 do n = 1, this%nreleasepoints
973 if (nboundchk(n) == 0)
then
974 write (
errmsg,
'(a,a,1x,i0,a)')
'No data specified for particle ', &
975 'release point', n,
'.'
977 else if (nboundchk(n) > 1)
then
978 write (
errmsg,
'(a,1x,i0,1x,a,1x,i0,1x,a)') &
979 'Data for particle release point', n,
'specified', nboundchk(n), &
985 call store_error(
'Required packagedata block not found.')
990 call this%parser%StoreErrorUnit()
994 do n = 1, this%nreleasepoints
995 this%rptnode(n) = noder(n)
999 this%rptname(n) = nametxt(n)
1008 deallocate (nametxt)
1009 deallocate (nboundchk)
1017 integer(I4B) :: i, ierr
1018 logical(LGP) :: eob, found, success
1020 real(DP),
allocatable :: times(:)
1023 call this%parser%GetBlock(
'RELEASETIMES', found, ierr, &
1024 supportopenclose=.true., &
1025 blockrequired=.false.)
1029 if (.not. found)
then
1030 if (this%nreleasetimes <= 0)
return
1031 write (
errmsg,
'(a, i0)') &
1032 "Expected RELEASETIMES with length ", this%nreleasetimes
1034 call this%parser%StoreErrorUnit(terminate=.true.)
1038 allocate (times(this%nreleasetimes))
1041 write (this%iout,
'(/1x,a)') &
1042 'PROCESSING '//trim(adjustl(this%text))//
' RELEASETIMES'
1043 do i = 1, this%nreleasetimes
1044 call this%parser%GetNextLine(eob)
1046 call this%parser%TryGetDouble(t, success)
1047 if (.not. success)
then
1048 errmsg =
"Failed to read double precision value"
1050 call this%parser%StoreErrorUnit(terminate=.true.)
1056 call this%schedule%time_select%extend(times)
1059 if (.not. this%schedule%time_select%increasing())
then
1060 errmsg =
"Release times must strictly increase"
1062 call this%parser%StoreErrorUnit(terminate=.true.)
1077 real(DP),
allocatable :: times(:)
1080 if (this%rtfreq <=
dzero)
return
1089 call this%schedule%time_select%extend(times)
1092 if (.not. this%schedule%time_select%increasing())
then
1093 errmsg =
"Release times must strictly increase"
1095 call this%parser%StoreErrorUnit(terminate=.true.)
This module contains block parser methods.
This module contains the base boundary package.
This module contains simulation constants.
real(dp), parameter dsame
real constant for values that are considered the same based on machine precision
integer(i4b), parameter linelength
maximum length of a standard line
@ tabcenter
centered table column
@ tableft
left justified table column
@ mnormal
normal output mode
real(dp), parameter dep3
real constant 1000
integer(i4b), parameter lenpakloc
maximum length of a package location
real(dp), parameter dem1
real constant 1e-1
real(dp), parameter dep9
real constant 1e9
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
integer(i4b), parameter lenboundname
maximum length of a bound name
real(dp), parameter dzero
real constant zero
real(dp), parameter dem5
real constant 1e-5
integer(i4b), parameter maxcharlen
maximum length of char string
real(dp), parameter done
real constant 1
subroutine pstop(status, message)
Stop the program, optionally specifying an error status code.
logical function, public point_in_polygon(x, y, poly)
Check if a point is within a polygon.
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,...
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...
This module defines variable data types.
pure real(dp) function, dimension(:), allocatable, public arange(start, stop, step)
Return reals separated by the given step over the given interval.
pure logical function, public is_close(a, b, rtol, atol, symmetric)
Check if a real value is approximately equal to another.
This module contains the derived type ObsType.
subroutine, public defaultobsidprocessor(obsrv, dis, inunitobs, iout)
@ brief Process IDstring provided for each observation
subroutine, public allocate_particle_store(this, np, mempath)
Create a new particle store.
subroutine, public create_particle(particle)
Create a new particle.
subroutine prp_set_pointers(this, ibound, izone, trackctl)
@ brief Set pointers to model variables
subroutine prp_allocate_arrays(this, nodelist, auxvar)
Allocate arrays.
subroutine prp_rp(this)
@ brief Read and prepare period data for particle input
subroutine prp_load_releasetimefrequency(this)
Load regularly spaced release times if configured.
subroutine prp_cq_simrate(this, hnew, flowja, imover)
@ brief Calculate flow between package and model.
subroutine prp_read_dimensions(this)
Read package dimensions.
character(len=lenftype) ftype
subroutine prp_read_releasetimes(this)
Load explicitly specified release times.
subroutine prp_df_obs(this)
Store supported observations.
subroutine, public prp_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, fmi)
Create a new particle release point package.
subroutine define_listlabel(this)
subroutine log_release(this)
Log the release scheduled for this time step.
subroutine prp_ad(this)
Advance a time step and release particles if scheduled.
subroutine prp_allocate_scalars(this)
Allocate scalars.
subroutine initialize_particle(this, particle, ip, trelease)
subroutine prp_da(this)
Deallocate memory.
logical function prp_obs_supported(this)
Indicates whether observations are supported.
subroutine prp_ar(this)
@ brief Allocate and read period data
subroutine release(this, ip, trelease)
Release a particle at the specified time.
subroutine prp_read_packagedata(this)
Load package data (release points).
subroutine validate_release_point(this, ic, x, y, z)
Verify that the release point is in the cell.
subroutine prp_options(this, option, found)
Set options specific to PrtPrpType.
Particle release scheduling.
type(releasescheduletype) function, pointer, public create_release_schedule(tol)
Create a new release schedule object.
This module contains simulation methods.
subroutine, public store_warning(msg, substring)
Store warning message.
subroutine, public store_error(msg, terminate)
Store an error message.
integer(i4b) function, public count_errors()
Return number of errors.
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
character(len=maxcharlen) warnmsg
warning message string
subroutine, public table_cr(this, name, title)
real(dp), pointer, public totalsimtime
time at end of simulation
integer(i4b), pointer, public kper
current stress period number
real(dp), pointer, public delt
length of the current time step
integer(i4b), pointer, public nper
number of stress period
type(timeserieslinktype) function, pointer, public gettimeserieslinkfromlist(list, indx)
Get time series link from a list.
character(len= *), parameter, public trackdtypes
character(len= *), parameter, public trackheader
Structured grid discretization.
Vertex grid discretization.
Structure of arrays to store particles.
Particle tracked by the PRT model.
Particle release point (PRP) package.
Particle release scheduling utility.
Manages particle track (i.e. pathline) files.