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

Commit

Permalink
Refactored to allow param to be inout in kick subroutines
Browse files Browse the repository at this point in the history
  • Loading branch information
daminton committed Sep 20, 2021
1 parent 22be994 commit 7199148
Show file tree
Hide file tree
Showing 14 changed files with 75 additions and 60 deletions.
4 changes: 2 additions & 2 deletions src/fraggle/fraggle_placeholder.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module subroutine fraggle_placeholder_accel(self, system, param, t, lbeg)
implicit none
class(fraggle_fragments), intent(inout) :: self !! Fraggle fragment system object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current simulation time
logical, intent(in) :: lbeg !! Optional argument that determines whether or not this is the beginning or end of the step
write(*,*) "The type-bound procedure 'accel' is not defined for type fraggle_fragments"
Expand All @@ -19,7 +19,7 @@ module subroutine fraggle_placeholder_kick(self, system, param, t, dt, lbeg)
implicit none
class(fraggle_fragments), intent(inout) :: self !! Fraggle fragment system object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system objec
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand Down
8 changes: 4 additions & 4 deletions src/helio/helio_kick.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ module subroutine helio_kick_getacch_pl(self, system, param, t, lbeg)
! Arguments
class(helio_pl), intent(inout) :: self !! Helio massive body particle data structure
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current simulation time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step

Expand Down Expand Up @@ -56,7 +56,7 @@ module subroutine helio_kick_getacch_tp(self, system, param, t, lbeg)
! Arguments
class(helio_tp), intent(inout) :: self !! Helio test particle data structure
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step

Expand Down Expand Up @@ -89,7 +89,7 @@ module subroutine helio_kick_vb_pl(self, system, param, t, dt, lbeg)
! Arguments
class(helio_pl), intent(inout) :: self !! Swiftest generic body object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand Down Expand Up @@ -128,7 +128,7 @@ module subroutine helio_kick_vb_tp(self, system, param, t, dt, lbeg)
! Arguments
class(helio_tp), intent(inout) :: self !! Swiftest generic body object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand Down
10 changes: 8 additions & 2 deletions src/kick/kick.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,14 @@ module subroutine kick_getacch_int_pl(self, param)
implicit none
! Arguments
class(swiftest_pl), intent(inout) :: self !! Swiftest massive body object
class(swiftest_parameters), intent(in) :: param !! Current swiftest run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current swiftest run configuration parameters
! Internals
type(interaction_timer), save :: itimer
logical, save :: lfirst

if (lfirst) then
call itimer%reset(param)
end if
if (param%lflatten_interactions) then
call kick_getacch_int_all_flat_pl(self%nbody, self%nplpl, self%k_plpl, self%xh, self%Gmass, self%radius, self%ah)
else
Expand All @@ -34,7 +40,7 @@ module subroutine kick_getacch_int_tp(self, param, GMpl, xhp, npl)
implicit none
! Arguments
class(swiftest_tp), intent(inout) :: self !! Swiftest test particle object
class(swiftest_parameters), intent(in) :: param !! Current swiftest run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current swiftest run configuration parameters
real(DP), dimension(:), intent(in) :: GMpl !! Massive body masses
real(DP), dimension(:,:), intent(in) :: xhp !! Massive body position vectors
integer(I4B), intent(in) :: npl !! Number of active massive bodies
Expand Down
6 changes: 3 additions & 3 deletions src/main/swiftest_driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ program swiftest_driver
!$ write(*,'(a)') ' OpenMP parameters:'
!$ write(*,'(a)') ' ------------------'
!$ write(*,'(a,i3,/)') ' Number of threads = ', nthreads
call timer%reset()
call timer%reset(param)
write(*, *) " *************** Main Loop *************** "
do iloop = 1, nloops
!> Step the system forward in time
Expand All @@ -86,9 +86,9 @@ program swiftest_driver
iout = iout - 1
if (iout == 0) then
ioutput = ioutput_t0 + iloop / istep_out
call timer%finish(nsubsteps=istep_out, message="Integration steps:")
call timer%finish(nsubsteps=istep_out, message="Integration steps:", param=param)
if (t > old_t_final) call nbody_system%write_frame(param)
call timer%finish(nsubsteps=1, message="File I/O: ")
call timer%finish(nsubsteps=1, message="File I/O: ", param=param)
iout = istep_out
end if
end if
Expand Down
4 changes: 2 additions & 2 deletions src/modules/fraggle_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,7 @@ module subroutine fraggle_placeholder_accel(self, system, param, t, lbeg)
implicit none
class(fraggle_fragments), intent(inout) :: self !! Fraggle fragment system object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current simulation time
logical, intent(in) :: lbeg !! Optional argument that determines whether or not this is the beginning or end of the step
end subroutine fraggle_placeholder_accel
Expand All @@ -152,7 +152,7 @@ module subroutine fraggle_placeholder_kick(self, system, param, t, dt, lbeg)
implicit none
class(fraggle_fragments), intent(inout) :: self !! Fraggle fragment system object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system objec
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand Down
10 changes: 5 additions & 5 deletions src/modules/helio_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ end subroutine helio_gr_p4_pl
module pure subroutine helio_gr_p4_tp(self, param, dt)
use swiftest_classes, only : swiftest_parameters
implicit none
class(helio_tp), intent(inout) :: self !! Swiftest particle object
class(helio_tp), intent(inout) :: self !! Swiftest particle object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
real(DP), intent(in) :: dt !! Step size
end subroutine helio_gr_p4_tp
Expand All @@ -140,7 +140,7 @@ module subroutine helio_kick_getacch_pl(self, system, param, t, lbeg)
implicit none
class(helio_pl), intent(inout) :: self !! Helio massive body object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current simulation time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step
end subroutine helio_kick_getacch_pl
Expand All @@ -150,7 +150,7 @@ module subroutine helio_kick_getacch_tp(self, system, param, t, lbeg)
implicit none
class(helio_tp), intent(inout) :: self !! Helio test particle object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step
end subroutine helio_kick_getacch_tp
Expand All @@ -160,7 +160,7 @@ module subroutine helio_kick_vb_pl(self, system, param, t, dt, lbeg)
implicit none
class(helio_pl), intent(inout) :: self !! Helio massive body object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand All @@ -171,7 +171,7 @@ module subroutine helio_kick_vb_tp(self, system, param, t, dt, lbeg)
implicit none
class(helio_tp), intent(inout) :: self !! Helio test particle object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand Down
2 changes: 1 addition & 1 deletion src/modules/rmvs_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ module subroutine rmvs_kick_getacch_tp(self, system, param, t, lbeg)
implicit none
class(rmvs_tp), intent(inout) :: self !! RMVS test particle data structure
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest central body particle data structuree
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step
end subroutine rmvs_kick_getacch_tp
Expand Down
8 changes: 4 additions & 4 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -463,7 +463,7 @@ subroutine abstract_accel(self, system, param, t, lbeg)
import swiftest_body, swiftest_nbody_system, swiftest_parameters, DP
class(swiftest_body), intent(inout) :: self !! Swiftest body data structure
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current simulation time
logical, intent(in) :: lbeg !! Optional argument that determines whether or not this is the beginning or end of the step
end subroutine abstract_accel
Expand All @@ -473,7 +473,7 @@ subroutine abstract_kick_body(self, system, param, t, dt, lbeg)
implicit none
class(swiftest_body), intent(inout) :: self !! Swiftest generic body object
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system objec
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
real(DP), intent(in) :: dt !! Stepsize
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
Expand Down Expand Up @@ -903,13 +903,13 @@ end subroutine io_write_hdr_system
module subroutine kick_getacch_int_pl(self, param)
implicit none
class(swiftest_pl), intent(inout) :: self !! Swiftest massive body object
class(swiftest_parameters), intent(in) :: param !! Current swiftest run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current swiftest run configuration parameters
end subroutine kick_getacch_int_pl

module subroutine kick_getacch_int_tp(self, param, GMpl, xhp, npl)
implicit none
class(swiftest_tp), intent(inout) :: self !! Swiftest test particle object
class(swiftest_parameters), intent(in) :: param !! Current swiftest run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current swiftest run configuration parameters
real(DP), dimension(:), intent(in) :: GMpl !! Massive body masses
real(DP), dimension(:,:), intent(in) :: xhp !! Massive body position vectors
integer(I4B), intent(in) :: npl !! Number of active massive bodies
Expand Down
8 changes: 4 additions & 4 deletions src/modules/symba_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -355,15 +355,15 @@ end subroutine symba_io_write_discard
module subroutine symba_kick_getacch_int_pl(self, param)
implicit none
class(symba_pl), intent(inout) :: self !! SyMBA massive body object
class(swiftest_parameters), intent(in) :: param !! Current swiftest run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current swiftest run configuration parameters
end subroutine symba_kick_getacch_int_pl

module subroutine symba_kick_getacch_pl(self, system, param, t, lbeg)
use swiftest_classes, only : swiftest_nbody_system, swiftest_parameters
implicit none
class(symba_pl), intent(inout) :: self !! SyMBA massive body particle data structure
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current simulation time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step
end subroutine symba_kick_getacch_pl
Expand All @@ -373,14 +373,14 @@ module subroutine symba_kick_getacch_tp(self, system, param, t, lbeg)
implicit none
class(symba_tp), intent(inout) :: self !! SyMBA test particle data structure
class(swiftest_nbody_system), intent(inout) :: system !! Swiftest nbody system object
class(swiftest_parameters), intent(in) :: param !! Current run configuration parameters
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
real(DP), intent(in) :: t !! Current time
logical, intent(in) :: lbeg !! Logical flag that determines whether or not this is the beginning or end of the step
end subroutine symba_kick_getacch_tp

module subroutine symba_kick_encounter(self, system, dt, irec, sgn)
implicit none
class(symba_encounter), intent(in) :: self !! SyMBA pl-tp encounter list object
class(symba_encounter), intent(in) :: self !! SyMBA pl-tp encounter list object
class(symba_nbody_system), intent(inout) :: system !! SyMBA nbody system object
real(DP), intent(in) :: dt !! step size
integer(I4B), intent(in) :: irec !! Current recursion level
Expand Down
Loading

0 comments on commit 7199148

Please sign in to comment.