{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
#endif
#if __GLASGOW_HASKELL__ >= 710
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
#if !(MIN_VERSION_base(4,9,0))
{-# OPTIONS_GHC -fno-warn-orphans #-}
#endif
-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Monad.Trans.Error
-- Copyright   :  (c) Michael Weber <michael.weber@post.rwth-aachen.de> 2001,
--                (c) Jeff Newbern 2003-2006,
--                (c) Andriy Palamarchuk 2006
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  R.Paterson@city.ac.uk
-- Stability   :  experimental
-- Portability :  portable
--
-- This monad transformer adds the ability to fail or throw exceptions
-- to a monad.
--
-- A sequence of actions succeeds, producing a value, only if all the
-- actions in the sequence are successful.  If one fails with an error,
-- the rest of the sequence is skipped and the composite action fails
-- with that error.
--
-- If the value of the error is not required, the variant in
-- "Control.Monad.Trans.Maybe" may be used instead.
--
-- /Note:/ This module will be removed in a future release.
-- Instead, use "Control.Monad.Trans.Except", which does not restrict
-- the exception type, and also includes a base exception monad.
-----------------------------------------------------------------------------

module Control.Monad.Trans.Error
  {-# DEPRECATED "Use Control.Monad.Trans.Except instead" #-} (
    -- * The ErrorT monad transformer
    Error(..),
    ErrorList(..),
    ErrorT(..),
    mapErrorT,
    -- * Error operations
    throwError,
    catchError,
    -- * Lifting other operations
    liftCallCC,
    liftListen,
    liftPass,
    -- * Examples
    -- $examples
  ) where

import Control.Monad.IO.Class
import Control.Monad.Signatures
import Control.Monad.Trans.Class
import Data.Functor.Classes
#if MIN_VERSION_base(4,12,0)
import Data.Functor.Contravariant
#endif

import Control.Applicative
import Control.Exception (IOException)
import Control.Monad
#if MIN_VERSION_base(4,9,0)
import qualified Control.Monad.Fail as Fail
#endif
import Control.Monad.Fix
#if !(MIN_VERSION_base(4,6,0))
import Control.Monad.Instances ()  -- deprecated from base-4.6
#endif
import Data.Foldable (Foldable(foldMap))
import Data.Monoid (mempty)
import Data.Traversable (Traversable(traverse))
import System.IO.Error

#if !(MIN_VERSION_base(4,9,0))
-- These instances are in base-4.9.0

instance MonadPlus IO where
    mzero       = ioError (userError "mzero")
    m `mplus` n = m `catchIOError` \ _ -> n

instance Alternative IO where
    empty = mzero
    (<|>) = mplus

# if !(MIN_VERSION_base(4,4,0))
-- exported by System.IO.Error from base-4.4
catchIOError :: IO a -> (IOError -> IO a) -> IO a
catchIOError = catch
# endif
#endif

instance (Error e) => Alternative (Either e) where
    empty :: forall a. Either e a
empty        = e -> Either e a
forall a b. a -> Either a b
Left e
forall a. Error a => a
noMsg
    Left e
_ <|> :: forall a. Either e a -> Either e a -> Either e a
<|> Either e a
n = Either e a
n
    Either e a
m      <|> Either e a
_ = Either e a
m

instance (Error e) => MonadPlus (Either e) where
    mzero :: forall a. Either e a
mzero            = e -> Either e a
forall a b. a -> Either a b
Left e
forall a. Error a => a
noMsg
    Left e
_ mplus :: forall a. Either e a -> Either e a -> Either e a
`mplus` Either e a
n = Either e a
n
    Either e a
m      `mplus` Either e a
_ = Either e a
m

#if !(MIN_VERSION_base(4,3,0))
-- These instances are in base-4.3

instance Applicative (Either e) where
    pure          = Right
    Left  e <*> _ = Left e
    Right f <*> r = fmap f r

instance Monad (Either e) where
    return        = Right
    Left  l >>= _ = Left l
    Right r >>= k = k r

instance MonadFix (Either e) where
    mfix f = let
        a = f $ case a of
            Right r -> r
            _       -> error "empty mfix argument"
        in a

#endif /* base to 4.2.0.x */

-- | An exception to be thrown.
--
-- Minimal complete definition: 'noMsg' or 'strMsg'.
class Error a where
    -- | Creates an exception without a message.
    -- The default implementation is @'strMsg' \"\"@.
    noMsg  :: a
    -- | Creates an exception with a message.
    -- The default implementation of @'strMsg' s@ is 'noMsg'.
    strMsg :: String -> a

    noMsg    = String -> a
forall a. Error a => String -> a
strMsg String
""
    strMsg String
_ = a
forall a. Error a => a
noMsg

instance Error IOException where
    strMsg :: String -> IOException
strMsg = String -> IOException
userError

-- | A string can be thrown as an error.
instance (ErrorList a) => Error [a] where
    strMsg :: String -> [a]
strMsg = String -> [a]
forall a. ErrorList a => String -> [a]
listMsg

-- | Workaround so that we can have a Haskell 98 instance @'Error' 'String'@.
class ErrorList a where
    listMsg :: String -> [a]

instance ErrorList Char where
    listMsg :: String -> String
listMsg = String -> String
forall a. a -> a
id

-- | The error monad transformer. It can be used to add error handling
-- to other monads.
--
-- The @ErrorT@ Monad structure is parameterized over two things:
--
-- * e - The error type.
--
-- * m - The inner monad.
--
-- The 'return' function yields a successful computation, while @>>=@
-- sequences two subcomputations, failing on the first error.
newtype ErrorT e m a = ErrorT { forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT :: m (Either e a) }

instance (Eq e, Eq1 m) => Eq1 (ErrorT e m) where
    liftEq :: forall a b.
(a -> b -> Bool) -> ErrorT e m a -> ErrorT e m b -> Bool
liftEq a -> b -> Bool
eq (ErrorT m (Either e a)
x) (ErrorT m (Either e b)
y) = (Either e a -> Either e b -> Bool)
-> m (Either e a) -> m (Either e b) -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq ((a -> b -> Bool) -> Either e a -> Either e b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq) m (Either e a)
x m (Either e b)
y

instance (Ord e, Ord1 m) => Ord1 (ErrorT e m) where
    liftCompare :: forall a b.
(a -> b -> Ordering) -> ErrorT e m a -> ErrorT e m b -> Ordering
liftCompare a -> b -> Ordering
comp (ErrorT m (Either e a)
x) (ErrorT m (Either e b)
y) = (Either e a -> Either e b -> Ordering)
-> m (Either e a) -> m (Either e b) -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare ((a -> b -> Ordering) -> Either e a -> Either e b -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
comp) m (Either e a)
x m (Either e b)
y

instance (Read e, Read1 m) => Read1 (ErrorT e m) where
    liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ErrorT e m a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl = (String -> ReadS (ErrorT e m a)) -> Int -> ReadS (ErrorT e m a)
forall a. (String -> ReadS a) -> Int -> ReadS a
readsData ((String -> ReadS (ErrorT e m a)) -> Int -> ReadS (ErrorT e m a))
-> (String -> ReadS (ErrorT e m a)) -> Int -> ReadS (ErrorT e m a)
forall a b. (a -> b) -> a -> b
$
        (Int -> ReadS (m (Either e a)))
-> String
-> (m (Either e a) -> ErrorT e m a)
-> String
-> ReadS (ErrorT e m a)
forall a t.
(Int -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith ((Int -> ReadS (Either e a))
-> ReadS [Either e a] -> Int -> ReadS (m (Either e a))
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS (Either e a)
rp' ReadS [Either e a]
rl') String
"ErrorT" m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT
      where
        rp' :: Int -> ReadS (Either e a)
rp' = (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Either e a)
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl
        rl' :: ReadS [Either e a]
rl' = (Int -> ReadS a) -> ReadS [a] -> ReadS [Either e a]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadList Int -> ReadS a
rp ReadS [a]
rl

instance (Show e, Show1 m) => Show1 (ErrorT e m) where
    liftShowsPrec :: forall a.
(Int -> a -> String -> String)
-> ([a] -> String -> String)
-> Int
-> ErrorT e m a
-> String
-> String
liftShowsPrec Int -> a -> String -> String
sp [a] -> String -> String
sl Int
d (ErrorT m (Either e a)
m) =
        (Int -> m (Either e a) -> String -> String)
-> String -> Int -> m (Either e a) -> String -> String
forall a.
(Int -> a -> String -> String)
-> String -> Int -> a -> String -> String
showsUnaryWith ((Int -> Either e a -> String -> String)
-> ([Either e a] -> String -> String)
-> Int
-> m (Either e a)
-> String
-> String
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> String -> String)
-> ([a] -> String -> String) -> Int -> f a -> String -> String
liftShowsPrec Int -> Either e a -> String -> String
sp' [Either e a] -> String -> String
sl') String
"ErrorT" Int
d m (Either e a)
m
      where
        sp' :: Int -> Either e a -> String -> String
sp' = (Int -> a -> String -> String)
-> ([a] -> String -> String)
-> Int
-> Either e a
-> String
-> String
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> String -> String)
-> ([a] -> String -> String) -> Int -> f a -> String -> String
liftShowsPrec Int -> a -> String -> String
sp [a] -> String -> String
sl
        sl' :: [Either e a] -> String -> String
sl' = (Int -> a -> String -> String)
-> ([a] -> String -> String) -> [Either e a] -> String -> String
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> String -> String)
-> ([a] -> String -> String) -> [f a] -> String -> String
liftShowList Int -> a -> String -> String
sp [a] -> String -> String
sl

instance (Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) where == :: ErrorT e m a -> ErrorT e m a -> Bool
(==) = ErrorT e m a -> ErrorT e m a -> Bool
forall (f :: * -> *) a. (Eq1 f, Eq a) => f a -> f a -> Bool
eq1
instance (Ord e, Ord1 m, Ord a) => Ord (ErrorT e m a) where compare :: ErrorT e m a -> ErrorT e m a -> Ordering
compare = ErrorT e m a -> ErrorT e m a -> Ordering
forall (f :: * -> *) a. (Ord1 f, Ord a) => f a -> f a -> Ordering
compare1
instance (Read e, Read1 m, Read a) => Read (ErrorT e m a) where
    readsPrec :: Int -> ReadS (ErrorT e m a)
readsPrec = Int -> ReadS (ErrorT e m a)
forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1
instance (Show e, Show1 m, Show a) => Show (ErrorT e m a) where
    showsPrec :: Int -> ErrorT e m a -> String -> String
showsPrec = Int -> ErrorT e m a -> String -> String
forall (f :: * -> *) a.
(Show1 f, Show a) =>
Int -> f a -> String -> String
showsPrec1

-- | Map the unwrapped computation using the given function.
--
-- * @'runErrorT' ('mapErrorT' f m) = f ('runErrorT' m)@
mapErrorT :: (m (Either e a) -> n (Either e' b))
          -> ErrorT e m a
          -> ErrorT e' n b
mapErrorT :: forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ErrorT e m a -> ErrorT e' n b
mapErrorT m (Either e a) -> n (Either e' b)
f ErrorT e m a
m = n (Either e' b) -> ErrorT e' n b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (n (Either e' b) -> ErrorT e' n b)
-> n (Either e' b) -> ErrorT e' n b
forall a b. (a -> b) -> a -> b
$ m (Either e a) -> n (Either e' b)
f (ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
m)

instance (Functor m) => Functor (ErrorT e m) where
    fmap :: forall a b. (a -> b) -> ErrorT e m a -> ErrorT e m b
fmap a -> b
f = m (Either e b) -> ErrorT e m b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e b) -> ErrorT e m b)
-> (ErrorT e m a -> m (Either e b)) -> ErrorT e m a -> ErrorT e m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either e a -> Either e b) -> m (Either e a) -> m (Either e b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Either e a -> Either e b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (m (Either e a) -> m (Either e b))
-> (ErrorT e m a -> m (Either e a))
-> ErrorT e m a
-> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT

instance (Foldable f) => Foldable (ErrorT e f) where
    foldMap :: forall m a. Monoid m => (a -> m) -> ErrorT e f a -> m
foldMap a -> m
f (ErrorT f (Either e a)
a) = (Either e a -> m) -> f (Either e a) -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((e -> m) -> (a -> m) -> Either e a -> m
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (m -> e -> m
forall a b. a -> b -> a
const m
forall a. Monoid a => a
mempty) a -> m
f) f (Either e a)
a

instance (Traversable f) => Traversable (ErrorT e f) where
    traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ErrorT e f a -> f (ErrorT e f b)
traverse a -> f b
f (ErrorT f (Either e a)
a) =
        f (Either e b) -> ErrorT e f b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (f (Either e b) -> ErrorT e f b)
-> f (f (Either e b)) -> f (ErrorT e f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Either e a -> f (Either e b))
-> f (Either e a) -> f (f (Either e b))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((e -> f (Either e b))
-> (a -> f (Either e b)) -> Either e a -> f (Either e b)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Either e b -> f (Either e b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either e b -> f (Either e b))
-> (e -> Either e b) -> e -> f (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) ((b -> Either e b) -> f b -> f (Either e b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> Either e b
forall a b. b -> Either a b
Right (f b -> f (Either e b)) -> (a -> f b) -> a -> f (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> f b
f)) f (Either e a)
a

instance (Functor m, Monad m) => Applicative (ErrorT e m) where
    pure :: forall a. a -> ErrorT e m a
pure a
a  = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
a)
    ErrorT e m (a -> b)
f <*> :: forall a b. ErrorT e m (a -> b) -> ErrorT e m a -> ErrorT e m b
<*> ErrorT e m a
v = m (Either e b) -> ErrorT e m b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e b) -> ErrorT e m b) -> m (Either e b) -> ErrorT e m b
forall a b. (a -> b) -> a -> b
$ do
        Either e (a -> b)
mf <- ErrorT e m (a -> b) -> m (Either e (a -> b))
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m (a -> b)
f
        case Either e (a -> b)
mf of
            Left  e
e -> Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e b
forall a b. a -> Either a b
Left e
e)
            Right a -> b
k -> do
                Either e a
mv <- ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
v
                case Either e a
mv of
                    Left  e
e -> Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e b
forall a b. a -> Either a b
Left e
e)
                    Right a
x -> Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either e b
forall a b. b -> Either a b
Right (a -> b
k a
x))

instance (Functor m, Monad m, Error e) => Alternative (ErrorT e m) where
    empty :: forall a. ErrorT e m a
empty = ErrorT e m a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
    <|> :: forall a. ErrorT e m a -> ErrorT e m a -> ErrorT e m a
(<|>) = ErrorT e m a -> ErrorT e m a -> ErrorT e m a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
mplus

instance (Monad m, Error e) => Monad (ErrorT e m) where
#if !(MIN_VERSION_base(4,8,0))
    return a = ErrorT $ return (Right a)
#endif
    ErrorT e m a
m >>= :: forall a b. ErrorT e m a -> (a -> ErrorT e m b) -> ErrorT e m b
>>= a -> ErrorT e m b
k  = m (Either e b) -> ErrorT e m b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e b) -> ErrorT e m b) -> m (Either e b) -> ErrorT e m b
forall a b. (a -> b) -> a -> b
$ do
        Either e a
a <- ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
m
        case Either e a
a of
            Left  e
l -> Either e b -> m (Either e b)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e b
forall a b. a -> Either a b
Left e
l)
            Right a
r -> ErrorT e m b -> m (Either e b)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (a -> ErrorT e m b
k a
r)
#if !(MIN_VERSION_base(4,13,0))
    fail msg = ErrorT $ return (Left (strMsg msg))
#endif

#if MIN_VERSION_base(4,9,0)
instance (Monad m, Error e) => Fail.MonadFail (ErrorT e m) where
    fail :: forall a. String -> ErrorT e m a
fail String
msg = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e a
forall a b. a -> Either a b
Left (String -> e
forall a. Error a => String -> a
strMsg String
msg))
#endif

instance (Monad m, Error e) => MonadPlus (ErrorT e m) where
    mzero :: forall a. ErrorT e m a
mzero       = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e a
forall a b. a -> Either a b
Left e
forall a. Error a => a
noMsg)
    ErrorT e m a
m mplus :: forall a. ErrorT e m a -> ErrorT e m a -> ErrorT e m a
`mplus` ErrorT e m a
n = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ do
        Either e a
a <- ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
m
        case Either e a
a of
            Left  e
_ -> ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
n
            Right a
r -> Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
r)

instance (MonadFix m, Error e) => MonadFix (ErrorT e m) where
    mfix :: forall a. (a -> ErrorT e m a) -> ErrorT e m a
mfix a -> ErrorT e m a
f = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ (Either e a -> m (Either e a)) -> m (Either e a)
forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix ((Either e a -> m (Either e a)) -> m (Either e a))
-> (Either e a -> m (Either e a)) -> m (Either e a)
forall a b. (a -> b) -> a -> b
$ \ Either e a
a -> ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (ErrorT e m a -> m (Either e a)) -> ErrorT e m a -> m (Either e a)
forall a b. (a -> b) -> a -> b
$ a -> ErrorT e m a
f (a -> ErrorT e m a) -> a -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ case Either e a
a of
        Right a
r -> a
r
        Either e a
_       -> String -> a
forall a. HasCallStack => String -> a
error String
"empty mfix argument"

instance MonadTrans (ErrorT e) where
    lift :: forall (m :: * -> *) a. Monad m => m a -> ErrorT e m a
lift m a
m = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ do
        a
a <- m a
m
        Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
a)

instance (Error e, MonadIO m) => MonadIO (ErrorT e m) where
    liftIO :: forall a. IO a -> ErrorT e m a
liftIO = m a -> ErrorT e m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ErrorT e m a) -> (IO a -> m a) -> IO a -> ErrorT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO

#if MIN_VERSION_base(4,12,0)
instance Contravariant m => Contravariant (ErrorT e m) where
    contramap :: forall a' a. (a' -> a) -> ErrorT e m a -> ErrorT e m a'
contramap a' -> a
f = m (Either e a') -> ErrorT e m a'
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a') -> ErrorT e m a')
-> (ErrorT e m a -> m (Either e a'))
-> ErrorT e m a
-> ErrorT e m a'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Either e a' -> Either e a) -> m (Either e a) -> m (Either e a')
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap ((a' -> a) -> Either e a' -> Either e a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a' -> a
f) (m (Either e a) -> m (Either e a'))
-> (ErrorT e m a -> m (Either e a))
-> ErrorT e m a
-> m (Either e a')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT
#endif

-- | Signal an error value @e@.
--
-- * @'runErrorT' ('throwError' e) = 'return' ('Left' e)@
--
-- * @'throwError' e >>= m = 'throwError' e@
throwError :: (Monad m) => e -> ErrorT e m a
throwError :: forall (m :: * -> *) e a. Monad m => e -> ErrorT e m a
throwError e
l = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (e -> Either e a
forall a b. a -> Either a b
Left e
l)

-- | Handle an error.
--
-- * @'catchError' h ('lift' m) = 'lift' m@
--
-- * @'catchError' h ('throwError' e) = h e@
catchError :: (Monad m) =>
    ErrorT e m a                -- ^ the inner computation
    -> (e -> ErrorT e m a)      -- ^ a handler for errors in the inner
                                -- computation
    -> ErrorT e m a
ErrorT e m a
m catchError :: forall (m :: * -> *) e a.
Monad m =>
ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a
`catchError` e -> ErrorT e m a
h = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ do
    Either e a
a <- ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ErrorT e m a
m
    case Either e a
a of
        Left  e
l -> ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT (e -> ErrorT e m a
h e
l)
        Right a
r -> Either e a -> m (Either e a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
r)

-- | Lift a @callCC@ operation to the new monad.
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ErrorT e m) a b
liftCallCC :: forall (m :: * -> *) e a b.
CallCC m (Either e a) (Either e b) -> CallCC (ErrorT e m) a b
liftCallCC CallCC m (Either e a) (Either e b)
callCC (a -> ErrorT e m b) -> ErrorT e m a
f = m (Either e a) -> ErrorT e m a
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e a) -> ErrorT e m a) -> m (Either e a) -> ErrorT e m a
forall a b. (a -> b) -> a -> b
$
    CallCC m (Either e a) (Either e b)
callCC CallCC m (Either e a) (Either e b)
-> CallCC m (Either e a) (Either e b)
forall a b. (a -> b) -> a -> b
$ \ Either e a -> m (Either e b)
c ->
    ErrorT e m a -> m (Either e a)
forall e (m :: * -> *) a. ErrorT e m a -> m (Either e a)
runErrorT ((a -> ErrorT e m b) -> ErrorT e m a
f (\ a
a -> m (Either e b) -> ErrorT e m b
forall e (m :: * -> *) a. m (Either e a) -> ErrorT e m a
ErrorT (m (Either e b) -> ErrorT e m b) -> m (Either e b) -> ErrorT e m b
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e b)
c (a -> Either e a
forall a b. b -> Either a b
Right a
a)))

-- | Lift a @listen@ operation to the new monad.
liftListen :: (Monad m) => Listen w m (Either e a) -> Listen w (ErrorT e m) a
liftListen :: forall (m :: * -> *) w e a.
Monad m =>
Listen w m (Either e a) -> Listen w (ErrorT e m) a
liftListen Listen w m (Either e a)
listen = (m (Either e a) -> m (Either e (a, w)))
-> ErrorT e m a -> ErrorT e m (a, w)
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ErrorT e m a -> ErrorT e' n b
mapErrorT ((m (Either e a) -> m (Either e (a, w)))
 -> ErrorT e m a -> ErrorT e m (a, w))
-> (m (Either e a) -> m (Either e (a, w)))
-> ErrorT e m a
-> ErrorT e m (a, w)
forall a b. (a -> b) -> a -> b
$ \ m (Either e a)
m -> do
    (Either e a
a, w
w) <- Listen w m (Either e a)
listen m (Either e a)
m
    Either e (a, w) -> m (Either e (a, w))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either e (a, w) -> m (Either e (a, w)))
-> Either e (a, w) -> m (Either e (a, w))
forall a b. (a -> b) -> a -> b
$! (a -> (a, w)) -> Either e a -> Either e (a, w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ a
r -> (a
r, w
w)) Either e a
a

-- | Lift a @pass@ operation to the new monad.
liftPass :: (Monad m) => Pass w m (Either e a) -> Pass w (ErrorT e m) a
liftPass :: forall (m :: * -> *) w e a.
Monad m =>
Pass w m (Either e a) -> Pass w (ErrorT e m) a
liftPass Pass w m (Either e a)
pass = (m (Either e (a, w -> w)) -> m (Either e a))
-> ErrorT e m (a, w -> w) -> ErrorT e m a
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ErrorT e m a -> ErrorT e' n b
mapErrorT ((m (Either e (a, w -> w)) -> m (Either e a))
 -> ErrorT e m (a, w -> w) -> ErrorT e m a)
-> (m (Either e (a, w -> w)) -> m (Either e a))
-> ErrorT e m (a, w -> w)
-> ErrorT e m a
forall a b. (a -> b) -> a -> b
$ \ m (Either e (a, w -> w))
m -> Pass w m (Either e a)
pass Pass w m (Either e a) -> Pass w m (Either e a)
forall a b. (a -> b) -> a -> b
$ do
    Either e (a, w -> w)
a <- m (Either e (a, w -> w))
m
    (Either e a, w -> w) -> m (Either e a, w -> w)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Either e a, w -> w) -> m (Either e a, w -> w))
-> (Either e a, w -> w) -> m (Either e a, w -> w)
forall a b. (a -> b) -> a -> b
$! case Either e (a, w -> w)
a of
        Left  e
l      -> (e -> Either e a
forall a b. a -> Either a b
Left  e
l, w -> w
forall a. a -> a
id)
        Right (a
r, w -> w
f) -> (a -> Either e a
forall a b. b -> Either a b
Right a
r, w -> w
f)

{- $examples

Wrapping an IO action that can throw an error @e@:

> type ErrorWithIO e a = ErrorT e IO a
> ==> ErrorT (IO (Either e a))

An IO monad wrapped in @StateT@ inside of @ErrorT@:

> type ErrorAndStateWithIO e s a = ErrorT e (StateT s IO) a
> ==> ErrorT (StateT s IO (Either e a))
> ==> ErrorT (StateT (s -> IO (Either e a,s)))

-}