module Codec.Archive.LibZip.Errors
( errFromCInt
, get_error
, get_file_error
, catchZipError
) where
import Data.Typeable (Typeable, typeOf)
import Foreign.C.Types
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr (nullPtr)
import Foreign.Storable (peek)
import qualified Control.Exception as E
import Codec.Archive.LibZip.LowLevel
import Codec.Archive.LibZip.Types
errFromCInt :: CInt -> ZipError
errFromCInt = toEnum . fromEnum
get_error :: Zip -> IO ZipError
get_error z | z == nullPtr = E.throwIO ErrINVAL
get_error z = alloca $ \zep -> do
c'zip_error_get z zep nullPtr
peek zep >>= return . errFromCInt
get_file_error :: ZipFile -> IO ZipError
get_file_error zf
| zf == nullPtr = E.throwIO ErrINVAL
| otherwise = alloca $ \zep -> do
c'zip_file_error_get zf zep nullPtr
peek zep >>= return . errFromCInt
catchZipError :: IO a -> (ZipError -> IO a) -> IO a
catchZipError f h = E.catchJust ifZipError f h
where
ifZipError :: (Typeable e, E.Exception e) => e -> Maybe e
ifZipError x | typeOf x == typeOf ErrOK = Just x
ifZipError _ | otherwise = Nothing