#if __GLASGOW_HASKELL__ >= 702
#endif
#if __GLASGOW_HASKELL__ >= 710
#endif
module Control.Monad.Trans.Except (
    
    Except,
    except,
    runExcept,
    mapExcept,
    withExcept,
    
    ExceptT(ExceptT),
    runExceptT,
    mapExceptT,
    withExceptT,
    
    throwE,
    catchE,
    
    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
import Data.Foldable (Foldable(foldMap))
import Data.Monoid
import Data.Traversable (Traversable(traverse))
type Except e = ExceptT e Identity
except :: (Monad m) => Either e a -> ExceptT e m a
except m = ExceptT (return m)
runExcept :: Except e a -> Either e a
runExcept (ExceptT m) = runIdentity m
mapExcept :: (Either e a -> Either e' b)
        -> Except e a
        -> Except e' b
mapExcept f = mapExceptT (Identity . f . runIdentity)
withExcept :: (e -> e') -> Except e a -> Except e' a
withExcept = withExceptT
newtype ExceptT e m a = ExceptT (m (Either e a))
instance (Eq e, Eq1 m) => Eq1 (ExceptT e m) where
    liftEq eq (ExceptT x) (ExceptT y) = liftEq (liftEq eq) x y
    
instance (Ord e, Ord1 m) => Ord1 (ExceptT e m) where
    liftCompare comp (ExceptT x) (ExceptT y) =
        liftCompare (liftCompare comp) x y
    
instance (Read e, Read1 m) => Read1 (ExceptT e m) where
    liftReadsPrec rp rl = readsData $
        readsUnaryWith (liftReadsPrec rp' rl') "ExceptT" ExceptT
      where
        rp' = liftReadsPrec rp rl
        rl' = liftReadList rp rl
instance (Show e, Show1 m) => Show1 (ExceptT e m) where
    liftShowsPrec sp sl d (ExceptT m) =
        showsUnaryWith (liftShowsPrec sp' sl') "ExceptT" d m
      where
        sp' = liftShowsPrec sp sl
        sl' = liftShowList sp sl
instance (Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a)
    where (==) = eq1
instance (Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a)
    where compare = compare1
instance (Read e, Read1 m, Read a) => Read (ExceptT e m a) where
    readsPrec = readsPrec1
instance (Show e, Show1 m, Show a) => Show (ExceptT e m a) where
    showsPrec = showsPrec1
runExceptT :: ExceptT e m a -> m (Either e a)
runExceptT (ExceptT m) = m
mapExceptT :: (m (Either e a) -> n (Either e' b))
        -> ExceptT e m a
        -> ExceptT e' n b
mapExceptT f m = ExceptT $ f (runExceptT m)
withExceptT :: (Functor m) => (e -> e') -> ExceptT e m a -> ExceptT e' m a
withExceptT f = mapExceptT $ fmap $ either (Left . f) Right
instance (Functor m) => Functor (ExceptT e m) where
    fmap f = ExceptT . fmap (fmap f) . runExceptT
    
instance (Foldable f) => Foldable (ExceptT e f) where
    foldMap f (ExceptT a) = foldMap (either (const mempty) f) a
    
instance (Traversable f) => Traversable (ExceptT e f) where
    traverse f (ExceptT a) =
        ExceptT <$> traverse (either (pure . Left) (fmap Right . f)) a
    
instance (Functor m, Monad m) => Applicative (ExceptT e m) where
    pure a = ExceptT $ return (Right a)
    
    ExceptT f <*> ExceptT v = ExceptT $ do
        mf <- f
        case mf of
            Left e -> return (Left e)
            Right k -> do
                mv <- v
                case mv of
                    Left e -> return (Left e)
                    Right x -> return (Right (k x))
    
    m *> k = m >>= \_ -> k
    
instance (Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) where
    empty = ExceptT $ return (Left mempty)
    
    ExceptT mx <|> ExceptT my = ExceptT $ do
        ex <- mx
        case ex of
            Left e -> liftM (either (Left . mappend e) Right) my
            Right x -> return (Right x)
    
instance (Monad m) => Monad (ExceptT e m) where
#if !(MIN_VERSION_base(4,8,0))
    return a = ExceptT $ return (Right a)
    
#endif
    m >>= k = ExceptT $ do
        a <- runExceptT m
        case a of
            Left e -> return (Left e)
            Right x -> runExceptT (k x)
    
#if !(MIN_VERSION_base(4,13,0))
    fail = ExceptT . fail
    
#endif
#if MIN_VERSION_base(4,9,0)
instance (Fail.MonadFail m) => Fail.MonadFail (ExceptT e m) where
    fail = ExceptT . Fail.fail
    
#endif
instance (Monad m, Monoid e) => MonadPlus (ExceptT e m) where
    mzero = ExceptT $ return (Left mempty)
    
    ExceptT mx `mplus` ExceptT my = ExceptT $ do
        ex <- mx
        case ex of
            Left e -> liftM (either (Left . mappend e) Right) my
            Right x -> return (Right x)
    
instance (MonadFix m) => MonadFix (ExceptT e m) where
    mfix f = ExceptT (mfix (runExceptT . f . either (const bomb) id))
      where bomb = error "mfix (ExceptT): inner computation returned Left value"
    
instance MonadTrans (ExceptT e) where
    lift = ExceptT . liftM Right
    
instance (MonadIO m) => MonadIO (ExceptT e m) where
    liftIO = lift . liftIO
    
#if MIN_VERSION_base(4,4,0)
instance (MonadZip m) => MonadZip (ExceptT e m) where
    mzipWith f (ExceptT a) (ExceptT b) = ExceptT $ mzipWith (liftA2 f) a b
    
#endif
#if MIN_VERSION_base(4,12,0)
instance Contravariant m => Contravariant (ExceptT e m) where
    contramap f = ExceptT . contramap (fmap f) . runExceptT
    
#endif
throwE :: (Monad m) => e -> ExceptT e m a
throwE = ExceptT . return . Left
catchE :: (Monad m) =>
    ExceptT e m a               
    -> (e -> ExceptT e' m a)    
                                
    -> ExceptT e' m a
m `catchE` h = ExceptT $ do
    a <- runExceptT m
    case a of
        Left  l -> runExceptT (h l)
        Right r -> return (Right r)
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
liftCallCC callCC f = ExceptT $
    callCC $ \ c ->
    runExceptT (f (\ a -> ExceptT $ c (Right a)))
liftListen :: (Monad m) => Listen w m (Either e a) -> Listen w (ExceptT e m) a
liftListen listen = mapExceptT $ \ m -> do
    (a, w) <- listen m
    return $! fmap (\ r -> (r, w)) a
liftPass :: (Monad m) => Pass w m (Either e a) -> Pass w (ExceptT e m) a
liftPass pass = mapExceptT $ \ m -> pass $ do
    a <- m
    return $! case a of
        Left l -> (Left l, id)
        Right (r, f) -> (Right r, f)