{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveGeneric #-}
#endif
#if __GLASGOW_HASKELL__ >= 710 && __GLASGOW_HASKELL__ < 802
{-# LANGUAGE AutoDeriveTypeable #-}
#endif
module Control.Monad.Trans.Except (
    
    Except,
    except,
    runExcept,
    mapExcept,
    withExcept,
    
    ExceptT(..),
    mapExceptT,
    withExceptT,
    
    throwE,
    catchE,
    handleE,
    tryE,
    finallyE,
    
    liftCallCC,
    liftListen,
    liftPass,
  ) 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 Data.Functor.Identity
import Control.Applicative
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,4,0)
import Control.Monad.Zip (MonadZip(mzipWith))
#endif
#if !(MIN_VERSION_base(4,8,0)) || defined(__MHS__)
import Data.Foldable (Foldable(foldMap))
import Data.Monoid (Monoid(mempty, mappend))
import Data.Traversable (Traversable(traverse))
#endif
#if __GLASGOW_HASKELL__ >= 704
import GHC.Generics
#endif
type Except e = ExceptT e Identity
except :: (Monad m) => Either e a -> ExceptT e m a
except :: forall (m :: * -> *) e a. Monad m => Either e a -> ExceptT e m a
except Either e a
m = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (Either e a -> m (Either e a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Either e a
m)
{-# INLINE except #-}
runExcept :: Except e a -> Either e a
runExcept :: forall e a. Except e a -> Either e a
runExcept (ExceptT Identity (Either e a)
m) = Identity (Either e a) -> Either e a
forall a. Identity a -> a
runIdentity Identity (Either e a)
m
{-# INLINE runExcept #-}
mapExcept :: (Either e a -> Either e' b)
        -> Except e a
        -> Except e' b
mapExcept :: forall e a e' b.
(Either e a -> Either e' b) -> Except e a -> Except e' b
mapExcept Either e a -> Either e' b
f = (Identity (Either e a) -> Identity (Either e' b))
-> ExceptT e Identity a -> ExceptT e' Identity b
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT (Either e' b -> Identity (Either e' b)
forall a. a -> Identity a
Identity (Either e' b -> Identity (Either e' b))
-> (Identity (Either e a) -> Either e' b)
-> Identity (Either e a)
-> Identity (Either e' b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either e a -> Either e' b
f (Either e a -> Either e' b)
-> (Identity (Either e a) -> Either e a)
-> Identity (Either e a)
-> Either e' b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identity (Either e a) -> Either e a
forall a. Identity a -> a
runIdentity)
{-# INLINE mapExcept #-}
withExcept :: (e -> e') -> Except e a -> Except e' a
withExcept :: forall e e' a. (e -> e') -> Except e a -> Except e' a
withExcept = (e -> e') -> ExceptT e Identity a -> ExceptT e' Identity a
forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> ExceptT e m a -> ExceptT e' m a
withExceptT
{-# INLINE withExcept #-}
newtype ExceptT e m a = ExceptT { forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT :: m (Either e a) }
#if __GLASGOW_HASKELL__ >= 710
    deriving ((forall x. ExceptT e m a -> Rep (ExceptT e m a) x)
-> (forall x. Rep (ExceptT e m a) x -> ExceptT e m a)
-> Generic (ExceptT e m a)
forall x. Rep (ExceptT e m a) x -> ExceptT e m a
forall x. ExceptT e m a -> Rep (ExceptT e m a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall e (m :: * -> *) a x. Rep (ExceptT e m a) x -> ExceptT e m a
forall e (m :: * -> *) a x. ExceptT e m a -> Rep (ExceptT e m a) x
$cfrom :: forall e (m :: * -> *) a x. ExceptT e m a -> Rep (ExceptT e m a) x
from :: forall x. ExceptT e m a -> Rep (ExceptT e m a) x
$cto :: forall e (m :: * -> *) a x. Rep (ExceptT e m a) x -> ExceptT e m a
to :: forall x. Rep (ExceptT e m a) x -> ExceptT e m a
Generic, (forall a. ExceptT e m a -> Rep1 (ExceptT e m) a)
-> (forall a. Rep1 (ExceptT e m) a -> ExceptT e m a)
-> Generic1 (ExceptT e m)
forall a. Rep1 (ExceptT e m) a -> ExceptT e m a
forall a. ExceptT e m a -> Rep1 (ExceptT e m) a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
forall e (m :: * -> *) a.
Functor m =>
Rep1 (ExceptT e m) a -> ExceptT e m a
forall e (m :: * -> *) a.
Functor m =>
ExceptT e m a -> Rep1 (ExceptT e m) a
$cfrom1 :: forall e (m :: * -> *) a.
Functor m =>
ExceptT e m a -> Rep1 (ExceptT e m) a
from1 :: forall a. ExceptT e m a -> Rep1 (ExceptT e m) a
$cto1 :: forall e (m :: * -> *) a.
Functor m =>
Rep1 (ExceptT e m) a -> ExceptT e m a
to1 :: forall a. Rep1 (ExceptT e m) a -> ExceptT e m a
Generic1)
#elif __GLASGOW_HASKELL__ >= 704
    deriving (Generic)
#endif
instance (Eq e, Eq1 m) => Eq1 (ExceptT e m) where
    liftEq :: forall a b.
(a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool
liftEq a -> b -> Bool
eq (ExceptT m (Either e a)
x) (ExceptT m (Either e b)
y) = (Either e a -> Either e b -> Bool)
-> m (Either e a) -> m (Either e b) -> Bool
forall a b. (a -> b -> Bool) -> m a -> m 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 a b. (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
    {-# INLINE liftEq #-}
instance (Ord e, Ord1 m) => Ord1 (ExceptT e m) where
    liftCompare :: forall a b.
(a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering
liftCompare a -> b -> Ordering
comp (ExceptT m (Either e a)
x) (ExceptT m (Either e b)
y) =
        (Either e a -> Either e b -> Ordering)
-> m (Either e a) -> m (Either e b) -> Ordering
forall a b. (a -> b -> Ordering) -> m a -> m 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 a b.
(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
    {-# INLINE liftCompare #-}
instance (Read e, Read1 m) => Read1 (ExceptT e m) where
    liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e m a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl = (String -> ReadS (ExceptT e m a)) -> Int -> ReadS (ExceptT e m a)
forall a. (String -> ReadS a) -> Int -> ReadS a
readsData ((String -> ReadS (ExceptT e m a)) -> Int -> ReadS (ExceptT e m a))
-> (String -> ReadS (ExceptT e m a))
-> Int
-> ReadS (ExceptT e m a)
forall a b. (a -> b) -> a -> b
$
        (Int -> ReadS (m (Either e a)))
-> String
-> (m (Either e a) -> ExceptT e m a)
-> String
-> ReadS (ExceptT 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 a. (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (m 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
"ExceptT" m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT
      where
        rp' :: Int -> ReadS (Either e a)
rp' = (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Either e a)
forall a.
(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 a. (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 (ExceptT e m) where
    liftShowsPrec :: forall a.
(Int -> a -> ShowS)
-> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl Int
d (ExceptT m (Either e a)
m) =
        (Int -> m (Either e a) -> ShowS)
-> String -> Int -> m (Either e a) -> ShowS
forall a. (Int -> a -> ShowS) -> String -> Int -> a -> ShowS
showsUnaryWith ((Int -> Either e a -> ShowS)
-> ([Either e a] -> ShowS) -> Int -> m (Either e a) -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> m a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> Either e a -> ShowS
sp' [Either e a] -> ShowS
sl') String
"ExceptT" Int
d m (Either e a)
m
      where
        sp' :: Int -> Either e a -> ShowS
sp' = (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Either e a -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Either e a -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
liftShowsPrec Int -> a -> ShowS
sp [a] -> ShowS
sl
        sl' :: [Either e a] -> ShowS
sl' = (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Either e a] -> ShowS
forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [Either e a] -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS
liftShowList Int -> a -> ShowS
sp [a] -> ShowS
sl
instance (Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a)
    where == :: ExceptT e m a -> ExceptT e m a -> Bool
(==) = ExceptT e m a -> ExceptT 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 (ExceptT e m a)
    where compare :: ExceptT e m a -> ExceptT e m a -> Ordering
compare = ExceptT e m a -> ExceptT 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 (ExceptT e m a) where
    readsPrec :: Int -> ReadS (ExceptT e m a)
readsPrec = Int -> ReadS (ExceptT e m a)
forall (f :: * -> *) a. (Read1 f, Read a) => Int -> ReadS (f a)
readsPrec1
instance (Show e, Show1 m, Show a) => Show (ExceptT e m a) where
    showsPrec :: Int -> ExceptT e m a -> ShowS
showsPrec = Int -> ExceptT e m a -> ShowS
forall (f :: * -> *) a. (Show1 f, Show a) => Int -> f a -> ShowS
showsPrec1
mapExceptT :: (m (Either e a) -> n (Either e' b))
        -> ExceptT e m a
        -> ExceptT e' n b
mapExceptT :: forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT m (Either e a) -> n (Either e' b)
f ExceptT e m a
m = n (Either e' b) -> ExceptT e' n b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (n (Either e' b) -> ExceptT e' n b)
-> n (Either e' b) -> ExceptT e' n b
forall a b. (a -> b) -> a -> b
$ m (Either e a) -> n (Either e' b)
f (ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT e m a
m)
{-# INLINE mapExceptT #-}
withExceptT :: (Functor m) => (e -> e') -> ExceptT e m a -> ExceptT e' m a
withExceptT :: forall (m :: * -> *) e e' a.
Functor m =>
(e -> e') -> ExceptT e m a -> ExceptT e' m a
withExceptT e -> e'
f = (m (Either e a) -> m (Either e' a))
-> ExceptT e m a -> ExceptT e' m a
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT ((m (Either e a) -> m (Either e' a))
 -> ExceptT e m a -> ExceptT e' m a)
-> (m (Either e a) -> m (Either e' a))
-> ExceptT e m a
-> ExceptT e' m a
forall a b. (a -> b) -> a -> b
$ (Either e a -> Either e' a) -> m (Either e a) -> m (Either e' a)
forall a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Either e a -> Either e' a) -> m (Either e a) -> m (Either e' a))
-> (Either e a -> Either e' a) -> m (Either e a) -> m (Either e' a)
forall a b. (a -> b) -> a -> b
$ (e -> Either e' a)
-> (a -> Either e' a) -> Either e a -> Either e' a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e' -> Either e' a
forall a b. a -> Either a b
Left (e' -> Either e' a) -> (e -> e') -> e -> Either e' a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> e'
f) a -> Either e' a
forall a b. b -> Either a b
Right
{-# INLINE withExceptT #-}
instance (Functor m) => Functor (ExceptT e m) where
    fmap :: forall a b. (a -> b) -> ExceptT e m a -> ExceptT e m b
fmap a -> b
f = m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> (ExceptT e m a -> m (Either e b))
-> ExceptT e m a
-> ExceptT 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 a b. (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Either e a -> Either e b
forall a b. (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))
-> (ExceptT e m a -> m (Either e a))
-> ExceptT e m a
-> m (Either e b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
    {-# INLINE fmap #-}
instance (Foldable f) => Foldable (ExceptT e f) where
    foldMap :: forall m a. Monoid m => (a -> m) -> ExceptT e f a -> m
foldMap a -> m
f (ExceptT f (Either e a)
a) = (Either e a -> m) -> f (Either e a) -> m
forall m a. Monoid m => (a -> m) -> f 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
    {-# INLINE foldMap #-}
instance (Traversable f) => Traversable (ExceptT e f) where
    traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ExceptT e f a -> f (ExceptT e f b)
traverse a -> f b
f (ExceptT f (Either e a)
a) =
        f (Either e b) -> ExceptT e f b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (f (Either e b) -> ExceptT e f b)
-> f (f (Either e b)) -> f (ExceptT 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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f 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 a. a -> f a
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 a b. (a -> b) -> f a -> f 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
    {-# INLINE traverse #-}
instance (Functor m, Monad m) => Applicative (ExceptT e m) where
    pure :: forall a. a -> ExceptT e m a
pure a
a = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
a)
    {-# INLINE pure #-}
    ExceptT m (Either e (a -> b))
f <*> :: forall a b. ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b
<*> ExceptT m (Either e a)
v = m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> m (Either e b) -> ExceptT e m b
forall a b. (a -> b) -> a -> b
$ do
        Either e (a -> b)
mf <- m (Either e (a -> b))
f
        case Either e (a -> b)
mf of
            Left e
e -> Either e b -> m (Either e b)
forall a. a -> m a
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 <- m (Either e a)
v
                case Either e a
mv of
                    Left e
e -> Either e b -> m (Either e b)
forall a. a -> m a
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 a. a -> m a
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))
    {-# INLINEABLE (<*>) #-}
    ExceptT e m a
m *> :: forall a b. ExceptT e m a -> ExceptT e m b -> ExceptT e m b
*> ExceptT e m b
k = ExceptT e m a
m ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b
forall a b. ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \a
_ -> ExceptT e m b
k
    {-# INLINE (*>) #-}
instance (Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) where
    empty :: forall a. ExceptT e m a
empty = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall a. a -> m 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. Monoid a => a
mempty)
    {-# INLINE empty #-}
    ExceptT m (Either e a)
mx <|> :: forall a. ExceptT e m a -> ExceptT e m a -> ExceptT e m a
<|> ExceptT m (Either e a)
my = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT e m a
forall a b. (a -> b) -> a -> b
$ do
        Either e a
ex <- m (Either e a)
mx
        case Either e a
ex of
            Left e
e -> (Either e a -> Either e a) -> m (Either e a) -> m (Either e a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((e -> Either e a) -> (a -> Either e a) -> Either e a -> Either e a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e -> Either e a
forall a b. a -> Either a b
Left (e -> Either e a) -> (e -> e) -> e -> Either e a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> e -> e
forall a. Monoid a => a -> a -> a
mappend e
e) a -> Either e a
forall a b. b -> Either a b
Right) m (Either e a)
my
            Right a
x -> Either e a -> m (Either e a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
x)
    {-# INLINEABLE (<|>) #-}
instance (Monad m) => Monad (ExceptT e m) where
#if !(MIN_VERSION_base(4,8,0))
    return a = ExceptT $ return (Right a)
    {-# INLINE return #-}
#endif
    ExceptT e m a
m >>= :: forall a b. ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b
>>= a -> ExceptT e m b
k = m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> m (Either e b) -> ExceptT e m b
forall a b. (a -> b) -> a -> b
$ do
        Either e a
a <- ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT e m a
m
        case Either e a
a of
            Left e
e -> Either e b -> m (Either e b)
forall a. a -> m a
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 -> ExceptT e m b -> m (Either e b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (a -> ExceptT e m b
k a
x)
    {-# INLINE (>>=) #-}
#if !(MIN_VERSION_base(4,13,0))
    fail = ExceptT . fail
    {-# INLINE fail #-}
#endif
#if MIN_VERSION_base(4,9,0)
instance (Fail.MonadFail m) => Fail.MonadFail (ExceptT e m) where
    fail :: forall a. String -> ExceptT e m a
fail = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> (String -> m (Either e a)) -> String -> ExceptT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m (Either e a)
forall a. String -> m a
forall (m :: * -> *) a. MonadFail m => String -> m a
Fail.fail
    {-# INLINE fail #-}
#endif
instance (Monad m, Monoid e) => MonadPlus (ExceptT e m) where
    mzero :: forall a. ExceptT e m a
mzero = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT e m a
forall a b. (a -> b) -> a -> b
$ Either e a -> m (Either e a)
forall a. a -> m 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. Monoid a => a
mempty)
    {-# INLINE mzero #-}
    ExceptT m (Either e a)
mx mplus :: forall a. ExceptT e m a -> ExceptT e m a -> ExceptT e m a
`mplus` ExceptT m (Either e a)
my = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT e m a
forall a b. (a -> b) -> a -> b
$ do
        Either e a
ex <- m (Either e a)
mx
        case Either e a
ex of
            Left e
e -> (Either e a -> Either e a) -> m (Either e a) -> m (Either e a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM ((e -> Either e a) -> (a -> Either e a) -> Either e a -> Either e a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (e -> Either e a
forall a b. a -> Either a b
Left (e -> Either e a) -> (e -> e) -> e -> Either e a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> e -> e
forall a. Monoid a => a -> a -> a
mappend e
e) a -> Either e a
forall a b. b -> Either a b
Right) m (Either e a)
my
            Right a
x -> Either e a -> m (Either e a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e a
forall a b. b -> Either a b
Right a
x)
    {-# INLINEABLE mplus #-}
instance (MonadFix m) => MonadFix (ExceptT e m) where
    mfix :: forall a. (a -> ExceptT e m a) -> ExceptT e m a
mfix a -> ExceptT e m a
f = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT ((Either e a -> m (Either e a)) -> m (Either e a)
forall a. (a -> m a) -> m a
forall (m :: * -> *) a. MonadFix m => (a -> m a) -> m a
mfix (ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT e m a -> m (Either e a))
-> (Either e a -> ExceptT e m a) -> Either e a -> m (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ExceptT e m a
f (a -> ExceptT e m a)
-> (Either e a -> a) -> Either e a -> ExceptT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (e -> a) -> (a -> a) -> Either e a -> a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (a -> e -> a
forall a b. a -> b -> a
const a
forall {a}. a
bomb) a -> a
forall a. a -> a
id))
      where bomb :: a
bomb = String -> a
forall a. HasCallStack => String -> a
error String
"mfix (ExceptT): inner computation returned Left value"
    {-# INLINE mfix #-}
instance MonadTrans (ExceptT e) where
    lift :: forall (m :: * -> *) a. Monad m => m a -> ExceptT e m a
lift = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> (m a -> m (Either e a)) -> m a -> ExceptT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Either e a) -> m a -> m (Either e a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> Either e a
forall a b. b -> Either a b
Right
    {-# INLINE lift #-}
instance (MonadIO m) => MonadIO (ExceptT e m) where
    liftIO :: forall a. IO a -> ExceptT e m a
liftIO = m a -> ExceptT e m a
forall (m :: * -> *) a. Monad m => m a -> ExceptT e m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m a -> ExceptT e m a) -> (IO a -> m a) -> IO a -> ExceptT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
    {-# INLINE liftIO #-}
#if MIN_VERSION_base(4,4,0)
instance (MonadZip m) => MonadZip (ExceptT e m) where
    mzipWith :: forall a b c.
(a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c
mzipWith a -> b -> c
f (ExceptT m (Either e a)
a) (ExceptT m (Either e b)
b) = m (Either e c) -> ExceptT e m c
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e c) -> ExceptT e m c)
-> m (Either e c) -> ExceptT e m c
forall a b. (a -> b) -> a -> b
$ (Either e a -> Either e b -> Either e c)
-> m (Either e a) -> m (Either e b) -> m (Either e c)
forall a b c. (a -> b -> c) -> m a -> m b -> m c
forall (m :: * -> *) a b c.
MonadZip m =>
(a -> b -> c) -> m a -> m b -> m c
mzipWith ((a -> b -> c) -> Either e a -> Either e b -> Either e c
forall a b c.
(a -> b -> c) -> Either e a -> Either e b -> Either e c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> b -> c
f) m (Either e a)
a m (Either e b)
b
    {-# INLINE mzipWith #-}
#endif
#if MIN_VERSION_base(4,12,0)
instance Contravariant m => Contravariant (ExceptT e m) where
    contramap :: forall a' a. (a' -> a) -> ExceptT e m a -> ExceptT e m a'
contramap a' -> a
f = m (Either e a') -> ExceptT e m a'
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a') -> ExceptT e m a')
-> (ExceptT e m a -> m (Either e a'))
-> ExceptT e m a
-> ExceptT 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 a' a. (a' -> a) -> m a -> m a'
forall (f :: * -> *) a' a.
Contravariant f =>
(a' -> a) -> f a -> f a'
contramap ((a' -> a) -> Either e a' -> Either e a
forall a b. (a -> b) -> Either e a -> Either e b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a' -> a
f) (m (Either e a) -> m (Either e a'))
-> (ExceptT e m a -> m (Either e a))
-> ExceptT e m a
-> m (Either e a')
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT
    {-# INLINE contramap #-}
#endif
throwE :: (Monad m) => e -> ExceptT e m a
throwE :: forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> (e -> m (Either e a)) -> e -> ExceptT e m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either e a -> m (Either e a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either e a -> m (Either e a))
-> (e -> Either e a) -> e -> m (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e a
forall a b. a -> Either a b
Left
{-# INLINE throwE #-}
catchE :: (Monad m) =>
    ExceptT e m a               
    -> (e -> ExceptT e' m a)    
                                
    -> ExceptT e' m a
ExceptT e m a
m catchE :: forall (m :: * -> *) e a e'.
Monad m =>
ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
`catchE` e -> ExceptT e' m a
h = m (Either e' a) -> ExceptT e' m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e' a) -> ExceptT e' m a)
-> m (Either e' a) -> ExceptT e' m a
forall a b. (a -> b) -> a -> b
$ do
    Either e a
a <- ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ExceptT e m a
m
    case Either e a
a of
        Left  e
l -> ExceptT e' m a -> m (Either e' a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (e -> ExceptT e' m a
h e
l)
        Right a
r -> Either e' a -> m (Either e' a)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either e' a
forall a b. b -> Either a b
Right a
r)
{-# INLINE catchE #-}
handleE :: Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
handleE :: forall (m :: * -> *) e e' a.
Monad m =>
(e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
handleE = (ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a)
-> (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
forall (m :: * -> *) e a e'.
Monad m =>
ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
catchE
{-# INLINE handleE #-}
tryE :: Monad m => ExceptT e m a -> ExceptT e m (Either e a)
tryE :: forall (m :: * -> *) e a.
Monad m =>
ExceptT e m a -> ExceptT e m (Either e a)
tryE ExceptT e m a
m = ExceptT e m (Either e a)
-> (e -> ExceptT e m (Either e a)) -> ExceptT e m (Either e a)
forall (m :: * -> *) e a e'.
Monad m =>
ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
catchE ((a -> Either e a) -> ExceptT e m a -> ExceptT e m (Either e a)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM a -> Either e a
forall a b. b -> Either a b
Right ExceptT e m a
m) (Either e a -> ExceptT e m (Either e a)
forall a. a -> ExceptT e m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either e a -> ExceptT e m (Either e a))
-> (e -> Either e a) -> e -> ExceptT e m (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Either e a
forall a b. a -> Either a b
Left)
{-# INLINE tryE #-}
finallyE :: Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a
finallyE :: forall (m :: * -> *) e a.
Monad m =>
ExceptT e m a -> ExceptT e m () -> ExceptT e m a
finallyE ExceptT e m a
m ExceptT e m ()
closer = do
    Either e a
res <- ExceptT e m a -> ExceptT e m (Either e a)
forall (m :: * -> *) e a.
Monad m =>
ExceptT e m a -> ExceptT e m (Either e a)
tryE ExceptT e m a
m
    ExceptT e m ()
closer
    (e -> ExceptT e m a)
-> (a -> ExceptT e m a) -> Either e a -> ExceptT e m a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either e -> ExceptT e m a
forall (m :: * -> *) e a. Monad m => e -> ExceptT e m a
throwE a -> ExceptT e m a
forall a. a -> ExceptT e m a
forall (m :: * -> *) a. Monad m => a -> m a
return Either e a
res
{-# INLINE finallyE #-}
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
liftCallCC :: forall (m :: * -> *) e a b.
CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
liftCallCC CallCC m (Either e a) (Either e b)
callCC (a -> ExceptT e m b) -> ExceptT e m a
f = m (Either e a) -> ExceptT e m a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e a) -> ExceptT e m a)
-> m (Either e a) -> ExceptT 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 ->
    ExceptT e m a -> m (Either e a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT ((a -> ExceptT e m b) -> ExceptT e m a
f (\ a
a -> m (Either e b) -> ExceptT e m b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT (m (Either e b) -> ExceptT e m b)
-> m (Either e b) -> ExceptT 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)))
{-# INLINE liftCallCC #-}
liftListen :: (Monad m) => Listen w m (Either e a) -> Listen w (ExceptT e m) a
liftListen :: forall (m :: * -> *) w e a.
Monad m =>
Listen w m (Either e a) -> Listen w (ExceptT e m) a
liftListen Listen w m (Either e a)
listen = (m (Either e a) -> m (Either e (a, w)))
-> ExceptT e m a -> ExceptT e m (a, w)
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT ((m (Either e a) -> m (Either e (a, w)))
 -> ExceptT e m a -> ExceptT e m (a, w))
-> (m (Either e a) -> m (Either e (a, w)))
-> ExceptT e m a
-> ExceptT 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 a. a -> m a
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 a b. (a -> b) -> Either e a -> Either e b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ a
r -> (a
r, w
w)) Either e a
a
{-# INLINE liftListen #-}
liftPass :: (Monad m) => Pass w m (Either e a) -> Pass w (ExceptT e m) a
liftPass :: forall (m :: * -> *) w e a.
Monad m =>
Pass w m (Either e a) -> Pass w (ExceptT e m) a
liftPass Pass w m (Either e a)
pass = (m (Either e (a, w -> w)) -> m (Either e a))
-> ExceptT e m (a, w -> w) -> ExceptT e m a
forall (m :: * -> *) e a (n :: * -> *) e' b.
(m (Either e a) -> n (Either e' b))
-> ExceptT e m a -> ExceptT e' n b
mapExceptT ((m (Either e (a, w -> w)) -> m (Either e a))
 -> ExceptT e m (a, w -> w) -> ExceptT e m a)
-> (m (Either e (a, w -> w)) -> m (Either e a))
-> ExceptT e m (a, w -> w)
-> ExceptT 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 a. a -> m a
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)
{-# INLINE liftPass #-}