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

Bindings.HDF5.Raw.H5E

Synopsis

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

Instances details
Storable H5E_type_t Source # 
Instance details

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 # 
Instance details

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

Instances

Instances details
Storable H5E_error2_t Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Bindings.HDF5.Raw.H5E

Methods

(==) :: H5E_error2_t -> H5E_error2_t -> Bool

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

h5e_ERR_CLS :: HId_t Source #

HDF5 error class

Major error codes

p'H5E_error2_t'cls_id :: Ptr H5E_error2_t -> Ptr HId_t Source #

Function entry/exit

p'H5E_error2_t'line :: Ptr H5E_error2_t -> Ptr CUInt Source #

File accessibility

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_VFL :: HId_t Source #

Virtual File Layer

h5e_INTERNAL :: HId_t Source #

Internal error (too specific to document in detail)

h5e_BTREE :: HId_t Source #

B-Tree node

h5e_RESOURCE :: HId_t Source #

Resource unavailable

h5e_PLIST :: HId_t Source #

Property lists

h5e_RS :: HId_t Source #

Reference Counted Strings

h5e_OHDR :: HId_t Source #

Object header

h5e_ATTR :: HId_t Source #

Attribute

h5e_IO :: HId_t Source #

Low-level I/O

h5e_SLIST :: HId_t Source #

Skip Lists

h5e_EFL :: HId_t Source #

External file list

h5e_TST :: HId_t Source #

Ternary Search Trees

h5e_ARGS :: HId_t Source #

Invalid arguments to routine

h5e_ERROR :: HId_t Source #

Error API

h5e_PLINE :: HId_t Source #

Data filters

h5e_FSPACE :: HId_t Source #

Free Space Manager

h5e_CACHE :: HId_t Source #

Object cache

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

h5e_FCNTL :: HId_t Source #

File control (fcntl) failed

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

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

newtype H5E_TRY_STATE Source #

Constructors

H5E_TRY_STATE (Either (H5E_auto1_t ()) (H5E_auto2_t ()), InOut ()) 

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

Instances details
Storable H5E_direction_t Source # 
Instance details

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 # 
Instance details

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);

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);

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);

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);

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);

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

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);

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);

p_H5Epop :: FunPtr (HId_t -> CSize -> IO HErr_t) Source #

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);

p_H5Eprint2 :: FunPtr (HId_t -> InOut CFile -> IO HErr_t) Source #

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);

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);

p_H5Eauto_is_v2 :: FunPtr (HId_t -> Out CUInt -> IO HErr_t) Source #

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

Instances details
Storable H5E_major_t Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Bindings.HDF5.Raw.H5E

Methods

(==) :: H5E_major_t -> H5E_major_t -> Bool

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

newtype H5E_minor_t Source #

Constructors

H5E_minor_t Int64 

Instances

Instances details
Storable H5E_minor_t Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Bindings.HDF5.Raw.H5E

Methods

(==) :: H5E_minor_t -> H5E_minor_t -> Bool

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

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

Instances

Instances details
Storable H5E_error1_t Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Bindings.HDF5.Raw.H5E

Methods

(==) :: H5E_error1_t -> H5E_error1_t -> Bool

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

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 #

Function prototypes

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_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);

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 #