Skip to content

Commit

Permalink
Add initial version of Gadget-4 subfind reader
Browse files Browse the repository at this point in the history
Only works with group sorted snapshots, and only if the full
snapshot was read in.
  • Loading branch information
jchelly committed Aug 18, 2022
1 parent 5b9f35f commit e1e38d7
Show file tree
Hide file tree
Showing 4 changed files with 268 additions and 7 deletions.
2 changes: 1 addition & 1 deletion main/src/Makefile.am
Original file line number Diff line number Diff line change
Expand Up @@ -15,4 +15,4 @@ bin_PROGRAMS = gadgetviewer

@ax_mod_deps_main@

gadgetviewer_SOURCES = data_types.F90 format_strings.f90 shrink_array.f90 math.F90 partial_read_info.f90 data_array.f90 sort.F90 reorder.f90 shuffle.f90 file_units.f90 return_status.f90 transform.f90 octree.F90 percentiles.f90 string.f90 gadget_path.f90 stereo.f90 colour_table.f90 progress_bar.f90 particle_store.F90 auxiliary_file_list.f90 catalogue_data.f90 additional_data.F90 read_gadget_groups.f90 velociraptor_groups.F90 group_catalogue.f90 summary.f90 view_parameters.f90 project.f90 selection.F90 graph.F90 colour_bar.F90 sampling.f90 overlay.F90 select_point.f90 dotplot.f90 density2d.F90 property_plot.f90 fancyplot.F90 smoothed_property_plot.F90 gadget_binary_reader.F90 gadget_binary_type2_reader.F90 gadget_hdf5_reader.F90 gadget_eagle_reader.F90 swift_reader.F90 dummy_reader.F90 plotter.f90 mouse_handler.f90 snapshot_reader.f90 movie_parameters.f90 save_settings.F90 threads.F90 movie.f90 screenshot.f90 read_partial.f90 info_window.f90 main_window.F90 configuration.f90 command_line.f90 gadgetviewer.F90
gadgetviewer_SOURCES = data_types.F90 format_strings.f90 shrink_array.f90 math.F90 partial_read_info.f90 data_array.f90 sort.F90 reorder.f90 shuffle.f90 file_units.f90 return_status.f90 transform.f90 octree.F90 percentiles.f90 string.f90 gadget_path.f90 stereo.f90 colour_table.f90 progress_bar.f90 particle_store.F90 auxiliary_file_list.f90 catalogue_data.f90 additional_data.F90 read_gadget_groups.f90 read_gadget4_groups.f90 velociraptor_groups.F90 group_catalogue.f90 summary.f90 view_parameters.f90 project.f90 selection.F90 graph.F90 colour_bar.F90 sampling.f90 overlay.F90 select_point.f90 dotplot.f90 density2d.F90 property_plot.f90 fancyplot.F90 smoothed_property_plot.F90 gadget_binary_reader.F90 gadget_binary_type2_reader.F90 gadget_hdf5_reader.F90 gadget_eagle_reader.F90 swift_reader.F90 dummy_reader.F90 plotter.f90 mouse_handler.f90 snapshot_reader.f90 movie_parameters.f90 save_settings.F90 threads.F90 movie.f90 screenshot.f90 read_partial.f90 info_window.f90 main_window.F90 configuration.f90 command_line.f90 gadgetviewer.F90
11 changes: 11 additions & 0 deletions main/src/group_catalogue.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module group_catalogue
use return_status
use gadget_groups
use velociraptor_groups
use gadget4_groups
use sort
use progress_bar

Expand All @@ -19,6 +20,7 @@ module group_catalogue
! Format types
integer, parameter, public :: FORMAT_TYPE_SUBFIND = 0
integer, parameter, public :: FORMAT_TYPE_VELOCIRAPTOR = 1
integer, parameter, public :: FORMAT_TYPE_GADGET4 = 2

! List of currently loaded catalogues
integer, parameter :: ngroupcatmax = 10
Expand Down Expand Up @@ -148,6 +150,15 @@ type (result_type) function group_catalogue_read(icat, isnap)
res = velociraptor_groups_read(isnap, groupcat(icat)%path_data, &
nfof, nsub, nids, foflen, foffset, sublen, suboffset, groupids, &
ID, hostHaloID)
case(FORMAT_TYPE_GADGET4)
res = gadget4_groups_read(isnap, groupcat(icat)%path_data, icat)
! There's no need for matching particle IDs if we have a group sorted snapshot
if(res%success)then
group_catalogue_read%success = .true.
call particle_store_verify(pdata)
call progress_bar_close()
return
endif
case default
call terminate("Unrecognised subhalo format index!")
end select
Expand Down
21 changes: 15 additions & 6 deletions main/src/main_window.F90
Original file line number Diff line number Diff line change
Expand Up @@ -88,6 +88,7 @@ module main_window
type (gui_menu) :: file_subfind
type (gui_menu_item), dimension(:), allocatable :: groupformat_item
type (gui_menu_item) :: file_read_velociraptor
type (gui_menu_item) :: file_read_gadget4

! View menu
type (gui_menu) :: view_menu
Expand Down Expand Up @@ -309,7 +310,17 @@ subroutine main_window_create()
! Set up list of group formats we can read
call gui_create_menu(file_read_groups, file_menu, &
"Read groups...")
call gui_create_menu(file_subfind, file_read_groups, "Subfind")
call gui_create_menu_item(file_read_gadget4, file_read_groups, &
"Gadget-4 fof_subhalo_tab (assuming group sorted snapshot)")
#ifndef HAVE_HDF5
call gui_set_sensitive(file_read_gadget4, .false.)
#endif
call gui_create_menu_item(file_read_velociraptor, file_read_groups, &
"VELOCIraptor HDF5")
#ifndef HAVE_HDF5
call gui_set_sensitive(file_read_velociraptor,.false.)
#endif
call gui_create_menu(file_subfind, file_read_groups, "Gadget-2/3 Subfind")
call gadget_groups_format_list(ngroupformat)
allocate(groupformat(ngroupformat), groupformat_item(ngroupformat), stat=istat)
if(istat.ne.0)then
Expand All @@ -320,11 +331,6 @@ subroutine main_window_create()
call gui_create_menu_item(groupformat_item(i), file_subfind, &
groupformat(i))
end do
call gui_create_menu_item(file_read_velociraptor, file_read_groups, &
"VELOCIraptor HDF5")
#ifndef HAVE_HDF5
call gui_set_sensitive(file_read_velociraptor,.false.)
#endif

call gui_create_menu(file_aux, file_menu, "Auxilliary data")
call gui_create_menu_item(file_read_additional, file_aux, &
Expand Down Expand Up @@ -1278,6 +1284,9 @@ subroutine main_window_process_events()
if(gui_menu_item_clicked(file_read_velociraptor))then
group_type=FORMAT_TYPE_VELOCIRAPTOR
endif
if(gui_menu_item_clicked(file_read_gadget4))then
group_type=FORMAT_TYPE_GADGET4
endif
if(group_type.ge.0)then
call gui_select_file(mainwin, "Select a group file", &
gui_file_open, ok, fname)
Expand Down
241 changes: 241 additions & 0 deletions main/src/read_gadget4_groups.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,241 @@
module gadget4_groups

use f90_util
use data_types
use return_status
use gadget_path
use particle_store
use read_hdf5

implicit none
private
save

public :: gadget4_groups_read

contains

type(result_type) function gadget4_groups_read(isnap, path_data, icat) result(res)
!
! Read Gadget-4 fof_subhalo_tab and label particles with fof/subhalo index
!
implicit none
! Input parameters
integer, intent(in) :: isnap
type (path_data_type), intent(in) :: path_data
integer, intent(in) :: icat
! Group catalogue info
character(len=fname_maxlen) :: tab_file
integer :: ifile, nfiles
integer(kind=int8byte) :: ngroups_total, nsubhalos_total
integer(kind=int8byte) :: ngroups_file, nsubhalos_file
integer(kind=int4byte), dimension(:,:), allocatable :: grouplen_type
integer(kind=int4byte), dimension(:,:), allocatable :: subhalolen_type
integer(kind=int4byte), dimension(:), allocatable :: groupnsubs
integer :: rank, ntypes
integer(kind=int8byte), dimension(7) :: dims
integer(kind=int8byte) :: group_offset, subhalo_offset
integer :: dummy
integer(kind=index_kind) :: np(maxspecies), offset, i, j, k, sub_offset, sub_index
integer :: nspecies, ispecies
integer(kind=i_prop_kind), dimension(:), allocatable :: grnr, subnr
character(len=maxlen), dimension(maxspecies) :: species_name
character(len=maxlen) :: propname

! Read the file headers to determine total groups and number of files
ifile = 0
nfiles = 1
group_offset = 0
subhalo_offset = 0
do while(ifile.lt.nfiles)

! Generate the path to the tab file
call gadget_path_generate(isnap, ifile, tab_file, path_data)

! Open the file
if(hdf5_open_file(tab_file).ne.0)then
res%success = .false.
res%string = "Unable to open file: "//trim(tab_file)
call cleanup()
return
endif

if(ifile.eq.0)then
! Read header on first iteration
if(hdf5_read_attribute("Header/NumFiles", nfiles).ne.0)then
res%success = .false.
res%string = "Unable to read Header/NumFiles"
call cleanup()
return
endif
if(hdf5_read_attribute("Header/Ngroups_Total", ngroups_total).ne.0)then
res%success = .false.
res%string = "Unable to read Header/Ngroups_Total"
call cleanup()
return
endif
if(hdf5_read_attribute("Header/Nsubhalos_Total", nsubhalos_total).ne.0)then
res%success = .false.
res%string = "Unable to read Header/Nsubhalos_Total"
call cleanup()
return
endif

! Determine number of particle types
if(hdf5_dataset_size("Group/GroupLenType", rank, dims).ne.0)then
res%success = .false.
res%string = "Unable to get size of GroupLenType dataset"
call cleanup()
return
endif
ntypes = dims(1)

! Allocate arrays
allocate(grouplen_type(ntypes, ngroups_total))
allocate(subhalolen_type(ntypes, nsubhalos_total))
allocate(groupnsubs(ngroups_total))

endif ! if (file_nr.eq.0)

! Find number of halos in this file
if(hdf5_read_attribute("Header/Ngroups_ThisFile", ngroups_file).ne.0)then
res%success = .false.
res%string = "Unable to read Header/Ngroups_ThisFile"
call cleanup()
return
endif
if(hdf5_read_attribute("Header/Nsubhalos_ThisFile", nsubhalos_file).ne.0)then
res%success = .false.
res%string = "Unable to read Header/Nsubhalos_ThisFile"
call cleanup()
return
endif

! Read arrays
if(hdf5_read_dataset("Group/GroupLenType", &
grouplen_type(:, group_offset+1:group_offset+ngroups_file)).ne.0)then
res%success = .false.
res%string = "Unable to read Group/GroupLenType"
call cleanup()
return
endif
if(hdf5_read_dataset("Subhalo/SubhaloLenType", &
subhalolen_type(:, subhalo_offset+1:subhalo_offset+nsubhalos_file)).ne.0)then
res%success = .false.
res%string = "Unable to read Subhalo/SubhaloLenType"
call cleanup()
return
endif
if(hdf5_read_dataset("Group/GroupNsubs", &
groupnsubs(group_offset+1:group_offset+ngroups_file)).ne.0)then
res%success = .false.
res%string = "Unable to read Group/GroupNsubs"
call cleanup()
return
endif

group_offset = group_offset + ngroups_file
subhalo_offset = subhalo_offset + nsubhalos_file
dummy = hdf5_close_file()
ifile = ifile + 1
end do ! Next file

! Now create arrays with halo membership for particles
call particle_store_contents(pdata, get_nspecies=nspecies, get_np=np, &
get_species_names=species_name)
do ispecies = 1, nspecies, 1
if(np(ispecies).gt.0.and.ispecies.le.ntypes)then
allocate(grnr(np(ispecies)))
allocate(subnr(np(ispecies)))
grnr = -1
subnr = -1

! Compute group membership for the particles
offset = 0
sub_index = 0
do i = 1, ngroups_total, 1
! Subhalos
sub_offset = offset
do j = 1, groupnsubs(i), 1
sub_index = sub_index + 1
do k = 1, subhalolen_type(ispecies, sub_index), 1
sub_offset = sub_offset + 1
! TODO: detect if we didn't read the full snapshot and generate a suitable error message
if(sub_offset.le.np(ispecies))subnr(sub_offset) = sub_index - 1
end do
end do
! Groups
do j = 1, grouplen_type(ispecies, i), 1
offset = offset + 1
! TODO: detect if we didn't read the full snapshot and generate a suitable error message
if(offset.le.np(ispecies))grnr(offset) = i - 1
end do
end do
! Store group membership
if(icat.gt.1)then
write(propname,'(1a,1i3.3)')"GroupNr",icat
else
propname = "GroupNr"
endif
res = particle_store_new_property(pdata, species_name(ispecies), &
propname, "INTEGER")
if(.not.res%success)then
call cleanup()
return
endif
res = particle_store_add_data(pdata, species_name(ispecies), &
prop_name=propname, idata=grnr)
if(.not.res%success)then
call cleanup()
return
endif

! Store subhalo membership
if(icat.gt.1)then
write(propname,'(1a,1i3.3)')"SubhaloNr",icat
else
propname = "SubhaloNr"
endif
res = particle_store_new_property(pdata, species_name(ispecies), &
propname, "INTEGER")
if(.not.res%success)then
call cleanup()
return
endif
res = particle_store_add_data(pdata, species_name(ispecies), &
prop_name=propname, idata=subnr)
if(.not.res%success)then
call cleanup()
return
endif

deallocate(grnr)
deallocate(subnr)
endif
end do

deallocate(grouplen_type)
deallocate(subhalolen_type)
deallocate(groupnsubs)

return

contains

subroutine cleanup()

implicit none

if(allocated(grouplen_type))deallocate(grouplen_type)
if(allocated(subhalolen_type))deallocate(subhalolen_type)
if(allocated(grnr))deallocate(grnr)
if(allocated(subnr))deallocate(subnr)
if(allocated(groupnsubs))deallocate(groupnsubs)
dummy = hdf5_close_file()

return
end subroutine cleanup

end function gadget4_groups_read

end module gadget4_groups

0 comments on commit e1e38d7

Please sign in to comment.