transformers-0.5.6.2: Concrete functor and monad transformers

Copyright(c) Michael Weber <michael.weber@post.rwth-aachen.de> 2001
(c) Jeff Newbern 2003-2006
(c) Andriy Palamarchuk 2006
LicenseBSD-style (see the file LICENSE)
MaintainerR.Paterson@city.ac.uk
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Error

Contents

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

The ErrorT monad transformer

class Error a where Source #

An exception to be thrown.

Minimal complete definition: noMsg or strMsg.

Minimal complete definition

Nothing

Methods

noMsg :: a Source #

Creates an exception without a message. The default implementation is strMsg "".

strMsg :: String -> a Source #

Creates an exception with a message. The default implementation of strMsg s is noMsg.

Instances
Error IOException Source # 
Instance details

Defined in Control.Monad.Trans.Error

ErrorList a => Error [a] Source #

A string can be thrown as an error.

Instance details

Defined in Control.Monad.Trans.Error

Methods

noMsg :: [a] Source #

strMsg :: String -> [a] Source #

class ErrorList a where Source #

Workaround so that we can have a Haskell 98 instance Error String.

Methods

listMsg :: String -> [a] Source #

Instances
ErrorList Char Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

listMsg :: String -> [Char] Source #

newtype ErrorT e m a Source #

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.

Constructors

ErrorT 

Fields

Instances
MonadTrans (ErrorT e) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

lift :: Monad m => m a -> ErrorT e m a Source #

(Monad m, Error e) => Monad (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

return :: a -> ErrorT e m a #

fail :: String -> ErrorT e m a #

Functor m => Functor (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

(MonadFix m, Error e) => MonadFix (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

(Monad m, Error e) => MonadFail (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

fail :: String -> ErrorT e m a #

(Functor m, Monad m) => Applicative (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

pure :: a -> ErrorT e m a #

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

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

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

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

Foldable f => Foldable (ErrorT e f) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

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

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

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

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

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

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

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

null :: ErrorT e f a -> Bool #

length :: ErrorT e f a -> Int #

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

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

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

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

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

Traversable f => Traversable (ErrorT e f) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

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

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

Contravariant m => Contravariant (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

contramap :: (a -> b) -> ErrorT e m b -> ErrorT e m a #

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

(Eq e, Eq1 m) => Eq1 (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

(Ord e, Ord1 m) => Ord1 (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

(Read e, Read1 m) => Read1 (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

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

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

(Show e, Show1 m) => Show1 (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

(Error e, MonadIO m) => MonadIO (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

(Functor m, Monad m, Error e) => Alternative (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

empty :: ErrorT e m a #

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

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

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

(Monad m, Error e) => MonadPlus (ErrorT e m) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

mzero :: ErrorT e m a #

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

(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

(Ord e, Ord1 m, Ord a) => Ord (ErrorT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

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

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

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

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

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

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

(Read e, Read1 m, Read a) => Read (ErrorT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

readList :: ReadS [ErrorT e m a] #

readPrec :: ReadPrec (ErrorT e m a) #

readListPrec :: ReadPrec [ErrorT e m a] #

(Show e, Show1 m, Show a) => Show (ErrorT e m a) Source # 
Instance details

Defined in Control.Monad.Trans.Error

Methods

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

show :: ErrorT e m a -> String #

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

mapErrorT :: (m (Either e a) -> n (Either e' b)) -> ErrorT e m a -> ErrorT e' n b Source #

Map the unwrapped computation using the given function.

Error operations

throwError :: Monad m => e -> ErrorT e m a Source #

Signal an error value e.

catchError Source #

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.

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)))

Orphan instances

Error e => Alternative (Either e) Source # 
Instance details

Methods

empty :: Either e a #

(<|>) :: Either e a -> Either e a -> Either e a #

some :: Either e a -> Either e [a] #

many :: Either e a -> Either e [a] #

Error e => MonadPlus (Either e) Source # 
Instance details

Methods

mzero :: Either e a #

mplus :: Either e a -> Either e a -> Either e a #