{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ImplicitParams #-}
module UnliftIO.Exception
(
throwIO
, throwString
, StringException (..)
, stringException
, throwTo
, impureThrow
, fromEither
, fromEitherIO
, fromEitherM
, catch
, catchIO
, catchAny
, catchDeep
, catchAnyDeep
, catchJust
, handle
, handleIO
, handleAny
, handleDeep
, handleAnyDeep
, handleJust
, try
, tryIO
, tryAny
, tryDeep
, tryAnyDeep
, tryJust
, pureTry
, pureTryDeep
, Handler(..)
, catches
, catchesDeep
, onException
, bracket
, bracket_
, finally
, withException
, bracketOnError
, bracketOnError_
, SyncExceptionWrapper (..)
, toSyncException
, AsyncExceptionWrapper (..)
, toAsyncException
, isSyncException
, isAsyncException
, mask
, uninterruptibleMask
, mask_
, uninterruptibleMask_
, evaluate
, evaluateDeep
, Exception (..)
, Typeable
, SomeException (..)
, SomeAsyncException (..)
, IOException
, EUnsafe.assert
#if !MIN_VERSION_base(4,8,0)
, displayException
#endif
) where
import Control.Concurrent (ThreadId)
import Control.Monad (liftM)
import Control.Monad.IO.Unlift
import Control.Exception (Exception (..), SomeException (..), IOException, SomeAsyncException (..))
import qualified Control.Exception as EUnsafe
import Control.DeepSeq (NFData (..), ($!!))
import Data.Typeable (Typeable, cast)
import System.IO.Unsafe (unsafePerformIO)
#if MIN_VERSION_base(4,9,0)
import GHC.Stack (prettySrcLoc)
import GHC.Stack.Types (HasCallStack, CallStack, getCallStack)
#endif
catch :: (MonadUnliftIO m, Exception e) => m a -> (e -> m a) -> m a
catch f g = withRunInIO $ \run -> run f `EUnsafe.catch` \e ->
if isSyncException e
then run (g e)
else EUnsafe.throwIO e
catchIO :: MonadUnliftIO m => m a -> (IOException -> m a) -> m a
catchIO = catch
catchAny :: MonadUnliftIO m => m a -> (SomeException -> m a) -> m a
catchAny = catch
catchDeep :: (MonadUnliftIO m, Exception e, NFData a)
=> m a -> (e -> m a) -> m a
catchDeep m = catch (m >>= evaluateDeep)
catchAnyDeep :: (NFData a, MonadUnliftIO m) => m a -> (SomeException -> m a) -> m a
catchAnyDeep = catchDeep
catchJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a
catchJust f a b = a `catch` \e -> maybe (liftIO (throwIO e)) b $ f e
handle :: (MonadUnliftIO m, Exception e) => (e -> m a) -> m a -> m a
handle = flip catch
handleIO :: MonadUnliftIO m => (IOException -> m a) -> m a -> m a
handleIO = handle
handleAny :: MonadUnliftIO m => (SomeException -> m a) -> m a -> m a
handleAny = handle
handleDeep :: (MonadUnliftIO m, Exception e, NFData a) => (e -> m a) -> m a -> m a
handleDeep = flip catchDeep
handleAnyDeep :: (MonadUnliftIO m, NFData a) => (SomeException -> m a) -> m a -> m a
handleAnyDeep = flip catchAnyDeep
handleJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a
handleJust f = flip (catchJust f)
try :: (MonadUnliftIO m, Exception e) => m a -> m (Either e a)
try f = catch (liftM Right f) (return . Left)
tryIO :: MonadUnliftIO m => m a -> m (Either IOException a)
tryIO = try
tryAny :: MonadUnliftIO m => m a -> m (Either SomeException a)
tryAny = try
tryDeep :: (MonadUnliftIO m, Exception e, NFData a) => m a -> m (Either e a)
tryDeep f = catch (liftM Right (f >>= evaluateDeep)) (return . Left)
tryAnyDeep :: (MonadUnliftIO m, NFData a) => m a -> m (Either SomeException a)
tryAnyDeep = tryDeep
tryJust :: (MonadUnliftIO m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a)
tryJust f a = catch (Right `liftM` a) (\e -> maybe (throwIO e) (return . Left) (f e))
pureTry :: a -> Either SomeException a
pureTry a = unsafePerformIO $ (return $! Right $! a) `catchAny` (return . Left)
pureTryDeep :: NFData a => a -> Either SomeException a
pureTryDeep = unsafePerformIO . tryAnyDeep . return
data Handler m a = forall e . Exception e => Handler (e -> m a)
catchesHandler :: MonadIO m => [Handler m a] -> SomeException -> m a
catchesHandler handlers e = foldr tryHandler (liftIO (EUnsafe.throwIO e)) handlers
where tryHandler (Handler handler) res
= case fromException e of
Just e' -> handler e'
Nothing -> res
catches :: MonadUnliftIO m => m a -> [Handler m a] -> m a
catches io handlers = io `catch` catchesHandler handlers
catchesDeep :: (MonadUnliftIO m, NFData a) => m a -> [Handler m a] -> m a
catchesDeep io handlers = (io >>= evaluateDeep) `catch` catchesHandler handlers
evaluate :: MonadIO m => a -> m a
evaluate = liftIO . EUnsafe.evaluate
evaluateDeep :: (MonadIO m, NFData a) => a -> m a
evaluateDeep = (evaluate $!!)
bracket :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c
bracket before after thing = withRunInIO $ \run -> EUnsafe.mask $ \restore -> do
x <- run before
res1 <- EUnsafe.try $ restore $ run $ thing x
case res1 of
Left (e1 :: SomeException) -> do
_ :: Either SomeException b <-
EUnsafe.try $ EUnsafe.uninterruptibleMask_ $ run $ after x
EUnsafe.throwIO e1
Right y -> do
_ <- EUnsafe.uninterruptibleMask_ $ run $ after x
return y
bracket_ :: MonadUnliftIO m => m a -> m b -> m c -> m c
bracket_ before after thing = bracket before (const after) (const thing)
bracketOnError :: MonadUnliftIO m => m a -> (a -> m b) -> (a -> m c) -> m c
bracketOnError before after thing = withRunInIO $ \run -> EUnsafe.mask $ \restore -> do
x <- run before
res1 <- EUnsafe.try $ restore $ run $ thing x
case res1 of
Left (e1 :: SomeException) -> do
_ :: Either SomeException b <-
EUnsafe.try $ EUnsafe.uninterruptibleMask_ $ run $ after x
EUnsafe.throwIO e1
Right y -> return y
bracketOnError_ :: MonadUnliftIO m => m a -> m b -> m c -> m c
bracketOnError_ before after thing = bracketOnError before (const after) (const thing)
finally :: MonadUnliftIO m => m a -> m b -> m a
finally thing after = withRunInIO $ \run -> EUnsafe.uninterruptibleMask $ \restore -> do
res1 <- EUnsafe.try $ restore $ run thing
case res1 of
Left (e1 :: SomeException) -> do
_ :: Either SomeException b <- EUnsafe.try $ run after
EUnsafe.throwIO e1
Right x -> do
_ <- run after
return x
withException :: (MonadUnliftIO m, Exception e)
=> m a -> (e -> m b) -> m a
withException thing after = withRunInIO $ \run -> EUnsafe.uninterruptibleMask $ \restore -> do
res1 <- EUnsafe.try $ restore $ run thing
case res1 of
Left e1 -> do
_ :: Either SomeException b <- EUnsafe.try $ run $ after e1
EUnsafe.throwIO e1
Right x -> return x
onException :: MonadUnliftIO m => m a -> m b -> m a
onException thing after = withException thing (\(_ :: SomeException) -> after)
throwIO :: (MonadIO m, Exception e) => e -> m a
throwIO = liftIO . EUnsafe.throwIO . toSyncException
data SyncExceptionWrapper = forall e. Exception e => SyncExceptionWrapper e
deriving Typeable
instance Show SyncExceptionWrapper where
show (SyncExceptionWrapper e) = show e
instance Exception SyncExceptionWrapper where
#if MIN_VERSION_base(4,8,0)
displayException (SyncExceptionWrapper e) = displayException e
#endif
toSyncException :: Exception e => e -> SomeException
toSyncException e =
case fromException se of
Just (SomeAsyncException _) -> toException (SyncExceptionWrapper e)
Nothing -> se
where
se = toException e
data AsyncExceptionWrapper = forall e. Exception e => AsyncExceptionWrapper e
deriving Typeable
instance Show AsyncExceptionWrapper where
show (AsyncExceptionWrapper e) = show e
instance Exception AsyncExceptionWrapper where
toException = toException . SomeAsyncException
fromException se = do
SomeAsyncException e <- fromException se
cast e
#if MIN_VERSION_base(4,8,0)
displayException (AsyncExceptionWrapper e) = displayException e
#endif
toAsyncException :: Exception e => e -> SomeException
toAsyncException e =
case fromException se of
Just (SomeAsyncException _) -> se
Nothing -> toException (AsyncExceptionWrapper e)
where
se = toException e
isSyncException :: Exception e => e -> Bool
isSyncException e =
case fromException (toException e) of
Just (SomeAsyncException _) -> False
Nothing -> True
isAsyncException :: Exception e => e -> Bool
isAsyncException = not . isSyncException
{-# INLINE isAsyncException #-}
#if !MIN_VERSION_base(4,8,0)
displayException :: Exception e => e -> String
displayException = show
#endif
mask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
mask f = withRunInIO $ \run -> EUnsafe.mask $ \unmask ->
run $ f $ liftIO . unmask . run
uninterruptibleMask :: MonadUnliftIO m => ((forall a. m a -> m a) -> m b) -> m b
uninterruptibleMask f = withRunInIO $ \run -> EUnsafe.uninterruptibleMask $ \unmask ->
run $ f $ liftIO . unmask . run
mask_ :: MonadUnliftIO m => m a -> m a
mask_ f = withRunInIO $ \run -> EUnsafe.mask_ (run f)
uninterruptibleMask_ :: MonadUnliftIO m => m a -> m a
uninterruptibleMask_ f = withRunInIO $ \run -> EUnsafe.uninterruptibleMask_ (run f)
#if MIN_VERSION_base(4,9,0)
throwString :: (MonadIO m, HasCallStack) => String -> m a
throwString s = throwIO (StringException s ?callStack)
#else
throwString :: MonadIO m => String -> m a
throwString s = throwIO (StringException s ())
#endif
#if MIN_VERSION_base(4,9,0)
stringException :: HasCallStack => String -> StringException
stringException s = StringException s ?callStack
#else
stringException :: String -> StringException
stringException s = StringException s ()
#endif
#if MIN_VERSION_base(4,9,0)
data StringException = StringException String CallStack
deriving Typeable
instance Show StringException where
show (StringException s cs) = concat
$ "UnliftIO.Exception.throwString called with:\n\n"
: s
: "\nCalled from:\n"
: map go (getCallStack cs)
where
go (x, y) = concat
[ " "
, x
, " ("
, prettySrcLoc y
, ")\n"
]
#else
data StringException = StringException String ()
deriving Typeable
instance Show StringException where
show (StringException s _) = "UnliftIO.Exception.throwString called with:\n\n" ++ s
#endif
instance Exception StringException
throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m ()
throwTo tid = liftIO . EUnsafe.throwTo tid . toAsyncException
impureThrow :: Exception e => e -> a
impureThrow = EUnsafe.throw . toSyncException
fromEither :: (Exception e, MonadIO m) => Either e a -> m a
fromEither = either throwIO return
fromEitherIO :: (Exception e, MonadIO m) => IO (Either e a) -> m a
fromEitherIO = fromEitherM . liftIO
fromEitherM :: (Exception e, MonadIO m) => m (Either e a) -> m a
fromEitherM = (>>= fromEither)