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

Commit

Permalink
Unified the variable names between integrators by refactoring mergesu…
Browse files Browse the repository at this point in the history
…b_list to pl_discards (and mergeadd_list to pl_adds for consistency). Fixed some issues related to identifying collisions.
  • Loading branch information
daminton committed Aug 6, 2021
1 parent 1869147 commit ac34918
Show file tree
Hide file tree
Showing 13 changed files with 541 additions and 533 deletions.
4 changes: 2 additions & 2 deletions docs/src/setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -54,8 +54,8 @@ module subroutine setup_construct_system(system, param)
allocate(symba_pl :: system%pl)
allocate(symba_tp :: system%tp)
allocate(symba_tp :: system%tp_discards)
allocate(symba_merger :: system%mergeadd_list)
allocate(symba_merger :: system%mergesub_list)
allocate(symba_merger :: system%pl_adds)
allocate(symba_merger :: system%pl_discards)
allocate(symba_plplenc :: system%plplenc_list)
allocate(symba_pltpenc :: system%pltpenc_list)
end select
Expand Down
4 changes: 2 additions & 2 deletions docs/src/symba_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -160,8 +160,8 @@ module symba_classes
! symba_nbody_system class definitions and method interfaces
!********************************************************************************************************************************
type, extends(helio_nbody_system) :: symba_nbody_system
class(symba_merger), allocatable :: mergeadd_list !! List of added bodies in mergers or collisions
class(symba_merger), allocatable :: mergesub_list !! List of subtracted bodies in mergers or collisions
class(symba_merger), allocatable :: pl_adds !! List of added bodies in mergers or collisions
class(symba_merger), allocatable :: pl_discards !! List of subtracted 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
integer(I4B) :: irec !! System recursion level
Expand Down
72 changes: 36 additions & 36 deletions docs/src/symba_fragmentation.f90
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ module function symba_fragmentation_casedisruption(system, param, family, x, v,

select type(pl => system%pl)
class is (symba_pl)
associate(mergeadd_list => system%mergeadd_list, mergesub_list => system%mergesub_list, cb => system%cb)
associate(pl_adds => system%pl_adds, pl_discards => system%pl_discards, cb => system%cb)
! Collisional fragments will be uniformly distributed around the pre-impact barycenter
nfrag = NFRAG_DISRUPT
allocate(m_frag(nfrag))
Expand Down Expand Up @@ -91,11 +91,11 @@ module function symba_fragmentation_casedisruption(system, param, family, x, v,
lmask(:) = .false.
lmask(family(:)) = .true.
pl%status(family(:)) = MERGED
nstart = mergesub_list%nbody + 1
nend = mergesub_list%nbody + nfamily
call mergesub_list%append(pl, lmask)
nstart = pl_discards%nbody + 1
nend = pl_discards%nbody + nfamily
call pl_discards%append(pl, lmask)
! Record how many bodies were subtracted in this event
mergesub_list%ncomp(nstart:nend) = nfamily
pl_discards%ncomp(nstart:nend) = nfamily

allocate(plnew, mold=pl)
call plnew%setup(nfrag, param)
Expand Down Expand Up @@ -133,10 +133,10 @@ module function symba_fragmentation_casedisruption(system, param, family, x, v,
end if

! Append the new merged body to the list and record how many we made
nstart = mergeadd_list%nbody + 1
nend = mergeadd_list%nbody + plnew%nbody
call mergeadd_list%append(plnew)
mergeadd_list%ncomp(nstart:nend) = plnew%nbody
nstart = pl_adds%nbody + 1
nend = pl_adds%nbody + plnew%nbody
call pl_adds%append(plnew)
pl_adds%ncomp(nstart:nend) = plnew%nbody

call plnew%setup(0, param)
deallocate(plnew)
Expand Down Expand Up @@ -179,7 +179,7 @@ module function symba_fragmentation_casehitandrun(system, param, family, x, v, m

select type(pl => system%pl)
class is (symba_pl)
associate(mergeadd_list => system%mergeadd_list, mergesub_list => system%mergesub_list, cb => system%cb)
associate(pl_adds => system%pl_adds, pl_discards => system%pl_discards, cb => system%cb)
mtot = sum(mass(:))
xcom(:) = (mass(1) * x(:,1) + mass(2) * x(:,2)) / mtot
vcom(:) = (mass(1) * v(:,1) + mass(2) * v(:,2)) / mtot
Expand Down Expand Up @@ -247,11 +247,11 @@ module function symba_fragmentation_casehitandrun(system, param, family, x, v, m
lmask(:) = .false.
lmask(family(:)) = .true.
pl%status(family(:)) = MERGED
nstart = mergesub_list%nbody + 1
nend = mergesub_list%nbody + nfamily
call mergesub_list%append(pl, lmask)
nstart = pl_discards%nbody + 1
nend = pl_discards%nbody + nfamily
call pl_discards%append(pl, lmask)
! Record how many bodies were subtracted in this event
mergesub_list%ncomp(nstart:nend) = nfamily
pl_discards%ncomp(nstart:nend) = nfamily

allocate(plnew, mold=pl)
call plnew%setup(nfrag, param)
Expand Down Expand Up @@ -289,10 +289,10 @@ module function symba_fragmentation_casehitandrun(system, param, family, x, v, m
end if

! Append the new merged body to the list and record how many we made
nstart = mergeadd_list%nbody + 1
nend = mergeadd_list%nbody + plnew%nbody
call mergeadd_list%append(plnew)
mergeadd_list%ncomp(nstart:nend) = plnew%nbody
nstart = pl_adds%nbody + 1
nend = pl_adds%nbody + plnew%nbody
call pl_adds%append(plnew)
pl_adds%ncomp(nstart:nend) = plnew%nbody

call plnew%setup(0, param)
deallocate(plnew)
Expand Down Expand Up @@ -334,7 +334,7 @@ module function symba_fragmentation_casemerge(system, param, family, x, v, mass,

select type(pl => system%pl)
class is (symba_pl)
associate(mergeadd_list => system%mergeadd_list, mergesub_list => system%mergesub_list, cb => system%cb)
associate(pl_adds => system%pl_adds, pl_discards => system%pl_discards, cb => system%cb)
status = MERGED
write(*, '("Merging bodies ",99(I8,",",:))') pl%id(family(:))
mass_new = sum(mass(:))
Expand Down Expand Up @@ -386,11 +386,11 @@ module function symba_fragmentation_casemerge(system, param, family, x, v, mass,
lmask(:) = .false.
lmask(family(:)) = .true.
pl%status(family(:)) = MERGED
nstart = mergesub_list%nbody + 1
nend = mergesub_list%nbody + nfamily
call mergesub_list%append(pl, lmask)
nstart = pl_discards%nbody + 1
nend = pl_discards%nbody + nfamily
call pl_discards%append(pl, lmask)
! Record how many bodies were subtracted in this event
mergesub_list%ncomp(nstart:nend) = nfamily
pl_discards%ncomp(nstart:nend) = nfamily

! Create the new merged body
allocate(plnew, mold=pl)
Expand Down Expand Up @@ -422,10 +422,10 @@ module function symba_fragmentation_casemerge(system, param, family, x, v, mass,
end if

! Append the new merged body to the list and record how many we made
nstart = mergeadd_list%nbody + 1
nend = mergeadd_list%nbody + plnew%nbody
call mergeadd_list%append(plnew)
mergeadd_list%ncomp(nstart:nend) = plnew%nbody
nstart = pl_adds%nbody + 1
nend = pl_adds%nbody + plnew%nbody
call pl_adds%append(plnew)
pl_adds%ncomp(nstart:nend) = plnew%nbody

call plnew%setup(0, param)
deallocate(plnew)
Expand Down Expand Up @@ -468,7 +468,7 @@ module function symba_fragmentation_casesupercatastrophic(system, param, family,

select type(pl => system%pl)
class is (symba_pl)
associate(mergeadd_list => system%mergeadd_list, mergesub_list => system%mergesub_list, cb => system%cb)
associate(pl_adds => system%pl_adds, pl_discards => system%pl_discards, cb => system%cb)
! Collisional fragments will be uniformly distributed around the pre-impact barycenter
nfrag = NFRAG_SUPERCAT
allocate(m_frag(nfrag))
Expand Down Expand Up @@ -521,11 +521,11 @@ module function symba_fragmentation_casesupercatastrophic(system, param, family,
lmask(:) = .false.
lmask(family(:)) = .true.
pl%status(family(:)) = MERGED
nstart = mergesub_list%nbody + 1
nend = mergesub_list%nbody + nfamily
call mergesub_list%append(pl, lmask)
nstart = pl_discards%nbody + 1
nend = pl_discards%nbody + nfamily
call pl_discards%append(pl, lmask)
! Record how many bodies were subtracted in this event
mergesub_list%ncomp(nstart:nend) = nfamily
pl_discards%ncomp(nstart:nend) = nfamily

allocate(plnew, mold=pl)
call plnew%setup(nfrag, param)
Expand Down Expand Up @@ -563,10 +563,10 @@ module function symba_fragmentation_casesupercatastrophic(system, param, family,
end if

! Append the new merged body to the list and record how many we made
nstart = mergeadd_list%nbody + 1
nend = mergeadd_list%nbody + plnew%nbody
call mergeadd_list%append(plnew)
mergeadd_list%ncomp(nstart:nend) = plnew%nbody
nstart = pl_adds%nbody + 1
nend = pl_adds%nbody + plnew%nbody
call pl_adds%append(plnew)
pl_adds%ncomp(nstart:nend) = plnew%nbody

call plnew%setup(0, param)
deallocate(plnew)
Expand Down
32 changes: 16 additions & 16 deletions docs/src/symba_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -225,10 +225,10 @@ module subroutine symba_io_write_discard(self, param)
character(*), parameter :: PLNAMEFMT = '(I8, 2(1X, E23.16))'
class(swiftest_body), allocatable :: pltemp

associate(pl => self%pl, npl => self%pl%nbody, mergesub_list => self%mergesub_list, mergeadd_list => self%mergeadd_list)
associate(pl => self%pl, npl => self%pl%nbody, pl_discards => self%pl_discards, pl_adds => self%pl_adds)
if (self%tp_discards%nbody > 0) call io_write_discard(self, param)

if (mergesub_list%nbody == 0) return
if (pl_discards%nbody == 0) return
select case(param%out_stat)
case('APPEND')
open(unit = LUN, file = param%discard_out, status = 'OLD', position = 'APPEND', form = 'FORMATTED', iostat = ierr)
Expand All @@ -240,31 +240,31 @@ module subroutine symba_io_write_discard(self, param)
end select
lfirst = .false.
if (param%lgr) then
call mergesub_list%pv2v(param)
call mergeadd_list%pv2v(param)
call pl_discards%pv2v(param)
call pl_adds%pv2v(param)
end if

write(LUN, HDRFMT) param%t, mergesub_list%nbody, param%lbig_discard
write(LUN, HDRFMT) param%t, pl_discards%nbody, param%lbig_discard
iadd = 1
isub = 1
do while (iadd <= mergeadd_list%nbody)
nadd = mergeadd_list%ncomp(iadd)
nsub = mergesub_list%ncomp(isub)
do while (iadd <= pl_adds%nbody)
nadd = pl_adds%ncomp(iadd)
nsub = pl_discards%ncomp(isub)
do j = 1, nadd
if (iadd <= mergeadd_list%nbody) then
write(LUN, NAMEFMT) ADD, mergesub_list%id(iadd), mergesub_list%status(iadd)
write(LUN, VECFMT) mergeadd_list%xh(1, iadd), mergeadd_list%xh(2, iadd), mergeadd_list%xh(3, iadd)
write(LUN, VECFMT) mergeadd_list%vh(1, iadd), mergeadd_list%vh(2, iadd), mergeadd_list%vh(3, iadd)
if (iadd <= pl_adds%nbody) then
write(LUN, NAMEFMT) ADD, pl_discards%id(iadd), pl_discards%status(iadd)
write(LUN, VECFMT) pl_adds%xh(1, iadd), pl_adds%xh(2, iadd), pl_adds%xh(3, iadd)
write(LUN, VECFMT) pl_adds%vh(1, iadd), pl_adds%vh(2, iadd), pl_adds%vh(3, iadd)
else
exit
end if
iadd = iadd + 1
end do
do j = 1, nsub
if (isub <= mergesub_list%nbody) then
write(LUN, NAMEFMT) SUB, mergesub_list%id(isub), mergesub_list%status(isub)
write(LUN, VECFMT) mergesub_list%xh(1, isub), mergesub_list%xh(2, isub), mergesub_list%xh(3, isub)
write(LUN, VECFMT) mergesub_list%vh(1, isub), mergesub_list%vh(2, isub), mergesub_list%vh(3, isub)
if (isub <= pl_discards%nbody) then
write(LUN, NAMEFMT) SUB, pl_discards%id(isub), pl_discards%status(isub)
write(LUN, VECFMT) pl_discards%xh(1, isub), pl_discards%xh(2, isub), pl_discards%xh(3, isub)
write(LUN, VECFMT) pl_discards%vh(1, isub), pl_discards%vh(2, isub), pl_discards%vh(3, isub)
else
exit
end if
Expand Down
6 changes: 3 additions & 3 deletions docs/src/symba_step.f90
Original file line number Diff line number Diff line change
Expand Up @@ -237,7 +237,7 @@ module subroutine symba_step_reset_system(self)
! Internals
integer(I4B) :: i

associate(system => self, pltpenc_list => self%pltpenc_list, plplenc_list => self%plplenc_list, mergeadd_list => self%mergeadd_list, mergesub_list => self%mergesub_list)
associate(system => self, pltpenc_list => self%pltpenc_list, plplenc_list => self%plplenc_list, pl_adds => self%pl_adds, pl_discards => self%pl_discards)
select type(pl => system%pl)
class is (symba_pl)
select type(tp => system%tp)
Expand Down Expand Up @@ -265,8 +265,8 @@ module subroutine symba_step_reset_system(self)
pltpenc_list%nenc = 0
end if

call mergeadd_list%resize(0)
call mergesub_list%resize(0)
call pl_adds%resize(0)
call pl_discards%resize(0)
end select
end select
end associate
Expand Down
6 changes: 3 additions & 3 deletions docs/src/symba_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -381,13 +381,13 @@ module subroutine symba_util_rearray_pl(self, system, param)
! Internals
class(symba_pl), allocatable :: pl_discards !! The discarded body list.

associate(pl => self, mergeadd_list => system%mergeadd_list)
associate(pl => self, pl_adds => system%pl_adds)
allocate(pl_discards, mold=pl)
! Remove the discards
call pl%spill(pl_discards, lspill_list=(pl%ldiscard(:) .or. pl%status(:) == INACTIVE), ldestructive=.true.)

! Add in any new bodies
call pl%append(mergeadd_list)
call pl%append(pl_adds)

! If there are still bodies in the system, sort by mass in descending order and re-index
if (pl%nbody > 0) then
Expand All @@ -397,7 +397,7 @@ module subroutine symba_util_rearray_pl(self, system, param)
call pl%eucl_index()
end if

! Destroy the discarded body list, since we already have what we need in the mergesub_list
! Destroy the discarded body list, since we already have what we need in the pl_discards
call pl_discards%setup(0,param)
deallocate(pl_discards)
end associate
Expand Down
3 changes: 1 addition & 2 deletions examples/symba_energy_momentum/param.disruption_off_axis.in
Original file line number Diff line number Diff line change
Expand Up @@ -17,9 +17,8 @@ CHK_RMIN 0.005
CHK_RMAX 1e6
CHK_EJECT -1.0 ! ignore this check
CHK_QMIN -1.0 ! ignore this check
!CHK_QMIN_COORD HELIO ! commented out here
!CHK_QMIN_RANGE 1.0 1000.0 ! commented out here
ENC_OUT enc.disruption_off_axis.dat
DISCARD_OUT discard.disruption_off_axis.out
EXTRA_FORCE no ! no extra user-defined forces
BIG_DISCARD no ! output all planets if anything discarded
RHILL_PRESENT yes ! Hill's sphere radii in input file
Expand Down
3 changes: 1 addition & 2 deletions src/modules/symba_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -160,8 +160,7 @@ module symba_classes
! symba_nbody_system class definitions and method interfaces
!********************************************************************************************************************************
type, extends(helio_nbody_system) :: symba_nbody_system
class(symba_merger), allocatable :: mergeadd_list !! List of added bodies in mergers or collisions
class(symba_merger), allocatable :: mergesub_list !! List of subtracted bodies in mergers or collisions
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
integer(I4B) :: irec !! System recursion level
Expand Down
4 changes: 2 additions & 2 deletions src/setup/setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -54,8 +54,8 @@ module subroutine setup_construct_system(system, param)
allocate(symba_pl :: system%pl)
allocate(symba_tp :: system%tp)
allocate(symba_tp :: system%tp_discards)
allocate(symba_merger :: system%mergeadd_list)
allocate(symba_merger :: system%mergesub_list)
allocate(symba_merger :: system%pl_adds)
allocate(symba_merger :: system%pl_discards)
allocate(symba_plplenc :: system%plplenc_list)
allocate(symba_pltpenc :: system%pltpenc_list)
end select
Expand Down
Loading

0 comments on commit ac34918

Please sign in to comment.