monadology-0.3: The best ideas in monad-related classes and types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Ology.Specific.ExceptT

Synopsis

Documentation

mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b #

Map the unwrapped computation using the given function.

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b #

Map the unwrapped computation using the given function.

runExcept :: Except e a -> Either e a #

Extractor for computations in the exception monad. (The inverse of except).

runExceptT :: ExceptT e m a -> m (Either e a) #

The inverse of ExceptT.

withExcept :: (e -> e') -> Except e a -> Except e' a #

Transform any exceptions thrown by the computation using the given function (a specialization of withExceptT).

withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a #

Transform any exceptions thrown by the computation using the given function.

type Except e = ExceptT e Identity #

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception. For a variant that continues after an error and collects all the errors, see Errors.

newtype ExceptT e (m :: Type -> Type) a #

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

  • e - The exception type.
  • m - The inner monad.

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Constructors

ExceptT (m (Either e a)) 

Instances

Instances details
TransConstraint MonadFail (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadFail m => Dict (MonadFail (ExceptT e m)) Source #

TransConstraint MonadFix (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadFix m => Dict (MonadFix (ExceptT e m)) Source #

TransConstraint MonadIO (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadIO m => Dict (MonadIO (ExceptT e m)) Source #

TransConstraint Functor (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). Functor m => Dict (Functor (ExceptT e m)) Source #

TransConstraint Monad (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). Monad m => Dict (Monad (ExceptT e m)) Source #

Monoid e => TransConstraint MonadPlus (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadPlus m => Dict (MonadPlus (ExceptT e m)) Source #

TransConstraint MonadException (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (ExceptT e m)) Source #

TransConstraint MonadInner (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadInner m => Dict (MonadInner (ExceptT e m)) Source #

MonadTransCoerce (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

transCoerce :: forall (m1 :: Type -> Type) (m2 :: Type -> Type). Coercible m1 m2 => Dict (Coercible (ExceptT e m1) (ExceptT e m2)) Source #

MonadTransHoist (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hoist :: forall (m1 :: Type -> Type) (m2 :: Type -> Type). (Monad m1, Monad m2) => (m1 --> m2) -> ExceptT e m1 --> ExceptT e m2 Source #

MonadTransTunnel (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Associated Types

type Tunnel (ExceptT e) :: Type -> Type Source #

Methods

tunnel :: Monad m => ((forall (m1 :: Type -> Type) a. Monad m1 => ExceptT e m1 a -> m1 (Tunnel (ExceptT e) a)) -> m (Tunnel (ExceptT e) r)) -> ExceptT e m r Source #

MonadTrans (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a #

MonadFail m => MonadFail (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fail :: String -> ExceptT e m a #

MonadFix m => MonadFix (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mfix :: (a -> ExceptT e m a) -> ExceptT e m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadZip m => MonadZip (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzip :: ExceptT e m a -> ExceptT e m b -> ExceptT e m (a, b) #

mzipWith :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

munzip :: ExceptT e m (a, b) -> (ExceptT e m a, ExceptT e m b) #

Foldable f => Foldable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fold :: Monoid m => ExceptT e f m -> m #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a #

toList :: ExceptT e f a -> [a] #

null :: ExceptT e f a -> Bool #

length :: ExceptT e f a -> Int #

elem :: Eq a => a -> ExceptT e f a -> Bool #

maximum :: Ord a => ExceptT e f a -> a #

minimum :: Ord a => ExceptT e f a -> a #

sum :: Num a => ExceptT e f a -> a #

product :: Num a => ExceptT e f a -> a #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool #

(Ord e, Ord1 m) => Ord1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering #

(Read e, Read1 m) => Read1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ExceptT e m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ExceptT e m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e m a] #

(Show e, Show1 m) => Show1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e m a] -> ShowS #

Contravariant m => Contravariant (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a' -> a) -> ExceptT e m a -> ExceptT e m a' #

(>$) :: b -> ExceptT e m b -> ExceptT e m a #

Traversable f => Traversable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ExceptT e f a -> f0 (ExceptT e f b) #

sequenceA :: Applicative f0 => ExceptT e f (f0 a) -> f0 (ExceptT e f a) #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

empty :: ExceptT e m a #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

some :: ExceptT e m a -> ExceptT e m [a] #

many :: ExceptT e m a -> ExceptT e m [a] #

(Functor m, Monad m) => Applicative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

Functor m => Functor (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b #

(<$) :: a -> ExceptT e m b -> ExceptT e m a #

Monad m => Monad (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

return :: a -> ExceptT e m a #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzero :: ExceptT e m a #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

Invariant m => Invariant (ExceptT e m)

from the transformers package

Instance details

Defined in Data.Functor.Invariant

Methods

invmap :: (a -> b) -> (b -> a) -> ExceptT e m a -> ExceptT e m b #

MonadException m => MonadException (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Associated Types

type Exc (ExceptT e m) Source #

Methods

throwExc :: Exc (ExceptT e m) -> ExceptT e m a Source #

catchExc :: ExceptT e m a -> (Exc (ExceptT e m) -> ExceptT e m a) -> ExceptT e m a Source #

MonadInner m => MonadInner (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

retrieveInner :: ExceptT e m a -> Result (Exc (ExceptT e m)) a Source #

MonadCatch ex m => MonadCatch (Either e ex) (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

catch :: ExceptT e m a -> (Either e ex -> ExceptT e m a) -> ExceptT e m a Source #

MonadThrow ex m => MonadThrow (Either e ex) (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

throw :: Either e ex -> ExceptT e m a Source #

(Read e, Read1 m, Read a) => Read (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

readsPrec :: Int -> ReadS (ExceptT e m a) #

readList :: ReadS [ExceptT e m a] #

readPrec :: ReadPrec (ExceptT e m a) #

readListPrec :: ReadPrec [ExceptT e m a] #

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(==) :: ExceptT e m a -> ExceptT e m a -> Bool #

(/=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

compare :: ExceptT e m a -> ExceptT e m a -> Ordering #

(<) :: ExceptT e m a -> ExceptT e m a -> Bool #

(<=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>=) :: ExceptT e m a -> ExceptT e m a -> Bool #

max :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

min :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

type Tunnel (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

type Tunnel (ExceptT e) = Either e
type Exc (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

type Exc (ExceptT e m) = Either e (Exc m)

throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a #

Signal an exception value e.

except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a #

Constructor for computations in the exception monad. (The inverse of runExcept).

catchE #

Arguments

:: forall (m :: Type -> Type) e a e'. Monad m 
=> ExceptT e m a

the inner computation

-> (e -> ExceptT e' m a)

a handler for exceptions in the inner computation

-> ExceptT e' m a 

Handle an exception.

transExcept :: forall t m e a. (MonadTransTunnel t, Applicative (Tunnel t), Monad m) => t (ExceptT e m) a -> t m (Either e a) Source #

Orphan instances

TransConstraint MonadFail (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadFail m => Dict (MonadFail (ExceptT e m)) Source #

TransConstraint MonadFix (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadFix m => Dict (MonadFix (ExceptT e m)) Source #

TransConstraint MonadIO (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadIO m => Dict (MonadIO (ExceptT e m)) Source #

TransConstraint Functor (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). Functor m => Dict (Functor (ExceptT e m)) Source #

TransConstraint Monad (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). Monad m => Dict (Monad (ExceptT e m)) Source #

Monoid e => TransConstraint MonadPlus (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadPlus m => Dict (MonadPlus (ExceptT e m)) Source #

TransConstraint MonadException (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (ExceptT e m)) Source #

TransConstraint MonadInner (ExceptT e) Source # 
Instance details

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadInner m => Dict (MonadInner (ExceptT e m)) Source #

MonadTransCoerce (ExceptT e) Source # 
Instance details

Methods

transCoerce :: forall (m1 :: Type -> Type) (m2 :: Type -> Type). Coercible m1 m2 => Dict (Coercible (ExceptT e m1) (ExceptT e m2)) Source #

MonadTransHoist (ExceptT e) Source # 
Instance details

Methods

hoist :: forall (m1 :: Type -> Type) (m2 :: Type -> Type). (Monad m1, Monad m2) => (m1 --> m2) -> ExceptT e m1 --> ExceptT e m2 Source #

MonadTransTunnel (ExceptT e) Source # 
Instance details

Associated Types

type Tunnel (ExceptT e) :: Type -> Type Source #

Methods

tunnel :: Monad m => ((forall (m1 :: Type -> Type) a. Monad m1 => ExceptT e m1 a -> m1 (Tunnel (ExceptT e) a)) -> m (Tunnel (ExceptT e) r)) -> ExceptT e m r Source #

MonadException m => MonadException (ExceptT e m) Source # 
Instance details

Associated Types

type Exc (ExceptT e m) Source #

Methods

throwExc :: Exc (ExceptT e m) -> ExceptT e m a Source #

catchExc :: ExceptT e m a -> (Exc (ExceptT e m) -> ExceptT e m a) -> ExceptT e m a Source #

MonadInner m => MonadInner (ExceptT e m) Source # 
Instance details

Methods

retrieveInner :: ExceptT e m a -> Result (Exc (ExceptT e m)) a Source #

MonadCatch ex m => MonadCatch (Either e ex) (ExceptT e m) Source # 
Instance details

Methods

catch :: ExceptT e m a -> (Either e ex -> ExceptT e m a) -> ExceptT e m a Source #

MonadThrow ex m => MonadThrow (Either e ex) (ExceptT e m) Source # 
Instance details

Methods

throw :: Either e ex -> ExceptT e m a Source #