{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UnboxedTuples #-}
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
module Control.Monad.Exception (
E.Exception(..),
E.SomeException,
MonadException(..),
onException,
MonadAsyncException(..),
bracket,
bracket_,
ExceptionT(..),
mapExceptionT,
liftException
) where
#if !MIN_VERSION_base(4,6,0)
import Prelude hiding (catch)
#endif /*!MIN_VERSION_base(4,6,0) */
import Control.Applicative
import qualified Control.Exception as E (Exception(..),
SomeException,
catch,
throw,
finally)
import qualified Control.Exception as E (mask)
import Control.Monad (MonadPlus(..))
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail
#endif /* !MIN_VERSION_base(4,13,0) */
#if !MIN_VERSION_base(4,11,0)
import qualified Control.Monad.Fail as Fail
#endif /* !MIN_VERSION_base(4,11,0) */
import Control.Monad.Fix (MonadFix(..))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Class (MonadTrans(..))
#if !MIN_VERSION_transformers(0,6,0)
import Control.Monad.Trans.Error (Error(..),
ErrorT(..),
mapErrorT,
runErrorT)
#endif /* !MIN_VERSION_transformers(0,6,0) */
import Control.Monad.Trans.Except (ExceptT(..),
mapExceptT,
runExceptT)
import Control.Monad.Trans.Identity (IdentityT(..),
mapIdentityT,
runIdentityT)
#if !MIN_VERSION_transformers(0,6,0)
import Control.Monad.Trans.List (ListT(..),
mapListT,
runListT)
#endif /* !MIN_VERSION_transformers(0,6,0) */
import Control.Monad.Trans.Maybe (MaybeT(..),
mapMaybeT,
runMaybeT)
import Control.Monad.Trans.RWS.Lazy as Lazy (RWST(..),
mapRWST,
runRWST)
import Control.Monad.Trans.RWS.Strict as Strict (RWST(..),
mapRWST,
runRWST)
import Control.Monad.Trans.Reader (ReaderT(..),
mapReaderT)
import Control.Monad.Trans.State.Lazy as Lazy (StateT(..),
mapStateT,
runStateT)
import Control.Monad.Trans.State.Strict as Strict (StateT(..),
mapStateT,
runStateT)
import Control.Monad.Trans.Writer.Lazy as Lazy (WriterT(..),
mapWriterT,
runWriterT)
import Control.Monad.Trans.Writer.Strict as Strict (WriterT(..),
mapWriterT,
runWriterT)
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid (Monoid)
#endif /* !MIN_VERSION_base(4,8,0) */
import GHC.Conc.Sync (STM(..),
catchSTM,
throwSTM)
class (Monad m) => MonadException m where
throw :: E.Exception e => e -> m a
catch :: E.Exception e
=> m a
-> (e -> m a)
-> m a
finally :: m a
-> m b
-> m a
m a
act `finally` m b
sequel = do
a
a <- m a
act forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
`onException` m b
sequel
b
_ <- m b
sequel
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
onException :: MonadException m
=> m a
-> m b
-> m a
onException :: forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
onException m a
act m b
what =
m a
act forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \(SomeException
e :: E.SomeException) -> m b
what forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw SomeException
e
class (MonadIO m, MonadException m) => MonadAsyncException m where
mask :: ((forall a. m a -> m a) -> m b) -> m b
bracket :: MonadAsyncException m
=> m a
-> (a -> m b)
-> (a -> m c)
-> m c
bracket :: forall (m :: * -> *) a b c.
MonadAsyncException m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket m a
before a -> m b
after a -> m c
thing =
forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore -> do
a
a <- m a
before
forall a. m a -> m a
restore (a -> m c
thing a
a) forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
`finally` a -> m b
after a
a
bracket_ :: MonadAsyncException m
=> m a
-> m b
-> m c
-> m c
bracket_ :: forall (m :: * -> *) a b c.
MonadAsyncException m =>
m a -> m b -> m c -> m c
bracket_ m a
before m b
after m c
thing =
forall (m :: * -> *) a b c.
MonadAsyncException m =>
m a -> (a -> m b) -> (a -> m c) -> m c
bracket m a
before (forall a b. a -> b -> a
const m b
after) (forall a b. a -> b -> a
const m c
thing)
newtype ExceptionT m a =
ExceptionT { forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT :: m (Either E.SomeException a) }
mapExceptionT :: (m (Either E.SomeException a) -> n (Either E.SomeException b))
-> ExceptionT m a
-> ExceptionT n b
mapExceptionT :: forall (m :: * -> *) a (n :: * -> *) b.
(m (Either SomeException a) -> n (Either SomeException b))
-> ExceptionT m a -> ExceptionT n b
mapExceptionT m (Either SomeException a) -> n (Either SomeException b)
f = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either SomeException a) -> n (Either SomeException b)
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT
liftException :: MonadException m => Either E.SomeException a -> m a
liftException :: forall (m :: * -> *) a.
MonadException m =>
Either SomeException a -> m a
liftException (Left SomeException
e) = forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw SomeException
e
liftException (Right a
a) = forall (m :: * -> *) a. Monad m => a -> m a
return a
a
instance MonadTrans ExceptionT where
lift :: forall (m :: * -> *) a. Monad m => m a -> ExceptionT m a
lift m a
m = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ do
a
a <- m a
m
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right a
a)
instance (Functor m, Monad m) => Applicative (ExceptionT m) where
pure :: forall a. a -> ExceptionT m a
pure a
a = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right a
a)
ExceptionT m (a -> b)
f <*> :: forall a b.
ExceptionT m (a -> b) -> ExceptionT m a -> ExceptionT m b
<*> ExceptionT m a
v = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ do
Either SomeException (a -> b)
mf <- forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT ExceptionT m (a -> b)
f
case Either SomeException (a -> b)
mf of
Left SomeException
e -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left SomeException
e)
Right a -> b
k -> do
Either SomeException a
mv <- forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT ExceptionT m a
v
case Either SomeException a
mv of
Left SomeException
e -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left SomeException
e)
Right a
x -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right (a -> b
k a
x))
instance (Functor m) => Functor (ExceptionT m) where
fmap :: forall a b. (a -> b) -> ExceptionT m a -> ExceptionT m b
fmap a -> b
f = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT
instance (Monad m) => Monad (ExceptionT m) where
#if MIN_VERSION_base(4,8,0)
return :: forall a. a -> ExceptionT m a
return = forall (f :: * -> *) a. Applicative f => a -> f a
pure
#else /* !MIN_VERSION_base(4,8,0) */
return a = ExceptionT $ return (Right a)
#endif /* !MIN_VERSION_base(4,8,0) */
ExceptionT m a
m >>= :: forall a b.
ExceptionT m a -> (a -> ExceptionT m b) -> ExceptionT m b
>>= a -> ExceptionT m b
k = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ do
Either SomeException a
a <- forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT ExceptionT m a
m
case Either SomeException a
a of
Left SomeException
l -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left SomeException
l)
Right a
r -> forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT (a -> ExceptionT m b
k a
r)
#if !MIN_VERSION_base(4,11,0)
fail = Fail.fail
#endif /* !MIN_VERSION_base(4,11,0) */
instance (Monad m) => MonadFail (ExceptionT m) where
fail :: forall a. String -> ExceptionT m a
fail String
msg = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left (forall e. Exception e => e -> SomeException
E.toException (String -> IOError
userError String
msg)))
instance (Monad m) => MonadPlus (ExceptionT m) where
mzero :: forall a. ExceptionT m a
mzero = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left (forall e. Exception e => e -> SomeException
E.toException (String -> IOError
userError String
"")))
ExceptionT m a
m mplus :: forall a. ExceptionT m a -> ExceptionT m a -> ExceptionT m a
`mplus` ExceptionT m a
n = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ do
Either SomeException a
a <- forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT ExceptionT m a
m
case Either SomeException a
a of
Left SomeException
_ -> forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT ExceptionT m a
n
Right a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right a
r)
instance (Functor m, Monad m) => Alternative (ExceptionT m) where
empty :: forall a. ExceptionT m a
empty = forall (m :: * -> *) a. MonadPlus m => m a
mzero
<|> :: forall a. ExceptionT m a -> ExceptionT m a -> ExceptionT m a
(<|>) = forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus
instance (MonadFix m) => MonadFix (ExceptionT m) where
mfix :: forall a. (a -> ExceptionT m a) -> ExceptionT m a
mfix a -> ExceptionT m a
f = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix forall a b. (a -> b) -> a -> b
$ \Either SomeException a
a -> forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT forall a b. (a -> b) -> a -> b
$ a -> ExceptionT m a
f forall a b. (a -> b) -> a -> b
$ case Either SomeException a
a of
Right a
r -> a
r
Either SomeException a
_ -> forall a. HasCallStack => String -> a
error String
"empty mfix argument"
instance (Monad m) => MonadException (ExceptionT m) where
throw :: forall e a. Exception e => e -> ExceptionT m a
throw e
e = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left (forall e. Exception e => e -> SomeException
E.toException e
e))
ExceptionT m a
m catch :: forall e a.
Exception e =>
ExceptionT m a -> (e -> ExceptionT m a) -> ExceptionT m a
`catch` e -> ExceptionT m a
h = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ do
Either SomeException a
a <- forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT ExceptionT m a
m
case Either SomeException a
a of
Left SomeException
l -> case forall e. Exception e => SomeException -> Maybe e
E.fromException SomeException
l of
Just e
e -> forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT (e -> ExceptionT m a
h e
e)
Maybe e
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left SomeException
l)
Right a
r -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. b -> Either a b
Right a
r)
instance (MonadIO m) => MonadIO (ExceptionT m) where
liftIO :: forall a. IO a -> ExceptionT m a
liftIO IO a
m = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. b -> Either a b
Right IO a
m forall e a. Exception e => IO a -> (e -> IO a) -> IO a
`E.catch` \(SomeException
e :: E.SomeException) -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left SomeException
e)
instance (MonadAsyncException m) => MonadAsyncException (ExceptionT m) where
mask :: forall b.
((forall a. ExceptionT m a -> ExceptionT m a) -> ExceptionT m b)
-> ExceptionT m b
mask (forall a. ExceptionT m a -> ExceptionT m a) -> ExceptionT m b
act = forall (m :: * -> *) a.
m (Either SomeException a) -> ExceptionT m a
ExceptionT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall (m :: * -> *) a.
ExceptionT m a -> m (Either SomeException a)
runExceptionT forall a b. (a -> b) -> a -> b
$ (forall a. ExceptionT m a -> ExceptionT m a) -> ExceptionT m b
act (forall (m :: * -> *) a (n :: * -> *) b.
(m (Either SomeException a) -> n (Either SomeException b))
-> ExceptionT m a -> ExceptionT n b
mapExceptionT forall a. m a -> m a
restore)
instance MonadException IO where
catch :: forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch = forall e a. Exception e => IO a -> (e -> IO a) -> IO a
E.catch
throw :: forall e a. Exception e => e -> IO a
throw = forall a e. Exception e => e -> a
E.throw
finally :: forall a b. IO a -> IO b -> IO a
finally = forall a b. IO a -> IO b -> IO a
E.finally
#if __GLASGOW_HASKELL__ >= 700
instance MonadAsyncException IO where
mask :: forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
mask = forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
E.mask
#else /* __GLASGOW_HASKELL__ < 700 */
instance MonadAsyncException IO where
mask act = do
b <- E.blocked
if b
then act id
else E.block $ act E.unblock
#endif /* __GLASGOW_HASKELL__ < 700 */
instance MonadException STM where
catch :: forall e a. Exception e => STM a -> (e -> STM a) -> STM a
catch = forall e a. Exception e => STM a -> (e -> STM a) -> STM a
catchSTM
throw :: forall e a. Exception e => e -> STM a
throw = forall e a. Exception e => e -> STM a
throwSTM
#if !MIN_VERSION_transformers(0,6,0)
instance (MonadException m, Error e) =>
MonadException (ErrorT e m) where
throw :: forall e a. Exception e => e -> ErrorT e m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
ErrorT e m a
m catch :: forall e a.
Exception e =>
ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a
`catch` e -> ErrorT e m a
h = forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ErrorT e m a -> ErrorT e' n b
mapErrorT (\m (Either e a)
m' -> m (Either e a)
m' forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (e -> ErrorT e m a
h e
e)) ErrorT e m a
m
ErrorT e m a
act finally :: forall a b. ErrorT e m a -> ErrorT e m b -> ErrorT e m a
`finally` ErrorT e m b
sequel =
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ErrorT e m a -> ErrorT e' n b
mapErrorT (\m (Either e a)
act' -> m (Either e a)
act' forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
`finally` forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m b
sequel) ErrorT e m a
act
#endif /* !MIN_VERSION_transformers(0,6,0) */
instance (MonadException m) =>
MonadException (ExceptT e' m) where
throw :: forall e a. Exception e => e -> ExceptT e' m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
ExceptT e' m a
m catch :: forall e a.
Exception e =>
ExceptT e' m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
`catch` e -> ExceptT e' m a
h = forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT (\m (Either e' a)
m' -> m (Either e' a)
m' forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (e -> ExceptT e' m a
h e
e)) ExceptT e' m a
m
ExceptT e' m a
act finally :: forall a b. ExceptT e' m a -> ExceptT e' m b -> ExceptT e' m a
`finally` ExceptT e' m b
sequel =
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT (\m (Either e' a)
act' -> m (Either e' a)
act' forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
`finally` forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT e' m b
sequel) ExceptT e' m a
act
instance (MonadException m) =>
MonadException (IdentityT m) where
throw :: forall e a. Exception e => e -> IdentityT m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
IdentityT m a
m catch :: forall e a.
Exception e =>
IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a
`catch` e -> IdentityT m a
h = forall {k1} {k2} (m :: k1 -> *) (a :: k1) (n :: k2 -> *) (b :: k2).
(m a -> n b) -> IdentityT m a -> IdentityT n b
mapIdentityT (\m a
m' -> m a
m' forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT (e -> IdentityT m a
h e
e)) IdentityT m a
m
#if !MIN_VERSION_transformers(0,6,0)
instance MonadException m =>
MonadException (ListT m) where
throw :: forall e a. Exception e => e -> ListT m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
ListT m a
m catch :: forall e a.
Exception e =>
ListT m a -> (e -> ListT m a) -> ListT m a
`catch` e -> ListT m a
h = forall (m :: * -> *) a (n :: * -> *) b.
(m [a] -> n [b]) -> ListT m a -> ListT n b
mapListT (\m [a]
m' -> m [a]
m' forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall (m :: * -> *) a. ListT m a -> m [a]
runListT (e -> ListT m a
h e
e)) ListT m a
m
#endif /* !MIN_VERSION_transformers(0,6,0) */
instance (MonadException m) =>
MonadException (MaybeT m) where
throw :: forall e a. Exception e => e -> MaybeT m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
MaybeT m a
m catch :: forall e a.
Exception e =>
MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a
`catch` e -> MaybeT m a
h = forall (m :: * -> *) a (n :: * -> *) b.
(m (Maybe a) -> n (Maybe b)) -> MaybeT m a -> MaybeT n b
mapMaybeT (\m (Maybe a)
m' -> m (Maybe a)
m' forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT (e -> MaybeT m a
h e
e)) MaybeT m a
m
MaybeT m a
act finally :: forall a b. MaybeT m a -> MaybeT m b -> MaybeT m a
`finally` MaybeT m b
sequel =
forall (m :: * -> *) a (n :: * -> *) b.
(m (Maybe a) -> n (Maybe b)) -> MaybeT m a -> MaybeT n b
mapMaybeT (\m (Maybe a)
act' -> m (Maybe a)
act' forall (m :: * -> *) a b. MonadException m => m a -> m b -> m a
`finally` forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT MaybeT m b
sequel) MaybeT m a
act
instance (Monoid w, MonadException m) =>
MonadException (Lazy.RWST r w s m) where
throw :: forall e a. Exception e => e -> RWST r w s m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
RWST r w s m a
m catch :: forall e a.
Exception e =>
RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a
`catch` e -> RWST r w s m a
h = forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Lazy.RWST forall a b. (a -> b) -> a -> b
$ \r
r s
s ->
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
Lazy.runRWST RWST r w s m a
m r
r s
s forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
Lazy.runRWST (e -> RWST r w s m a
h e
e) r
r s
s
instance (Monoid w, MonadException m) =>
MonadException (Strict.RWST r w s m) where
throw :: forall e a. Exception e => e -> RWST r w s m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
RWST r w s m a
m catch :: forall e a.
Exception e =>
RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a
`catch` e -> RWST r w s m a
h = forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Strict.RWST forall a b. (a -> b) -> a -> b
$ \r
r s
s ->
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
Strict.runRWST RWST r w s m a
m r
r s
s forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
Strict.runRWST (e -> RWST r w s m a
h e
e) r
r s
s
instance (MonadException m) =>
MonadException (ReaderT r m) where
throw :: forall e a. Exception e => e -> ReaderT r m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
ReaderT r m a
m catch :: forall e a.
Exception e =>
ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a
`catch` e -> ReaderT r m a
h = forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \r
r ->
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ReaderT r m a
m r
r forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (e -> ReaderT r m a
h e
e) r
r
instance (MonadException m) =>
MonadException (Lazy.StateT s m) where
throw :: forall e a. Exception e => e -> StateT s m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
StateT s m a
m catch :: forall e a.
Exception e =>
StateT s m a -> (e -> StateT s m a) -> StateT s m a
`catch` e -> StateT s m a
h = forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Lazy.StateT forall a b. (a -> b) -> a -> b
$ \s
s ->
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
Lazy.runStateT StateT s m a
m s
s forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
Lazy.runStateT (e -> StateT s m a
h e
e) s
s
instance (MonadException m) =>
MonadException (Strict.StateT s m) where
throw :: forall e a. Exception e => e -> StateT s m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
StateT s m a
m catch :: forall e a.
Exception e =>
StateT s m a -> (e -> StateT s m a) -> StateT s m a
`catch` e -> StateT s m a
h = forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Strict.StateT forall a b. (a -> b) -> a -> b
$ \s
s ->
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
Strict.runStateT StateT s m a
m s
s forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
Strict.runStateT (e -> StateT s m a
h e
e) s
s
instance (Monoid w, MonadException m) =>
MonadException (Lazy.WriterT w m) where
throw :: forall e a. Exception e => e -> WriterT w m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
WriterT w m a
m catch :: forall e a.
Exception e =>
WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a
`catch` e -> WriterT w m a
h = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT forall a b. (a -> b) -> a -> b
$
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Lazy.runWriterT WriterT w m a
m forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Lazy.runWriterT (e -> WriterT w m a
h e
e)
instance (Monoid w, MonadException m) =>
MonadException (Strict.WriterT w m) where
throw :: forall e a. Exception e => e -> WriterT w m a
throw = forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
e -> m a
throw
WriterT w m a
m catch :: forall e a.
Exception e =>
WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a
`catch` e -> WriterT w m a
h = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT forall a b. (a -> b) -> a -> b
$
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Strict.runWriterT WriterT w m a
m forall (m :: * -> *) e a.
(MonadException m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e
e -> forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Strict.runWriterT (e -> WriterT w m a
h e
e)
#if !MIN_VERSION_transformers(0,6,0)
instance (MonadAsyncException m, Error e) =>
MonadAsyncException (ErrorT e m) where
mask :: forall b.
((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b)
-> ErrorT e m b
mask (forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b
act = forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT forall a b. (a -> b) -> a -> b
$ (forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b
act (forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ErrorT e m a -> ErrorT e' n b
mapErrorT forall a. m a -> m a
restore)
#endif /* !MIN_VERSION_transformers(0,6,0) */
instance (MonadAsyncException m) =>
MonadAsyncException (ExceptT e' m) where
mask :: forall b.
((forall a. ExceptT e' m a -> ExceptT e' m a) -> ExceptT e' m b)
-> ExceptT e' m b
mask (forall a. ExceptT e' m a -> ExceptT e' m a) -> ExceptT e' m b
act = forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT forall a b. (a -> b) -> a -> b
$ (forall a. ExceptT e' m a -> ExceptT e' m a) -> ExceptT e' m b
act (forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT forall a. m a -> m a
restore)
instance (MonadAsyncException m) =>
MonadAsyncException (IdentityT m) where
mask :: forall b.
((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b)
-> IdentityT m b
mask (forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
act = forall {k} (f :: k -> *) (a :: k). f a -> IdentityT f a
IdentityT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall {k} (f :: k -> *) (a :: k). IdentityT f a -> f a
runIdentityT forall a b. (a -> b) -> a -> b
$ (forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b
act (forall {k1} {k2} (m :: k1 -> *) (a :: k1) (n :: k2 -> *) (b :: k2).
(m a -> n b) -> IdentityT m a -> IdentityT n b
mapIdentityT forall a. m a -> m a
restore)
#if !MIN_VERSION_transformers(0,6,0)
instance (MonadAsyncException m) =>
MonadAsyncException (ListT m) where
mask :: forall b.
((forall a. ListT m a -> ListT m a) -> ListT m b) -> ListT m b
mask (forall a. ListT m a -> ListT m a) -> ListT m b
act = forall (m :: * -> *) a. m [a] -> ListT m a
ListT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall (m :: * -> *) a. ListT m a -> m [a]
runListT forall a b. (a -> b) -> a -> b
$ (forall a. ListT m a -> ListT m a) -> ListT m b
act (forall (m :: * -> *) a (n :: * -> *) b.
(m [a] -> n [b]) -> ListT m a -> ListT n b
mapListT forall a. m a -> m a
restore)
#endif /* !MIN_VERSION_transformers(0,6,0) */
instance (MonadAsyncException m) =>
MonadAsyncException (MaybeT m) where
mask :: forall b.
((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b
mask (forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b
act = forall (m :: * -> *) a. m (Maybe a) -> MaybeT m a
MaybeT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall (m :: * -> *) a. MaybeT m a -> m (Maybe a)
runMaybeT forall a b. (a -> b) -> a -> b
$ (forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b
act (forall (m :: * -> *) a (n :: * -> *) b.
(m (Maybe a) -> n (Maybe b)) -> MaybeT m a -> MaybeT n b
mapMaybeT forall a. m a -> m a
restore)
instance (Monoid w, MonadAsyncException m) =>
MonadAsyncException (Lazy.RWST r w s m) where
mask :: forall b.
((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> RWST r w s m b
mask (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
act = forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Lazy.RWST forall a b. (a -> b) -> a -> b
$ \r
r s
s -> forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
Lazy.runRWST ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
act (forall (m :: * -> *) a s w (n :: * -> *) b w' r.
(m (a, s, w) -> n (b, s, w')) -> RWST r w s m a -> RWST r w' s n b
Lazy.mapRWST forall a. m a -> m a
restore)) r
r s
s
instance (Monoid w, MonadAsyncException m) =>
MonadAsyncException (Strict.RWST r w s m) where
mask :: forall b.
((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b)
-> RWST r w s m b
mask (forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
act = forall r w s (m :: * -> *) a.
(r -> s -> m (a, s, w)) -> RWST r w s m a
Strict.RWST forall a b. (a -> b) -> a -> b
$ \r
r s
s -> forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall r w s (m :: * -> *) a.
RWST r w s m a -> r -> s -> m (a, s, w)
Strict.runRWST ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b
act (forall (m :: * -> *) a s w (n :: * -> *) b w' r.
(m (a, s, w) -> n (b, s, w')) -> RWST r w s m a -> RWST r w' s n b
Strict.mapRWST forall a. m a -> m a
restore)) r
r s
s
instance (MonadAsyncException m) =>
MonadAsyncException (ReaderT r m) where
mask :: forall b.
((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b)
-> ReaderT r m b
mask (forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
act = forall r (m :: * -> *) a. (r -> m a) -> ReaderT r m a
ReaderT forall a b. (a -> b) -> a -> b
$ \r
r -> forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b
act (forall (m :: * -> *) a (n :: * -> *) b r.
(m a -> n b) -> ReaderT r m a -> ReaderT r n b
mapReaderT forall a. m a -> m a
restore)) r
r
instance (MonadAsyncException m) =>
MonadAsyncException (Lazy.StateT s m) where
mask :: forall b.
((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> StateT s m b
mask (forall a. StateT s m a -> StateT s m a) -> StateT s m b
act = forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Lazy.StateT forall a b. (a -> b) -> a -> b
$ \s
s -> forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
Lazy.runStateT ((forall a. StateT s m a -> StateT s m a) -> StateT s m b
act (forall (m :: * -> *) a s (n :: * -> *) b.
(m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
Lazy.mapStateT forall a. m a -> m a
restore)) s
s
instance (MonadAsyncException m) =>
MonadAsyncException (Strict.StateT s m) where
mask :: forall b.
((forall a. StateT s m a -> StateT s m a) -> StateT s m b)
-> StateT s m b
mask (forall a. StateT s m a -> StateT s m a) -> StateT s m b
act = forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
Strict.StateT forall a b. (a -> b) -> a -> b
$ \s
s -> forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
Strict.runStateT ((forall a. StateT s m a -> StateT s m a) -> StateT s m b
act (forall (m :: * -> *) a s (n :: * -> *) b.
(m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
Strict.mapStateT forall a. m a -> m a
restore)) s
s
instance (Monoid w, MonadAsyncException m) =>
MonadAsyncException (Lazy.WriterT w m) where
mask :: forall b.
((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> WriterT w m b
mask (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
act = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Lazy.WriterT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Lazy.runWriterT forall a b. (a -> b) -> a -> b
$ (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
act (forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
Lazy.mapWriterT forall a. m a -> m a
restore)
instance (Monoid w, MonadAsyncException m) =>
MonadAsyncException (Strict.WriterT w m) where
mask :: forall b.
((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b)
-> WriterT w m b
mask (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
act = forall w (m :: * -> *) a. m (a, w) -> WriterT w m a
Strict.WriterT forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b.
MonadAsyncException m =>
((forall a. m a -> m a) -> m b) -> m b
mask forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore ->
forall w (m :: * -> *) a. WriterT w m a -> m (a, w)
Strict.runWriterT forall a b. (a -> b) -> a -> b
$ (forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b
act (forall (m :: * -> *) a w (n :: * -> *) b w'.
(m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b
Strict.mapWriterT forall a. m a -> m a
restore)