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

Commit

Permalink
Improved the efficiency of coarray test particles by allowing each im…
Browse files Browse the repository at this point in the history
…age to write to file independently, and to only do a distribute/collect cycle if the system gets too far out of balance
  • Loading branch information
daminton committed Apr 24, 2023
1 parent 68c7596 commit 9cf4bcb
Show file tree
Hide file tree
Showing 4 changed files with 187 additions and 77 deletions.
38 changes: 34 additions & 4 deletions src/swiftest/swiftest_coarray.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,37 @@
use coarray
contains


module subroutine swiftest_coarray_balance_system(nbody_system, param)
!! author: David A. Minton
!!
!! Checks whether or not the system needs to be rebalance. Rebalancing occurs when the difference between the number of test particles between the
!! image with the smallest and largest number of test particles is larger than the number of images
implicit none
! Arguments
class(swiftest_nbody_system), intent(inout) :: nbody_system !! Swiftest nbody system
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
! Internals
integer(I4B), codimension[:], allocatable :: ntp
integer(I4B) :: img,ntp_min, ntp_max

allocate(ntp[*])
ntp = nbody_system%tp%nbody
sync all
ntp_min = huge(1)
ntp_max = 0
do img = 1, num_images()
if (ntp[img] < ntp_min) ntp_min = ntp[img]
if (ntp[img] > ntp_max) ntp_max = ntp[img]
end do
if (ntp_max - ntp_min >= num_images()) then
call nbody_system%coarray_collect(param)
call nbody_system%coarray_distribute(param)
end if

return
end subroutine swiftest_coarray_balance_system

module subroutine swiftest_coarray_coclone_body(self)
!! author: David A. Minton
!!
Expand Down Expand Up @@ -451,13 +482,11 @@ module subroutine swiftest_coarray_collect_system(nbody_system, param)
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
! Internals
integer(I4B) :: i,j
integer(I4B), codimension[*], save :: ntp
class(swiftest_tp), allocatable, codimension[:] :: cotp
character(len=NAMELEN) :: image_num_char

if (.not.param%lcoarray) return

sync all
if (this_image() == 1) then
write(image_num_char,*) num_images()
write(param%display_unit,*) " Collecting test particles from " // trim(adjustl(image_num_char)) // " images."
Expand Down Expand Up @@ -486,18 +515,18 @@ module subroutine swiftest_coarray_distribute_system(nbody_system, param)
integer(I4B) :: i, istart, iend, ntot, num_per_image, ncopy
class(swiftest_tp), allocatable :: tp
logical, dimension(:), allocatable :: lspill_list
integer(I4B), codimension[*], save :: ntp
integer(I4B), codimension[:], allocatable :: ntp
character(len=NAMELEN) :: image_num_char
class(swiftest_tp), allocatable, codimension[:] :: cotp
class(swiftest_tp), allocatable :: tmp

if (.not.param%lcoarray) return
sync all
if (this_image() == 1) then
write(image_num_char,*) num_images()
write(param%display_unit,*) " Distributing test particles across " // trim(adjustl(image_num_char)) // " images."
end if

allocate(ntp[*])
ntp = nbody_system%tp%nbody
sync all
ntot = ntp[1]
Expand Down Expand Up @@ -529,4 +558,5 @@ module subroutine swiftest_coarray_distribute_system(nbody_system, param)
return
end subroutine swiftest_coarray_distribute_system


end submodule s_swiftest_coarray
70 changes: 28 additions & 42 deletions src/swiftest/swiftest_driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -96,20 +96,20 @@ program swiftest_driver
#endif

#ifdef COARRAY
! The following line lets us read in the input files one image at a time
! The following line lets us read in the input files one image at a time. Letting each image read the input in is faster than broadcasting all of the data
if (param%lcoarray .and. (this_image() /= 1)) sync images(this_image() - 1)
#endif
call nbody_system%initialize(system_history, param)
#ifdef COARRAY
if (param%lcoarray .and. (this_image() < num_images())) sync images(this_image() + 1)

if (this_image() == 1) then
! Distribute test particles to the various images
call nbody_system%coarray_distribute(param)
#endif
! If this is a new run, compute energy initial conditions (if energy tracking is turned on) and write the initial conditions to file.
call nbody_system%display_run_information(param, integration_timer, phase="first")

#ifdef COARRAY
end if ! this_image() == 1
#endif
! If this is a new run, compute energy initial conditions (if energy tracking is turned on) and write the initial conditions to file.
call nbody_system%display_run_information(param, integration_timer, phase="first")

if (param%lenergy) then
if (param%lrestart) then
call nbody_system%get_t0_values(system_history%nc, param)
Expand All @@ -118,21 +118,10 @@ program swiftest_driver
end if
call nbody_system%conservation_report(param, lterminal=.true.)
end if

call system_history%take_snapshot(param,nbody_system)

#ifdef COARRAY
if (this_image() == 1) then
#endif
call nbody_system%dump(param, system_history)
#ifdef COARRAY
end if ! this_image() == 1
#endif
call nbody_system%dump(param, system_history)

#ifdef COARRAY
if (param%lcoarray .and. (this_image() < num_images())) sync images(this_image() + 1)
! Distribute test particles to the various images
call nbody_system%coarray_distribute(param)
#endif
do iloop = istart, nloops
!> Step the nbody_system forward in time
call integration_timer%start()
Expand All @@ -154,40 +143,37 @@ program swiftest_driver
nout = nout + 1
istep = floor(istep_out * fstep_out**nout, kind=I4B)
end if

call system_history%take_snapshot(param,nbody_system)

if (idump == dump_cadence) then
idump = 0
call nbody_system%dump(param, system_history)
end if
#ifdef COARRAY
call nbody_system%coarray_collect(param)
if (this_image() == 1) then
#endif
call system_history%take_snapshot(param,nbody_system)

if (idump == dump_cadence) then
idump = 0
call nbody_system%dump(param, system_history)
end if

call integration_timer%report(message="Integration steps:", unit=display_unit)
call nbody_system%display_run_information(param, integration_timer)
call integration_timer%reset()
#ifdef COARRAY
end if !(this_image() == 1)
#endif
call nbody_system%display_run_information(param, integration_timer)
call integration_timer%reset()
#ifdef COARRAY
if (this_image() == 1) then
#endif
if (param%lenergy) call nbody_system%conservation_report(param, lterminal=.true.)
#ifdef COARRAY
end if
call nbody_system%coarray_distribute(param)
end if ! (this_image() == 1)
call nbody_system%coarray_balance(param)
#endif
end if
end if

end do
! Dump any remaining history if it exists
#ifdef COARRAY
call nbody_system%coarray_collect(param)
if (this_image() == 1) then
#endif
call nbody_system%dump(param, system_history)
call nbody_system%display_run_information(param, integration_timer, phase="last")
#ifdef COARRAY
end if ! this_image() == 1
#endif

call nbody_system%dump(param, system_history)
call nbody_system%display_run_information(param, integration_timer, phase="last")
end associate

#ifdef COARRAY
Expand Down
144 changes: 113 additions & 31 deletions src/swiftest/swiftest_io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -223,12 +223,26 @@ module subroutine swiftest_io_display_run_information(self, param, integration_t
type(progress_bar), save :: pbar !! Object used to print out a progress bar
character(len=64) :: pbarmessage
character(*), parameter :: symbacompactfmt = '(";NPLM",ES22.15,$)'
#ifdef COARRAY
character(*), parameter :: statusfmt = '("Image: ",I4, "; Time = ", ES12.5, "; fraction done = ", F6.3, ' // &
'"; Number of active pl, tp = ", I6, ", ", I6)'
character(*), parameter :: symbastatfmt = '("Image: ",I4, "; Image: Time = ", ES12.5, "; fraction done = ", F6.3, ' // &
'"; Number of active pl, plm, tp = ", I6, ", ", I6, ", ", I6)'
#else
character(*), parameter :: statusfmt = '("Time = ", ES12.5, "; fraction done = ", F6.3, ' // &
'"; Number of active pl, tp = ", I6, ", ", I6)'
character(*), parameter :: symbastatfmt = '("Time = ", ES12.5, "; fraction done = ", F6.3, ' // &
'"; Number of active pl, plm, tp = ", I6, ", ", I6, ", ", I6)'
#endif
character(*), parameter :: pbarfmt = '("Time = ", ES12.5," of ",ES12.5)'

! The following will syncronize the images so that they report in order, and only write to file one at at ime


#ifdef COARRAY
! The following line lets us read in the input files one image at a time
if (param%lcoarray .and. (this_image() /= 1)) sync images(this_image() - 1)
#endif
phase_val = 1
if (present(phase)) then
if (phase == "first") then
Expand All @@ -240,36 +254,68 @@ module subroutine swiftest_io_display_run_information(self, param, integration_t

tfrac = (self%t - param%t0) / (param%tstop - param%t0)

if (phase_val == 0) then
if (param%lrestart) then
write(param%display_unit, *) " *************** Swiftest restart " // trim(adjustl(param%integrator)) // " *************** "
else
write(param%display_unit, *) " *************** Swiftest start " // trim(adjustl(param%integrator)) // " *************** "
end if
if (param%display_style == "PROGRESS") then
call pbar%reset(param%nloops)
else if (param%display_style == "COMPACT") then
write(*,*) "SWIFTEST START " // trim(adjustl(param%integrator))
#ifdef COARRAY
if (this_image() == 1) then
#endif
if (phase_val == 0) then
if (param%lrestart) then
write(param%display_unit, *) " *************** Swiftest restart " // trim(adjustl(param%integrator)) // " *************** "
else
write(param%display_unit, *) " *************** Swiftest start " // trim(adjustl(param%integrator)) // " *************** "
end if
if (param%display_style == "PROGRESS") then
call pbar%reset(param%nloops)
else if (param%display_style == "COMPACT") then
write(param%display_unit,*) "SWIFTEST START " // trim(adjustl(param%integrator))
end if
end if
end if
#ifdef COARRAY
end if !(this_image() == 1)
#endif

if (param%display_style == "PROGRESS") then
write(pbarmessage,fmt=pbarfmt) self%t, param%tstop
call pbar%update(1_I8B,message=pbarmessage)
#ifdef COARRAY
if (this_image() == 1) then
#endif
write(pbarmessage,fmt=pbarfmt) self%t, param%tstop
call pbar%update(1_I8B,message=pbarmessage)
#ifdef COARRAY
end if !(this_image() == 1)
#endif
else if (param%display_style == "COMPACT") then
call self%compact_output(param,integration_timer)
end if

if (self%pl%nplm > 0) then
#ifdef COARRAY
write(param%display_unit, symbastatfmt) this_image(),self%t, tfrac, self%pl%nbody, self%pl%nplm, self%tp%nbody
#else
write(param%display_unit, symbastatfmt) self%t, tfrac, self%pl%nbody, self%pl%nplm, self%tp%nbody
#endif
else
#ifdef COARRAY
write(param%display_unit, statusfmt) this_image(),self%t, tfrac, self%pl%nbody, self%tp%nbody
#else
write(param%display_unit, statusfmt) self%t, tfrac, self%pl%nbody, self%tp%nbody
#endif
end if

if (phase_val == -1) then
write(param%display_unit, *)" *************** Swiftest stop " // trim(adjustl(param%integrator)) // " *************** "
if (param%display_style == "COMPACT") write(*,*) "SWIFTEST STOP" // trim(adjustl(param%integrator))
end if
#ifdef COARRAY
if (this_image() == num_images()) then
#endif
if (phase_val == -1) then
write(param%display_unit, *)" *************** Swiftest stop " // trim(adjustl(param%integrator)) // " *************** "
if (param%display_style == "COMPACT") write(*,*) "SWIFTEST STOP" // trim(adjustl(param%integrator))
end if
#ifdef COARRAY
end if ! this_image() == num_images()

! Allow the other images to report
if (param%lcoarray .and. (this_image() < num_images())) sync images(this_image() + 1)

! Wait for everyone to catch up
sync all
#endif

return
end subroutine swiftest_io_display_run_information
Expand Down Expand Up @@ -330,19 +376,24 @@ module subroutine swiftest_io_dump_system(self, param, system_history)
! Dump the nbody_system history to file
call system_history%dump(param)

allocate(param_restart, source=param)
param_restart%in_form = "XV"
param_restart%out_stat = 'APPEND'
param_restart%in_type = "NETCDF_DOUBLE"
param_restart%nc_in = param%outfile
param_restart%lrestart = .true.
param_restart%tstart = self%t
param_file_name = trim(adjustl(PARAM_RESTART_FILE))
call param_restart%dump(param_file_name)
write(time_text,'(I0.20)') param%iloop
param_file_name = "param." // trim(adjustl(time_text)) // ".in"
call param_restart%dump(param_file_name)

#ifdef COARRAY
if (this_image() == 1) then
#endif
allocate(param_restart, source=param)
param_restart%in_form = "XV"
param_restart%out_stat = 'APPEND'
param_restart%in_type = "NETCDF_DOUBLE"
param_restart%nc_in = param%outfile
param_restart%lrestart = .true.
param_restart%tstart = self%t
param_file_name = trim(adjustl(PARAM_RESTART_FILE))
call param_restart%dump(param_file_name)
write(time_text,'(I0.20)') param%iloop
param_file_name = "param." // trim(adjustl(time_text)) // ".in"
call param_restart%dump(param_file_name)
#ifdef COARRAY
end if ! (this_image() == 1)
#endif
return
end subroutine swiftest_io_dump_system

Expand All @@ -360,22 +411,53 @@ module subroutine swiftest_io_dump_storage(self, param)
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
! Internals
integer(I4B) :: i
#ifdef COARRAY
integer(I4B) :: img, tslot
integer(I4B), dimension(self%iframe) :: ntp_tot
integer(I4B), codimension[:], allocatable :: ntp
#endif

if (self%iframe == 0) return
call self%make_index_map()
associate(nc => self%nc)
call nc%open(param)
#ifdef COARRAY
! Get the sum of all test particles across snapshots from all images
allocate(ntp[*])
ntp_tot(:) = 0
do i = 1, self%iframe
if (allocated(self%frame(i)%item)) then
select type(nbody_system => self%frame(i)%item)
class is (swiftest_nbody_system)
ntp = nbody_system%tp%nbody
sync all
do img = 1, num_images()
ntp_tot(i) = ntp_tot(i) + ntp[img]
end do
end select
end if
end do

critical
#endif
call nc%open(param)
do i = 1, self%iframe
if (allocated(self%frame(i)%item)) then
select type(nbody_system => self%frame(i)%item)
class is (swiftest_nbody_system)
call nbody_system%write_frame(nc, param)
#ifdef COARRAY
! Record the correct number of test particles from all images
call nc%find_tslot(nbody_system%t, tslot)
call netcdf_io_check( nf90_put_var(nc%id, nc%ntp_varid, ntp_tot(i), start=[tslot]), "swiftest_io_dump_storage nf90_put_var ntp_varid" )
#endif COARRAY
end select
deallocate(self%frame(i)%item)
end if
end do
call nc%close()
#ifdef COARRAY
end critical
#endif
end associate
call self%reset()
return
Expand Down
Loading

0 comments on commit 9cf4bcb

Please sign in to comment.