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

Commit

Permalink
Refactored nciu to nc for simplicity
Browse files Browse the repository at this point in the history
  • Loading branch information
daminton committed Dec 6, 2022
1 parent b9a0570 commit 77478cf
Show file tree
Hide file tree
Showing 8 changed files with 398 additions and 397 deletions.
4 changes: 2 additions & 2 deletions src/discard/discard.f90
Original file line number Diff line number Diff line change
Expand Up @@ -38,8 +38,8 @@ module subroutine discard_system(self, param)
call tp%discard(system, param)
ltp_discards = (tp_discards%nbody > 0)
end if
if (ltp_discards) call tp_discards%write_info(param%nciu, param)
if (lpl_discards) call pl_discards%write_info(param%nciu, param)
if (ltp_discards) call tp_discards%write_info(param%nc, param)
if (lpl_discards) call pl_discards%write_info(param%nc, param)
if (lpl_discards .and. param%lenergy) call self%conservation_report(param, lterminal=.false.)
if (lpl_check) call pl_discards%setup(0,param)
if (ltp_check) call tp_discards%setup(0,param)
Expand Down
28 changes: 14 additions & 14 deletions src/io/io.f90
Original file line number Diff line number Diff line change
Expand Up @@ -179,8 +179,8 @@ module subroutine io_conservation_report(self, param, lterminal)
write(*,*) "Severe error! Mass not conserved! Halting!"
! Save the frame of data to the bin file in the slot just after the present one for diagnostics
param%ioutput = param%ioutput + 1
call self%write_frame(param%nciu, param)
call param%nciu%close()
call self%write_frame(param%nc, param)
call param%nc%close()
call util_exit(FAILURE)
end if
end if
Expand Down Expand Up @@ -248,20 +248,20 @@ module subroutine io_dump_system(self, param)
dump_param%out_stat = 'APPEND'
dump_param%in_type = "NETCDF_DOUBLE"
dump_param%in_netcdf = trim(adjustl(DUMP_NC_FILE(idx)))
dump_param%nciu%id_chunk = self%pl%nbody + self%tp%nbody
dump_param%nciu%time_chunk = 1
dump_param%nc%id_chunk = self%pl%nbody + self%tp%nbody
dump_param%nc%time_chunk = 1
dump_param%tstart = self%t

call dump_param%dump(param_file_name)

dump_param%out_form = "XV"
dump_param%outfile = trim(adjustl(DUMP_NC_FILE(idx)))
dump_param%ioutput = 1
call dump_param%nciu%initialize(dump_param)
call self%write_frame(dump_param%nciu, dump_param)
call dump_param%nciu%close()
call dump_param%nc%initialize(dump_param)
call self%write_frame(dump_param%nc, dump_param)
call dump_param%nc%close()
! Syncrhonize the disk and memory buffer of the NetCDF file (e.g. commit the frame files stored in memory to disk)
call param%nciu%flush(param)
call param%nc%flush(param)

idx = idx + 1
if (idx > NDUMPFILES) idx = 1
Expand Down Expand Up @@ -1308,7 +1308,7 @@ module subroutine io_read_in_system(self, param)
! Turn off energy computation so we don't have to feed it into the initial conditions
tmp_param%lenergy = .false.
end if
ierr = self%read_frame(tmp_param%nciu, tmp_param)
ierr = self%read_frame(tmp_param%nc, tmp_param)
deallocate(tmp_param)
if (ierr /=0) call util_exit(FAILURE)
end if
Expand Down Expand Up @@ -1537,8 +1537,8 @@ module subroutine io_write_frame_system(self, param)
character(len=STRMAX) :: errmsg
logical :: fileExists

param%nciu%id_chunk = self%pl%nbody + self%tp%nbody
param%nciu%time_chunk = max(param%dump_cadence / param%istep_out, 1)
param%nc%id_chunk = self%pl%nbody + self%tp%nbody
param%nc%time_chunk = max(param%dump_cadence / param%istep_out, 1)
if (lfirst) then
inquire(file=param%outfile, exist=fileExists)

Expand All @@ -1553,15 +1553,15 @@ module subroutine io_write_frame_system(self, param)
errmsg = param%outfile // " Alread Exists! You must specify OUT_STAT = APPEND, REPLACE, or UNKNOWN"
goto 667
end if
call param%nciu%initialize(param)
call param%nc%initialize(param)
case('REPLACE', 'UNKNOWN')
call param%nciu%initialize(param)
call param%nc%initialize(param)
end select

lfirst = .false.
end if

call self%write_frame(param%nciu, param)
call self%write_frame(param%nc, param)

return

Expand Down
34 changes: 17 additions & 17 deletions src/modules/swiftest_classes.f90
Original file line number Diff line number Diff line change
Expand Up @@ -150,8 +150,8 @@ module swiftest_classes
!> User defined parameters that are read in from the parameters input file.
!> Each paramter is initialized to a default values.
type :: swiftest_parameters
character(len=:), allocatable :: integrator !! Symbolic name of the nbody integrator used
character(len=:), allocatable :: param_file_name !! The name of the parameter file
character(len=:), allocatable :: integrator !! Symbolic name of the nbody integrator used
character(len=:), allocatable :: param_file_name !! The name of the parameter file
integer(I4B) :: maxid = -1 !! The current maximum particle id number
integer(I4B) :: maxid_collision = 0 !! The current maximum collision id number
real(DP) :: t0 = 0.0_DP !! Integration reference time
Expand Down Expand Up @@ -229,7 +229,7 @@ module swiftest_classes
logical :: lyarkovsky = .false. !! Turn on Yarkovsky effect
logical :: lyorp = .false. !! Turn on YORP effect

type(netcdf_parameters) :: nciu !! Object containing NetCDF parameters
type(netcdf_parameters) :: nc !! Object containing NetCDF parameters
contains
procedure :: reader => io_param_reader
procedure :: writer => io_param_writer
Expand Down Expand Up @@ -1024,55 +1024,55 @@ module subroutine netcdf_sync(self)
class(netcdf_parameters), intent(inout) :: self !! Parameters used to identify a particular NetCDF dataset
end subroutine netcdf_sync

module function netcdf_read_frame_system(self, nciu, param) result(ierr)
module function netcdf_read_frame_system(self, nc, param) result(ierr)
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to for reading a NetCDF dataset to file
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to for reading a NetCDF dataset to file
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
integer(I4B) :: ierr !! Error code: returns 0 if the read is successful
end function netcdf_read_frame_system

module subroutine netcdf_read_hdr_system(self, nciu, param)
module subroutine netcdf_read_hdr_system(self, nc, param)
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest nbody system object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to for reading a NetCDF dataset to file
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to for reading a NetCDF dataset to file
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine netcdf_read_hdr_system

module subroutine netcdf_read_particle_info_system(self, nciu, param, plmask, tpmask)
module subroutine netcdf_read_particle_info_system(self, nc, param, plmask, tpmask)
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest nbody system object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to identify a particular NetCDF dataset
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to identify a particular NetCDF dataset
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
logical, dimension(:), intent(in) :: plmask !! Logical array indicating which index values belong to massive bodies
logical, dimension(:), intent(in) :: tpmask !! Logical array indicating which index values belong to test particles
end subroutine netcdf_read_particle_info_system

module subroutine netcdf_write_frame_base(self, nciu, param)
module subroutine netcdf_write_frame_base(self, nc, param)
implicit none
class(swiftest_base), intent(in) :: self !! Swiftest base object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to for writing a NetCDF dataset to file
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to for writing a NetCDF dataset to file
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine netcdf_write_frame_base

module subroutine netcdf_write_frame_system(self, nciu, param)
module subroutine netcdf_write_frame_system(self, nc, param)
implicit none
class(swiftest_nbody_system), intent(inout) :: self !! Swiftest system object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to for writing a NetCDF dataset to file
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to for writing a NetCDF dataset to file
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine netcdf_write_frame_system

module subroutine netcdf_write_hdr_system(self, nciu, param)
module subroutine netcdf_write_hdr_system(self, nc, param)
implicit none
class(swiftest_nbody_system), intent(in) :: self !! Swiftest nbody system object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to for writing a NetCDF dataset to file
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to for writing a NetCDF dataset to file
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine netcdf_write_hdr_system

module subroutine netcdf_write_info_base(self, nciu, param)
module subroutine netcdf_write_info_base(self, nc, param)
implicit none
class(swiftest_base), intent(in) :: self !! Swiftest particle object
class(netcdf_parameters), intent(inout) :: nciu !! Parameters used to identify a particular NetCDF dataset
class(netcdf_parameters), intent(inout) :: nc !! Parameters used to identify a particular NetCDF dataset
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine netcdf_write_info_base

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 @@ -181,7 +181,7 @@ module symba_classes
!! NetCDF dimension and variable names for the enounter save object
type, extends(netcdf_parameters) :: symba_io_encounter_parameters
integer(I4B) :: COLLIDER_DIM_SIZE = 2 !! Size of collider dimension
integer(I4B) :: ienc_frame !! Current frame number for the encounter history
integer(I4B) :: ienc_frame = 1 !! Current frame number for the encounter history
character(STRMAX) :: enc_file = "encounter.nc" !! Encounter output file name

character(NAMELEN) :: level_varname = "level" !! Recursion depth
Expand All @@ -192,7 +192,7 @@ module symba_classes

type, extends(swiftest_storage) :: symba_encounter_storage
!! A class that that is used to store simulation history data between file output
type(symba_io_encounter_parameters) :: nciu
type(symba_io_encounter_parameters) :: nc
contains
procedure :: dump => symba_io_encounter_dump !! Dumps contents of encounter history to file
final :: symba_util_final_encounter_storage
Expand Down Expand Up @@ -425,10 +425,10 @@ module subroutine symba_io_encounter_initialize_output(self, param)
class(swiftest_parameters), intent(in) :: param
end subroutine symba_io_encounter_initialize_output

module subroutine symba_io_encounter_write_frame(self, nciu, param)
module subroutine symba_io_encounter_write_frame(self, nc, param)
implicit none
class(symba_encounter_snapshot), intent(in) :: self !! Swiftest encounter structure
class(symba_io_encounter_parameters), intent(inout) :: nciu !! Parameters used to identify a particular encounter io NetCDF dataset
class(symba_io_encounter_parameters), intent(inout) :: nc !! Parameters used to identify a particular encounter io NetCDF dataset
class(swiftest_parameters), intent(inout) :: param !! Current run configuration parameters
end subroutine symba_io_encounter_write_frame

Expand Down
Loading

0 comments on commit 77478cf

Please sign in to comment.