MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
MethodDisv.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b, lgp
4  use errorutilmodule, only: pstop
5  use constantsmodule, only: done, dzero
10  use cellpolymodule
11  use particlemodule
12  use prtfmimodule, only: prtfmitype
13  use disvmodule, only: disvtype
16  implicit none
17 
18  private
19  public :: methoddisvtype
20  public :: create_method_disv
21 
22  type, extends(methodmodeltype) :: methoddisvtype
23  private
24  type(celldefntype), pointer :: neighbor => null() !< ptr to a neighbor defn
25  contains
26  procedure, public :: apply => apply_disv !< apply the DISV tracking method
27  procedure, public :: deallocate !< deallocate arrays and scalars
28  procedure, public :: load => load_disv !< load the cell method
29  procedure, public :: load_cell_defn !< load cell definition from the grid
30  procedure, public :: pass => pass_disv !< pass the particle to the next cell
31  procedure :: map_neighbor !< map a location on the cell face to the shared face of a neighbor
32  procedure :: update_flowja !< update intercell mass flows
33  procedure :: load_particle !< load particle properties
34  procedure :: load_properties !< load cell properties
35  procedure :: load_polygon !< load cell polygon
36  procedure :: load_neighbors !< load cell face neighbors
37  procedure :: load_indicators !< load cell 180-degree vertex indicator
38  procedure :: load_flows !< load the cell's flows
39  procedure :: load_boundary_flows_to_defn_poly !< load boundary flows to a polygonal cell definition
40  procedure :: load_face_flows_to_defn_poly !< load face flows to a polygonal cell definition
41  end type methoddisvtype
42 
43 contains
44 
45  !> @brief Create a new vertex grid (DISV) tracking method
46  subroutine create_method_disv(method)
47  ! dummy
48  type(methoddisvtype), pointer :: method
49  ! local
50  type(cellpolytype), pointer :: cell
51 
52  allocate (method)
53  allocate (method%name)
54  call create_cell_poly(cell)
55  method%cell => cell
56  method%name = "disv"
57  method%delegates = .true.
58  call create_defn(method%neighbor)
59  end subroutine create_method_disv
60 
61  !> @brief Destroy the tracking method
62  subroutine deallocate (this)
63  class(methoddisvtype), intent(inout) :: this
64  deallocate (this%name)
65  end subroutine deallocate
66 
67  !> @brief Load the cell and the tracking method
68  subroutine load_disv(this, particle, next_level, submethod)
69  use cellmodule
70  use cellrectmodule
72  use cellutilmodule
73  ! dummy
74  class(methoddisvtype), intent(inout) :: this
75  type(particletype), pointer, intent(inout) :: particle
76  integer(I4B), intent(in) :: next_level
77  class(methodtype), pointer, intent(inout) :: submethod
78  ! local
79  integer(I4B) :: ic
80  class(celltype), pointer :: base
81  type(cellrecttype), pointer :: rect
82  type(cellrectquadtype), pointer :: quad
83 
84  select type (cell => this%cell)
85  type is (cellpolytype)
86  ic = particle%itrdomain(next_level)
87  call this%load_cell_defn(ic, cell%defn)
88  if (this%fmi%ibdgwfsat0(ic) == 0) then
89  ! Cell is active but dry, so select and initialize pass-to-bottom
90  ! cell method and set cell method pointer
91  call method_cell_ptb%init( &
92  fmi=this%fmi, &
93  cell=this%cell, &
94  events=this%events, &
95  tracktimes=this%tracktimes)
96  submethod => method_cell_ptb
97  else if (particle%ifrctrn > 0) then
98  ! Force the ternary method
99  call method_cell_tern%init( &
100  fmi=this%fmi, &
101  cell=this%cell, &
102  events=this%events, &
103  tracktimes=this%tracktimes)
104  submethod => method_cell_tern
105  else if (cell%defn%can_be_rect) then
106  ! Cell is a rectangle, convert it to a rectangular cell type and
107  ! initialize Pollock's method
108  call cell_poly_to_rect(cell, rect)
109  base => rect
110  call method_cell_plck%init( &
111  fmi=this%fmi, &
112  cell=base, &
113  events=this%events, &
114  tracktimes=this%tracktimes)
115  submethod => method_cell_plck
116  else if (cell%defn%can_be_quad) then
117  ! Cell is quad-refined, convert to a quad rect cell type and
118  ! initialize the corresponding method
119  call cell_poly_to_quad(cell, quad)
120  base => quad
121  call method_cell_quad%init( &
122  fmi=this%fmi, &
123  cell=base, &
124  events=this%events, &
125  tracktimes=this%tracktimes)
126  submethod => method_cell_quad
127  else
128  ! Default to the ternary method
129  call method_cell_tern%init( &
130  fmi=this%fmi, &
131  cell=this%cell, &
132  events=this%events, &
133  tracktimes=this%tracktimes)
134  submethod => method_cell_tern
135  end if
136  end select
137  end subroutine load_disv
138 
139  subroutine load_particle(this, cell, particle)
140  ! modules
141  use disvmodule, only: disvtype
142  use particlemodule, only: term_boundary
143  use particleeventmodule, only: terminate
144  ! dummy
145  class(methoddisvtype), intent(inout) :: this
146  type(cellpolytype), pointer, intent(inout) :: cell
147  type(particletype), pointer, intent(inout) :: particle
148  ! local
149  integer(I4B) :: inface
150  integer(I4B) :: ipos
151  integer(I4B) :: ic
152  integer(I4B) :: icu
153  integer(I4B) :: inbr
154  integer(I4B) :: idiag
155  integer(I4B) :: icpl
156  integer(I4B) :: ilay
157  real(DP) :: z
158 
159  select type (dis => this%fmi%dis)
160  type is (disvtype)
161  inface = particle%iboundary(level_feature)
162  idiag = dis%con%ia(cell%defn%icell)
163  inbr = cell%defn%facenbr(inface)
164  ipos = idiag + inbr
165  ic = dis%con%ja(ipos)
166  icu = dis%get_nodeuser(ic)
167  call get_jk(icu, dis%ncpl, dis%nlay, icpl, ilay)
168 
169  ! if returning to a cell through the bottom
170  ! face after previously leaving it through
171  ! that same face, we've entered a cycle
172  ! as can occur e.g. in wells. terminate
173  ! in the previous cell.
174  if (ic == particle%icp .and. inface == 7 .and. ilay < particle%ilay) then
175  particle%itrdomain(level_feature) = particle%icp
176  particle%izone = particle%izp
177  call this%terminate(particle, &
178  status=term_boundary)
179  return
180  else
181  particle%icp = particle%itrdomain(level_feature)
182  particle%izp = particle%izone
183  end if
184 
185  particle%itrdomain(level_feature) = ic
186  particle%icu = icu
187  particle%ilay = ilay
188 
189  z = particle%z
190  call this%map_neighbor(cell%defn, inface, z)
191 
192  particle%iboundary(level_feature) = inface
193  particle%itrdomain(level_subfeature:) = 0
194  particle%iboundary(level_subfeature:) = 0
195  particle%z = z
196  end select
197 
198  end subroutine
199 
200  subroutine update_flowja(this, cell, particle)
201  ! dummy
202  class(methoddisvtype), intent(inout) :: this
203  type(cellpolytype), pointer, intent(inout) :: cell
204  type(particletype), pointer, intent(inout) :: particle
205  ! local
206  integer(I4B) :: inbr
207  integer(I4B) :: idiag
208  integer(I4B) :: ipos
209 
210  idiag = this%fmi%dis%con%ia(cell%defn%icell)
211  inbr = cell%defn%facenbr(particle%iboundary(level_feature))
212  ipos = idiag + inbr
213 
214  ! leaving old cell
215  this%flowja(ipos) = this%flowja(ipos) - done
216 
217  ! entering new cell
218  this%flowja(this%fmi%dis%con%isym(ipos)) &
219  = this%flowja(this%fmi%dis%con%isym(ipos)) + done
220 
221  end subroutine update_flowja
222 
223  !> @brief Pass a particle to the next cell, if there is one
224  subroutine pass_disv(this, particle)
225  use particlemodule, only: term_boundary
226  use particleeventmodule, only: terminate
227  ! dummy
228  class(methoddisvtype), intent(inout) :: this
229  type(particletype), pointer, intent(inout) :: particle
230  ! local
231  type(cellpolytype), pointer :: cell
232 
233  select type (c => this%cell)
234  type is (cellpolytype)
235  cell => c
236  ! If the entry face has no neighbors it's a
237  ! boundary face, so terminate the particle.
238  ! todo AMP: reconsider when multiple models supported
239  if (cell%defn%facenbr(particle%iboundary(level_feature)) .eq. 0) then
240  call this%terminate(particle, &
241  status=term_boundary)
242  else
243  ! Otherwise, load cell properties into the
244  ! particle. It may be marked to terminate.
245  call this%load_particle(cell, particle)
246  if (.not. particle%advancing) return
247 
248  ! Update intercell mass flows
249  call this%update_flowja(cell, particle)
250  end if
251  end select
252  end subroutine pass_disv
253 
254  !> @brief Map location on cell face to shared cell face of neighbor
255  subroutine map_neighbor(this, defn, inface, z)
256  ! dummy
257  class(methoddisvtype), intent(inout) :: this
258  type(celldefntype), pointer, intent(inout) :: defn
259  integer(I4B), intent(inout) :: inface
260  double precision, intent(inout) :: z
261  ! local
262  integer(I4B) :: icin
263  integer(I4B) :: npolyvertsin
264  integer(I4B) :: ic
265  integer(I4B) :: npolyverts
266  integer(I4B) :: inbr
267  integer(I4B) :: inbrnbr
268  integer(I4B) :: j
269  integer(I4B) :: m
270  real(DP) :: zrel
271  real(DP) :: topfrom
272  real(DP) :: botfrom
273  real(DP) :: top
274  real(DP) :: bot
275  real(DP) :: sat
276 
277  ! Map to shared cell face of neighbor
278  inbr = defn%facenbr(inface)
279  if (inbr .eq. 0) then
280  ! Exterior face; no neighbor to map to
281  ! todo AMP: reconsider when multiple models allowed
282  inface = -1
283  else
284  ! Load definition for neighbor cell (neighbor with shared face)
285  icin = defn%icell
286  j = this%fmi%dis%con%ia(icin)
287  ic = this%fmi%dis%con%ja(j + inbr)
288  call this%load_cell_defn(ic, this%neighbor)
289 
290  npolyvertsin = defn%npolyverts
291  npolyverts = this%neighbor%npolyverts
292  if (inface .eq. npolyvertsin + 2) then
293  ! Exits through bot, enters through top
294  inface = npolyverts + 3
295  else if (inface .eq. npolyvertsin + 3) then
296  ! Exits through top, enters through bot
297  inface = npolyverts + 2
298  else
299  ! Exits and enters through shared polygon face
300  j = this%fmi%dis%con%ia(ic)
301  do m = 1, npolyverts + 3
302  inbrnbr = this%neighbor%facenbr(m)
303  if (this%fmi%dis%con%ja(j + inbrnbr) .eq. icin) then
304  inface = m
305  exit
306  end if
307  end do
308  ! Map z between cells
309  topfrom = defn%top
310  botfrom = defn%bot
311  zrel = (z - botfrom) / (topfrom - botfrom)
312  top = this%fmi%dis%top(ic)
313  bot = this%fmi%dis%bot(ic)
314  sat = this%fmi%gwfsat(ic)
315  z = bot + zrel * sat * (top - bot)
316  end if
317  end if
318  end subroutine map_neighbor
319 
320  !> @brief Apply the DISV tracking method to a particle.
321  subroutine apply_disv(this, particle, tmax)
322  class(methoddisvtype), intent(inout) :: this
323  type(particletype), pointer, intent(inout) :: particle
324  real(DP), intent(in) :: tmax
325 
326  call this%track(particle, 1, tmax)
327  end subroutine apply_disv
328 
329  !> @brief Load cell definition from the grid
330  subroutine load_cell_defn(this, ic, defn)
331  ! dummy
332  class(methoddisvtype), intent(inout) :: this
333  integer(I4B), intent(in) :: ic
334  type(celldefntype), pointer, intent(inout) :: defn
335 
336  call this%load_properties(ic, defn)
337  call this%load_polygon(defn)
338  call this%load_neighbors(defn)
339  call this%load_indicators(defn)
340  call this%load_flows(defn)
341  end subroutine load_cell_defn
342 
343  !> @brief Loads cell properties to cell definition from the grid.
344  subroutine load_properties(this, ic, defn)
345  ! dummy
346  class(methoddisvtype), intent(inout) :: this
347  integer(I4B), intent(in) :: ic
348  type(celldefntype), pointer, intent(inout) :: defn
349  ! local
350  real(DP) :: top
351  real(DP) :: bot
352  real(DP) :: sat
353  integer(I4B) :: icu, icpl, ilay
354 
355  defn%icell = ic
356  defn%iatop = get_iatop(this%fmi%dis%get_ncpl(), &
357  this%fmi%dis%get_nodeuser(ic))
358  top = this%fmi%dis%top(ic)
359  bot = this%fmi%dis%bot(ic)
360  sat = this%fmi%gwfsat(ic)
361  top = bot + sat * (top - bot)
362  defn%top = top
363  defn%bot = bot
364  defn%sat = sat
365  defn%porosity = this%porosity(ic)
366  defn%retfactor = this%retfactor(ic)
367  defn%izone = this%izone(ic)
368  select type (dis => this%fmi%dis)
369  type is (disvtype)
370  icu = dis%get_nodeuser(ic)
371  call get_jk(icu, dis%ncpl, dis%nlay, icpl, ilay)
372  defn%ilay = ilay
373  end select
374  end subroutine load_properties
375 
376  subroutine load_polygon(this, defn)
377  ! dummy
378  class(methoddisvtype), intent(inout) :: this
379  type(celldefntype), pointer, intent(inout) :: defn
380 
381  call this%fmi%dis%get_polyverts( &
382  defn%icell, &
383  defn%polyvert, &
384  closed=.true.)
385  defn%npolyverts = size(defn%polyvert, dim=2) - 1
386  end subroutine load_polygon
387 
388  !> @brief Loads face neighbors to cell definition from the grid
389  !! Assumes cell index and number of vertices are already loaded.
390  subroutine load_neighbors(this, defn)
391  ! dummy
392  class(methoddisvtype), intent(inout) :: this
393  type(celldefntype), pointer, intent(inout) :: defn
394  ! local
395  integer(I4B) :: ic1
396  integer(I4B) :: ic2
397  integer(I4B) :: icu1
398  integer(I4B) :: icu2
399  integer(I4B) :: j1
400  integer(I4B) :: j2
401  integer(I4B) :: k1
402  integer(I4B) :: k2
403  integer(I4B) :: iloc
404  integer(I4B) :: ipos
405  integer(I4B) :: istart1
406  integer(I4B) :: istart2
407  integer(I4B) :: istop1
408  integer(I4B) :: istop2
409  integer(I4B) :: isharedface
410  integer(I4B) :: ncpl
411  integer(I4B) :: nfaces
412  integer(I4B) :: nslots
413 
414  ! expand facenbr array if needed
415  nfaces = defn%npolyverts + 3
416  nslots = size(defn%facenbr)
417  if (nslots < nfaces) call expandarray(defn%facenbr, nfaces - nslots)
418 
419  select type (dis => this%fmi%dis)
420  type is (disvtype)
421  ! Load face neighbors.
422  defn%facenbr = 0
423  ic1 = defn%icell
424  icu1 = dis%get_nodeuser(ic1)
425  ncpl = dis%get_ncpl()
426  call get_jk(icu1, ncpl, dis%nlay, j1, k1)
427  istart1 = dis%iavert(j1)
428  istop1 = dis%iavert(j1 + 1) - 1
429  do iloc = 1, dis%con%ia(ic1 + 1) - dis%con%ia(ic1) - 1
430  ipos = dis%con%ia(ic1) + iloc
431  ! mask could become relevant if PRT uses interface model
432  if (dis%con%mask(ipos) == 0) cycle
433  ic2 = dis%con%ja(ipos)
434  icu2 = dis%get_nodeuser(ic2)
435  call get_jk(icu2, ncpl, dis%nlay, j2, k2)
436  istart2 = dis%iavert(j2)
437  istop2 = dis%iavert(j2 + 1) - 1
438  call shared_face(dis%javert(istart1:istop1), &
439  dis%javert(istart2:istop2), &
440  isharedface)
441  if (isharedface /= 0) then
442  ! Edge (polygon) face neighbor
443  defn%facenbr(isharedface) = int(iloc, 1)
444  else
445  if (k2 > k1) then
446  ! Bottom face neighbor
447  defn%facenbr(defn%npolyverts + 2) = int(iloc, 1)
448  else if (k2 < k1) then
449  ! Top face neighbor
450  defn%facenbr(defn%npolyverts + 3) = int(iloc, 1)
451  else
452  call pstop(1, "k2 should be <> k1, since no shared edge face")
453  end if
454  end if
455  end do
456  end select
457  ! List of edge (polygon) faces wraps around
458  defn%facenbr(defn%npolyverts + 1) = defn%facenbr(1)
459  end subroutine load_neighbors
460 
461  !> @brief Load flows into the cell definition.
462  !! These include face, boundary and net distributed flows.
463  !! Assumes cell index and number of vertices are already loaded.
464  subroutine load_flows(this, defn)
465  ! dummy
466  class(methoddisvtype), intent(inout) :: this
467  type(celldefntype), intent(inout) :: defn
468  ! local
469  integer(I4B) :: nfaces, nslots
470 
471  ! expand faceflow array if needed
472  nfaces = defn%npolyverts + 3
473  nslots = size(defn%faceflow)
474  if (nslots < nfaces) call expandarray(defn%faceflow, nfaces - nslots)
475 
476  ! Load face flows, including boundary flows. As with cell verts,
477  ! the face flow array wraps around. Top and bottom flows make up
478  ! the last two elements, respectively, for size npolyverts + 3.
479  ! If there is no flow through any face, set a no-exit-face flag.
480  defn%faceflow = dzero
481  defn%inoexitface = 1
482  call this%load_boundary_flows_to_defn_poly(defn)
483  call this%load_face_flows_to_defn_poly(defn)
484 
485  ! Add up net distributed flow
486  defn%distflow = this%fmi%SourceFlows(defn%icell) + &
487  this%fmi%SinkFlows(defn%icell) + &
488  this%fmi%StorageFlows(defn%icell)
489 
490  ! Set weak sink flag
491  if (this%fmi%SinkFlows(defn%icell) .ne. dzero) then
492  defn%iweaksink = 1
493  else
494  defn%iweaksink = 0
495  end if
496  end subroutine load_flows
497 
498  subroutine load_face_flows_to_defn_poly(this, defn)
499  ! dummy
500  class(methoddisvtype), intent(inout) :: this
501  type(celldefntype), intent(inout) :: defn
502  ! local
503  integer(I4B) :: m, n, nfaces
504  real(DP) :: q
505 
506  nfaces = defn%npolyverts + 3
507  do m = 1, nfaces
508  n = defn%facenbr(m)
509  if (n > 0) then
510  q = this%fmi%gwfflowja(this%fmi%dis%con%ia(defn%icell) + n)
511  defn%faceflow(m) = defn%faceflow(m) + q
512  end if
513  if (defn%faceflow(m) < dzero) defn%inoexitface = 0
514  end do
515  end subroutine load_face_flows_to_defn_poly
516 
517  !> @brief Load boundary flows from the grid into a polygonal cell.
518  !! Assumes cell index and number of vertices are already loaded.
519  subroutine load_boundary_flows_to_defn_poly(this, defn)
520  ! dummy
521  class(methoddisvtype), intent(inout) :: this
522  type(celldefntype), intent(inout) :: defn
523 
524  ! local
525  integer(I4B) :: ic, iv, ioffset, npolyverts, max_faces
526 
527  ic = defn%icell
528  npolyverts = defn%npolyverts
529  max_faces = this%fmi%max_faces
530  ioffset = (ic - 1) * max_faces
531  do iv = 1, npolyverts
532  defn%faceflow(iv) = &
533  defn%faceflow(iv) + &
534  this%fmi%BoundaryFlows(ioffset + iv)
535  end do
536  defn%faceflow(npolyverts + 1) = defn%faceflow(1)
537  defn%faceflow(npolyverts + 2) = &
538  defn%faceflow(npolyverts + 2) + &
539  this%fmi%BoundaryFlows(ioffset + max_faces - 1)
540  defn%faceflow(npolyverts + 3) = &
541  defn%faceflow(npolyverts + 3) + &
542  this%fmi%BoundaryFlows(ioffset + max_faces)
543 
544  end subroutine load_boundary_flows_to_defn_poly
545 
546  !> @brief Load 180-degree vertex indicator array and set flags
547  !! indicating how cell can be represented. Assumes cell index
548  !! and number of vertices are already loaded.
549  !<
550  subroutine load_indicators(this, defn)
551  ! dummy
552  class(methoddisvtype), intent(inout) :: this
553  type(celldefntype), pointer, intent(inout) :: defn
554  ! local
555  integer(I4B) :: npolyverts
556  integer(I4B) :: m
557  integer(I4B) :: m0
558  integer(I4B) :: m1
559  integer(I4B) :: m2
560  integer(I4B) :: ic
561  integer(I4B) :: num90
562  integer(I4B) :: num180
563  real(DP) :: x0
564  real(DP) :: y0
565  real(DP) :: x1
566  real(DP) :: y1
567  real(DP) :: x2
568  real(DP) :: y2
569  real(DP) :: epsang
570  real(DP) :: s0x
571  real(DP) :: s0y
572  real(DP) :: &
573  s0mag, s2x, s2y, s2mag, sinang, cosang, dotprod
574  logical(LGP) last180
575 
576  ic = defn%icell
577  npolyverts = defn%npolyverts
578 
579  if (size(defn%ispv180) < npolyverts + 3) &
580  call expandarray(defn%ispv180, npolyverts + 1)
581 
582  defn%ispv180(1:npolyverts + 1) = .false.
583  defn%can_be_rect = .false.
584  defn%can_be_quad = .false.
585  epsang = 1d-5
586  num90 = 0
587  num180 = 0
588  last180 = .false.
589 
590  ! assumes non-self-intersecting polygon
591  do m = 1, npolyverts
592  m1 = m
593  if (m1 .eq. 1) then
594  m0 = npolyverts
595  m2 = 2
596  else if (m1 .eq. npolyverts) then
597  m0 = npolyverts - 1
598  m2 = 1
599  else
600  m0 = m1 - 1
601  m2 = m1 + 1
602  end if
603  x0 = defn%polyvert(1, m0)
604  y0 = defn%polyvert(2, m0)
605  x1 = defn%polyvert(1, m1)
606  y1 = defn%polyvert(2, m1)
607  x2 = defn%polyvert(1, m2)
608  y2 = defn%polyvert(2, m2)
609  s0x = x0 - x1
610  s0y = y0 - y1
611  s0mag = dsqrt(s0x * s0x + s0y * s0y)
612  s2x = x2 - x1
613  s2y = y2 - y1
614  s2mag = dsqrt(s2x * s2x + s2y * s2y)
615  sinang = (s0x * s2y - s0y * s2x) / (s0mag * s2mag)
616  cosang = dsqrt(dabs(done - (sinang * sinang)))
617  if (dabs(sinang) .lt. epsang) then
618  dotprod = s0x * s2x + s0y * s2y
619  if (dotprod .lt. dzero) then
620  num180 = num180 + 1
621  last180 = .true.
622  defn%ispv180(m) = .true.
623  end if
624  else
625  if (dabs(cosang) .lt. epsang) num90 = num90 + 1
626  last180 = .false.
627  end if
628  end do
629 
630  ! List of 180-degree indicators wraps around for convenience
631  defn%ispv180(npolyverts + 1) = defn%ispv180(1)
632 
633  ! Set rect/quad flags
634  if (num90 .eq. 4) then
635  if (num180 .eq. 0) then
636  defn%can_be_rect = .true.
637  else
638  defn%can_be_quad = .true.
639  end if
640  end if
641  end subroutine load_indicators
642 
643 end module methoddisvmodule
subroutine, public create_defn(cellDefn)
Create a new cell definition object.
Definition: CellDefn.f90:42
integer(i4b) function, public get_iatop(ncpl, icu)
Get the index corresponding to top elevation of a cell in the grid. This is -1 if the cell is in the ...
Definition: CellDefn.f90:54
subroutine, public create_cell_poly(cell)
Create a new polygonal cell.
Definition: CellPoly.f90:20
subroutine, public cell_poly_to_rect(poly, rect)
Convert CellPoly representation to CellRect. Assumes the conversion is possible.
Definition: CellUtil.f90:14
subroutine, public cell_poly_to_quad(poly, quad)
Convert CellPoly representation to CellRectQuad. Assumes the conversion is possible.
Definition: CellUtil.f90:115
This module contains simulation constants.
Definition: Constants.f90:9
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
subroutine pstop(status, message)
Stop the program, optionally specifying an error status code.
Definition: ErrorUtil.f90:24
subroutine, public shared_face(iverts1, iverts2, iface)
Find the lateral face shared by two cells.
Definition: GeomUtil.f90:403
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
This module defines variable data types.
Definition: kind.f90:8
Cell-level tracking methods.
type(methodcellpollocktype), pointer, public method_cell_plck
type(methodcellpasstobottype), pointer, public method_cell_ptb
type(methodcellpollockquadtype), pointer, public method_cell_quad
type(methodcellternarytype), pointer, public method_cell_tern
subroutine, public create_method_disv(method)
Create a new vertex grid (DISV) tracking method.
Definition: MethodDisv.f90:47
subroutine load_neighbors(this, defn)
Loads face neighbors to cell definition from the grid Assumes cell index and number of vertices are a...
Definition: MethodDisv.f90:391
subroutine map_neighbor(this, defn, inface, z)
Map location on cell face to shared cell face of neighbor.
Definition: MethodDisv.f90:256
subroutine load_indicators(this, defn)
Load 180-degree vertex indicator array and set flags indicating how cell can be represented....
Definition: MethodDisv.f90:551
subroutine update_flowja(this, cell, particle)
Definition: MethodDisv.f90:201
subroutine load_disv(this, particle, next_level, submethod)
Load the cell and the tracking method.
Definition: MethodDisv.f90:69
subroutine load_face_flows_to_defn_poly(this, defn)
Definition: MethodDisv.f90:499
subroutine load_polygon(this, defn)
Definition: MethodDisv.f90:377
subroutine load_particle(this, cell, particle)
Definition: MethodDisv.f90:140
subroutine load_properties(this, ic, defn)
Loads cell properties to cell definition from the grid.
Definition: MethodDisv.f90:345
subroutine load_flows(this, defn)
Load flows into the cell definition. These include face, boundary and net distributed flows....
Definition: MethodDisv.f90:465
subroutine load_boundary_flows_to_defn_poly(this, defn)
Load boundary flows from the grid into a polygonal cell. Assumes cell index and number of vertices ar...
Definition: MethodDisv.f90:520
subroutine load_cell_defn(this, ic, defn)
Load cell definition from the grid.
Definition: MethodDisv.f90:331
subroutine apply_disv(this, particle, tmax)
Apply the DISV tracking method to a particle.
Definition: MethodDisv.f90:322
subroutine pass_disv(this, particle)
Pass a particle to the next cell, if there is one.
Definition: MethodDisv.f90:225
Particle tracking strategies.
Definition: Method.f90:2
@, public level_feature
Definition: Method.f90:37
@, public level_subfeature
Definition: Method.f90:38
@, public terminate
particle terminated
@ term_boundary
terminated at a boundary face
Definition: Particle.f90:30
Base grid cell definition.
Definition: CellDefn.f90:10
Base type for grid cells of a concrete type. Contains a cell-definition which is information shared b...
Definition: Cell.f90:11
Vertex grid discretization.
Definition: Disv.f90:24
Base type for particle tracking methods.
Definition: Method.f90:54
Particle tracked by the PRT model.
Definition: Particle.f90:56