Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Bindings.HDF5.Raw.H5L
Synopsis
- h5l_MAX_LINK_NAME_LEN :: Word32
- h5l_SAME_LOC :: HId_t
- h5l_LINK_CLASS_T_VERS :: Num a => a
- newtype H5L_type_t = H5L_type_t Int32
- h5l_TYPE_ERROR :: H5L_type_t
- h5l_TYPE_HARD :: H5L_type_t
- h5l_TYPE_SOFT :: H5L_type_t
- h5l_TYPE_EXTERNAL :: H5L_type_t
- h5l_TYPE_MAX :: H5L_type_t
- h5l_TYPE_BUILTIN_MAX :: H5L_type_t
- h5l_TYPE_UD_MIN :: H5L_type_t
- type H5L_create_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> HId_t -> IO HErr_t)
- type H5L_move_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> IO HErr_t)
- type H5L_copy_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> IO HErr_t)
- type H5L_traverse_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> HId_t -> IO HErr_t)
- type H5L_delete_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> IO HErr_t)
- type H5L_query_func_t a b = FunPtr (CString -> Ptr a -> CSize -> Out b -> CSize -> IO CSSize)
- data H5L_class_t = H5L_class_t {
- h5l_class_t'version :: CInt
- h5l_class_t'id :: H5L_type_t
- h5l_class_t'comment :: CString
- h5l_class_t'create_func :: H5L_create_func_t ()
- h5l_class_t'move_func :: H5L_move_func_t ()
- h5l_class_t'copy_func :: H5L_copy_func_t ()
- h5l_class_t'trav_func :: H5L_traverse_func_t ()
- h5l_class_t'del_func :: H5L_delete_func_t ()
- h5l_class_t'query_func :: H5L_query_func_t () ()
- type H5L_elink_traverse_t a = FunPtr (CString -> CString -> CString -> CString -> Ptr CUInt -> HId_t -> Ptr a -> IO HErr_t)
- p'H5L_class_t'version :: Ptr H5L_class_t -> Ptr CInt
- p'H5L_class_t'id :: Ptr H5L_class_t -> Ptr H5L_type_t
- p'H5L_class_t'comment :: Ptr H5L_class_t -> Ptr CString
- p'H5L_class_t'create_func :: Ptr H5L_class_t -> Ptr (H5L_create_func_t ())
- p'H5L_class_t'move_func :: Ptr H5L_class_t -> Ptr (H5L_move_func_t ())
- p'H5L_class_t'copy_func :: Ptr H5L_class_t -> Ptr (H5L_copy_func_t ())
- p'H5L_class_t'trav_func :: Ptr H5L_class_t -> Ptr (H5L_traverse_func_t ())
- p'H5L_class_t'del_func :: Ptr H5L_class_t -> Ptr (H5L_delete_func_t ())
- h5l_move :: HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
- p'H5L_class_t'query_func :: Ptr H5L_class_t -> Ptr (H5L_query_func_t () ())
- p_H5Lmove :: FunPtr (HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
- h5l_copy :: HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
- p_H5Lcopy :: FunPtr (HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
- h5l_create_hard :: HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
- p_H5Lcreate_hard :: FunPtr (HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
- h5l_create_soft :: CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
- p_H5Lcreate_soft :: FunPtr (CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
- h5l_delete :: HId_t -> CString -> HId_t -> IO HErr_t
- p_H5Ldelete :: FunPtr (HId_t -> CString -> HId_t -> IO HErr_t)
- h5l_delete_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> HId_t -> IO HErr_t
- p_H5Ldelete_by_idx :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> HId_t -> IO HErr_t)
- h5l_get_val :: HId_t -> CString -> OutArray a -> CSize -> HId_t -> IO HErr_t
- p_H5Lget_val :: FunPtr (HId_t -> CString -> OutArray a -> CSize -> HId_t -> IO HErr_t)
- h5l_get_val_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray a -> CSize -> HId_t -> IO HErr_t
- p_H5Lget_val_by_idx :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray a -> CSize -> HId_t -> IO HErr_t)
- h5l_exists :: HId_t -> CString -> HId_t -> IO HTri_t
- p_H5Lexists :: FunPtr (HId_t -> CString -> HId_t -> IO HTri_t)
- h5l_get_name_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray CChar -> CSSize -> HId_t -> IO CSSize
- p_H5Lget_name_by_idx :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray CChar -> CSSize -> HId_t -> IO CSSize)
- h5l_create_ud :: HId_t -> CString -> H5L_type_t -> In a -> CSize -> HId_t -> HId_t -> IO HErr_t
- p_H5Lcreate_ud :: FunPtr (HId_t -> CString -> H5L_type_t -> In a -> CSize -> HId_t -> HId_t -> IO HErr_t)
- h5l_register :: In H5L_class_t -> IO HErr_t
- p_H5Lregister :: FunPtr (In H5L_class_t -> IO HErr_t)
- h5l_unregister :: H5L_type_t -> IO HErr_t
- p_H5Lunregister :: FunPtr (H5L_type_t -> IO HErr_t)
- h5l_is_registered :: H5L_type_t -> IO HTri_t
- p_H5Lis_registered :: FunPtr (H5L_type_t -> IO HTri_t)
- h5l_unpack_elink_val :: InArray a -> CSize -> Out CUInt -> Out (Ptr CChar) -> Out (Ptr CChar) -> IO HErr_t
- p_H5Lunpack_elink_val :: FunPtr (InArray a -> CSize -> Out CUInt -> Out (Ptr CChar) -> Out (Ptr CChar) -> IO HErr_t)
- h5l_create_external :: CString -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t
- p_H5Lcreate_external :: FunPtr (CString -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t)
- data H5L_info1_t = H5L_info1_t {}
- p'H5L_info1_t'type :: Ptr H5L_info1_t -> Ptr H5L_type_t
- data H5L_info2_t = H5L_info2_t {}
- p'H5L_info1_t'corder_valid :: Ptr H5L_info1_t -> Ptr HBool_t
- type H5L_info_t = H5L_info1_t
- p'H5L_info1_t'corder :: Ptr H5L_info1_t -> Ptr Int64
- p'H5L_info1_t'cset :: Ptr H5L_info1_t -> Ptr H5T_cset_t
- p'H5L_info1_t'u'address :: Ptr H5L_info1_t -> Ptr HAddr_t
- p'H5L_info2_t'type :: Ptr H5L_info2_t -> Ptr H5L_type_t
- p'H5L_info1_t'u'val_size :: Ptr H5L_info1_t -> Ptr CSize
- p'H5L_info2_t'corder_valid :: Ptr H5L_info2_t -> Ptr HBool_t
- u_H5L_info1_t'u'address :: H5L_info1_t -> HAddr_t -> IO H5L_info1_t
- p'H5L_info2_t'corder :: Ptr H5L_info2_t -> Ptr Int64
- p'H5L_info2_t'cset :: Ptr H5L_info2_t -> Ptr H5T_cset_t
- p'H5L_info2_t'u'token :: Ptr H5L_info2_t -> Ptr H5O_token_t
- p'H5L_info2_t'u'val_size :: Ptr H5L_info2_t -> Ptr CSize
- u_H5L_info1_t'u'val_size :: H5L_info1_t -> CSize -> IO H5L_info1_t
- u_H5L_info2_t'u'token :: H5L_info2_t -> H5O_token_t -> IO H5L_info2_t
- u_H5L_info2_t'u'val_size :: H5L_info2_t -> CSize -> IO H5L_info2_t
- h5l_get_info1 :: HId_t -> CString -> Out H5L_info1_t -> HId_t -> IO HErr_t
- h5l_get_info2 :: HId_t -> CString -> Out H5L_info2_t -> HId_t -> IO HErr_t
- p_H5Lget_info1 :: FunPtr (HId_t -> CString -> Out H5L_info1_t -> HId_t -> IO HErr_t)
- h5l_get_info :: HId_t -> CString -> Out H5L_info_t -> HId_t -> IO HErr_t
- p_H5Lget_info2 :: FunPtr (HId_t -> CString -> Out H5L_info2_t -> HId_t -> IO HErr_t)
- h5l_get_info_by_idx1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info1_t -> HId_t -> IO HErr_t
- h5l_get_info_by_idx2 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info2_t -> HId_t -> IO HErr_t
- p_H5Lget_info_by_idx1 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info1_t -> HId_t -> IO HErr_t)
- h5l_get_info_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info_t -> HId_t -> IO HErr_t
- p_H5Lget_info_by_idx2 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info2_t -> HId_t -> IO HErr_t)
- type H5L_iterate1_t a = FunPtr (HId_t -> CString -> In H5L_info1_t -> InOut a -> IO HErr_t)
- mk'H5L_iterate1_t :: (HId_t -> CString -> In H5L_info1_t -> InOut a -> IO HErr_t) -> IO (FunPtr (HId_t -> CString -> In H5L_info1_t -> InOut a -> IO HErr_t))
- type H5L_iterate2_t a = FunPtr (HId_t -> CString -> In H5L_info2_t -> InOut a -> IO HErr_t)
- mk'H5L_iterate2_t :: (HId_t -> CString -> In H5L_info2_t -> InOut a -> IO HErr_t) -> IO (FunPtr (HId_t -> CString -> In H5L_info2_t -> InOut a -> IO HErr_t))
- type H5L_iterate_t a = FunPtr (HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t)
- mk'H5L_iterate_t :: (HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t) -> IO (FunPtr (HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t))
- h5l_iterate1 :: HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t
- h5l_iterate2 :: HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t
- p_H5Literate1 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t)
- h5l_iterate :: HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate_t a -> InOut a -> IO HErr_t
- p_H5Literate2 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t)
- h5l_iterate_by_name1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t
- h5l_iterate_by_name2 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t
- p_H5Literate_by_name1 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t)
- h5l_iterate_by_name :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate_t a -> InOut a -> HId_t -> IO HErr_t
- p_H5Literate_by_name2 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t)
- h5l_visit1 :: HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t
- h5l_visit2 :: HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t
- p_H5Lvisit1 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t)
- h5l_visit :: HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate_t a -> InOut a -> IO HErr_t
- p_H5Lvisit2 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t)
- h5l_visit_by_name1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t
- h5l_visit_by_name2 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t
- p_H5Lvisit_by_name1 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t)
- h5l_visit_by_name :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate_t a -> InOut a -> HId_t -> IO HErr_t
- p_H5Lvisit_by_name2 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t)
Documentation
h5l_MAX_LINK_NAME_LEN :: Word32 Source #
Maximum length of a link's name (encoded in a 32-bit unsigned integer)
h5l_SAME_LOC :: HId_t Source #
Macro to indicate operation occurs on same location
h5l_LINK_CLASS_T_VERS :: Num a => a Source #
Current version of the H5L_class_t struct
newtype H5L_type_t Source #
Link class types.
Values less than 64 are reserved for the HDF5 library's internal use. Values 64 to 255 are for "user-defined" link class types; these types are defined by HDF5 but their behavior can be overridden by users. Users who want to create new classes of links should contact the HDF5 development team at mailto:hdfhelp@ncsa.uiuc.edu.
These values can never change because they appear in HDF5 files.
Constructors
H5L_type_t Int32 |
Instances
h5l_TYPE_ERROR :: H5L_type_t Source #
Invalid link type id
h5l_TYPE_HARD :: H5L_type_t Source #
Hard link id
h5l_TYPE_SOFT :: H5L_type_t Source #
Soft link id
h5l_TYPE_EXTERNAL :: H5L_type_t Source #
External link id
h5l_TYPE_MAX :: H5L_type_t Source #
Maximum link type id
h5l_TYPE_BUILTIN_MAX :: H5L_type_t Source #
Maximum value link value for "built-in" link types
h5l_TYPE_UD_MIN :: H5L_type_t Source #
Link ids at or above this value are "user-defined" link types.
Callback prototypes for user-defined links
type H5L_create_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> HId_t -> IO HErr_t) Source #
Link creation callback
typedef herr_t (*H5L_create_func_t)(const char *link_name, hid_t loc_group, const void *lnkdata, size_t lnkdata_size, hid_t lcpl_id);
type H5L_move_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> IO HErr_t) Source #
Callback for when the link is moved
typedef herr_t (*H5L_move_func_t)(const char *new_name, hid_t new_loc, const void *lnkdata, size_t lnkdata_size);
type H5L_copy_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> IO HErr_t) Source #
Callback for when the link is copied
typedef herr_t (*H5L_copy_func_t)(const char *new_name, hid_t new_loc, const void *lnkdata, size_t lnkdata_size);
type H5L_traverse_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> HId_t -> IO HErr_t) Source #
Callback during link traversal
typedef herr_t (*H5L_traverse_func_t)(const char *link_name, hid_t cur_group, const void *lnkdata, size_t lnkdata_size, hid_t lapl_id);
type H5L_delete_func_t a = FunPtr (CString -> HId_t -> Ptr a -> CSize -> IO HErr_t) Source #
Callback for when the link is deleted
typedef herr_t (*H5L_delete_func_t)(const char *link_name, hid_t file, const void *lnkdata, size_t lnkdata_size);
type H5L_query_func_t a b = FunPtr (CString -> Ptr a -> CSize -> Out b -> CSize -> IO CSSize) Source #
Callback for querying the link
Returns the size of the buffer needed
typedef ssize_t (*H5L_query_func_t)(const char *link_name, const void *lnkdata, size_t lnkdata_size, void *buf /*out*/, size_t buf_size);
data H5L_class_t Source #
User-defined link types
Version number of this struct
Link type ID
Comment for debugging
Callback during link creation
Callback after moving link
Callback after copying link
Callback during link traversal
Callback for link deletion
Callback for queries
Constructors
H5L_class_t | |
Fields
|
Instances
Storable H5L_class_t Source # | Creates an identical copy of a link with the same creation time and target. The new link can have a different name and be in a different location than the original. Returns non-negative on success, negative on failure. herr_t H5Lcopy(hid_t src_loc, const char *src_name, hid_t dst_loc, const char *dst_name, hid_t lcpl_id, hid_t lapl_id); |
Defined in Bindings.HDF5.Raw.H5L Methods sizeOf :: H5L_class_t -> Int alignment :: H5L_class_t -> Int peekElemOff :: Ptr H5L_class_t -> Int -> IO H5L_class_t pokeElemOff :: Ptr H5L_class_t -> Int -> H5L_class_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5L_class_t pokeByteOff :: Ptr b -> Int -> H5L_class_t -> IO () peek :: Ptr H5L_class_t -> IO H5L_class_t poke :: Ptr H5L_class_t -> H5L_class_t -> IO () | |
Show H5L_class_t Source # | |
Defined in Bindings.HDF5.Raw.H5L Methods showsPrec :: Int -> H5L_class_t -> ShowS show :: H5L_class_t -> String showList :: [H5L_class_t] -> ShowS | |
Eq H5L_class_t Source # | |
Defined in Bindings.HDF5.Raw.H5L |
type H5L_elink_traverse_t a = FunPtr (CString -> CString -> CString -> CString -> Ptr CUInt -> HId_t -> Ptr a -> IO HErr_t) Source #
Callback for external link traversal
typedef herr_t (*H5L_elink_traverse_t)(const char *parent_file_name, const char *parent_group_name, const char *child_file_name, const char *child_object_name, unsigned *acc_flags, hid_t fapl_id, void *op_data);
p'H5L_class_t'version :: Ptr H5L_class_t -> Ptr CInt Source #
p'H5L_class_t'id :: Ptr H5L_class_t -> Ptr H5L_type_t Source #
p'H5L_class_t'comment :: Ptr H5L_class_t -> Ptr CString Source #
Renames an object within an HDF5 file and moves it to a new
group. The original name src
is unlinked from the group graph
and then inserted with the new name dst
(which can specify a
new path for the object) as an atomic operation. The names
are interpreted relative to src_loc_id
and
dst_loc_id
, which are either file IDs or group ID.
Returns non-negative on success, negative on failure.
herr_t H5Lmove(hid_t src_loc, const char *src_name, hid_t dst_loc, const char *dst_name, hid_t lcpl_id, hid_t lapl_id);
p'H5L_class_t'create_func :: Ptr H5L_class_t -> Ptr (H5L_create_func_t ()) Source #
p'H5L_class_t'move_func :: Ptr H5L_class_t -> Ptr (H5L_move_func_t ()) Source #
p'H5L_class_t'copy_func :: Ptr H5L_class_t -> Ptr (H5L_copy_func_t ()) Source #
p'H5L_class_t'trav_func :: Ptr H5L_class_t -> Ptr (H5L_traverse_func_t ()) Source #
p'H5L_class_t'del_func :: Ptr H5L_class_t -> Ptr (H5L_delete_func_t ()) Source #
p'H5L_class_t'query_func :: Ptr H5L_class_t -> Ptr (H5L_query_func_t () ()) Source #
h5l_create_hard :: HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t Source #
Creates a hard link from new_name
to cur_name
.
cur_name
must name an existing object. cur_name
and
new_name
are interpreted relative to cur_loc_id
and
new_loc_id
, which are either file IDs or group IDs.
Returns non-negative on success, negative on failure
herr_t H5Lcreate_hard(hid_t cur_loc, const char *cur_name, hid_t dst_loc, const char *dst_name, hid_t lcpl_id, hid_t lapl_id);
p_H5Lcreate_hard :: FunPtr (HId_t -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t) Source #
h5l_create_soft :: CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t Source #
Creates a soft link from link_name
to link_target
.
link_target
can be anything and is interpreted at lookup
time relative to the group which contains the final component
of link_name
. For instance, if link_target
is "./foo" and
link_name
is ".xybar" and a request is made for ".xybar"
then the actual object looked up is ".xy.foo".
Returns non-negative on success, negative on failure.
herr_t H5Lcreate_soft(const char *link_target, hid_t link_loc_id, const char *link_name, hid_t lcpl_id, hid_t lapl_id);
h5l_delete :: HId_t -> CString -> HId_t -> IO HErr_t Source #
Removes the specified name
from the group graph and
decrements the link count for the object to which name
points. If the link count reaches zero then all file-space
associated with the object will be reclaimed (but if the
object is open, then the reclamation of the file space is
delayed until all handles to the object are closed).
Returns non-negative on success, negative on failure.
herr_t H5Ldelete(hid_t loc_id, const char *name, hid_t lapl_id);
h5l_delete_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> HId_t -> IO HErr_t Source #
Removes the specified link from the group graph and decrements the link count for the object to which it points, according to the order within an index.
If the link count reaches zero then all file-space associated with the object will be reclaimed (but if the object is open, then the reclamation of the file space is delayed until all handles to the object are closed).
Returns non-negative on success, negative on failure.
herr_t H5Ldelete_by_idx(hid_t loc_id, const char *group_name, H5_index_t idx_type, H5_iter_order_t order, hsize_t n, hid_t lapl_id);
p_H5Ldelete_by_idx :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> HId_t -> IO HErr_t) Source #
h5l_get_val :: HId_t -> CString -> OutArray a -> CSize -> HId_t -> IO HErr_t Source #
Returns the link value of a link whose name is name
. For
symbolic links, this is the path to which the link points,
including the null terminator. For user-defined links, it
is the link buffer.
At most size
bytes are copied to the buf
result buffer.
Returns non-negative on success, negative on failure.
herr_t H5Lget_val(hid_t loc_id, const char *name, void *buf/*out*/, size_t size, hid_t lapl_id);
h5l_get_val_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray a -> CSize -> HId_t -> IO HErr_t Source #
Returns the link value of a link, according to the order of an index. For symbolic links, this is the path to which the link points, including the null terminator. For user-defined links, it is the link buffer.
At most size
bytes are copied to the buf
result buffer.
Returns non-negative on success, negative on failure.
herr_t H5Lget_val_by_idx(hid_t loc_id, const char *group_name, H5_index_t idx_type, H5_iter_order_t order, hsize_t n, void *buf/*out*/, size_t size, hid_t lapl_id);
p_H5Lget_val_by_idx :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray a -> CSize -> HId_t -> IO HErr_t) Source #
h5l_exists :: HId_t -> CString -> HId_t -> IO HTri_t Source #
Checks if a link of a given name exists in a group
htri_t H5Lexists(hid_t loc_id, const char *name, hid_t lapl_id);
h5l_get_name_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray CChar -> CSSize -> HId_t -> IO CSSize Source #
Gets name for a link, according to the order within an index.
Same pattern of behavior as h5i_get_name
.
On success, returns non-negative length of name, with information
in name
buffer
On failure,returns a negative value.
ssize_t H5Lget_name_by_idx(hid_t loc_id, const char *group_name, H5_index_t idx_type, H5_iter_order_t order, hsize_t n, char *name /*out*/, size_t size, hid_t lapl_id);
p_H5Lget_name_by_idx :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> OutArray CChar -> CSSize -> HId_t -> IO CSSize) Source #
h5l_create_ud :: HId_t -> CString -> H5L_type_t -> In a -> CSize -> HId_t -> HId_t -> IO HErr_t Source #
Creates a user-defined link of type link_type
named link_name
with user-specified data udata
.
The format of the information pointed to by udata
is
defined by the user. udata_size
holds the size of this buffer.
link_name
is interpreted relative to link_loc_id
.
The property list specified by lcpl_id
holds properties used
to create the link.
The link class of the new link must already be registered with the library.
Returns non-negative on success, negative on failure.
herr_t H5Lcreate_ud(hid_t link_loc_id, const char *link_name, H5L_type_t link_type, const void *udata, size_t udata_size, hid_t lcpl_id, hid_t lapl_id);
p_H5Lcreate_ud :: FunPtr (HId_t -> CString -> H5L_type_t -> In a -> CSize -> HId_t -> HId_t -> IO HErr_t) Source #
h5l_register :: In H5L_class_t -> IO HErr_t Source #
Registers a class of user-defined links, or changes the behavior of an existing class.
The link class passed in will override any existing link
class for the specified link class ID. It must at least
include a H5L_class_t
version (which should be
h5l_LINK_CLASS_T_VERS
), a link class ID, and a traversal
function.
Returns non-negative on success, negative on failure.
herr_t H5Lregister(const H5L_class_t *cls);
p_H5Lregister :: FunPtr (In H5L_class_t -> IO HErr_t) Source #
h5l_unregister :: H5L_type_t -> IO HErr_t Source #
Unregisters a class of user-defined links, preventing them from being traversed, queried, moved, etc.
A link class can be re-registered using h5l_register
.
Returns non-negative on success, negative on failure.
herr_t H5Lunregister(H5L_type_t id);
p_H5Lunregister :: FunPtr (H5L_type_t -> IO HErr_t) Source #
h5l_is_registered :: H5L_type_t -> IO HTri_t Source #
Tests whether a user-defined link class has been registered or not.
htri_t H5Lis_registered(H5L_type_t id);
p_H5Lis_registered :: FunPtr (H5L_type_t -> IO HTri_t) Source #
h5l_unpack_elink_val :: InArray a -> CSize -> Out CUInt -> Out (Ptr CChar) -> Out (Ptr CChar) -> IO HErr_t Source #
Given a buffer holding the "link value" from an external link, gets pointers to the information within the link value buffer.
External link link values contain some flags and two NULL-terminated strings, one after the other.
The flags
value will be filled in and filename
and
obj_path
will be set to pointers within ext_linkval
(unless
any of these values is NULL).
Using this function on strings that aren't external link
udata
buffers can result in segmentation faults.
Returns non-negative on success, negative on failure.
herr_t H5Lunpack_elink_val(const void *ext_linkval/*in*/, size_t link_size, unsigned *flags, const char **filename/*out*/, const char **obj_path /*out*/);
p_H5Lunpack_elink_val :: FunPtr (InArray a -> CSize -> Out CUInt -> Out (Ptr CChar) -> Out (Ptr CChar) -> IO HErr_t) Source #
h5l_create_external :: CString -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t Source #
Creates an external link from link_name
to obj_name
.
External links are links to objects in other HDF5 files. They
are allowed to "dangle" like soft links internal to a file.
file_name
is the name of the file that obj_name
is is contained
within. If obj_name
is given as a relative path name, the
path will be relative to the root group of file_name
.
link_name
is interpreted relative to link_loc_id
, which is
either a file ID or a group ID.
Returns non-negative on success, negative on failure.
herr_t H5Lcreate_external(const char *file_name, const char *obj_name, hid_t link_loc_id, const char *link_name, hid_t lcpl_id, hid_t lapl_id);
p_H5Lcreate_external :: FunPtr (CString -> CString -> HId_t -> CString -> HId_t -> HId_t -> IO HErr_t) Source #
data H5L_info1_t Source #
Constructors
H5L_info1_t | |
Fields
|
Instances
Storable H5L_info1_t Source # | |
Defined in Bindings.HDF5.Raw.H5L Methods sizeOf :: H5L_info1_t -> Int alignment :: H5L_info1_t -> Int peekElemOff :: Ptr H5L_info1_t -> Int -> IO H5L_info1_t pokeElemOff :: Ptr H5L_info1_t -> Int -> H5L_info1_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5L_info1_t pokeByteOff :: Ptr b -> Int -> H5L_info1_t -> IO () peek :: Ptr H5L_info1_t -> IO H5L_info1_t poke :: Ptr H5L_info1_t -> H5L_info1_t -> IO () | |
Show H5L_info1_t Source # | |
Defined in Bindings.HDF5.Raw.H5L Methods showsPrec :: Int -> H5L_info1_t -> ShowS show :: H5L_info1_t -> String showList :: [H5L_info1_t] -> ShowS | |
Eq H5L_info1_t Source # | |
Defined in Bindings.HDF5.Raw.H5L |
p'H5L_info1_t'type :: Ptr H5L_info1_t -> Ptr H5L_type_t Source #
data H5L_info2_t Source #
Constructors
H5L_info2_t | |
Fields
|
Instances
Storable H5L_info2_t Source # | |
Defined in Bindings.HDF5.Raw.H5L Methods sizeOf :: H5L_info2_t -> Int alignment :: H5L_info2_t -> Int peekElemOff :: Ptr H5L_info2_t -> Int -> IO H5L_info2_t pokeElemOff :: Ptr H5L_info2_t -> Int -> H5L_info2_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5L_info2_t pokeByteOff :: Ptr b -> Int -> H5L_info2_t -> IO () peek :: Ptr H5L_info2_t -> IO H5L_info2_t poke :: Ptr H5L_info2_t -> H5L_info2_t -> IO () | |
Show H5L_info2_t Source # | |
Defined in Bindings.HDF5.Raw.H5L Methods showsPrec :: Int -> H5L_info2_t -> ShowS show :: H5L_info2_t -> String showList :: [H5L_info2_t] -> ShowS | |
Eq H5L_info2_t Source # | |
Defined in Bindings.HDF5.Raw.H5L |
p'H5L_info1_t'corder_valid :: Ptr H5L_info1_t -> Ptr HBool_t Source #
type H5L_info_t = H5L_info1_t Source #
p'H5L_info1_t'corder :: Ptr H5L_info1_t -> Ptr Int64 Source #
p'H5L_info1_t'cset :: Ptr H5L_info1_t -> Ptr H5T_cset_t Source #
p'H5L_info1_t'u'address :: Ptr H5L_info1_t -> Ptr HAddr_t Source #
p'H5L_info2_t'type :: Ptr H5L_info2_t -> Ptr H5L_type_t Source #
p'H5L_info1_t'u'val_size :: Ptr H5L_info1_t -> Ptr CSize Source #
p'H5L_info2_t'corder_valid :: Ptr H5L_info2_t -> Ptr HBool_t Source #
u_H5L_info1_t'u'address :: H5L_info1_t -> HAddr_t -> IO H5L_info1_t Source #
p'H5L_info2_t'corder :: Ptr H5L_info2_t -> Ptr Int64 Source #
p'H5L_info2_t'cset :: Ptr H5L_info2_t -> Ptr H5T_cset_t Source #
p'H5L_info2_t'u'token :: Ptr H5L_info2_t -> Ptr H5O_token_t Source #
p'H5L_info2_t'u'val_size :: Ptr H5L_info2_t -> Ptr CSize Source #
u_H5L_info1_t'u'val_size :: H5L_info1_t -> CSize -> IO H5L_info1_t Source #
u_H5L_info2_t'u'token :: H5L_info2_t -> H5O_token_t -> IO H5L_info2_t Source #
u_H5L_info2_t'u'val_size :: H5L_info2_t -> CSize -> IO H5L_info2_t Source #
h5l_get_info1 :: HId_t -> CString -> Out H5L_info1_t -> HId_t -> IO HErr_t Source #
h5l_get_info2 :: HId_t -> CString -> Out H5L_info2_t -> HId_t -> IO HErr_t Source #
p_H5Lget_info1 :: FunPtr (HId_t -> CString -> Out H5L_info1_t -> HId_t -> IO HErr_t) Source #
h5l_get_info :: HId_t -> CString -> Out H5L_info_t -> HId_t -> IO HErr_t Source #
p_H5Lget_info2 :: FunPtr (HId_t -> CString -> Out H5L_info2_t -> HId_t -> IO HErr_t) Source #
h5l_get_info_by_idx1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info1_t -> HId_t -> IO HErr_t Source #
h5l_get_info_by_idx2 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info2_t -> HId_t -> IO HErr_t Source #
p_H5Lget_info_by_idx1 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info1_t -> HId_t -> IO HErr_t) Source #
h5l_get_info_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info_t -> HId_t -> IO HErr_t Source #
p_H5Lget_info_by_idx2 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5L_info2_t -> HId_t -> IO HErr_t) Source #
type H5L_iterate1_t a = FunPtr (HId_t -> CString -> In H5L_info1_t -> InOut a -> IO HErr_t) Source #
mk'H5L_iterate1_t :: (HId_t -> CString -> In H5L_info1_t -> InOut a -> IO HErr_t) -> IO (FunPtr (HId_t -> CString -> In H5L_info1_t -> InOut a -> IO HErr_t)) Source #
type H5L_iterate2_t a = FunPtr (HId_t -> CString -> In H5L_info2_t -> InOut a -> IO HErr_t) Source #
mk'H5L_iterate2_t :: (HId_t -> CString -> In H5L_info2_t -> InOut a -> IO HErr_t) -> IO (FunPtr (HId_t -> CString -> In H5L_info2_t -> InOut a -> IO HErr_t)) Source #
type H5L_iterate_t a = FunPtr (HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t) Source #
mk'H5L_iterate_t :: (HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t) -> IO (FunPtr (HId_t -> CString -> In H5L_info_t -> InOut a -> IO HErr_t)) Source #
h5l_iterate1 :: HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t Source #
h5l_iterate2 :: HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t Source #
p_H5Literate1 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t) Source #
h5l_iterate :: HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate_t a -> InOut a -> IO HErr_t Source #
p_H5Literate2 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t) Source #
h5l_iterate_by_name1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t Source #
h5l_iterate_by_name2 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t Source #
p_H5Literate_by_name1 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t) Source #
h5l_iterate_by_name :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate_t a -> InOut a -> HId_t -> IO HErr_t Source #
p_H5Literate_by_name2 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> InOut HSize_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t) Source #
h5l_visit1 :: HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t Source #
h5l_visit2 :: HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t Source #
p_H5Lvisit1 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> IO HErr_t) Source #
h5l_visit :: HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate_t a -> InOut a -> IO HErr_t Source #
p_H5Lvisit2 :: FunPtr (HId_t -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> IO HErr_t) Source #
h5l_visit_by_name1 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t Source #
h5l_visit_by_name2 :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t Source #
p_H5Lvisit_by_name1 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate1_t a -> InOut a -> HId_t -> IO HErr_t) Source #
h5l_visit_by_name :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate_t a -> InOut a -> HId_t -> IO HErr_t Source #
p_H5Lvisit_by_name2 :: FunPtr (HId_t -> CString -> H5_index_t -> H5_iter_order_t -> H5L_iterate2_t a -> InOut a -> HId_t -> IO HErr_t) Source #