Skip to content
This repository was archived by the owner on Aug 28, 2024. It is now read-only.

Commit

Permalink
Updated integer variables involved in tracking number of encoutners t…
Browse files Browse the repository at this point in the history
…o be 8-byte. Restructured the double-list version of the sort-sweep algorithm to remove some inefficiencies. Timers still active, so this is not production ready.
  • Loading branch information
daminton committed Nov 22, 2021
1 parent 393cd4a commit 1b2a17f
Show file tree
Hide file tree
Showing 12 changed files with 621 additions and 239 deletions.
577 changes: 391 additions & 186 deletions src/encounter/encounter_check.f90

Large diffs are not rendered by default.

4 changes: 2 additions & 2 deletions src/encounter/encounter_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ module subroutine encounter_setup_list(self, n)
implicit none
! Arguments
class(encounter_list), intent(inout) :: self !! Swiftest encounter structure
integer(I4B), intent(in) :: n !! Number of encounters to allocate space for
integer(I8B), intent(in) :: n !! Number of encounters to allocate space for

if (n < 0) return

Expand All @@ -69,7 +69,7 @@ module subroutine encounter_setup_list(self, n)
if (allocated(self%t)) deallocate(self%t)

self%nenc = n
if (n == 0) return
if (n == 0_I8B) return

allocate(self%lvdotr(n))
allocate(self%status(n))
Expand Down
12 changes: 6 additions & 6 deletions src/encounter/encounter_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -140,27 +140,27 @@ module subroutine encounter_util_resize_list(self, nnew)
implicit none
! Arguments
class(encounter_list), intent(inout) :: self !! Swiftest encounter list
integer(I4B), intent(in) :: nnew !! New size of list needed
integer(I8B), intent(in) :: nnew !! New size of list needed
! Internals
class(encounter_list), allocatable :: enc_temp
integer(I4B) :: nold
integer(I8B) :: nold
logical :: lmalloc

lmalloc = allocated(self%status)
if (lmalloc) then
nold = size(self%status)
else
nold = 0
nold = 0_I8B
end if
if (nnew > nold) then
if (lmalloc) allocate(enc_temp, source=self)
call self%setup(2 * nnew)
call self%setup(2_I8B * nnew)
if (lmalloc) then
call self%copy(enc_temp)
deallocate(enc_temp)
end if
else
self%status(nnew+1:nold) = INACTIVE
self%status(nnew+1_I8B:nold) = INACTIVE
end if
self%nenc = nnew

Expand All @@ -179,7 +179,7 @@ module subroutine encounter_util_spill_list(self, discards, lspill_list, ldestru
logical, dimension(:), intent(in) :: lspill_list !! Logical array of bodies to spill into the discards
logical, intent(in) :: ldestructive !! Logical flag indicating whether or not this operation should alter body by removing the discard list
! Internals
integer(I4B) :: nenc_old
integer(I8B) :: nenc_old

associate(keeps => self)
call util_spill(keeps%lvdotr, discards%lvdotr, lspill_list, ldestructive)
Expand Down
32 changes: 16 additions & 16 deletions src/modules/encounter_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module encounter_classes
integer(I4B), parameter :: SWEEPDIM = 3

type :: encounter_list
integer(I4B) :: nenc = 0 !! Total number of encounters
integer(I8B) :: nenc = 0 !! Total number of encounters
logical, dimension(:), allocatable :: lvdotr !! relative vdotr flag
integer(I4B), dimension(:), allocatable :: status !! status of the interaction
integer(I4B), dimension(:), allocatable :: index1 !! position of the first body in the encounter
Expand All @@ -36,8 +36,8 @@ module encounter_classes
type encounter_bounding_box_1D
integer(I4B) :: n !! Number of bodies with extents
integer(I4B), dimension(:), allocatable :: ind !! Sorted minimum/maximum extent indices (value > n indicates an ending index)
integer(I4B), dimension(:), allocatable :: ibeg !! Beginning index for box
integer(I4B), dimension(:), allocatable :: iend !! Ending index for box
integer(I8B), dimension(:), allocatable :: ibeg !! Beginning index for box
integer(I8B), dimension(:), allocatable :: iend !! Ending index for box
contains
procedure :: sort => encounter_check_sort_aabb_1D !! Sorts the bounding box extents along a single dimension prior to the sweep phase
procedure :: dealloc => encounter_util_dealloc_aabb !! Deallocates all allocatables
Expand All @@ -56,7 +56,7 @@ module encounter_classes
interface
module subroutine encounter_check_all(nenc, index1, index2, x1, v1, x2, v2, renc1, renc2, dt, lencounter, lvdotr)
implicit none
integer(I4B), intent(in) :: nenc !! Number of encounters in the encounter lists
integer(I8B), intent(in) :: nenc !! Number of encounters in the encounter lists
integer(I4B), dimension(:), intent(in) :: index1 !! List of indices for body 1 in each encounter
integer(I4B), dimension(:), intent(in) :: index2 !! List of indices for body 2 in each encounter1
real(DP), dimension(:,:), intent(in) :: x1, v1 !! Array of indices of bodies 1
Expand All @@ -80,7 +80,7 @@ module subroutine encounter_check_all_plpl(param, npl, x, v, renc, dt, lvdotr, i
logical, dimension(:), allocatable, intent(out) :: lvdotr !! Logical flag indicating the sign of v .dot. x
integer(I4B), dimension(:), allocatable, intent(out) :: index1 !! List of indices for body 1 in each encounter
integer(I4B), dimension(:), allocatable, intent(out) :: index2 !! List of indices for body 2 in each encounter
integer(I4B), intent(out) :: nenc !! Total number of encounters
integer(I8B), intent(out) :: nenc !! Total number of encounters
end subroutine encounter_check_all_plpl

module subroutine encounter_check_all_plplm(param, nplm, nplt, xplm, vplm, xplt, vplt, rencm, renct, dt, lvdotr, index1, index2, nenc)
Expand All @@ -99,7 +99,7 @@ module subroutine encounter_check_all_plplm(param, nplm, nplt, xplm, vplm, xplt,
logical, dimension(:), allocatable, intent(out) :: lvdotr !! Logical flag indicating the sign of v .dot. x
integer(I4B), dimension(:), allocatable, intent(out) :: index1 !! List of indices for body 1 in each encounter
integer(I4B), dimension(:), allocatable, intent(out) :: index2 !! List of indices for body 2 in each encounter
integer(I4B), intent(out) :: nenc !! Total number of encounters
integer(I8B), intent(out) :: nenc !! Total number of encounters
end subroutine encounter_check_all_plplm

module subroutine encounter_check_all_pltp(param, npl, ntp, xpl, vpl, xtp, vtp, renc, dt, lvdotr, index1, index2, nenc)
Expand All @@ -117,7 +117,7 @@ module subroutine encounter_check_all_pltp(param, npl, ntp, xpl, vpl, xtp, vtp,
logical, dimension(:), allocatable, intent(out) :: lvdotr !! Logical flag indicating the sign of v .dot. x
integer(I4B), dimension(:), allocatable, intent(out) :: index1 !! List of indices for body 1 in each encounter
integer(I4B), dimension(:), allocatable, intent(out) :: index2 !! List of indices for body 2 in each encounter
integer(I4B), intent(out) :: nenc !! Total number of encounters
integer(I8B), intent(out) :: nenc !! Total number of encounters
end subroutine encounter_check_all_pltp

module pure subroutine encounter_check_one(xr, yr, zr, vxr, vyr, vzr, renc, dt, lencounter, lvdotr)
Expand All @@ -135,7 +135,7 @@ module subroutine encounter_check_collapse_ragged_list(ragged_list, n1, nenc, in
implicit none
type(encounter_list), dimension(:), intent(in) :: ragged_list !! The ragged encounter list
integer(I4B), intent(in) :: n1 !! Number of bodies 1
integer(I4B), intent(out) :: nenc !! Total number of encountersj
integer(I8B), intent(out) :: nenc !! Total number of encountersj
integer(I4B), dimension(:), allocatable, intent(out) :: index1 !! Array of indices for body 1
integer(I4B), dimension(:), allocatable, intent(out) :: index2 !! Array of indices for body 1
logical, dimension(:), allocatable, intent(out), optional :: lvdotr !! Array indicating which bodies are approaching
Expand All @@ -153,7 +153,7 @@ module subroutine encounter_check_sweep_aabb_double_list(self, n1, n2, nenc, ind
class(encounter_bounding_box), intent(inout) :: self !! Multi-dimensional bounding box structure
integer(I4B), intent(in) :: n1 !! Number of bodies 1
integer(I4B), intent(in) :: n2 !! Number of bodies 2
integer(I4B), intent(out) :: nenc !! Total number of encounter candidates
integer(I8B), intent(out) :: nenc !! Total number of encounter candidates
integer(I4B), dimension(:), allocatable, intent(out) :: index1 !! List of indices for body 1 in each encounter candidate pair
integer(I4B), dimension(:), allocatable, intent(out) :: index2 !! List of indices for body 2 in each encounter candidate pair
end subroutine encounter_check_sweep_aabb_double_list
Expand All @@ -162,7 +162,7 @@ module subroutine encounter_check_sweep_aabb_single_list(self, n, nenc, index1,
implicit none
class(encounter_bounding_box), intent(inout) :: self !! Multi-dimensional bounding box structure
integer(I4B), intent(in) :: n !! Number of bodies 1
integer(I4B), intent(out) :: nenc !! Total number of encounter candidates
integer(I8B), intent(out) :: nenc !! Total number of encounter candidates
integer(I4B), dimension(:), allocatable, intent(out) :: index1 !! List of indices for body 1 in each encounter candidate pair
integer(I4B), dimension(:), allocatable, intent(out) :: index2 !! List of indices for body 2 in each encounter candidate pair
end subroutine encounter_check_sweep_aabb_single_list
Expand All @@ -181,7 +181,7 @@ end subroutine encounter_io_write_frame
module subroutine encounter_io_write_list(self, pl, encbody, param)
use swiftest_classes, only : swiftest_pl, swiftest_body, swiftest_parameters
implicit none
class(encounter_list), intent(in) :: self !! Swiftest encounter list object
class(encounter_list), intent(in) :: self !! Swiftest encounter list object
class(swiftest_pl), intent(in) :: pl !! Swiftest massive body object
class(swiftest_body), intent(in) :: encbody !! Encountering body - Swiftest generic body object (pl or tp)
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
Expand All @@ -197,14 +197,14 @@ end subroutine encounter_setup_aabb
module subroutine encounter_setup_list(self, n)
implicit none
class(encounter_list), intent(inout) :: self !! Swiftest encounter structure
integer(I4B), intent(in) :: n !! Number of encounters to allocate space for
integer(I8B), intent(in) :: n !! Number of encounters to allocate space for
end subroutine encounter_setup_list

module subroutine encounter_util_append_list(self, source, lsource_mask)
implicit none
class(encounter_list), intent(inout) :: self !! Swiftest encounter list object
class(encounter_list), intent(in) :: source !! Source object to append
logical, dimension(:), intent(in) :: lsource_mask !! Logical mask indicating which elements to append to
logical, dimension(:), intent(in) :: lsource_mask !! Logical mask indicating which elements to append to
end subroutine encounter_util_append_list

module subroutine encounter_util_copy_list(self, source)
Expand Down Expand Up @@ -236,15 +236,15 @@ end subroutine encounter_util_final_list
module subroutine encounter_util_resize_list(self, nnew)
implicit none
class(encounter_list), intent(inout) :: self !! Swiftest encounter list
integer(I4B), intent(in) :: nnew !! New size of list needed
integer(I8B), intent(in) :: nnew !! New size of list needed
end subroutine encounter_util_resize_list

module subroutine encounter_util_spill_list(self, discards, lspill_list, ldestructive)
implicit none
class(encounter_list), intent(inout) :: self !! Swiftest encounter list
class(encounter_list), intent(inout) :: discards !! Discarded object
logical, dimension(:), intent(in) :: lspill_list !! Logical array of bodies to spill into the discards
logical, intent(in) :: ldestructive !! Logical flag indicating whether or not this operation should alter body by removing the discard list
logical, dimension(:), intent(in) :: lspill_list !! Logical array of bodies to spill into the discards
logical, intent(in) :: ldestructive !! Logical flag indicating whether or not this operation should alter body by removing the discard list
end subroutine encounter_util_spill_list

end interface
Expand Down
20 changes: 20 additions & 0 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1661,6 +1661,12 @@ module pure subroutine util_sort_index_i4b(arr,ind)
integer(I4B), dimension(:), allocatable, intent(inout) :: ind
end subroutine util_sort_index_i4b

module pure subroutine util_sort_index_i4b_I8Bind(arr,ind)
implicit none
integer(I4B), dimension(:), intent(in) :: arr
integer(I8B), dimension(:), allocatable, intent(inout) :: ind
end subroutine util_sort_index_i4b_I8Bind

module pure subroutine util_sort_sp(arr)
implicit none
real(SP), dimension(:), intent(inout) :: arr
Expand Down Expand Up @@ -1713,6 +1719,13 @@ module pure subroutine util_sort_rearrange_arr_I4B(arr, ind, n)
integer(I4B), intent(in) :: n !! Number of elements in arr and ind to rearrange
end subroutine util_sort_rearrange_arr_I4B

module pure subroutine util_sort_rearrange_arr_I4B_I8Bind(arr, ind, n)
implicit none
integer(I4B), dimension(:), allocatable, intent(inout) :: arr !! Destination array
integer(I8B), dimension(:), intent(in) :: ind !! Index to rearrange against
integer(I8B), intent(in) :: n !! Number of elements in arr and ind to rearrange
end subroutine util_sort_rearrange_arr_I4B_I8Bind

module subroutine util_sort_rearrange_arr_info(arr, ind, n)
implicit none
type(swiftest_particle_info), dimension(:), allocatable, intent(inout) :: arr !! Destination array
Expand All @@ -1726,6 +1739,13 @@ module pure subroutine util_sort_rearrange_arr_logical(arr, ind, n)
integer(I4B), dimension(:), intent(in) :: ind !! Index to rearrange against
integer(I4B), intent(in) :: n !! Number of elements in arr and ind to rearrange
end subroutine util_sort_rearrange_arr_logical

module pure subroutine util_sort_rearrange_arr_logical_I8Bind(arr, ind, n)
implicit none
logical, dimension(:), allocatable, intent(inout) :: arr !! Destination array
integer(I8B), dimension(:), intent(in) :: ind !! Index to rearrange against
integer(I8B), intent(in) :: n !! Number of elements in arr and ind to rearrange
end subroutine util_sort_rearrange_arr_logical_I8Bind
end interface util_sort_rearrange

interface
Expand Down
2 changes: 1 addition & 1 deletion src/modules/symba_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -427,7 +427,7 @@ end subroutine symba_setup_pl
module subroutine symba_setup_encounter_list(self,n)
implicit none
class(symba_encounter), intent(inout) :: self !! SyMBA pl-tp encounter structure
integer(I4B), intent(in) :: n !! Number of encounters to allocate space for
integer(I8B), intent(in) :: n !! Number of encounters to allocate space for
end subroutine symba_setup_encounter_list

module subroutine symba_setup_tp(self, n, param)
Expand Down
7 changes: 4 additions & 3 deletions src/rmvs/rmvs_encounter_check.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,8 @@ module function rmvs_encounter_check_tp(self, param, system, dt) result(lencount
! Result
logical :: lencounter !! Returns true if there is at least one close encounter
! Internals
integer(I4B) :: i, j, nenc
integer(I4B) :: i, j
integer(I8B) :: nenc
real(DP) :: xr, yr, zr, vxr, vyr, vzr
real(DP), dimension(system%pl%nbody) :: rcrit
logical :: lflag
Expand All @@ -37,9 +38,9 @@ module function rmvs_encounter_check_tp(self, param, system, dt) result(lencount
tp%plencP(1:ntp) = 0
call encounter_check_all_pltp(param, npl, ntp, pl%xbeg, pl%vbeg, tp%xh, tp%vh, pl%renc, dt, lvdotr, index1, index2, nenc)

lencounter = (nenc > 0)
lencounter = (nenc > 0_I8B)
if (lencounter) then
tp%plencP(index2(1:nenc)) = index1(1:nenc)
tp%plencP(index2(1_I8B:nenc)) = index1(1_I8B:nenc)
do j = 1, npl
pl%nenc(j) = count(tp%plencP(1:ntp) == j)
end do
Expand Down
13 changes: 7 additions & 6 deletions src/symba/symba_encounter_check.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,8 +17,8 @@ module function symba_encounter_check_pl(self, param, system, dt, irec) result(l
! Result
logical :: lany_encounter !! Returns true if there is at least one close encounter
! Internals
integer(I8B) :: k, nplplm, kenc
integer(I4B) :: i, j, nenc, npl, nplm, nplt
integer(I8B) :: k, nplplm, kenc, nenc
integer(I4B) :: i, j, npl, nplm, nplt
logical, dimension(:), allocatable :: lencounter, loc_lvdotr, lvdotr
integer(I4B), dimension(:), allocatable :: index1, index2
integer(I4B), dimension(:,:), allocatable :: k_plpl_enc
Expand All @@ -43,7 +43,7 @@ module function symba_encounter_check_pl(self, param, system, dt, irec) result(l
call encounter_check_all_plplm(param, nplm, nplt, pl%xh(:,1:nplm), pl%vh(:,1:nplm), pl%xh(:,nplm+1:npl), pl%vh(:,nplm+1:npl), pl%renc(1:nplm), pl%renc(nplm+1:npl), dt, lvdotr, index1, index2, nenc)
end if

lany_encounter = nenc > 0
lany_encounter = nenc > 0_I8B
if (lany_encounter) then
call plplenc_list%resize(nenc)
call move_alloc(lvdotr, plplenc_list%lvdotr)
Expand All @@ -52,7 +52,7 @@ module function symba_encounter_check_pl(self, param, system, dt, irec) result(l
end if

if (lany_encounter) then
do k = 1, nenc
do k = 1_I8B, nenc
i = plplenc_list%index1(k)
j = plplenc_list%index2(k)
plplenc_list%id1(k) = pl%id(i)
Expand Down Expand Up @@ -197,7 +197,8 @@ module function symba_encounter_check_tp(self, param, system, dt, irec) result(l
logical :: lany_encounter !! Returns true if there is at least one close encounter
! Internals
real(DP) :: r2crit, vdotr, r2, v2, tmin, r2min, term2
integer(I4B) :: i, j, k,nenc, plind, tpind
integer(I4B) :: i, j, plind, tpind
integer(I8B) :: k, nenc
real(DP), dimension(NDIM) :: xr, vr
real(DP) :: rshell_irec
logical, dimension(:), allocatable :: lvdotr
Expand All @@ -224,7 +225,7 @@ module function symba_encounter_check_tp(self, param, system, dt, irec) result(l
select type(pl)
class is (symba_pl)
pl%lencounter(1:npl) = .false.
do k = 1, nenc
do k = 1_I8B, nenc
plind = pltpenc_list%index1(k)
tpind = pltpenc_list%index2(k)
pl%lencounter(plind) = .true.
Expand Down
Loading

0 comments on commit 1b2a17f

Please sign in to comment.