diff --git a/Control/Error.hs b/Control/Error.hs index 7aa31b4..0da4d08 100644 --- a/Control/Error.hs +++ b/Control/Error.hs @@ -15,7 +15,7 @@ * "Control.Error.Util": Utility functions and conversions between common error-handling types - * @Control.Monad.Trans.Either@: The 'EitherT' monad transformer + * @Control.Monad.Trans.Except@: The 'ExceptT' monad transformer * @Control.Monad.Trans.Maybe@: The 'MaybeT' monad transformer @@ -36,7 +36,7 @@ module Control.Error ( module Control.Error.Safe, module Control.Error.Script, module Control.Error.Util, - module Control.Monad.Trans.Either, + module Control.Monad.Trans.Except, module Control.Monad.Trans.Maybe, module Data.Either, module Data.EitherR, @@ -47,15 +47,13 @@ module Control.Error ( import Control.Error.Safe import Control.Error.Script import Control.Error.Util -import Control.Monad.Trans.Either ( - EitherT(EitherT), - runEitherT, - eitherT, - bimapEitherT, - mapEitherT, - hoistEither, - left, - right ) +import Control.Monad.Trans.Except ( + ExceptT(ExceptT), + runExceptT, + throwE, + catchE, + mapExceptT, + withExceptT ) import Control.Monad.Trans.Maybe ( MaybeT(MaybeT), runMaybeT, diff --git a/Control/Error/Safe.hs b/Control/Error/Safe.hs index 8b4d53b..24058c0 100644 --- a/Control/Error/Safe.hs +++ b/Control/Error/Safe.hs @@ -1,9 +1,9 @@ {-| This module extends the @safe@ library's functions with corresponding - versions compatible with 'Either' and 'EitherT', and also provides a few + versions compatible with 'Either' and 'ExceptT', and also provides a few 'Maybe'-compatible functions missing from @safe@. I suffix the 'Either'-compatible functions with @Err@ and prefix the - 'EitherT'-compatible functions with @try@. + 'ExceptT'-compatible functions with @try@. Note that this library re-exports the 'Maybe' compatible functions from @safe@ in the "Control.Error" module, so they are not provided here. @@ -15,7 +15,7 @@ * Most parsers - * 'EitherT' (if the left value is a 'Monoid') + * 'ExceptT' (if the left value is a 'Monoid') -} module Control.Error.Safe ( @@ -38,7 +38,7 @@ module Control.Error.Safe ( assertErr, justErr, - -- * EitherT-compatible functions + -- * ExceptT-compatible functions tryTail, tryInit, tryHead, @@ -71,9 +71,9 @@ module Control.Error.Safe ( rightZ ) where -import Control.Error.Util (note) +import Control.Error.Util (note, hoistEither) import Control.Monad (MonadPlus(mzero)) -import Control.Monad.Trans.Either (EitherT, hoistEither) +import Control.Monad.Trans.Except (ExceptT) import qualified Safe as S -- | An assertion that fails in the 'Maybe' monad @@ -136,60 +136,60 @@ assertErr e p = if p then Right () else Left e justErr :: e -> Maybe a -> Either e a justErr e = maybe (Left e) Right --- | A 'tail' that fails in the 'EitherT' monad -tryTail :: (Monad m) => e -> [a] -> EitherT e m [a] +-- | A 'tail' that fails in the 'ExceptT' monad +tryTail :: (Monad m) => e -> [a] -> ExceptT e m [a] tryTail e xs = hoistEither $ tailErr e xs --- | An 'init' that fails in the 'EitherT' monad -tryInit :: (Monad m) => e -> [a] -> EitherT e m [a] +-- | An 'init' that fails in the 'ExceptT' monad +tryInit :: (Monad m) => e -> [a] -> ExceptT e m [a] tryInit e xs = hoistEither $ initErr e xs --- | A 'head' that fails in the 'EitherT' monad -tryHead :: (Monad m) => e -> [a] -> EitherT e m a +-- | A 'head' that fails in the 'ExceptT' monad +tryHead :: (Monad m) => e -> [a] -> ExceptT e m a tryHead e xs = hoistEither $ headErr e xs --- | A 'last' that fails in the 'EitherT' monad -tryLast :: (Monad m) => e -> [a] -> EitherT e m a +-- | A 'last' that fails in the 'ExceptT' monad +tryLast :: (Monad m) => e -> [a] -> ExceptT e m a tryLast e xs = hoistEither $ lastErr e xs --- | A 'minimum' that fails in the 'EitherT' monad -tryMinimum :: (Monad m, Ord a) => e -> [a] -> EitherT e m a +-- | A 'minimum' that fails in the 'ExceptT' monad +tryMinimum :: (Monad m, Ord a) => e -> [a] -> ExceptT e m a tryMinimum e xs = hoistEither $ maximumErr e xs --- | A 'maximum' that fails in the 'EitherT' monad -tryMaximum :: (Monad m, Ord a) => e -> [a] -> EitherT e m a +-- | A 'maximum' that fails in the 'ExceptT' monad +tryMaximum :: (Monad m, Ord a) => e -> [a] -> ExceptT e m a tryMaximum e xs = hoistEither $ maximumErr e xs --- | A 'foldr1' that fails in the 'EitherT' monad -tryFoldr1 :: (Monad m) => e -> (a -> a -> a) -> [a] -> EitherT e m a +-- | A 'foldr1' that fails in the 'ExceptT' monad +tryFoldr1 :: (Monad m) => e -> (a -> a -> a) -> [a] -> ExceptT e m a tryFoldr1 e step xs = hoistEither $ foldr1Err e step xs --- | A 'foldl1' that fails in the 'EitherT' monad -tryFoldl1 :: (Monad m) => e -> (a -> a -> a) -> [a] -> EitherT e m a +-- | A 'foldl1' that fails in the 'ExceptT' monad +tryFoldl1 :: (Monad m) => e -> (a -> a -> a) -> [a] -> ExceptT e m a tryFoldl1 e step xs = hoistEither $ foldl1Err e step xs --- | A 'foldl1'' that fails in the 'EitherT' monad -tryFoldl1' :: (Monad m) => e -> (a -> a -> a) -> [a] -> EitherT e m a +-- | A 'foldl1'' that fails in the 'ExceptT' monad +tryFoldl1' :: (Monad m) => e -> (a -> a -> a) -> [a] -> ExceptT e m a tryFoldl1' e step xs = hoistEither $ foldl1Err' e step xs --- | A ('!!') that fails in the 'EitherT' monad -tryAt :: (Monad m) => e -> [a] -> Int -> EitherT e m a +-- | A ('!!') that fails in the 'ExceptT' monad +tryAt :: (Monad m) => e -> [a] -> Int -> ExceptT e m a tryAt e xs n = hoistEither $ atErr e xs n --- | A 'read' that fails in the 'EitherT' monad -tryRead :: (Monad m, Read a) => e -> String -> EitherT e m a +-- | A 'read' that fails in the 'ExceptT' monad +tryRead :: (Monad m, Read a) => e -> String -> ExceptT e m a tryRead e str = hoistEither $ readErr e str --- | An assertion that fails in the 'EitherT' monad -tryAssert :: (Monad m) => e -> Bool -> EitherT e m () +-- | An assertion that fails in the 'ExceptT' monad +tryAssert :: (Monad m) => e -> Bool -> ExceptT e m () tryAssert e p = hoistEither $ assertErr e p --- | A 'fromJust' that fails in the 'EitherT' monad -tryJust :: (Monad m) => e -> Maybe a -> EitherT e m a +-- | A 'fromJust' that fails in the 'ExceptT' monad +tryJust :: (Monad m) => e -> Maybe a -> ExceptT e m a tryJust e m = hoistEither $ justErr e m --- | A 'fromRight' that fails in the 'EitherT' monad -tryRight :: (Monad m) => Either e a -> EitherT e m a +-- | A 'fromRight' that fails in the 'ExceptT' monad +tryRight :: (Monad m) => Either e a -> ExceptT e m a tryRight = hoistEither -- | A 'tail' that fails using 'mzero' diff --git a/Control/Error/Script.hs b/Control/Error/Script.hs index 15bbfff..59a05a2 100644 --- a/Control/Error/Script.hs +++ b/Control/Error/Script.hs @@ -1,6 +1,6 @@ {-| Use this module if you like to write simple scripts with 'String'-based - errors, but you prefer to use 'EitherT' to handle errors rather than + errors, but you prefer to use 'ExceptT' to handle errors rather than @Control.Exception@. > import Control.Error @@ -21,7 +21,7 @@ module Control.Error.Script ( import Control.Exception (try, SomeException) import Control.Monad (liftM) import Control.Monad.IO.Class (MonadIO(liftIO)) -import Control.Monad.Trans.Either (EitherT(EitherT, runEitherT)) +import Control.Monad.Trans.Except (ExceptT(ExceptT), runExceptT) import Control.Error.Util (errLn) import Data.EitherR (fmapL) import System.Environment (getProgName) @@ -32,7 +32,7 @@ import Control.Monad.Trans.Class (lift) import System.IO (stderr) -- | An 'IO' action that can fail with a 'String' error message -type Script = EitherT String IO +type Script = ExceptT String IO {-| Runs the 'Script' monad @@ -40,7 +40,7 @@ type Script = EitherT String IO -} runScript :: Script a -> IO a runScript s = do - e <- runEitherT s + e <- runExceptT s case e of Left e -> do errLn =<< liftM (++ ": " ++ e) getProgName @@ -52,8 +52,8 @@ runScript s = do Note that 'scriptIO' is compatible with the 'Script' monad. -} -scriptIO :: (MonadIO m) => IO a -> EitherT String m a -scriptIO = EitherT +scriptIO :: (MonadIO m) => IO a -> ExceptT String m a +scriptIO = ExceptT . liftIO . liftM (fmapL show) . (try :: IO a -> IO (Either SomeException a)) diff --git a/Control/Error/Util.hs b/Control/Error/Util.hs index 646d624..4d65465 100644 --- a/Control/Error/Util.hs +++ b/Control/Error/Util.hs @@ -8,6 +8,7 @@ module Control.Error.Util ( note, noteT, hoistMaybe, + hoistEither, (??), (!?), failWith, @@ -33,10 +34,12 @@ module Control.Error.Util ( AllE(..), AnyE(..), - -- * EitherT + -- * ExceptT isLeftT, isRightT, fmapRT, + exceptT, + bimapExceptT, -- * Error Reporting err, @@ -51,7 +54,7 @@ import Control.Applicative (Applicative, pure, (<$>)) import qualified Control.Exception as Ex import Control.Monad (liftM) import Control.Monad.IO.Class (MonadIO(liftIO)) -import Control.Monad.Trans.Either (EitherT(EitherT), runEitherT, eitherT) +import Control.Monad.Trans.Except (ExceptT(ExceptT), runExceptT) import Control.Monad.Trans.Maybe (MaybeT(MaybeT), runMaybeT) import Data.Dynamic (Dynamic) import Data.Monoid (Monoid(mempty, mappend)) @@ -59,57 +62,75 @@ import Data.Maybe (fromMaybe) import System.Exit (ExitCode) import System.IO (hPutStr, hPutStrLn, stderr) +-- | Fold an 'ExceptT' by providing one continuation for each constructor +exceptT :: Monad m => (a -> m c) -> (b -> m c) -> ExceptT a m b -> m c +exceptT f g (ExceptT m) = m >>= \z -> case z of + Left a -> f a + Right b -> g b +{-# INLINEABLE exceptT #-} + +-- | Transform the left and right value +bimapExceptT :: Functor m => (e -> f) -> (a -> b) -> ExceptT e m a -> ExceptT f m b +bimapExceptT f g (ExceptT m) = ExceptT (fmap h m) + where + h (Left e) = Left (f e) + h (Right a) = Right (g a) +{-# INLINEABLE bimapExceptT #-} + +-- | Upgrade an 'Either' to an 'ExceptT' +hoistEither :: Monad m => Either e a -> ExceptT e m a +hoistEither = ExceptT . return +{-# INLINEABLE hoistEither #-} + {- $conversion Use these functions to convert between 'Maybe', 'Either', 'MaybeT', and - 'EitherT'. - - Note that 'hoistEither' and 'eitherT' are provided by the @either@ package. + 'ExceptT'. -} -- | Suppress the 'Left' value of an 'Either' hush :: Either a b -> Maybe b hush = either (const Nothing) Just --- | Suppress the 'Left' value of an 'EitherT' -hushT :: (Monad m) => EitherT a m b -> MaybeT m b -hushT = MaybeT . liftM hush . runEitherT +-- | Suppress the 'Left' value of an 'ExceptT' +hushT :: (Monad m) => ExceptT a m b -> MaybeT m b +hushT = MaybeT . liftM hush . runExceptT -- | Tag the 'Nothing' value of a 'Maybe' note :: a -> Maybe b -> Either a b note a = maybe (Left a) Right -- | Tag the 'Nothing' value of a 'MaybeT' -noteT :: (Monad m) => a -> MaybeT m b -> EitherT a m b -noteT a = EitherT . liftM (note a) . runMaybeT +noteT :: (Monad m) => a -> MaybeT m b -> ExceptT a m b +noteT a = ExceptT . liftM (note a) . runMaybeT -- | Lift a 'Maybe' to the 'MaybeT' monad hoistMaybe :: (Monad m) => Maybe b -> MaybeT m b hoistMaybe = MaybeT . return --- | Convert a 'Maybe' value into the 'EitherT' monad -(??) :: Applicative m => Maybe a -> e -> EitherT e m a -(??) a e = EitherT (pure $ note e a) +-- | Convert a 'Maybe' value into the 'ExceptT' monad +(??) :: Applicative m => Maybe a -> e -> ExceptT e m a +(??) a e = ExceptT (pure $ note e a) --- | Convert an applicative 'Maybe' value into the 'EitherT' monad -(!?) :: Applicative m => m (Maybe a) -> e -> EitherT e m a -(!?) a e = EitherT (note e <$> a) +-- | Convert an applicative 'Maybe' value into the 'ExceptT' monad +(!?) :: Applicative m => m (Maybe a) -> e -> ExceptT e m a +(!?) a e = ExceptT (note e <$> a) -- | An infix form of 'fromMaybe' with arguments flipped. (?:) :: Maybe a -> a -> a maybeA ?: b = fromMaybe b maybeA {-# INLINABLE (?:) #-} -{-| Convert a 'Maybe' value into the 'EitherT' monad +{-| Convert a 'Maybe' value into the 'ExceptT' monad Named version of ('??') with arguments flipped -} -failWith :: Applicative m => e -> Maybe a -> EitherT e m a +failWith :: Applicative m => e -> Maybe a -> ExceptT e m a failWith e a = a ?? e -{- | Convert an applicative 'Maybe' value into the 'EitherT' monad +{- | Convert an applicative 'Maybe' value into the 'ExceptT' monad Named version of ('!?') with arguments flipped -} -failWithM :: Applicative m => e -> m (Maybe a) -> EitherT e m a +failWithM :: Applicative m => e -> m (Maybe a) -> ExceptT e m a failWithM e a = a !? e {- | Case analysis for the 'Bool' type. @@ -186,20 +207,20 @@ instance (Monoid e, Monoid r) => Monoid (AnyE e r) where mappend (AnyE (Left _)) (AnyE (Right y)) = AnyE (Right y) mappend (AnyE (Left x)) (AnyE (Left y)) = AnyE (Left (mappend x y)) --- | Analogous to 'isLeft', but for 'EitherT' -isLeftT :: (Monad m) => EitherT a m b -> m Bool -isLeftT = eitherT (\_ -> return True) (\_ -> return False) +-- | Analogous to 'isLeft', but for 'ExceptT' +isLeftT :: (Monad m) => ExceptT a m b -> m Bool +isLeftT = exceptT (\_ -> return True) (\_ -> return False) {-# INLINABLE isLeftT #-} --- | Analogous to 'isRight', but for 'EitherT' -isRightT :: (Monad m) => EitherT a m b -> m Bool -isRightT = eitherT (\_ -> return False) (\_ -> return True) +-- | Analogous to 'isRight', but for 'ExceptT' +isRightT :: (Monad m) => ExceptT a m b -> m Bool +isRightT = exceptT (\_ -> return False) (\_ -> return True) {-# INLINABLE isRightT #-} -{- | 'fmap' specialized to 'EitherT', given a name symmetric to +{- | 'fmap' specialized to 'ExceptT', given a name symmetric to 'Data.EitherR.fmapLT' -} -fmapRT :: (Monad m) => (a -> b) -> EitherT l m a -> EitherT l m b +fmapRT :: (Monad m) => (a -> b) -> ExceptT l m a -> ExceptT l m b fmapRT = liftM -- | Write a string to standard error @@ -210,15 +231,15 @@ err = hPutStr stderr errLn :: String -> IO () errLn = hPutStrLn stderr --- | Catch 'Ex.IOException's and convert them to the 'EitherT' monad -tryIO :: (MonadIO m) => IO a -> EitherT Ex.IOException m a -tryIO = EitherT . liftIO . Ex.try +-- | Catch 'Ex.IOException's and convert them to the 'ExceptT' monad +tryIO :: (MonadIO m) => IO a -> ExceptT Ex.IOException m a +tryIO = ExceptT . liftIO . Ex.try {-| Catch all exceptions, except for asynchronous exceptions found in @base@ - and convert them to the 'EitherT' monad + and convert them to the 'ExceptT' monad -} -syncIO :: MonadIO m => IO a -> EitherT Ex.SomeException m a -syncIO a = EitherT . liftIO $ Ex.catches (Right <$> a) +syncIO :: MonadIO m => IO a -> ExceptT Ex.SomeException m a +syncIO a = ExceptT . liftIO $ Ex.catches (Right <$> a) [ Ex.Handler $ \e -> Ex.throw (e :: Ex.ArithException) , Ex.Handler $ \e -> Ex.throw (e :: Ex.ArrayException) , Ex.Handler $ \e -> Ex.throw (e :: Ex.AssertionFailed) diff --git a/Data/EitherR.hs b/Data/EitherR.hs index e3649fc..a569559 100644 --- a/Data/EitherR.hs +++ b/Data/EitherR.hs @@ -1,22 +1,21 @@ -{-| This module provides 'throwE' and 'catchE' for 'Either'. These two - functions reside here because 'throwE' and 'catchE' correspond to 'return' - and ('>>=') for the flipped 'Either' monad: 'EitherR'. Similarly, this - module defines 'throwT' and 'catchT' for 'EitherT', which correspond to the - 'Monad' operations for 'EitherRT'. +{-| This module provides 'throwEither' and 'catchEither' for 'Either'. These two + functions reside here because 'throwEither' and 'catchEither' correspond to 'return' + and ('>>=') for the flipped 'Either' monad: 'EitherR'. Additionally, this + module defines 'handleE' as the flipped version of 'catchE' for 'ExceptT'. - These throw and catch functions improve upon @MonadError@ because: + 'throwEither' and 'catchEither' improve upon @MonadError@ because: - * 'catch' is more general and allows you to change the left value's type + * 'catchEither' is more general than 'catch' and allows you to change the left value's type - * They are Haskell98 + * Both are Haskell98 - More advanced users can use 'EitherR' and 'EitherRT' to program in an + More advanced users can use 'EitherR' and 'ExceptRT' to program in an entirely symmetric \"success monad\" where exceptional results are the norm and successful results terminate the computation. This allows you to chain error-handlers using @do@ notation and pass around exceptional values of varying types until you can finally recover from the error: -> runEitherRT $ do +> runExceptRT $ do > e2 <- ioExceptionHandler e1 > bool <- arithmeticExceptionhandler e2 > when bool $ lift $ putStrLn "DEBUG: Arithmetic handler did something" @@ -24,7 +23,7 @@ If any of the above error handlers 'succeed', no other handlers are tried. If you choose not to typefully distinguish between the error and sucess - monad, then use 'flipE' and 'flipET', which swap the type variables without + monad, then use 'flipEither' and 'flipET', which swap the type variables without changing the type. -} @@ -36,24 +35,22 @@ module Data.EitherR ( succeed, -- ** Conversions to the Either monad - throwE, - catchE, - handleE, + throwEither, + catchEither, + handleEither, fmapL, -- ** Flip alternative - flipE, + flipEither, - -- * EitherRT - EitherRT(..), + -- * ExceptRT + ExceptRT(..), - -- ** Operations in the EitherRT monad + -- ** Operations in the ExceptRT monad succeedT, - -- ** Conversions to the EitherT monad - throwT, - catchT, - handleT, + -- ** Conversions to the ExceptT monad + handleE, fmapLT, -- ** Flip alternative @@ -64,15 +61,15 @@ 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.Either (EitherT(EitherT, runEitherT), left, right) +import Control.Monad.Trans.Except (ExceptT(ExceptT), runExceptT, throwE, catchE) import Data.Monoid (Monoid(mempty, mappend)) {-| If \"@Either e r@\" is the error monad, then \"@EitherR r e@\" is the corresponding success monad, where: - * 'return' is 'throwE'. + * 'return' is 'throwEither'. - * ('>>=') is 'catchE'. + * ('>>=') is 'catchEither'. * Successful results abort the computation -} @@ -106,88 +103,80 @@ instance (Monoid r) => MonadPlus (EitherR r) where succeed :: r -> EitherR r e succeed r = EitherR (return r) --- | 'throwE' in the error monad corresponds to 'return' in the success monad -throwE :: e -> Either e r -throwE e = runEitherR (return e) +-- | 'throwEither' in the error monad corresponds to 'return' in the success monad +throwEither :: e -> Either e r +throwEither e = runEitherR (return e) --- | 'catchE' in the error monad corresponds to ('>>=') in the success monad -catchE :: Either a r -> (a -> Either b r) -> Either b r -e `catchE` f = runEitherR $ EitherR e >>= \a -> EitherR (f a) +-- | 'catchEither' in the error monad corresponds to ('>>=') in the success monad +catchEither :: Either a r -> (a -> Either b r) -> Either b r +e `catchEither` f = runEitherR $ EitherR e >>= \a -> EitherR (f a) --- | 'catchE' with the arguments flipped -handleE :: (a -> Either b r) -> Either a r -> Either b r -handleE = flip catchE +-- | 'catchEither' with the arguments flipped +handleEither :: (a -> Either b r) -> Either a r -> Either b r +handleEither = flip catchEither -- | Map a function over the 'Left' value of an 'Either' fmapL :: (a -> b) -> Either a r -> Either b r fmapL f = runEitherR . fmap f . EitherR -- | Flip the type variables of 'Either' -flipE :: Either a b -> Either b a -flipE e = case e of +flipEither :: Either a b -> Either b a +flipEither e = case e of Left a -> Right a Right b -> Left b -- | 'EitherR' converted into a monad transformer -newtype EitherRT r m e = EitherRT { runEitherRT :: EitherT e m r } +newtype ExceptRT r m e = ExceptRT { runExceptRT :: ExceptT e m r } -instance (Monad m) => Functor (EitherRT r m) where +instance (Monad m) => Functor (ExceptRT r m) where fmap = liftM -instance (Monad m) => Applicative (EitherRT r m) where +instance (Monad m) => Applicative (ExceptRT r m) where pure = return (<*>) = ap -instance (Monad m) => Monad (EitherRT r m) where - return e = EitherRT (left e) - m >>= f = EitherRT $ EitherT $ do - x <- runEitherT $ runEitherRT m - runEitherT $ runEitherRT $ case x of +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 -> EitherRT (right r) + Right r -> ExceptRT (return r) -instance (Monad m, Monoid r) => Alternative (EitherRT r m) where - empty = EitherRT $ EitherT $ return $ Right mempty - e1 <|> e2 = EitherRT $ EitherT $ do - x1 <- runEitherT $ runEitherRT e1 +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 <- runEitherT $ runEitherRT e2 + 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 (EitherRT r m) where +instance (Monad m, Monoid r) => MonadPlus (ExceptRT r m) where mzero = empty mplus = (<|>) -instance MonadTrans (EitherRT r) where - lift = EitherRT . EitherT . liftM Left +instance MonadTrans (ExceptRT r) where + lift = ExceptRT . ExceptT . liftM Left -instance (MonadIO m) => MonadIO (EitherRT r m) where +instance (MonadIO m) => MonadIO (ExceptRT r m) where liftIO = lift . liftIO -- | Complete error handling, returning a result -succeedT :: (Monad m) => r -> EitherRT r m e -succeedT r = EitherRT (return r) - --- | 'throwT' in the error monad corresponds to 'return' in the success monad -throwT :: (Monad m) => e -> EitherT e m r -throwT e = runEitherRT (return e) - --- | 'catchT' in the error monad corresponds to ('>>=') in the success monad -catchT :: (Monad m) => EitherT a m r -> (a -> EitherT b m r) -> EitherT b m r -e `catchT` f = runEitherRT $ EitherRT e >>= \a -> EitherRT (f a) +succeedT :: (Monad m) => r -> ExceptRT r m e +succeedT r = ExceptRT (return r) -- | 'catchT' with the arguments flipped -handleT :: (Monad m) => (a -> EitherT b m r) -> EitherT a m r -> EitherT b m r -handleT = flip catchT +handleE :: (Monad m) => (a -> ExceptT b m r) -> ExceptT a m r -> ExceptT b m r +handleE = flip catchE --- | Map a function over the 'Left' value of an 'EitherT' -fmapLT :: (Monad m) => (a -> b) -> EitherT a m r -> EitherT b m r -fmapLT f = runEitherRT . fmap f . EitherRT +-- | Map a function over the 'Left' value of an 'ExceptT' +fmapLT :: (Monad m) => (a -> b) -> ExceptT a m r -> ExceptT b m r +fmapLT f = runExceptRT . fmap f . ExceptRT --- | Flip the type variables of an 'EitherT' -flipET :: (Monad m) => EitherT a m b -> EitherT b m a -flipET = EitherT . liftM flipE . runEitherT +-- | Flip the type variables of an 'ExceptT' +flipET :: (Monad m) => ExceptT a m b -> ExceptT b m a +flipET = ExceptT . liftM flipEither . runExceptT diff --git a/errors.cabal b/errors.cabal index 715f48e..5759ba8 100644 --- a/errors.cabal +++ b/errors.cabal @@ -23,9 +23,8 @@ Source-Repository head Library Build-Depends: base >= 4 && < 5 , - either >= 3.1 && < 5 , safe >= 0.3.3 && < 0.4, - transformers >= 0.2 && < 0.5 + transformers >= 0.4 && < 0.5 Exposed-Modules: Control.Error, Control.Error.Safe,