Skip to content

Commit

Permalink
fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
wpbonelli committed Dec 31, 2024
1 parent a3a37c3 commit cdefe67
Show file tree
Hide file tree
Showing 12 changed files with 52 additions and 52 deletions.
3 changes: 0 additions & 3 deletions src/Solution/ParticleTracker/Cell.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,9 +13,6 @@ module CellModule
type, abstract :: CellType
character(len=40), pointer :: type ! tracking domain type
type(CellDefnType), pointer :: defn => null() ! cell defn
double precision, public :: xO ! model x origin for local (x, y)
double precision, public :: yO ! model y origin for local (x, y)
double precision, public :: zO ! model z origin for local z
contains
procedure(destroy), deferred :: destroy !< destroy the cell
end type CellType
Expand Down
4 changes: 4 additions & 0 deletions src/Solution/ParticleTracker/CellRect.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,10 @@ module CellRectModule
double precision, public :: sinrot ! sine of rotation angle for local (x, y)
double precision, public :: cosrot ! cosine of rotation angle for local (x, y)

double precision, public :: xOrigin ! model x origin for local (x, y)
double precision, public :: yOrigin ! model y origin for local (x, y)
double precision, public :: zOrigin ! model z origin for local z

double precision, public :: vx1 ! west-boundary local-x velocity
double precision, public :: vx2 ! east-boundary local-x velocity
double precision, public :: vy1 ! south-boundary local-y velocity
Expand Down
6 changes: 3 additions & 3 deletions src/Solution/ParticleTracker/CellUtil.f90
Original file line number Diff line number Diff line change
Expand Up @@ -88,9 +88,9 @@ subroutine cell_poly_to_rect(poly, rect)
rect%dz = dz
rect%sinrot = sinrot
rect%cosrot = cosrot
rect%xO = xOrigin
rect%yO = yOrigin
rect%zO = zOrigin
rect%xOrigin = xOrigin
rect%yOrigin = yOrigin
rect%zOrigin = zOrigin
rect%ipvOrigin = ipv1

! -- Compute (unscaled) cell edge velocities from face flows
Expand Down
12 changes: 6 additions & 6 deletions src/Solution/ParticleTracker/MethodCellPollock.f90
Original file line number Diff line number Diff line change
Expand Up @@ -135,9 +135,9 @@ subroutine apply_mcp(this, particle, tmax)

! Transform model coordinates to local cell coordinates
! (translated/rotated but not scaled relative to model)
xOrigin = cell%xO
yOrigin = cell%yO
zOrigin = cell%zO
xOrigin = cell%xOrigin
yOrigin = cell%yOrigin
zOrigin = cell%zOrigin
sinrot = cell%sinrot
cosrot = cell%cosrot
call particle%transform(xOrigin, yOrigin, zOrigin, &
Expand Down Expand Up @@ -171,9 +171,9 @@ subroutine load_subcell(this, particle, subcell) !
subcell%dz = cell%dz
subcell%sinrot = DZERO
subcell%cosrot = DONE
subcell%xO = DZERO
subcell%yO = DZERO
subcell%zO = DZERO
subcell%xOrigin = DZERO
subcell%yOrigin = DZERO
subcell%zOrigin = DZERO

! Set subcell edge velocities
subcell%vx1 = cell%vx1 ! cell velocities already account for retfactor and porosity
Expand Down
18 changes: 9 additions & 9 deletions src/Solution/ParticleTracker/MethodCellPollockQuad.f90
Original file line number Diff line number Diff line change
Expand Up @@ -297,38 +297,38 @@ subroutine load_subcell(this, particle, subcell)
subcell%dz = dz
subcell%sinrot = DZERO
subcell%cosrot = DONE
subcell%zO = DZERO
subcell%zOrigin = DZERO
select case (isc)
case (1)
subcell%xO = dx
subcell%yO = dy
subcell%xOrigin = dx
subcell%yOrigin = dy
term = factor / areax
subcell%vx1 = qintl1 * term
subcell%vx2 = -qextl2 * term
term = factor / areay
subcell%vy1 = -qintl2 * term
subcell%vy2 = -qextl1 * term
case (2)
subcell%xO = dx
subcell%yO = DZERO
subcell%xOrigin = dx
subcell%yOrigin = DZERO
term = factor / areax
subcell%vx1 = -qintl2 * term
subcell%vx2 = -qextl1 * term
term = factor / areay
subcell%vy1 = qextl2 * term
subcell%vy2 = -qintl1 * term
case (3)
subcell%xO = DZERO
subcell%yO = DZERO
subcell%xOrigin = DZERO
subcell%yOrigin = DZERO
term = factor / areax
subcell%vx1 = qextl2 * term
subcell%vx2 = -qintl1 * term
term = factor / areay
subcell%vy1 = qextl1 * term
subcell%vy2 = qintl2 * term
case (4)
subcell%xO = DZERO
subcell%yO = dy
subcell%xOrigin = DZERO
subcell%yOrigin = dy
term = factor / areax
subcell%vx1 = qextl1 * term
subcell%vx2 = qintl2 * term
Expand Down
25 changes: 19 additions & 6 deletions src/Solution/ParticleTracker/MethodCellTernary.f90
Original file line number Diff line number Diff line change
Expand Up @@ -158,7 +158,8 @@ subroutine apply_mct(this, particle, tmax)
real(DP), intent(in) :: tmax
! local
integer(I4B) :: i
real(DP) :: x, y, z
real(DP) :: x, y, z, xO, yO
real(DP), allocatable :: xs(:), ys(:)

! (Re)allocate type-bound arrays
select type (cell => this%cell)
Expand Down Expand Up @@ -195,11 +196,23 @@ subroutine apply_mct(this, particle, tmax)
allocate (this%xvertnext(this%nverts))
allocate (this%yvertnext(this%nverts))

allocate (xs(this%nverts))
allocate (ys(this%nverts))

xs = cell%defn%polyvert(1, :)
ys = cell%defn%polyvert(2, :)

xO = xs(minloc(abs(xs), dim=1))
yO = ys(minloc(abs(ys), dim=1))

deallocate (xs)
deallocatE (ys)

! Cell vertices
do i = 1, this%nverts
x = cell%defn%polyvert(1, i)
y = cell%defn%polyvert(2, i)
call transform(x, y, DZERO, x, y, z, cell%xO, cell%yO)
call transform(x, y, DZERO, x, y, z, xO, yO)
this%xvert(i) = x
this%yvert(i) = y
end do
Expand All @@ -221,13 +234,13 @@ subroutine apply_mct(this, particle, tmax)
call this%vertvelo()

! Transform particle coordinates
call particle%transform(cell%xO, cell%yO)
call particle%transform(xO, yO)

! Track the particle across the cell.
call this%track(particle, 2, tmax)

! Transform particle coordinates back
call particle%transform(cell%xO, cell%yO, invert=.true.)
call particle%transform(xO, yO, invert=.true.)
call particle%reset_transform()

end select
Expand Down Expand Up @@ -310,8 +323,8 @@ subroutine load_subcell(this, particle, subcell)

! Set coordinates and velocities at vertices of triangular subcell
iv0 = isc
subcell%xO = this%xvert(iv0)
subcell%yO = this%yvert(iv0)
subcell%x0 = this%xvert(iv0)
subcell%y0 = this%yvert(iv0)
subcell%x1 = this%xvertnext(iv0)
subcell%y1 = this%yvertnext(iv0)
subcell%x2 = this%xctr
Expand Down
6 changes: 3 additions & 3 deletions src/Solution/ParticleTracker/MethodDis.f90
Original file line number Diff line number Diff line change
Expand Up @@ -95,9 +95,9 @@ subroutine load_cell(this, ic, cell)
cell%dz = dz
cell%sinrot = DZERO
cell%cosrot = DONE
cell%xO = cell%defn%polyvert(1, 1)
cell%yO = cell%defn%polyvert(2, 1)
cell%zO = cell%defn%bot
cell%xOrigin = cell%defn%polyvert(1, 1)
cell%yOrigin = cell%defn%polyvert(2, 1)
cell%zOrigin = cell%defn%bot
cell%ipvOrigin = 1

factor = DONE / cell%defn%retfactor
Expand Down
14 changes: 0 additions & 14 deletions src/Solution/ParticleTracker/MethodDisv.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,6 @@ module MethodDisvModule
procedure, public :: deallocate !< deallocate arrays and scalars
procedure, public :: load => load_disv !< load the cell method
procedure, public :: load_cell_defn !< load cell definition from the grid
procedure, public :: load_cell !< load the cell from the grid
procedure, public :: pass => pass_disv !< pass the particle to the next cell
procedure :: map_neighbor !< map a location on the cell face to the shared face of a neighbor
procedure :: update_flowja !< update intercell mass flows
Expand Down Expand Up @@ -88,7 +87,6 @@ subroutine load_disv(this, particle, next_level, submethod)
type is (CellPolyType)
ic = particle%idomain(next_level)
call this%load_cell_defn(ic, cell%defn)
call this%load_cell(ic, cell)
if (this%fmi%ibdgwfsat0(ic) == 0) then
call method_cell_ptb%init( &
fmi=this%fmi, &
Expand Down Expand Up @@ -333,18 +331,6 @@ subroutine load_cell_defn(this, ic, defn)
call this%load_flows(defn)
end subroutine load_cell_defn

subroutine load_cell(this, ic, cell)
! dummy
class(MethodDisvType), intent(inout) :: this
integer(I4B), intent(in) :: ic
type(CellPolyType), pointer, intent(inout) :: cell

cell%xO = cell%defn%polyvert(1, 1)
cell%yO = cell%defn%polyvert(2, 1)
cell%zO = cell%defn%bot

end subroutine load_cell

!> @brief Loads cell properties to cell definition from the grid.
subroutine load_properties(this, ic, defn)
! dummy
Expand Down
6 changes: 3 additions & 3 deletions src/Solution/ParticleTracker/MethodSubcellPollock.f90
Original file line number Diff line number Diff line change
Expand Up @@ -65,9 +65,9 @@ subroutine apply_msp(this, particle, tmax)
! track particle across subcell, convert back to model coords
! (sinrot and cosrot should be 0 and 1, respectively, i.e. no
! rotation, also no z translation; only x and y translations)
xOrigin = subcell%xO
yOrigin = subcell%yO
zOrigin = subcell%zO
xOrigin = subcell%xOrigin
yOrigin = subcell%yOrigin
zOrigin = subcell%zOrigin
sinrot = subcell%sinrot
cosrot = subcell%cosrot
call particle%transform(xOrigin, yOrigin)
Expand Down
4 changes: 2 additions & 2 deletions src/Solution/ParticleTracker/MethodSubcellTernary.f90
Original file line number Diff line number Diff line change
Expand Up @@ -147,8 +147,8 @@ subroutine track_subcell(this, subcell, particle, tmax)
xi = particle%x
yi = particle%y
zi = particle%z
x0 = subcell%xO
y0 = subcell%yO
x0 = subcell%x0
y0 = subcell%y0
x1 = subcell%x1
y1 = subcell%y1
x2 = subcell%x2
Expand Down
3 changes: 0 additions & 3 deletions src/Solution/ParticleTracker/Subcell.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,6 @@ module SubcellModule
character(len=40), pointer, public :: type !< character string that names the tracking domain type
integer, public :: isubcell !< index of subcell in the cell
integer, public :: icell !< index of cell in the source grid
double precision, public :: xO !< x origin for local coords
double precision, public :: yO !< y origin for local coords
double precision, public :: zO !< z origin for local coords
contains
procedure(destroy), deferred :: destroy !< destructor
procedure(init), deferred :: init !< initializer
Expand Down
3 changes: 3 additions & 0 deletions src/Solution/ParticleTracker/SubcellRect.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,9 @@ module SubcellRectModule
private
double precision, public :: sinrot !< sine of rotation angle for local (x, y)
double precision, public :: cosrot !< cosine of rotation angle for local (x, y)
double precision, public :: xOrigin !< cell x origin for local (x, y)
double precision, public :: yOrigin !< cell y origin for local (x, y)
double precision, public :: zOrigin !< cell z origin for local z
double precision, public :: dx, dy, dz !< subcell dimensions
double precision, public :: vx1, vx2, vy1, vy2, vz1, vz2 !< subcell face velocities
contains
Expand Down

0 comments on commit cdefe67

Please sign in to comment.