{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
module Control.Monad.Trans.Either (
EitherT
, pattern EitherT
, newEitherT
, runEitherT
, eitherT
, left
, right
, mapEitherT
, hoistEither
, bimapEitherT
, firstEitherT
, secondEitherT
, hoistMaybe
, hoistEitherT
, handleIOEitherT
, handleEitherT
, handlesEitherT
, handleLeftT
, catchIOEitherT
, catchEitherT
, catchesEitherT
, catchLeftT
, bracketEitherT
, bracketExceptionT
) where
import Control.Exception (Exception, IOException, SomeException)
import qualified Control.Exception as Exception
import Control.Monad (Monad(..), (=<<))
import Control.Monad.Catch (Handler (..), MonadCatch, MonadMask, catchAll, mask, throwM)
import qualified Control.Monad.Catch as Catch
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Except (ExceptT(..))
import Data.Maybe (Maybe, maybe)
import Data.Either (Either(..), either)
import Data.Foldable (Foldable, foldr)
import Data.Function (($), (.), const, id, flip)
import Data.Functor (Functor(..))
import System.IO (IO)
type EitherT = ExceptT
pattern EitherT :: m (Either x a) -> ExceptT x m a
pattern $bEitherT :: m (Either x a) -> ExceptT x m a
$mEitherT :: forall r (m :: * -> *) x a.
ExceptT x m a -> (m (Either x a) -> r) -> (Void# -> r) -> r
EitherT m = ExceptT m
runEitherT :: EitherT x m a -> m (Either x a)
runEitherT :: EitherT x m a -> m (Either x a)
runEitherT (ExceptT m (Either x a)
m) = m (Either x a)
m
{-# INLINE runEitherT #-}
newEitherT :: m (Either x a) -> EitherT x m a
newEitherT :: m (Either x a) -> EitherT x m a
newEitherT =
m (Either x a) -> EitherT x m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT
{-# INLINE newEitherT #-}
eitherT :: Monad m => (x -> m b) -> (a -> m b) -> EitherT x m a -> m b
eitherT :: (x -> m b) -> (a -> m b) -> EitherT x m a -> m b
eitherT x -> m b
f a -> m b
g EitherT x m a
m =
(x -> m b) -> (a -> m b) -> Either x a -> m b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either x -> m b
f a -> m b
g (Either x a -> m b) -> m (Either x a) -> m b
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< EitherT x m a -> m (Either x a)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT EitherT x m a
m
{-# INLINE eitherT #-}
left :: Monad m => x -> EitherT x m a
left :: x -> EitherT x m a
left =
m (Either x a) -> EitherT x m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
EitherT (m (Either x a) -> EitherT x m a)
-> (x -> m (Either x a)) -> x -> EitherT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either x a -> m (Either x a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either x a -> m (Either x a))
-> (x -> Either x a) -> x -> m (Either x a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. x -> Either x a
forall a b. a -> Either a b
Left
{-# INLINE left #-}
right :: Monad m => a -> EitherT x m a
right :: a -> EitherT x m a
right =
a -> EitherT x m a
forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE right #-}
mapEitherT :: (m (Either x a) -> n (Either y b)) -> EitherT x m a -> EitherT y n b
mapEitherT :: (m (Either x a) -> n (Either y b))
-> EitherT x m a -> EitherT y n b
mapEitherT m (Either x a) -> n (Either y b)
f =
n (Either y b) -> EitherT y n b
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
EitherT (n (Either y b) -> EitherT y n b)
-> (EitherT x m a -> n (Either y b))
-> EitherT x m a
-> EitherT y n b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either x a) -> n (Either y b)
f (m (Either x a) -> n (Either y b))
-> (EitherT x m a -> m (Either x a))
-> EitherT x m a
-> n (Either y b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EitherT x m a -> m (Either x a)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT
{-# INLINE mapEitherT #-}
hoistEither :: Monad m => Either x a -> EitherT x m a
hoistEither :: Either x a -> EitherT x m a
hoistEither =
m (Either x a) -> EitherT x m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
EitherT (m (Either x a) -> EitherT x m a)
-> (Either x a -> m (Either x a)) -> Either x a -> EitherT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either x a -> m (Either x a)
forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE hoistEither #-}
bimapEitherT :: Functor m => (x -> y) -> (a -> b) -> EitherT x m a -> EitherT y m b
bimapEitherT :: (x -> y) -> (a -> b) -> EitherT x m a -> EitherT y m b
bimapEitherT x -> y
f a -> b
g =
let
h :: Either x a -> Either y b
h (Left x
e) = y -> Either y b
forall a b. a -> Either a b
Left (x -> y
f x
e)
h (Right a
a) = b -> Either y b
forall a b. b -> Either a b
Right (a -> b
g a
a)
in
(m (Either x a) -> m (Either y b))
-> EitherT x m a -> EitherT y m b
forall (m :: * -> *) x a (n :: * -> *) y b.
(m (Either x a) -> n (Either y b))
-> EitherT x m a -> EitherT y n b
mapEitherT ((Either x a -> Either y b) -> m (Either x a) -> m (Either y b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Either x a -> Either y b
h)
{-# INLINE bimapEitherT #-}
firstEitherT :: Functor m => (x -> y) -> EitherT x m a -> EitherT y m a
firstEitherT :: (x -> y) -> EitherT x m a -> EitherT y m a
firstEitherT x -> y
f =
(x -> y) -> (a -> a) -> EitherT x m a -> EitherT y m a
forall (m :: * -> *) x y a b.
Functor m =>
(x -> y) -> (a -> b) -> EitherT x m a -> EitherT y m b
bimapEitherT x -> y
f a -> a
forall a. a -> a
id
{-# INLINE firstEitherT #-}
secondEitherT :: Functor m => (a -> b) -> EitherT x m a -> EitherT x m b
secondEitherT :: (a -> b) -> EitherT x m a -> EitherT x m b
secondEitherT =
(x -> x) -> (a -> b) -> EitherT x m a -> EitherT x m b
forall (m :: * -> *) x y a b.
Functor m =>
(x -> y) -> (a -> b) -> EitherT x m a -> EitherT y m b
bimapEitherT x -> x
forall a. a -> a
id
{-# INLINE secondEitherT #-}
hoistMaybe :: Monad m => x -> Maybe a -> EitherT x m a
hoistMaybe :: x -> Maybe a -> EitherT x m a
hoistMaybe x
x =
EitherT x m a -> (a -> EitherT x m a) -> Maybe a -> EitherT x m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (x -> EitherT x m a
forall (m :: * -> *) x a. Monad m => x -> EitherT x m a
left x
x) a -> EitherT x m a
forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE hoistMaybe #-}
hoistEitherT :: (forall b. m b -> n b) -> EitherT x m a -> EitherT x n a
hoistEitherT :: (forall b. m b -> n b) -> EitherT x m a -> EitherT x n a
hoistEitherT forall b. m b -> n b
f =
n (Either x a) -> EitherT x n a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
EitherT (n (Either x a) -> EitherT x n a)
-> (EitherT x m a -> n (Either x a))
-> EitherT x m a
-> EitherT x n a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either x a) -> n (Either x a)
forall b. m b -> n b
f (m (Either x a) -> n (Either x a))
-> (EitherT x m a -> m (Either x a))
-> EitherT x m a
-> n (Either x a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EitherT x m a -> m (Either x a)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT
{-# INLINE hoistEitherT #-}
handleIOEitherT :: MonadIO m => (IOException -> x) -> IO a -> EitherT x m a
handleIOEitherT :: (IOException -> x) -> IO a -> EitherT x m a
handleIOEitherT IOException -> x
wrap =
(IOException -> x) -> EitherT IOException m a -> EitherT x m a
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> EitherT x m a -> EitherT y m a
firstEitherT IOException -> x
wrap (EitherT IOException m a -> EitherT x m a)
-> (IO a -> EitherT IOException m a) -> IO a -> EitherT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either IOException a) -> EitherT IOException m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newEitherT (m (Either IOException a) -> EitherT IOException m a)
-> (IO a -> m (Either IOException a))
-> IO a
-> EitherT IOException m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO (Either IOException a) -> m (Either IOException a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either IOException a) -> m (Either IOException a))
-> (IO a -> IO (Either IOException a))
-> IO a
-> m (Either IOException a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> IO (Either IOException a)
forall e a. Exception e => IO a -> IO (Either e a)
Exception.try
{-# INLINE handleIOEitherT #-}
catchIOEitherT :: MonadIO m => IO a -> (IOException -> x) -> EitherT x m a
catchIOEitherT :: IO a -> (IOException -> x) -> EitherT x m a
catchIOEitherT = ((IOException -> x) -> IO a -> EitherT x m a)
-> IO a -> (IOException -> x) -> EitherT x m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (IOException -> x) -> IO a -> EitherT x m a
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> EitherT x m a
handleIOEitherT
{-# INLINE catchIOEitherT #-}
handleEitherT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> EitherT x m a
handleEitherT :: (e -> x) -> m a -> EitherT x m a
handleEitherT e -> x
wrap =
(e -> x) -> EitherT e m a -> EitherT x m a
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> EitherT x m a -> EitherT y m a
firstEitherT e -> x
wrap (EitherT e m a -> EitherT x m a)
-> (m a -> EitherT e m a) -> m a -> EitherT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either e a) -> EitherT e m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newEitherT (m (Either e a) -> EitherT e m a)
-> (m a -> m (Either e a)) -> m a -> EitherT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m a -> m (Either e a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> m (Either e a)
Catch.try
{-# INLINE handleEitherT #-}
catchEitherT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> EitherT x m a
catchEitherT :: m a -> (e -> x) -> EitherT x m a
catchEitherT = ((e -> x) -> m a -> EitherT x m a)
-> m a -> (e -> x) -> EitherT x m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (e -> x) -> m a -> EitherT x m a
forall (m :: * -> *) e x a.
(MonadCatch m, Exception e) =>
(e -> x) -> m a -> EitherT x m a
handleEitherT
{-# INLINE catchEitherT #-}
handlesEitherT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> EitherT x m a
handlesEitherT :: f (Handler m x) -> m a -> EitherT x m a
handlesEitherT f (Handler m x)
wrappers m a
action =
m (Either x a) -> EitherT x m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newEitherT ((a -> Either x a) -> m a -> m (Either x a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Either x a
forall a b. b -> Either a b
Right m a
action m (Either x a)
-> (SomeException -> m (Either x a)) -> m (Either x a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`Catch.catch` (m x -> m (Either x a))
-> (SomeException -> m x) -> SomeException -> m (Either x a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((x -> Either x a) -> m x -> m (Either x a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap x -> Either x a
forall a b. a -> Either a b
Left) SomeException -> m x
handler)
where
handler :: SomeException -> m x
handler SomeException
e =
let probe :: Handler m a -> m a -> m a
probe (Handler e -> m a
h) m a
xs =
m a -> (e -> m a) -> Maybe e -> m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m a
xs e -> m a
h (SomeException -> Maybe e
forall e. Exception e => SomeException -> Maybe e
Exception.fromException SomeException
e)
in
(Handler m x -> m x -> m x) -> m x -> f (Handler m x) -> m x
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Handler m x -> m x -> m x
forall (m :: * -> *) a. Handler m a -> m a -> m a
probe (SomeException -> m x
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
Catch.throwM SomeException
e) f (Handler m x)
wrappers
catchesEitherT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> EitherT x m a
catchesEitherT :: m a -> f (Handler m x) -> EitherT x m a
catchesEitherT = (f (Handler m x) -> m a -> EitherT x m a)
-> m a -> f (Handler m x) -> EitherT x m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip f (Handler m x) -> m a -> EitherT x m a
forall (f :: * -> *) (m :: * -> *) x a.
(Foldable f, MonadCatch m) =>
f (Handler m x) -> m a -> EitherT x m a
handlesEitherT
{-# INLINE catchesEitherT #-}
handleLeftT :: Monad m => (e -> EitherT e m a) -> EitherT e m a -> EitherT e m a
handleLeftT :: (e -> EitherT e m a) -> EitherT e m a -> EitherT e m a
handleLeftT e -> EitherT e m a
handler EitherT e m a
thing = do
Either e a
r <- m (Either e a) -> ExceptT e m (Either e a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m (Either e a) -> ExceptT e m (Either e a))
-> m (Either e a) -> ExceptT e m (Either e a)
forall a b. (a -> b) -> a -> b
$ EitherT e m a -> m (Either e a)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT EitherT e m a
thing
case Either e a
r of
Left e
e ->
e -> EitherT e m a
handler e
e
Right a
a ->
a -> EitherT e m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
{-# INLINE handleLeftT #-}
catchLeftT :: Monad m => EitherT e m a -> (e -> EitherT e m a) -> EitherT e m a
catchLeftT :: EitherT e m a -> (e -> EitherT e m a) -> EitherT e m a
catchLeftT = ((e -> EitherT e m a) -> EitherT e m a -> EitherT e m a)
-> EitherT e m a -> (e -> EitherT e m a) -> EitherT e m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (e -> EitherT e m a) -> EitherT e m a -> EitherT e m a
forall (m :: * -> *) e a.
Monad m =>
(e -> EitherT e m a) -> EitherT e m a -> EitherT e m a
handleLeftT
{-# INLINE catchLeftT #-}
bracketEitherT :: Monad m => EitherT e m a -> (a -> EitherT e m b) -> (a -> EitherT e m c) -> EitherT e m c
bracketEitherT :: EitherT e m a
-> (a -> EitherT e m b) -> (a -> EitherT e m c) -> EitherT e m c
bracketEitherT EitherT e m a
before a -> EitherT e m b
after a -> EitherT e m c
thing = do
a
a <- EitherT e m a
before
c
r <- (\e
err -> a -> EitherT e m b
after a
a EitherT e m b -> EitherT e m c -> EitherT e m c
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> e -> EitherT e m c
forall (m :: * -> *) x a. Monad m => x -> EitherT x m a
left e
err) (e -> EitherT e m c) -> EitherT e m c -> EitherT e m c
forall (m :: * -> *) e a.
Monad m =>
(e -> EitherT e m a) -> EitherT e m a -> EitherT e m a
`handleLeftT` a -> EitherT e m c
thing a
a
b
_ <- a -> EitherT e m b
after a
a
c -> EitherT e m c
forall (m :: * -> *) a. Monad m => a -> m a
return c
r
{-# INLINE bracketEitherT #-}
bracketExceptionT ::
MonadMask m
=> EitherT e m a
-> (a -> EitherT e m c)
-> (a -> EitherT e m b)
-> EitherT e m b
bracketExceptionT :: EitherT e m a
-> (a -> EitherT e m c) -> (a -> EitherT e m b) -> EitherT e m b
bracketExceptionT EitherT e m a
acquire a -> EitherT e m c
release a -> EitherT e m b
run =
m (Either e b) -> EitherT e m b
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
EitherT (m (Either e b) -> EitherT e m b)
-> m (Either e b) -> EitherT e m b
forall a b. (a -> b) -> a -> b
$ m (Either e a)
-> (Either e a -> m (Either (Either e b) ()))
-> (Either e a -> m (Either e b))
-> m (Either e b)
forall (m :: * -> *) a b c.
MonadMask m =>
m a -> (a -> m (Either b c)) -> (a -> m b) -> m b
bracketF
(EitherT e m a -> m (Either e a)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT EitherT e m a
acquire)
(\Either e a
r -> case Either e a
r of
Left e
_ ->
Either (Either e b) () -> m (Either (Either e b) ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either (Either e b) () -> m (Either (Either e b) ()))
-> (() -> Either (Either e b) ())
-> ()
-> m (Either (Either e b) ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. () -> Either (Either e b) ()
forall a b. b -> Either a b
Right (() -> m (Either (Either e b) ()))
-> () -> m (Either (Either e b) ())
forall a b. (a -> b) -> a -> b
$ ()
Right a
r' ->
EitherT e m c -> m (Either e c)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT (a -> EitherT e m c
release a
r') m (Either e c)
-> (Either e c -> m (Either (Either e b) ()))
-> m (Either (Either e b) ())
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Either e c
x -> Either (Either e b) () -> m (Either (Either e b) ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Either (Either e b) () -> m (Either (Either e b) ()))
-> Either (Either e b) () -> m (Either (Either e b) ())
forall a b. (a -> b) -> a -> b
$ case Either e c
x of
Left e
err -> Either e b -> Either (Either e b) ()
forall a b. a -> Either a b
Left (e -> Either e b
forall a b. a -> Either a b
Left e
err)
Right c
_ -> () -> Either (Either e b) ()
forall a b. b -> Either a b
Right ())
(\Either e a
r -> case Either e a
r of
Left e
err ->
Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either e b -> m (Either e b))
-> (e -> Either e b) -> e -> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e b
forall a b. a -> Either a b
Left (e -> m (Either e b)) -> e -> m (Either e b)
forall a b. (a -> b) -> a -> b
$ e
err
Right a
r' ->
EitherT e m b -> m (Either e b)
forall x (m :: * -> *) a. EitherT x m a -> m (Either x a)
runEitherT (a -> EitherT e m b
run a
r'))
{-# INLINE bracketExceptionT #-}
data BracketResult a =
BracketOk a
| BracketFailedFinalizerOk SomeException
| BracketFailedFinalizerError a
bracketF :: MonadMask m => m a -> (a -> m (Either b c)) -> (a -> m b) -> m b
bracketF :: m a -> (a -> m (Either b c)) -> (a -> m b) -> m b
bracketF m a
a a -> m (Either b c)
f a -> m b
g =
((forall a. m a -> m a) -> m b) -> m b
forall (m :: * -> *) b.
MonadMask m =>
((forall a. m a -> m a) -> m b) -> m b
mask (((forall a. m a -> m a) -> m b) -> m b)
-> ((forall a. m a -> m a) -> m b) -> m b
forall a b. (a -> b) -> a -> b
$ \forall a. m a -> m a
restore -> do
a
a' <- m a
a
BracketResult b
x <- m (BracketResult b) -> m (BracketResult b)
forall a. m a -> m a
restore (b -> BracketResult b
forall a. a -> BracketResult a
BracketOk (b -> BracketResult b) -> m b -> m (BracketResult b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` a -> m b
g a
a') m (BracketResult b)
-> (SomeException -> m (BracketResult b)) -> m (BracketResult b)
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
`catchAll`
(\SomeException
ex -> (b -> BracketResult b)
-> (c -> BracketResult b) -> Either b c -> BracketResult b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either b -> BracketResult b
forall a. a -> BracketResult a
BracketFailedFinalizerError (BracketResult b -> c -> BracketResult b
forall a b. a -> b -> a
const (BracketResult b -> c -> BracketResult b)
-> BracketResult b -> c -> BracketResult b
forall a b. (a -> b) -> a -> b
$ SomeException -> BracketResult b
forall a. SomeException -> BracketResult a
BracketFailedFinalizerOk SomeException
ex) (Either b c -> BracketResult b)
-> m (Either b c) -> m (BracketResult b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` a -> m (Either b c)
f a
a')
case BracketResult b
x of
BracketFailedFinalizerOk SomeException
ex ->
SomeException -> m b
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM SomeException
ex
BracketFailedFinalizerError b
b ->
b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
return b
b
BracketOk b
b -> do
Either b c
z <- a -> m (Either b c)
f a
a'
b -> m b
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> m b) -> b -> m b
forall a b. (a -> b) -> a -> b
$ (b -> b) -> (c -> b) -> Either b c -> b
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either b -> b
forall a. a -> a
id (b -> c -> b
forall a b. a -> b -> a
const b
b) Either b c
z
{-# INLINE bracketF #-}