{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ImplicitParams #-}
module Control.Exception.Safe
(
throw
, throwIO
, throwM
, throwString
, StringException (..)
, throwTo
, impureThrow
, catch
, catchIO
, catchAny
, catchDeep
, catchAnyDeep
, catchAsync
, catchJust
, handle
, handleIO
, handleAny
, handleDeep
, handleAnyDeep
, handleAsync
, handleJust
, try
, tryIO
, tryAny
, tryDeep
, tryAnyDeep
, tryAsync
, tryJust
, Handler(..)
, catches
, catchesDeep
, catchesAsync
, onException
, bracket
, bracket_
, finally
, withException
, bracketOnError
, bracketOnError_
, bracketWithError
, SyncExceptionWrapper (..)
, toSyncException
, AsyncExceptionWrapper (..)
, toAsyncException
, isSyncException
, isAsyncException
, C.MonadThrow
, C.MonadCatch
, C.MonadMask (..)
, C.mask_
, C.uninterruptibleMask_
, C.catchIOError
, C.handleIOError
, Exception (..)
, Typeable
, SomeException (..)
, SomeAsyncException (..)
, E.IOException
, E.assert
#if !MIN_VERSION_base(4,8,0)
, displayException
#endif
) where
import Control.Concurrent (ThreadId)
import Control.DeepSeq (($!!), NFData)
import Control.Exception (Exception (..), SomeException (..), SomeAsyncException (..))
import qualified Control.Exception as E
import qualified Control.Monad.Catch as C
import Control.Monad.Catch (Handler (..))
import Control.Monad (liftM)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Typeable (Typeable, cast)
#if MIN_VERSION_base(4,9,0)
import GHC.Stack (prettySrcLoc)
import GHC.Stack.Types (HasCallStack, CallStack, getCallStack)
#endif
throw :: (C.MonadThrow m, Exception e) => e -> m a
throw = C.throwM . toSyncException
throwIO :: (C.MonadThrow m, Exception e) => e -> m a
throwIO = throw
throwM :: (C.MonadThrow m, Exception e) => e -> m a
throwM = throw
#if MIN_VERSION_base(4,9,0)
throwString :: (C.MonadThrow m, HasCallStack) => String -> m a
throwString s = throwM (StringException s ?callStack)
#else
throwString :: C.MonadThrow m => String -> m a
throwString s = throwM (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
$ "Control.Exception.Safe.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 _) = "Control.Exception.Safe.throwString called with:\n\n" ++ s
#endif
instance Exception StringException
throwTo :: (Exception e, MonadIO m) => ThreadId -> e -> m ()
throwTo tid = liftIO . E.throwTo tid . toAsyncException
impureThrow :: Exception e => e -> a
impureThrow = E.throw . toSyncException
catch :: (C.MonadCatch m, Exception e) => m a -> (e -> m a) -> m a
catch f g = f `C.catch` \e ->
if isSyncException e
then g e
else C.throwM e
catchIO :: C.MonadCatch m => m a -> (E.IOException -> m a) -> m a
catchIO = C.catch
catchAny :: C.MonadCatch m => m a -> (SomeException -> m a) -> m a
catchAny = catch
catchDeep :: (C.MonadCatch m, MonadIO m, Exception e, NFData a)
=> m a -> (e -> m a) -> m a
catchDeep = catch . evaluateDeep
evaluateDeep :: (MonadIO m, NFData a) => m a -> m a
evaluateDeep action = do
res <- action
liftIO (E.evaluate $!! res)
catchAnyDeep :: (C.MonadCatch m, MonadIO m, NFData a) => m a -> (SomeException -> m a) -> m a
catchAnyDeep = catchDeep
catchAsync :: (C.MonadCatch m, Exception e) => m a -> (e -> m a) -> m a
catchAsync = C.catch
catchJust :: (C.MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a
catchJust f a b = a `catch` \e -> maybe (throwM e) b $ f e
handle :: (C.MonadCatch m, Exception e) => (e -> m a) -> m a -> m a
handle = flip catch
handleIO :: C.MonadCatch m => (E.IOException -> m a) -> m a -> m a
handleIO = C.handle
handleAny :: C.MonadCatch m => (SomeException -> m a) -> m a -> m a
handleAny = flip catchAny
handleDeep :: (C.MonadCatch m, Exception e, MonadIO m, NFData a) => (e -> m a) -> m a -> m a
handleDeep = flip catchDeep
handleAnyDeep :: (C.MonadCatch m, MonadIO m, NFData a) => (SomeException -> m a) -> m a -> m a
handleAnyDeep = flip catchAnyDeep
handleAsync :: (C.MonadCatch m, Exception e) => (e -> m a) -> m a -> m a
handleAsync = C.handle
handleJust :: (C.MonadCatch m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a
handleJust f = flip (catchJust f)
try :: (C.MonadCatch m, E.Exception e) => m a -> m (Either e a)
try f = catch (liftM Right f) (return . Left)
tryIO :: C.MonadCatch m => m a -> m (Either E.IOException a)
tryIO = C.try
tryAny :: C.MonadCatch m => m a -> m (Either SomeException a)
tryAny = try
tryDeep :: (C.MonadCatch m, MonadIO m, E.Exception e, NFData a) => m a -> m (Either e a)
tryDeep f = catch (liftM Right (evaluateDeep f)) (return . Left)
tryAnyDeep :: (C.MonadCatch m, MonadIO m, NFData a) => m a -> m (Either SomeException a)
tryAnyDeep = tryDeep
tryAsync :: (C.MonadCatch m, E.Exception e) => m a -> m (Either e a)
tryAsync = C.try
tryJust :: (C.MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a)
tryJust f a = catch (Right `liftM` a) (\e -> maybe (throwM e) (return . Left) (f e))
onException :: C.MonadMask m => m a -> m b -> m a
onException thing after = withException thing (\(_ :: SomeException) -> after)
withException :: (C.MonadMask m, E.Exception e) => m a -> (e -> m b) -> m a
withException thing after = C.uninterruptibleMask $ \restore -> do
res1 <- C.try $ restore thing
case res1 of
Left e1 -> do
_ :: Either SomeException b <- C.try $ after e1
C.throwM e1
Right x -> return x
bracket :: forall m a b c. C.MonadMask m
=> m a -> (a -> m b) -> (a -> m c) -> m c
bracket before after = bracketWithError before (const after)
bracket_ :: C.MonadMask m => m a -> m b -> m c -> m c
bracket_ before after thing = bracket before (const after) (const thing)
finally :: C.MonadMask m => m a -> m b -> m a
finally thing after = C.uninterruptibleMask $ \restore -> do
res1 <- C.try $ restore thing
case res1 of
Left (e1 :: SomeException) -> do
_ :: Either SomeException b <- C.try after
C.throwM e1
Right x -> do
_ <- after
return x
bracketOnError :: forall m a b c. C.MonadMask m
=> m a -> (a -> m b) -> (a -> m c) -> m c
bracketOnError before after thing = C.mask $ \restore -> do
x <- before
res1 <- C.try $ restore (thing x)
case res1 of
Left (e1 :: SomeException) -> do
_ :: Either SomeException b <-
C.try $ C.uninterruptibleMask_ $ after x
C.throwM e1
Right y -> return y
bracketOnError_ :: C.MonadMask m => m a -> m b -> m c -> m c
bracketOnError_ before after thing = bracketOnError before (const after) (const thing)
bracketWithError :: forall m a b c. C.MonadMask m
=> m a -> (Maybe SomeException -> a -> m b) -> (a -> m c) -> m c
bracketWithError before after thing = C.mask $ \restore -> do
x <- before
res1 <- C.try $ restore (thing x)
case res1 of
Left (e1 :: SomeException) -> do
_ :: Either SomeException b <-
C.try $ C.uninterruptibleMask_ $ after (Just e1) x
C.throwM e1
Right y -> do
_ <- C.uninterruptibleMask_ $ after Nothing x
return y
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
catches :: (C.MonadCatch m, C.MonadThrow m) => m a -> [Handler m a] -> m a
catches io handlers = io `catch` catchesHandler handlers
catchesDeep :: (C.MonadCatch m, C.MonadThrow m, MonadIO m, NFData a) => m a -> [Handler m a] -> m a
catchesDeep io handlers = evaluateDeep io `catch` catchesHandler handlers
catchesAsync :: (C.MonadCatch m, C.MonadThrow m) => m a -> [Handler m a] -> m a
catchesAsync io handlers = io `catchAsync` catchesHandler handlers
catchesHandler :: (C.MonadThrow m) => [Handler m a] -> SomeException -> m a
catchesHandler handlers e = foldr tryHandler (C.throwM e) handlers
where tryHandler (Handler handler) res
= case fromException e of
Just e' -> handler e'
Nothing -> res