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

Commit

Permalink
Added templates for setup and initilization methods for symba, and th…
Browse files Browse the repository at this point in the history
…e encounter and merger structures.
  • Loading branch information
daminton committed Jul 10, 2021
1 parent ee55741 commit 28cdd47
Show file tree
Hide file tree
Showing 4 changed files with 178 additions and 109 deletions.
111 changes: 54 additions & 57 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -76,9 +76,6 @@ module swiftest_classes
procedure, public :: writer => io_param_writer
procedure, public :: dump => io_dump_param
procedure, public :: read_from_file => io_read_param_in
!TODO: Figure out if user-defined derived-type io can be made to work properly
!generic :: read(FORMATTED) => param_reader
!generic :: write(FORMATTED) => param_writer
end type swiftest_parameters

!********************************************************************************************************************************
Expand Down Expand Up @@ -166,7 +163,7 @@ module swiftest_classes
procedure, public :: accel_obl => obl_acc_body !! Compute the barycentric accelerations of bodies due to the oblateness of the central body
procedure, public :: el2xv => orbel_el2xv_vec !! Convert orbital elements to position and velocity vectors
procedure, public :: xv2el => orbel_xv2el_vec !! Convert position and velocity vectors to orbital elements
procedure, public :: set_ir3 => util_set_ir3h !! Sets the inverse heliocentric radius term (1/rh**3)
procedure, public :: set_ir3 => util_set_ir3h !! Sets the inverse heliocentric radius term (1/rh**3)
procedure, public :: setup => setup_body !! A constructor that sets the number of bodies and allocates all allocatable arrays
procedure, public :: accel_user => user_getacch_body !! Add user-supplied heliocentric accelerations to planets
procedure, public :: fill => util_fill_body !! "Fills" bodies from one object into another depending on the results of a mask (uses the MERGE intrinsic)
Expand All @@ -180,15 +177,15 @@ module swiftest_classes
!> An abstract class for a generic collection of Swiftest massive bodies
type, abstract, public, extends(swiftest_body) :: swiftest_pl
!! Superclass that defines the generic elements of a Swiftest particle
real(DP), dimension(:), allocatable :: mass !! Body mass (units MU)
real(DP), dimension(:), allocatable :: Gmass !! Mass gravitational term G * mass (units GU * MU)
real(DP), dimension(:), allocatable :: rhill !! Body mass (units MU)
real(DP), dimension(:), allocatable :: radius !! Body radius (units DU)
real(DP), dimension(:), allocatable :: irij3 !! 1.0_DP / (rji2 * sqrt(rji2)) where rji2 is the square of the Euclidean distance
real(DP), dimension(:,:), allocatable :: xbeg !! Position at beginning of step
real(DP), dimension(:,:), allocatable :: xend !! Position at end of step
real(DP), dimension(:,:), allocatable :: vbeg !! Velocity at beginning of step
real(DP), dimension(:), allocatable :: density !! Body mass density - calculated internally (units MU / DU**3)
real(DP), dimension(:), allocatable :: mass !! Body mass (units MU)
real(DP), dimension(:), allocatable :: Gmass !! Mass gravitational term G * mass (units GU * MU)
real(DP), dimension(:), allocatable :: rhill !! Body mass (units MU)
real(DP), dimension(:), allocatable :: radius !! Body radius (units DU)
real(DP), dimension(:), allocatable :: irij3 !! 1.0_DP / (rji2 * sqrt(rji2)) where rji2 is the square of the Euclidean distance
real(DP), dimension(:,:), allocatable :: xbeg !! Position at beginning of step
real(DP), dimension(:,:), allocatable :: xend !! Position at end of step
real(DP), dimension(:,:), allocatable :: vbeg !! Velocity at beginning of step
real(DP), dimension(:), allocatable :: density !! Body mass density - calculated internally (units MU / DU**3)
!! Note to developers: If you add components to this class, be sure to update methods and subroutines that traverse the
!! component list, such as setup_pl and util_spill_pl
contains
Expand All @@ -200,8 +197,8 @@ module swiftest_classes
procedure, public :: eucl_irij3 => eucl_irij3_plpl !! Parallelized single loop blocking for Euclidean distance matrix calcualtion
procedure, public :: accel_obl => obl_acc_pl !! Compute the barycentric accelerations of bodies due to the oblateness of the central body
procedure, public :: setup => setup_pl !! A base constructor that sets the number of bodies and allocates and initializes all arrays
procedure, public :: set_mu => util_set_mu_pl !! Method used to construct the vectorized form of the central body mass
procedure, public :: set_rhill => util_set_rhill !! Calculates the Hill's radii for each body
procedure, public :: set_mu => util_set_mu_pl !! Method used to construct the vectorized form of the central body mass
procedure, public :: set_rhill => util_set_rhill !! Calculates the Hill's radii for each body
procedure, public :: h2b => util_coord_h2b_pl !! Convert massive bodies from heliocentric to barycentric coordinates (position and velocity)
procedure, public :: b2h => util_coord_b2h_pl !! Convert massive bodies from barycentric to heliocentric coordinates (position and velocity)
procedure, public :: fill => util_fill_pl !! "Fills" bodies from one object into another depending on the results of a mask (uses the MERGE intrinsic)
Expand All @@ -215,10 +212,10 @@ module swiftest_classes
!> An abstract class for a generic collection of Swiftest test particles
type, abstract, public, extends(swiftest_body) :: swiftest_tp
!! Superclass that defines the generic elements of a Swiftest test particle
integer(I4B), dimension(:), allocatable :: isperi !! Perihelion passage flag
real(DP), dimension(:), allocatable :: peri !! Perihelion distance
real(DP), dimension(:), allocatable :: atp !! Semimajor axis following perihelion passage
real(DP), dimension(:, :), allocatable :: irij3 !! 1.0_DP / (rji2 * sqrt(rji2)) where rji2 is the square of the Euclidean distance betwen each pl-tp
integer(I4B), dimension(:), allocatable :: isperi !! Perihelion passage flag
real(DP), dimension(:), allocatable :: peri !! Perihelion distance
real(DP), dimension(:), allocatable :: atp !! Semimajor axis following perihelion passage
real(DP), dimension(:, :), allocatable :: irij3 !! 1.0_DP / (rji2 * sqrt(rji2)) where rji2 is the square of the Euclidean distance betwen each pl-tp
!! Note to developers: If you add components to this class, be sure to update methods and subroutines that traverse the
!! component list, such as setup_tp and util_spill_tp
contains
Expand All @@ -227,9 +224,9 @@ module swiftest_classes
! These are concrete because they are the same implemenation for all integrators
procedure, public :: discard => discard_tp !! Check to see if test particles should be discarded based on their positions relative to the massive bodies
procedure, public :: eucl_index => eucl_dist_index_pltp !! Sets up the (i, j) -> k indexing used for the single-loop blocking Euclidean distance matrix
procedure, public :: accel_obl => obl_acc_tp !! Compute the barycentric accelerations of bodies due to the oblateness of the central body
procedure, public :: accel_obl => obl_acc_tp !! Compute the barycentric accelerations of bodies due to the oblateness of the central body
procedure, public :: setup => setup_tp !! A base constructor that sets the number of bodies and
procedure, public :: set_mu => util_set_mu_tp !! Method used to construct the vectorized form of the central body mass
procedure, public :: set_mu => util_set_mu_tp !! Method used to construct the vectorized form of the central body mass
procedure, public :: h2b => util_coord_h2b_tp !! Convert test particles from heliocentric to barycentric coordinates (position and velocity)
procedure, public :: b2h => util_coord_b2h_tp !! Convert test particles from barycentric to heliocentric coordinates (position and velocity)
procedure, public :: fill => util_fill_tp !! "Fills" bodies from one object into another depending on the results of a mask (uses the MERGE intrinsic)
Expand Down Expand Up @@ -264,13 +261,13 @@ module swiftest_classes
procedure(abstract_step_system), public, deferred :: step

! Concrete classes that are common to the basic integrator (only test particles considered for discard)
procedure, public :: discard => discard_system !! Perform a discard step on the system
procedure, public :: dump => io_dump_system !! Dump the state of the system to a file
procedure, public :: initialize => io_read_initialize_system !! Initialize the system from an input file
procedure, public :: read_frame => io_read_frame_system !! Append a frame of output data to file
procedure, public :: set_msys => util_set_msys !! Sets the value of msys from the masses of system bodies.
procedure, public :: write_discard => io_write_discard !! Append a frame of output data to file
procedure, public :: write_frame => io_write_frame_system !! Append a frame of output data to file
procedure, public :: discard => discard_system !! Perform a discard step on the system
procedure, public :: dump => io_dump_system !! Dump the state of the system to a file
procedure, public :: initialize => io_read_initialize_system !! Initialize the system from an input file
procedure, public :: read_frame => io_read_frame_system !! Append a frame of output data to file
procedure, public :: set_msys => util_set_msys !! Sets the value of msys from the masses of system bodies.
procedure, public :: write_discard => io_write_discard !! Append a frame of output data to file
procedure, public :: write_frame => io_write_frame_system !! Append a frame of output data to file
end type swiftest_nbody_system

abstract interface
Expand Down Expand Up @@ -324,17 +321,17 @@ end subroutine abstract_step_body
subroutine abstract_step_system(self, param, t, dt)
import DP, swiftest_nbody_system, swiftest_parameters
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Simulation time
real(DP), intent(in) :: dt !! Current stepsize
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Simulation time
real(DP), intent(in) :: dt !! Current stepsize
end subroutine abstract_step_system

subroutine abstract_write_frame(self, iu, param)
import DP, I4B, swiftest_base, swiftest_parameters
class(swiftest_base), intent(in) :: self !! Swiftest base object
integer(I4B), intent(inout) :: iu !! Unit number for the output file to write frame to
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_base), intent(in) :: self !! Swiftest base object
integer(I4B), intent(inout) :: iu !! Unit number for the output file to write frame to
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
end subroutine abstract_write_frame
end interface

Expand All @@ -348,8 +345,8 @@ end subroutine discard_pl

module subroutine discard_system(self, param)
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
end subroutine discard_system

module subroutine discard_tp(self, system, param)
Expand All @@ -361,10 +358,10 @@ end subroutine discard_tp

module pure elemental subroutine drift_one(mu, px, py, pz, vx, vy, vz, dt, iflag)
implicit none
real(DP), intent(in) :: mu !! G * (Mcb + m), G = gravitational constant, Mcb = mass of central body, m = mass of body to drift
real(DP), intent(inout) :: px, py, pz, vx, vy, vz !! Position and velocity of body to drift
real(DP), intent(in) :: dt !! Step size
integer(I4B), intent(out) :: iflag !! iflag : error status flag for Danby drift (0 = OK, nonzero = ERROR)
real(DP), intent(in) :: mu !! G * (Mcb + m), G = gravitational constant, Mcb = mass of central body, m = mass of body to drift
real(DP), intent(inout) :: px, py, pz, vx, vy, vz !! Position and velocity of body to drift
real(DP), intent(in) :: dt !! Step size
integer(I4B), intent(out) :: iflag !! iflag : error status flag for Danby drift (0 = OK, nonzero = ERROR)
end subroutine drift_one

module subroutine eucl_dist_index_plpl(self)
Expand All @@ -374,26 +371,26 @@ module subroutine eucl_dist_index_plpl(self)

module subroutine eucl_dist_index_pltp(self, pl)
implicit none
class(swiftest_tp), intent(inout) :: self !! Swiftest test particle object
class(swiftest_pl), intent(inout) :: pl !! Swiftest massive body object
class(swiftest_tp), intent(inout) :: self !! Swiftest test particle object
class(swiftest_pl), intent(inout) :: pl !! Swiftest massive body object
end subroutine

module subroutine eucl_irij3_plpl(self)
implicit none
class(swiftest_pl), intent(inout) :: self !! Swiftest massive body object
class(swiftest_pl), intent(inout) :: self !! Swiftest massive body object
end subroutine eucl_irij3_plpl

module subroutine io_dump_param(self, param_file_name)
implicit none
class(swiftest_parameters),intent(in) :: self !! Output collection of parameters
class(swiftest_parameters),intent(in) :: self !! Output collection of parameters
character(len=*), intent(in) :: param_file_name !! Parameter input file name (i.e. param.in)
end subroutine io_dump_param

module subroutine io_dump_swiftest(self, param, msg)
implicit none
class(swiftest_base), intent(inout) :: self !! Swiftest base object
class(swiftest_base), intent(inout) :: self !! Swiftest base object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
character(*), optional, intent(in) :: msg !! Message to display with dump operation
character(*), optional, intent(in) :: msg !! Message to display with dump operation
end subroutine io_dump_swiftest

module subroutine io_dump_system(self, param, msg)
Expand Down Expand Up @@ -432,25 +429,25 @@ end subroutine io_param_reader

module subroutine io_param_writer(self, unit, iotype, v_list, iostat, iomsg)
implicit none
class(swiftest_parameters), intent(in) :: self !! Collection of parameters
integer(I4B), intent(in) :: unit !! File unit number
character(len=*), intent(in) :: iotype !! Dummy argument passed to the input/output procedure contains the text from the char-literal-constant, prefixed with DT.
!! If you do not include a char-literal-constant, the iotype argument contains only DT.
integer(I4B), intent(in) :: v_list(:) !! Not used in this procedure
integer(I4B), intent(out) :: iostat !! IO status code
character(len=*), intent(inout) :: iomsg !! Message to pass if iostat /= 0
class(swiftest_parameters), intent(in) :: self !! Collection of parameters
integer(I4B), intent(in) :: unit !! File unit number
character(len=*), intent(in) :: iotype !! Dummy argument passed to the input/output procedure contains the text from the char-literal-constant, prefixed with DT.
!! If you do not include a char-literal-constant, the iotype argument contains only DT.
integer(I4B), intent(in) :: v_list(:) !! Not used in this procedure
integer(I4B), intent(out) :: iostat !! IO status code
character(len=*), intent(inout) :: iomsg !! Message to pass if iostat /= 0
end subroutine io_param_writer

module subroutine io_read_body_in(self, param)
implicit none
class(swiftest_body), intent(inout) :: self !! Swiftest body object
class(swiftest_body), intent(inout) :: self !! Swiftest body object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine io_read_body_in

module subroutine io_read_cb_in(self, param)
implicit none
class(swiftest_cb), intent(inout) :: self
class(swiftest_parameters), intent(inout) :: param
class(swiftest_cb), intent(inout) :: self !! Swiftest central body object
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine io_read_cb_in

module subroutine io_read_param_in(self, param_file_name)
Expand Down
Loading

0 comments on commit 28cdd47

Please sign in to comment.