{-# LANGUAGE CPP, ForeignFunctionInterface #-} {-# OPTIONS_GHC -Wall #-} module Foreign.C.Error.Errno (withErrno,withErrnoPred) where import Control.Monad.Error import Foreign.C.Error import Foreign.C.String import Foreign.C.Types #include getErrorString :: IO String getErrorString = do (Errno i) <- getErrno s <- errorString i peekCString s withErrno :: (Integral a, MonadIO m) => m a -> ErrorT String m a withErrno = withErrnoPred (==(-1)) withErrnoPred :: (Integral a, MonadIO m) => (a -> Bool) -> m a -> ErrorT String m a withErrnoPred f m = do i <- lift m if f i then do msg <- liftIO getErrorString throwError msg else return i foreign import ccall "errno.h strerror" errorString :: CInt -> IO CString