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

Bindings.HDF5.Raw.H5D

Synopsis

Documentation

h5d_XFER_DIRECT_CHUNK_WRITE_FLAG_NAME :: String Source #

Property names for H5LTDdirect_chunk_write

newtype H5D_layout_t Source #

Values for the H5D_LAYOUT property

Constructors

H5D_layout_t Int32 

Instances

Instances details
Storable H5D_layout_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

sizeOf :: H5D_layout_t -> Int

alignment :: H5D_layout_t -> Int

peekElemOff :: Ptr H5D_layout_t -> Int -> IO H5D_layout_t

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

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

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

peek :: Ptr H5D_layout_t -> IO H5D_layout_t

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

Show H5D_layout_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_layout_t -> ShowS

show :: H5D_layout_t -> String

showList :: [H5D_layout_t] -> ShowS

Eq H5D_layout_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

(==) :: H5D_layout_t -> H5D_layout_t -> Bool

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

h5d_COMPACT :: H5D_layout_t Source #

raw data is very small

h5d_CHUNKED :: H5D_layout_t Source #

slow and fancy

h5d_NLAYOUTS :: Num a => a Source #

newtype H5D_chunk_index_t Source #

Types of chunk index data structures

Constructors

H5D_chunk_index_t Word32 

Instances

Instances details
Storable H5D_chunk_index_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Show H5D_chunk_index_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_chunk_index_t -> ShowS

show :: H5D_chunk_index_t -> String

showList :: [H5D_chunk_index_t] -> ShowS

newtype H5D_alloc_time_t Source #

Values for the space allocation time property

Constructors

H5D_alloc_time_t Int32 

Instances

Instances details
Storable H5D_alloc_time_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Show H5D_alloc_time_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_alloc_time_t -> ShowS

show :: H5D_alloc_time_t -> String

showList :: [H5D_alloc_time_t] -> ShowS

Eq H5D_alloc_time_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

newtype H5D_space_status_t Source #

Values for the status of space allocation

Constructors

H5D_space_status_t Int32 

Instances

Instances details
Storable H5D_space_status_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Show H5D_space_status_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_space_status_t -> ShowS

show :: H5D_space_status_t -> String

showList :: [H5D_space_status_t] -> ShowS

Eq H5D_space_status_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

newtype H5D_fill_time_t Source #

Values for time of writing fill value property

Constructors

H5D_fill_time_t Int32 

Instances

Instances details
Storable H5D_fill_time_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

sizeOf :: H5D_fill_time_t -> Int

alignment :: H5D_fill_time_t -> Int

peekElemOff :: Ptr H5D_fill_time_t -> Int -> IO H5D_fill_time_t

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

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

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

peek :: Ptr H5D_fill_time_t -> IO H5D_fill_time_t

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

Show H5D_fill_time_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_fill_time_t -> ShowS

show :: H5D_fill_time_t -> String

showList :: [H5D_fill_time_t] -> ShowS

Eq H5D_fill_time_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

newtype H5D_fill_value_t Source #

Values for fill value status

Constructors

H5D_fill_value_t Int32 

Instances

Instances details
Storable H5D_fill_value_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Show H5D_fill_value_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_fill_value_t -> ShowS

show :: H5D_fill_value_t -> String

showList :: [H5D_fill_value_t] -> ShowS

Eq H5D_fill_value_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

type H5D_operator_t a b = FunPtr (InOut a -> HId_t -> CUInt -> InArray HSize_t -> InOut b -> IO HErr_t) Source #

Operator function type for h5d_iterate

Parameters:

elem :: InOut a
Pointer to the element in memory containing the current point.
type_id :: HId_t
Datatype ID for the elements stored in ELEM.
ndim :: CUInt
Number of dimensions for POINT array
point :: InArray HSize_t
Array containing the location of the element within the original dataspace.
operator_data :: InOut b
Pointer to any user-defined data associated with the operation.

Return Values:

  • Zero causes the iterator to continue, returning zero when all elements have been processed.
  • Positive causes the iterator to immediately return that positive value, indicating short-circuit success. The iterator can be restarted at the next element.
  • Negative causes the iterator to immediately return that value, indicating failure. The iterator can be restarted at the next element.
typedef herr_t (*H5D_operator_t)(void *elem, hid_t type_id, unsigned ndim,
				 const hsize_t *point, void *operator_data);

type H5D_scatter_func_t a b = FunPtr (Out (Ptr a) -> Out CSize -> InOut b -> IO HErr_t) Source #

type H5D_gather_func_t a b = FunPtr (InArray a -> CSize -> InOut b -> IO HErr_t) Source #

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

Creates a new dataset named name at loc_id, opens the dataset for access, and associates with that dataset constant and initial persistent properties including the type of each datapoint as stored in the file (type_id), the size of the dataset (space_id), and other initial miscellaneous properties (dcpl_id).

All arguments are copied into the dataset, so the caller is allowed to derive new types, data spaces, and creation parameters from the old ones and reuse them in calls to create other datasets.

On success, returns the object ID of the new dataset. At this point, the dataset is ready to receive its raw data. Attempting to read raw data from the dataset will probably return the fill value. The dataset should be closed when the caller is no longer interested in it.

On failure, returns a negative value.

hid_t H5Dcreate2(hid_t loc_id, const char *name, hid_t type_id,
    hid_t space_id, hid_t lcpl_id, hid_t dcpl_id, hid_t dapl_id);

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

h5d_create_anon :: HId_t -> HId_t -> HId_t -> HId_t -> HId_t -> IO HId_t Source #

Creates a new dataset named name at loc_id, opens the dataset for access, and associates with that dataset constant and initial persistent properties including the type of each datapoint as stored in the file (type_id), the size of the dataset (space_id), and other initial miscellaneous properties (dcpl_id).

All arguments are copied into the dataset, so the caller is allowed to derive new types, data spaces, and creation parameters from the old ones and reuse them in calls to create other datasets.

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

On success returns the object ID of the new dataset. At this point, the dataset is ready to receive its raw data. Attempting to read raw data from the dataset will probably return the fill value. The dataset should be linked into the group hierarchy before being closed or it will be deleted. The dataset should be closed when the caller is no longer interested in it.

On failure, returns a negative value.

hid_t H5Dcreate_anon(hid_t file_id, hid_t type_id, hid_t space_id,
    hid_t plist_id, hid_t dapl_id);

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

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

Finds a dataset named name at loc_id, opens it, and returns its ID. The dataset should be close when the caller is no longer interested in it.

Takes a dataset access property list

On success, returns a new dataset ID. On failure, returns a negative value.

hid_t H5Dopen2(hid_t file_id, const char *name, hid_t dapl_id);

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

h5d_close :: HId_t -> IO HErr_t Source #

Closes access to a dataset (dset_id) and releases resources used by it. It is illegal to subsequently use that same dataset ID in calls to other dataset functions.

Returns non-negative on success / negative on failure

herr_t H5Dclose(hid_t dset_id);

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

h5d_get_space :: HId_t -> IO HId_t Source #

Returns a copy of the file data space for a dataset.

On success, returns a new ID for a copy of the data space. The data space should be released by calling h5s_close.

hid_t H5Dget_space(hid_t dset_id);

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

h5d_get_space_status :: HId_t -> Out H5D_space_status_t -> IO HErr_t Source #

Gets the status of data space allocation.

Returns non-negative on success / negative on failure

herr_t H5Dget_space_status(hid_t dset_id, H5D_space_status_t *allocation);

h5d_get_type :: HId_t -> IO HId_t Source #

Gets a copy of the file datatype for a dataset.

On success, returns the ID for a copy of the datatype. The data type should be released by calling h5t_close. On failure, returns a negative value.

hid_t H5Dget_type(hid_t dset_id);

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

h5d_get_create_plist :: HId_t -> IO HId_t Source #

Gets a copy of the dataset creation property list.

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

hid_t H5Dget_create_plist(hid_t dset_id);

h5d_get_access_plist :: HId_t -> IO HId_t Source #

Returns a copy of the dataset creation property list of the specified dataset.

The chunk cache parameters in the returned property lists will be those used by the dataset. If the properties in the file access property list were used to determine the dataset's chunk cache configuration, then those properties will be present in the returned dataset access property list. If the dataset does not use a chunked layout, then the chunk cache properties will be set to the default. The chunk cache properties in the returned list are considered to be "set", and any use of this list will override the corresponding properties in the file's file access property list.

All link access properties in the returned list will be set to the default values.

On success, returns the ID for a copy of the dataset access property list. The template should be released by calling h5p_close. On failure, returns a negative value.

hid_t H5Dget_access_plist(hid_t dset_id);

h5d_get_storage_size :: HId_t -> IO HSize_t Source #

Returns the amount of storage that is required for the dataset. For chunked datasets this is the number of allocated chunks times the chunk size.

On success, returns the amount of storage space allocated for the dataset, not counting meta data. The return value may be zero if no data has been stored.

On failure, returns zero.

hsize_t H5Dget_storage_size(hid_t dset_id);

h5d_get_offset :: HId_t -> IO HAddr_t Source #

Returns the address of dataset in file, or hADDR_UNDEF on failure.

haddr_t H5Dget_offset(hid_t dset_id);

h5d_read :: HId_t -> HId_t -> HId_t -> HId_t -> HId_t -> OutArray a -> IO HErr_t Source #

Reads (part of) a data set from the file into application memory buf. The part of the dataset to read is defined with mem_space_id and file_space_id. The data points are converted from their file type to the mem_type_id specified. Additional miscellaneous data transfer properties can be passed to this function with the plist_id argument.

The file_space_id can be the constant h5s_ALL which indicates that the entire file data space is to be referenced.

The mem_space_id can be the constant h5s_ALL in which case the memory data space is the same as the file data space defined when the dataset was created.

The number of elements in the memory data space must match the number of elements in the file data space.

The plist_id can be the constant h5p_DEFAULT in which case the default data transfer properties are used.

Returns non-negative on success / negative on failure.

herr_t H5Dread(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id,
       hid_t file_space_id, hid_t plist_id, void *buf/*out*/);

p_H5Dread :: FunPtr (HId_t -> HId_t -> HId_t -> HId_t -> HId_t -> OutArray a -> IO HErr_t) Source #

h5d_write :: HId_t -> HId_t -> HId_t -> HId_t -> HId_t -> InArray a -> IO HErr_t Source #

Writes (part of) a data set from application memory buf to the file. The part of the dataset to write is defined with the mem_space_id and file_space_id arguments. The data points are converted from their current type (mem_type_id) to their file datatype. Additional miscellaneous data transfer properties can be passed to this function with the plist_id argument.

The file_space_id can be the constant h5s_ALL which indicates that the entire file data space is to be referenced.

The mem_space_id can be the constant h5s_ALL in which case the memory data space is the same as the file data space defined when the dataset was created.

The number of elements in the memory data space must match the number of elements in the file data space.

The plist_id can be the constant h5p_DEFAULT in which case the default data transfer properties are used.

Returns non-negative on success / negative on failure.

herr_t H5Dwrite(hid_t dset_id, hid_t mem_type_id, hid_t mem_space_id,
       hid_t file_space_id, hid_t plist_id, const void *buf);

p_H5Dwrite :: FunPtr (HId_t -> HId_t -> HId_t -> HId_t -> HId_t -> InArray a -> IO HErr_t) Source #

h5d_iterate :: InOutArray a -> HId_t -> HId_t -> H5D_operator_t a b -> InOut b -> IO HErr_t Source #

This routine iterates over all the elements selected in a memory buffer. The callback function is called once for each element selected in the dataspace. The selection in the dataspace is modified so that any elements already iterated over are removed from the selection if the iteration is interrupted (by the H5D_operator_t function returning non-zero) in the "middle" of the iteration and may be re-started by the user where it left off.

NOTE: Until "subtracting" elements from a selection is implemented, the selection is not modified.

Parameters:

buf :: InOut a
Pointer to the buffer in memory containing the elements to iterate over.
type_id :: HId_t
Datatype ID for the elements stored in buf.
space_id :: HId_t
Dataspace ID for buf, also contains the selection to iterate over.
op :: H5D_operator_t a b
Function pointer to the routine to be called for each element in buf iterated over.
operator_data :: InOut b
Pointer to any user-defined data associated with the operation.

Returns the return value of the last operator if it was non-zero, or zero if all elements were processed. Otherwise returns a negative value.

herr_t H5Diterate(void *buf, hid_t type_id, hid_t space_id,
       H5D_operator_t op, void *operator_data);

p_H5Diterate :: FunPtr (InOutArray a -> HId_t -> HId_t -> H5D_operator_t a b -> InOut b -> IO HErr_t) Source #

h5d_vlen_reclaim :: HId_t -> HId_t -> HId_t -> Ptr a -> IO HErr_t Source #

Frees the buffers allocated for storing variable-length data in memory. Only frees the VL data in the selection defined in the dataspace. The dataset transfer property list is required to find the correct allocation/free methods for the VL data in the buffer.

Returns non-negative on success, negative on failure

herr_t H5Dvlen_reclaim(hid_t type_id, hid_t space_id, hid_t plist_id, void *buf);

p_H5Dvlen_reclaim :: FunPtr (HId_t -> HId_t -> HId_t -> Ptr a -> IO HErr_t) Source #

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

This routine checks the number of bytes required to store the VL data from the dataset, using the space_id for the selection in the dataset on disk and the type_id for the memory representation of the VL data, in memory. The size value is modified according to how many bytes are required to store the VL data in memory.

This routine actually performs the read with a custom memory manager which basically just counts the bytes requested and uses a temporary memory buffer (through the H5FL API) to make certain enough space is available to perform the read. Then the temporary buffer is released and the number of bytes allocated is returned. Kinda kludgy, but easier than the other method of trying to figure out the sizes without actually reading the data in... - QAK

Returns non-negative on success, negative on failure

herr_t H5Dvlen_get_buf_size(hid_t dataset_id, hid_t type_id, hid_t space_id, hsize_t *size);

h5d_fill :: In a -> HId_t -> InOutArray b -> HId_t -> HId_t -> IO HErr_t Source #

Fill a selection in memory with a value. Use the selection in the dataspace to fill elements in a memory buffer. If "fill" parameter is NULL, uses all zeros as fill value

Parameters:

fill :: In a
Pointer to fill value to use
fill_type_id :: HId_t
Datatype of the fill value
buf :: InOut b
Memory buffer to fill selection within
buf_type_id :: HId_t
Datatype of the elements in buffer
space_id :: HId_t
Dataspace describing memory buffer & containing selection to use.

Returns non-negative on success / negative on failure.

herr_t H5Dfill(const void *fill, hid_t fill_type, void *buf,
        hid_t buf_type, hid_t space);

p_H5Dfill :: FunPtr (In a -> HId_t -> InOutArray b -> HId_t -> HId_t -> IO HErr_t) Source #

h5d_set_extent :: HId_t -> InArray HSize_t -> IO HErr_t Source #

Modifies the dimensions of a dataset. Can change to a smaller dimension.

Returns non-negative on success, negative on failure

herr_t H5Dset_extent(hid_t dset_id, const hsize_t size[]);

h5d_scatter :: H5D_scatter_func_t a b -> InOut b -> HId_t -> HId_t -> OutArray a -> IO HErr_t Source #

Scatters data provided by the callback op to the destination buffer dst_buf, where the dimensions of dst_buf and the selection to be scattered to are specified by the dataspace dst_space_id. The type of the data to be scattered is specified by type_id.

Returns non-negative on success, negative on failure

herr_t H5Dscatter(H5D_scatter_func_t op, void *op_data, hid_t type_id,
    hid_t dst_space_id, void *dst_buf);

p_H5Dscatter :: FunPtr (H5D_scatter_func_t a b -> InOut b -> HId_t -> HId_t -> OutArray a -> IO HErr_t) Source #

h5d_gather :: HId_t -> InArray a -> HId_t -> CSize -> OutArray a -> H5D_gather_func_t a b -> InOut b -> IO HErr_t Source #

Gathers data provided from the source buffer src_buf to contiguous buffer dst_buf, then calls the callback op. The dimensions of src_buf and the selection to be gathered are specified by the dataspace src_space_id. The type of the data to be gathered is specified by type_id.

Returns non-negative on success, negative on failure

herr_t H5Dgather(hid_t src_space_id, const void *src_buf, hid_t type_id,
    size_t dst_buf_size, void *dst_buf, H5D_gather_func_t op, void *op_data);

p_H5Dgather :: FunPtr (HId_t -> InArray a -> HId_t -> CSize -> OutArray a -> H5D_gather_func_t a b -> InOut b -> IO HErr_t) Source #

h5d_debug :: HId_t -> IO HErr_t Source #

Prints various information about a dataset. This function is not to be documented in the API at this time.

Returns non-negative on success, negative on failure

herr_t H5Ddebug(hid_t dset_id);

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

Bit flags for the H5Pset_chunk_opts() and H5Pget_chunk_opts()

h5d_VIRTUAL :: H5D_layout_t Source #

actual data is stored in other datasets

h5d_CHUNK_IDX_BTREE :: H5D_chunk_index_t Source #

v1 B-tree index (default)

h5d_CHUNK_IDX_SINGLE :: H5D_chunk_index_t Source #

Single Chunk index (cur dims[]=max dims[]=chunk dims[]; filtered & non-filtered)

h5d_CHUNK_IDX_NONE :: H5D_chunk_index_t Source #

Fixed array (for 0 unlimited dims)

Implicit: No Index (H5D_ALLOC_TIME_EARLY, non-filtered, fixed dims)

h5d_CHUNK_IDX_FARRAY :: H5D_chunk_index_t Source #

Extensible array (for 1 unlimited dim)

h5d_CHUNK_IDX_EARRAY :: H5D_chunk_index_t Source #

v2 B-tree index (for >1 unlimited dims)

newtype H5D_vds_view_t Source #

Values for VDS bounds option

Constructors

H5D_vds_view_t Int32 

Instances

Instances details
Storable H5D_vds_view_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

sizeOf :: H5D_vds_view_t -> Int

alignment :: H5D_vds_view_t -> Int

peekElemOff :: Ptr H5D_vds_view_t -> Int -> IO H5D_vds_view_t

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

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

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

peek :: Ptr H5D_vds_view_t -> IO H5D_vds_view_t

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

Show H5D_vds_view_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

Methods

showsPrec :: Int -> H5D_vds_view_t -> ShowS

show :: H5D_vds_view_t -> String

showList :: [H5D_vds_view_t] -> ShowS

Eq H5D_vds_view_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5D

h5d_format_convert :: HId_t -> IO HErr_t Source #

Internal API routines > H5_DLL herr_t H5Dformat_convert(hid_t dset_id);

type H5D_append_cb_t a = FunPtr (HId_t -> Out HSize_t -> InOut a -> IO HErr_t) Source #

Callback for H5Pset_append_flush() in a dataset access property list > typedef herr_t (*H5D_append_cb_t)(hid_t dataset_id, hsize_t *cur_dims, void *op_data)

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

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

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

Creates a new dataset named name at loc_id, opens the dataset for access, and associates with that dataset constant and initial persistent properties including the type of each datapoint as stored in the file (type_id), the size of the dataset (space_id), and other initial miscellaneous properties (dcpl_id).

All arguments are copied into the dataset, so the caller is allowed to derive new types, data spaces, and creation parameters from the old ones and reuse them in calls to create other datasets.

On success, returns the object ID of the new dataset. At this point, the dataset is ready to receive its raw data. Attempting to read raw data from the dataset will probably return the fill value. The dataset should be closed when the caller is no longer interested in it.

On failure, returns a negative value.

Note: Deprecated in favor of h5d_create2

hid_t H5Dcreate1(hid_t file_id, const char *name, hid_t type_id,
    hid_t space_id, hid_t dcpl_id);

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

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

Finds a dataset named name at loc_id, opens it, and returns its ID. The dataset should be closed when the caller is no longer interested in it.

On success returns a new dataset ID. On failure, returns a negative value.

Note: Deprecated in favor of h5d_open2

hid_t H5Dopen1(hid_t file_id, const char *name);

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

h5d_extend :: HId_t -> InArray HSize_t -> IO HErr_t Source #

This function makes sure that the dataset is at least of size size. The dimensionality of size is the same as the data space of the dataset being changed.

Note: Deprecated in favor of h5d_set_extent

Returns non-negative on success / negative on failure

herr_t H5Dextend(hid_t dset_id, const hsize_t size[]);