MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
prtocmodule Module Reference

Data Types

type  prtoctype
 @ brief Output control for particle tracking models More...
 

Functions/Subroutines

subroutine, public oc_cr (ocobj, name_model, inunit, iout)
 @ brief Create an output control object More...
 
subroutine prt_oc_allocate_scalars (this, name_model)
 
subroutine oc_ar (this, dis, dnodata)
 @ brief Setup output control variables. More...
 
subroutine prt_oc_da (this)
 
subroutine prt_oc_read_options (this)
 
subroutine prt_oc_read_dimensions (this)
 Read the dimensions block. More...
 
subroutine prt_oc_read_tracktimes (this)
 Read the tracking times block. More...
 

Function/Subroutine Documentation

◆ oc_ar()

subroutine prtocmodule::oc_ar ( class(prtoctype this,
class(disbasetype), intent(in), pointer  dis,
real(dp), intent(in)  dnodata 
)
private
Parameters
thisPrtOcType object
[in]dismodel discretization package
[in]dnodatano data value

Definition at line 120 of file prt-oc.f90.

121  ! dummy
122  class(PrtOcType) :: this !< PrtOcType object
123  class(DisBaseType), pointer, intent(in) :: dis !< model discretization package
124  real(DP), intent(in) :: dnodata !< no data value
125  ! local
126  integer(I4B) :: i, nocdobj, inodata
127  type(OutputControlDataType), pointer :: ocdobjptr
128  real(DP), dimension(:), pointer, contiguous :: nullvec => null()
129 
130  ! Allocate and initialize variables
131  allocate (this%tracktimes)
132  call this%tracktimes%init()
133  inodata = 0
134  nocdobj = 1
135  allocate (this%ocds(nocdobj))
136  do i = 1, nocdobj
137  call ocd_cr(ocdobjptr)
138  select case (i)
139  case (1)
140  call ocdobjptr%init_dbl('BUDGET', nullvec, dis, 'PRINT LAST ', &
141  'COLUMNS 10 WIDTH 11 DIGITS 4 GENERAL ', &
142  this%iout, dnodata)
143  end select
144  this%ocds(i) = ocdobjptr
145  deallocate (ocdobjptr)
146  end do
147 
148  ! Read options, dimensions, and tracktimes
149  ! blocks if this package is enabled
150  if (this%inunit <= 0) return
151  call this%read_options()
152  call this%prt_oc_read_dimensions()
153  call this%prt_oc_read_tracktimes()
154 
Here is the call graph for this function:

◆ oc_cr()

subroutine, public prtocmodule::oc_cr ( type(prtoctype), pointer  ocobj,
character(len=*), intent(in)  name_model,
integer(i4b), intent(in)  inunit,
integer(i4b), intent(in)  iout 
)
Parameters
ocobjPrtOcType object
[in]name_modelname of the model
[in]inunitunit number for input
[in]ioutunit number for output

Definition at line 51 of file prt-oc.f90.

52  type(PrtOcType), pointer :: ocobj !< PrtOcType object
53  character(len=*), intent(in) :: name_model !< name of the model
54  integer(I4B), intent(in) :: inunit !< unit number for input
55  integer(I4B), intent(in) :: iout !< unit number for output
56 
57  ! Create the object
58  allocate (ocobj)
59 
60  ! Allocate scalars
61  call ocobj%allocate_scalars(name_model)
62 
63  ! Save unit numbers
64  ocobj%inunit = inunit
65  ocobj%iout = iout
66 
67  ! Initialize block parser
68  call ocobj%parser%Initialize(inunit, iout)
Here is the caller graph for this function:

◆ prt_oc_allocate_scalars()

subroutine prtocmodule::prt_oc_allocate_scalars ( class(prtoctype this,
character(len=*), intent(in)  name_model 
)
private
Parameters
[in]name_modelname of model

Definition at line 71 of file prt-oc.f90.

72  class(PrtOcType) :: this
73  character(len=*), intent(in) :: name_model !< name of model
74 
75  this%memoryPath = create_mem_path(name_model, 'OC')
76 
77  allocate (this%name_model)
78  call mem_allocate(this%dump_event_trace, 'DUMP_EVENT_TRACE', this%memoryPath)
79  call mem_allocate(this%inunit, 'INUNIT', this%memoryPath)
80  call mem_allocate(this%iout, 'IOUT', this%memoryPath)
81  call mem_allocate(this%ibudcsv, 'IBUDCSV', this%memoryPath)
82  call mem_allocate(this%iperoc, 'IPEROC', this%memoryPath)
83  call mem_allocate(this%iocrep, 'IOCREP', this%memoryPath)
84  call mem_allocate(this%itrkout, 'ITRKOUT', this%memoryPath)
85  call mem_allocate(this%itrkhdr, 'ITRKHDR', this%memoryPath)
86  call mem_allocate(this%itrkcsv, 'ITRKCSV', this%memoryPath)
87  call mem_allocate(this%itrktls, 'ITRKTLS', this%memoryPath)
88  call mem_allocate(this%trackrelease, 'ITRACKRELEASE', this%memoryPath)
89  call mem_allocate(this%trackfeatexit, 'ITRACKFEATEXIT', this%memoryPath)
90  call mem_allocate(this%tracktimestep, 'ITRACKTIMESTEP', this%memoryPath)
91  call mem_allocate(this%trackterminate, 'ITRACKTERMINATE', this%memoryPath)
92  call mem_allocate(this%trackweaksink, 'ITRACKWEAKSINK', this%memoryPath)
93  call mem_allocate(this%trackusertime, 'ITRACKUSERTIME', this%memoryPath)
94  call mem_allocate(this%tracksubfexit, 'ITRACKSUBFEXIT', this%memoryPath)
95  call mem_allocate(this%ntracktimes, 'NTRACKTIMES', this%memoryPath)
96 
97  this%name_model = name_model
98  this%dump_event_trace = .false.
99  this%inunit = 0
100  this%iout = 0
101  this%ibudcsv = 0
102  this%iperoc = 0
103  this%iocrep = 0
104  this%itrkout = 0
105  this%itrkhdr = 0
106  this%itrkcsv = 0
107  this%itrktls = 0
108  this%trackrelease = .false.
109  this%trackfeatexit = .false.
110  this%tracktimestep = .false.
111  this%trackterminate = .false.
112  this%trackweaksink = .false.
113  this%trackusertime = .false.
114  this%tracksubfexit = .false.
115  this%ntracktimes = 0
116 
Here is the call graph for this function:

◆ prt_oc_da()

subroutine prtocmodule::prt_oc_da ( class(prtoctype this)
private

Definition at line 157 of file prt-oc.f90.

158  ! dummy
159  class(PrtOcType) :: this
160  ! local
161  integer(I4B) :: i
162 
163  call this%tracktimes%deallocate()
164 
165  do i = 1, size(this%ocds)
166  call this%ocds(i)%ocd_da()
167  end do
168  deallocate (this%ocds)
169 
170  deallocate (this%name_model)
171  call mem_deallocate(this%dump_event_trace)
172  call mem_deallocate(this%inunit)
173  call mem_deallocate(this%iout)
174  call mem_deallocate(this%ibudcsv)
175  call mem_deallocate(this%iperoc)
176  call mem_deallocate(this%iocrep)
177  call mem_deallocate(this%itrkout)
178  call mem_deallocate(this%itrkhdr)
179  call mem_deallocate(this%itrkcsv)
180  call mem_deallocate(this%itrktls)
181  call mem_deallocate(this%trackrelease)
182  call mem_deallocate(this%trackfeatexit)
183  call mem_deallocate(this%tracktimestep)
184  call mem_deallocate(this%trackterminate)
185  call mem_deallocate(this%trackweaksink)
186  call mem_deallocate(this%trackusertime)
187  call mem_deallocate(this%tracksubfexit)
188  call mem_deallocate(this%ntracktimes)
189 

◆ prt_oc_read_dimensions()

subroutine prtocmodule::prt_oc_read_dimensions ( class(prtoctype), intent(inout)  this)

Definition at line 353 of file prt-oc.f90.

354  use constantsmodule, only: linelength
356  ! dummy
357  class(PrtOcType), intent(inout) :: this
358  ! local
359  character(len=LINELENGTH) :: keyword
360  integer(I4B) :: ierr
361  logical(LGP) :: isfound, endOfBlock
362 
363  ! initialize dimensions to -1
364  this%ntracktimes = -1
365 
366  ! get dimensions block
367  call this%parser%GetBlock('DIMENSIONS', isfound, ierr, &
368  supportopenclose=.true., &
369  blockrequired=.false.)
370 
371  ! parse dimensions block if detected
372  if (.not. isfound) return
373  write (this%iout, '(/1x,a)') &
374  'PROCESSING OUTPUT CONTROL DIMENSIONS'
375  do
376  call this%parser%GetNextLine(endofblock)
377  if (endofblock) exit
378  call this%parser%GetStringCaps(keyword)
379  select case (keyword)
380  case ('NTRACKTIMES')
381  this%ntracktimes = this%parser%GetInteger()
382  write (this%iout, '(4x,a,i7)') 'NTRACKTIMES = ', this%ntracktimes
383  case default
384  write (errmsg, '(a,a)') &
385  'UNKNOWN OUTPUT CONTROL DIMENSION: ', trim(keyword)
386  call store_error(errmsg)
387  end select
388  end do
389  write (this%iout, '(1x,a)') &
390  'END OF OUTPUT CONTROL DIMENSIONS'
391 
392  if (this%ntracktimes < 0) then
393  write (errmsg, '(a)') &
394  'NTRACKTIMES WAS NOT SPECIFIED OR WAS SPECIFIED INCORRECTLY.'
395  call store_error(errmsg)
396  end if
397 
398  ! stop if errors were encountered in the block
399  if (count_errors() > 0) &
400  call this%parser%StoreErrorUnit()
401 
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
Here is the call graph for this function:

◆ prt_oc_read_options()

subroutine prtocmodule::prt_oc_read_options ( class(prtoctype this)
private

Definition at line 192 of file prt-oc.f90.

193  ! modules
194  use openspecmodule, only: access, form
196  use constantsmodule, only: linelength
200  ! dummy
201  class(PrtOcType) :: this
202  ! local
203  character(len=LINELENGTH) :: keyword
204  character(len=LINELENGTH) :: keyword2
205  character(len=LINELENGTH) :: fname
206  character(len=:), allocatable :: line
207  integer(I4B) :: ierr, ipos
208  logical(LGP) :: block_found, param_found, event_found, eob
209  type(OutputControlDataType), pointer :: ocdobjptr
210  ! formats
211  character(len=*), parameter :: fmttrkbin = &
212  "(4x, 'PARTICLE TRACKS WILL BE SAVED TO BINARY FILE: ', a, /4x, &
213  &'OPENED ON UNIT: ', I0)"
214  character(len=*), parameter :: fmttrkcsv = &
215  "(4x, 'PARTICLE TRACKS WILL BE SAVED TO CSV FILE: ', a, /4x, &
216  &'OPENED ON UNIT: ', I0)"
217 
218  ! get options block
219  call this%parser%GetBlock('OPTIONS', block_found, ierr, &
220  supportopenclose=.true., blockrequired=.false.)
221 
222  ! parse options block if detected
223  if (block_found) then
224  write (this%iout, '(/,1x,a,/)') 'PROCESSING OC OPTIONS'
225  event_found = .false.
226  do
227  call this%parser%GetNextLine(eob)
228  if (eob) exit
229  call this%parser%GetStringCaps(keyword)
230  param_found = .false.
231  select case (keyword)
232  case ('BUDGETCSV')
233  call this%parser%GetStringCaps(keyword2)
234  if (keyword2 /= 'FILEOUT') then
235  errmsg = "BUDGETCSV must be followed by FILEOUT and then budget &
236  &csv file name. Found '"//trim(keyword2)//"'."
237  call store_error(errmsg)
238  call this%parser%StoreErrorUnit()
239  end if
240  call this%parser%GetString(fname)
241  this%ibudcsv = getunit()
242  call openfile(this%ibudcsv, this%iout, fname, 'CSV', &
243  filstat_opt='REPLACE')
244  param_found = .true.
245  case ('TRACK')
246  call this%parser%GetStringCaps(keyword)
247  if (keyword == 'FILEOUT') then
248  ! parse filename
249  call this%parser%GetString(fname)
250  ! open binary track output file
251  this%itrkout = getunit()
252  call openfile(this%itrkout, this%iout, fname, 'DATA(BINARY)', &
253  form, access, filstat_opt='REPLACE', &
254  mode_opt=mnormal)
255  write (this%iout, fmttrkbin) trim(adjustl(fname)), this%itrkout
256  ! open and write ascii track header file
257  this%itrkhdr = getunit()
258  fname = trim(fname)//'.hdr'
259  call openfile(this%itrkhdr, this%iout, fname, 'CSV', &
260  filstat_opt='REPLACE', mode_opt=mnormal)
261  write (this%itrkhdr, '(a,/,a)') trackheader, trackdtypes
262  else
263  call store_error('OPTIONAL TRACK KEYWORD MUST BE '// &
264  'FOLLOWED BY FILEOUT')
265  end if
266  param_found = .true.
267  case ('TRACKCSV')
268  call this%parser%GetStringCaps(keyword)
269  if (keyword == 'FILEOUT') then
270  ! parse filename
271  call this%parser%GetString(fname)
272  ! open CSV track output file and write headers
273  this%itrkcsv = getunit()
274  call openfile(this%itrkcsv, this%iout, fname, 'CSV', &
275  filstat_opt='REPLACE')
276  write (this%iout, fmttrkcsv) trim(adjustl(fname)), this%itrkcsv
277  write (this%itrkcsv, '(a)') trackheader
278  else
279  call store_error('OPTIONAL TRACKCSV KEYWORD MUST BE &
280  &FOLLOWED BY FILEOUT')
281  end if
282  param_found = .true.
283  case ('TRACK_RELEASE')
284  this%trackrelease = .true.
285  event_found = .true.
286  param_found = .true.
287  case ('TRACK_EXIT')
288  this%trackfeatexit = .true.
289  event_found = .true.
290  param_found = .true.
291  case ('TRACK_TIMESTEP')
292  this%tracktimestep = .true.
293  event_found = .true.
294  param_found = .true.
295  case ('TRACK_TERMINATE')
296  this%trackterminate = .true.
297  event_found = .true.
298  param_found = .true.
299  case ('TRACK_WEAKSINK')
300  this%trackweaksink = .true.
301  event_found = .true.
302  param_found = .true.
303  case ('TRACK_USERTIME')
304  this%trackusertime = .true.
305  event_found = .true.
306  param_found = .true.
307  case ('TRACK_SUBFEATURE_EXIT')
308  this%tracksubfexit = .true.
309  event_found = .true.
310  param_found = .true.
311  case ('DEV_DUMP_EVENT_TRACE')
312  this%dump_event_trace = .true.
313  param_found = .true.
314  case default
315  param_found = .false.
316  end select
317 
318  ! check if we're done
319  if (.not. param_found) then
320  do ipos = 1, size(this%ocds)
321  ocdobjptr => this%ocds(ipos)
322  if (keyword == trim(ocdobjptr%cname)) then
323  param_found = .true.
324  exit
325  end if
326  end do
327  if (.not. param_found) then
328  errmsg = "UNKNOWN OC OPTION '"//trim(keyword)//"'."
329  call store_error(errmsg)
330  call this%parser%StoreErrorUnit()
331  end if
332  call this%parser%GetRemainingLine(line)
333  call ocdobjptr%set_option(line, this%parser%iuactive, this%iout)
334  end if
335  end do
336 
337  ! default events
338  if (.not. event_found) then
339  this%trackrelease = .true.
340  this%trackfeatexit = .true.
341  this%tracktimestep = .true.
342  this%trackterminate = .true.
343  this%trackweaksink = .true.
344  this%trackusertime = .true.
345  end if
346 
347  ! logging
348  write (this%iout, '(1x,a)') 'END OF OC OPTIONS'
349  end if
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public lowcase(word)
Convert to lower case.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
Particle track output module.
character(len= *), parameter, public trackheader
character(len= *), parameter, public trackdtypes
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
Here is the call graph for this function:

◆ prt_oc_read_tracktimes()

subroutine prtocmodule::prt_oc_read_tracktimes ( class(prtoctype), intent(inout)  this)

Definition at line 405 of file prt-oc.f90.

406  ! dummy
407  class(PrtOcType), intent(inout) :: this
408  ! local
409  integer(I4B) :: i, ierr
410  logical(LGP) :: eob, found, success
411  real(DP) :: t
412 
413  ! get tracktimes block
414  call this%parser%GetBlock('TRACKTIMES', found, ierr, &
415  supportopenclose=.true., &
416  blockrequired=.false.)
417 
418  ! raise an error if tracktimes has a dimension
419  ! but no block was found, otherwise return early
420  if (.not. found) then
421  if (this%ntracktimes <= 0) return
422  write (errmsg, '(a, i0)') &
423  "Expected TRACKTIMES with length ", this%ntracktimes
424  call store_error(errmsg)
425  call this%parser%StoreErrorUnit(terminate=.true.)
426  end if
427 
428  ! allocate time selection
429  call this%tracktimes%expand(this%ntracktimes)
430 
431  ! read the block
432  write (this%iout, '(/1x,a)') &
433  'PROCESSING OUTPUT CONTROL TRACKTIMES'
434  do i = 1, this%ntracktimes
435  call this%parser%GetNextLine(eob)
436  if (eob) exit
437  call this%parser%TryGetDouble(t, success)
438  if (.not. success) then
439  errmsg = "Failed to read double precision value"
440  call store_error(errmsg)
441  call this%parser%StoreErrorUnit(terminate=.true.)
442  end if
443  this%tracktimes%times(i) = t
444  end do
445 
446  ! make sure times strictly increase
447  if (.not. this%tracktimes%increasing()) then
448  errmsg = "TRACKTIMES must strictly increase"
449  call store_error(errmsg)
450  call this%parser%StoreErrorUnit(terminate=.true.)
451  end if
452 
Here is the call graph for this function: