{-# 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 EitherT m = ExceptT m
runEitherT :: EitherT x m a -> m (Either x a)
runEitherT (ExceptT m) = m
{-# INLINE runEitherT #-}
newEitherT :: m (Either x a) -> EitherT x m a
newEitherT =
ExceptT
{-# INLINE newEitherT #-}
eitherT :: Monad m => (x -> m b) -> (a -> m b) -> EitherT x m a -> m b
eitherT f g m =
either f g =<< runEitherT m
{-# INLINE eitherT #-}
left :: Monad m => x -> EitherT x m a
left =
EitherT . return . Left
{-# INLINE left #-}
right :: Monad m => a -> EitherT x m a
right =
return
{-# INLINE right #-}
mapEitherT :: (m (Either x a) -> n (Either y b)) -> EitherT x m a -> EitherT y n b
mapEitherT f =
EitherT . f . runEitherT
{-# INLINE mapEitherT #-}
hoistEither :: Monad m => Either x a -> EitherT x m a
hoistEither =
EitherT . return
{-# INLINE hoistEither #-}
bimapEitherT :: Functor m => (x -> y) -> (a -> b) -> EitherT x m a -> EitherT y m b
bimapEitherT f g =
let
h (Left e) = Left (f e)
h (Right a) = Right (g a)
in
mapEitherT (fmap h)
{-# INLINE bimapEitherT #-}
firstEitherT :: Functor m => (x -> y) -> EitherT x m a -> EitherT y m a
firstEitherT f =
bimapEitherT f id
{-# INLINE firstEitherT #-}
secondEitherT :: Functor m => (a -> b) -> EitherT x m a -> EitherT x m b
secondEitherT =
bimapEitherT id
{-# INLINE secondEitherT #-}
hoistMaybe :: Monad m => x -> Maybe a -> EitherT x m a
hoistMaybe x =
maybe (left x) return
{-# INLINE hoistMaybe #-}
hoistEitherT :: (forall b. m b -> n b) -> EitherT x m a -> EitherT x n a
hoistEitherT f =
EitherT . f . runEitherT
{-# INLINE hoistEitherT #-}
handleIOEitherT :: MonadIO m => (IOException -> x) -> IO a -> EitherT x m a
handleIOEitherT wrap =
firstEitherT wrap . newEitherT . liftIO . Exception.try
{-# INLINE handleIOEitherT #-}
catchIOEitherT :: MonadIO m => IO a -> (IOException -> x) -> EitherT x m a
catchIOEitherT = flip handleIOEitherT
{-# INLINE catchIOEitherT #-}
handleEitherT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> EitherT x m a
handleEitherT wrap =
firstEitherT wrap . newEitherT . Catch.try
{-# INLINE handleEitherT #-}
catchEitherT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> EitherT x m a
catchEitherT = flip handleEitherT
{-# INLINE catchEitherT #-}
handlesEitherT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> EitherT x m a
handlesEitherT wrappers action =
newEitherT (fmap Right action `Catch.catch` fmap (fmap Left) handler)
where
handler e =
let probe (Handler h) xs =
maybe xs h (Exception.fromException e)
in
foldr probe (Catch.throwM e) wrappers
catchesEitherT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> EitherT x m a
catchesEitherT = flip handlesEitherT
{-# INLINE catchesEitherT #-}
handleLeftT :: Monad m => (e -> EitherT e m a) -> EitherT e m a -> EitherT e m a
handleLeftT handler thing = do
r <- lift $ runEitherT thing
case r of
Left e ->
handler e
Right a ->
return a
{-# INLINE handleLeftT #-}
catchLeftT :: Monad m => EitherT e m a -> (e -> EitherT e m a) -> EitherT e m a
catchLeftT = flip 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 before after thing = do
a <- before
r <- (\err -> after a >> left err) `handleLeftT` thing a
_ <- after a
return 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 acquire release run =
EitherT $ bracketF
(runEitherT acquire)
(\r -> case r of
Left _ ->
return . Right $ ()
Right r' ->
runEitherT (release r') >>= \x -> return $ case x of
Left err -> Left (Left err)
Right _ -> Right ())
(\r -> case r of
Left err ->
return . Left $ err
Right r' ->
runEitherT (run 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 a f g =
mask $ \restore -> do
a' <- a
x <- restore (BracketOk `fmap` g a') `catchAll`
(\ex -> either BracketFailedFinalizerError (const $ BracketFailedFinalizerOk ex) `fmap` f a')
case x of
BracketFailedFinalizerOk ex ->
throwM ex
BracketFailedFinalizerError b ->
return b
BracketOk b -> do
z <- f a'
return $ either id (const b) z
{-# INLINE bracketF #-}