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

Commit

Permalink
Restructured the swiftest_storage object to be a general purpose stor…
Browse files Browse the repository at this point in the history
…age tool capabable of storing *any* object you want. I added an extension in the encounter class definitions that will specialized in encounter list storage
  • Loading branch information
daminton committed Dec 1, 2022
1 parent 08584c4 commit c2c781f
Show file tree
Hide file tree
Showing 8 changed files with 61 additions and 49 deletions.
1 change: 1 addition & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ SET(FAST_MATH_FILES
${SRC}/discard/discard.f90
${SRC}/drift/drift.f90
${SRC}/encounter/encounter_check.f90
${SRC}/encounter/encounter_io.f90
${SRC}/encounter/encounter_setup.f90
${SRC}/encounter/encounter_util.f90
${SRC}/fraggle/fraggle_generate.f90
Expand Down
24 changes: 24 additions & 0 deletions src/encounter/encounter_io.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,24 @@
!! Copyright 2022 - David Minton, Carlisle Wishard, Jennifer Pouplin, Jake Elliott, & Dana Singh
!! This file is part of Swiftest.
!! Swiftest is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License
!! as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version.
!! Swiftest is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty
!! of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details.
!! You should have received a copy of the GNU General Public License along with Swiftest.
!! If not, see: https://www.gnu.org/licenses.

submodule (encounter_classes) s_encounter_io
use swiftest
contains

module subroutine encounter_io_dump_storage_list(self, param)
!! author: David A. Minton
!!
!! Dumps the time history of an encounter to file.
implicit none
! Arguments
class(encounter_storage(*)), intent(inout) :: self !! Encounter storage object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine encounter_io_dump_storage_list

end submodule s_encounter_io
11 changes: 5 additions & 6 deletions src/encounter/encounter_util.f90
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,6 @@ module subroutine encounter_util_copy_list(self, source)
return
end subroutine encounter_util_copy_list


module subroutine encounter_util_dealloc_aabb(self)
!! author: David A. Minton
!!
Expand Down Expand Up @@ -149,11 +148,11 @@ module subroutine encounter_util_resize_list(self, nnew)
implicit none
! Arguments
class(encounter_list), intent(inout) :: self !! Swiftest encounter list
integer(I8B), 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(I8B) :: nold
logical :: lmalloc
integer(I8B) :: nold
logical :: lmalloc

lmalloc = allocated(self%status)
if (lmalloc) then
Expand Down Expand Up @@ -185,8 +184,8 @@ module subroutine encounter_util_spill_list(self, discards, lspill_list, ldestru
! Arguments
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
! Internals
integer(I8B) :: nenc_old

Expand Down
15 changes: 9 additions & 6 deletions src/io/io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -270,7 +270,7 @@ module subroutine io_dump_system(self, param)
end subroutine io_dump_system


module subroutine io_dump_storage_system(self, param)
module subroutine io_dump_storage(self, param)
!! author: David A. Minton
!!
!! Dumps the time history of the simulation to file. Each time it writes a frame to file, it deallocates the system
Expand All @@ -287,15 +287,18 @@ module subroutine io_dump_storage_system(self, param)

iloop_start = param%iloop - int(param%istep_out * param%dump_cadence + 1, kind=I8B)
do i = 1, param%dump_cadence
if (allocated(self%frame(i)%system)) then
param%ioutput = int(iloop_start / param%istep_out, kind=I4B) + i
call self%frame(i)%system%write_frame(param)
deallocate(self%frame(i)%system)
param%ioutput = int(iloop_start / param%istep_out, kind=I4B) + i
if (allocated(self%frame(i)%item)) then
select type(system => self%frame(i)%item)
class is (swiftest_nbody_system)
call system%write_frame(param)
end select
deallocate(self%frame(i)%item)
end if
end do

return
end subroutine io_dump_storage_system
end subroutine io_dump_storage


module subroutine io_get_args(integrator, param_file_name, display_style)
Expand Down
2 changes: 1 addition & 1 deletion src/main/swiftest_driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ program swiftest_driver
character(len=64) :: pbarmessage

character(*), parameter :: symbacompactfmt = '(";NPLM",ES22.15,$)'
type(swiftest_storage(nframes=:)), allocatable :: system_history
type(swiftest_storage(nframes=:)), allocatable :: system_history

call io_get_args(integrator, param_file_name, display_style)

Expand Down
17 changes: 1 addition & 16 deletions src/modules/encounter_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -41,17 +41,8 @@ module encounter_classes
final :: encounter_util_final_list !! Finalize the encounter list - deallocates all allocatables
end type encounter_list

type encounter_storage_frame_list
class(swiftest_nbody_system), allocatable :: system
contains
procedure :: store => encounter_util_copy_store_list !! Stores a snapshot of the nbody system so that later it can be retrieved for saving to file.
generic :: assignment(=) => store
end type

type :: encounter_storage(nframes)
integer(I4B), len :: nframes
type, extends(swiftest_storage) :: encounter_storage
!! A class that that is used to store simulation history data between file output
type(encounter_storage_frame_list), dimension(nframes) :: frame
contains
procedure :: dump => encounter_io_dump_storage_list
end type encounter_storage
Expand Down Expand Up @@ -220,12 +211,6 @@ module subroutine encounter_util_copy_list(self, source)
class(encounter_list), intent(in) :: source !! Source object to copy into
end subroutine encounter_util_copy_list

module subroutine encounter_util_copy_store_list(self, system)
implicit none
class(encounter_storage_frame_list), intent(inout) :: self !! Encounter storage object
class(encounter_list), intent(in) :: system !! Swiftest encounter list structure
end subroutine encounter_util_copy_store_list

module subroutine encounter_util_dealloc_aabb(self)
implicit none
class(encounter_bounding_box_1D), intent(inout) :: self !!Bounding box structure along a single dimension
Expand Down
26 changes: 13 additions & 13 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -417,19 +417,19 @@ module swiftest_classes
generic :: write_frame => write_frame_system, write_frame_netcdf !! Generic method call for reading a frame of output data
end type swiftest_nbody_system

type swiftest_storage_frame_system
class(swiftest_nbody_system), allocatable :: system
type swiftest_storage_frame
class(*), allocatable :: item
contains
procedure :: store => util_copy_store_system !! Stores a snapshot of the nbody system so that later it can be retrieved for saving to file.
procedure :: store => util_copy_store !! Stores a snapshot of the nbody system so that later it can be retrieved for saving to file.
generic :: assignment(=) => store
end type

type :: swiftest_storage(nframes)
integer(I4B), len :: nframes
!! A class that that is used to store simulation history data between file output
type(swiftest_storage_frame_system), dimension(nframes) :: frame
!! An abstract class that establishes the pattern for various storage objects
type(swiftest_storage_frame), dimension(nframes) :: frame
contains
procedure :: dump => io_dump_storage_system
procedure :: dump => io_dump_storage
end type swiftest_storage

abstract interface
Expand All @@ -449,7 +449,6 @@ subroutine abstract_discard_body(self, system, param)
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine abstract_discard_body


subroutine abstract_kick_body(self, system, param, t, dt, lbeg)
import swiftest_body, swiftest_nbody_system, swiftest_parameters, DP
implicit none
Expand Down Expand Up @@ -493,6 +492,7 @@ subroutine abstract_step_system(self, param, t, dt)
real(DP), intent(in) :: t !! Simulation time
real(DP), intent(in) :: dt !! Current stepsize
end subroutine abstract_step_system

end interface

interface
Expand Down Expand Up @@ -625,11 +625,11 @@ module subroutine io_dump_system(self, param)
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine io_dump_system

module subroutine io_dump_storage_system(self, param)
module subroutine io_dump_storage(self, param)
implicit none
class(swiftest_storage(*)), intent(inout) :: self !! Swiftest simulation history storage object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine io_dump_storage_system
end subroutine io_dump_storage

module subroutine io_get_args(integrator, param_file_name, display_style)
implicit none
Expand Down Expand Up @@ -1242,11 +1242,11 @@ module subroutine util_copy_particle_info_arr(source, dest, idx)
integer(I4B), dimension(:), intent(in), optional :: idx !! Optional array of indices to draw the source object
end subroutine util_copy_particle_info_arr

module subroutine util_copy_store_system(self, system)
module subroutine util_copy_store(self, source)
implicit none
class(swiftest_storage_frame_system), intent(inout) :: self !! Swiftest storage frame object
class(swiftest_nbody_system), intent(in) :: system !! Swiftest n-body system object
end subroutine util_copy_store_system
class(swiftest_storage_frame), intent(inout) :: self !! Swiftest storage frame object
class(*), intent(in) :: source !! Any object that one wishes to store
end subroutine util_copy_store

module subroutine util_dealloc_body(self)
implicit none
Expand Down
14 changes: 7 additions & 7 deletions src/util/util_copy.f90
Original file line number Diff line number Diff line change
Expand Up @@ -78,18 +78,18 @@ module subroutine util_copy_particle_info_arr(source, dest, idx)
end subroutine util_copy_particle_info_arr


module subroutine util_copy_store_system(self, system)
module subroutine util_copy_store(self, source)
!! author: David A. Minton
!!
!! Stores a snapshot of the nbody system so that later it can be retrieved for saving to file.
implicit none
class(swiftest_storage_frame_system), intent(inout) :: self !! Swiftest storage frame object
class(swiftest_nbody_system), intent(in) :: system !! Swiftest n-body system object
class(swiftest_storage_frame), intent(inout) :: self !! Swiftest storage frame object
class(*), intent(in) :: source !! Swiftest n-body system object

if (allocated(self%system)) deallocate(self%system)
allocate(self%system, source=system)
if (allocated(self%item)) deallocate(self%item)
allocate(self%item, source=source)

return

end subroutine util_copy_store_system
end subroutine util_copy_store

end submodule s_util_copy

0 comments on commit c2c781f

Please sign in to comment.