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)
313 integer(I4B) :: ip, it
326 do ip = 1, this%nreleasepoints
327 this%rptm(ip) =
dzero
332 call this%schedule%advance()
333 if (.not. this%schedule%any())
return
336 call this%log_release()
340 call this%particles%resize( &
341 this%particles%num_stored() + &
342 (this%nreleasepoints * this%schedule%count()), &
347 do ip = 1, this%nreleasepoints
348 do it = 1, this%schedule%count()
349 t = this%schedule%times(it)
354 'Skipping negative release time (t=', t,
').'
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.'
365 call this%release(ip, t)
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)
388 integer(I4B),
intent(in) :: ic
389 real(DP),
intent(in) :: x, y, z
391 real(DP),
allocatable :: polyverts(:, :)
393 call this%fmi%dis%get_polyverts(ic, polyverts)
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)
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 ', &
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 ', &
414 deallocate (polyverts)
432 integer(I4B),
intent(in) :: ip
433 real(DP),
intent(in) :: trelease
438 call this%initialize_particle(particle, ip, trelease)
441 np = this%nparticles + 1
445 call this%particles%save_particle(particle, np)
446 deallocate (particle)
449 this%rptm(ip) = this%rptm(ip) +
done
456 integer(I4B),
intent(in) :: ip
457 real(DP),
intent(in) :: trelease
459 integer(I4B) :: irow, icol, ilay, icpl
460 integer(I4B) :: ic, icu, ic_old
462 real(DP) :: top, bot, hds
464 ic = this%rptnode(ip)
465 icu = this%dis%get_nodeuser(ic)
469 if (
size(this%boundname) /= 0)
then
470 particle%name = this%boundname(ip)
476 particle%istopweaksink = this%istopweaksink
477 particle%istopzone = this%istopzone
478 particle%idrymeth = this%idrymeth
481 select type (dis => this%dis)
483 call get_ijk(icu, dis%nrow, dis%ncol, dis%nlay, irow, icol, ilay)
485 call get_jk(icu, dis%ncpl, dis%nlay, icpl, ilay)
488 particle%izone = this%rptzone(ic)
494 if (this%ibound(ic) == 0)
then
496 if (this%idrape > 0)
then
497 call this%dis%highest_active(ic, this%ibound)
498 if (ic == ic_old .or. this%ibound(ic) == 0) &
508 if (this%ilocalz > 0)
then
509 top = this%fmi%dis%top(ic)
510 bot = this%fmi%dis%bot(ic)
511 hds = this%fmi%gwfhead(ic)
512 z = bot + this%rptz(ip) * (hds - bot)
517 call this%validate_release_point(ic, x, y, z)
522 particle%trelease = trelease
525 if (this%stoptraveltime == huge(1d0))
then
526 particle%tstop = this%stoptime
528 particle%tstop = particle%trelease + this%stoptraveltime
529 if (this%stoptime < particle%tstop) particle%tstop = this%stoptime
532 particle%ttrack = particle%trelease
533 particle%idomain(1) = 0
534 particle%iboundary(1) = 0
535 particle%idomain(2) = ic
536 particle%iboundary(2) = 0
537 particle%idomain(3) = 0
538 particle%iboundary(3) = 0
539 particle%ifrctrn = this%ifrctrn
540 particle%iexmeth = this%iexmeth
541 particle%iextend = this%iextend
542 particle%extol = this%extol
554 logical(LGP) :: is_found
555 logical(LGP) :: end_of_block
556 logical(LGP) :: no_blocks
557 character(len=LINELENGTH) :: line
558 character(len=LINELENGTH),
allocatable :: lines(:)
560 character(len=*),
parameter :: fmtblkerr = &
561 "('Looking for BEGIN PERIOD iper. &
562 &Found ', a, ' instead.')"
563 character(len=*),
parameter :: fmt_steps = &
564 "(6x,'TIME STEP(S) ',50(I0,' '))"
565 character(len=*),
parameter :: fmt_freq = &
566 "(6x,'EVERY ',I0,' TIME STEP(S)')"
567 character(len=*),
parameter :: fmt_fracs = &
572 if (this%inunit == 0)
return
576 if (this%ionper <
kper)
then
578 call this%parser%GetBlock(
'PERIOD', is_found, ierr, &
579 supportopenclose=.true., &
580 blockrequired=.false.)
583 call this%read_check_ionper()
592 this%ionper =
nper + 1
596 call this%parser%GetCurrentLine(line)
597 write (
errmsg, fmtblkerr) adjustl(trim(line))
607 if (no_blocks .and. &
609 size(this%schedule%time_select%times) == 0)
then
613 call this%schedule%advance(lines=lines)
614 else if (this%ionper ==
kper)
then
620 call this%parser%GetNextLine(end_of_block)
621 if (end_of_block)
exit recordloop
622 call this%parser%GetCurrentLine(line)
624 lines(
size(lines)) = line
626 if (
size(lines) > 0) &
627 call this%schedule%advance(lines=lines)
639 real(DP),
dimension(:),
intent(in) :: hnew
640 real(DP),
dimension(:),
intent(inout) :: flowja
641 integer(I4B),
intent(in) :: imover
645 integer(I4B) :: idiag
649 if (this%nbound <= 0)
return
652 do i = 1, this%nbound
653 node = this%nodelist(i)
658 idiag = this%dis%con%ia(node)
659 rrate = this%rptm(i) * (
done /
delt)
660 flowja(idiag) = flowja(idiag) + rrate
664 this%simvals(i) = rrate
685 call this%obs%StoreObsType(
'prp', .true., indx)
690 call this%obs%StoreObsType(
'to-mvr', .true., indx)
702 character(len=*),
intent(inout) :: option
703 logical(LGP),
intent(inout) :: found
705 character(len=MAXCHARLEN) :: fname
706 character(len=MAXCHARLEN) :: keyword
708 character(len=*),
parameter :: fmttrkbin = &
709 "(4x, 'PARTICLE TRACKS WILL BE SAVED TO BINARY FILE: ', a, /4x, &
710 &'OPENED ON UNIT: ', I0)"
711 character(len=*),
parameter :: fmttrkcsv = &
712 "(4x, 'PARTICLE TRACKS WILL BE SAVED TO CSV FILE: ', a, /4x, &
713 &'OPENED ON UNIT: ', I0)"
717 this%stoptime = this%parser%GetDouble()
719 case (
'STOPTRAVELTIME')
720 this%stoptraveltime = this%parser%GetDouble()
722 case (
'STOP_AT_WEAK_SINK')
723 this%istopweaksink = 1
726 this%istopzone = this%parser%GetInteger()
731 case (
'DRY_TRACKING_METHOD')
732 call this%parser%GetStringCaps(keyword)
733 select case (keyword)
741 write (
errmsg,
'(a, a)') &
742 'Unknown dry tracking method: ', trim(keyword)
744 write (
errmsg,
'(a, a)') &
745 'DRY must be "DROP", "STOP" or "STAY"'
747 call this%parser%StoreErrorUnit()
751 call this%parser%GetStringCaps(keyword)
752 if (keyword ==
'FILEOUT')
then
754 call this%parser%GetString(fname)
757 call openfile(this%itrkout, this%iout, fname,
'DATA(BINARY)', &
760 write (this%iout, fmttrkbin) trim(adjustl(fname)), this%itrkout
763 fname = trim(fname)//
'.hdr'
764 call openfile(this%itrkhdr, this%iout, fname,
'CSV', &
765 filstat_opt=
'REPLACE', mode_opt=mnormal)
768 call store_error(
'OPTIONAL TRACK KEYWORD MUST BE '// &
769 'FOLLOWED BY FILEOUT')
773 call this%parser%GetStringCaps(keyword)
774 if (keyword ==
'FILEOUT')
then
776 call this%parser%GetString(fname)
779 call openfile(this%itrkcsv, this%iout, fname,
'CSV', &
780 filstat_opt=
'REPLACE')
781 write (this%iout, fmttrkcsv) trim(adjustl(fname)), this%itrkcsv
784 call store_error(
'OPTIONAL TRACKCSV KEYWORD MUST BE &
785 &FOLLOWED BY FILEOUT')
791 case (
'EXTEND_TRACKING')
794 case (
'EXIT_SOLVE_TOLERANCE')
795 this%extol = this%parser%GetDouble()
796 if (this%extol <=
dzero) &
797 call store_error(
'EXIT_SOLVE_TOLERANCE MUST BE POSITIVE')
799 case (
'RELEASE_TIME_TOLERANCE')
800 this%rttol = this%parser%GetDouble()
801 if (this%rttol <=
dzero) &
802 call store_error(
'RELEASE_TIME_TOLERANCE MUST BE POSITIVE')
804 case (
'RELEASE_TIME_FREQUENCY')
805 this%rtfreq = this%parser%GetDouble()
806 if (this%rtfreq <=
dzero) &
807 call store_error(
'RELEASE_TIME_FREQUENCY MUST BE POSITIVE')
809 case (
'DEV_FORCETERNARY')
810 call this%parser%DevOpt()
812 write (this%iout,
'(4x,a)') &
813 'TRACKING WILL BE DONE USING THE TERNARY METHOD REGARDLESS OF CELL TYPE'
815 case (
'DEV_EXIT_SOLVE_METHOD')
816 call this%parser%DevOpt()
817 this%iexmeth = this%parser%GetInteger()
818 if (.not. (this%iexmeth /= 1 .or. this%iexmeth /= 2)) &
820 &1 (BRENT) OR 2 (CHANDRUPATLA)')
827 if (.not. found)
then
828 errmsg =
"UNKNOWN PRP OPTION '"//trim(keyword)//
"'."
830 call this%parser%StoreErrorUnit()
844 character(len=LINELENGTH) :: errmsg, keyword
846 logical :: isfound, endOfBlock
849 call this%parser%GetBlock(
'DIMENSIONS', isfound, ierr, &
850 supportopenclose=.true.)
854 write (this%iout,
'(1x,a)')
'PROCESSING PARTICLE INPUT DIMENSIONS'
856 call this%parser%GetNextLine(endofblock)
858 call this%parser%GetStringCaps(keyword)
859 select case (keyword)
861 this%nreleasepoints = this%parser%GetInteger()
862 case (
'NRELEASETIMES')
863 this%nreleasetimes = this%parser%GetInteger()
866 '(4x,a,a)')
'****ERROR. UNKNOWN PARTICLE INPUT DIMENSION: ', &
869 call this%parser%StoreErrorUnit()
872 write (this%iout,
'(1x,a)')
'END OF PARTICLE INPUT DIMENSIONS'
874 call store_error(
'ERROR. REQUIRED DIMENSIONS BLOCK NOT FOUND.')
878 this%maxbound = this%nreleasepoints
879 this%nbound = this%nreleasepoints
882 call this%prp_allocate_arrays()
885 call this%prp_read_packagedata()
886 call this%prp_read_releasetimes()
887 call this%prp_load_releasetimefrequency()
895 character(len=LINELENGTH) :: cellid
896 character(len=LENBOUNDNAME) :: bndName, bndNameTemp
897 character(len=9) :: cno
899 logical :: endOfBlock
903 character(len=LENBOUNDNAME),
dimension(:),
allocatable :: nametxt
904 integer(I4B),
dimension(:),
allocatable :: nboundchk
905 integer(I4B),
dimension(:),
allocatable :: noder
906 real(DP),
dimension(:),
allocatable :: x
907 real(DP),
dimension(:),
allocatable :: y
908 real(DP),
dimension(:),
allocatable :: z
909 real(DP),
dimension(:),
allocatable :: tstop
911 character(len=*),
parameter :: fmttend = &
912 "('end time (', G0, ') must be greater than or equal to the &
913 &begin time (', G0, ').')"
916 allocate (noder(this%nreleasepoints))
917 allocate (x(this%nreleasepoints))
918 allocate (y(this%nreleasepoints))
919 allocate (z(this%nreleasepoints))
920 allocate (tstop(this%nreleasepoints))
921 allocate (nametxt(this%nreleasepoints))
922 allocate (nboundchk(this%nreleasepoints))
925 do n = 1, this%nreleasepoints
931 call this%parser%GetBlock(
'PACKAGEDATA', isfound, ierr, &
932 supportopenclose=.true.)
936 write (this%iout,
'(/1x,a)')
'PROCESSING '//trim(adjustl(this%packName)) &
939 call this%parser%GetNextLine(endofblock)
941 ival = this%parser%GetInteger()
944 if (n < 1 .or. n > this%nreleasepoints)
then
945 write (
errmsg,
'(a,i0,a,i0,a)') &
946 'Expected ', this%nreleasepoints,
' release points. &
947 &Points must be numbered from 1 to ', this%nreleasepoints,
'.'
953 nboundchk(n) = nboundchk(n) + 1
956 call this%parser%GetCellid(this%dis%ndim, cellid)
957 noder(n) = this%dis%noder_from_cellid(cellid, this%inunit, this%iout)
960 x(n) = this%parser%GetDouble()
961 y(n) = this%parser%GetDouble()
962 z(n) = this%parser%GetDouble()
964 if (this%ilocalz > 0 .and. (z(n) < 0 .or. z(n) > 1))
then
965 call store_error(
'Local z coordinate must fall in the interval [0, 1]')
970 write (cno,
'(i9.9)') n
974 if (this%inamedbound /= 0)
then
975 call this%parser%GetStringCaps(bndnametemp)
976 if (bndnametemp /=
'') &
977 bndname = bndnametemp
986 write (this%iout,
'(1x,a)') &
987 'END OF '//trim(adjustl(this%packName))//
' PACKAGEDATA'
990 do n = 1, this%nreleasepoints
991 if (nboundchk(n) == 0)
then
992 write (
errmsg,
'(a,a,1x,i0,a)')
'No data specified for particle ', &
993 'release point', n,
'.'
995 else if (nboundchk(n) > 1)
then
996 write (
errmsg,
'(a,1x,i0,1x,a,1x,i0,1x,a)') &
997 'Data for particle release point', n,
'specified', nboundchk(n), &
1003 call store_error(
'Required packagedata block not found.')
1008 call this%parser%StoreErrorUnit()
1012 do n = 1, this%nreleasepoints
1013 this%rptnode(n) = noder(n)
1017 this%rptname(n) = nametxt(n)
1026 deallocate (nametxt)
1027 deallocate (nboundchk)
1035 integer(I4B) :: i, ierr
1036 logical(LGP) :: eob, found, success
1038 real(DP),
allocatable :: times(:)
1041 call this%parser%GetBlock(
'RELEASETIMES', found, ierr, &
1042 supportopenclose=.true., &
1043 blockrequired=.false.)
1047 if (.not. found)
then
1048 if (this%nreleasetimes <= 0)
return
1049 write (
errmsg,
'(a, i0)') &
1050 "Expected RELEASETIMES with length ", this%nreleasetimes
1052 call this%parser%StoreErrorUnit(terminate=.true.)
1056 allocate (times(this%nreleasetimes))
1059 write (this%iout,
'(/1x,a)') &
1060 'PROCESSING '//trim(adjustl(this%text))//
' RELEASETIMES'
1061 do i = 1, this%nreleasetimes
1062 call this%parser%GetNextLine(eob)
1064 call this%parser%TryGetDouble(t, success)
1065 if (.not. success)
then
1066 errmsg =
"Failed to read double precision value"
1068 call this%parser%StoreErrorUnit(terminate=.true.)
1074 call this%schedule%time_select%extend(times)
1077 if (.not. this%schedule%time_select%increasing())
then
1078 errmsg =
"Release times must strictly increase"
1080 call this%parser%StoreErrorUnit(terminate=.true.)
1095 real(DP),
allocatable :: times(:)
1098 if (this%rtfreq <=
dzero)
return
1107 call this%schedule%time_select%extend(times)
1110 if (.not. this%schedule%time_select%increasing())
then
1111 errmsg =
"Release times must strictly increase"
1113 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.