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

Commit

Permalink
Added mass, radius, and name variables to encounter list. Also added …
Browse files Browse the repository at this point in the history
…collision time to SyMBAs version of the list. Added methods needed for basic operations on the lists
  • Loading branch information
daminton committed Dec 2, 2022
1 parent 538310c commit 813c736
Show file tree
Hide file tree
Showing 9 changed files with 117 additions and 35 deletions.
26 changes: 23 additions & 3 deletions src/encounter/encounter_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,8 @@ module subroutine encounter_setup_list(self, n)
! Arguments
class(encounter_list), intent(inout) :: self !! Swiftest encounter structure
integer(I8B), intent(in) :: n !! Number of encounters to allocate space for
! Internals
integer(I8B) :: i

if (n < 0) return

Expand All @@ -75,10 +77,16 @@ module subroutine encounter_setup_list(self, n)
if (allocated(self%x2)) deallocate(self%x2)
if (allocated(self%v1)) deallocate(self%v1)
if (allocated(self%v2)) deallocate(self%v2)
if (allocated(self%t)) deallocate(self%t)
if (allocated(self%Gmass1)) deallocate(self%Gmass1)
if (allocated(self%Gmass2)) deallocate(self%Gmass2)
if (allocated(self%radius1)) deallocate(self%radius1)
if (allocated(self%radius2)) deallocate(self%radius2)
if (allocated(self%name1)) deallocate(self%name1)
if (allocated(self%name2)) deallocate(self%name2)

self%nenc = n
if (n == 0_I8B) return
self%t = 0.0_DP

allocate(self%lvdotr(n))
allocate(self%status(n))
Expand All @@ -90,7 +98,12 @@ module subroutine encounter_setup_list(self, n)
allocate(self%x2(NDIM,n))
allocate(self%v1(NDIM,n))
allocate(self%v2(NDIM,n))
allocate(self%t(n))
allocate(self%Gmass1(n))
allocate(self%Gmass2(n))
allocate(self%radius1(n))
allocate(self%radius2(n))
allocate(self%name1(n))
allocate(self%name2(n))

self%lvdotr(:) = .false.
self%status(:) = INACTIVE
Expand All @@ -102,7 +115,14 @@ module subroutine encounter_setup_list(self, n)
self%x2(:,:) = 0.0_DP
self%v1(:,:) = 0.0_DP
self%v2(:,:) = 0.0_DP
self%t(:) = 0.0_DP
self%Gmass1(:) = 0.0_DP
self%Gmass2(:) = 0.0_DP
self%radius1(:) = 0.0_DP
self%radius2(:) = 0.0_DP
do i = 1_I8B, n
self%name1(i) = "UNNAMED"
self%name2(i) = "UNNAMED"
end do

return
end subroutine encounter_setup_list
Expand Down
30 changes: 26 additions & 4 deletions src/encounter/encounter_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,12 @@ module subroutine encounter_util_append_list(self, source, lsource_mask)
call util_append(self%x2, source%x2, nold, nsrc, lsource_mask)
call util_append(self%v1, source%v1, nold, nsrc, lsource_mask)
call util_append(self%v2, source%v2, nold, nsrc, lsource_mask)
call util_append(self%t, source%t, nold, nsrc, lsource_mask)
call util_append(self%Gmass1, source%Gmass1, nold, nsrc, lsource_mask)
call util_append(self%Gmass2, source%Gmass2, nold, nsrc, lsource_mask)
call util_append(self%radius1, source%radius1, nold, nsrc, lsource_mask)
call util_append(self%radius2, source%radius2, nold, nsrc, lsource_mask)
call util_append(self%name1, source%name1, nold, nsrc, lsource_mask)
call util_append(self%name2, source%name2, nold, nsrc, lsource_mask)
self%nenc = nold + count(lsource_mask(1:nsrc))

return
Expand All @@ -54,6 +59,7 @@ module subroutine encounter_util_copy_list(self, source)

associate(n => source%nenc)
self%nenc = n
self%t = source%t
self%lvdotr(1:n) = source%lvdotr(1:n)
self%status(1:n) = source%status(1:n)
self%index1(1:n) = source%index1(1:n)
Expand All @@ -64,7 +70,12 @@ module subroutine encounter_util_copy_list(self, source)
self%x2(:,1:n) = source%x2(:,1:n)
self%v1(:,1:n) = source%v1(:,1:n)
self%v2(:,1:n) = source%v2(:,1:n)
self%t(1:n) = source%t(1:n)
self%Gmass1(1:n) = source%Gmass1(1:n)
self%Gmass2(1:n) = source%Gmass2(1:n)
self%radius1(1:n) = source%radius1(1:n)
self%radius2(1:n) = source%radius2(1:n)
self%name1(1:n) = source%name1(1:n)
self%name2(1:n) = source%name2(1:n)
end associate

return
Expand Down Expand Up @@ -104,7 +115,12 @@ module subroutine encounter_util_dealloc_list(self)
if (allocated(self%x2)) deallocate(self%x2)
if (allocated(self%v1)) deallocate(self%v1)
if (allocated(self%v2)) deallocate(self%v2)
if (allocated(self%t)) deallocate(self%t)
if (allocated(self%Gmass1)) deallocate(self%Gmass1)
if (allocated(self%Gmass2)) deallocate(self%Gmass2)
if (allocated(self%radius1)) deallocate(self%radius1)
if (allocated(self%radius2)) deallocate(self%radius2)
if (allocated(self%name1)) deallocate(self%name1)
if (allocated(self%name2)) deallocate(self%name2)

return
end subroutine encounter_util_dealloc_list
Expand Down Expand Up @@ -214,6 +230,7 @@ module subroutine encounter_util_resize_storage(self, nnew)
return
end subroutine encounter_util_resize_storage


module subroutine encounter_util_spill_list(self, discards, lspill_list, ldestructive)
!! author: David A. Minton
!!
Expand All @@ -238,7 +255,12 @@ module subroutine encounter_util_spill_list(self, discards, lspill_list, ldestru
call util_spill(keeps%x2, discards%x2, lspill_list, ldestructive)
call util_spill(keeps%v1, discards%v1, lspill_list, ldestructive)
call util_spill(keeps%v2, discards%v2, lspill_list, ldestructive)
call util_spill(keeps%t, discards%t, lspill_list, ldestructive)
call util_spill(keeps%Gmass1, discards%Gmass1, lspill_list, ldestructive)
call util_spill(keeps%Gmass2, discards%Gmass2, lspill_list, ldestructive)
call util_spill(keeps%radius1, discards%radius1, lspill_list, ldestructive)
call util_spill(keeps%radius2, discards%radius2, lspill_list, ldestructive)
call util_spill(keeps%name1, discards%name1, lspill_list, ldestructive)
call util_spill(keeps%name2, discards%name2, lspill_list, ldestructive)

nenc_old = keeps%nenc

Expand Down
30 changes: 18 additions & 12 deletions src/modules/encounter_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,18 +19,24 @@ module encounter_classes
integer(I4B), parameter :: SWEEPDIM = 3

type :: encounter_list
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
integer(I4B), dimension(:), allocatable :: index2 !! position of the second body in the encounter
integer(I4B), dimension(:), allocatable :: id1 !! id of the first body in the encounter
integer(I4B), dimension(:), allocatable :: id2 !! id of the second body in the encounter
real(DP), dimension(:,:), allocatable :: x1 !! the position of body 1 in the encounter
real(DP), dimension(:,:), allocatable :: x2 !! the position of body 2 in the encounter
real(DP), dimension(:,:), allocatable :: v1 !! the velocity of body 1 in the encounter
real(DP), dimension(:,:), allocatable :: v2 !! the velocity of body 2 in the encounter
real(DP), dimension(:), allocatable :: t !! Time of encounter
integer(I8B) :: nenc = 0 !! Total number of encounters
real(DP) :: t !! Time of encounter
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
integer(I4B), dimension(:), allocatable :: index2 !! position of the second body in the encounter
integer(I4B), dimension(:), allocatable :: id1 !! id of the first body in the encounter
integer(I4B), dimension(:), allocatable :: id2 !! id of the second body in the encounter
real(DP), dimension(:,:), allocatable :: x1 !! the position of body 1 in the encounter
real(DP), dimension(:,:), allocatable :: x2 !! the position of body 2 in the encounter
real(DP), dimension(:,:), allocatable :: v1 !! the velocity of body 1 in the encounter
real(DP), dimension(:,:), allocatable :: v2 !! the velocity of body 2 in the encounter
real(DP), dimension(:), allocatable :: Gmass1 !! G*mass of body 1 in the encounter
real(DP), dimension(:), allocatable :: Gmass2 !! G*mass of body 2 in the encounter
real(DP), dimension(:), allocatable :: radius1 !! radius of body 1 in the encounter
real(DP), dimension(:), allocatable :: radius2 !! radius of body 2 in the encounter
character(NAMELEN), dimension(:), allocatable :: name1 !! name body 1 in the encounter
character(NAMELEN), dimension(:), allocatable :: name2 !! name of body 2 in the encounter
contains
procedure :: setup => encounter_setup_list !! A constructor that sets the number of encounters and allocates and initializes all arrays
procedure :: append => encounter_util_append_list !! Appends elements from one structure to another
Expand Down
17 changes: 9 additions & 8 deletions src/modules/symba_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,8 @@ module symba_classes
!*******************************************************************************************************************************
!> SyMBA class for tracking close encounters in a step
type, extends(encounter_list) :: symba_encounter
integer(I4B), dimension(:), allocatable :: level !! encounter recursion level
integer(I4B), dimension(:), allocatable :: level !! encounter recursion level
real(DP), dimension(:), allocatable :: tcollision !! Time of collision
contains
procedure :: collision_check => symba_collision_check_encounter !! Checks if a test particle is going to collide with a massive body
procedure :: encounter_check => symba_encounter_check !! Checks if massive bodies are going through close encounters with each other
Expand Down Expand Up @@ -180,13 +181,13 @@ module symba_classes
! symba_nbody_system class definitions and method interfaces
!********************************************************************************************************************************
type, extends(helio_nbody_system) :: symba_nbody_system
class(symba_merger), allocatable :: pl_adds !! List of added bodies in mergers or collisions
class(symba_pltpenc), allocatable :: pltpenc_list !! List of massive body-test particle encounters in a single step
class(symba_plplenc), allocatable :: plplenc_list !! List of massive body-massive body encounters in a single step
class(symba_plplenc), allocatable :: plplcollision_list !! List of massive body-massive body collisions in a single step
integer(I4B) :: irec !! System recursion level
type(encounter_storage(nframes=:)), allocatable :: encounter_history
integer(I4B) :: iframe = 0 !! Encounter history frame number
class(symba_merger), allocatable :: pl_adds !! List of added bodies in mergers or collisions
class(symba_pltpenc), allocatable :: pltpenc_list !! List of massive body-test particle encounters in a single step
class(symba_plplenc), allocatable :: plplenc_list !! List of massive body-massive body encounters in a single step
class(symba_plplenc), allocatable :: plplcollision_list !! List of massive body-massive body collisions in a single step
integer(I4B) :: irec !! System recursion level
type(encounter_storage(nframes=:)), allocatable :: encounter_history !! Stores encounter history for later retrieval and saving to file
integer(I4B) :: ienc_frame = 0 !! Encounter history frame number
contains
procedure :: write_discard => symba_io_write_discard !! Write out information about discarded and merged planets and test particles in SyMBA
procedure :: initialize => symba_setup_initialize_system !! Performs SyMBA-specific initilization steps
Expand Down
2 changes: 1 addition & 1 deletion src/symba/symba_collision.f90
Original file line number Diff line number Diff line change
Expand Up @@ -339,7 +339,7 @@ module function symba_collision_check_encounter(self, system, param, t, dt, irec
i = self%index1(k)
j = self%index2(k)
if (lcollision(k)) self%status(k) = COLLISION
self%t(k) = t
self%tcollision(k) = t
self%x1(:,k) = pl%xh(:,i) + system%cb%xb(:)
self%v1(:,k) = pl%vb(:,i)
if (isplpl) then
Expand Down
15 changes: 12 additions & 3 deletions src/symba/symba_encounter_check.f90
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ module function symba_encounter_check_pl(self, param, system, dt, irec) result(l
lany_encounter = .false.
if (self%nbody == 0) return

associate(pl => self, plplenc_list => system%plplenc_list, cb => system%cb, iframe => system%iframe, encounter_history => system%encounter_history)
associate(pl => self, plplenc_list => system%plplenc_list, cb => system%cb, ienc_frame => system%ienc_frame, encounter_history => system%encounter_history)

npl = pl%nbody
nplm = pl%nplm
Expand Down Expand Up @@ -69,6 +69,15 @@ module function symba_encounter_check_pl(self, param, system, dt, irec) result(l
plplenc_list%x2(:,k) = pl%xh(:,j)
plplenc_list%v1(:,k) = pl%vb(:,i) - cb%vb(:)
plplenc_list%v2(:,k) = pl%vb(:,j) - cb%vb(:)
plplenc_list%Gmass1(k) = pl%Gmass(i)
plplenc_list%Gmass2(k) = pl%Gmass(j)
if (param%lclose) then
plplenc_list%radius1(k) = pl%radius(i)
plplenc_list%radius2(k) = pl%radius(j)
end if
plplenc_list%name1(k) = pl%info(i)%name
plplenc_list%name2(k) = pl%info(j)%name

pl%lencounter(i) = .true.
pl%lencounter(j) = .true.
pl%levelg(i) = irec
Expand All @@ -78,8 +87,8 @@ module function symba_encounter_check_pl(self, param, system, dt, irec) result(l
pl%nplenc(i) = pl%nplenc(i) + 1
pl%nplenc(j) = pl%nplenc(j) + 1
end do
iframe = iframe + 1
encounter_history%frame(iframe) = plplenc_list
ienc_frame = ienc_frame + 1
encounter_history%frame(ienc_frame) = plplenc_list
end if

end associate
Expand Down
3 changes: 3 additions & 0 deletions src/symba/symba_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -120,9 +120,12 @@ module subroutine symba_setup_encounter_list(self, n)
if (n <= 0_I8B) return

if (allocated(self%level)) deallocate(self%level)
if (allocated(self%tcollision)) deallocate(self%tcollision)
allocate(self%level(n))
allocate(self%tcollision(n))

self%level(:) = -1
self%tcollision(:) = 0.0_DP

return
end subroutine symba_setup_encounter_list
Expand Down
3 changes: 2 additions & 1 deletion src/symba/symba_step.f90
Original file line number Diff line number Diff line change
Expand Up @@ -275,7 +275,8 @@ module subroutine symba_step_reset_system(self, param)
nenc_old = system%plplenc_list%nenc
call system%plplenc_list%setup(0_I8B)
call system%plplcollision_list%setup(0_I8B)
system%iframe = 0
system%ienc_frame = 0
if (allocated(system%encounter_history)) deallocate(system%encounter_history)
if (npl > 0) then
pl%lcollision(1:npl) = .false.
call pl%reset_kinship([(i, i=1, npl)])
Expand Down
Loading

0 comments on commit 813c736

Please sign in to comment.