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

Commit

Permalink
Improved handling of restarts. Now the code will check whether or not…
Browse files Browse the repository at this point in the history
… a restarted run would duplicate output frames in the bin.dat file. If so, skip writing until the simulation time is greater than the time of the last frame of the old output.
  • Loading branch information
daminton committed Aug 19, 2021
1 parent 792aa12 commit 7182995
Show file tree
Hide file tree
Showing 3 changed files with 134 additions and 45 deletions.
125 changes: 97 additions & 28 deletions src/io/io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -299,6 +299,45 @@ module function io_get_args(integrator, param_file_name) result(ierr)
end function io_get_args


module function io_get_old_t_final_system(self, param) result(old_t_final)
!! author: David A. Minton
!!
!! Validates the dump file to check whether the dump file initial conditions duplicate the last frame of the binary output.
!!
implicit none
! Arguments
class(swiftest_nbody_system), intent(in) :: self
class(swiftest_parameters), intent(in) :: param
! Result
real(DP) :: old_t_final
! Internals
class(swiftest_nbody_system), allocatable :: tmpsys
class(swiftest_parameters), allocatable :: tmpparam
integer(I4B), parameter :: LUN = 76
integer(I4B) :: ierr, iu = LUN
character(len=STRMAX) :: errmsg

old_t_final = 0.0_DP
allocate(tmpsys, source=self)
allocate(tmpparam, source=param)

ierr = 0
open(unit = iu, file = param%outfile, status = 'OLD', form = 'UNFORMATTED', err = 667, iomsg = errmsg)
do
ierr = tmpsys%read_frame(iu, tmpparam)
if (ierr /= 0) exit
end do
if (is_iostat_end(ierr)) then
old_t_final = tmpparam%t
return
end if

667 continue
write(*,*) "Error reading binary output file. " // trim(adjustl(errmsg))
call util_exit(FAILURE)
end function io_get_old_t_final_system


module function io_get_token(buffer, ifirst, ilast, ierr) result(token)
!! author: David A. Minton
!!
Expand Down Expand Up @@ -814,6 +853,7 @@ module subroutine io_read_in_body(self, param)
character(len=:), allocatable :: infile
real(DP) :: t
character(STRMAX) :: errmsg
integer(I4B) :: ierr

! Select the appropriate polymorphic class (test particle or massive body)
select type(self)
Expand All @@ -839,15 +879,15 @@ module subroutine io_read_in_body(self, param)
end select

call self%setup(nbody, param)
ierr = 0
if (nbody > 0) then
call self%read_frame(iu, param)
ierr = self%read_frame(iu, param)
self%status(:) = ACTIVE
self%lmask(:) = .true.
end if

close(iu, err = 667, iomsg = errmsg)

return
if (ierr == 0) return

667 continue
write(*,*) 'Error reading in initial conditions file: ',trim(adjustl(errmsg))
Expand All @@ -870,6 +910,7 @@ module subroutine io_read_in_cb(self, param)
integer(I4B), parameter :: LUN = 7 !! Unit number of input file
integer(I4B) :: iu = LUN
character(len=STRMAX) :: errmsg
integer(I4B) :: ierr

if (param%in_type == 'ASCII') then
open(unit = iu, file = param%incbfile, status = 'old', form = 'FORMATTED', err = 667, iomsg = errmsg)
Expand All @@ -885,20 +926,22 @@ module subroutine io_read_in_cb(self, param)
end if
else
open(unit = iu, file = param%incbfile, status = 'old', form = 'UNFORMATTED', err = 667, iomsg = errmsg)
call self%read_frame(iu, param)
ierr = self%read_frame(iu, param)
end if
close(iu, err = 667, iomsg = errmsg)

if (self%j2rp2 /= 0.0_DP) param%loblatecb = .true.
if (param%rmin < 0.0) param%rmin = self%radius

select type(cb => self)
class is (symba_cb)
cb%M0 = cb%mass
cb%R0 = cb%radius
cb%L0(:) = cb%Ip(3) * cb%mass * cb%radius**2 * cb%rot(:)
end select

if (ierr == 0) then

if (self%j2rp2 /= 0.0_DP) param%loblatecb = .true.
if (param%rmin < 0.0) param%rmin = self%radius

select type(cb => self)
class is (symba_cb)
cb%M0 = cb%mass
cb%R0 = cb%radius
cb%L0(:) = cb%Ip(3) * cb%mass * cb%radius**2 * cb%rot(:)
end select
end if
return

667 continue
Expand Down Expand Up @@ -958,7 +1001,7 @@ function io_read_encounter(t, id1, id2, Gmass1, Gmass2, radius1, radius2, &
end function io_read_encounter


module subroutine io_read_frame_body(self, iu, param)
module function io_read_frame_body(self, iu, param) result(ierr)
!! author: David A. Minton
!!
!! Reads a frame of output of either test particle or massive body data from a binary output file
Expand All @@ -970,11 +1013,15 @@ module subroutine io_read_frame_body(self, iu, param)
class(swiftest_body), intent(inout) :: self !! Swiftest particle 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
! Result
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
! Internals
character(len=STRMAX) :: errmsg
integer(I4B) :: i
real(QP) :: val

if (self%nbody == 0) return

if ((param%in_form /= EL) .and. (param%in_form /= XV)) then
write(errmsg, *) trim(adjustl(param%in_form)) // " is not a recognized format code for input files."
goto 667
Expand Down Expand Up @@ -1074,6 +1121,7 @@ module subroutine io_read_frame_body(self, iu, param)
end select
end associate

ierr = 0
return

667 continue
Expand All @@ -1086,10 +1134,10 @@ module subroutine io_read_frame_body(self, iu, param)
write(*,*) "Error reading body file: " // trim(adjustl(errmsg))
end select
call util_exit(FAILURE)
end subroutine io_read_frame_body
end function io_read_frame_body


module subroutine io_read_frame_cb(self, iu, param)
module function io_read_frame_cb(self, iu, param) result(ierr)
!! author: David A. Minton
!!
!! Reads a frame of output of central body data to the binary output file
Expand All @@ -1101,6 +1149,8 @@ module subroutine io_read_frame_cb(self, iu, param)
class(swiftest_cb), intent(inout) :: self !! Swiftest central body 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
! Result
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
! Internals
character(len=STRMAX) :: errmsg

Expand All @@ -1123,15 +1173,17 @@ module subroutine io_read_frame_cb(self, iu, param)
read(iu, err = 667, iomsg = errmsg) self%k2
read(iu, err = 667, iomsg = errmsg) self%Q
end if

ierr = 0
return

667 continue
write(*,*) "Error reading central body file: " // trim(adjustl(errmsg))
call util_exit(FAILURE)
end subroutine io_read_frame_cb
end function io_read_frame_cb


module subroutine io_read_frame_system(self, iu, param)
module function io_read_frame_system(self, iu, param) result(ierr)
!! author: The Purdue Swiftest Team - David A. Minton, Carlisle A. Wishard, Jennifer L.L. Pouplin, and Jacob R. Elliott
!!
!! Read a frame (header plus records for each massive body and active test particle) from a output binary file
Expand All @@ -1140,18 +1192,34 @@ module subroutine io_read_frame_system(self, iu, param)
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system 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
! Result
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
! Internals
character(len=STRMAX) :: errmsg
integer(I4B) :: ierr

ierr = io_read_hdr(iu, param%t, self%pl%nbody, self%tp%nbody, param%out_form, param%out_type)
if (is_iostat_end(ierr)) return ! Reached the end of the frames

if (ierr /= 0) then
write(errmsg, *) "Cannot read header."
write(errmsg, *) "Cannot read frame header."
goto 667
end if
call self%cb%read_frame(iu, param)
call self%pl%read_frame(iu, param)
call self%tp%read_frame(iu, param)
ierr = self%cb%read_frame(iu, param)
if (ierr /= 0) then
write(errmsg, *) "Cannot read central body frame."
goto 667
end if
ierr = self%pl%read_frame(iu, param)
if (ierr /= 0) then
write(errmsg, *) "Cannot read massive body frame."
goto 667
end if
ierr = self%tp%read_frame(iu, param)
if (ierr /= 0) then
write(errmsg, *) "Cannot read test particle frame."
goto 667
end if

if (param%in_form == EL) then
call self%pl%el2xv(self%cb)
call self%tp%el2xv(self%cb)
Expand All @@ -1161,8 +1229,7 @@ module subroutine io_read_frame_system(self, iu, param)

667 continue
write(*,*) "Error reading system frame: " // trim(adjustl(errmsg))
call util_exit(FAILURE)
end subroutine io_read_frame_system
end function io_read_frame_system


function io_read_hdr(iu, t, npl, ntp, out_form, out_type) result(ierr)
Expand All @@ -1187,10 +1254,10 @@ function io_read_hdr(iu, t, npl, ntp, out_form, out_type) result(ierr)

select case (out_type)
case (REAL4_TYPE)
read(iu, iostat = ierr, err = 667, iomsg = errmsg) ttmp
read(iu, iostat = ierr, err = 667, iomsg = errmsg, end = 333) ttmp
t = ttmp
case (REAL8_TYPE)
read(iu, iostat = ierr, err = 667, iomsg = errmsg) t
read(iu, iostat = ierr, err = 667, iomsg = errmsg, end = 333) t
case default
write(errmsg,*) trim(adjustl(out_type)) // ' is an unrecognized file type'
ierr = -1
Expand All @@ -1203,6 +1270,8 @@ function io_read_hdr(iu, t, npl, ntp, out_form, out_type) result(ierr)

667 continue
write(*,*) "Error reading header: " // trim(adjustl(errmsg))
333 continue
return

return
end function io_read_hdr
Expand Down
14 changes: 11 additions & 3 deletions src/main/swiftest_driver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ program swiftest_driver
integer(I8B) :: iout !! Output cadence counter
integer(I8B) :: nloops !! Number of steps to take in the simulation
integer(I4B) :: iu !! Unit number of binary file
real(DP) :: old_t_final = 0.0_DP !! Output time at which writing should start, in order to prevent duplicate lines being written for restarts

ierr = io_get_args(integrator, param_file_name)
if (ierr /= 0) then
Expand Down Expand Up @@ -50,8 +51,15 @@ program swiftest_driver
iout = istep_out
idump = istep_dump
nloops = ceiling(tstop / dt, kind=I8B)
if (istep_out > 0 .and. (.not.param%lrestart)) call nbody_system%write_frame(iu, param)
if (.not.param%lrestart) call nbody_system%dump(param)
! Prevent duplicate frames from being written if this is a restarted run
if (param%lrestart) then
old_t_final = nbody_system%get_old_t_final(param)
else
old_t_final = t0
if (istep_out > 0) call nbody_system%write_frame(iu, param)
call nbody_system%dump(param)
end if


!> Define the maximum number of threads
nthreads = 1 ! In the *serial* case
Expand All @@ -73,7 +81,7 @@ program swiftest_driver
if (istep_out > 0) then
iout = iout - 1
if (iout == 0) then
call nbody_system%write_frame(iu, param)
if (t > old_t_final) call nbody_system%write_frame(iu, param)
iout = istep_out
end if
end if
Expand Down
40 changes: 26 additions & 14 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -306,6 +306,7 @@ module swiftest_classes
procedure :: discard => discard_system !! Perform a discard step on the system
procedure :: conservation_report => io_conservation_report !! Compute energy and momentum and print out the change with time
procedure :: dump => io_dump_system !! Dump the state of the system to a file
procedure :: get_old_t_final => io_get_old_t_final_system !! Validates the dump file to check whether the dump file initial conditions duplicate the last frame of the binary output.
procedure :: read_frame => io_read_frame_system !! Read in a frame of input data from file
procedure :: write_discard => io_write_discard !! Write out information about discarded test particles
procedure :: write_frame => io_write_frame_system !! Append a frame of output data to file
Expand Down Expand Up @@ -367,12 +368,13 @@ subroutine abstract_kick_body(self, system, param, t, dt, lbeg)
logical, intent(in) :: lbeg !! Logical flag indicating whether this is the beginning of the half step or not.
end subroutine abstract_kick_body

subroutine abstract_read_frame(self, iu, param)
function abstract_read_frame(self, iu, param) result(ierr)
import DP, I4B, swiftest_base, swiftest_parameters
class(swiftest_base), intent(inout) :: self !! Swiftest base 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
end subroutine abstract_read_frame
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
end function abstract_read_frame

subroutine abstract_set_mu(self, cb)
import swiftest_body, swiftest_cb
Expand Down Expand Up @@ -572,6 +574,13 @@ module function io_get_args(integrator, param_file_name) result(ierr)
integer(I4B) :: ierr !! I/O error code
end function io_get_args

module function io_get_old_t_final_system(self, param) result(old_t_final)
implicit none
class(swiftest_nbody_system), intent(in) :: self
class(swiftest_parameters), intent(in) :: param
real(DP) :: old_t_final
end function io_get_old_t_final_system

module function io_get_token(buffer, ifirst, ilast, ierr) result(token)
implicit none
character(len=*), intent(in) :: buffer !! Input string buffer
Expand Down Expand Up @@ -621,26 +630,29 @@ module subroutine io_read_in_param(self, param_file_name)
character(len=*), intent(in) :: param_file_name !! Parameter input file name (i.e. param.in)
end subroutine io_read_in_param

module subroutine io_read_frame_body(self, iu, param)
module function io_read_frame_body(self, iu, param) result(ierr)
implicit none
class(swiftest_body), intent(inout) :: self !! Swiftest body 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
end subroutine io_read_frame_body
class(swiftest_body), intent(inout) :: self !! Swiftest body 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
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
end function io_read_frame_body

module subroutine io_read_frame_cb(self, iu, param)
module function io_read_frame_cb(self, iu, param) result(ierr)
implicit none
class(swiftest_cb), intent(inout) :: self !! Swiftest central body 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
end subroutine io_read_frame_cb
class(swiftest_cb), intent(inout) :: self !! Swiftest central body 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
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
end function io_read_frame_cb

module subroutine io_read_frame_system(self, iu, param)
module function io_read_frame_system(self, iu, param) result(ierr)
implicit none
class(swiftest_nbody_system),intent(inout) :: self !! Swiftest system 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
end subroutine io_read_frame_system
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
end function io_read_frame_system

module subroutine io_write_discard(self, param)
implicit none
Expand Down

0 comments on commit 7182995

Please sign in to comment.