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

Commit

Permalink
Revert "Updates to storage classes and methods"
Browse files Browse the repository at this point in the history
This reverts commit 552db80.
  • Loading branch information
daminton committed Dec 5, 2022
1 parent 552db80 commit 06c7726
Show file tree
Hide file tree
Showing 8 changed files with 31 additions and 112 deletions.
1 change: 0 additions & 1 deletion src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,6 @@ SET(FAST_MATH_FILES
${SRC}/util/util_minimize_bfgs.f90
${SRC}/util/util_peri.f90
${SRC}/util/util_rescale.f90
${SRC}/util/util_reset.f90
${SRC}/util/util_resize.f90
${SRC}/util/util_set.f90
${SRC}/util/util_solve.f90
Expand Down
23 changes: 5 additions & 18 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -544,13 +544,11 @@ module swiftest_classes

type :: swiftest_storage(nframes)
!! An class that establishes the pattern for various storage objects
integer(I4B), len :: nframes = 10 !! Total number of frames that can be stored
type(swiftest_storage_frame), dimension(nframes) :: frame !! Array of stored frames
integer(I4B) :: iframe = 0 !! The current frame number
integer(I4B), len :: nframes !! Total number of frames that can be stored
type(swiftest_storage_frame), dimension(nframes) :: frame !! Array of stored frames
integer(I4B) :: iframe = 0 !! The current frame number
contains
procedure :: dump => io_dump_storage !! Dumps storage object contents to file
procedure :: reset => util_reset_storage !! Resets a storage object by deallocating all items and resetting the frame counter to 0
procedure :: resize => util_resize_storage
procedure :: dump => io_dump_storage
end type swiftest_storage

abstract interface
Expand Down Expand Up @@ -1528,17 +1526,13 @@ module subroutine util_peri_tp(self, system, param)
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
end subroutine util_peri_tp


module subroutine util_rescale_system(self, param, mscale, dscale, tscale)
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest nbody system object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters. Returns with new values of the scale vactors and GU
real(DP), intent(in) :: mscale, dscale, tscale !! Scale factors for mass, distance, and time units, respectively.
end subroutine util_rescale_system

module subroutine util_reset_storage(self)
implicit none
class(swiftest_storage(*)), intent(inout) :: self !! Swiftest storage object
end subroutine util_reset_storage
end interface


Expand Down Expand Up @@ -1593,13 +1587,6 @@ module subroutine util_resize_pl(self, nnew)
integer(I4B), intent(in) :: nnew !! New size neded
end subroutine util_resize_pl

module subroutine util_resize_storage(self, nnew, new_storage)
implicit none
class(swiftest_storage(*)), intent(in) :: self !! Swiftest storage object
integer(I4B), intent(in) :: nnew !! New size of list needed
class(swiftest_storage(*)), allocatable, intent(out) :: new_storage
end subroutine util_resize_storage

module subroutine util_resize_tp(self, nnew)
implicit none
class(swiftest_tp), intent(inout) :: self !! Swiftest test particle object
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 @@ -208,7 +208,7 @@ module symba_classes
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
class(symba_encounter_storage(nframes=:)), allocatable :: encounter_history !! Stores encounter history for later retrieval and saving to file
type(symba_encounter_storage(nframes=:)), allocatable :: encounter_history !! Stores encounter history for later retrieval and saving to file
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
1 change: 0 additions & 1 deletion src/setup/setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,6 @@ module subroutine setup_construct_system(system, param)
allocate(symba_merger :: system%pl_discards)
allocate(symba_pltpenc :: system%pltpenc_list)
allocate(symba_plplenc :: system%plplenc_list)
allocate(symba_encounter_storage :: system%encounter_history)
allocate(symba_plplenc :: system%plplcollision_list)
end select
case (RINGMOONS)
Expand Down
5 changes: 3 additions & 2 deletions src/symba/symba_step.f90
Original file line number Diff line number Diff line change
Expand Up @@ -278,6 +278,7 @@ 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)
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 Expand Up @@ -312,8 +313,8 @@ module subroutine symba_step_reset_system(self, param)
tp%lfirst = param%lfirstkick
pl%lfirst = param%lfirstkick

call system%encounter_history%reset()

if (allocated(system%encounter_history)) deallocate(system%encounter_history)
allocate(symba_encounter_storage(8) :: system%encounter_history)
end associate
end select
end select
Expand Down
35 changes: 22 additions & 13 deletions src/symba/symba_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -918,22 +918,34 @@ module subroutine symba_util_resize_storage(self, nnew)
class(symba_nbody_system), intent(inout) :: self !! Swiftest encounter list
integer(I4B), intent(in) :: nnew !! New size of list needed
! Internals
class(swiftest_storage), allocatable :: tmp

if (nnew > self%encounter_history%nframes) then
call self%encounter_history%resize(nnew,tmp)
deallocate(self%encounter_history)
select type(tmp)
class is (symba_encounter_storage(*))
allocate(self%encounter_history, source=tmp)
end select
deallocate(tmp)
type(symba_encounter_storage(nframes=:)), allocatable :: tmp
integer(I4B) :: i, nold
logical :: lmalloc


lmalloc = allocated(self%encounter_history)
if (lmalloc) then
nold = self%encounter_history%nframes
else
nold = 0
end if

if (nnew > nold) then
allocate(symba_encounter_storage(8 * nnew) :: tmp)
if (lmalloc) then
do i = 1, nold
if (allocated(self%encounter_history%frame(i)%item)) tmp%frame(i) = self%encounter_history%frame(i)%item
end do
deallocate(self%encounter_history)
end if
call move_alloc(tmp,self%encounter_history)
end if

return
end subroutine symba_util_resize_storage



module subroutine symba_util_resize_tp(self, nnew)
!! author: David A. Minton
!!
Expand Down Expand Up @@ -1311,8 +1323,6 @@ module subroutine symba_util_take_encounter_snapshot(self, param, t)
if (npl > 0) allocate(symba_pl :: snapshot%pl)
if (ntp > 0) allocate(symba_tp :: snapshot%tp)
if (npl + ntp == 0) return
npl_snap = npl
ntp_snap = ntp

select type (pl => self%pl)
class is (symba_pl)
Expand Down Expand Up @@ -1374,7 +1384,6 @@ module subroutine symba_util_take_encounter_snapshot(self, param, t)

! Save the snapshot
self%encounter_history%iframe = self%encounter_history%iframe + 1
call self%resize_storage(self%encounter_history%iframe)
self%encounter_history%frame(self%encounter_history%iframe) = snapshot
end select
end select
Expand Down
32 changes: 0 additions & 32 deletions src/util/util_reset.f90

This file was deleted.

44 changes: 0 additions & 44 deletions src/util/util_resize.f90
Original file line number Diff line number Diff line change
Expand Up @@ -350,50 +350,6 @@ module subroutine util_resize_pl(self, nnew)
end subroutine util_resize_pl


module subroutine util_resize_storage(self, nnew, new_storage)
!! author: David A. Minton
!!
!! Checks the current size of the encounter storage against the required size and extends it by a factor of 2 more than requested if it is too small.
!! Note: The reason to extend it by a factor of 2 is for performance. When there are many enounters per step, resizing every time you want to add an
!! encounter takes significant computational effort. Resizing by a factor of 2 is a tradeoff between performance (fewer resize calls) and memory managment
!! Memory usage grows by a factor of 2 each time it fills up, but no more.
implicit none
! Arguments
class(swiftest_storage(*)), intent(in) :: self !! Swiftest storage_object
integer(I4B), intent(in) :: nnew !! New size of list needed
class(swiftest_storage), allocatable, intent(out) :: new_storage !! New, resized storage
! Internals
!type(symba_encounter_storage(nframes=:)), allocatable :: tmp
integer(I4B) :: i, nold, iframe_old, nbig

nold = self%nframes
iframe_old = self%iframe

if (nnew > nold) then
nbig = nold
do while (nbig < nnew)
nbig = 2*nbig
end do
select type(self)
class is (symba_encounter_storage(*))
allocate(symba_encounter_storage(nbig) :: new_storage)
class is (swiftest_storage(*))
allocate(swiftest_storage(nbig) :: new_storage)
end select
do i = 1, nold
if (allocated(self%frame(i)%item)) new_storage%frame(i) = self%frame(i)%item
end do
else
allocate(new_storage, source=self)
end if

new_storage%iframe = iframe_old
return
end subroutine util_resize_storage




module subroutine util_resize_tp(self, nnew)
!! author: David A. Minton
!!
Expand Down

0 comments on commit 06c7726

Please sign in to comment.