hdf5-1.8.14: Haskell interface to the HDF5 scientific data storage library.
Safe HaskellNone
LanguageHaskell2010

Bindings.HDF5.Raw.H5

Synopsis

Version numbers

h5_VERS_MAJOR :: Num a => a Source #

For major interface/format changes

h5_VERS_MINOR :: Num a => a Source #

For minor interface/format changes

h5_VERS_RELEASE :: Num a => a Source #

For tweaks, bug-fixes, or development

h5_VERS_SUBRELEASE :: String Source #

For pre-releases like snap0

vers :: Version Source #

h5_VERS_MAJOR, et al., wrapped up as a Version

h5_VERS_INFO :: String Source #

Full version string

h5_check :: HErr_t Source #

Check that the HDF5 library that is linked with the current executable is the same version that these bindings were compiled against. Returns 0 on success, calls abort() on failure.

Types and constants

newtype HErr_t Source #

Status return values. Failed integer functions in HDF5 result almost always in a negative value (unsigned failing functions sometimes return zero for failure) while successfull return is non-negative (often zero). The negative failure value is most commonly -1, but don't bet on it. The proper way to detect failure is something like:

if((dset = H5Dopen2(file, name)) < 0)
   fprintf(stderr, "unable to open the requested datasetn");

Constructors

HErr_t Int32 

Instances

Instances details
Storable HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: HErr_t -> Int

alignment :: HErr_t -> Int

peekElemOff :: Ptr HErr_t -> Int -> IO HErr_t

pokeElemOff :: Ptr HErr_t -> Int -> HErr_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO HErr_t

pokeByteOff :: Ptr b -> Int -> HErr_t -> IO ()

peek :: Ptr HErr_t -> IO HErr_t

poke :: Ptr HErr_t -> HErr_t -> IO ()

Bits HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(.&.) :: HErr_t -> HErr_t -> HErr_t

(.|.) :: HErr_t -> HErr_t -> HErr_t

xor :: HErr_t -> HErr_t -> HErr_t

complement :: HErr_t -> HErr_t

shift :: HErr_t -> Int -> HErr_t

rotate :: HErr_t -> Int -> HErr_t

zeroBits :: HErr_t

bit :: Int -> HErr_t

setBit :: HErr_t -> Int -> HErr_t

clearBit :: HErr_t -> Int -> HErr_t

complementBit :: HErr_t -> Int -> HErr_t

testBit :: HErr_t -> Int -> Bool

bitSizeMaybe :: HErr_t -> Maybe Int

bitSize :: HErr_t -> Int

isSigned :: HErr_t -> Bool

shiftL :: HErr_t -> Int -> HErr_t

unsafeShiftL :: HErr_t -> Int -> HErr_t

shiftR :: HErr_t -> Int -> HErr_t

unsafeShiftR :: HErr_t -> Int -> HErr_t

rotateL :: HErr_t -> Int -> HErr_t

rotateR :: HErr_t -> Int -> HErr_t

popCount :: HErr_t -> Int

Bounded HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Enum HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Num HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Integral HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Real HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

toRational :: HErr_t -> Rational

Show HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> HErr_t -> ShowS

show :: HErr_t -> String

showList :: [HErr_t] -> ShowS

Eq HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: HErr_t -> HErr_t -> Bool

(/=) :: HErr_t -> HErr_t -> Bool

Ord HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

compare :: HErr_t -> HErr_t -> Ordering

(<) :: HErr_t -> HErr_t -> Bool

(<=) :: HErr_t -> HErr_t -> Bool

(>) :: HErr_t -> HErr_t -> Bool

(>=) :: HErr_t -> HErr_t -> Bool

max :: HErr_t -> HErr_t -> HErr_t

min :: HErr_t -> HErr_t -> HErr_t

HDFResultType HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Core.HDFResultType

Methods

isError :: HErr_t -> Bool Source #

NativeType HErr_t Source # 
Instance details

Defined in Bindings.HDF5.Datatype.Internal

newtype HBool_t Source #

Boolean type. Successful return values are zero (false) or positive (true). The typical true value is 1 but don't bet on it. Boolean functions cannot fail. Functions that return htri_t however return zero (false), positive (true), or negative (failure). The proper way to test for truth from a htri_t function is:

 if ((retval = H5Tcommitted(type))>0) {
   printf("data type is committedn");
 } else if (!retval) {
   printf("data type is not committedn");
 } else {
   printf("error determining whether data type is committedn");
 }

Constructors

HBool_t Word8 

Instances

Instances details
Storable HBool_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: HBool_t -> Int

alignment :: HBool_t -> Int

peekElemOff :: Ptr HBool_t -> Int -> IO HBool_t

pokeElemOff :: Ptr HBool_t -> Int -> HBool_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO HBool_t

pokeByteOff :: Ptr b -> Int -> HBool_t -> IO ()

peek :: Ptr HBool_t -> IO HBool_t

poke :: Ptr HBool_t -> HBool_t -> IO ()

Show HBool_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> HBool_t -> ShowS

show :: HBool_t -> String

showList :: [HBool_t] -> ShowS

Eq HBool_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: HBool_t -> HBool_t -> Bool

(/=) :: HBool_t -> HBool_t -> Bool

NativeType HBool_t Source # 
Instance details

Defined in Bindings.HDF5.Datatype.Internal

newtype HTri_t Source #

Constructors

HTri_t Int32 

Instances

Instances details
Storable HTri_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: HTri_t -> Int

alignment :: HTri_t -> Int

peekElemOff :: Ptr HTri_t -> Int -> IO HTri_t

pokeElemOff :: Ptr HTri_t -> Int -> HTri_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO HTri_t

pokeByteOff :: Ptr b -> Int -> HTri_t -> IO ()

peek :: Ptr HTri_t -> IO HTri_t

poke :: Ptr HTri_t -> HTri_t -> IO ()

Show HTri_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> HTri_t -> ShowS

show :: HTri_t -> String

showList :: [HTri_t] -> ShowS

Eq HTri_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: HTri_t -> HTri_t -> Bool

(/=) :: HTri_t -> HTri_t -> Bool

HDFResultType HTri_t Source # 
Instance details

Defined in Bindings.HDF5.Core.HDFResultType

Methods

isError :: HTri_t -> Bool Source #

newtype CSSize Source #

C signed size type. This is a semi-standard POSIX type that isn't in the Foreign.C.Types module. It is in System.Posix.Types, but I'm not sure whether that module is available on all platforms.

Constructors

CSSize Int64 

Instances

Instances details
Storable CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: CSSize -> Int

alignment :: CSSize -> Int

peekElemOff :: Ptr CSSize -> Int -> IO CSSize

pokeElemOff :: Ptr CSSize -> Int -> CSSize -> IO ()

peekByteOff :: Ptr b -> Int -> IO CSSize

pokeByteOff :: Ptr b -> Int -> CSSize -> IO ()

peek :: Ptr CSSize -> IO CSSize

poke :: Ptr CSSize -> CSSize -> IO ()

Bits CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(.&.) :: CSSize -> CSSize -> CSSize

(.|.) :: CSSize -> CSSize -> CSSize

xor :: CSSize -> CSSize -> CSSize

complement :: CSSize -> CSSize

shift :: CSSize -> Int -> CSSize

rotate :: CSSize -> Int -> CSSize

zeroBits :: CSSize

bit :: Int -> CSSize

setBit :: CSSize -> Int -> CSSize

clearBit :: CSSize -> Int -> CSSize

complementBit :: CSSize -> Int -> CSSize

testBit :: CSSize -> Int -> Bool

bitSizeMaybe :: CSSize -> Maybe Int

bitSize :: CSSize -> Int

isSigned :: CSSize -> Bool

shiftL :: CSSize -> Int -> CSSize

unsafeShiftL :: CSSize -> Int -> CSSize

shiftR :: CSSize -> Int -> CSSize

unsafeShiftR :: CSSize -> Int -> CSSize

rotateL :: CSSize -> Int -> CSSize

rotateR :: CSSize -> Int -> CSSize

popCount :: CSSize -> Int

Bounded CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Enum CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Num CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Integral CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Real CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

toRational :: CSSize -> Rational

Show CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> CSSize -> ShowS

show :: CSSize -> String

showList :: [CSSize] -> ShowS

Eq CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: CSSize -> CSSize -> Bool

(/=) :: CSSize -> CSSize -> Bool

Ord CSSize Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

compare :: CSSize -> CSSize -> Ordering

(<) :: CSSize -> CSSize -> Bool

(<=) :: CSSize -> CSSize -> Bool

(>) :: CSSize -> CSSize -> Bool

(>=) :: CSSize -> CSSize -> Bool

max :: CSSize -> CSSize -> CSSize

min :: CSSize -> CSSize -> CSSize

newtype HSize_t Source #

Constructors

HSize_t Word64 

Instances

Instances details
Storable HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: HSize_t -> Int

alignment :: HSize_t -> Int

peekElemOff :: Ptr HSize_t -> Int -> IO HSize_t

pokeElemOff :: Ptr HSize_t -> Int -> HSize_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO HSize_t

pokeByteOff :: Ptr b -> Int -> HSize_t -> IO ()

peek :: Ptr HSize_t -> IO HSize_t

poke :: Ptr HSize_t -> HSize_t -> IO ()

Bits HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(.&.) :: HSize_t -> HSize_t -> HSize_t

(.|.) :: HSize_t -> HSize_t -> HSize_t

xor :: HSize_t -> HSize_t -> HSize_t

complement :: HSize_t -> HSize_t

shift :: HSize_t -> Int -> HSize_t

rotate :: HSize_t -> Int -> HSize_t

zeroBits :: HSize_t

bit :: Int -> HSize_t

setBit :: HSize_t -> Int -> HSize_t

clearBit :: HSize_t -> Int -> HSize_t

complementBit :: HSize_t -> Int -> HSize_t

testBit :: HSize_t -> Int -> Bool

bitSizeMaybe :: HSize_t -> Maybe Int

bitSize :: HSize_t -> Int

isSigned :: HSize_t -> Bool

shiftL :: HSize_t -> Int -> HSize_t

unsafeShiftL :: HSize_t -> Int -> HSize_t

shiftR :: HSize_t -> Int -> HSize_t

unsafeShiftR :: HSize_t -> Int -> HSize_t

rotateL :: HSize_t -> Int -> HSize_t

rotateR :: HSize_t -> Int -> HSize_t

popCount :: HSize_t -> Int

Bounded HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Enum HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Num HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Integral HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Real HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

toRational :: HSize_t -> Rational

Show HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> HSize_t -> ShowS

show :: HSize_t -> String

showList :: [HSize_t] -> ShowS

Eq HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: HSize_t -> HSize_t -> Bool

(/=) :: HSize_t -> HSize_t -> Bool

Ord HSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

compare :: HSize_t -> HSize_t -> Ordering

(<) :: HSize_t -> HSize_t -> Bool

(<=) :: HSize_t -> HSize_t -> Bool

(>) :: HSize_t -> HSize_t -> Bool

(>=) :: HSize_t -> HSize_t -> Bool

max :: HSize_t -> HSize_t -> HSize_t

min :: HSize_t -> HSize_t -> HSize_t

newtype HSSize_t Source #

Constructors

HSSize_t Int64 

Instances

Instances details
Storable HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: HSSize_t -> Int

alignment :: HSSize_t -> Int

peekElemOff :: Ptr HSSize_t -> Int -> IO HSSize_t

pokeElemOff :: Ptr HSSize_t -> Int -> HSSize_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO HSSize_t

pokeByteOff :: Ptr b -> Int -> HSSize_t -> IO ()

peek :: Ptr HSSize_t -> IO HSSize_t

poke :: Ptr HSSize_t -> HSSize_t -> IO ()

Bits HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Bounded HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Enum HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Num HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Integral HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Real HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

toRational :: HSSize_t -> Rational

Show HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> HSSize_t -> ShowS

show :: HSSize_t -> String

showList :: [HSSize_t] -> ShowS

Eq HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: HSSize_t -> HSSize_t -> Bool

(/=) :: HSSize_t -> HSSize_t -> Bool

Ord HSSize_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

compare :: HSSize_t -> HSSize_t -> Ordering

(<) :: HSSize_t -> HSSize_t -> Bool

(<=) :: HSSize_t -> HSSize_t -> Bool

(>) :: HSSize_t -> HSSize_t -> Bool

(>=) :: HSSize_t -> HSSize_t -> Bool

max :: HSSize_t -> HSSize_t -> HSSize_t

min :: HSSize_t -> HSSize_t -> HSSize_t

newtype HAddr_t Source #

Constructors

HAddr_t Word64 

Instances

Instances details
Storable HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: HAddr_t -> Int

alignment :: HAddr_t -> Int

peekElemOff :: Ptr HAddr_t -> Int -> IO HAddr_t

pokeElemOff :: Ptr HAddr_t -> Int -> HAddr_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO HAddr_t

pokeByteOff :: Ptr b -> Int -> HAddr_t -> IO ()

peek :: Ptr HAddr_t -> IO HAddr_t

poke :: Ptr HAddr_t -> HAddr_t -> IO ()

Bits HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(.&.) :: HAddr_t -> HAddr_t -> HAddr_t

(.|.) :: HAddr_t -> HAddr_t -> HAddr_t

xor :: HAddr_t -> HAddr_t -> HAddr_t

complement :: HAddr_t -> HAddr_t

shift :: HAddr_t -> Int -> HAddr_t

rotate :: HAddr_t -> Int -> HAddr_t

zeroBits :: HAddr_t

bit :: Int -> HAddr_t

setBit :: HAddr_t -> Int -> HAddr_t

clearBit :: HAddr_t -> Int -> HAddr_t

complementBit :: HAddr_t -> Int -> HAddr_t

testBit :: HAddr_t -> Int -> Bool

bitSizeMaybe :: HAddr_t -> Maybe Int

bitSize :: HAddr_t -> Int

isSigned :: HAddr_t -> Bool

shiftL :: HAddr_t -> Int -> HAddr_t

unsafeShiftL :: HAddr_t -> Int -> HAddr_t

shiftR :: HAddr_t -> Int -> HAddr_t

unsafeShiftR :: HAddr_t -> Int -> HAddr_t

rotateL :: HAddr_t -> Int -> HAddr_t

rotateR :: HAddr_t -> Int -> HAddr_t

popCount :: HAddr_t -> Int

Bounded HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Enum HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Num HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Integral HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Real HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

toRational :: HAddr_t -> Rational

Show HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> HAddr_t -> ShowS

show :: HAddr_t -> String

showList :: [HAddr_t] -> ShowS

Eq HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: HAddr_t -> HAddr_t -> Bool

(/=) :: HAddr_t -> HAddr_t -> Bool

Ord HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

compare :: HAddr_t -> HAddr_t -> Ordering

(<) :: HAddr_t -> HAddr_t -> Bool

(<=) :: HAddr_t -> HAddr_t -> Bool

(>) :: HAddr_t -> HAddr_t -> Bool

(>=) :: HAddr_t -> HAddr_t -> Bool

max :: HAddr_t -> HAddr_t -> HAddr_t

min :: HAddr_t -> HAddr_t -> HAddr_t

HDFResultType HAddr_t Source # 
Instance details

Defined in Bindings.HDF5.Core.HDFResultType

Methods

isError :: HAddr_t -> Bool Source #

newtype H5_iter_order_t Source #

Common iteration orders

Constructors

H5_iter_order_t Int32 

Instances

Instances details
Storable H5_iter_order_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: H5_iter_order_t -> Int

alignment :: H5_iter_order_t -> Int

peekElemOff :: Ptr H5_iter_order_t -> Int -> IO H5_iter_order_t

pokeElemOff :: Ptr H5_iter_order_t -> Int -> H5_iter_order_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO H5_iter_order_t

pokeByteOff :: Ptr b -> Int -> H5_iter_order_t -> IO ()

peek :: Ptr H5_iter_order_t -> IO H5_iter_order_t

poke :: Ptr H5_iter_order_t -> H5_iter_order_t -> IO ()

Show H5_iter_order_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> H5_iter_order_t -> ShowS

show :: H5_iter_order_t -> String

showList :: [H5_iter_order_t] -> ShowS

HDFResultType H5_iter_order_t Source # 
Instance details

Defined in Bindings.HDF5.Core.HDFResultType

Methods

isError :: H5_iter_order_t -> Bool Source #

h5_ITER_INC :: H5_iter_order_t Source #

Increasing order

h5_ITER_DEC :: H5_iter_order_t Source #

Decreasing order

h5_ITER_NATIVE :: H5_iter_order_t Source #

No particular order, whatever is fastest

h5_ITER_N :: Num a => a Source #

Number of iteration orders

h5_ITER_ERROR :: HErr_t Source #

Iteration callback return value indicating that iteration should stop and report an error.

h5_ITER_CONT :: HErr_t Source #

Iteration callback return value indicating that iteration should continue.

h5_ITER_STOP :: HErr_t Source #

Iteration callback return value indicating that iteration should stop without error.

Actually, any postive value will cause the iterator to stop and pass back that positive value to the function that called the iterator

newtype H5_index_t Source #

The types of indices on links in groups/attributes on objects. Primarily used for "<do> <foo> by index" routines and for iterating over links in groups/attributes on objects.

Constructors

H5_index_t Int32 

Instances

Instances details
Storable H5_index_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: H5_index_t -> Int

alignment :: H5_index_t -> Int

peekElemOff :: Ptr H5_index_t -> Int -> IO H5_index_t

pokeElemOff :: Ptr H5_index_t -> Int -> H5_index_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO H5_index_t

pokeByteOff :: Ptr b -> Int -> H5_index_t -> IO ()

peek :: Ptr H5_index_t -> IO H5_index_t

poke :: Ptr H5_index_t -> H5_index_t -> IO ()

Show H5_index_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> H5_index_t -> ShowS

show :: H5_index_t -> String

showList :: [H5_index_t] -> ShowS

HDFResultType H5_index_t Source # 
Instance details

Defined in Bindings.HDF5.Core.HDFResultType

Methods

isError :: H5_index_t -> Bool Source #

h5_INDEX_UNKNOWN :: H5_index_t Source #

Unknown index type

h5_INDEX_NAME :: H5_index_t Source #

Index on names

h5_INDEX_CRT_ORDER :: H5_index_t Source #

Index on creation order

h5_INDEX_N :: Num a => a Source #

Number of indices defined

data H5_ih_info_t Source #

Storage info struct used by H5O_info_t and H5F_info_t

Instances

Instances details
Storable H5_ih_info_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

sizeOf :: H5_ih_info_t -> Int

alignment :: H5_ih_info_t -> Int

peekElemOff :: Ptr H5_ih_info_t -> Int -> IO H5_ih_info_t

pokeElemOff :: Ptr H5_ih_info_t -> Int -> H5_ih_info_t -> IO ()

peekByteOff :: Ptr b -> Int -> IO H5_ih_info_t

pokeByteOff :: Ptr b -> Int -> H5_ih_info_t -> IO ()

peek :: Ptr H5_ih_info_t -> IO H5_ih_info_t

poke :: Ptr H5_ih_info_t -> H5_ih_info_t -> IO ()

Show H5_ih_info_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

showsPrec :: Int -> H5_ih_info_t -> ShowS

show :: H5_ih_info_t -> String

showList :: [H5_ih_info_t] -> ShowS

Eq H5_ih_info_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5

Methods

(==) :: H5_ih_info_t -> H5_ih_info_t -> Bool

(/=) :: H5_ih_info_t -> H5_ih_info_t -> Bool

Functions in H5.c

p'H5_ih_info_t'index_size :: Ptr H5_ih_info_t -> Ptr HSize_t Source #

Initialize the library. This is normally called automatically, but if you find that an HDF5 library function is failing inexplicably, then try calling this function first.

Return: Non-negative on success/Negative on failure

herr_t H5open(void);

p_H5open :: FunPtr (IO HErr_t) Source #

h5_close :: IO HErr_t Source #

Terminate the library and release all resources.

Return: Non-negative on success/Negative on failure

herr_t H5close(void);

p_H5close :: FunPtr (IO HErr_t) Source #

h5_dont_atexit :: IO HErr_t Source #

Indicates that the library is not to clean up after itself when the application exits by calling exit() or returning from main(). This function must be called before any other HDF5 function or constant is used or it will have no effect.

If this function is used then certain memory buffers will not be de-allocated nor will open files be flushed automatically. The application may still call H5close() explicitly to accomplish these things.

Return: non-negative on success, negative if this function is called more than once or if it is called too late.

herr_t H5dont_atexit(void);

h5_garbage_collect :: IO HErr_t Source #

Walks through all the garbage collection routines for the library, which are supposed to free any unused memory they have allocated.

These should probably be registered dynamicly in a linked list of functions to call, but there aren't that many right now, so we hard-wire them...

Return: non-negative on success, negative on failure

herr_t H5garbage_collect(void);

h5_set_free_list_limits :: CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO HErr_t Source #

Sets limits on the different kinds of free lists. Setting a value of -1 for a limit means no limit of that type. These limits are global for the entire library. Each "global" limit only applies to free lists of that type, so if an application sets a limit of 1 MB on each of the global lists, up to 3 MB of total storage might be allocated (1MB on each of regular, array and block type lists).

The settings for block free lists are duplicated to factory free lists. Factory free list limits cannot be set independently currently.

Parameters:

reg_global_lim :: CInt
The limit on all "regular" free list memory used
reg_list_lim :: CInt
The limit on memory used in each "regular" free list
arr_global_lim :: CInt
The limit on all "array" free list memory used
arr_list_lim :: CInt
The limit on memory used in each "array" free list
blk_global_lim :: CInt
The limit on all "block" free list memory used
blk_list_lim :: CInt
The limit on memory used in each "block" free list

Return: non-negative on success, negative on failure

herr_t H5set_free_list_limits (int reg_global_lim, int reg_list_lim,
        int arr_global_lim, int arr_list_lim, int blk_global_lim,
        int blk_list_lim);

p_H5set_free_list_limits :: FunPtr (CInt -> CInt -> CInt -> CInt -> CInt -> CInt -> IO HErr_t) Source #

h5_get_libversion :: Out CUInt -> Out CUInt -> Out CUInt -> IO HErr_t Source #

Returns the library version numbers through arguments. MAJNUM will be the major revision number of the library, MINNUM the minor revision number, and RELNUM the release revision number.

Note: When printing an HDF5 version number it should be printed as

printf("%u.%u.%u", maj, min, rel)		or
printf("version %u.%u release %u", maj, min, rel)

Return: Non-negative on success/Negative on failure

herr_t H5get_libversion(unsigned *majnum, unsigned *minnum,
        unsigned *relnum);

p_H5get_libversion :: FunPtr (Out CUInt -> Out CUInt -> Out CUInt -> IO HErr_t) Source #

h5_check_version :: CUInt -> CUInt -> CUInt -> IO HErr_t Source #

Purpose: Verifies that the arguments match the version numbers compiled into the library. This function is intended to be called from user to verify that the versions of header files compiled into the application match the version of the hdf5 library.

Return: Success: 0, Failure: calls abort()

herr_t H5check_version(unsigned majnum, unsigned minnum,
        unsigned relnum);

p_H5check_version :: FunPtr (CUInt -> CUInt -> CUInt -> IO HErr_t) Source #