#include #include module Bindings.HDF5.Raw.H5E where import Data.Int import Data.Word import Foreign.C.String import Foreign.C.Types import Foreign.Marshal.Alloc import Control.Monad import Foreign.Ptr import Foreign.Storable import Foreign.LibFFI import Bindings.HDF5.Raw.H5 import Bindings.HDF5.Raw.H5I import Foreign.Ptr.Conventions -- |Value for the default error stack #newtype_const hid_t, H5E_DEFAULT -- |Different kinds of error information #newtype H5E_type_t #newtype_const H5E_type_t, H5E_MAJOR #newtype_const H5E_type_t, H5E_MINOR -- |Information about an error; element of error stack #starttype H5E_error2_t -- | class ID #field cls_id, -- | major error ID #field maj_num, -- | minor error number #field min_num, -- | line in file where error occurs #field line, CUInt -- | function in which error occurred #field func_name, CString -- | file in which error occurred #field file_name, CString -- | optional supplied description #field desc, CString #stoptype -- |HDF5 error class #cinline H5E_ERR_CLS, -- * Major error codes -- |Dataset #cinline H5E_DATASET, -- |Function entry/exit #cinline H5E_FUNC, -- |Data storage #cinline H5E_STORAGE, -- |File accessibility #cinline H5E_FILE, -- |Shared Object Header Messages #cinline H5E_SOHM, -- |Symbol table #cinline H5E_SYM, #if H5_VERSION_GE(1,8,11) -- |Plugin for dynamically loaded library #cinline H5E_PLUGIN, #endif /* H5_VERSION_GE */ -- |Virtual File Layer #cinline H5E_VFL, -- |Internal error (too specific to document in detail) #cinline H5E_INTERNAL, -- |B-Tree node #cinline H5E_BTREE, -- |References #cinline H5E_REFERENCE, -- |Dataspace #cinline H5E_DATASPACE, -- |Resource unavailable #cinline H5E_RESOURCE, -- |Property lists #cinline H5E_PLIST, -- |Links #cinline H5E_LINK, -- |Datatype #cinline H5E_DATATYPE, -- |Reference Counted Strings #cinline H5E_RS, -- |Heap #cinline H5E_HEAP, -- |Object header #cinline H5E_OHDR, -- |Object atom #cinline H5E_ATOM, -- |Attribute #cinline H5E_ATTR, -- |No error #cinline H5E_NONE_MAJOR, -- |Low-level I/O #cinline H5E_IO, -- |Skip Lists #cinline H5E_SLIST, -- |External file list #cinline H5E_EFL, -- |Ternary Search Trees #cinline H5E_TST, -- |Invalid arguments to routine #cinline H5E_ARGS, -- |Error API #cinline H5E_ERROR, -- |Data filters #cinline H5E_PLINE, -- |Free Space Manager #cinline H5E_FSPACE, -- |Object cache #cinline H5E_CACHE, -- * Minor error codes -- ** Generic low-level file I/O errors -- |Seek failed #cinline H5E_SEEKERROR, -- |Read failed #cinline H5E_READERROR, -- |Write failed #cinline H5E_WRITEERROR, -- |Close failed #cinline H5E_CLOSEERROR, -- |Address overflowed #cinline H5E_OVERFLOW, -- |File control (fcntl) failed #cinline H5E_FCNTL, -- ** Resource errors -- |No space available for allocation #cinline H5E_NOSPACE, -- |Can't allocate space #cinline H5E_CANTALLOC, -- |Unable to copy object #cinline H5E_CANTCOPY, -- |Unable to free object #cinline H5E_CANTFREE, -- |Object already exists #cinline H5E_ALREADYEXISTS, -- |Unable to lock object #cinline H5E_CANTLOCK, -- |Unable to unlock object #cinline H5E_CANTUNLOCK, -- |Unable to garbage collect #cinline H5E_CANTGC, -- |Unable to compute size #cinline H5E_CANTGETSIZE, -- |Object is already open #cinline H5E_OBJOPEN, -- ** Heap errors #cinline H5E_CANTRESTORE, #cinline H5E_CANTCOMPUTE, #cinline H5E_CANTEXTEND, #cinline H5E_CANTATTACH, #cinline H5E_CANTUPDATE, #cinline H5E_CANTOPERATE, -- ** Function entry/exit interface errors #cinline H5E_CANTINIT, #cinline H5E_ALREADYINIT, #cinline H5E_CANTRELEASE, -- ** Property list errors #cinline H5E_CANTGET, #cinline H5E_CANTSET, #cinline H5E_DUPCLASS, #if H5_VERSION_GE(1,8,9) #cinline H5E_SETDISALLOWED, #endif -- ** Free space errors #cinline H5E_CANTMERGE, #cinline H5E_CANTREVIVE, #cinline H5E_CANTSHRINK, -- ** Object header related errors #cinline H5E_LINKCOUNT, #cinline H5E_VERSION, #cinline H5E_ALIGNMENT, #cinline H5E_BADMESG, #cinline H5E_CANTDELETE, #cinline H5E_BADITER, #cinline H5E_CANTPACK, #cinline H5E_CANTRESET, #cinline H5E_CANTRENAME, -- ** System level errors #cinline H5E_SYSERRSTR, -- ** I/O pipeline errors #cinline H5E_NOFILTER, #cinline H5E_CALLBACK, #cinline H5E_CANAPPLY, #cinline H5E_SETLOCAL, #cinline H5E_NOENCODER, #cinline H5E_CANTFILTER, -- ** Group related errors #cinline H5E_CANTOPENOBJ, #cinline H5E_CANTCLOSEOBJ, #cinline H5E_COMPLEN, #cinline H5E_PATH, -- ** No error #cinline H5E_NONE_MINOR, #if H5_VERSION_GE(1,8,11) -- ** Plugin errors #cinline H5E_OPENERROR, #endif /* H5_VERSION_GE */ -- ** File accessibility errors #cinline H5E_FILEEXISTS, #cinline H5E_FILEOPEN, #cinline H5E_CANTCREATE, #cinline H5E_CANTOPENFILE, #cinline H5E_CANTCLOSEFILE, #cinline H5E_NOTHDF5, #cinline H5E_BADFILE, #cinline H5E_TRUNCATED, #cinline H5E_MOUNT, -- ** Object atom related errors #cinline H5E_BADATOM, #cinline H5E_BADGROUP, #cinline H5E_CANTREGISTER, #cinline H5E_CANTINC, #cinline H5E_CANTDEC, #cinline H5E_NOIDS, -- ** Cache related errors #cinline H5E_CANTFLUSH, #cinline H5E_CANTSERIALIZE, #cinline H5E_CANTLOAD, #cinline H5E_PROTECT, #cinline H5E_NOTCACHED, #cinline H5E_SYSTEM, #cinline H5E_CANTINS, #cinline H5E_CANTPROTECT, #cinline H5E_CANTUNPROTECT, #cinline H5E_CANTPIN, #cinline H5E_CANTUNPIN, #cinline H5E_CANTMARKDIRTY, #cinline H5E_CANTDIRTY, #cinline H5E_CANTEXPUNGE, #cinline H5E_CANTRESIZE, -- ** Link related errors #cinline H5E_TRAVERSE, #cinline H5E_NLINKS, #cinline H5E_NOTREGISTERED, #cinline H5E_CANTMOVE, #cinline H5E_CANTSORT, -- ** Parallel MPI errors #cinline H5E_MPI, #cinline H5E_MPIERRSTR, #cinline H5E_CANTRECV, -- ** Dataspace errors #cinline H5E_CANTCLIP, #cinline H5E_CANTCOUNT, #cinline H5E_CANTSELECT, #cinline H5E_CANTNEXT, #cinline H5E_BADSELECT, #cinline H5E_CANTCOMPARE, -- ** Argument errors #cinline H5E_UNINITIALIZED, #cinline H5E_UNSUPPORTED, #cinline H5E_BADTYPE, #cinline H5E_BADRANGE, #cinline H5E_BADVALUE, -- ** B-tree related errors #cinline H5E_NOTFOUND, #cinline H5E_EXISTS, #cinline H5E_CANTENCODE, #cinline H5E_CANTDECODE, #cinline H5E_CANTSPLIT, #cinline H5E_CANTREDISTRIBUTE, #cinline H5E_CANTSWAP, #cinline H5E_CANTINSERT, #cinline H5E_CANTLIST, #cinline H5E_CANTMODIFY, #cinline H5E_CANTREMOVE, -- ** Datatype conversion errors #cinline H5E_CANTCONVERT, #cinline H5E_BADSIZE, newtype H5E_TRY_STATE = H5E_TRY_STATE (Either (H5E_auto1_t ()) (H5E_auto2_t ()), InOut ()) h5e_BEGIN_TRY :: IO H5E_TRY_STATE h5e_BEGIN_TRY = do isV2 <- alloca $ \isV2 -> do void $ h5e_auto_is_v2 h5e_DEFAULT (Out isV2) peek isV2 alloca $ \cdata -> if isV2 /= 0 then alloca $ \func -> do void $ h5e_get_auto2 h5e_DEFAULT (Out func) (Out cdata) void $ h5e_set_auto2 h5e_DEFAULT nullFunPtr (InOut nullPtr) func_ <- peek func cdata_ <- peek cdata return (H5E_TRY_STATE (Right func_, cdata_)) else alloca $ \func -> do void $ h5e_get_auto1 (Out func) (Out cdata) void $ h5e_set_auto1 nullFunPtr (InOut nullPtr) func_ <- peek func cdata_ <- peek cdata return (H5E_TRY_STATE (Left func_, cdata_)) h5e_END_TRY :: H5E_TRY_STATE -> IO HErr_t h5e_END_TRY (H5E_TRY_STATE (Right func, cdata)) = h5e_set_auto2 h5e_DEFAULT func cdata h5e_END_TRY (H5E_TRY_STATE (Left func, cdata)) = h5e_set_auto1 func cdata -- |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. h5e_try :: IO a -> IO a h5e_try action = do tryState <- h5e_BEGIN_TRY result <- action void $ h5e_END_TRY tryState return result -- TODO: wrap these up in an exported header file (something like "Bindings.HDF5.Raw.H5E.h") as macros for use in haskell code, or maybe as TH macros -- /* -- * Public API Convenience Macros for Error reporting - Documented -- */ -- /* Use the Standard C __FILE__ & __LINE__ macros instead of typing them in */ -- #define H5Epush_sim(func, cls, maj, min, str) H5Epush2(H5E_DEFAULT, __FILE__, func, __LINE__, cls, maj, min, str) -- -- /* -- * Public API Convenience Macros for Error reporting - Undocumented -- */ -- /* Use the Standard C __FILE__ & __LINE__ macros instead of typing them in */ -- /* And return after pushing error onto stack */ -- #define H5Epush_ret(func, cls, maj, min, str, ret) { \ -- H5Epush2(H5E_DEFAULT, __FILE__, func, __LINE__, cls, maj, min, str); \ -- return(ret); \ -- } -- -- /* Use the Standard C __FILE__ & __LINE__ macros instead of typing them in -- * And goto a label after pushing error onto stack. -- */ -- #define H5Epush_goto(func, cls, maj, min, str, label) { \ -- H5Epush2(H5E_DEFAULT, __FILE__, func, __LINE__, cls, maj, min, str); \ -- goto label; \ -- } -- |Error stack traversal direction #newtype H5E_direction_t -- |begin deep, end at API function #newtype_const H5E_direction_t, H5E_WALK_UPWARD -- |begin at API function, end deep #newtype_const H5E_direction_t, H5E_WALK_DOWNWARD -- * Error stack traversal callback function types -- |Callback type for 'h5e_walk2' -- -- > typedef herr_t (*H5E_walk2_t)(unsigned n, const H5E_error2_t *err_desc, -- > void *client_data); type H5E_walk2_t a = FunPtr (CUInt -> In H5E_error2_t -> InOut a -> IO HErr_t) -- |Callback type for 'h5e_set_auto2' -- -- > typedef herr_t (*H5E_auto2_t)(hid_t estack, void *client_data); type H5E_auto2_t a = FunPtr (HId_t -> InOut a -> IO HErr_t) -- * Public API functions -- |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); #ccall H5Eregister_class, CString -> CString -> CString -> IO -- |Closes an error class. -- -- Returns non-negative value on success / negative on failure -- -- > herr_t H5Eunregister_class(hid_t class_id); #ccall H5Eunregister_class, -> IO -- |Closes a major or minor error. -- -- Returns non-negative value on success / negative on failure -- -- > herr_t H5Eclose_msg(hid_t err_id); #ccall H5Eclose_msg, -> IO -- |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); #ccall H5Ecreate_msg, -> H5E_type_t -> CString -> IO -- |Creates a new, empty, error stack. -- -- Returns non-negative value as stack ID on success / negative on failure -- -- > hid_t H5Ecreate_stack(void); #ccall H5Ecreate_stack, IO -- |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); #ccall H5Eget_current_stack, IO -- |Closes an error stack. -- -- Returns non-negative value on success / negative on failure -- -- > herr_t H5Eclose_stack(hid_t stack_id); #ccall H5Eclose_stack, -> IO -- |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); #ccall H5Eget_class_name, -> OutArray CChar -> -> IO -- |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); #ccall H5Eset_current_stack, -> IO -- libffi to the rescue! I have no idea how I'd wrap this without it, and there -- doesn't appear to be a non-deprecated non-private non-varargs equivalent. -- -- |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 :: HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> [Arg] -> IO HErr_t h5e_push2 err_stack file func line cls_id maj_id min_id fmt [] = h5e_push2_no_varargs err_stack file func line cls_id maj_id min_id fmt h5e_push2 (HId_t err_stack) file func line (HId_t cls_id) (HId_t maj_id) (HId_t min_id) fmt varargs = callFFI p_H5Epush2 retHErr_t args where argHId_t = arg#type hid_t retHErr_t = fmap HErr_t (ret#type herr_t) args = argHId_t err_stack : argPtr file : argPtr func : argCUInt line : argHId_t cls_id : argHId_t maj_id : argHId_t min_id : argPtr fmt : varargs foreign import ccall "H5Epush2" h5e_push2_no_varargs :: HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> IO HErr_t foreign import ccall "&H5Epush2" p_H5Epush2 :: FunPtr (HId_t -> CString -> CString -> CUInt -> HId_t -> HId_t -> HId_t -> CString -> IO HErr_t) -- |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); #ccall H5Epop, -> -> IO -- |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); #ccall H5Eprint2, -> InOut CFile -> IO -- |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); #ccall H5Ewalk2, -> -> H5E_walk2_t a -> InOut a -> IO -- |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. #ccall H5Eget_auto2, -> Out (H5E_auto2_t a) -> Out (InOut a) -> IO -- |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); #ccall H5Eset_auto2, -> H5E_auto2_t a -> InOut a -> IO -- |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); #ccall H5Eclear2, -> IO -- TODO: I think the type names mentioned here are wrong. Sort them out. -- |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); #ccall H5Eauto_is_v2, -> Out CUInt -> IO -- |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); #ccall H5Eget_msg, -> Out -> OutArray CChar -> -> IO -- |Retrieves the number of error message. -- -- Returns non-negative value on success / negative on failure -- -- > ssize_t H5Eget_num(hid_t error_stack_id); #ccall H5Eget_num, -> IO #ifndef H5_NO_DEPRECATED_SYMBOLS -- * Deprecated symbols #newtype H5E_major_t, Eq #newtype H5E_minor_t, Eq -- | Information about an error element of error stack #starttype H5E_error1_t -- |major error number #field maj_num, -- |minor error number #field min_num, -- |function in which error occurred #field func_name, CString -- |file in which error occurred #field file_name, CString -- |line in file where error occurs #field line, CUInt -- |optional supplied description #field desc, CString #stoptype -- | Callback type for 'h5e_walk1' -- -- > typedef herr_t (*H5E_walk1_t)(int n, H5E_error1_t *err_desc, void *client_data); type H5E_walk1_t a = FunPtr (CInt -> In H5E_error1_t -> InOut a -> IO HErr_t) -- | 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) -- ** Function prototypes -- |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); #ccall H5Eclear1, IO -- |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. #ccall H5Eget_auto1, Out (H5E_auto1_t a) -> Out (InOut a) -> IO -- |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); #ccall H5Epush1, CString -> CString -> CUInt -> -> -> CString -> IO -- |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. #ccall H5Eprint1, InOut CFile -> IO -- |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); #ccall H5Eset_auto1, H5E_auto1_t a -> InOut a -> IO -- |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); #ccall H5Ewalk1, H5E_direction_t -> H5E_walk1_t a -> InOut a -> IO -- |Retrieves a major error message. -- -- Returns message if succeeds, otherwise returns NULL. -- -- > char *H5Eget_major(H5E_major_t maj); #ccall H5Eget_major, -> IO CString -- |Retrieves a minor error message. -- -- Returns message if succeeds, otherwise returns NULL. -- -- > char *H5Eget_minor(H5E_minor_t min); #ccall H5Eget_minor, -> IO CString #endif /* H5_NO_DEPRECATED_SYMBOLS */