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 |
Safe Haskell | Safe |
Language | Haskell98 |
Control.Monad.Trans.Error
Description
Deprecated: Use Control.Monad.Trans.Except instead
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.
Synopsis
- class Error a where
- class ErrorList a where
- newtype ErrorT e m a = ErrorT {}
- mapErrorT :: (m (Either e a) -> n (Either e' b)) -> ErrorT e m a -> ErrorT e' n b
- throwError :: Monad m => e -> ErrorT e m a
- catchError :: Monad m => ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a
- liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ErrorT e m) a b
- liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ErrorT e m) a
- liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ErrorT e m) a
The ErrorT monad transformer
Minimal complete definition
Nothing
Methods
Creates an exception without a message.
The default implementation is
.strMsg
""
Instances
Error IOException # | |
Defined in Control.Monad.Trans.Error | |
ErrorList a => Error [a] # | A string can be thrown as an error. |
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.
Instances
MonadTrans (ErrorT e) # | |
(Monad m, Error e) => Monad (ErrorT e m) # | |
Functor m => Functor (ErrorT e m) # | |
(MonadFix m, Error e) => MonadFix (ErrorT e m) # | |
(Monad m, Error e) => MonadFail (ErrorT e m) # | |
(Functor m, Monad m) => Applicative (ErrorT e m) # | |
Defined in Control.Monad.Trans.Error Methods pure :: a -> ErrorT e m a Source # (<*>) :: ErrorT e m (a -> b) -> ErrorT e m a -> ErrorT e m b Source # liftA2 :: (a -> b -> c) -> ErrorT e m a -> ErrorT e m b -> ErrorT e m c Source # (*>) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m b Source # (<*) :: ErrorT e m a -> ErrorT e m b -> ErrorT e m a Source # | |
Foldable f => Foldable (ErrorT e f) # | |
Defined in Control.Monad.Trans.Error Methods fold :: Monoid m => ErrorT e f m -> m Source # foldMap :: Monoid m => (a -> m) -> ErrorT e f a -> m Source # foldMap' :: Monoid m => (a -> m) -> ErrorT e f a -> m Source # foldr :: (a -> b -> b) -> b -> ErrorT e f a -> b Source # foldr' :: (a -> b -> b) -> b -> ErrorT e f a -> b Source # foldl :: (b -> a -> b) -> b -> ErrorT e f a -> b Source # foldl' :: (b -> a -> b) -> b -> ErrorT e f a -> b Source # foldr1 :: (a -> a -> a) -> ErrorT e f a -> a Source # foldl1 :: (a -> a -> a) -> ErrorT e f a -> a Source # toList :: ErrorT e f a -> [a] Source # null :: ErrorT e f a -> Bool Source # length :: ErrorT e f a -> Int Source # elem :: Eq a => a -> ErrorT e f a -> Bool Source # maximum :: Ord a => ErrorT e f a -> a Source # minimum :: Ord a => ErrorT e f a -> a Source # | |
Traversable f => Traversable (ErrorT e f) # | |
Defined in Control.Monad.Trans.Error Methods traverse :: Applicative f0 => (a -> f0 b) -> ErrorT e f a -> f0 (ErrorT e f b) Source # sequenceA :: Applicative f0 => ErrorT e f (f0 a) -> f0 (ErrorT e f a) Source # mapM :: Monad m => (a -> m b) -> ErrorT e f a -> m (ErrorT e f b) Source # sequence :: Monad m => ErrorT e f (m a) -> m (ErrorT e f a) Source # | |
Contravariant m => Contravariant (ErrorT e m) # | |
(Eq e, Eq1 m) => Eq1 (ErrorT e m) # | |
(Ord e, Ord1 m) => Ord1 (ErrorT e m) # | |
Defined in Control.Monad.Trans.Error | |
(Read e, Read1 m) => Read1 (ErrorT e m) # | |
Defined in Control.Monad.Trans.Error Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ErrorT e m a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ErrorT e m a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ErrorT e m a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ErrorT e m a] Source # | |
(Show e, Show1 m) => Show1 (ErrorT e m) # | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) # | |
(Functor m, Monad m, Error e) => Alternative (ErrorT e m) # | |
(Monad m, Error e) => MonadPlus (ErrorT e m) # | |
(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) # | |
(Ord e, Ord1 m, Ord a) => Ord (ErrorT e m a) # | |
Defined in Control.Monad.Trans.Error | |
(Read e, Read1 m, Read a) => Read (ErrorT e m a) # | |
(Show e, Show1 m, Show a) => Show (ErrorT e m a) # | |
Error operations
throwError :: Monad m => e -> ErrorT e m a Source #
Signal an error value e
.
runErrorT
(throwError
e) =return
(Left
e)throwError
e >>= m =throwError
e
Arguments
:: 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 |
Handle an error.
catchError
h (lift
m) =lift
mcatchError
h (throwError
e) = h e
Lifting other operations
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ErrorT e m) a b Source #
Lift a callCC
operation to the new monad.
liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ErrorT e m) a Source #
Lift a listen
operation to the new monad.
liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ErrorT e m) a Source #
Lift a pass
operation to the new monad.
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)))