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

Commit

Permalink
Pulled the system_history object out of param and into swiftest_nbody…
Browse files Browse the repository at this point in the history
…_system where it belongs. Now that the system history snapshots are more carefully curated, this shouldn't cause any memory issues
  • Loading branch information
daminton committed Jan 9, 2023
1 parent 328cda7 commit fcac2d7
Show file tree
Hide file tree
Showing 6 changed files with 35 additions and 90 deletions.
4 changes: 0 additions & 4 deletions src/encounter/encounter_check.f90
Original file line number Diff line number Diff line change
Expand Up @@ -125,10 +125,6 @@ module subroutine encounter_check_all_plplm(param, nplm, nplt, rplm, vplm, rplt,
! end if

allocate(tmp_param, source=param)
select type(tmp_param)
class is (swiftest_parameters)
tmp_param%system_history%nc%lfile_is_open = .false.
end select

! Turn off adaptive encounter checks for the pl-pl group
tmp_param%ladaptive_encounters_plpl = .false.
Expand Down
6 changes: 3 additions & 3 deletions src/swiftest/swiftest_discard.f90
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module subroutine swiftest_discard_system(self, param)
lpl_check = allocated(self%pl_discards)
ltp_check = allocated(self%tp_discards)

associate(nbody_system => self, tp => self%tp, pl => self%pl, tp_discards => self%tp_discards, pl_discards => self%pl_discards, nc => param%system_history%nc)
associate(nbody_system => self, tp => self%tp, pl => self%pl, tp_discards => self%tp_discards, pl_discards => self%pl_discards, nc => self%system_history%nc)
lpl_discards = .false.
ltp_discards = .false.
if (lpl_check) then
Expand All @@ -41,12 +41,12 @@ module subroutine swiftest_discard_system(self, param)
if (ltp_discards.or.lpl_discards) then
call nc%open(param)
if (lpl_discards) then
call pl_discards%write_info(param%system_history%nc, param)
call pl_discards%write_info(self%system_history%nc, param)
if (param%lenergy) call self%conservation_report(param, lterminal=.false.)
call pl_discards%setup(0,param)
end if
if (ltp_discards) then
call tp_discards%write_info(param%system_history%nc, param)
call tp_discards%write_info(self%system_history%nc, param)
call tp_discards%setup(0,param)
end if
call nc%close()
Expand Down
20 changes: 10 additions & 10 deletions src/swiftest/swiftest_driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,15 +18,15 @@ program swiftest_driver
use swiftest
implicit none

class(swiftest_nbody_system), allocatable :: nbody_system !! Polymorphic object containing the nbody system to be integrated
class(swiftest_parameters), allocatable :: param !! Run configuration parameters
character(len=:), allocatable :: integrator !! Integrator type code (see globals for symbolic names)
character(len=:), allocatable :: param_file_name !! Name of the file containing user-defined parameters
character(len=:), allocatable :: display_style !! Style of the output display {"STANDARD", "COMPACT", "PROGRESS"}). Default is "STANDARD"
integer(I8B) :: istart !! Starting index for loop counter
integer(I4B) :: iout !! Output cadence counter
integer(I4B) :: idump !! Dump cadence counter
type(walltimer) :: integration_timer !! Object used for computing elapsed wall time
class(swiftest_nbody_system), allocatable :: nbody_system !! Polymorphic object containing the nbody system to be integrated
class(swiftest_parameters), allocatable :: param !! Run configuration parameters
character(len=:), allocatable :: integrator !! Integrator type code (see globals for symbolic names)
character(len=:), allocatable :: param_file_name !! Name of the file containing user-defined parameters
character(len=:), allocatable :: display_style !! Style of the output display {"STANDARD", "COMPACT", "PROGRESS"}). Default is "STANDARD"
integer(I8B) :: istart !! Starting index for loop counter
integer(I4B) :: iout !! Output cadence counter
integer(I4B) :: idump !! Dump cadence counter
type(walltimer) :: integration_timer !! Object used for computing elapsed wall time

call swiftest_io_get_args(integrator, param_file_name, display_style)

Expand Down Expand Up @@ -69,7 +69,7 @@ program swiftest_driver

call nbody_system%initialize(param)

associate (system_history => param%system_history)
associate (system_history => nbody_system%system_history)
! If this is a new run, compute energy initial conditions (if energy tracking is turned on) and write the initial conditions to file.
call nbody_system%display_run_information(param, integration_timer, phase="first")
if (param%lenergy) then
Expand Down
18 changes: 9 additions & 9 deletions src/swiftest/swiftest_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,7 @@ module subroutine swiftest_io_conservation_report(self, param, lterminal)
integer(I4B), parameter :: EGYIU = 72
character(len=*), parameter :: EGYTERMFMT = '(" DL/L0 = ", ES12.5, "; DE/|E0| = ", ES12.5, "; DM/M0 = ", ES12.5)'

associate(nbody_system => self, pl => self%pl, cb => self%cb, npl => self%pl%nbody, display_unit => param%display_unit, nc => param%system_history%nc)
associate(nbody_system => self, pl => self%pl, cb => self%cb, npl => self%pl%nbody, display_unit => param%display_unit, nc => self%system_history%nc)

call pl%vb2vh(cb)
call pl%rh2rb(cb)
Expand Down Expand Up @@ -311,7 +311,7 @@ module subroutine swiftest_io_dump_system(self, param)
if (allocated(self%collision_history)) call self%collision_history%dump(param)

! Dump the nbody_system history to file
call param%system_history%dump(param)
call self%system_history%dump(param)

allocate(param_restart, source=param)
param_restart%in_form = "XV"
Expand Down Expand Up @@ -346,7 +346,7 @@ module subroutine swiftest_io_dump_storage(self, param)

if (self%iframe == 0) return
call self%make_index_map()
associate(nc => param%system_history%nc)
associate(nc => self%nc)
call nc%open(param)

do i = 1, self%iframe
Expand Down Expand Up @@ -561,15 +561,15 @@ module subroutine swiftest_io_netcdf_get_t0_values_system(self, param)
implicit none
! Arguments
class(swiftest_nbody_system), intent(inout) :: self
class(swiftest_parameters), intent(inout) :: param
class(swiftest_parameters), intent(inout) :: param
! Internals
integer(I4B) :: itmax, idmax, tslot
real(DP), dimension(:), allocatable :: vals
real(DP), dimension(1) :: rtemp
real(DP), dimension(NDIM) :: rot0, Ip0
real(DP) :: KE_orb_orig, KE_spin_orig, PE_orig, BE_orig

associate (nc => param%system_history%nc, cb => self%cb)
associate (nc => self%system_history%nc, cb => self%cb)
call nc%open(param, readonly=.true.)
call nc%find_tslot(param%t0)
tslot = nc%tslot
Expand Down Expand Up @@ -2708,13 +2708,13 @@ module subroutine swiftest_io_read_in_system(self, param)
self%E_untracked = param%E_untracked
else
allocate(tmp_param, source=param)
tmp_param%system_history%nc%file_name = param%nc_in
self%system_history%nc%file_name = param%nc_in
tmp_param%out_form = param%in_form
if (.not. param%lrestart) then
! Turn off energy computation so we don't have to feed it into the initial conditions
tmp_param%lenergy = .false.
end if
ierr = self%read_frame(tmp_param%system_history%nc, tmp_param)
ierr = self%read_frame(self%system_history%nc, tmp_param)
deallocate(tmp_param)
if (ierr /=0) call base_util_exit(FAILURE)
end if
Expand Down Expand Up @@ -2940,7 +2940,7 @@ module subroutine swiftest_io_write_discard(self, param)
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
! Internals

associate(pl => self%pl, npl => self%pl%nbody, pl_adds => self%pl_adds, nc => param%system_history%nc)
associate(pl => self%pl, npl => self%pl%nbody, pl_adds => self%pl_adds, nc => self%system_history%nc)

call nc%open(param)
if (self%tp_discards%nbody > 0) call self%tp_discards%write_info(nc, param)
Expand Down Expand Up @@ -2972,7 +2972,7 @@ module subroutine swiftest_io_write_frame_system(self, param)
character(len=STRMAX) :: errmsg
logical :: fileExists

associate (nc => param%system_history%nc, pl => self%pl, tp => self%tp, npl => self%pl%nbody, ntp => self%tp%nbody)
associate (nc => self%system_history%nc, pl => self%pl, tp => self%tp, npl => self%pl%nbody, ntp => self%tp%nbody)
nc%file_name = param%outfile
if (lfirst) then
inquire(file=param%outfile, exist=fileExists)
Expand Down
38 changes: 1 addition & 37 deletions src/swiftest/swiftest_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,6 @@ module swiftest
procedure :: initialize => swiftest_io_netcdf_initialize_output !! Initialize a set of parameters used to identify a NetCDF output object
procedure :: open => swiftest_io_netcdf_open !! Opens a NetCDF file and does the variable inquiries to activate variable ids
procedure :: flush => swiftest_io_netcdf_flush !! Flushes a NetCDF file by closing it then opening it again
final :: swiftest_final_netcdf_parameters !! Finalizer will close the NetCDF file
end type swiftest_netcdf_parameters


Expand All @@ -71,15 +70,12 @@ module swiftest

! The following extended types or their children should be used, where possible, as the base of any types defined in additional modules, such as new integrators.
type, extends(base_parameters) :: swiftest_parameters
class(swiftest_storage), allocatable :: system_history
contains
procedure :: dealloc => swiftest_util_dealloc_param
procedure :: dump => swiftest_io_dump_param
procedure :: reader => swiftest_io_param_reader
procedure :: writer => swiftest_io_param_writer
procedure :: read_in => swiftest_io_read_in_param
procedure :: set_display => swiftest_io_set_display_param
final :: swiftest_final_param
end type swiftest_parameters


Expand Down Expand Up @@ -328,6 +324,7 @@ module swiftest
class(collision_basic), allocatable :: collider !! Collision system object
class(encounter_storage), allocatable :: encounter_history !! Stores encounter history for later retrieval and saving to file
class(collision_storage), allocatable :: collision_history !! Stores encounter history for later retrieval and saving to file
class(swiftest_storage), allocatable :: system_history !! Stores the system history between output dumps

real(DP) :: t = -1.0_DP !! Integration current time
real(DP) :: GMtot = 0.0_DP !! Total nbody_system mass - used for barycentric coordinate conversion
Expand Down Expand Up @@ -1239,11 +1236,6 @@ module subroutine swiftest_util_dealloc_kin(self)
class(swiftest_kinship), intent(inout) :: self !! Swiftest kinship object
end subroutine swiftest_util_dealloc_kin

module subroutine swiftest_util_dealloc_param(self)
implicit none
class(swiftest_parameters),intent(inout) :: self !! Collection of parameters
end subroutine swiftest_util_dealloc_param

module subroutine swiftest_util_dealloc_cb(self)
implicit none
class(swiftest_cb), intent(inout) :: self !! Swiftest central body object
Expand Down Expand Up @@ -1935,34 +1927,6 @@ subroutine swiftest_final_kin(self)
end subroutine swiftest_final_kin


subroutine swiftest_final_param(self)
!! author: David A. Minton
!!
!! Finalize the Swiftest parameter object - deallocates all allocatables
implicit none
! Argument
type(swiftest_parameters), intent(inout) :: self !! SyMBA kinship object

call self%dealloc()

return
end subroutine swiftest_final_param


subroutine swiftest_final_netcdf_parameters(self)
!! author: David A. Minton
!!
!! Finalize the NetCDF by closing the file
implicit none
! Arguments
type(swiftest_netcdf_parameters), intent(inout) :: self

call self%close()

return
end subroutine swiftest_final_netcdf_parameters


subroutine swiftest_final_storage(self)
!! author: David A. Minton
!!
Expand Down
39 changes: 12 additions & 27 deletions src/swiftest/swiftest_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -802,25 +802,6 @@ module subroutine swiftest_util_dealloc_kin(self)
end subroutine swiftest_util_dealloc_kin


module subroutine swiftest_util_dealloc_param(self)
!! author: David A. Minton
!!
!! Deallocates all allocatables
implicit none
! Arguments
class(swiftest_parameters),intent(inout) :: self !! Collection of parameters

if (allocated(self%system_history)) then
call self%system_history%dealloc()
deallocate(self%system_history)
end if

call base_util_dealloc_param(self)

return
end subroutine swiftest_util_dealloc_param


module subroutine swiftest_util_dealloc_pl(self)
!! author: David A. Minton
!!
Expand Down Expand Up @@ -902,6 +883,7 @@ module subroutine swiftest_util_dealloc_system(self)
if (allocated(self%collider)) deallocate(self%collider)
if (allocated(self%encounter_history)) deallocate(self%encounter_history)
if (allocated(self%collision_history)) deallocate(self%collision_history)
if (allocated(self%system_history)) deallocate(self%system_history)

self%t = -1.0_DP
self%GMtot = 0.0_DP
Expand Down Expand Up @@ -1831,7 +1813,7 @@ module subroutine swiftest_util_rearray_pl(self, nbody_system, param)
class(encounter_list), allocatable :: plplenc_old
logical :: lencounter

associate(pl => self, tp => nbody_system%tp, pl_adds => nbody_system%pl_adds, nc => param%system_history%nc)
associate(pl => self, tp => nbody_system%tp, pl_adds => nbody_system%pl_adds)

npl = pl%nbody
nadd = pl_adds%nbody
Expand Down Expand Up @@ -2825,15 +2807,15 @@ module subroutine swiftest_util_setup_initialize_system(self, param)
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest nbody_system object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters

if (allocated(param%system_history)) then
call param%system_history%dealloc()
deallocate(param%system_history)
if (allocated(self%system_history)) then
call self%system_history%dealloc()
deallocate(self%system_history)
end if
allocate(swiftest_storage :: param%system_history)
call param%system_history%setup(param%dump_cadence)
allocate(swiftest_netcdf_parameters :: param%system_history%nc)
allocate(swiftest_storage :: self%system_history)
call self%system_history%setup(param%dump_cadence)
allocate(swiftest_netcdf_parameters :: self%system_history%nc)

associate(nbody_system => self, cb => self%cb, pl => self%pl, tp => self%tp, nc => param%system_history%nc)
associate(nbody_system => self, cb => self%cb, pl => self%pl, tp => self%tp, nc => self%system_history%nc)
call nbody_system%read_in(param)
call nbody_system%validate_ids(param)
call nbody_system%set_msys()
Expand Down Expand Up @@ -3067,6 +3049,9 @@ module subroutine swiftest_util_snapshot_system(self, param, nbody_system, t, ar
allocate(snapshot%cb, source=nbody_system%cb )
allocate(snapshot%pl, source=nbody_system%pl )
allocate(snapshot%tp, source=nbody_system%tp )
allocate(snapshot%system_history)
allocate(snapshot%system_history%nc, source=nbody_system%system_history%nc)
snapshot%system_history%nc%lfile_is_open = .true.

snapshot%t = nbody_system%t
snapshot%GMtot = nbody_system%GMtot
Expand Down

0 comments on commit fcac2d7

Please sign in to comment.