Safe Haskell | None |
---|---|
Language | Haskell2010 |
Bindings.HDF5.Raw.H5E
Contents
- Major error codes
- Minor error codes
- Generic low-level file I/O errors
- Resource errors
- Heap errors
- Function entry/exit interface errors
- Property list errors
- Free space errors
- Object header related errors
- System level errors
- I/O pipeline errors
- Group related errors
- No error
- Plugin errors
- File accessibility errors
- Object atom related errors
- Cache related errors
- Link related errors
- Parallel MPI errors
- Dataspace errors
- Argument errors
- B-tree related errors
- Datatype conversion errors
- Error stack traversal callback function types
- Public API functions
- Deprecated symbols
Synopsis
- h5e_DEFAULT :: HId_t
- newtype H5E_type_t = H5E_type_t Word32
- h5e_MAJOR :: H5E_type_t
- h5e_MINOR :: H5E_type_t
- data H5E_error2_t = H5E_error2_t {
- h5e_error2_t'cls_id :: HId_t
- h5e_error2_t'maj_num :: HId_t
- h5e_error2_t'min_num :: HId_t
- h5e_error2_t'line :: CUInt
- h5e_error2_t'func_name :: CString
- h5e_error2_t'file_name :: CString
- h5e_error2_t'desc :: CString
- h5e_ERR_CLS :: HId_t
- h5e_DATASET :: HId_t
- p'H5E_error2_t'cls_id :: Ptr H5E_error2_t -> Ptr HId_t
- h5e_FUNC :: HId_t
- p'H5E_error2_t'maj_num :: Ptr H5E_error2_t -> Ptr HId_t
- p'H5E_error2_t'min_num :: Ptr H5E_error2_t -> Ptr HId_t
- h5e_STORAGE :: HId_t
- p'H5E_error2_t'line :: Ptr H5E_error2_t -> Ptr CUInt
- h5e_FILE :: HId_t
- p'H5E_error2_t'func_name :: Ptr H5E_error2_t -> Ptr CString
- p'H5E_error2_t'file_name :: Ptr H5E_error2_t -> Ptr CString
- h5e_SOHM :: HId_t
- p'H5E_error2_t'desc :: Ptr H5E_error2_t -> Ptr CString
- h5e_SYM :: HId_t
- h5e_PLUGIN :: HId_t
- h5e_VFL :: HId_t
- h5e_INTERNAL :: HId_t
- h5e_BTREE :: HId_t
- h5e_REFERENCE :: HId_t
- h5e_DATASPACE :: HId_t
- h5e_RESOURCE :: HId_t
- h5e_PLIST :: HId_t
- h5e_LINK :: HId_t
- h5e_DATATYPE :: HId_t
- h5e_RS :: HId_t
- h5e_HEAP :: HId_t
- h5e_OHDR :: HId_t
- h5e_ATTR :: HId_t
- h5e_NONE_MAJOR :: HId_t
- h5e_IO :: HId_t
- h5e_SLIST :: HId_t
- h5e_EFL :: HId_t
- h5e_TST :: HId_t
- h5e_ARGS :: HId_t
- h5e_ERROR :: HId_t
- h5e_PLINE :: HId_t
- h5e_FSPACE :: HId_t
- h5e_CACHE :: HId_t
- h5e_SEEKERROR :: HId_t
- h5e_READERROR :: HId_t
- h5e_WRITEERROR :: HId_t
- h5e_CLOSEERROR :: HId_t
- h5e_OVERFLOW :: HId_t
- h5e_FCNTL :: HId_t
- h5e_NOSPACE :: HId_t
- h5e_CANTALLOC :: HId_t
- h5e_CANTCOPY :: HId_t
- h5e_CANTFREE :: HId_t
- h5e_ALREADYEXISTS :: HId_t
- h5e_CANTLOCK :: HId_t
- h5e_CANTUNLOCK :: HId_t
- h5e_CANTGC :: HId_t
- h5e_CANTGETSIZE :: HId_t
- h5e_OBJOPEN :: HId_t
- h5e_CANTRESTORE :: HId_t
- h5e_CANTCOMPUTE :: HId_t
- h5e_CANTEXTEND :: HId_t
- h5e_CANTATTACH :: HId_t
- h5e_CANTUPDATE :: HId_t
- h5e_CANTOPERATE :: HId_t
- h5e_CANTINIT :: HId_t
- h5e_ALREADYINIT :: HId_t
- h5e_CANTRELEASE :: HId_t
- h5e_CANTGET :: HId_t
- h5e_CANTSET :: HId_t
- h5e_DUPCLASS :: HId_t
- h5e_SETDISALLOWED :: HId_t
- h5e_CANTMERGE :: HId_t
- h5e_CANTREVIVE :: HId_t
- h5e_CANTSHRINK :: HId_t
- h5e_LINKCOUNT :: HId_t
- h5e_VERSION :: HId_t
- h5e_ALIGNMENT :: HId_t
- h5e_BADMESG :: HId_t
- h5e_CANTDELETE :: HId_t
- h5e_BADITER :: HId_t
- h5e_CANTPACK :: HId_t
- h5e_CANTRESET :: HId_t
- h5e_CANTRENAME :: HId_t
- h5e_SYSERRSTR :: HId_t
- h5e_NOFILTER :: HId_t
- h5e_CALLBACK :: HId_t
- h5e_CANAPPLY :: HId_t
- h5e_SETLOCAL :: HId_t
- h5e_NOENCODER :: HId_t
- h5e_CANTFILTER :: HId_t
- h5e_CANTOPENOBJ :: HId_t
- h5e_CANTCLOSEOBJ :: HId_t
- h5e_COMPLEN :: HId_t
- h5e_PATH :: HId_t
- h5e_NONE_MINOR :: HId_t
- h5e_OPENERROR :: HId_t
- h5e_FILEEXISTS :: HId_t
- h5e_FILEOPEN :: HId_t
- h5e_CANTCREATE :: HId_t
- h5e_CANTOPENFILE :: HId_t
- h5e_CANTCLOSEFILE :: HId_t
- h5e_NOTHDF5 :: HId_t
- h5e_BADFILE :: HId_t
- h5e_TRUNCATED :: HId_t
- h5e_MOUNT :: HId_t
- h5e_BADGROUP :: HId_t
- h5e_CANTREGISTER :: HId_t
- h5e_CANTINC :: HId_t
- h5e_CANTDEC :: HId_t
- h5e_NOIDS :: HId_t
- h5e_CANTFLUSH :: HId_t
- h5e_CANTSERIALIZE :: HId_t
- h5e_CANTLOAD :: HId_t
- h5e_PROTECT :: HId_t
- h5e_NOTCACHED :: HId_t
- h5e_SYSTEM :: HId_t
- h5e_CANTINS :: HId_t
- h5e_CANTPROTECT :: HId_t
- h5e_CANTUNPROTECT :: HId_t
- h5e_CANTPIN :: HId_t
- h5e_CANTUNPIN :: HId_t
- h5e_CANTMARKDIRTY :: HId_t
- h5e_CANTDIRTY :: HId_t
- h5e_CANTEXPUNGE :: HId_t
- h5e_CANTRESIZE :: HId_t
- h5e_TRAVERSE :: HId_t
- h5e_NLINKS :: HId_t
- h5e_NOTREGISTERED :: HId_t
- h5e_CANTMOVE :: HId_t
- h5e_CANTSORT :: HId_t
- h5e_MPI :: HId_t
- h5e_MPIERRSTR :: HId_t
- h5e_CANTRECV :: HId_t
- h5e_CANTCLIP :: HId_t
- h5e_CANTCOUNT :: HId_t
- h5e_CANTSELECT :: HId_t
- h5e_CANTNEXT :: HId_t
- h5e_BADSELECT :: HId_t
- h5e_CANTCOMPARE :: HId_t
- h5e_UNINITIALIZED :: HId_t
- h5e_UNSUPPORTED :: HId_t
- h5e_BADTYPE :: HId_t
- h5e_BADRANGE :: HId_t
- h5e_BADVALUE :: HId_t
- h5e_NOTFOUND :: HId_t
- h5e_EXISTS :: HId_t
- h5e_CANTENCODE :: HId_t
- h5e_CANTDECODE :: HId_t
- h5e_CANTSPLIT :: HId_t
- h5e_CANTREDISTRIBUTE :: HId_t
- h5e_CANTSWAP :: HId_t
- h5e_CANTINSERT :: HId_t
- h5e_CANTLIST :: HId_t
- h5e_CANTMODIFY :: HId_t
- h5e_CANTREMOVE :: HId_t
- h5e_CANTCONVERT :: HId_t
- h5e_BADSIZE :: HId_t
- newtype H5E_TRY_STATE = H5E_TRY_STATE (Either (H5E_auto1_t ()) (H5E_auto2_t ()), InOut ())
- h5e_BEGIN_TRY :: IO H5E_TRY_STATE
- h5e_END_TRY :: H5E_TRY_STATE -> IO HErr_t
- h5e_try :: IO a -> IO a
- newtype H5E_direction_t = H5E_direction_t Word32
- h5e_WALK_UPWARD :: H5E_direction_t
- h5e_WALK_DOWNWARD :: H5E_direction_t
- type H5E_walk2_t a = FunPtr (CUInt -> In H5E_error2_t -> InOut a -> IO HErr_t)
- type H5E_auto2_t a = FunPtr (HId_t -> InOut a -> IO HErr_t)
- h5e_register_class :: CString -> CString -> CString -> IO HId_t
- p_H5Eregister_class :: FunPtr (CString -> CString -> CString -> IO HId_t)
- h5e_unregister_class :: HId_t -> IO HErr_t
- p_H5Eunregister_class :: FunPtr (HId_t -> IO HErr_t)
- h5e_close_msg :: HId_t -> IO HErr_t
- p_H5Eclose_msg :: FunPtr (HId_t -> IO HErr_t)
- h5e_create_msg :: HId_t -> H5E_type_t -> CString -> IO HId_t
- p_H5Ecreate_msg :: FunPtr (HId_t -> H5E_type_t -> CString -> IO HId_t)
- h5e_create_stack :: IO HId_t
- p_H5Ecreate_stack :: FunPtr (IO HId_t)
- h5e_get_current_stack :: IO HId_t
- p_H5Eget_current_stack :: FunPtr (IO HId_t)
- h5e_close_stack :: HId_t -> IO HErr_t
- p_H5Eclose_stack :: FunPtr (HId_t -> IO HErr_t)
- h5e_get_class_name :: HId_t -> OutArray CChar -> CSize -> IO CSSize
- p_H5Eget_class_name :: FunPtr (HId_t -> OutArray CChar -> CSize -> IO CSSize)
- h5e_set_current_stack :: HId_t -> IO HErr_t
- p_H5Eset_current_stack :: FunPtr (HId_t -> IO HErr_t)
- h5e_push2 :: HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> [Arg] -> IO HErr_t
- h5e_push2_no_varargs :: HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> IO HErr_t
- p_H5Epush2 :: FunPtr (HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> IO HErr_t)
- h5e_pop :: HId_t -> CSize -> IO HErr_t
- p_H5Epop :: FunPtr (HId_t -> CSize -> IO HErr_t)
- h5e_print2 :: HId_t -> InOut CFile -> IO HErr_t
- p_H5Eprint2 :: FunPtr (HId_t -> InOut CFile -> IO HErr_t)
- h5e_walk2 :: HId_t -> H5E_direction_t -> H5E_walk2_t a -> InOut a -> IO HErr_t
- p_H5Ewalk2 :: FunPtr (HId_t -> H5E_direction_t -> H5E_walk2_t a -> InOut a -> IO HErr_t)
- h5e_get_auto2 :: HId_t -> Out (H5E_auto2_t a) -> Out (InOut a) -> IO HErr_t
- p_H5Eget_auto2 :: FunPtr (HId_t -> Out (H5E_auto2_t a) -> Out (InOut a) -> IO HErr_t)
- h5e_set_auto2 :: HId_t -> H5E_auto2_t a -> InOut a -> IO HErr_t
- p_H5Eset_auto2 :: FunPtr (HId_t -> H5E_auto2_t a -> InOut a -> IO HErr_t)
- h5e_clear2 :: HId_t -> IO HErr_t
- p_H5Eclear2 :: FunPtr (HId_t -> IO HErr_t)
- h5e_auto_is_v2 :: HId_t -> Out CUInt -> IO HErr_t
- p_H5Eauto_is_v2 :: FunPtr (HId_t -> Out CUInt -> IO HErr_t)
- h5e_get_msg :: HId_t -> Out H5E_type_t -> OutArray CChar -> CSize -> IO CSSize
- p_H5Eget_msg :: FunPtr (HId_t -> Out H5E_type_t -> OutArray CChar -> CSize -> IO CSSize)
- h5e_get_num :: HId_t -> IO CSSize
- p_H5Eget_num :: FunPtr (HId_t -> IO CSSize)
- newtype H5E_major_t = H5E_major_t Int64
- newtype H5E_minor_t = H5E_minor_t Int64
- data H5E_error1_t = H5E_error1_t {
- h5e_error1_t'maj_num :: H5E_major_t
- h5e_error1_t'min_num :: H5E_minor_t
- h5e_error1_t'func_name :: CString
- h5e_error1_t'file_name :: CString
- h5e_error1_t'line :: CUInt
- h5e_error1_t'desc :: CString
- type H5E_walk1_t a = FunPtr (CInt -> In H5E_error1_t -> InOut a -> IO HErr_t)
- p'H5E_error1_t'maj_num :: Ptr H5E_error1_t -> Ptr H5E_major_t
- type H5E_auto1_t a = FunPtr (InOut a -> IO HErr_t)
- p'H5E_error1_t'min_num :: Ptr H5E_error1_t -> Ptr H5E_minor_t
- p'H5E_error1_t'func_name :: Ptr H5E_error1_t -> Ptr CString
- p'H5E_error1_t'file_name :: Ptr H5E_error1_t -> Ptr CString
- p'H5E_error1_t'line :: Ptr H5E_error1_t -> Ptr CUInt
- p'H5E_error1_t'desc :: Ptr H5E_error1_t -> Ptr CString
- h5e_clear1 :: IO HErr_t
- p_H5Eclear1 :: FunPtr (IO HErr_t)
- h5e_get_auto1 :: Out (H5E_auto1_t a) -> Out (InOut a) -> IO HErr_t
- p_H5Eget_auto1 :: FunPtr (Out (H5E_auto1_t a) -> Out (InOut a) -> IO HErr_t)
- h5e_push1 :: CString -> CString -> CUInt -> H5E_major_t -> H5E_minor_t -> CString -> IO HErr_t
- p_H5Epush1 :: FunPtr (CString -> CString -> CUInt -> H5E_major_t -> H5E_minor_t -> CString -> IO HErr_t)
- h5e_print1 :: InOut CFile -> IO HErr_t
- p_H5Eprint1 :: FunPtr (InOut CFile -> IO HErr_t)
- h5e_set_auto1 :: H5E_auto1_t a -> InOut a -> IO HErr_t
- p_H5Eset_auto1 :: FunPtr (H5E_auto1_t a -> InOut a -> IO HErr_t)
- h5e_walk1 :: H5E_direction_t -> H5E_walk1_t a -> InOut a -> IO HErr_t
- p_H5Ewalk1 :: FunPtr (H5E_direction_t -> H5E_walk1_t a -> InOut a -> IO HErr_t)
- h5e_get_major :: H5E_major_t -> IO CString
- p_H5Eget_major :: FunPtr (H5E_major_t -> IO CString)
- h5e_get_minor :: H5E_minor_t -> IO CString
- p_H5Eget_minor :: FunPtr (H5E_minor_t -> IO CString)
Documentation
h5e_DEFAULT :: HId_t Source #
Value for the default error stack
newtype H5E_type_t Source #
Different kinds of error information
Constructors
H5E_type_t Word32 |
Instances
Storable H5E_type_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods sizeOf :: H5E_type_t -> Int alignment :: H5E_type_t -> Int peekElemOff :: Ptr H5E_type_t -> Int -> IO H5E_type_t pokeElemOff :: Ptr H5E_type_t -> Int -> H5E_type_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5E_type_t pokeByteOff :: Ptr b -> Int -> H5E_type_t -> IO () peek :: Ptr H5E_type_t -> IO H5E_type_t poke :: Ptr H5E_type_t -> H5E_type_t -> IO () | |
Show H5E_type_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods showsPrec :: Int -> H5E_type_t -> ShowS show :: H5E_type_t -> String showList :: [H5E_type_t] -> ShowS |
data H5E_error2_t Source #
Information about an error; element of error stack
class ID
major error ID
minor error number
line in file where error occurs
function in which error occurred
file in which error occurred
optional supplied description
Constructors
H5E_error2_t | |
Fields
|
Instances
Storable H5E_error2_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods sizeOf :: H5E_error2_t -> Int alignment :: H5E_error2_t -> Int peekElemOff :: Ptr H5E_error2_t -> Int -> IO H5E_error2_t pokeElemOff :: Ptr H5E_error2_t -> Int -> H5E_error2_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5E_error2_t pokeByteOff :: Ptr b -> Int -> H5E_error2_t -> IO () peek :: Ptr H5E_error2_t -> IO H5E_error2_t poke :: Ptr H5E_error2_t -> H5E_error2_t -> IO () | |
Show H5E_error2_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods showsPrec :: Int -> H5E_error2_t -> ShowS show :: H5E_error2_t -> String showList :: [H5E_error2_t] -> ShowS | |
Eq H5E_error2_t Source # | |
Defined in Bindings.HDF5.Raw.H5E |
h5e_ERR_CLS :: HId_t Source #
HDF5 error class
Major error codes
h5e_DATASET :: HId_t Source #
Dataset
p'H5E_error2_t'cls_id :: Ptr H5E_error2_t -> Ptr HId_t Source #
Function entry/exit
p'H5E_error2_t'maj_num :: Ptr H5E_error2_t -> Ptr HId_t Source #
p'H5E_error2_t'min_num :: Ptr H5E_error2_t -> Ptr HId_t Source #
Data storage
h5e_STORAGE :: HId_t Source #
p'H5E_error2_t'line :: Ptr H5E_error2_t -> Ptr CUInt Source #
File accessibility
p'H5E_error2_t'func_name :: Ptr H5E_error2_t -> Ptr CString Source #
p'H5E_error2_t'file_name :: Ptr H5E_error2_t -> Ptr CString Source #
Shared Object Header Messages
p'H5E_error2_t'desc :: Ptr H5E_error2_t -> Ptr CString Source #
Symbol table
h5e_PLUGIN :: HId_t Source #
Plugin for dynamically loaded library
h5e_INTERNAL :: HId_t Source #
Internal error (too specific to document in detail)
h5e_REFERENCE :: HId_t Source #
References
h5e_DATASPACE :: HId_t Source #
Dataspace
h5e_RESOURCE :: HId_t Source #
Resource unavailable
h5e_DATATYPE :: HId_t Source #
Datatype
h5e_NONE_MAJOR :: HId_t Source #
No error
h5e_FSPACE :: HId_t Source #
Free Space Manager
Minor error codes
Generic low-level file I/O errors
h5e_SEEKERROR :: HId_t Source #
Seek failed
h5e_READERROR :: HId_t Source #
Read failed
h5e_WRITEERROR :: HId_t Source #
Write failed
h5e_CLOSEERROR :: HId_t Source #
Close failed
h5e_OVERFLOW :: HId_t Source #
Address overflowed
Resource errors
h5e_NOSPACE :: HId_t Source #
No space available for allocation
h5e_CANTALLOC :: HId_t Source #
Can't allocate space
h5e_CANTCOPY :: HId_t Source #
Unable to copy object
h5e_CANTFREE :: HId_t Source #
Unable to free object
h5e_ALREADYEXISTS :: HId_t Source #
Object already exists
h5e_CANTLOCK :: HId_t Source #
Unable to lock object
h5e_CANTUNLOCK :: HId_t Source #
Unable to unlock object
h5e_CANTGC :: HId_t Source #
Unable to garbage collect
h5e_CANTGETSIZE :: HId_t Source #
Unable to compute size
h5e_OBJOPEN :: HId_t Source #
Object is already open
Heap errors
Function entry/exit interface errors
h5e_CANTINIT :: HId_t Source #
Property list errors
h5e_CANTGET :: HId_t Source #
h5e_CANTSET :: HId_t Source #
h5e_DUPCLASS :: HId_t Source #
Free space errors
Object header related errors
h5e_VERSION :: HId_t Source #
h5e_BADMESG :: HId_t Source #
h5e_BADITER :: HId_t Source #
h5e_CANTPACK :: HId_t Source #
System level errors
I/O pipeline errors
h5e_NOFILTER :: HId_t Source #
h5e_CALLBACK :: HId_t Source #
h5e_CANAPPLY :: HId_t Source #
h5e_SETLOCAL :: HId_t Source #
Group related errors
h5e_COMPLEN :: HId_t Source #
No error
Plugin errors
File accessibility errors
h5e_FILEOPEN :: HId_t Source #
h5e_NOTHDF5 :: HId_t Source #
h5e_BADFILE :: HId_t Source #
Object atom related errors
h5e_BADGROUP :: HId_t Source #
h5e_CANTINC :: HId_t Source #
h5e_CANTDEC :: HId_t Source #
Cache related errors
h5e_CANTLOAD :: HId_t Source #
h5e_PROTECT :: HId_t Source #
h5e_SYSTEM :: HId_t Source #
h5e_CANTINS :: HId_t Source #
h5e_CANTPIN :: HId_t Source #
Link related errors
h5e_TRAVERSE :: HId_t Source #
h5e_NLINKS :: HId_t Source #
h5e_CANTMOVE :: HId_t Source #
h5e_CANTSORT :: HId_t Source #
Parallel MPI errors
h5e_CANTRECV :: HId_t Source #
Dataspace errors
h5e_CANTCLIP :: HId_t Source #
h5e_CANTNEXT :: HId_t Source #
Argument errors
h5e_BADTYPE :: HId_t Source #
h5e_BADRANGE :: HId_t Source #
h5e_BADVALUE :: HId_t Source #
B-tree related errors
h5e_NOTFOUND :: HId_t Source #
h5e_EXISTS :: HId_t Source #
h5e_CANTSWAP :: HId_t Source #
h5e_CANTLIST :: HId_t Source #
Datatype conversion errors
h5e_BADSIZE :: HId_t Source #
newtype H5E_TRY_STATE Source #
Constructors
H5E_TRY_STATE (Either (H5E_auto1_t ()) (H5E_auto2_t ()), InOut ()) |
h5e_BEGIN_TRY :: IO H5E_TRY_STATE Source #
h5e_END_TRY :: H5E_TRY_STATE -> IO HErr_t Source #
h5e_try :: IO a -> IO a Source #
This is not a standard HDF5 function or macro, but rather a wrapper to the paired macros H5E_BEGIN_TRY and H5E_END_TRY, wrapping a simple action.
newtype H5E_direction_t Source #
Error stack traversal direction
Constructors
H5E_direction_t Word32 |
Instances
Storable H5E_direction_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods sizeOf :: H5E_direction_t -> Int alignment :: H5E_direction_t -> Int peekElemOff :: Ptr H5E_direction_t -> Int -> IO H5E_direction_t pokeElemOff :: Ptr H5E_direction_t -> Int -> H5E_direction_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5E_direction_t pokeByteOff :: Ptr b -> Int -> H5E_direction_t -> IO () peek :: Ptr H5E_direction_t -> IO H5E_direction_t poke :: Ptr H5E_direction_t -> H5E_direction_t -> IO () | |
Show H5E_direction_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods showsPrec :: Int -> H5E_direction_t -> ShowS show :: H5E_direction_t -> String showList :: [H5E_direction_t] -> ShowS |
h5e_WALK_UPWARD :: H5E_direction_t Source #
begin deep, end at API function
h5e_WALK_DOWNWARD :: H5E_direction_t Source #
begin at API function, end deep
Error stack traversal callback function types
type H5E_walk2_t a = FunPtr (CUInt -> In H5E_error2_t -> InOut a -> IO HErr_t) Source #
Callback type for h5e_walk2
typedef herr_t (*H5E_walk2_t)(unsigned n, const H5E_error2_t *err_desc, void *client_data);
type H5E_auto2_t a = FunPtr (HId_t -> InOut a -> IO HErr_t) Source #
Callback type for h5e_set_auto2
typedef herr_t (*H5E_auto2_t)(hid_t estack, void *client_data);
Public API functions
h5e_register_class :: CString -> CString -> CString -> IO HId_t Source #
Registers an error class.
Returns non-negative value as class ID on success / negative on failure
hid_t H5Eregister_class(const char *cls_name, const char *lib_name, const char *version);
p_H5Eregister_class :: FunPtr (CString -> CString -> CString -> IO HId_t) Source #
h5e_unregister_class :: HId_t -> IO HErr_t Source #
Closes an error class.
Returns non-negative value on success / negative on failure
herr_t H5Eunregister_class(hid_t class_id);
p_H5Eunregister_class :: FunPtr (HId_t -> IO HErr_t) Source #
h5e_close_msg :: HId_t -> IO HErr_t Source #
Closes a major or minor error.
Returns non-negative value on success / negative on failure
herr_t H5Eclose_msg(hid_t err_id);
p_H5Eclose_msg :: FunPtr (HId_t -> IO HErr_t) Source #
h5e_create_msg :: HId_t -> H5E_type_t -> CString -> IO HId_t Source #
Creates a major or minor error, returns an ID.
Returns non-negative value on success / negative on failure
hid_t H5Ecreate_msg(hid_t cls, H5E_type_t msg_type, const char *msg);
p_H5Ecreate_msg :: FunPtr (HId_t -> H5E_type_t -> CString -> IO HId_t) Source #
h5e_create_stack :: IO HId_t Source #
Creates a new, empty, error stack.
Returns non-negative value as stack ID on success / negative on failure
hid_t H5Ecreate_stack(void);
p_H5Ecreate_stack :: FunPtr (IO HId_t) Source #
h5e_get_current_stack :: IO HId_t Source #
Registers current error stack, returns object handle for it, clears it.
Returns non-negative value as stack ID on success / negative on failure
hid_t H5Eget_current_stack(void);
p_H5Eget_current_stack :: FunPtr (IO HId_t) Source #
h5e_close_stack :: HId_t -> IO HErr_t Source #
Closes an error stack.
Returns non-negative value on success / negative on failure
herr_t H5Eclose_stack(hid_t stack_id);
p_H5Eclose_stack :: FunPtr (HId_t -> IO HErr_t) Source #
h5e_get_class_name :: HId_t -> OutArray CChar -> CSize -> IO CSSize Source #
Retrieves error class name.
Returns non-negative for name length if succeeds(zero means no name); otherwise returns negative value.
On successful return, name
will always be zero-terminated.
NB: The return value is the length of the name, not the length copied to the buffer.
ssize_t H5Eget_class_name(hid_t class_id, char *name, size_t size);
h5e_set_current_stack :: HId_t -> IO HErr_t Source #
Replaces current stack with specified stack. This closes the stack ID also.
Returns non-negative value on success / negative on failure
herr_t H5Eset_current_stack(hid_t err_stack_id);
p_H5Eset_current_stack :: FunPtr (HId_t -> IO HErr_t) Source #
h5e_push2 :: HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> [Arg] -> IO HErr_t Source #
Pushes a new error record onto error stack for the current
thread. The error has major and minor IDs maj_id
and
min_id
, the name of a function where the error was detected,
the name of the file where the error was detected, the
line within that file, and an error description string. The
function name, file name, and error description strings must
be statically allocated.
Returns non-negative on success/Negative on failure.
herr_t H5Epush2(hid_t err_stack, const char *file, const char *func, unsigned line, hid_t cls_id, hid_t maj_id, hid_t min_id, const char *msg, ...);
(msg is a printf format string, the varargs are the format parameters)
h5e_push2_no_varargs :: HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> IO HErr_t Source #
p_H5Epush2 :: FunPtr (HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> IO HErr_t) Source #
h5e_pop :: HId_t -> CSize -> IO HErr_t Source #
Deletes some error messages from the top of error stack.
Returns non-negative value on success / negative on failure
herr_t H5Epop(hid_t err_stack, size_t count);
h5e_print2 :: HId_t -> InOut CFile -> IO HErr_t Source #
Prints the error stack in some default way. This is just a
convenience function for h5e_walk
with a function that
prints error messages. Users are encouraged to write their
own more specific error handlers.
Returns non-negative on success / negative on failure
herr_t H5Eprint2(hid_t err_stack, FILE *stream);
h5e_walk2 :: HId_t -> H5E_direction_t -> H5E_walk2_t a -> InOut a -> IO HErr_t Source #
Walks the error stack for the current thread and calls some function for each error along the way.
Returns non-negative on success / negative on failure
herr_t H5Ewalk2(hid_t err_stack, H5E_direction_t direction, H5E_walk2_t func, void *client_data);
p_H5Ewalk2 :: FunPtr (HId_t -> H5E_direction_t -> H5E_walk2_t a -> InOut a -> IO HErr_t) Source #
h5e_get_auto2 :: HId_t -> Out (H5E_auto2_t a) -> Out (InOut a) -> IO HErr_t Source #
Returns the current settings for the automatic error stack traversal function and its data for specific error stack. Either (or both) arguments may be null in which case the value is not returned.
Returns non-negative on success / negative on failure
herr_t H5Eget_auto2(hid_t estack_id, H5E_auto2_t *func, void **client_data);
NB: the a
type here should be existentially quantified, not universally, but
Haskell doesn't have a convenient way to say so in a foreign import.
p_H5Eget_auto2 :: FunPtr (HId_t -> Out (H5E_auto2_t a) -> Out (InOut a) -> IO HErr_t) Source #
h5e_set_auto2 :: HId_t -> H5E_auto2_t a -> InOut a -> IO HErr_t Source #
Turns on or off automatic printing of errors for certain
error stack. When turned on (non-null func
pointer) any
API function which returns an error indication will first
call func
passing it client_data
as an argument.
The default values before this function is called are
h5e_print2
with client data being the standard error stream,
stderr
.
Automatic stack traversal is always in the h5e_WALK_DOWNWARD
direction.
herr_t H5Eset_auto2(hid_t estack_id, H5E_auto2_t func, void *client_data);
p_H5Eset_auto2 :: FunPtr (HId_t -> H5E_auto2_t a -> InOut a -> IO HErr_t) Source #
h5e_clear2 :: HId_t -> IO HErr_t Source #
Clears the error stack for the specified error stack.
Returns non-negative value on success / negative on failure
herr_t H5Eclear2(hid_t err_stack);
p_H5Eclear2 :: FunPtr (HId_t -> IO HErr_t) Source #
h5e_auto_is_v2 :: HId_t -> Out CUInt -> IO HErr_t Source #
Determines if the error auto reporting function for an
error stack conforms to the H5E_auto_stack_t
typedef
or the H5E_auto_t
typedef. The is_stack
parameter is set
to 1 for the first case and 0 for the latter case.
Returns non-negative on success / negative on failure
herr_t H5Eauto_is_v2(hid_t err_stack, unsigned *is_stack);
h5e_get_msg :: HId_t -> Out H5E_type_t -> OutArray CChar -> CSize -> IO CSSize Source #
Retrieves an error message.
Returns non-negative for message length if succeeds(zero means no message); otherwise returns negative value.
ssize_t H5Eget_msg(hid_t msg_id, H5E_type_t *type, char *msg, size_t size);
p_H5Eget_msg :: FunPtr (HId_t -> Out H5E_type_t -> OutArray CChar -> CSize -> IO CSSize) Source #
h5e_get_num :: HId_t -> IO CSSize Source #
Retrieves the number of error message.
Returns non-negative value on success / negative on failure
ssize_t H5Eget_num(hid_t error_stack_id);
p_H5Eget_num :: FunPtr (HId_t -> IO CSSize) Source #
Deprecated symbols
newtype H5E_major_t Source #
Constructors
H5E_major_t Int64 |
Instances
Storable H5E_major_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods sizeOf :: H5E_major_t -> Int alignment :: H5E_major_t -> Int peekElemOff :: Ptr H5E_major_t -> Int -> IO H5E_major_t pokeElemOff :: Ptr H5E_major_t -> Int -> H5E_major_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5E_major_t pokeByteOff :: Ptr b -> Int -> H5E_major_t -> IO () peek :: Ptr H5E_major_t -> IO H5E_major_t poke :: Ptr H5E_major_t -> H5E_major_t -> IO () | |
Show H5E_major_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods showsPrec :: Int -> H5E_major_t -> ShowS show :: H5E_major_t -> String showList :: [H5E_major_t] -> ShowS | |
Eq H5E_major_t Source # | |
Defined in Bindings.HDF5.Raw.H5E |
newtype H5E_minor_t Source #
Constructors
H5E_minor_t Int64 |
Instances
Storable H5E_minor_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods sizeOf :: H5E_minor_t -> Int alignment :: H5E_minor_t -> Int peekElemOff :: Ptr H5E_minor_t -> Int -> IO H5E_minor_t pokeElemOff :: Ptr H5E_minor_t -> Int -> H5E_minor_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5E_minor_t pokeByteOff :: Ptr b -> Int -> H5E_minor_t -> IO () peek :: Ptr H5E_minor_t -> IO H5E_minor_t poke :: Ptr H5E_minor_t -> H5E_minor_t -> IO () | |
Show H5E_minor_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods showsPrec :: Int -> H5E_minor_t -> ShowS show :: H5E_minor_t -> String showList :: [H5E_minor_t] -> ShowS | |
Eq H5E_minor_t Source # | |
Defined in Bindings.HDF5.Raw.H5E |
data H5E_error1_t Source #
Information about an error element of error stack
major error number
minor error number
function in which error occurred
file in which error occurred
line in file where error occurs
optional supplied description
Constructors
H5E_error1_t | |
Fields
|
Instances
Storable H5E_error1_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods sizeOf :: H5E_error1_t -> Int alignment :: H5E_error1_t -> Int peekElemOff :: Ptr H5E_error1_t -> Int -> IO H5E_error1_t pokeElemOff :: Ptr H5E_error1_t -> Int -> H5E_error1_t -> IO () peekByteOff :: Ptr b -> Int -> IO H5E_error1_t pokeByteOff :: Ptr b -> Int -> H5E_error1_t -> IO () peek :: Ptr H5E_error1_t -> IO H5E_error1_t poke :: Ptr H5E_error1_t -> H5E_error1_t -> IO () | |
Show H5E_error1_t Source # | |
Defined in Bindings.HDF5.Raw.H5E Methods showsPrec :: Int -> H5E_error1_t -> ShowS show :: H5E_error1_t -> String showList :: [H5E_error1_t] -> ShowS | |
Eq H5E_error1_t Source # | |
Defined in Bindings.HDF5.Raw.H5E |
type H5E_walk1_t a = FunPtr (CInt -> In H5E_error1_t -> InOut a -> IO HErr_t) Source #
Callback type for h5e_walk1
typedef herr_t (*H5E_walk1_t)(int n, H5E_error1_t *err_desc, void *client_data);
p'H5E_error1_t'maj_num :: Ptr H5E_error1_t -> Ptr H5E_major_t Source #
Callback type for h5e_set_auto1
typedef herr_t (*H5E_auto1_t)(void *client_data);
type H5E_auto1_t a = FunPtr (InOut a -> IO HErr_t) Source #
p'H5E_error1_t'min_num :: Ptr H5E_error1_t -> Ptr H5E_minor_t Source #
Function prototypes
p'H5E_error1_t'func_name :: Ptr H5E_error1_t -> Ptr CString Source #
p'H5E_error1_t'file_name :: Ptr H5E_error1_t -> Ptr CString Source #
p'H5E_error1_t'line :: Ptr H5E_error1_t -> Ptr CUInt Source #
This function is for backward compatbility. Clears the error stack for the specified error stack.
Returns non-negative on success / negative on failure
herr_t H5Eclear1(void);
p'H5E_error1_t'desc :: Ptr H5E_error1_t -> Ptr CString Source #
h5e_clear1 :: IO HErr_t Source #
p_H5Eclear1 :: FunPtr (IO HErr_t) Source #
h5e_get_auto1 :: Out (H5E_auto1_t a) -> Out (InOut a) -> IO HErr_t Source #
This function is for backward compatbility. Returns the current settings for the automatic error stack traversal function and its data for specific error stack. Either (or both) arguments may be null in which case the value is not returned.
Returns non-negative on success / negative on failure
herr_t H5Eget_auto1(H5E_auto1_t *func, void **client_data);
NB: the a
type here should be existentially quantified, not universally, but
Haskell doesn't have a convenient way to say so in a foreign import.
p_H5Eget_auto1 :: FunPtr (Out (H5E_auto1_t a) -> Out (InOut a) -> IO HErr_t) Source #
h5e_push1 :: CString -> CString -> CUInt -> H5E_major_t -> H5E_minor_t -> CString -> IO HErr_t Source #
This function definition is for backward compatibility only. It doesn't have error stack and error class as parameters. The old definition of major and minor is casted as HID_T in H5Epublic.h
Returns non-negative on success / negative on failure
herr_t H5Epush1(const char *file, const char *func, unsigned line, H5E_major_t maj, H5E_minor_t min, const char *str);
p_H5Epush1 :: FunPtr (CString -> CString -> CUInt -> H5E_major_t -> H5E_minor_t -> CString -> IO HErr_t) Source #
h5e_print1 :: InOut CFile -> IO HErr_t Source #
This function is for backward compatbility.
Prints the error stack in some default way. This is just a
convenience function for h5e_walk1
with a function that
prints error messages. Users are encouraged to write there
own more specific error handlers.
Returns non-negative on success / negative on failure
herr_t H5Eprint1(FILE *stream);
NB: The first parameter is declared as InOut
to match H5E_auto1_t
,
but I'm quite sure it never modifies the passed value.
p_H5Eprint1 :: FunPtr (InOut CFile -> IO HErr_t) Source #
h5e_set_auto1 :: H5E_auto1_t a -> InOut a -> IO HErr_t Source #
This function is for backward compatbility.
Turns on or off automatic printing of errors for certain
error stack. When turned on (non-null func
pointer) any
API function which returns an error indication will first
call func
passing it client_data
as an argument.
The default values before this function is called are
h5e_print1
with client data being the standard error stream,
stderr
.
Automatic stack traversal is always in the h5e_WALK_DOWNWARD
direction.
Returns non-negative on success / negative on failure
herr_t H5Eset_auto1(H5E_auto1_t func, void *client_data);
p_H5Eset_auto1 :: FunPtr (H5E_auto1_t a -> InOut a -> IO HErr_t) Source #
h5e_walk1 :: H5E_direction_t -> H5E_walk1_t a -> InOut a -> IO HErr_t Source #
This function is for backward compatbility. Walks the error stack for the current thread and calls some function for each error along the way.
Returns non-negative on success / negative on failure
herr_t H5Ewalk1(H5E_direction_t direction, H5E_walk1_t func, void *client_data);
p_H5Ewalk1 :: FunPtr (H5E_direction_t -> H5E_walk1_t a -> InOut a -> IO HErr_t) Source #
h5e_get_major :: H5E_major_t -> IO CString Source #
Retrieves a major error message.
Returns message if succeeds, otherwise returns NULL.
char *H5Eget_major(H5E_major_t maj);
p_H5Eget_major :: FunPtr (H5E_major_t -> IO CString) Source #
h5e_get_minor :: H5E_minor_t -> IO CString Source #
Retrieves a minor error message.
Returns message if succeeds, otherwise returns NULL.
char *H5Eget_minor(H5E_minor_t min);
p_H5Eget_minor :: FunPtr (H5E_minor_t -> IO CString) Source #