{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
module Control.Monad.Trans.Except.Extra (
newExceptT
, runExceptT
, exceptT
, left
, right
, mapExceptT
, hoistEither
, bimapExceptT
, firstExceptT
, secondExceptT
, hoistMaybe
, hoistExceptT
, handleIOExceptT
, handleExceptT
, handlesExceptT
, handleLeftT
, catchIOExceptT
, catchExceptT
, catchesExceptT
, catchLeftT
, bracketExceptT
, bracketExceptionT
, hushM
) 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
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)
newExceptT :: m (Either x a) -> ExceptT x m a
newExceptT :: m (Either x a) -> ExceptT x m a
newExceptT =
m (Either x a) -> ExceptT x m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT
{-# INLINE newExceptT #-}
exceptT :: Monad m => (x -> m b) -> (a -> m b) -> ExceptT x m a -> m b
exceptT :: (x -> m b) -> (a -> m b) -> ExceptT x m a -> m b
exceptT x -> m b
f a -> m b
g ExceptT 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
=<< ExceptT x m a -> m (Either x a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT x m a
m
{-# INLINE exceptT #-}
left :: Monad m => x -> ExceptT x m a
left :: x -> ExceptT x m a
left =
m (Either x a) -> ExceptT x m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either x a) -> ExceptT x m a)
-> (x -> m (Either x a)) -> x -> ExceptT 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 -> ExceptT x m a
right :: a -> ExceptT x m a
right =
a -> ExceptT x m a
forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE right #-}
hoistEither :: Monad m => Either x a -> ExceptT x m a
hoistEither :: Either x a -> ExceptT x m a
hoistEither =
m (Either x a) -> ExceptT x m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either x a) -> ExceptT x m a)
-> (Either x a -> m (Either x a)) -> Either x a -> ExceptT 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 #-}
bimapExceptT :: Functor m => (x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b
bimapExceptT :: (x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b
bimapExceptT 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))
-> ExceptT x m a -> ExceptT y m b
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT ((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 bimapExceptT #-}
firstExceptT :: Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT :: (x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT x -> y
f =
(x -> y) -> (a -> a) -> ExceptT x m a -> ExceptT y m a
forall (m :: * -> *) x y a b.
Functor m =>
(x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b
bimapExceptT x -> y
f a -> a
forall a. a -> a
id
{-# INLINE firstExceptT #-}
secondExceptT :: Functor m => (a -> b) -> ExceptT x m a -> ExceptT x m b
secondExceptT :: (a -> b) -> ExceptT x m a -> ExceptT x m b
secondExceptT =
(x -> x) -> (a -> b) -> ExceptT x m a -> ExceptT x m b
forall (m :: * -> *) x y a b.
Functor m =>
(x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b
bimapExceptT x -> x
forall a. a -> a
id
{-# INLINE secondExceptT #-}
hoistMaybe :: Monad m => x -> Maybe a -> ExceptT x m a
hoistMaybe :: x -> Maybe a -> ExceptT x m a
hoistMaybe x
x =
ExceptT x m a -> (a -> ExceptT x m a) -> Maybe a -> ExceptT x m a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (x -> ExceptT x m a
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left x
x) a -> ExceptT x m a
forall (m :: * -> *) a. Monad m => a -> m a
return
{-# INLINE hoistMaybe #-}
hoistExceptT :: (forall b. m b -> n b) -> ExceptT x m a -> ExceptT x n a
hoistExceptT :: (forall b. m b -> n b) -> ExceptT x m a -> ExceptT x n a
hoistExceptT forall b. m b -> n b
f =
n (Either x a) -> ExceptT x n a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (n (Either x a) -> ExceptT x n a)
-> (ExceptT x m a -> n (Either x a))
-> ExceptT x m a
-> ExceptT 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))
-> (ExceptT x m a -> m (Either x a))
-> ExceptT x m a
-> n (Either x a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT x m a -> m (Either x a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
{-# INLINE hoistExceptT #-}
handleIOExceptT :: MonadIO m => (IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT :: (IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT IOException -> x
wrap =
(IOException -> x) -> ExceptT IOException m a -> ExceptT x m a
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT IOException -> x
wrap (ExceptT IOException m a -> ExceptT x m a)
-> (IO a -> ExceptT IOException m a) -> IO a -> ExceptT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either IOException a) -> ExceptT IOException m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (m (Either IOException a) -> ExceptT IOException m a)
-> (IO a -> m (Either IOException a))
-> IO a
-> ExceptT 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 handleIOExceptT #-}
catchIOExceptT :: MonadIO m => IO a -> (IOException -> x) -> ExceptT x m a
catchIOExceptT :: IO a -> (IOException -> x) -> ExceptT x m a
catchIOExceptT = ((IOException -> x) -> IO a -> ExceptT x m a)
-> IO a -> (IOException -> x) -> ExceptT x m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (IOException -> x) -> IO a -> ExceptT x m a
forall (m :: * -> *) x a.
MonadIO m =>
(IOException -> x) -> IO a -> ExceptT x m a
handleIOExceptT
{-# INLINE catchIOExceptT #-}
handleExceptT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> ExceptT x m a
handleExceptT :: (e -> x) -> m a -> ExceptT x m a
handleExceptT e -> x
wrap =
(e -> x) -> ExceptT e m a -> ExceptT x m a
forall (m :: * -> *) x y a.
Functor m =>
(x -> y) -> ExceptT x m a -> ExceptT y m a
firstExceptT e -> x
wrap (ExceptT e m a -> ExceptT x m a)
-> (m a -> ExceptT e m a) -> m a -> ExceptT x m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m (Either e a) -> ExceptT e m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT (m (Either e a) -> ExceptT e m a)
-> (m a -> m (Either e a)) -> m a -> ExceptT 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 handleExceptT #-}
catchExceptT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> ExceptT x m a
catchExceptT :: m a -> (e -> x) -> ExceptT x m a
catchExceptT = ((e -> x) -> m a -> ExceptT x m a)
-> m a -> (e -> x) -> ExceptT x m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (e -> x) -> m a -> ExceptT x m a
forall (m :: * -> *) e x a.
(MonadCatch m, Exception e) =>
(e -> x) -> m a -> ExceptT x m a
handleExceptT
{-# INLINE catchExceptT #-}
handlesExceptT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> ExceptT x m a
handlesExceptT :: f (Handler m x) -> m a -> ExceptT x m a
handlesExceptT f (Handler m x)
wrappers m a
action =
m (Either x a) -> ExceptT x m a
forall (m :: * -> *) x a. m (Either x a) -> ExceptT x m a
newExceptT ((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
catchesExceptT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> ExceptT x m a
catchesExceptT :: m a -> f (Handler m x) -> ExceptT x m a
catchesExceptT = (f (Handler m x) -> m a -> ExceptT x m a)
-> m a -> f (Handler m x) -> ExceptT x m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip f (Handler m x) -> m a -> ExceptT x m a
forall (f :: * -> *) (m :: * -> *) x a.
(Foldable f, MonadCatch m) =>
f (Handler m x) -> m a -> ExceptT x m a
handlesExceptT
{-# INLINE catchesExceptT #-}
handleLeftT :: Monad m => (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
handleLeftT :: (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
handleLeftT e -> ExceptT e m a
handler ExceptT 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
$ ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT e m a
thing
case Either e a
r of
Left e
e ->
e -> ExceptT e m a
handler e
e
Right a
a ->
a -> ExceptT e m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
{-# INLINE handleLeftT #-}
catchLeftT :: Monad m => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a
catchLeftT :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a
catchLeftT = ((e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a)
-> ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
forall (m :: * -> *) e a.
Monad m =>
(e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
handleLeftT
{-# INLINE catchLeftT #-}
bracketExceptT :: Monad m => ExceptT e m a -> (a -> ExceptT e m b) -> (a -> ExceptT e m c) -> ExceptT e m c
bracketExceptT :: ExceptT e m a
-> (a -> ExceptT e m b) -> (a -> ExceptT e m c) -> ExceptT e m c
bracketExceptT ExceptT e m a
before a -> ExceptT e m b
after a -> ExceptT e m c
thing = do
a
a <- ExceptT e m a
before
c
r <- (\e
err -> a -> ExceptT e m b
after a
a ExceptT e m b -> ExceptT e m c -> ExceptT e m c
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> e -> ExceptT e m c
forall (m :: * -> *) x a. Monad m => x -> ExceptT x m a
left e
err) (e -> ExceptT e m c) -> ExceptT e m c -> ExceptT e m c
forall (m :: * -> *) e a.
Monad m =>
(e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
`handleLeftT` a -> ExceptT e m c
thing a
a
b
_ <- a -> ExceptT e m b
after a
a
c -> ExceptT e m c
forall (m :: * -> *) a. Monad m => a -> m a
return c
r
{-# INLINE bracketExceptT #-}
bracketExceptionT ::
MonadMask m
=> ExceptT e m a
-> (a -> ExceptT e m c)
-> (a -> ExceptT e m b)
-> ExceptT e m b
bracketExceptionT :: ExceptT e m a
-> (a -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m b
bracketExceptionT ExceptT e m a
acquire a -> ExceptT e m c
release a -> ExceptT e m b
run =
m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> m (Either e b) -> ExceptT 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
(ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT 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' ->
ExceptT e m c -> m (Either e c)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (a -> ExceptT 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' ->
ExceptT e m b -> m (Either e b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (a -> ExceptT 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 #-}
hushM :: Monad m => Either e a -> (e -> m ()) -> m (Maybe a)
hushM :: Either e a -> (e -> m ()) -> m (Maybe a)
hushM Either e a
r e -> m ()
f = case Either e a
r of
Right a
a -> Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Maybe a
forall a. a -> Maybe a
Just a
a)
Left e
e -> e -> m ()
f e
e m () -> m (Maybe a) -> m (Maybe a)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe a -> m (Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing
{-# INLINE hushM #-}