| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Bindings.HDF5.Raw.H5I
Synopsis
- newtype H5I_type_t = H5I_type_t Int32
- h5i_UNINIT :: H5I_type_t
- h5i_BADID :: H5I_type_t
- h5i_FILE :: H5I_type_t
- h5i_GROUP :: H5I_type_t
- h5i_DATATYPE :: H5I_type_t
- h5i_DATASPACE :: H5I_type_t
- h5i_DATASET :: H5I_type_t
- h5i_ATTR :: H5I_type_t
- h5i_VFL :: H5I_type_t
- h5i_GENPROP_CLS :: H5I_type_t
- h5i_GENPROP_LST :: H5I_type_t
- h5i_ERROR_CLASS :: H5I_type_t
- h5i_ERROR_MSG :: H5I_type_t
- h5i_ERROR_STACK :: H5I_type_t
- h5i_NTYPES :: Num a => a
- newtype HId_t = HId_t Int64
- h5_SIZEOF_HID_T :: CSize
- h5i_INVALID_HID :: HId_t
- type H5I_free_t a = FunPtr (In a -> IO HErr_t)
- type H5I_search_func_t a = FunPtr (In a -> HId_t -> In a -> IO CInt)
- h5i_register :: H5I_type_t -> In a -> IO HId_t
- p_H5Iregister :: FunPtr (H5I_type_t -> In a -> IO HId_t)
- h5i_object_verify :: HId_t -> H5I_type_t -> IO (Ptr a)
- p_H5Iobject_verify :: FunPtr (HId_t -> H5I_type_t -> IO (Ptr a))
- h5i_remove_verify :: HId_t -> H5I_type_t -> IO (Ptr a)
- p_H5Iremove_verify :: FunPtr (HId_t -> H5I_type_t -> IO (Ptr a))
- h5i_get_type :: HId_t -> IO H5I_type_t
- p_H5Iget_type :: FunPtr (HId_t -> IO H5I_type_t)
- h5i_get_file_id :: HId_t -> IO HId_t
- p_H5Iget_file_id :: FunPtr (HId_t -> IO HId_t)
- h5i_get_name :: HId_t -> OutArray CChar -> CSize -> IO CSSize
- p_H5Iget_name :: FunPtr (HId_t -> OutArray CChar -> CSize -> IO CSSize)
- h5i_inc_ref :: HId_t -> IO CInt
- p_H5Iinc_ref :: FunPtr (HId_t -> IO CInt)
- h5i_dec_ref :: HId_t -> IO CInt
- p_H5Idec_ref :: FunPtr (HId_t -> IO CInt)
- h5i_get_ref :: HId_t -> IO CInt
- p_H5Iget_ref :: FunPtr (HId_t -> IO CInt)
- h5i_register_type :: CSize -> CUInt -> H5I_free_t a -> IO H5I_type_t
- p_H5Iregister_type :: FunPtr (CSize -> CUInt -> H5I_free_t a -> IO H5I_type_t)
- h5i_clear_type :: H5I_type_t -> HBool_t -> IO HErr_t
- p_H5Iclear_type :: FunPtr (H5I_type_t -> HBool_t -> IO HErr_t)
- h5i_destroy_type :: H5I_type_t -> IO HErr_t
- p_H5Idestroy_type :: FunPtr (H5I_type_t -> IO HErr_t)
- h5i_inc_type_ref :: H5I_type_t -> IO CInt
- p_H5Iinc_type_ref :: FunPtr (H5I_type_t -> IO CInt)
- h5i_dec_type_ref :: H5I_type_t -> IO CInt
- p_H5Idec_type_ref :: FunPtr (H5I_type_t -> IO CInt)
- h5i_get_type_ref :: H5I_type_t -> IO CInt
- p_H5Iget_type_ref :: FunPtr (H5I_type_t -> IO CInt)
- h5i_search :: H5I_type_t -> H5I_search_func_t a -> In a -> IO (Ptr a)
- p_H5Isearch :: FunPtr (H5I_type_t -> H5I_search_func_t a -> In a -> IO (Ptr a))
- h5i_nmembers :: H5I_type_t -> Out HSize_t -> IO HErr_t
- p_H5Inmembers :: FunPtr (H5I_type_t -> Out HSize_t -> IO HErr_t)
- h5i_type_exists :: H5I_type_t -> IO HTri_t
- p_H5Itype_exists :: FunPtr (H5I_type_t -> IO HTri_t)
- h5i_is_valid :: HId_t -> IO HTri_t
- p_H5Iis_valid :: FunPtr (HId_t -> IO HTri_t)
Documentation
newtype H5I_type_t Source #
Library type values
Constructors
| H5I_type_t Int32 | 
Instances
| Storable H5I_type_t Source # | |
| Defined in Bindings.HDF5.Raw.H5I Methods sizeOf :: H5I_type_t -> Int alignment :: H5I_type_t -> Int peekElemOff :: Ptr H5I_type_t -> Int -> IO H5I_type_t pokeElemOff :: Ptr H5I_type_t -> Int -> H5I_type_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5I_type_t pokeByteOff :: Ptr b -> Int -> H5I_type_t -> IO () peek :: Ptr H5I_type_t -> IO H5I_type_t poke :: Ptr H5I_type_t -> H5I_type_t -> IO () | |
| Show H5I_type_t Source # | |
| Defined in Bindings.HDF5.Raw.H5I Methods showsPrec :: Int -> H5I_type_t -> ShowS show :: H5I_type_t -> String showList :: [H5I_type_t] -> ShowS | |
| Eq H5I_type_t Source # | |
| Defined in Bindings.HDF5.Raw.H5I | |
| HDFResultType H5I_type_t Source # | |
| Defined in Bindings.HDF5.Core.HDFResultType Methods isError :: H5I_type_t -> Bool Source # | |
h5i_UNINIT :: H5I_type_t Source #
uninitialized type
h5i_BADID :: H5I_type_t Source #
invalid Type
h5i_FILE :: H5I_type_t Source #
type ID for File objects
h5i_GROUP :: H5I_type_t Source #
type ID for Group objects
h5i_DATATYPE :: H5I_type_t Source #
type ID for Datatype objects
h5i_DATASPACE :: H5I_type_t Source #
type ID for Dataspace objects
h5i_DATASET :: H5I_type_t Source #
type ID for Dataset objects
h5i_ATTR :: H5I_type_t Source #
type ID for Attribute objects
h5i_VFL :: H5I_type_t Source #
type ID for virtual file layer
h5i_GENPROP_CLS :: H5I_type_t Source #
type ID for generic property list classes
h5i_GENPROP_LST :: H5I_type_t Source #
type ID for generic property lists
h5i_ERROR_CLASS :: H5I_type_t Source #
type ID for error classes
h5i_ERROR_MSG :: H5I_type_t Source #
type ID for error messages
h5i_ERROR_STACK :: H5I_type_t Source #
type ID for error stacks
h5i_NTYPES :: Num a => a Source #
number of library types
Type of atoms to return to users
Constructors
| HId_t Int64 | 
Instances
| Storable HId_t Source # | |
| Defined in Bindings.HDF5.Raw.H5I Methods peekElemOff :: Ptr HId_t -> Int -> IO HId_t pokeElemOff :: Ptr HId_t -> Int -> HId_t -> IO () peekByteOff :: Ptr b -> Int -> IO HId_t pokeByteOff :: Ptr b -> Int -> HId_t -> IO () | |
| Show HId_t Source # | |
| Eq HId_t Source # | |
| Ord HId_t Source # | |
| HDFResultType HId_t Source # | |
| Defined in Bindings.HDF5.Core.HDFResultType | |
| FromHId HId_t Source # | |
| Defined in Bindings.HDF5.Core.HId Methods uncheckedFromHId :: HId_t -> HId_t Source # | |
| HId HId_t Source # | |
h5_SIZEOF_HID_T :: CSize Source #
h5i_INVALID_HID :: HId_t Source #
An invalid object ID. This is also negative for error return.
type H5I_free_t a = FunPtr (In a -> IO HErr_t) Source #
Function for freeing objects. This function will be called with an object ID type number and a pointer to the object. The function should free the object and return non-negative to indicate that the object can be removed from the ID type. If the function returns negative (failure) then the object will remain in the ID type.
type H5I_search_func_t a = FunPtr (In a -> HId_t -> In a -> IO CInt) Source #
Type of the function to compare objects & keys
h5i_register :: H5I_type_t -> In a -> IO HId_t Source #
Registers an object in a 'type' and returns an ID for it.
 This routine does _not_ check for unique-ness of the objects,
 if you register an object twice, you will get two different
 IDs for it.  This routine does make certain that each ID in a
 type is unique.  IDs are created by getting a unique number
 for the type the ID is in and incorporating the type into
 the ID which is returned to the user.
Return: Success: New object id. Failure: Negative
hid_t H5Iregister(H5I_type_t type, const void *object);
p_H5Iregister :: FunPtr (H5I_type_t -> In a -> IO HId_t) Source #
h5i_object_verify :: HId_t -> H5I_type_t -> IO (Ptr a) Source #
Find an object pointer for the specified ID, verifying that it is in a particular type.
On success, returns a non-null object pointer associated with the specified ID. On failure, returns NULL.
void *H5Iobject_verify(hid_t id, H5I_type_t id_type);
p_H5Iobject_verify :: FunPtr (HId_t -> H5I_type_t -> IO (Ptr a)) Source #
h5i_remove_verify :: HId_t -> H5I_type_t -> IO (Ptr a) Source #
Removes the specified ID from its type, first checking that the type of the ID and the type type are the same.
On success, returns a pointer to the object that was removed, the
 same pointer which would have been found by calling h5i_object.
 On failure, returns NULL.
void *H5Iremove_verify(hid_t id, H5I_type_t id_type);
p_H5Iremove_verify :: FunPtr (HId_t -> H5I_type_t -> IO (Ptr a)) Source #
h5i_get_type :: HId_t -> IO H5I_type_t Source #
Retrieves the number of references outstanding for a type. Returns negative on failure.
H5I_type_t H5Iget_type(hid_t id);
p_H5Iget_type :: FunPtr (HId_t -> IO H5I_type_t) Source #
h5i_get_file_id :: HId_t -> IO HId_t Source #
Obtains the file ID given an object ID. User has to close this ID. Returns a negative value on failure.
hid_t H5Iget_file_id(hid_t id);
p_H5Iget_file_id :: FunPtr (HId_t -> IO HId_t) Source #
h5i_get_name :: HId_t -> OutArray CChar -> CSize -> IO CSSize Source #
Gets a name of an object from its ID.
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.
 If a zero is returned for the name's length, then there is no name
 associated with the ID.
ssize_t H5Iget_name(hid_t id, char *name/*out*/, size_t size);
h5i_inc_ref :: HId_t -> IO CInt Source #
Increments the number of references outstanding for an ID.
On success, returns the new reference count. On failure, returns a negative value.
int H5Iinc_ref(hid_t id);
p_H5Iinc_ref :: FunPtr (HId_t -> IO CInt) Source #
h5i_dec_ref :: HId_t -> IO CInt Source #
Decrements the number of references outstanding for an ID. If the reference count for an ID reaches zero, the object will be closed.
On success, returns the new reference count. On failure, returns a negative value.
int H5Idec_ref(hid_t id);
p_H5Idec_ref :: FunPtr (HId_t -> IO CInt) Source #
h5i_get_ref :: HId_t -> IO CInt Source #
Retrieves the number of references outstanding for an ID. Returns a negative value on failure.
int H5Iget_ref(hid_t id);
p_H5Iget_ref :: FunPtr (HId_t -> IO CInt) Source #
h5i_register_type :: CSize -> CUInt -> H5I_free_t a -> IO H5I_type_t Source #
Creates a new type of ID's to give out.  A specific number
 (reserved) of type entries may be reserved to enable "constant"
 values to be handed out which are valid IDs in the type, but which
 do not map to any data structures and are not allocated dynamically
 later.  hash_size is the minimum hash table size to use for the
 type.  free_func is called with an object pointer when the object
 is removed from the type.
On success, returns the type ID of the new type.
 On failure, returns h5i_BADID.
H5I_type_t H5Iregister_type(size_t hash_size, unsigned reserved, H5I_free_t free_func);
p_H5Iregister_type :: FunPtr (CSize -> CUInt -> H5I_free_t a -> IO H5I_type_t) Source #
h5i_clear_type :: H5I_type_t -> HBool_t -> IO HErr_t Source #
Removes all objects from the type, calling the free function for each object regardless of the reference count.
Returns non-negative on success, negative on failure.
herr_t H5Iclear_type(H5I_type_t type, hbool_t force);
p_H5Iclear_type :: FunPtr (H5I_type_t -> HBool_t -> IO HErr_t) Source #
h5i_destroy_type :: H5I_type_t -> IO HErr_t Source #
Destroys a type along with all atoms in that type regardless of their reference counts. Destroying IDs involves calling the free-func for each ID's object and then adding the ID struct to the ID free list.
Returns zero on success, negative on failure.
herr_t H5Idestroy_type(H5I_type_t type);
p_H5Idestroy_type :: FunPtr (H5I_type_t -> IO HErr_t) Source #
h5i_inc_type_ref :: H5I_type_t -> IO CInt Source #
Increments the number of references outstanding for an ID type.
On success, returns the new reference count. On failure, returns a negative value.
int H5Iinc_type_ref(H5I_type_t type);
p_H5Iinc_type_ref :: FunPtr (H5I_type_t -> IO CInt) Source #
h5i_dec_type_ref :: H5I_type_t -> IO CInt Source #
Decrements the reference count on an entire type of IDs. If the type reference count becomes zero then the type is destroyed along with all atoms in that type regardless of their reference counts. Destroying IDs involves calling the free-func for each ID's object and then adding the ID struct to the ID free list.
Returns the number of references to the type on success; a return value of 0 means that the type will have to be re-initialized before it can be used again (and should probably be set to H5I_UNINIT).
int H5Idec_type_ref(H5I_type_t type);
p_H5Idec_type_ref :: FunPtr (H5I_type_t -> IO CInt) Source #
h5i_get_type_ref :: H5I_type_t -> IO CInt Source #
Retrieves the number of references outstanding for a type. Returns a negative value on failure.
int H5Iget_type_ref(H5I_type_t type);
p_H5Iget_type_ref :: FunPtr (H5I_type_t -> IO CInt) Source #
h5i_search :: H5I_type_t -> H5I_search_func_t a -> In a -> IO (Ptr a) Source #
Apply function func to each member of type 'type' and return a
 pointer to the first object for which func returns non-zero.
 The func should take a pointer to the object and the key as
 arguments and return non-zero to terminate the search (zero
 to continue).
Limitation: Currently there is no way to start searching from where a previous search left off.
Returns the first object in the type for which func returns
 non-zero.  Returns NULL if func returned zero for every object in
 the type.
void *H5Isearch(H5I_type_t type, H5I_search_func_t func, void *key);
p_H5Isearch :: FunPtr (H5I_type_t -> H5I_search_func_t a -> In a -> IO (Ptr a)) Source #
h5i_nmembers :: H5I_type_t -> Out HSize_t -> IO HErr_t Source #
Returns the number of members in a type. The public interface throws an error if the supplied type does not exist. This is different than the private interface, which will just return 0.
Returns zero on success, negative on failure.
herr_t H5Inmembers(H5I_type_t type, hsize_t *num_members);
p_H5Inmembers :: FunPtr (H5I_type_t -> Out HSize_t -> IO HErr_t) Source #
h5i_type_exists :: H5I_type_t -> IO HTri_t Source #
Check whether the given type is currently registered with the library.
htri_t H5Itype_exists(H5I_type_t type);
p_H5Itype_exists :: FunPtr (H5I_type_t -> IO HTri_t) Source #
h5i_is_valid :: HId_t -> IO HTri_t Source #
Check if the given id is valid. An id is valid if it is in use and has an application reference count of at least 1.
htri_t H5Iis_valid(hid_t id);
p_H5Iis_valid :: FunPtr (HId_t -> IO HTri_t) Source #