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

Bindings.HDF5.Raw.H5G

Synopsis

Documentation

newtype H5G_storage_type_t Source #

Types of link storage for groups

Constructors

H5G_storage_type_t Int32 

Instances

Instances details
Storable H5G_storage_type_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Read H5G_storage_type_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Show H5G_storage_type_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

showsPrec :: Int -> H5G_storage_type_t -> ShowS

show :: H5G_storage_type_t -> String

showList :: [H5G_storage_type_t] -> ShowS

Eq H5G_storage_type_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Ord H5G_storage_type_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

h5g_STORAGE_TYPE_SYMBOL_TABLE :: H5G_storage_type_t Source #

Links in group are stored with a "symbol table" (this is sometimes called "old-style" groups)

h5g_STORAGE_TYPE_COMPACT :: H5G_storage_type_t Source #

Links are stored in object header

h5g_STORAGE_TYPE_DENSE :: H5G_storage_type_t Source #

Links are stored in fractal heap & indexed with v2 B-tree

data H5G_info_t Source #

Information struct for group (for h5g_get_info h5g_get_info_by_name h5g_get_info_by_idx)

Type of storage for links in group

Number of links in group

Current max. creation order value for group

Whether group has a file mounted on it

Instances

Instances details
Storable H5G_info_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

sizeOf :: H5G_info_t -> Int

alignment :: H5G_info_t -> Int

peekElemOff :: Ptr H5G_info_t -> Int -> IO H5G_info_t

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

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

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

peek :: Ptr H5G_info_t -> IO H5G_info_t

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

Show H5G_info_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

showsPrec :: Int -> H5G_info_t -> ShowS

show :: H5G_info_t -> String

showList :: [H5G_info_t] -> ShowS

Eq H5G_info_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

(==) :: H5G_info_t -> H5G_info_t -> Bool

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

p'H5G_info_t'storage_type :: Ptr H5G_info_t -> Ptr H5G_storage_type_t Source #

Creates a new group relative to loc_id, giving it the specified creation property list gcpl_id and access property list gapl_id. The link to the new group is created with the lcpl_id.

Parameters:

loc_id :: HId_t
File or group identifier
name :: CString
Absolute or relative name of the new group
lcpl_id :: HId_t
Property list for link creation
gcpl_id :: HId_t
Property list for group creation
gapl_id :: HId_t
Property list for group access

On success, returns the object ID of a new, empty group open for writing. Call h5g_close when finished with the group. Returns a negative value on failure.

hid_t H5Gcreate2(hid_t loc_id, const char *name, hid_t lcpl_id,
    hid_t gcpl_id, hid_t gapl_id);

h5g_create2 :: HId_t -> CString -> HId_t -> HId_t -> HId_t -> IO HId_t Source #

p_H5Gcreate2 :: FunPtr (HId_t -> CString -> HId_t -> HId_t -> HId_t -> IO HId_t) Source #

h5g_create_anon :: HId_t -> HId_t -> HId_t -> IO HId_t Source #

Creates a new group relative to loc_id, giving it the specified creation property list gcpl_id and access property list gapl_id.

The resulting ID should be linked into the file with h5o_link or it will be deleted when closed.

Given the default setting, h5g_create_anon followed by h5o_link will have the same function as h5g_create2.

Parameters:

loc_id :: HId_t
File or group identifier
name :: CString
Absolute or relative name of the new group
gcpl_id :: HId_t
Property list for group creation
gapl_id :: HId_t
Property list for group access

Example: To create missing groups "A" and "B01" along the given path "AB01/grp" (TODO: translate to Haskell):

hid_t create_id = H5Pcreate(H5P_GROUP_CREATE);
int   status = H5Pset_create_intermediate_group(create_id, TRUE);
hid_t gid = H5Gcreate_anon(file_id, "/A/B01/grp", create_id, H5P_DEFAULT);

On success, returns the object ID of a new, empty group open for writing. Call h5g_close when finished with the group. On failure, returns a negative value.

hid_t H5Gcreate_anon(hid_t loc_id, hid_t gcpl_id, hid_t gapl_id);

p_H5Gcreate_anon :: FunPtr (HId_t -> HId_t -> HId_t -> IO HId_t) Source #

h5g_open2 :: HId_t -> CString -> HId_t -> IO HId_t Source #

Opens an existing group for modification. When finished, call h5g_close to close it and release resources.

This function allows the user the pass in a Group Access Property List, which h5g_open1 does not.

On success, returns the object ID of the group. On failure, returns a negative value.

hid_t H5Gopen2(hid_t loc_id, const char *name, hid_t gapl_id);

p_H5Gopen2 :: FunPtr (HId_t -> CString -> HId_t -> IO HId_t) Source #

h5g_get_create_plist :: HId_t -> IO HId_t Source #

Returns a copy of the group creation property list.

On success, returns the ID for a copy of the group creation property list. The property list ID should be released by calling h5p_close.

hid_t H5Gget_create_plist(hid_t group_id);

h5g_get_info :: HId_t -> Out H5G_info_t -> IO HErr_t Source #

Retrieve information about a group.

Returns non-negative on success, negative on failure.

herr_t H5Gget_info(hid_t loc_id, H5G_info_t *ginfo);

h5g_get_info_by_name :: HId_t -> CString -> Out H5G_info_t -> HId_t -> IO HErr_t Source #

Retrieve information about a group.

Returns non-negative on success, negative on failure.

herr_t H5Gget_info_by_name(hid_t loc_id, const char *name, H5G_info_t *ginfo,
    hid_t lapl_id);

p_H5Gget_info_by_name :: FunPtr (HId_t -> CString -> Out H5G_info_t -> HId_t -> IO HErr_t) Source #

h5g_get_info_by_idx :: HId_t -> CString -> H5_index_t -> H5_iter_order_t -> HSize_t -> Out H5G_info_t -> HId_t -> IO HErr_t Source #

Retrieve information about a group, according to the order of an index.

Returns non-negative on success, negative on failure.

herr_t H5Gget_info_by_idx(hid_t loc_id, const char *group_name,
    H5_index_t idx_type, H5_iter_order_t order, hsize_t n, H5G_info_t *ginfo,
    hid_t lapl_id);

h5g_close :: HId_t -> IO HErr_t Source #

Closes the specified group. The group ID will no longer be valid for accessing the group.

Returns non-negative on success, negative on failure.

herr_t H5Gclose(hid_t group_id);

p_H5Gclose :: FunPtr (HId_t -> IO HErr_t) Source #

p_H5Gflush :: FunPtr (HId_t -> IO HErr_t) Source #

p_H5Grefresh :: FunPtr (HId_t -> IO HErr_t) Source #

h5g_SAME_LOC :: Num a => a Source #

h5g_NTYPES :: Num a => a Source #

h5g_NLIBTYPES :: Num a => a Source #

h5g_NUSERTYPES :: Num a => a Source #

newtype H5G_obj_t Source #

An object has a certain type. The first few numbers are reserved for use internally by HDF5. Users may add their own types with higher values. The values are never stored in the file - they only exist while an application is running. An object may satisfy the isa function for more than one type.

Constructors

H5G_obj_t Int32 

Instances

Instances details
Storable H5G_obj_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

sizeOf :: H5G_obj_t -> Int

alignment :: H5G_obj_t -> Int

peekElemOff :: Ptr H5G_obj_t -> Int -> IO H5G_obj_t

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

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

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

peek :: Ptr H5G_obj_t -> IO H5G_obj_t

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

Show H5G_obj_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

showsPrec :: Int -> H5G_obj_t -> ShowS

show :: H5G_obj_t -> String

showList :: [H5G_obj_t] -> ShowS

Eq H5G_obj_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

(==) :: H5G_obj_t -> H5G_obj_t -> Bool

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

h5g_UNKNOWN :: H5G_obj_t Source #

Unknown object type

h5g_GROUP :: H5G_obj_t Source #

Object is a group

h5g_DATASET :: H5G_obj_t Source #

Object is a dataset

h5g_TYPE :: H5G_obj_t Source #

Object is a named data type

h5g_LINK :: H5G_obj_t Source #

Object is a symbolic link

h5g_UDLINK :: H5G_obj_t Source #

Object is a user-defined link

h5g_RESERVED_5 :: H5G_obj_t Source #

Reserved for future use

h5g_RESERVED_6 :: H5G_obj_t Source #

Reserved for future use

h5g_RESERVED_7 :: H5G_obj_t Source #

Reserved for future use

type H5G_iterate_t a = FunPtr (HId_t -> CString -> InOut a -> IO HErr_t) Source #

Type of h5g_iterate operator

typedef herr_t (*H5G_iterate_t)(hid_t group, const char *name, void *op_data);

data H5G_stat_t Source #

Information about an object

file number

object number

number of hard links to object

basic object type

modification time

symbolic link value length

Object header information

Instances

Instances details
Storable H5G_stat_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

sizeOf :: H5G_stat_t -> Int

alignment :: H5G_stat_t -> Int

peekElemOff :: Ptr H5G_stat_t -> Int -> IO H5G_stat_t

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

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

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

peek :: Ptr H5G_stat_t -> IO H5G_stat_t

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

Show H5G_stat_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

showsPrec :: Int -> H5G_stat_t -> ShowS

show :: H5G_stat_t -> String

showList :: [H5G_stat_t] -> ShowS

Eq H5G_stat_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5G

Methods

(==) :: H5G_stat_t -> H5G_stat_t -> Bool

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

p'H5G_stat_t'fileno :: Ptr H5G_stat_t -> Ptr CULong Source #

Creates a new group relative to loc_id and gives it the specified name. The group is opened for write access and it's object ID is returned.

The optional size_hint specifies how much file space to reserve to store the names that will appear in this group. If a non-positive value is supplied for the size_hint then a default size is chosen.

Note: Deprecated in favor of h5g_create2

On success, returns the object ID of a new, empty group open for writing. Call h5g_close when finished with the group. On failure, returns a negative value.

hid_t H5Gcreate1(hid_t loc_id, const char *name, size_t size_hint);

p'H5G_stat_t'objno :: Ptr H5G_stat_t -> Ptr CULong Source #

h5g_create1 :: HId_t -> CString -> CSize -> IO HId_t Source #

p_H5Gcreate1 :: FunPtr (HId_t -> CString -> CSize -> IO HId_t) Source #

p'H5G_stat_t'ohdr :: Ptr H5G_stat_t -> Ptr H5O_stat_t Source #

Opens an existing group for modification. When finished, call h5g_close to close it and release resources.

Note: Deprecated in favor of h5g_open2

On success, returns the Object ID of the group. On failure, returns a negative value.

hid_t H5Gopen1(hid_t loc_id, const char *name);

h5g_open1 :: HId_t -> CString -> IO HId_t Source #

p_H5Gopen1 :: FunPtr (HId_t -> CString -> IO HId_t) Source #

h5g_link :: HId_t -> H5L_type_t -> CString -> CString -> IO HErr_t Source #

Creates a link between two existing objects. The new APIs to do this are h5l_create_hard and h5l_create_soft.

herr_t H5Glink(hid_t cur_loc_id, H5G_link_t type, const char *cur_name,
    const char *new_name);

p_H5Glink :: FunPtr (HId_t -> H5L_type_t -> CString -> CString -> IO HErr_t) Source #

h5g_link2 :: HId_t -> CString -> H5L_type_t -> HId_t -> CString -> IO HErr_t Source #

Creates a link between two existing objects. The new APIs to do this are h5l_create_hard and h5l_create_soft.

herr_t H5Glink2(hid_t cur_loc_id, const char *cur_name, H5G_link_t type, hid_t new_loc_id, const char *new_name);

p_H5Glink2 :: FunPtr (HId_t -> CString -> H5L_type_t -> HId_t -> CString -> IO HErr_t) Source #

h5g_move :: HId_t -> CString -> CString -> IO HErr_t Source #

Moves and renames a link. The new API to do this is h5l_move.

herr_t H5Gmove(hid_t src_loc_id, const char *src_name,
    const char *dst_name);

p_H5Gmove :: FunPtr (HId_t -> CString -> CString -> IO HErr_t) Source #

h5g_move2 :: HId_t -> CString -> HId_t -> CString -> IO HErr_t Source #

Moves and renames a link. The new API to do this is h5l_move.

herr_t H5Gmove2(hid_t src_loc_id, const char *src_name, hid_t dst_loc_id,
    const char *dst_name);

p_H5Gmove2 :: FunPtr (HId_t -> CString -> HId_t -> CString -> IO HErr_t) Source #

h5g_unlink :: HId_t -> CString -> IO HErr_t Source #

Removes a link. The new API is h5l_delete / h5l_delete_by_idx.

herr_t H5Gunlink(hid_t loc_id, const char *name);

p_H5Gunlink :: FunPtr (HId_t -> CString -> IO HErr_t) Source #

h5g_get_linkval :: HId_t -> CString -> CSize -> OutArray a -> IO HErr_t Source #

Retrieve's a soft link's data. The new API is h5l_get_val / h5l_get_val_by_idx.

herr_t H5Gget_linkval(hid_t loc_id, const char *name, size_t size,
    char *buf/*out*/);

p_H5Gget_linkval :: FunPtr (HId_t -> CString -> CSize -> OutArray a -> IO HErr_t) Source #

h5g_set_comment :: HId_t -> CString -> CString -> IO HErr_t Source #

Gives the specified object a comment. The comment string should be a null terminated string. An object can have only one comment at a time. Passing nullPtr for the comment argument will remove the comment property from the object.

Note: Deprecated in favor of h5o_set_comment / h5o_set_comment_by_name

Returns non-negative on success / negative on failure

herr_t H5Gset_comment(hid_t loc_id, const char *name, const char *comment);

p_H5Gset_comment :: FunPtr (HId_t -> CString -> CString -> IO HErr_t) Source #

h5g_get_comment :: HId_t -> CString -> CSize -> OutArray CChar -> IO CInt Source #

Return at most bufsize characters of the comment for the specified object. If bufsize is large enough to hold the entire comment then the comment string will be null terminated, otherwise it will not. If the object does not have a comment value then no bytes are copied to the BUF buffer.

Note: Deprecated in favor of h5o_get_comment / h5o_get_comment_by_name

On success, returns the number of characters in the comment counting the null terminator. The value returned may be larger than the bufsize argument.

int H5Gget_comment(hid_t loc_id, const char *name, size_t bufsize,
    char *buf);

p_H5Gget_comment :: FunPtr (HId_t -> CString -> CSize -> OutArray CChar -> IO CInt) Source #

h5g_iterate :: HId_t -> CString -> InOut CInt -> H5G_iterate_t a -> InOut a -> IO HErr_t Source #

Iterates over the entries of a group. The loc_id and name identify the group over which to iterate and idx indicates where to start iterating (zero means at the beginning). The operator is called for each member and the iteration continues until the operator returns non-zero or all members are processed. The operator is passed a group ID for the group being iterated, a member name, and op_data for each member.

Note: Deprecated in favor of h5l_iterate

Returns the return value of the first operator that returns non-zero, or zero if all members were processed with no operator returning non-zero.

Returns negative if something goes wrong within the library, or the negative value returned by one of the operators.

herr_t H5Giterate(hid_t loc_id, const char *name, int *idx,
        H5G_iterate_t op, void *op_data);

p_H5Giterate :: FunPtr (HId_t -> CString -> InOut CInt -> H5G_iterate_t a -> InOut a -> IO HErr_t) Source #

h5g_get_num_objs :: HId_t -> Out HSize_t -> IO HErr_t Source #

Returns the number of objects in the group. It iterates all B-tree leaves and sum up total number of group members.

Note: Deprecated in favor of h5g_get_info

Returns non-negative on success, negative on failure

herr_t H5Gget_num_objs(hid_t loc_id, hsize_t *num_objs);

h5g_get_objinfo :: HId_t -> CString -> HBool_t -> Out H5G_stat_t -> IO HErr_t Source #

Returns information about an object. If follow_link is non-zero then all symbolic links are followed; otherwise all links except the last component of the name are followed.

Note: Deprecated in favor of h5l_get_info / h5o_get_info

Returns non-negative on success, with the fields of statbuf (if non-null) initialized. Negative on failure.

herr_t H5Gget_objinfo(hid_t loc_id, const char *name,
    hbool_t follow_link, H5G_stat_t *statbuf/*out*/);

p_H5Gget_objinfo :: FunPtr (HId_t -> CString -> HBool_t -> Out H5G_stat_t -> IO HErr_t) Source #

h5g_get_objname_by_idx :: HId_t -> HSize_t -> OutArray CChar -> CSize -> IO CSSize Source #

Returns the name of objects in the group by giving index. 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.

Note: Deprecated in favor of h5l_get_name_by_idx

Returns non-negative on success, negative on failure.

ssize_t H5Gget_objname_by_idx(hid_t loc_id, hsize_t idx, char* name,
    size_t size);

p_H5Gget_objname_by_idx :: FunPtr (HId_t -> HSize_t -> OutArray CChar -> CSize -> IO CSSize) Source #

h5g_get_objtype_by_idx :: HId_t -> HSize_t -> IO H5G_obj_t Source #

Returns the type of objects in the group by giving index.

Note: Deprecated in favor of h5l_get_info / h5o_get_info

Returns h5g_GROUP, h5g_DATASET, or h5g_TYPE on success, or h5g_UNKNOWN on failure.

H5G_obj_t H5Gget_objtype_by_idx(hid_t loc_id, hsize_t idx);