| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trans.Ether.Except
Description
- type Except tag e = ExceptT tag e Identity
- except :: Monad m => proxy tag -> Either e a -> ExceptT tag e m a
- runExcept :: proxy tag -> Except tag e a -> Either e a
- data ExceptT tag e m a
- exceptT :: proxy tag -> m (Either e a) -> ExceptT tag e m a
- runExceptT :: proxy tag -> ExceptT tag e m a -> m (Either e a)
- mapExceptT :: proxy tag -> (m (Either e a) -> n (Either e' b)) -> ExceptT tag e m a -> ExceptT tag e' n b
- throw :: Monad m => proxy tag -> e -> ExceptT tag e m a
- catch :: Monad m => proxy tag -> ExceptT tag e m a -> (e -> ExceptT tag e m a) -> ExceptT tag e m a
- liftCallCC :: proxy tag -> CallCC m (Either e a) (Either e b) -> CallCC (ExceptT tag e m) a b
- liftListen :: Monad m => proxy tag -> Listen w m (Either e a) -> Listen w (ExceptT tag e m) a
- liftPass :: Monad m => proxy tag -> Pass w m (Either e a) -> Pass w (ExceptT tag e m) a
- liftCatch :: proxy tag -> Catch e m (Either e' a) -> Catch e (ExceptT tag e' m) a
The Except monad
except :: Monad m => proxy tag -> Either e a -> ExceptT tag e m a Source
Constructor for computations in the exception monad
(the inverse of runExcept).
runExcept :: proxy tag -> Except tag e a -> Either e a Source
Runs an Except and returns either an exception or a normal value.
The ExceptT monad transformer
The exception monad transformer.
The return function returns a normal value, while >>= exits on
the first exception.
Instances
| MonadReader tag r m => MonadReader tag r (ExceptT tag' e m) | |
| MonadState tag s m => MonadState tag s (ExceptT tag' e m) | |
| MonadExcept tag e m => MonadExcept tag e (ExceptT tag' e' m) | |
| Monad m => MonadExcept tag e (ExceptT tag e m) | |
| MonadWriter tag w m => MonadWriter tag w (ExceptT tag' e m) | |
| MonadError e' m => MonadError e' (ExceptT tag e m) | |
| MonadReader r m => MonadReader r (ExceptT tag e m) | |
| MonadState s m => MonadState s (ExceptT tag e m) | |
| MonadWriter w m => MonadWriter w (ExceptT tag e m) | |
| MonadTrans (ExceptT tag e) | |
| (Monad m, Functor m, Monoid e) => Alternative (ExceptT tag e m) | |
| Monad m => Monad (ExceptT tag e m) | |
| Functor m => Functor (ExceptT tag e m) | |
| MonadFix m => MonadFix (ExceptT tag e m) | |
| (Monad m, Monoid e) => MonadPlus (ExceptT tag e m) | |
| (Monad m, Functor m) => Applicative (ExceptT tag e m) | |
| MonadIO m => MonadIO (ExceptT tag e m) | |
| MonadCont m => MonadCont (ExceptT tag e m) | |
| Taggable (ExceptT tag e m) | |
| Tagged (ExceptT tag e m) tag | |
| Generic (ExceptT tag e m a) | |
| Newtype (ExceptT tag e m a) | |
| type Untagged (ExceptT tag e m) = ExceptT e m | |
| type Tag (ExceptT tag e m) = Just * tag | |
| type Inner (ExceptT tag e m) = Just (* -> *) m | |
| type Rep (ExceptT tag e m a) | |
| type O (ExceptT tag e m a) = GO (Rep (ExceptT tag e m a)) |
exceptT :: proxy tag -> m (Either e a) -> ExceptT tag e m a Source
Constructor for computations in the exception monad transformer.
runExceptT :: proxy tag -> ExceptT tag e m a -> m (Either e a) Source
Runs an ExceptT and returns either an exception or a normal value.
mapExceptT :: proxy tag -> (m (Either e a) -> n (Either e' b)) -> ExceptT tag e m a -> ExceptT tag e' n b Source
Transforms the computation inside an ExceptT.
runExceptTtag (mapExceptTtag f m) = f (runExceptTtag m)
Exception operations
throw :: Monad m => proxy tag -> e -> ExceptT tag e m a Source
Is used within a monadic computation to begin exception processing.
catch :: Monad m => proxy tag -> ExceptT tag e m a -> (e -> ExceptT tag e m a) -> ExceptT tag e m a Source
A handler function to handle previous exceptions and return to normal execution.
Lifting other operations
liftCallCC :: proxy tag -> CallCC m (Either e a) (Either e b) -> CallCC (ExceptT tag e m) a b Source
Lift a callCC operation to the new monad.
liftListen :: Monad m => proxy tag -> Listen w m (Either e a) -> Listen w (ExceptT tag e m) a Source
Lift a listen operation to the new monad.