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

Pull Request with Dump File Changes #1

Merged
merged 4 commits into from
Jun 28, 2021
Merged
Show file tree
Hide file tree
Changes from 1 commit
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
1 change: 0 additions & 1 deletion Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,6 @@
#******************************************************************************

SWIFTEST_MODULES = swiftest_globals.f90 \
user.f90 \
swiftest_data_structures.f90 \
lambda_function.f90\
module_swifter.f90 \
Expand Down
4 changes: 2 additions & 2 deletions src/main/swiftest_symba.f90
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,7 @@ program swiftest_symba
100 format(a)
inparfile = trim(adjustl(inparfile))
! read in the param.in file and get simulation parameters
call param%read_from_file(inparfile)
call param%read_from_file(inparfile, symba_plA%helio%swiftest)
param%lmtiny = .true. ! Turn this on for SyMBA

! reads in initial conditions of all massive bodies from input file
Expand Down Expand Up @@ -216,7 +216,7 @@ program swiftest_symba
finish = clock_count / (count_rate * 1.0_DP)
write(*,walltimefmt) finish - start, wallperstep

call param%dump_to_file(t)
call param%dump_to_file(t, symba_plA%helio%swiftest)
call io_dump_pl_symba(npl, symba_plA, param)
call io_dump_tp(ntp, symba_tpA%helio%swiftest)
idump = istep_dump
Expand Down
1 change: 0 additions & 1 deletion src/modules/io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,6 @@ module io
!! Module containing all input/output subroutine interface blocks
use swiftest_globals
use swiftest_data_structures
use user

interface

Expand Down
7 changes: 0 additions & 7 deletions src/modules/module_interfaces.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@
MODULE module_interfaces
use swiftest_globals
use swiftest_data_structures
use user

IMPLICIT NONE

Expand Down Expand Up @@ -1148,7 +1147,6 @@ SUBROUTINE symba_step(t, dt, param,npl, ntp,symba_plA, symba_tpA, &
USE swiftest_data_structures
USE module_helio
USE module_symba
use user
IMPLICIT NONE
TYPE(user_input_parameters), INTENT(INOUT) :: param ! Derived type containing user defined parameters
INTEGER(I4B), INTENT(IN) :: npl, ntp
Expand Down Expand Up @@ -1205,7 +1203,6 @@ SUBROUTINE symba_step_interp(t, npl, nplm, ntp, symba_plA, symba_tpA, &
USE swiftest_data_structures
USE module_helio
USE module_symba
use user
IMPLICIT NONE
INTEGER(I4B), INTENT(IN) :: npl, nplm, ntp, nplplenc, npltpenc
INTEGER(I4B), INTENT(INOUT) :: nmergeadd, nmergesub
Expand All @@ -1226,7 +1223,6 @@ RECURSIVE SUBROUTINE symba_step_recur(t, ireci, npl, nplm, ntp, symba_plA, symba
USE swiftest_data_structures
USE module_helio
USE module_symba
use user
IMPLICIT NONE
INTEGER(I4B), INTENT(IN) :: ireci, npl, nplm, ntp, nplplenc, npltpenc
INTEGER(I4B), INTENT(INOUT) :: nmergeadd, nmergesub
Expand Down Expand Up @@ -1345,7 +1341,6 @@ SUBROUTINE symba_step_eucl(t,dt,param,npl, ntp,symba_plA, symba_tpA, &
USE swiftest_data_structures
USE module_helio
USE module_symba
use user
IMPLICIT NONE
TYPE(user_input_parameters), INTENT(INOUT) :: param ! Derived type containing user defined parameters
INTEGER(I4B), INTENT(IN) :: npl, ntp
Expand All @@ -1367,7 +1362,6 @@ SUBROUTINE symba_step_interp_eucl(t, npl, nplm, ntp, symba_plA, symba_tpA,&
USE swiftest_globals
USE swiftest_data_structures
USE module_symba
USE user
IMPLICIT NONE
INTEGER(I4B), INTENT(IN) :: npl, nplm, ntp, nplplenc, npltpenc
INTEGER(I4B), INTENT(INOUT) :: nmergeadd, nmergesub
Expand Down Expand Up @@ -1402,7 +1396,6 @@ function symba_mergeadd_eoffset(npl, symba_plA, mergeadd_list, mergesub_list, ad
USE swiftest_globals
USE swiftest_data_structures
USE module_symba
USE user
implicit none
integer(I4B), intent(in) :: npl
type(symba_pl), intent(in) :: symba_plA
Expand Down
1 change: 0 additions & 1 deletion src/modules/swiftest.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module swiftest
use swiftest_globals
use swiftest_data_structures
use io
use user
use lambda_function
!$ use omp_lib
implicit none
Expand Down
112 changes: 111 additions & 1 deletion src/modules/swiftest_data_structures.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@ module swiftest_data_structures
!! Definition of data and structures generic to all integrators.
!! Adapted from David E. Kaufmann's Swifter modules: module_swifter.f90
use swiftest_globals
use user
implicit none

type swiftest_particle_info
Expand Down Expand Up @@ -61,6 +60,72 @@ module swiftest_data_structures
procedure :: read_from_file => swiftest_read_pl_in
end type swiftest_pl

type, public :: user_input_parameters
real(DP) :: t0 = 0.0_DP !! Integration start time
real(DP) :: tstop = 0.0_DP !! Integration stop time
real(DP) :: dt = 0.0_DP !! Time step
character(STRMAX) :: inplfile = '' !! Name of input file for planets
character(STRMAX) :: intpfile = '' !! Name of input file for test particles
character(STRMAX) :: in_type = 'ASCII' !! Format of input data files
integer(I4B) :: istep_out = -1 !! Number of time steps between binary outputs
character(STRMAX) :: outfile = '' !! Name of output binary file
character(STRMAX) :: particle_file = '' !! Name of output particle information file
character(STRMAX) :: out_type = REAL4_TYPE!! Binary format of output file
character(STRMAX) :: out_form = 'XV' !! Data to write to output file
character(STRMAX) :: out_stat = 'NEW' !! Open status for output binary file
integer(I4B) :: istep_dump = -1 !! Number of time steps between dumps
real(DP) :: j2rp2 = 0.0_DP !! J2 * R**2 for the Sun
real(DP) :: j4rp4 = 0.0_DP !! J4 * R**4 for the Sun
real(DP) :: rmin = -1.0_DP !! Minimum heliocentric radius for test particle
real(DP) :: rmax = -1.0_DP !! Maximum heliocentric radius for test particle
real(DP) :: rmaxu = -1.0_DP !! Maximum unbound heliocentric radius for test particle
real(DP) :: qmin = -1.0_DP !! Minimum pericenter distance for test particle
character(STRMAX) :: qmin_coord = 'HELIO' !! Coordinate frame to use for qmin
real(DP) :: qmin_alo = -1.0_DP !! Minimum semimajor axis for qmin
real(DP) :: qmin_ahi = -1.0_DP !! Maximum semimajor axis for qmin
character(STRMAX) :: encounter_file = '' !! Name of output file for encounters
real(DP) :: mtiny = 0.0_DP !! Smallest mass that is fully gravitating
character(STRMAX) :: ring_outfile = '' !! Name of output file in ring moons
real(DP) :: MU2KG = -1.0_DP !! Converts mass units to grams
real(DP) :: TU2S = -1.0_DP !! Converts time units to seconds
real(DP) :: DU2M = -1.0_DP !! Converts distance unit to centimeters
integer(I4B), dimension(:), allocatable :: seed !! Random seeds


!Logical flags to turn on or off various features of the code
logical :: lextra_force = .false. !! User defined force function turned on
logical :: lbig_discard = .false. !! Save big bodies on every discard
logical :: lrhill_present = .false. !! Hill's radius is in input file
logical :: lclose = .false. !! Turn on close encounters
logical :: lfragmentation = .false. !! Do fragmentation modeling instead of simple merger.
logical :: lmtiny = .false. !! Use the MTINY variable (Automatically set if running SyMBA)
logical :: lrotation = .false. !! Include rotation states of big bodies
logical :: ltides = .false. !! Include tidal dissipation
logical :: lringmoons = .false. !! Turn on the ringmoons code
logical :: lenergy = .false. !! Track the total energy of the system
logical :: lfirstenergy = .true.
real(DP) :: Eorbit_orig = 0.0_DP
real(DP) :: Mtot_orig = 0.0_DP
real(DP) :: Lmag_orig = 0.0_DP
real(DP), dimension(NDIM) :: Ltot_orig = 0.0_DP
real(DP), dimension(NDIM) :: Lorbit_orig = 0.0_DP
real(DP), dimension(NDIM) :: Lspin_orig = 0.0_DP
logical :: lfirstkick = .true. !! Initiate the first kick in a symplectic step

! Future features not implemented or in development
logical :: lgr = .false. !! Turn on GR
logical :: lyarkovsky = .false. !! Turn on Yarkovsky effect
logical :: lyorp = .false. !! Turn on YORP effect
contains
procedure :: read_from_file => user_read_param_in
procedure :: dump_to_file => user_dump_param
procedure :: udio_reader => user_udio_reader
procedure :: udio_writer => user_udio_writer
!TODO: Figure out if user-defined derived-type io can be made to work properly
!generic :: read(formatted) => udio_reader
!generic :: write(formatted) => udio_writer
end type user_input_parameters

interface

module subroutine swiftest_read_pl_in(self, param)
Expand All @@ -72,6 +137,51 @@ module subroutine swiftest_read_tp_in(self, param)
class(swiftest_tp), intent(inout) :: self !! Swiftest data structure to store massive body initial conditions
type(user_input_parameters), intent(inout) :: param !! Input collection of user-defined parameters
end subroutine swiftest_read_tp_in

module function user_get_token(buffer, ifirst, ilast, ierr) result(token)
character(len=*), intent(in) :: buffer !! Input string buffer
integer(I4B), intent(inout) :: ifirst !! Index of the buffer at which to start the search for a token
integer(I4B), intent(out) :: ilast !! Index of the buffer at the end of the returned token
integer(I4B), intent(out) :: ierr !! Error code
character(len=:),allocatable :: token !! Returned token string
end function user_get_token

!> Interface for type-bound procedure to read in the input parameters from a file
module subroutine user_read_param_in(param, inparfile, swiftest_plA)
class(user_input_parameters),intent(out) :: param !! Input collection of user-defined parameters
character(*), intent(in) :: inparfile !! Parameter input file name (i.e. param.in)
type(swiftest_pl), intent(inout) :: swiftest_plA
end subroutine user_read_param_in

!> Interface for type-bound procedure to write out the user parameters into a dump file in case the run needs to be restarted
module subroutine user_dump_param(param, t, swiftest_plA)
class(user_input_parameters),intent(in) :: param !! Output collection of user-defined parameters
real(DP),intent(in) :: t !! Current simulation time
type(swiftest_pl), intent(inout) :: swiftest_plA
end subroutine user_dump_param

!> Interface for type-bound procedure for user-defined derived-type IO for reading
module subroutine user_udio_reader(param, unit, iotype, v_list, iostat, iomsg, swiftest_plA)
class(user_input_parameters),intent(inout) :: param !! Input collection of user-defined parameters
integer, intent(in) :: unit
character(len=*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(len=*), intent(inout) :: iomsg
type(swiftest_pl), intent(inout) :: swiftest_plA
end subroutine user_udio_reader

!> Interface for type-bound procedure for user-defined derived-type IO for writing
module subroutine user_udio_writer(param, unit, iotype, v_list, iostat, iomsg, swiftest_plA)
class(user_input_parameters),intent(in) :: param !! Output collection of user-defined parameters
integer, intent(in) :: unit
character(len=*), intent(in) :: iotype
integer, intent(in) :: v_list(:)
integer, intent(out) :: iostat
character(len=*), intent(inout) :: iomsg
type(swiftest_pl), intent(inout) :: swiftest_plA
end subroutine user_udio_writer

end interface

contains
Expand Down
Loading