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

Bindings.HDF5.Raw.H5FD

Description

The Virtual File Layer as described in documentation. This is the greatest common denominator for all types of storage access whether a file, memory, network, etc. This layer usually just dispatches the request to an actual file driver layer.

Synopsis

Documentation

h5fd_VFD_DEFAULT :: HId_t Source #

Default VFL driver value

type H5FD_mem_t = H5F_mem_t Source #

Types of allocation requests: see Bindings.HDF5.Raw.H5F

h5fd_MEM_FHEAP_HDR :: H5F_mem_t Source #

Map "fractal heap" header blocks to ohdr type file memory, since its a fair amount of work to add a new kind of file memory and they are similar enough to object headers and probably too minor to deserve their own type.

h5fd_MEM_FHEAP_IBLOCK :: H5F_mem_t Source #

Map "fractal heap" indirect blocks to ohdr type file memory, since they are similar to fractal heap header blocks.

h5fd_MEM_FHEAP_DBLOCK :: H5F_mem_t Source #

Map "fractal heap" direct blocks to lheap type file memory, since they will be replacing local heaps.

h5fd_MEM_FHEAP_HUGE_OBJ :: H5F_mem_t Source #

Map "fractal heap" huge objects to draw type file memory, since they represent large objects that are directly stored in the file.

h5fd_MEM_FSPACE_HDR :: H5F_mem_t Source #

Map "free space" header blocks to ohdr type file memory, since its a fair amount of work to add a new kind of file memory and they are similar enough to object headers and probably too minor to deserve their own type.

h5fd_MEM_FSPACE_SINFO :: H5F_mem_t Source #

Map "free space" serialized sections to lheap type file memory, since they are similar enough to local heap info.

h5fd_MEM_SOHM_TABLE :: H5F_mem_t Source #

Map "shared object header message" master table to ohdr type file memory, since its a fair amount of work to add a new kind of file memory and they are similar enough to object headers and probably too minor to deserve their own type.

h5fd_MEM_SOHM_INDEX :: H5F_mem_t Source #

Map "shared object header message" indices to btree type file memory, since they are similar enough to B-tree nodes.

h5fd_FLMAP_SINGLE :: OutArray H5FD_mem_t -> CSize -> IO () Source #

Initialize a free-list map which maps all types of allocation requests to a single free list. This is useful for drivers that don't really care about keeping different requests segregated in the underlying file and which want to make most efficient reuse of freed memory. The use of the h5fd_MEM_SUPER free list is arbitrary.

h5fd_FLMAP_DICHOTOMY :: OutArray H5FD_mem_t -> CSize -> IO () Source #

A free-list map which segregates requests into "raw" or "meta" data pools.

h5fd_FLMAP_DEFAULT :: OutArray H5FD_mem_t -> CSize -> IO () Source #

The default free list map which causes each request type to use its own free-list.

h5fd_FEAT_AGGREGATE_METADATA :: Num a => a Source #

Defining h5fd_FEAT_AGGREGATE_METADATA for a VFL driver means that the library will attempt to allocate a larger block for metadata and then sub-allocate each metadata request from that larger block.

h5fd_FEAT_ACCUMULATE_METADATA :: Num a => a Source #

Defining h5fd_FEAT_ACCUMULATE_METADATA for a VFL driver means that the library will attempt to cache metadata as it is written to the file and build up a larger block of metadata to eventually pass to the VFL write routine.

Distinguish between updating the metadata accumulator on writes (h5fd_FEAT_ACCUMULATE_METADATA_WRITE) and reads (h5fd_FEAT_ACCUMULATE_METADATA_READ). This is particularly (perhaps only, even) important for MPI-I/O where we guarantee that writes are collective, but reads may not be. If we were to allow the metadata accumulator to be written during a read operation, the application would hang.

h5fd_FEAT_DATA_SIEVE :: Num a => a Source #

Defining h5fd_FEAT_DATA_SIEVE for a VFL driver means that the library will attempt to cache raw data as it is read from/written to a file in a "data seive" buffer. See Rajeev Thakur's papers:

h5fd_FEAT_AGGREGATE_SMALLDATA :: Num a => a Source #

Defining h5fd_FEAT_AGGREGATE_SMALLDATA for a VFL driver means that the library will attempt to allocate a larger block for "small" raw data and then sub-allocate "small" raw data requests from that larger block.

h5fd_FEAT_IGNORE_DRVRINFO :: Num a => a Source #

Defining h5fd_FEAT_IGNORE_DRVRINFO for a VFL driver means that the library will ignore the driver info that is encoded in the file for the VFL driver. (This will cause the driver info to be eliminated from the file when it is flushedclosed, if the file is opened RW).

h5fd_FEAT_DIRTY_DRVRINFO_LOAD :: Num a => a Source #

Defining h5fd_FEAT_DIRTY_SBLK_LOAD for a VFL driver means that the library will mark the superblock dirty when the file is opened R/W. This will cause the driver info to be re-encoded when the file is flushed/closed.

h5fd_FEAT_POSIX_COMPAT_HANDLE :: Num a => a Source #

Defining h5fd_FEAT_POSIX_COMPAT_HANDLE for a VFL driver means that the handle for the VFD (returned with the get_handle callback) is of type int and is compatible with POSIX I/O calls.

h5fd_FEAT_ALLOW_FILE_IMAGE :: Num a => a Source #

Defining H5FD_FEAT_ALLOW_FILE_IMAGE for a VFL driver means that the driver is able to use a file image in the fapl as the initial contents of a file.

h5fd_FEAT_CAN_USE_FILE_IMAGE_CALLBACKS :: Num a => a Source #

Defining H5FD_FEAT_CAN_USE_FILE_IMAGE_CALLBACKS for a VFL driver means that the driver is able to use callbacks to make a copy of the image to store in memory.

data H5FD_class_t Source #

Class information for each file driver

Constructors

H5FD_class_t 

Fields

Instances

Instances details
Storable H5FD_class_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

sizeOf :: H5FD_class_t -> Int

alignment :: H5FD_class_t -> Int

peekElemOff :: Ptr H5FD_class_t -> Int -> IO H5FD_class_t

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

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

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

peek :: Ptr H5FD_class_t -> IO H5FD_class_t

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

Show H5FD_class_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

showsPrec :: Int -> H5FD_class_t -> ShowS

show :: H5FD_class_t -> String

showList :: [H5FD_class_t] -> ShowS

Eq H5FD_class_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

(==) :: H5FD_class_t -> H5FD_class_t -> Bool

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

data H5FD_free_t Source #

A free list is a singly-linked list of address/size pairs.

Instances

Instances details
Storable H5FD_free_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

sizeOf :: H5FD_free_t -> Int

alignment :: H5FD_free_t -> Int

peekElemOff :: Ptr H5FD_free_t -> Int -> IO H5FD_free_t

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

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

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

peek :: Ptr H5FD_free_t -> IO H5FD_free_t

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

Show H5FD_free_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

showsPrec :: Int -> H5FD_free_t -> ShowS

show :: H5FD_free_t -> String

showList :: [H5FD_free_t] -> ShowS

Eq H5FD_free_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

(==) :: H5FD_free_t -> H5FD_free_t -> Bool

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

p'H5FD_free_t'addr :: Ptr H5FD_free_t -> Ptr HAddr_t Source #

The main datatype for each driver. Public fields common to all drivers are declared here and the driver appends private fields in memory.

p'H5FD_free_t'size :: Ptr H5FD_free_t -> Ptr HSize_t Source #

driver ID for this file

p'H5FD_free_t'next :: Ptr H5FD_free_t -> Ptr (Ptr H5FD_free_t) Source #

constant class info

p'H5FD_class_t'name :: Ptr H5FD_class_t -> Ptr CString Source #

Threshold for alignment

File serial number

VFL Driver feature Flags

For this file, overrides class

Base address for HDF5 data w/in file

p'H5FD_class_t'maxaddr :: Ptr H5FD_class_t -> Ptr HAddr_t Source #

Allocation alignment

data H5FD_t Source #

Instances

Instances details
Storable H5FD_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

sizeOf :: H5FD_t -> Int

alignment :: H5FD_t -> Int

peekElemOff :: Ptr H5FD_t -> Int -> IO H5FD_t

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

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

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

peek :: Ptr H5FD_t -> IO H5FD_t

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

Show H5FD_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

showsPrec :: Int -> H5FD_t -> ShowS

show :: H5FD_t -> String

showList :: [H5FD_t] -> ShowS

Eq H5FD_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

(==) :: H5FD_t -> H5FD_t -> Bool

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

p'H5FD_class_t'terminate :: Ptr H5FD_class_t -> Ptr (FunPtr (IO HErr_t)) Source #

enum for the source of file image callbacks

newtype H5FD_file_image_op_t Source #

Constructors

H5FD_file_image_op_t Word32 

Instances

Instances details
Storable H5FD_file_image_op_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Show H5FD_file_image_op_t Source # 
Instance details

Defined in Bindings.HDF5.Raw.H5FD

Methods

showsPrec :: Int -> H5FD_file_image_op_t -> ShowS

show :: H5FD_file_image_op_t -> String

showList :: [H5FD_file_image_op_t] -> ShowS

p'H5FD_class_t'sb_encode :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> OutArray CChar -> Out CUChar -> IO HErr_t)) Source #

p'H5FD_class_t'sb_decode :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> CString -> In CUChar -> IO HErr_t)) Source #

p'H5FD_class_t'fapl_get :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> IO (Ptr ()))) Source #

p'H5FD_class_t'fapl_copy :: Ptr H5FD_class_t -> Ptr (FunPtr (Ptr () -> IO (Ptr ()))) Source #

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

p'H5FD_class_t'fapl_free :: Ptr H5FD_class_t -> Ptr (FunPtr (Ptr () -> IO HErr_t)) Source #

TODO: wrap this. not tackling it now, because there are a lot of pointer types to pin down.

p'H5FD_t'feature_flags :: Ptr H5FD_t -> Ptr CULong Source #

p'H5FD_class_t'dxpl_copy :: Ptr H5FD_class_t -> Ptr (FunPtr (Ptr () -> IO (Ptr ()))) Source #

p'H5FD_class_t'dxpl_free :: Ptr H5FD_class_t -> Ptr (FunPtr (Ptr () -> IO HErr_t)) Source #

p'H5FD_class_t'open :: Ptr H5FD_class_t -> Ptr (FunPtr (CString -> CUInt -> HId_t -> HAddr_t -> IO (Ptr H5FD_t))) Source #

p'H5FD_class_t'close :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> IO HErr_t)) Source #

p'H5FD_class_t'cmp :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> In H5FD_t -> IO CInt)) Source #

p'H5FD_class_t'query :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> Ptr CULong -> IO HErr_t)) Source #

p'H5FD_class_t'free :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> HSize_t -> IO HErr_t)) Source #

Registers a new file driver as a member of the virtual file driver class. Certain fields of the class struct are required and that is checked here so it doesn't have to be checked every time the field is accessed.

On success, returns a file driver ID which is good until the library is closed or the driver is unregistered. On failure, returns a negative value.

hid_t H5FDregister(const H5FD_class_t *cls);

p'H5FD_class_t'get_handle :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> HId_t -> Out (Ptr ()) -> IO HErr_t)) Source #

p'H5FD_class_t'read :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> CSize -> OutArray () -> IO HErr_t)) Source #

p'H5FD_class_t'write :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> CSize -> InArray () -> IO HErr_t)) Source #

Removes a driver ID from the library. This in no way affects file access property lists which have been defined to use this driver or files which are already opened under this driver.

Returns non-negative on success, negative on failure.

herr_t H5FDunregister(hid_t driver_id);

p'H5FD_class_t'flush :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> HId_t -> CUInt -> IO HErr_t)) Source #

p'H5FD_class_t'lock :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> HBool_t -> IO HErr_t)) Source #

p'H5FD_class_t'unlock :: Ptr H5FD_class_t -> Ptr (FunPtr (In H5FD_t -> IO HErr_t)) Source #

p'H5FD_class_t'fl_map :: Ptr H5FD_class_t -> Ptr H5FD_mem_t Source #

Opens a file named name for the type(s) of access described by the bit vector flags according to a file access property list fapl_id (which may be the constant h5p_DEFAULT). The file should expect to handle format addresses in the range [0, maxaddr] (if maxaddr is hADDR_UNDEF then the caller doesn't care about the address range).

Possible values for the flags bits are:

h5f_ACC_RDWR
Open the file for read and write access. If this bit is not set then open the file for read only access. It is permissible to open a file for read and write access when only read access is requested by the library (the library will never attempt to write to a file which it opened with only read access).
h5f_ACC_CREAT
Create the file if it doesn't already exist. However, see h5f_ACC_EXCL below.
h5f_ACC_TRUNC
Truncate the file if it already exists. This is equivalent to deleting the file and then creating a new empty file.
h5f_ACC_EXCL
When used with h5f_ACC_CREAT, if the file already exists then the open should fail. Note that this is unsupported/broken with some file drivers (e.g., sec2 across nfs) and will contain a race condition when used to perform file locking.

The maxaddr is the maximum address which will be requested by the library during an allocation operation. Usually this is the same value as the maxaddr field of the class structure, but it can be smaller if the driver is being used under some other driver.

Note that when the driver open callback gets control that the public part of the file struct (the H5FD_t part) will be incomplete and will be filled in after that callback returns.

On success, returns a pointer to a new file driver struct. On failure, returns nullPtr.

H5FD_t *H5FDopen(const char *name, unsigned flags, hid_t fapl_id,
       haddr_t maxaddr);

h5fd_open :: CString -> CUInt -> HId_t -> HAddr_t -> IO (Ptr H5FD_t) Source #

p_H5FDopen :: FunPtr (CString -> CUInt -> HId_t -> HAddr_t -> IO (Ptr H5FD_t)) Source #

h5fd_close :: In H5FD_t -> IO HErr_t Source #

Closes the file by calling the driver close callback, which should free all driver-private data and free the file struct. Note that the public part of the file struct (the H5FD_t part) will be all zero during the driver close callback like during the open callback.

Returns non-negative on success, negative on failure.

herr_t H5FDclose(H5FD_t *file);

p_H5FDclose :: FunPtr (In H5FD_t -> IO HErr_t) Source #

h5fd_cmp :: In H5FD_t -> In H5FD_t -> IO CInt Source #

Compare the keys of two files using the file driver callback if the files belong to the same driver, otherwise sort the files by driver class pointer value.

Returns an integer greater than, less than, or equal to zero, indicating the corresponding ordering.

Must never fail. If both file handles are invalid then they compare equal. If one file handle is invalid then it compares less than the other. If both files belong to the same driver and the driver doesn't provide a comparison callback then the file pointers themselves are compared.

int H5FDcmp(const H5FD_t *f1, const H5FD_t *f2);

p_H5FDcmp :: FunPtr (In H5FD_t -> In H5FD_t -> IO CInt) Source #

h5fd_query :: In H5FD_t -> Out CULong -> IO CInt Source #

Query a VFL driver for its feature flags. (listed in Bindings.HDF5.Raw.H5FD)

Returns non-negative on success, negative on failure.

int H5FDquery(const H5FD_t *f, unsigned long *flags);

p_H5FDquery :: FunPtr (In H5FD_t -> Out CULong -> IO CInt) Source #

h5fd_alloc :: In H5FD_t -> H5FD_mem_t -> HId_t -> HSize_t -> IO HAddr_t Source #

Allocates size bytes of memory from the file. The memory will be used according to the allocation class 'type'. First we try to satisfy the request from one of the free lists, according to the free list map provided by the driver. The free list array has one entry for each request type and the value of that array element can be one of four possibilities:

  • It can be the constant h5fd_MEM_DEFAULT (or zero) which indicates that the identity mapping is used. In other words, the request type maps to its own free list.
  • It can be the request type itself, which has the same effect as the h5fd_MEM_DEFAULT value above.
  • It can be the ID for another request type, which indicates that the free list for the specified type should be used instead.
  • It can be the constant h5fd_MEM_NOLIST which means that no free list should be used for this type of request.

If the request cannot be satisfied from a free list then either the driver's alloc callback is invoked (if one was supplied) or the end-of-address marker is extended. The alloc callback is always called with the same arguments as the h5fd_alloc.

Returns the format address of the new file memory, or the undefined address hADDR_UNDEF on failure.

haddr_t H5FDalloc(H5FD_t *file, H5FD_mem_t type, hid_t dxpl_id, hsize_t size);

h5fd_free :: In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> HSize_t -> IO HErr_t Source #

Frees format addresses starting with addr and continuing for size bytes in the file file. The type of space being freed is specified by 'type', which is mapped to a free list as described for the h5fd_alloc function above. If the request doesn't map to a free list then either the application free callback is invoked (if defined) or the memory is leaked.

Returns non-negative on success, negative on failure.

herr_t H5FDfree(H5FD_t *file, H5FD_mem_t type, hid_t dxpl_id,
                       haddr_t addr, hsize_t size);

h5fd_get_eoa :: In H5FD_t -> H5FD_mem_t -> IO HAddr_t Source #

Returns the address of the first byte after the last allocated memory in the file, or hADDR_UNDEF on failure.

haddr_t H5FDget_eoa(H5FD_t *file, H5FD_mem_t type);

h5fd_set_eoa :: In H5FD_t -> H5FD_mem_t -> HAddr_t -> IO HErr_t Source #

Set the end-of-address marker for the file. The addr is the address of the first byte past the last allocated byte of the file. This function is called from two places:

  1. It is called after an existing file is opened in order to "allocate" enough space to read the superblock and then to "allocate" the entire hdf5 file based on the contents of the superblock.
  2. It is called during file memory allocation if the allocation request cannot be satisfied from the free list and the driver didn't supply an allocation callback.

Returns non-negative on success, or negative on failure. If the operation fails, it will do so with no side-effects.

herr_t H5FDset_eoa(H5FD_t *file, H5FD_mem_t type, haddr_t eoa);

h5fd_get_vfd_handle :: In H5FD_t -> HId_t -> Out (Ptr a) -> IO HErr_t Source #

Returns the end-of-file address, which is the greater of the end-of-format address and the actual EOF marker. This function is called after an existing file is opened in order for the library to learn the true size of the underlying file and to determine whether the hdf5 data has been truncated.

It is also used when a file is first opened to learn whether the file is empty or not.

It is permissible for the driver to return the maximum address for the file size if the file is not empty.

On failure, returns hADDR_UNDEF

Returns a pointer to the file handle of low-level virtual file driver.

returns non-negative on success, negative otherwise.

herr_t H5FDget_vfd_handle(H5FD_t *file, hid_t fapl, void**file_handle);

p_H5FDget_vfd_handle :: FunPtr (In H5FD_t -> HId_t -> Out (Ptr a) -> IO HErr_t) Source #

h5fd_read :: In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> CSize -> OutArray a -> IO HErr_t Source #

Reads size bytes from file beginning at address addr according to the data transfer property list dxpl_id (which may be the constant h5p_DEFAULT). The result is written into the buffer buf.

Returns non-negative on success. The read result is written into the buf buffer which should be allocated by the caller.

On failure, returns a negative value and the contents of buf is undefined.

herr_t H5FDread(H5FD_t *file, H5FD_mem_t type, hid_t dxpl_id,
       haddr_t addr, size_t size, void *buf/*out*/);

p_H5FDread :: FunPtr (In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> CSize -> OutArray a -> IO HErr_t) Source #

h5fd_write :: In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> CSize -> InArray a -> IO HErr_t Source #

Writes size bytes to file beginning at address addr according to the data transfer property list dxpl_id (which may be the constant h5p_DEFAULT). The bytes to be written come from the buffer buf.

Returns non-negative on success, negative on failure.

herr_t H5FDwrite(H5FD_t *file, H5FD_mem_t type, hid_t dxpl_id,
       haddr_t addr, size_t size, const void *buf);

p_H5FDwrite :: FunPtr (In H5FD_t -> H5FD_mem_t -> HId_t -> HAddr_t -> CSize -> InArray a -> IO HErr_t) Source #

h5fd_flush :: In H5FD_t -> HId_t -> CUInt -> IO HErr_t Source #

Notify driver to flush all cached data. If the driver has no flush method then nothing happens.

Returns non-negative on success, negative on failure.

herr_t H5FDflush(H5FD_t *file, hid_t dxpl_id, unsigned closing);

p_H5FDflush :: FunPtr (In H5FD_t -> HId_t -> CUInt -> IO HErr_t) Source #

h5fd_truncate :: In H5FD_t -> HId_t -> HBool_t -> IO HErr_t Source #

Notify driver to truncate the file back to the allocated size.

Returns non-negative on success, negative on failure.

herr_t H5FDtruncate(H5FD_t *file, hid_t dxpl_id, hbool_t closing);

h5fd_MEM_EARRAY_HDR :: H5F_mem_t Source #

Map "extensible array" header blocks to ohdr type file memory, since its a fair amount of work to add a new kind of file memory and they are similar enough to object headers and probably too minor to deserve their own type.

Map "extensible array" index blocks to ohdr type file memory, since they are similar to extensible array header blocks.

Map "extensible array" super blocks to btree type file memory, since they are similar enough to B-tree nodes.

Map "extensible array" data blocks & pages to lheap type file memory, since they are similar enough to local heap info.

h5fd_MEM_FARRAY_HDR :: H5F_mem_t Source #

Map "fixed array" header blocks to ohdr type file memory, since its a fair amount of work to add a new kind of file memory and they are similar enough to object headers and probably too minor to deserve their own type.

Map "fixed array" data blocks & pages to lheap type file memory, since they are similar enough to local heap info.

h5fd_FEAT_SUPPORTS_SWMR_IO :: Num a => a Source #

Defining H5FD_FEAT_SUPPORTS_SWMR_IO for a VFL driver means that the driver supports the single-writermultiple-readers IO pattern.

p_H5FDlock :: FunPtr (In H5FD_t -> HBool_t -> IO HErr_t) Source #

p_H5FDunlock :: FunPtr (In H5FD_t -> IO HErr_t) Source #