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

Commit

Permalink
Adding in particle info initialization methods
Browse files Browse the repository at this point in the history
  • Loading branch information
daminton committed Aug 10, 2021
1 parent 88ba918 commit ac702ce
Show file tree
Hide file tree
Showing 5 changed files with 45 additions and 47 deletions.
2 changes: 2 additions & 0 deletions src/io/io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -540,6 +540,7 @@ module subroutine io_param_reader(self, unit, iotype, v_list, iostat, iomsg)
iostat = -1
return
end if
param%lrestart = (param%out_stat == "APPEND")
if (param%outfile /= "") then
if ((param%out_type /= REAL4_TYPE) .and. (param%out_type /= REAL8_TYPE) .and. &
(param%out_type /= SWIFTER_REAL4_TYPE) .and. (param%out_type /= SWIFTER_REAL8_TYPE)) then
Expand All @@ -557,6 +558,7 @@ module subroutine io_param_reader(self, unit, iotype, v_list, iostat, iomsg)
iostat = -1
return
end if

end if
if (param%qmin > 0.0_DP) then
if ((param%qmin_coord /= "HELIO") .and. (param%qmin_coord /= "BARY")) then
Expand Down
11 changes: 6 additions & 5 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -64,13 +64,14 @@ module swiftest_classes
real(DP), dimension(NDIM) :: Ltot_orig = 0.0_DP !! Initial total angular momentum vector
real(DP), dimension(NDIM) :: Lorbit_orig = 0.0_DP !! Initial orbital angular momentum
real(DP), dimension(NDIM) :: Lspin_orig = 0.0_DP !! Initial spin angular momentum vector
real(DP), dimension(NDIM) :: Ltot = 0.0_DP !! System angular momentum vector
real(DP), dimension(NDIM) :: Lescape = 0.0_DP !! Angular momentum of bodies that escaped the system (used for bookeeping)
real(DP) :: Mescape = 0.0_DP !! Mass of bodies that escaped the system (used for bookeeping)
real(DP) :: Ecollisions = 0.0_DP !! Energy lost from system due to collisions
real(DP) :: Euntracked = 0.0_DP !! Energy gained from system due to escaped bodies
real(DP), dimension(NDIM) :: Ltot = 0.0_DP !! System angular momentum vector
real(DP), dimension(NDIM) :: Lescape = 0.0_DP !! Angular momentum of bodies that escaped the system (used for bookeeping)
real(DP) :: Mescape = 0.0_DP !! Mass of bodies that escaped the system (used for bookeeping)
real(DP) :: Ecollisions = 0.0_DP !! Energy lost from system due to collisions
real(DP) :: Euntracked = 0.0_DP !! Energy gained from system due to escaped bodies
logical :: lfirstenergy = .true. !! This is the first time computing energe
logical :: lfirstkick = .true. !! Initiate the first kick in a symplectic step
logical :: lrestart = .false. !! Indicates whether or not this is a restarted run

! Future features not implemented or in development
logical :: lgr = .false. !! Turn on GR
Expand Down
24 changes: 10 additions & 14 deletions src/modules/symba_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -354,22 +354,12 @@ module subroutine symba_io_param_writer(self, unit, iotype, v_list, iostat, ioms
integer, intent(out) :: iostat !! IO status code
character(len=*), intent(inout) :: iomsg !! Message to pass if iostat /= 0
end subroutine symba_io_param_writer
module subroutine symba_io_initialize_particle_info(system, param)

module subroutine symba_io_read_particle(system, param)
implicit none
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system object
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system file
class(symba_parameters), intent(inout) :: param !! Current run configuration parameters with SyMBA extensions
end subroutine symba_io_initialize_particle_info

!module subroutine symba_io_read_frame_info(self, iu, param, form, ierr)
! use swiftest_classes, only : swiftest_parameters
! implicit none
! class(symba_particle_info), intent(inout) :: self !! SyMBA particle info object
! integer(I4B), intent(inout) :: iu !! Unit number for the output file to write frame to
! class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
! character(*), intent(in) :: form !! Input format code ("XV" or "EL")
! integer(I4B), intent(out) :: ierr !! Error code
!end subroutine symba_io_read_frame_info
end subroutine symba_io_read_particle

module subroutine symba_kick_getacch_pl(self, system, param, t, lbeg)
use swiftest_classes, only : swiftest_nbody_system, swiftest_parameters
Expand Down Expand Up @@ -399,6 +389,12 @@ module subroutine symba_kick_pltpenc(self, system, dt, irec, sgn)
integer(I4B), intent(in) :: irec !! Current recursion level
integer(I4B), intent(in) :: sgn !! sign to be applied to acceleration
end subroutine symba_kick_pltpenc

module subroutine symba_setup_initialize_particle_info(system, param)
implicit none
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system object
class(symba_parameters), intent(inout) :: param !! Current run configuration parameters with SyMBA extensions
end subroutine symba_setup_initialize_particle_info

module subroutine symba_setup_initialize_system(self, param)
use swiftest_classes, only : swiftest_parameters
Expand Down
38 changes: 10 additions & 28 deletions src/symba/symba_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -75,21 +75,6 @@ module subroutine symba_io_dump_particle_info(system, param, tpidx, plidx)
return
end subroutine symba_io_dump_particle_info


module subroutine symba_io_initialize_particle_info(system, param)
!! author: David A. Minton
!!
!! Initializes a particle info data structure, either starting a new one or reading one in
!! from a file if it is a restarted run
implicit none
! Argumets
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system object
class(symba_parameters), intent(inout) :: param !! Current run configuration parameters with SyMBA extensions

return
end subroutine symba_io_initialize_particle_info


module subroutine symba_io_param_reader(self, unit, iotype, v_list, iostat, iomsg)
!! author: The Purdue Swiftest Team - David A. Minton, Carlisle A. Wishard, Jennifer L.L. Pouplin, and Jacob R. Elliott
!!
Expand Down Expand Up @@ -260,19 +245,16 @@ module subroutine symba_io_param_writer(self, unit, iotype, v_list, iostat, ioms
end subroutine symba_io_param_writer


!module subroutine symba_io_read_frame_info(self, iu, param, form, ierr)
! !! author: David A. Minton
! !!
! !! Reads a single frame of a particle info data from a file.
! implicit none
! class(symba_particle_info), intent(inout) :: self !! SyMBA particle info object
! integer(I4B), intent(inout) :: iu !! Unit number for the output file to write frame to
! class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
! character(*), intent(in) :: form !! Input format code ("XV" or "EL")
! integer(I4B), intent(out) :: ierr !! Error code
!
! ierr = 0
! end subroutine symba_io_read_frame_info
module subroutine symba_io_read_particle(system, param)
!! author: David A. Minton
!!
!! Reads an old particle information file for a restartd run
implicit none
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system file
class(symba_parameters), intent(inout) :: param !! Current run configuration parameters with SyMBA extensions

return
end subroutine symba_io_read_particle


module subroutine symba_io_write_discard(self, param)
Expand Down
17 changes: 17 additions & 0 deletions src/symba/symba_setup.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,18 @@
use swiftest
contains

module subroutine symba_setup_initialize_particle_info(system, param)
!! author: David A. Minton
!!
!! Initializes a new particle information data structure with initial conditions recorded
implicit none
! Argumets
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system object
class(symba_parameters), intent(inout) :: param !! Current run configuration parameters with SyMBA extensions

return
end subroutine symba_setup_initialize_particle_info

module subroutine symba_setup_initialize_system(self, param)
!! author: David A. Minton
!!
Expand All @@ -27,6 +39,11 @@ module subroutine symba_setup_initialize_system(self, param)
class is (symba_parameters)
pl%lmtiny(:) = pl%Gmass(:) > param%GMTINY
pl%nplm = count(pl%lmtiny(:))
if (param%lrestart) then
call symba_io_read_particle(system, param)
else
call symba_setup_initialize_particle_info(system, param)
end if
end select
end select
end associate
Expand Down

0 comments on commit ac702ce

Please sign in to comment.