Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- h5f_ACC_RDONLY :: Num a => a
- h5f_ACC_RDWR :: Num a => a
- h5f_ACC_TRUNC :: Num a => a
- h5f_ACC_EXCL :: Num a => a
- h5f_ACC_DEBUG :: Num a => a
- h5f_ACC_CREAT :: Num a => a
- h5f_ACC_SWMR_WRITE :: Num a => a
- h5f_ACC_SWMR_READ :: Num a => a
- h5f_ACC_DEFAULT :: Num a => a
- h5f_OBJ_FILE :: Num a => a
- h5f_OBJ_DATASET :: Num a => a
- h5f_OBJ_GROUP :: Num a => a
- h5f_OBJ_DATATYPE :: Num a => a
- h5f_OBJ_ATTR :: Num a => a
- h5f_OBJ_ALL :: Num a => a
- h5f_OBJ_LOCAL :: Num a => a
- h5f_FAMILY_DEFAULT :: HSize_t
- h5f_MPIO_DEBUG_KEY :: String
- newtype H5F_scope_t = H5F_scope_t Word32
- h5f_SCOPE_LOCAL :: H5F_scope_t
- h5f_SCOPE_GLOBAL :: H5F_scope_t
- h5f_UNLIMITED :: HSize_t
- newtype H5F_close_degree_t = H5F_close_degree_t Word32
- h5f_CLOSE_DEFAULT :: H5F_close_degree_t
- h5f_CLOSE_WEAK :: H5F_close_degree_t
- h5f_CLOSE_SEMI :: H5F_close_degree_t
- h5f_CLOSE_STRONG :: H5F_close_degree_t
- newtype H5F_mem_t = H5F_mem_t Int32
- h5fd_MEM_NOLIST :: H5F_mem_t
- h5fd_MEM_DEFAULT :: H5F_mem_t
- h5fd_MEM_SUPER :: H5F_mem_t
- h5fd_MEM_BTREE :: H5F_mem_t
- h5fd_MEM_DRAW :: H5F_mem_t
- h5fd_MEM_GHEAP :: H5F_mem_t
- h5fd_MEM_LHEAP :: H5F_mem_t
- h5fd_MEM_OHDR :: H5F_mem_t
- h5fd_MEM_NTYPES :: Num a => a
- data H5F_sect_info_t = H5F_sect_info_t {}
- p'H5F_sect_info_t'addr :: Ptr H5F_sect_info_t -> Ptr HAddr_t
- newtype H5F_libver_t = H5F_libver_t Int32
- p'H5F_sect_info_t'size :: Ptr H5F_sect_info_t -> Ptr HSize_t
- h5f_LIBVER_EARLIEST :: H5F_libver_t
- h5f_LIBVER_LATEST :: H5F_libver_t
- newtype H5F_file_space_type_t = H5F_file_space_type_t Word32
- h5f_FILE_SPACE_DEFAULT :: H5F_file_space_type_t
- h5f_FILE_SPACE_ALL_PERSIST :: H5F_file_space_type_t
- h5f_FILE_SPACE_ALL :: H5F_file_space_type_t
- h5f_FILE_SPACE_AGGR_VFD :: H5F_file_space_type_t
- h5f_FILE_SPACE_VFD :: H5F_file_space_type_t
- h5f_FILE_SPACE_NTYPES :: Num a => a
- h5f_NUM_METADATA_READ_RETRY_TYPES :: Num a => a
- data H5F_retry_info_t = H5F_retry_info_t {}
- type H5F_flush_cb_t a = FunPtr (HId_t -> InOut a -> IO HErr_t)
- p'H5F_retry_info_t'nbins :: Ptr H5F_retry_info_t -> Ptr CUInt
- p'H5F_retry_info_t'retries :: Ptr H5F_retry_info_t -> Ptr (Ptr Word32)
- h5f_is_hdf5 :: CString -> IO HTri_t
- p_H5Fis_hdf5 :: FunPtr (CString -> IO HTri_t)
- h5f_create :: CString -> CUInt -> HId_t -> HId_t -> IO HId_t
- p_H5Fcreate :: FunPtr (CString -> CUInt -> HId_t -> HId_t -> IO HId_t)
- h5f_open :: CString -> CUInt -> HId_t -> IO HId_t
- p_H5Fopen :: FunPtr (CString -> CUInt -> HId_t -> IO HId_t)
- h5f_reopen :: HId_t -> IO HId_t
- p_H5Freopen :: FunPtr (HId_t -> IO HId_t)
- h5f_flush :: HId_t -> H5F_scope_t -> IO HErr_t
- p_H5Fflush :: FunPtr (HId_t -> H5F_scope_t -> IO HErr_t)
- h5f_close :: HId_t -> IO HErr_t
- p_H5Fclose :: FunPtr (HId_t -> IO HErr_t)
- h5f_get_create_plist :: HId_t -> IO HId_t
- p_H5Fget_create_plist :: FunPtr (HId_t -> IO HId_t)
- h5f_get_access_plist :: HId_t -> IO HId_t
- p_H5Fget_access_plist :: FunPtr (HId_t -> IO HId_t)
- h5f_get_intent :: HId_t -> Out CUInt -> IO HErr_t
- p_H5Fget_intent :: FunPtr (HId_t -> Out CUInt -> IO HErr_t)
- h5f_get_obj_count :: HId_t -> CUInt -> IO CSSize
- p_H5Fget_obj_count :: FunPtr (HId_t -> CUInt -> IO CSSize)
- h5f_get_obj_ids :: HId_t -> CUInt -> CSize -> OutArray HId_t -> IO CSSize
- p_H5Fget_obj_ids :: FunPtr (HId_t -> CUInt -> CSize -> OutArray HId_t -> IO CSSize)
- h5f_get_vfd_handle :: HId_t -> HId_t -> Out (Ptr CFile) -> IO HErr_t
- p_H5Fget_vfd_handle :: FunPtr (HId_t -> HId_t -> Out (Ptr CFile) -> IO HErr_t)
- h5f_mount :: HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
- p_H5Fmount :: FunPtr (HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
- h5f_unmount :: HId_t -> CString -> IO HErr_t
- p_H5Funmount :: FunPtr (HId_t -> CString -> IO HErr_t)
- h5f_get_freespace :: HId_t -> IO HSSize_t
- p_H5Fget_freespace :: FunPtr (HId_t -> IO HSSize_t)
- h5f_get_filesize :: HId_t -> Out HSize_t -> IO HErr_t
- p_H5Fget_filesize :: FunPtr (HId_t -> Out HSize_t -> IO HErr_t)
- h5f_get_file_image :: HId_t -> InArray a -> CSize -> IO CSSize
- p_H5Fget_file_image :: FunPtr (HId_t -> InArray a -> CSize -> IO CSSize)
- h5f_get_mdc_config :: HId_t -> Out H5AC_cache_config_t -> IO HErr_t
- p_H5Fget_mdc_config :: FunPtr (HId_t -> Out H5AC_cache_config_t -> IO HErr_t)
- h5f_set_mdc_config :: HId_t -> In H5AC_cache_config_t -> IO HErr_t
- p_H5Fset_mdc_config :: FunPtr (HId_t -> In H5AC_cache_config_t -> IO HErr_t)
- h5f_get_mdc_hit_rate :: HId_t -> Out CDouble -> IO HErr_t
- p_H5Fget_mdc_hit_rate :: FunPtr (HId_t -> Out CDouble -> IO HErr_t)
- h5f_get_mdc_size :: HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CInt -> IO HErr_t
- p_H5Fget_mdc_size :: FunPtr (HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CInt -> IO HErr_t)
- h5f_reset_mdc_hit_rate_stats :: HId_t -> IO HErr_t
- p_H5Freset_mdc_hit_rate_stats :: FunPtr (HId_t -> IO HErr_t)
- h5f_get_name :: HId_t -> OutArray CChar -> CSize -> IO CSSize
- p_H5Fget_name :: FunPtr (HId_t -> OutArray CChar -> CSize -> IO CSSize)
- h5f_get_metadata_read_retry_info :: HId_t -> Out H5F_retry_info_t -> IO HErr_t
- p_H5Fget_metadata_read_retry_info :: FunPtr (HId_t -> Out H5F_retry_info_t -> IO HErr_t)
- h5f_start_swmr_write :: HId_t -> IO HErr_t
- p_H5Fstart_swmr_write :: FunPtr (HId_t -> IO HErr_t)
- h5f_get_free_sections :: HId_t -> H5F_mem_t -> CSize -> Out H5F_sect_info_t -> IO CSSize
- p_H5Fget_free_sections :: FunPtr (HId_t -> H5F_mem_t -> CSize -> Out H5F_sect_info_t -> IO CSSize)
- h5f_clear_elink_file_cache :: HId_t -> IO HErr_t
- p_H5Fclear_elink_file_cache :: FunPtr (HId_t -> IO HErr_t)
- h5f_start_mdc_logging :: HId_t -> IO HErr_t
- p_H5Fstart_mdc_logging :: FunPtr (HId_t -> IO HErr_t)
- h5f_stop_mdc_logging :: HId_t -> IO HErr_t
- p_H5Fstop_mdc_logging :: FunPtr (HId_t -> IO HErr_t)
- h5f_get_mdc_logging_status :: HId_t -> Out hbool_t -> Out hbool_t -> IO HErr_t
- p_H5Fget_mdc_logging_status :: FunPtr (HId_t -> Out hbool_t -> Out hbool_t -> IO HErr_t)
- h5f_format_convert :: HId_t -> IO HErr_t
- p_H5Fformat_convert :: FunPtr (HId_t -> IO HErr_t)
- h5f_get_info1 :: HId_t -> Out H5F_info1_t -> IO HErr_t
- p_H5Fget_info1 :: FunPtr (HId_t -> Out H5F_info1_t -> IO HErr_t)
- h5f_set_mpi_atomicity :: HId_t -> HBool_t -> IO HErr_t
- p_H5Fset_mpi_atomicity :: FunPtr (HId_t -> HBool_t -> IO HErr_t)
- h5f_get_mpi_atomicity :: HId_t -> Out HBool_t -> IO HErr_t
- p_H5Fget_mpi_atomicity :: FunPtr (HId_t -> Out HBool_t -> IO HErr_t)
- data H5F_info1_t = H5F_info1_t {}
- p'H5F_info1_t'super_ext_size :: Ptr H5F_info1_t -> Ptr HSize_t
- p'H5F_info1_t'sohm'hdr_size :: Ptr H5F_info1_t -> Ptr HSize_t
- p'H5F_info1_t'sohm'msgs_info :: Ptr H5F_info1_t -> Ptr H5_ih_info_t
- data H5F_info_t = H5F_info_t {}
- p'H5F_info_t'super_ext_size :: Ptr H5F_info_t -> Ptr HSize_t
- p'H5F_info_t'sohm'hdr_size :: Ptr H5F_info_t -> Ptr HSize_t
- p'H5F_info_t'sohm'msgs_info :: Ptr H5F_info_t -> Ptr H5_ih_info_t
- h5f_get_info :: HId_t -> Out H5F_info_t -> IO HErr_t
Types and constants
Flags for h5f_create
and h5f_open
h5f_ACC_RDONLY :: Num a => a Source #
absence of rdwr => rd-only
h5f_ACC_RDWR :: Num a => a Source #
open for read and write
h5f_ACC_TRUNC :: Num a => a Source #
overwrite existing files
h5f_ACC_EXCL :: Num a => a Source #
fail if file already exists
h5f_ACC_DEBUG :: Num a => a Source #
print debug info
h5f_ACC_CREAT :: Num a => a Source #
create non-existing files
h5f_ACC_SWMR_WRITE :: Num a => a Source #
indicate that this file is open for writing in a single-writer/multi-reader (SWMR) scenario. Note that the process(es) opening the file for reading must open the file with RDONLY access, and use the special SWMR_READ access flag.
h5f_ACC_SWMR_READ :: Num a => a Source #
indicate that this file is open for reading in a single-writer/multi-reader (SWMR) scenario. Note that the process(es) opening the file for SWMR reading must also open the file with the RDONLY flag. */
h5f_ACC_DEFAULT :: Num a => a Source #
Value passed to h5p_set_elink_acc_flags
to cause flags to be taken from the
parent file.
Flags for h5f_get_obj_count
and h5f_get_obj_ids
calls
h5f_OBJ_FILE :: Num a => a Source #
File objects
h5f_OBJ_DATASET :: Num a => a Source #
Dataset objects
h5f_OBJ_GROUP :: Num a => a Source #
Group objects
h5f_OBJ_DATATYPE :: Num a => a Source #
Named datatype objects
h5f_OBJ_ATTR :: Num a => a Source #
Attribute objects
h5f_OBJ_ALL :: Num a => a Source #
h5f_OBJ_LOCAL :: Num a => a Source #
Restrict search to objects opened through current file ID
h5f_MPIO_DEBUG_KEY :: String Source #
Use this constant string as the MPI_Info key to set h5f_mpio
debug flags.
To turn on h5f_mpio
debug flags, set the MPI_Info value with this key to
have the value of a string consisting of the characters that turn on the
desired flags.
newtype H5F_scope_t Source #
The difference between a single file and a set of mounted files
Instances
Storable H5F_scope_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_scope_t -> Int # alignment :: H5F_scope_t -> Int # peekElemOff :: Ptr H5F_scope_t -> Int -> IO H5F_scope_t # pokeElemOff :: Ptr H5F_scope_t -> Int -> H5F_scope_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_scope_t # pokeByteOff :: Ptr b -> Int -> H5F_scope_t -> IO () # peek :: Ptr H5F_scope_t -> IO H5F_scope_t # poke :: Ptr H5F_scope_t -> H5F_scope_t -> IO () # | |
Show H5F_scope_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_scope_t -> ShowS # show :: H5F_scope_t -> String # showList :: [H5F_scope_t] -> ShowS # |
h5f_SCOPE_LOCAL :: H5F_scope_t Source #
specified file handle only
h5f_SCOPE_GLOBAL :: H5F_scope_t Source #
entire virtual file
h5f_UNLIMITED :: HSize_t Source #
Unlimited file size for h5p_set_external
newtype H5F_close_degree_t Source #
How does file close behave?
Instances
Storable H5F_close_degree_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_close_degree_t -> Int # alignment :: H5F_close_degree_t -> Int # peekElemOff :: Ptr H5F_close_degree_t -> Int -> IO H5F_close_degree_t # pokeElemOff :: Ptr H5F_close_degree_t -> Int -> H5F_close_degree_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_close_degree_t # pokeByteOff :: Ptr b -> Int -> H5F_close_degree_t -> IO () # peek :: Ptr H5F_close_degree_t -> IO H5F_close_degree_t # poke :: Ptr H5F_close_degree_t -> H5F_close_degree_t -> IO () # | |
Show H5F_close_degree_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_close_degree_t -> ShowS # show :: H5F_close_degree_t -> String # showList :: [H5F_close_degree_t] -> ShowS # | |
Eq H5F_close_degree_t Source # | |
Defined in Bindings.HDF5.Raw.H5F (==) :: H5F_close_degree_t -> H5F_close_degree_t -> Bool # (/=) :: H5F_close_degree_t -> H5F_close_degree_t -> Bool # |
h5f_CLOSE_DEFAULT :: H5F_close_degree_t Source #
Use the degree pre-defined by underlining VFL
h5f_CLOSE_WEAK :: H5F_close_degree_t Source #
file closes only after all opened objects are closed
h5f_CLOSE_SEMI :: H5F_close_degree_t Source #
if no opened objects, file is close; otherwise, file close fails
h5f_CLOSE_STRONG :: H5F_close_degree_t Source #
if there are opened objects, close them first, then close file
Types of allocation requests. The values larger than h5fd_MEM_DEFAULT
should not change other than adding new types to the end. These numbers
might appear in files.
Instances
Storable H5F_mem_t Source # | |
Defined in Bindings.HDF5.Raw.H5F | |
Show H5F_mem_t Source # | |
Eq H5F_mem_t Source # | |
h5fd_MEM_NOLIST :: H5F_mem_t Source #
Data should not appear in the free list. Must be negative.
h5fd_MEM_DEFAULT :: H5F_mem_t Source #
Superblock data
Value not yet set. Can also be the datatype set in a larger allocation that will be suballocated by the library. Must be zero.
h5fd_MEM_SUPER :: H5F_mem_t Source #
B-tree data
h5fd_MEM_DRAW :: H5F_mem_t Source #
Global heap data
Raw data (content of datasets, etc.)
h5fd_MEM_GHEAP :: H5F_mem_t Source #
Local heap data
h5fd_MEM_LHEAP :: H5F_mem_t Source #
Object header data
h5fd_MEM_NTYPES :: Num a => a Source #
Sentinel value - must be last
data H5F_sect_info_t Source #
Free space section information
Address of free space section
Size of free space section
Instances
Storable H5F_sect_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_sect_info_t -> Int # alignment :: H5F_sect_info_t -> Int # peekElemOff :: Ptr H5F_sect_info_t -> Int -> IO H5F_sect_info_t # pokeElemOff :: Ptr H5F_sect_info_t -> Int -> H5F_sect_info_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_sect_info_t # pokeByteOff :: Ptr b -> Int -> H5F_sect_info_t -> IO () # peek :: Ptr H5F_sect_info_t -> IO H5F_sect_info_t # poke :: Ptr H5F_sect_info_t -> H5F_sect_info_t -> IO () # | |
Show H5F_sect_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_sect_info_t -> ShowS # show :: H5F_sect_info_t -> String # showList :: [H5F_sect_info_t] -> ShowS # | |
Eq H5F_sect_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F (==) :: H5F_sect_info_t -> H5F_sect_info_t -> Bool # (/=) :: H5F_sect_info_t -> H5F_sect_info_t -> Bool # |
p'H5F_sect_info_t'addr :: Ptr H5F_sect_info_t -> Ptr HAddr_t Source #
Library's file format versions
newtype H5F_libver_t Source #
Instances
Storable H5F_libver_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_libver_t -> Int # alignment :: H5F_libver_t -> Int # peekElemOff :: Ptr H5F_libver_t -> Int -> IO H5F_libver_t # pokeElemOff :: Ptr H5F_libver_t -> Int -> H5F_libver_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_libver_t # pokeByteOff :: Ptr b -> Int -> H5F_libver_t -> IO () # peek :: Ptr H5F_libver_t -> IO H5F_libver_t # poke :: Ptr H5F_libver_t -> H5F_libver_t -> IO () # | |
Show H5F_libver_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_libver_t -> ShowS # show :: H5F_libver_t -> String # showList :: [H5F_libver_t] -> ShowS # |
p'H5F_sect_info_t'size :: Ptr H5F_sect_info_t -> Ptr HSize_t Source #
Use the earliest possible format for storing objects
h5f_LIBVER_LATEST :: H5F_libver_t Source #
Use the latest possible format available for storing objects
newtype H5F_file_space_type_t Source #
File space handling strategy
Instances
Storable H5F_file_space_type_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_file_space_type_t -> Int # alignment :: H5F_file_space_type_t -> Int # peekElemOff :: Ptr H5F_file_space_type_t -> Int -> IO H5F_file_space_type_t # pokeElemOff :: Ptr H5F_file_space_type_t -> Int -> H5F_file_space_type_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_file_space_type_t # pokeByteOff :: Ptr b -> Int -> H5F_file_space_type_t -> IO () # peek :: Ptr H5F_file_space_type_t -> IO H5F_file_space_type_t # poke :: Ptr H5F_file_space_type_t -> H5F_file_space_type_t -> IO () # | |
Show H5F_file_space_type_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_file_space_type_t -> ShowS # show :: H5F_file_space_type_t -> String # showList :: [H5F_file_space_type_t] -> ShowS # | |
Eq H5F_file_space_type_t Source # | |
Defined in Bindings.HDF5.Raw.H5F (==) :: H5F_file_space_type_t -> H5F_file_space_type_t -> Bool # (/=) :: H5F_file_space_type_t -> H5F_file_space_type_t -> Bool # |
h5f_FILE_SPACE_DEFAULT :: H5F_file_space_type_t Source #
Default (or current) free space strategy setting
h5f_FILE_SPACE_ALL_PERSIST :: H5F_file_space_type_t Source #
Persistent free space managers, aggregators, virtual file driver
h5f_FILE_SPACE_ALL :: H5F_file_space_type_t Source #
Non-persistent free space managers, aggregators, virtual file driver This is the library default
h5f_FILE_SPACE_AGGR_VFD :: H5F_file_space_type_t Source #
Aggregators, Virtual file driver
h5f_FILE_SPACE_VFD :: H5F_file_space_type_t Source #
Virtual file driver
h5f_FILE_SPACE_NTYPES :: Num a => a Source #
h5f_NUM_METADATA_READ_RETRY_TYPES :: Num a => a Source #
Data structure to report the collection of read retries for metadata items with checksum Used by public routine H5Fget_metadata_read_retry_info() TODO check the retries static array
data H5F_retry_info_t Source #
Instances
Storable H5F_retry_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_retry_info_t -> Int # alignment :: H5F_retry_info_t -> Int # peekElemOff :: Ptr H5F_retry_info_t -> Int -> IO H5F_retry_info_t # pokeElemOff :: Ptr H5F_retry_info_t -> Int -> H5F_retry_info_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_retry_info_t # pokeByteOff :: Ptr b -> Int -> H5F_retry_info_t -> IO () # peek :: Ptr H5F_retry_info_t -> IO H5F_retry_info_t # poke :: Ptr H5F_retry_info_t -> H5F_retry_info_t -> IO () # | |
Show H5F_retry_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_retry_info_t -> ShowS # show :: H5F_retry_info_t -> String # showList :: [H5F_retry_info_t] -> ShowS # | |
Eq H5F_retry_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F (==) :: H5F_retry_info_t -> H5F_retry_info_t -> Bool # (/=) :: H5F_retry_info_t -> H5F_retry_info_t -> Bool # |
p'H5F_retry_info_t'nbins :: Ptr H5F_retry_info_t -> Ptr CUInt Source #
Callback for H5Pset_object_flush_cb() in a file access property list > typedef herr_t (*H5F_flush_cb_t)(hid_t object_id, void *udata);
Public functions
h5f_is_hdf5 :: CString -> IO HTri_t Source #
Check the file signature to detect an HDF5 file.
- Bugs:
- This function is not robust: it only uses the default file driver when attempting to open the file when in fact it should use all known file drivers.
htri_t H5Fis_hdf5(const char *filename);
h5f_create :: CString -> CUInt -> HId_t -> HId_t -> IO HId_t Source #
This is the primary function for creating HDF5 files. The
flags
parameter determines whether an existing file will be
overwritten or not. All newly created files are opened for
both reading and writing. All flags may be combined with the
bit-wise OR operator ( .|.
from Data.Bits) to change the
behavior of the file create call.
The more complex behaviors of a file's creation and access
are controlled through the file-creation and file-access
property lists. The value of h5p_DEFAULT
for a template
value indicates that the library should use the default
values for the appropriate template.
See also: Bindings.HDF5.Raw.H5F for the list of supported flags. Bindings.HDF5.Raw.H5P for the list of file creation and file access properties.
On success, returns a file ID. On failure, returns a negative value.
hid_t H5Fcreate(const char *filename, unsigned flags, hid_t create_plist, hid_t access_plist);
h5f_open :: CString -> CUInt -> HId_t -> IO HId_t Source #
This is the primary function for accessing existing HDF5
files. The flags
argument determines whether writing to an
existing file will be allowed or not. All flags may be
combined with the bit-wise OR operator ( .|.
from Data.Bits)
to change the behavior of the file open call. The more complex
behaviors of a file's access are controlled through the file-access
property list.
See Also: Bindings.HDF5.Raw.H5F for a list of possible values for flags
.
On success, returns a file ID. On failure, returns a negative value.
hid_t H5Fopen(const char *filename, unsigned flags, hid_t access_plist);
h5f_reopen :: HId_t -> IO HId_t Source #
Reopen a file. The new file handle which is returned points to the same file as the specified file handle. Both handles share caches and other information. The only difference between the handles is that the new handle is not mounted anywhere and no files are mounted on it.
On success, returns a file ID. On failure, returns a negative value.
hid_t H5Freopen(hid_t file_id);
h5f_flush :: HId_t -> H5F_scope_t -> IO HErr_t Source #
Flushes all outstanding buffers of a file to disk but does
not remove them from the cache. The object_id
can be a file,
dataset, group, attribute, or named data type.
Returns non-negative on success / negative on failure
herr_t H5Fflush(hid_t object_id, H5F_scope_t scope);
p_H5Fflush :: FunPtr (HId_t -> H5F_scope_t -> IO HErr_t) Source #
h5f_close :: HId_t -> IO HErr_t Source #
This function closes the file specified by file_id
by
flushing all data to storage, and terminating access to the
file through file_id
. If objects (e.g., datasets, groups,
etc.) are open in the file then the underlying storage is not
closed until those objects are closed; however, all data for
the file and the open objects is flushed.
Returns non-negative on success / negative on failure
herr_t H5Fclose(hid_t file_id);
h5f_get_create_plist :: HId_t -> IO HId_t Source #
Get an atom for a copy of the file-creation property list for this file. This function returns an atom with a copy of the properties used to create a file.
On success, returns a template ID. On failure, returns a negative value.
hid_t H5Fget_create_plist(hid_t file_id);
h5f_get_access_plist :: HId_t -> IO HId_t Source #
Returns a copy of the file access property list of the specified file.
NOTE: If you are going to overwrite information in the copied property list that was previously opened and assigned to the property list, then you must close it before overwriting the values.
On success, returns an Object ID for a copy of the file access property list. On failure, returns a negative value.
hid_t H5Fget_access_plist(hid_t file_id);
h5f_get_intent :: HId_t -> Out CUInt -> IO HErr_t Source #
Public API to retrieve the file's intent
flags passed
during h5f_open
.
Returns non-negative on success / negative on failure
herr_t H5Fget_intent(hid_t file_id, unsigned * intent);
h5f_get_obj_count :: HId_t -> CUInt -> IO CSSize Source #
Returns the number of opened object IDs (files, datasets, groups and datatypes) in the same file.
Returns non-negative on success, negative on failure.
ssize_t H5Fget_obj_count(hid_t file_id, unsigned types);
h5f_get_obj_ids :: HId_t -> CUInt -> CSize -> OutArray HId_t -> IO CSSize Source #
Returns a list of opened object IDs.
Returns non-negative on success, negative on failure
ssize_t H5Fget_obj_ids(hid_t file_id, unsigned types, size_t max_objs, hid_t *obj_id_list);
h5f_get_vfd_handle :: HId_t -> HId_t -> Out (Ptr CFile) -> IO HErr_t Source #
Returns a pointer to the file handle of the low-level file driver.
Returns non-negative on success, negative on failure
herr_t H5Fget_vfd_handle(hid_t file_id, hid_t fapl, void **file_handle);
h5f_mount :: HId_t -> CString -> HId_t -> HId_t -> IO HErr_t Source #
Mount file child_id
onto the group specified by loc_id
and
name
using mount properties plist_id
.
Returns non-negative on success, negative on failure
herr_t H5Fmount(hid_t loc, const char *name, hid_t child, hid_t plist);
h5f_unmount :: HId_t -> CString -> IO HErr_t Source #
Given a mount point, dissassociate the mount point's file from the file mounted there. Do not close either file.
The mount point can either be the group in the parent or the root group of the mounted file (both groups have the same name). If the mount point was opened before the mount then it's the group in the parent, but if it was opened after the mount then it's the root group of the child.
Returns non-negative on success, negative on failure
herr_t H5Funmount(hid_t loc, const char *name);
h5f_get_freespace :: HId_t -> IO HSSize_t Source #
Retrieves the amount of free space in the file. Returns a negative value on failure.
hssize_t H5Fget_freespace(hid_t file_id);
h5f_get_filesize :: HId_t -> Out HSize_t -> IO HErr_t Source #
Retrieves the file size of the HDF5 file. This function is called after an existing file is opened in order to learn the true size of the underlying file.
Returns non-negative on success, negative on failure
herr_t H5Fget_filesize(hid_t file_id, hsize_t *size);
h5f_get_file_image :: HId_t -> InArray a -> CSize -> IO CSSize Source #
If a buffer is provided (via the buf_ptr argument) and is big enough (size in buf_len argument), load *buf_ptr with an image of the open file whose ID is provided in the file_id parameter, and return the number of bytes copied to the buffer.
If the buffer exists, but is too small to contain an image of the indicated file, return a negative number.
Finally, if no buffer is provided, return the size of the buffer needed. This value is simply the eoa of the target file.
Note that any user block is skipped.
Also note that the function may not be used on files opened with either the split/multi file driver or the family file driver.
In the former case, the sparse address space makes the get file image operation impractical, due to the size of the image typically required.
In the case of the family file driver, the problem is the driver message in the super block, which will prevent the image being opened with any driver other than the family file driver -- which negates the purpose of the operation. This can be fixed, but no resources for this now.
Return: Success: Bytes copied / number of bytes needed. Failure: negative value
ssize_t H5Fget_file_image(hid_t file_id, void * buf_ptr, size_t buf_len);
h5f_get_mdc_config :: HId_t -> Out H5AC_cache_config_t -> IO HErr_t Source #
Retrieves the current automatic cache resize configuration
from the metadata cache, and return it in config_ptr
.
Note that the version
field of config_ptr
must be correctly
filled in by the caller. This allows us to adapt for
obsolete versions of the structure.
Returns non-negative on success, negative on failure
herr_t H5Fget_mdc_config(hid_t file_id, H5AC_cache_config_t * config_ptr);
p_H5Fget_mdc_config :: FunPtr (HId_t -> Out H5AC_cache_config_t -> IO HErr_t) Source #
h5f_set_mdc_config :: HId_t -> In H5AC_cache_config_t -> IO HErr_t Source #
Sets the current metadata cache automatic resize
configuration, using the contents of the instance of
H5AC_cache_config_t
pointed to by config_ptr
.
Returns non-negative on success, negative on failure
herr_t H5Fset_mdc_config(hid_t file_id, H5AC_cache_config_t * config_ptr);
p_H5Fset_mdc_config :: FunPtr (HId_t -> In H5AC_cache_config_t -> IO HErr_t) Source #
h5f_get_mdc_hit_rate :: HId_t -> Out CDouble -> IO HErr_t Source #
Retrieves the current hit rate from the metadata cache. This rate is the overall hit rate since the last time the hit rate statistics were reset either manually or automatically.
Returns non-negative on success, negative on failure
herr_t H5Fget_mdc_hit_rate(hid_t file_id, double * hit_rate_ptr);
h5f_get_mdc_size :: HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CInt -> IO HErr_t Source #
Retrieves the maximum size, minimum clean size, current size, and current number of entries from the metadata cache associated with the specified file. If any of the ptr parameters are NULL, the associated datum is not returned.
Returns non-negative on success, negative on failure
herr_t H5Fget_mdc_size(hid_t file_id, size_t * max_size_ptr, size_t * min_clean_size_ptr, size_t * cur_size_ptr, int * cur_num_entries_ptr);
p_H5Fget_mdc_size :: FunPtr (HId_t -> Out CSize -> Out CSize -> Out CSize -> Out CInt -> IO HErr_t) Source #
h5f_reset_mdc_hit_rate_stats :: HId_t -> IO HErr_t Source #
Reset the hit rate statistic whose current value can
be obtained via the h5f_get_mdc_hit_rate
call. Note
that this statistic will also be reset once per epoch
by the automatic cache resize code if it is enabled.
It is probably a bad idea to call this function unless you are controlling cache size from your program instead of using our cache size control code.
Returns non-negative on success, negative on failure
herr_t H5Freset_mdc_hit_rate_stats(hid_t file_id);
h5f_get_name :: HId_t -> OutArray CChar -> CSize -> IO CSSize Source #
Gets the name of the file to which object OBJ_ID belongs.
If name
is non-NULL then write up to size
bytes into that
buffer and always return the length of the entry name.
Otherwise size
is ignored and the function does not store the name,
just returning the number of characters required to store the name.
If an error occurs then the buffer pointed to by name
(NULL or non-NULL)
is unchanged and the function returns a negative value.
Note: This routine returns the name that was used to open the file, not the actual name after resolving symlinks, etc.
Returns the length of the file name (_not_ the length of the data copied into the output buffer) on success, or a negative value on failure.
ssize_t H5Fget_name(hid_t obj_id, char *name, size_t size);
h5f_get_metadata_read_retry_info :: HId_t -> Out H5F_retry_info_t -> IO HErr_t Source #
#. Get storage size for superblock extension if there is one
#. Get the amount of btree and heap storage for entries in the SOHM table if there is one.
#. Consider success when there is no superblock extension and/or SOHM table
Returns non-negative on success, negative on failure
h5f_get_free_sections :: HId_t -> H5F_mem_t -> CSize -> Out H5F_sect_info_t -> IO CSSize Source #
p_H5Fget_free_sections :: FunPtr (HId_t -> H5F_mem_t -> CSize -> Out H5F_sect_info_t -> IO CSSize) Source #
h5f_clear_elink_file_cache :: HId_t -> IO HErr_t Source #
Releases the external file cache associated with the provided file, potentially closing any cached files unless they are held open from somewhere else.
Returns non-negative on success, negative on failure
herr_t H5Fclear_elink_file_cache(hid_t file_id);
h5f_get_info1 :: HId_t -> Out H5F_info1_t -> IO HErr_t Source #
p_H5Fget_info1 :: FunPtr (HId_t -> Out H5F_info1_t -> IO HErr_t) Source #
h5f_set_mpi_atomicity :: HId_t -> HBool_t -> IO HErr_t Source #
Sets the atomicity mode
Returns non-negative on success, negative on failure > herr_t H5Fset_mpi_atomicity(hid_t file_id, hbool_t flag);
h5f_get_mpi_atomicity :: HId_t -> Out HBool_t -> IO HErr_t Source #
Returns the atomicity mode
Returns non-negative on success, negative on failure > herr_t H5Fget_mpi_atomicity(hid_t file_id, hbool_t *flag);
data H5F_info1_t Source #
Current "global" information about file (just size info currently)
Superblock extension size
Shared object header message header size
Shared object header message index & heap size
Instances
Storable H5F_info1_t Source # | Superblock extension size |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_info1_t -> Int # alignment :: H5F_info1_t -> Int # peekElemOff :: Ptr H5F_info1_t -> Int -> IO H5F_info1_t # pokeElemOff :: Ptr H5F_info1_t -> Int -> H5F_info1_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_info1_t # pokeByteOff :: Ptr b -> Int -> H5F_info1_t -> IO () # peek :: Ptr H5F_info1_t -> IO H5F_info1_t # poke :: Ptr H5F_info1_t -> H5F_info1_t -> IO () # | |
Show H5F_info1_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_info1_t -> ShowS # show :: H5F_info1_t -> String # showList :: [H5F_info1_t] -> ShowS # | |
Eq H5F_info1_t Source # | |
Defined in Bindings.HDF5.Raw.H5F (==) :: H5F_info1_t -> H5F_info1_t -> Bool # (/=) :: H5F_info1_t -> H5F_info1_t -> Bool # |
p'H5F_info1_t'sohm'hdr_size :: Ptr H5F_info1_t -> Ptr HSize_t Source #
Current "global" information about file (just size info currently)
data H5F_info_t Source #
Shared object header message header size
Shared object header message index & heap size
Instances
Storable H5F_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F sizeOf :: H5F_info_t -> Int # alignment :: H5F_info_t -> Int # peekElemOff :: Ptr H5F_info_t -> Int -> IO H5F_info_t # pokeElemOff :: Ptr H5F_info_t -> Int -> H5F_info_t -> IO () # peekByteOff :: Ptr b -> Int -> IO H5F_info_t # pokeByteOff :: Ptr b -> Int -> H5F_info_t -> IO () # peek :: Ptr H5F_info_t -> IO H5F_info_t # poke :: Ptr H5F_info_t -> H5F_info_t -> IO () # | |
Show H5F_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F showsPrec :: Int -> H5F_info_t -> ShowS # show :: H5F_info_t -> String # showList :: [H5F_info_t] -> ShowS # | |
Eq H5F_info_t Source # | |
Defined in Bindings.HDF5.Raw.H5F (==) :: H5F_info_t -> H5F_info_t -> Bool # (/=) :: H5F_info_t -> H5F_info_t -> Bool # |
h5f_get_info :: HId_t -> Out H5F_info_t -> IO HErr_t Source #