{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Exception
(
module Control.Exception,
module Exception
)
where
import GhcPrelude
import Control.Exception
import Control.Monad.IO.Class
catchIO :: IO a -> (IOException -> IO a) -> IO a
catchIO :: IO a -> (IOException -> IO a) -> IO a
catchIO = IO a -> (IOException -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Control.Exception.catch
handleIO :: (IOException -> IO a) -> IO a -> IO a
handleIO :: (IOException -> IO a) -> IO a -> IO a
handleIO = (IO a -> (IOException -> IO a) -> IO a)
-> (IOException -> IO a) -> IO a -> IO a
forall a b c. (a -> b -> c) -> b -> a -> c
flip IO a -> (IOException -> IO a) -> IO a
forall a. IO a -> (IOException -> IO a) -> IO a
catchIO
tryIO :: IO a -> IO (Either IOException a)
tryIO :: IO a -> IO (Either IOException a)
tryIO = IO a -> IO (Either IOException a)
forall e a. Exception e => IO a -> IO (Either e a)
try
class MonadIO m => ExceptionMonad m where
gcatch :: Exception e => m a -> (e -> m a) -> m a
gmask :: ((m a -> m a) -> m b) -> m b
gbracket :: m a -> (a -> m b) -> (a -> m c) -> m c
gfinally :: m a -> m b -> m a
gbracket before :: m a
before after :: a -> m b
after thing :: a -> m c
thing =
((m c -> m c) -> m c) -> m c
forall (m :: * -> *) a b.
ExceptionMonad m =>
((m a -> m a) -> m b) -> m b
gmask (((m c -> m c) -> m c) -> m c) -> ((m c -> m c) -> m c) -> m c
forall a b. (a -> b) -> a -> b
$ \restore :: m c -> m c
restore -> do
a
a <- m a
before
c
r <- m c -> m c
restore (a -> m c
thing a
a) m c -> m b -> m c
forall (m :: * -> *) a b. ExceptionMonad m => m a -> m b -> m a
`gonException` a -> m b
after a
a
b
_ <- a -> m b
after a
a
c -> m c
forall (m :: * -> *) a. Monad m => a -> m a
return c
r
a :: m a
a `gfinally` sequel :: m b
sequel =
((m a -> m a) -> m a) -> m a
forall (m :: * -> *) a b.
ExceptionMonad m =>
((m a -> m a) -> m b) -> m b
gmask (((m a -> m a) -> m a) -> m a) -> ((m a -> m a) -> m a) -> m a
forall a b. (a -> b) -> a -> b
$ \restore :: m a -> m a
restore -> do
a
r <- m a -> m a
restore m a
a m a -> m b -> m a
forall (m :: * -> *) a b. ExceptionMonad m => m a -> m b -> m a
`gonException` m b
sequel
b
_ <- m b
sequel
a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
instance ExceptionMonad IO where
gcatch :: IO a -> (e -> IO a) -> IO a
gcatch = IO a -> (e -> IO a) -> IO a
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
Control.Exception.catch
gmask :: ((IO a -> IO a) -> IO b) -> IO b
gmask f :: (IO a -> IO a) -> IO b
f = ((forall a. IO a -> IO a) -> IO b) -> IO b
forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask (\x :: forall a. IO a -> IO a
x -> (IO a -> IO a) -> IO b
f IO a -> IO a
forall a. IO a -> IO a
x)
gtry :: (ExceptionMonad m, Exception e) => m a -> m (Either e a)
gtry :: m a -> m (Either e a)
gtry act :: m a
act = m (Either e a) -> (e -> m (Either e a)) -> m (Either e a)
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
m a -> (e -> m a) -> m a
gcatch (m a
act m a -> (a -> m (Either e a)) -> m (Either e a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a :: a
a -> Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
a))
(\e :: e
e -> Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e a
forall a b. a -> Either a b
Left e
e))
ghandle :: (ExceptionMonad m, Exception e) => (e -> m a) -> m a -> m a
ghandle :: (e -> m a) -> m a -> m a
ghandle = (m a -> (e -> m a) -> m a) -> (e -> m a) -> m a -> m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip m a -> (e -> m a) -> m a
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
m a -> (e -> m a) -> m a
gcatch
gonException :: (ExceptionMonad m) => m a -> m b -> m a
gonException :: m a -> m b -> m a
gonException ioA :: m a
ioA cleanup :: m b
cleanup = m a
ioA m a -> (SomeException -> m a) -> m a
forall (m :: * -> *) e a.
(ExceptionMonad m, Exception e) =>
m a -> (e -> m a) -> m a
`gcatch` \e :: SomeException
e ->
do b
_ <- m b
cleanup
IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ SomeException -> IO a
forall e a. Exception e => e -> IO a
throwIO (SomeException
e :: SomeException)