module Z.IO.Exception
  ( 
    SomeIOException(..)
  , ioExceptionToException
  , ioExceptionFromException
    
  , IOEInfo(..)
  , AlreadyExists(..)
  , NoSuchThing(..)
  , ResourceBusy(..)
  , ResourceExhausted(..)
  , EOF(..)
  , IllegalOperation(..)
  , PermissionDenied(..)
  , UnsatisfiedConstraints(..)
  , SystemError(..)
  , ProtocolError(..)
  , OtherError(..)
  , InvalidArgument(..)
  , InappropriateType(..)
  , HardwareFault(..)
  , UnsupportedOperation(..)
  , TimeExpired(..)
  , ResourceVanished(..)
  , Interrupted(..)
    
  , throwOOMIfNull
  , throwUVIfMinus
  , throwUVIfMinus_
  , throwECLOSED
  , throwECLOSEDSTM
  , throwUVError
    
  , module Control.Exception
  , HasCallStack
  , CallStack
  , callStack
  , module Z.IO.UV.Errno
  ) where
import Control.Exception hiding (IOException)
import Control.Monad
import Control.Concurrent.STM
import Data.Typeable
import Foreign.Ptr
import Foreign.C.Types
import GHC.Stack
import Z.IO.UV.Errno
import qualified Z.Data.Text       as T
import qualified Z.Data.Text.ShowT as T
data SomeIOException = forall e . Exception e => SomeIOException e
    deriving Typeable
instance Show SomeIOException where
    show :: SomeIOException -> String
show (SomeIOException e
e) = e -> String
forall a. Show a => a -> String
show e
e
instance Exception SomeIOException
ioExceptionToException :: Exception e => e -> SomeException
ioExceptionToException :: e -> SomeException
ioExceptionToException = SomeIOException -> SomeException
forall e. Exception e => e -> SomeException
toException (SomeIOException -> SomeException)
-> (e -> SomeIOException) -> e -> SomeException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> SomeIOException
forall e. Exception e => e -> SomeIOException
SomeIOException
ioExceptionFromException :: Exception e => SomeException -> Maybe e
ioExceptionFromException :: SomeException -> Maybe e
ioExceptionFromException SomeException
x = do
    SomeIOException e
a <- SomeException -> Maybe SomeIOException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
x
    e -> Maybe e
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast e
a
#define IOE(e) data e = e IOEInfo deriving (Show, Typeable);  \
               instance Exception e where                     \
                   { toException = ioExceptionToException     \
                   ; fromException = ioExceptionFromException \
                   }
IOE(AlreadyExists)
IOE(NoSuchThing)
IOE(ResourceBusy)
IOE(ResourceExhausted)
IOE(EOF)
IOE(IllegalOperation)
IOE(PermissionDenied)
IOE(UnsatisfiedConstraints)
IOE(SystemError)
IOE(ProtocolError)
IOE(OtherError)
IOE(InvalidArgument)
IOE(InappropriateType)
IOE(HardwareFault)
IOE(UnsupportedOperation)
IOE(TimeExpired)
IOE(ResourceVanished)
IOE(Interrupted)
throwOOMIfNull :: HasCallStack
               => IO (Ptr a)    
               -> IO (Ptr a)
{-# INLINABLE throwOOMIfNull #-}
throwOOMIfNull :: IO (Ptr a) -> IO (Ptr a)
throwOOMIfNull IO (Ptr a)
f = do
    Ptr a
addr <- IO (Ptr a)
f
    if Ptr a
addr Ptr a -> Ptr a -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr a
forall a. Ptr a
nullPtr
        then ResourceExhausted -> IO (Ptr a)
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
"OOM" Text
"out of memory when doing allocation" CallStack
HasCallStack => CallStack
callStack))
        else Ptr a -> IO (Ptr a)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr a
addr
throwUVIfMinus :: (HasCallStack, Integral a)
               => IO a    
               -> IO a
{-# INLINABLE throwUVIfMinus #-}
throwUVIfMinus :: IO a -> IO a
throwUVIfMinus IO a
f = do
    a
errno <- IO a
f
    let errno' :: CInt
errno' = a -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
errno
    if CInt
errno' CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0
        then do
            Text
name <- CInt -> IO Text
uvErrName CInt
errno'
            Text
desc <- CInt -> IO Text
uvStdError CInt
errno'
            CInt -> IOEInfo -> IO a
forall a. CInt -> IOEInfo -> IO a
throwUVError CInt
errno' (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
name Text
desc CallStack
HasCallStack => CallStack
callStack)
        else a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
errno
throwUVIfMinus_ :: (HasCallStack, Integral a)
                => IO a    
                -> IO ()
{-# INLINABLE throwUVIfMinus_ #-}
throwUVIfMinus_ :: IO a -> IO ()
throwUVIfMinus_ IO a
f = do
    a
errno <- IO a
f
    let errno' :: CInt
errno' = a -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
errno
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CInt
errno' CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
< CInt
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        Text
name <- CInt -> IO Text
uvErrName CInt
errno'
        Text
desc <- CInt -> IO Text
uvStdError CInt
errno'
        CInt -> IOEInfo -> IO ()
forall a. CInt -> IOEInfo -> IO a
throwUVError CInt
errno' (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
name Text
desc CallStack
HasCallStack => CallStack
callStack)
throwECLOSED :: HasCallStack => IO a
throwECLOSED :: IO a
throwECLOSED = ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished
    (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
"ECLOSED" Text
"resource is closed" CallStack
HasCallStack => CallStack
callStack))
throwECLOSEDSTM :: HasCallStack => STM a
throwECLOSEDSTM :: STM a
throwECLOSEDSTM = ResourceVanished -> STM a
forall e a. Exception e => e -> STM a
throwSTM (IOEInfo -> ResourceVanished
ResourceVanished
    (Text -> Text -> CallStack -> IOEInfo
IOEInfo Text
"ECLOSED" Text
"resource is closed" CallStack
HasCallStack => CallStack
callStack))
data IOEInfo = IOEInfo
    { IOEInfo -> Text
ioeName        :: T.Text      
    , IOEInfo -> Text
ioeDescription :: T.Text      
    , IOEInfo -> CallStack
ioeCallStack   :: CallStack   
    }
instance Show IOEInfo where show :: IOEInfo -> String
show = IOEInfo -> String
forall a. ShowT a => a -> String
T.toString
instance T.ShowT IOEInfo where
    toUTF8BuilderP :: Int -> IOEInfo -> Builder ()
toUTF8BuilderP Int
_ (IOEInfo Text
errno Text
desc CallStack
cstack) = do
         Builder ()
"{name:"
         Text -> Builder ()
T.text Text
errno
         Builder ()
", description:"
         Text -> Builder ()
T.text Text
desc
         Builder ()
", callstack:"
         String -> Builder ()
T.stringUTF8 (CallStack -> String
prettyCallStack CallStack
cstack)
         Builder ()
"}"
throwUVError :: CInt -> IOEInfo -> IO a
throwUVError :: CInt -> IOEInfo -> IO a
throwUVError CInt
e IOEInfo
info = case CInt
e of
    CInt
UV_EOF             -> EOF -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> EOF
EOF                     IOEInfo
info)
    CInt
UV_E2BIG           -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_EACCES          -> PermissionDenied -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> PermissionDenied
PermissionDenied        IOEInfo
info)
    CInt
UV_EADDRINUSE      -> ResourceBusy -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceBusy
ResourceBusy            IOEInfo
info)
    CInt
UV_EADDRNOTAVAIL   -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAFNOSUPPORT    -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAGAIN          -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_EAI_ADDRFAMILY  -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAI_AGAIN       -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_EAI_BADFLAGS    -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAI_BADHINTS    -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAI_CANCELED    -> ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished        IOEInfo
info)
    CInt
UV_EAI_FAIL        -> OtherError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> OtherError
OtherError              IOEInfo
info)
    CInt
UV_EAI_FAMILY      -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAI_MEMORY      -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_EAI_NODATA      -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_EAI_NONAME      -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_EAI_OVERFLOW    -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_EAI_PROTOCOL    -> ProtocolError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ProtocolError
ProtocolError           IOEInfo
info)
    CInt
UV_EAI_SERVICE     -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EAI_SOCKTYPE    -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EALREADY        -> AlreadyExists -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> AlreadyExists
AlreadyExists           IOEInfo
info)
    CInt
UV_EBADF           -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_EBUSY           -> ResourceBusy -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceBusy
ResourceBusy            IOEInfo
info)
    CInt
UV_ECANCELED       -> ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished        IOEInfo
info)
    CInt
UV_ECHARSET        -> OtherError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> OtherError
OtherError              IOEInfo
info)
    CInt
UV_ECONNABORTED    -> ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished        IOEInfo
info)
    CInt
UV_ECONNREFUSED    -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_ECONNRESET      -> ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished        IOEInfo
info)
    CInt
UV_EDESTADDRREQ    -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_EEXIST          -> AlreadyExists -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> AlreadyExists
AlreadyExists           IOEInfo
info)
    CInt
UV_EFAULT          -> OtherError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> OtherError
OtherError              IOEInfo
info)
    CInt
UV_EFBIG           -> PermissionDenied -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> PermissionDenied
PermissionDenied        IOEInfo
info)
    CInt
UV_EHOSTUNREACH    -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_EINTR           -> Interrupted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> Interrupted
Interrupted             IOEInfo
info)
    CInt
UV_EINVAL          -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_EIO             -> HardwareFault -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> HardwareFault
HardwareFault           IOEInfo
info)
    CInt
UV_EISCONN         -> AlreadyExists -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> AlreadyExists
AlreadyExists           IOEInfo
info)
    CInt
UV_EISDIR          -> InappropriateType -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InappropriateType
InappropriateType       IOEInfo
info)
    CInt
UV_ELOOP           -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_EMFILE          -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_EMSGSIZE        -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_ENAMETOOLONG    -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_ENETDOWN        -> ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished        IOEInfo
info)
    CInt
UV_ENETUNREACH     -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_ENFILE          -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_ENOBUFS         -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_ENODEV          -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_ENOENT          -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_ENOMEM          -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_ENOPROTOOPT     -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_ENOSPC          -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
UV_ENOSYS          -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_ENOTCONN        -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_ENOTDIR         -> InappropriateType -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InappropriateType
InappropriateType       IOEInfo
info)
    CInt
UV_ENOTEMPTY       -> UnsatisfiedConstraints -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsatisfiedConstraints
UnsatisfiedConstraints  IOEInfo
info)
    CInt
UV_ENOTSOCK        -> InvalidArgument -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> InvalidArgument
InvalidArgument         IOEInfo
info)
    CInt
UV_ENOTSUP         -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EPERM           -> PermissionDenied -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> PermissionDenied
PermissionDenied        IOEInfo
info)
    CInt
UV_EPIPE           -> ResourceVanished -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceVanished
ResourceVanished        IOEInfo
info)
    CInt
UV_EPROTO          -> ProtocolError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ProtocolError
ProtocolError           IOEInfo
info)
    CInt
UV_EPROTONOSUPPORT -> ProtocolError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ProtocolError
ProtocolError           IOEInfo
info)
    CInt
UV_EPROTOTYPE      -> ProtocolError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ProtocolError
ProtocolError           IOEInfo
info)
    CInt
UV_ERANGE          -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_EROFS           -> PermissionDenied -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> PermissionDenied
PermissionDenied        IOEInfo
info)
    CInt
UV_ESHUTDOWN       -> IllegalOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> IllegalOperation
IllegalOperation        IOEInfo
info)
    CInt
UV_ESPIPE          -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_ESRCH           -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_ETIMEDOUT       -> TimeExpired -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> TimeExpired
TimeExpired             IOEInfo
info)
    CInt
UV_ETXTBSY         -> ResourceBusy -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceBusy
ResourceBusy            IOEInfo
info)
    CInt
UV_EXDEV           -> UnsupportedOperation -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> UnsupportedOperation
UnsupportedOperation    IOEInfo
info)
    CInt
UV_UNKNOWN         -> OtherError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> OtherError
OtherError              IOEInfo
info)
    CInt
UV_ENXIO           -> NoSuchThing -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> NoSuchThing
NoSuchThing             IOEInfo
info)
    CInt
UV_EMLINK          -> ResourceExhausted -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> ResourceExhausted
ResourceExhausted       IOEInfo
info)
    CInt
_                  -> OtherError -> IO a
forall e a. Exception e => e -> IO a
throwIO (IOEInfo -> OtherError
OtherError              IOEInfo
info)