-- | Extend a monad with the ability to terminate a computation with a value module Mini.Transformers.EitherT ( -- * Type EitherT ( EitherT ), -- * Runner runEitherT, -- * Operations left, anticipate, ) where import Control.Applicative ( Alternative, empty, (<|>), ) import Control.Monad ( ap, liftM, (>=>), ) import Control.Monad.IO.Class ( MonadIO, liftIO, ) import Mini.Transformers.Class ( MonadTrans, lift, ) import Prelude ( Applicative, Either ( Left, Right ), Functor, Monad, MonadFail, Monoid, either, fail, fmap, mappend, mempty, pure, ($), (.), (<$>), (<*>), (>>=), ) {- - Type -} -- | A terminable transformer with termination /e/, inner monad /m/, return /a/ newtype EitherT e m a = EitherT { runEitherT :: m (Either e a) -- ^ Unwrap an 'EitherT' computation } instance (Monad m) => Functor (EitherT e m) where fmap = liftM instance (Monad m) => Applicative (EitherT e m) where pure = EitherT . pure . Right (<*>) = ap instance (Monad m, Monoid e) => Alternative (EitherT e m) where empty = EitherT . pure $ Left mempty m <|> n = EitherT $ runEitherT m >>= either (\e -> either (Left . mappend e) Right <$> runEitherT n) (pure . Right) instance (Monad m) => Monad (EitherT e m) where m >>= k = EitherT $ runEitherT m >>= either (pure . Left) (runEitherT . k) instance MonadTrans (EitherT e) where lift = EitherT . fmap Right instance (MonadFail m) => MonadFail (EitherT e m) where fail = EitherT . fail instance (MonadIO m) => MonadIO (EitherT e m) where liftIO = lift . liftIO {- - Operations -} -- | Terminate the computation with a value left :: (Monad m) => e -> EitherT e m a left = EitherT . pure . Left -- | Run a computation and get its result anticipate :: (Monad m) => EitherT e m a -> EitherT e m (Either e a) anticipate = lift . runEitherT . (Right <$>) >=> either (pure . Left) pure