{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude, ExistentialQuantification #-}
module GHC.Internal.Control.Exception (
SomeException(..),
Exception(..),
IOException,
ArithException(..),
ArrayException(..),
AssertionFailed(..),
SomeAsyncException(..),
AsyncException(..),
asyncExceptionToException, asyncExceptionFromException,
NonTermination(..),
NestedAtomically(..),
BlockedIndefinitelyOnMVar(..),
BlockedIndefinitelyOnSTM(..),
AllocationLimitExceeded(..),
CompactionFailed(..),
Deadlock(..),
NoMethodError(..),
PatternMatchFail(..),
RecConError(..),
RecSelError(..),
RecUpdError(..),
ErrorCall(..),
TypeError(..),
throw,
throwIO,
ioError,
throwTo,
catch,
catches, Handler(..),
catchJust,
handle,
handleJust,
try,
tryJust,
evaluate,
mapException,
mask,
mask_,
uninterruptibleMask,
uninterruptibleMask_,
MaskingState(..),
getMaskingState,
interruptible,
allowInterrupt,
assert,
bracket,
bracket_,
bracketOnError,
finally,
onException,
) where
import GHC.Internal.Control.Exception.Base
import GHC.Internal.Base
import GHC.Internal.IO (interruptible)
data Handler a = forall e . Exception e => Handler (e -> IO a)
instance Functor Handler where
fmap :: forall a b. (a -> b) -> Handler a -> Handler b
fmap a -> b
f (Handler e -> IO a
h) = (e -> IO b) -> Handler b
forall a e. Exception e => (e -> IO a) -> Handler a
Handler ((a -> b) -> IO a -> IO b
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (IO a -> IO b) -> (e -> IO a) -> e -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> IO a
h)
catches :: IO a -> [Handler a] -> IO a
catches :: forall a. IO a -> [Handler a] -> IO a
catches IO a
io [Handler a]
handlers = IO a
io IO a -> (SomeException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`catch` [Handler a] -> SomeException -> IO a
forall a. [Handler a] -> SomeException -> IO a
catchesHandler [Handler a]
handlers
catchesHandler :: [Handler a] -> SomeException -> IO a
catchesHandler :: forall a. [Handler a] -> SomeException -> IO a
catchesHandler [Handler a]
handlers SomeException
e = (Handler a -> IO a -> IO a) -> IO a -> [Handler a] -> IO a
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr Handler a -> IO a -> IO a
forall {a}. Handler a -> IO a -> IO a
tryHandler (SomeException -> IO a
forall a e. (?callStack::CallStack, Exception e) => e -> a
throw SomeException
e) [Handler a]
handlers
where tryHandler :: Handler a -> IO a -> IO a
tryHandler (Handler e -> IO a
handler) IO a
res
= case SomeException -> Maybe e
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e of
Just e
e' -> e -> IO a
handler e
e'
Maybe e
Nothing -> IO a
res
allowInterrupt :: IO ()
allowInterrupt :: IO ()
allowInterrupt = IO () -> IO ()
forall a. IO a -> IO a
interruptible (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()