{-# LANGUAGE CPP #-}
module Data.EitherR (
EitherR(..),
succeed,
throwEither,
catchEither,
handleEither,
fmapL,
flipEither,
ExceptRT(..),
succeedT,
handleE,
fmapLT,
flipET,
) where
import Control.Applicative (Applicative(pure, (<*>)), Alternative(empty, (<|>)))
import Control.Monad (liftM, ap, MonadPlus(mzero, mplus))
import Control.Monad.Trans.Class (MonadTrans(lift))
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.Trans.Except (ExceptT(ExceptT), runExceptT, throwE, catchE)
import Data.Monoid (Monoid(mempty, mappend))
import qualified Control.Monad.Trans.Except
newtype EitherR r e = EitherR { runEitherR :: Either e r }
instance Functor (EitherR r) where
fmap = liftM
instance Applicative (EitherR r) where
pure = return
(<*>) = ap
instance Monad (EitherR r) where
return e = EitherR (Left e)
EitherR m >>= f = case m of
Left e -> f e
Right r -> EitherR (Right r)
instance (Monoid r) => Alternative (EitherR r) where
empty = EitherR (Right mempty)
e1@(EitherR (Left _)) <|> _ = e1
_ <|> e2@(EitherR (Left _)) = e2
EitherR (Right r1) <|> EitherR (Right r2)
= EitherR (Right (mappend r1 r2))
instance (Monoid r) => MonadPlus (EitherR r) where
mzero = empty
mplus = (<|>)
succeed :: r -> EitherR r e
succeed r = EitherR (return r)
throwEither :: e -> Either e r
throwEither e = runEitherR (return e)
catchEither :: Either a r -> (a -> Either b r) -> Either b r
e `catchEither` f = runEitherR $ EitherR e >>= \a -> EitherR (f a)
handleEither :: (a -> Either b r) -> Either a r -> Either b r
handleEither = flip catchEither
fmapL :: (a -> b) -> Either a r -> Either b r
fmapL f = runEitherR . fmap f . EitherR
flipEither :: Either a b -> Either b a
flipEither e = case e of
Left a -> Right a
Right b -> Left b
newtype ExceptRT r m e = ExceptRT { runExceptRT :: ExceptT e m r }
instance (Monad m) => Functor (ExceptRT r m) where
fmap = liftM
instance (Monad m) => Applicative (ExceptRT r m) where
pure = return
(<*>) = ap
instance (Monad m) => Monad (ExceptRT r m) where
return e = ExceptRT (throwE e)
m >>= f = ExceptRT $ ExceptT $ do
x <- runExceptT $ runExceptRT m
runExceptT $ runExceptRT $ case x of
Left e -> f e
Right r -> ExceptRT (return r)
instance (Monad m, Monoid r) => Alternative (ExceptRT r m) where
empty = ExceptRT $ ExceptT $ return $ Right mempty
e1 <|> e2 = ExceptRT $ ExceptT $ do
x1 <- runExceptT $ runExceptRT e1
case x1 of
Left l -> return (Left l)
Right r1 -> do
x2 <- runExceptT $ runExceptRT e2
case x2 of
Left l -> return (Left l)
Right r2 -> return (Right (mappend r1 r2))
instance (Monad m, Monoid r) => MonadPlus (ExceptRT r m) where
mzero = empty
mplus = (<|>)
instance MonadTrans (ExceptRT r) where
lift = ExceptRT . ExceptT . liftM Left
instance (MonadIO m) => MonadIO (ExceptRT r m) where
liftIO = lift . liftIO
succeedT :: (Monad m) => r -> ExceptRT r m e
succeedT r = ExceptRT (return r)
handleE :: (Monad m) => (a -> ExceptT b m r) -> ExceptT a m r -> ExceptT b m r
handleE = flip catchE
#if MIN_VERSION_base(4,8,0)
fmapLT :: Functor m => (a -> b) -> ExceptT a m r -> ExceptT b m r
fmapLT = Control.Monad.Trans.Except.withExceptT
#else
fmapLT :: (Monad m) => (a -> b) -> ExceptT a m r -> ExceptT b m r
fmapLT f = runExceptRT . fmap f . ExceptRT
#endif
flipET :: (Monad m) => ExceptT a m b -> ExceptT b m a
flipET = ExceptT . liftM flipEither . runExceptT