constrained-monads-0.1.0.0: Typeclasses and instances for monads with constraints.

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Constrained.Error

Description

This module is a duplication of the Control.Monad.Error module from the mtl, for constrained monads.

Synopsis

Documentation

class Monad m => MonadError e m | m -> e where Source #

A class for monads which can error out.

Minimal complete definition

throwError, catchError

Associated Types

type SuitableError m a :: Constraint Source #

Methods

throwError :: SuitableError m a => e -> m a Source #

Raise an error.

catchError :: SuitableError m a => m a -> (e -> m a) -> m a Source #

A handler function to handle previous errors and return to normal execution. A common idiom is:

do { action1; action2; action3 } `catchError` handler

where the action functions can call throwError. Note that handler and the do-block must have the same return type.

Instances

MonadError e m => MonadError e (MaybeT m) Source # 

Associated Types

type SuitableError (MaybeT m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (MaybeT m) a => e -> MaybeT m a Source #

catchError :: SuitableError (MaybeT m) a => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a Source #

MonadError e (Either e) Source # 

Associated Types

type SuitableError (Either e :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (Either e) a => e -> Either e a Source #

catchError :: SuitableError (Either e) a => Either e a -> (e -> Either e a) -> Either e a Source #

MonadError e m => MonadError e (StateT s m) Source # 

Associated Types

type SuitableError (StateT s m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (StateT s m) a => e -> StateT s m a Source #

catchError :: SuitableError (StateT s m) a => StateT s m a -> (e -> StateT s m a) -> StateT s m a Source #

MonadError e m => MonadError e (StateT s m) Source # 

Associated Types

type SuitableError (StateT s m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (StateT s m) a => e -> StateT s m a Source #

catchError :: SuitableError (StateT s m) a => StateT s m a -> (e -> StateT s m a) -> StateT s m a Source #

MonadError e m => MonadError e (IdentityT * m) Source # 

Associated Types

type SuitableError (IdentityT * m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (IdentityT * m) a => e -> IdentityT * m a Source #

catchError :: SuitableError (IdentityT * m) a => IdentityT * m a -> (e -> IdentityT * m a) -> IdentityT * m a Source #

Monad m => MonadError e (ExceptT e m) Source # 

Associated Types

type SuitableError (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (ExceptT e m) a => e -> ExceptT e m a Source #

catchError :: SuitableError (ExceptT e m) a => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a Source #

MonadError e m => MonadError e (WriterT w m) Source # 

Associated Types

type SuitableError (WriterT w m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (WriterT w m) a => e -> WriterT w m a Source #

catchError :: SuitableError (WriterT w m) a => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source #

MonadError e m => MonadError e (ReaderT * r m) Source # 

Associated Types

type SuitableError (ReaderT * r m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (ReaderT * r m) a => e -> ReaderT * r m a Source #

catchError :: SuitableError (ReaderT * r m) a => ReaderT * r m a -> (e -> ReaderT * r m a) -> ReaderT * r m a Source #

newtype ExceptT e m 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

Monad m => MonadError e (ExceptT e m) Source # 

Associated Types

type SuitableError (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

throwError :: SuitableError (ExceptT e m) a => e -> ExceptT e m a Source #

catchError :: SuitableError (ExceptT e m) a => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a Source #

MonadReader r m => MonadReader r (ExceptT e m) Source # 

Associated Types

type ReaderSuitable (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

ask :: ExceptT e m r Source #

local :: (ReaderSuitable (ExceptT e m) a, ReaderSuitable (ExceptT e m) r) => (r -> r) -> ExceptT e m a -> ExceptT e m a Source #

reader :: (ReaderSuitable (ExceptT e m) r, ReaderSuitable (ExceptT e m) a) => (r -> a) -> ExceptT e m a Source #

MonadState s m => MonadState s (ExceptT e m) Source # 

Associated Types

type StateSuitable (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

get :: ExceptT e m s Source #

put :: s -> ExceptT e m () Source #

state :: (StateSuitable (ExceptT e m) a, StateSuitable (ExceptT e m) s) => (s -> (a, s)) -> ExceptT e m a Source #

MonadWriter w m => MonadWriter w (ExceptT e m) Source # 

Associated Types

type WriterSuitable (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

writer :: WriterSuitable (ExceptT e m) a => (a, w) -> ExceptT e m a Source #

tell :: w -> ExceptT e m () Source #

listenC :: WriterSuitable (ExceptT e m) b => (a -> w -> b) -> ExceptT e m a -> ExceptT e m b Source #

passC :: WriterSuitable (ExceptT e m) a => (a -> w -> w) -> ExceptT e m a -> ExceptT e m a Source #

MonadTrans (ExceptT e) 

Methods

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

MonadTrans (ExceptT e) Source # 

Associated Types

type SuitableLift (ExceptT e :: (* -> *) -> * -> *) (m :: * -> *) a :: Constraint Source #

Methods

lift :: (Monad m, SuitableLift (ExceptT e) m a) => m a -> ExceptT e m a Source #

Monad m => Monad (ExceptT e m) 

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 #

fail :: String -> ExceptT e m a #

Functor m => Functor (ExceptT e m) 

Methods

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

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

MonadFix m => MonadFix (ExceptT e m) 

Methods

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

MonadFail m => MonadFail (ExceptT e m) 

Methods

fail :: String -> ExceptT e m a #

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

Methods

pure :: a -> ExceptT e m a #

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

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

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

Foldable f => Foldable (ExceptT e f) 

Methods

fold :: Monoid m => ExceptT e f m -> 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 #

Traversable f => Traversable (ExceptT e f) 

Methods

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

sequenceA :: Applicative f => ExceptT e f (f a) -> f (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) #

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

Methods

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

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

Methods

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

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

Methods

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

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

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

Methods

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

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

MonadZip m => MonadZip (ExceptT e m) 

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

MonadIO m => MonadIO (ExceptT e m) 

Methods

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

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

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] #

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

Methods

mzero :: ExceptT e m a #

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

(Monad m, Monoid e) => Alternative (ExceptT e m) Source # 

Methods

empty :: Suitable (ExceptT e m) a => ExceptT e m a Source #

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

some :: Suitable (ExceptT e m) [a] => ExceptT e m a -> ExceptT e m [a] Source #

many :: Suitable (ExceptT e m) [a] => ExceptT e m a -> ExceptT e m [a] Source #

Monad m => Monad (ExceptT e m) Source # 

Methods

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

Monad m => Applicative (ExceptT e m) Source # 

Methods

pure :: Suitable (ExceptT e m) a => a -> ExceptT e m a Source #

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

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

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

liftA :: Suitable (ExceptT e m) b => (Vect xs -> b) -> AppVect (ExceptT e m) xs -> ExceptT e m b Source #

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

liftA3 :: Suitable (ExceptT e m) d => (a -> b -> c -> d) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d Source #

liftA4 :: Suitable (ExceptT e m) e => (a -> b -> c -> d -> e) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d -> ExceptT e m e Source #

liftA5 :: Suitable (ExceptT e m) g => (a -> b -> c -> d -> e -> g) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d -> ExceptT e m e -> ExceptT e m g Source #

liftA6 :: Suitable (ExceptT e m) h => (a -> b -> c -> d -> e -> g -> h) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d -> ExceptT e m e -> ExceptT e m g -> ExceptT e m h Source #

liftA7 :: Suitable (ExceptT e m) i => (a -> b -> c -> d -> e -> g -> h -> i) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d -> ExceptT e m e -> ExceptT e m g -> ExceptT e m h -> ExceptT e m i Source #

liftA8 :: Suitable (ExceptT e m) j => (a -> b -> c -> d -> e -> g -> h -> i -> j) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d -> ExceptT e m e -> ExceptT e m g -> ExceptT e m h -> ExceptT e m i -> ExceptT e m j Source #

liftA9 :: Suitable (ExceptT e m) k => (a -> b -> c -> d -> e -> g -> h -> i -> j -> k) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c -> ExceptT e m d -> ExceptT e m e -> ExceptT e m g -> ExceptT e m h -> ExceptT e m i -> ExceptT e m j -> ExceptT e m k Source #

Functor m => Functor (ExceptT e m) Source # 

Associated Types

type Suitable (ExceptT e m :: * -> *) a :: Constraint Source #

Methods

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

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

MonadCont m => MonadCont (ExceptT e m) Source # 

Methods

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

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

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) 

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 #

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

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) 

Methods

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

show :: ExceptT e m a -> String #

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

type SuitableLift (ExceptT e) m a Source # 
type SuitableLift (ExceptT e) m a = Suitable m (Either e a)
type Suitable (ExceptT e m) a Source # 
type Suitable (ExceptT e m) a = Suitable m (Either e a)
type SuitableError (ExceptT e m) a Source # 
type SuitableError (ExceptT e m) a = Suitable m (Either e a)
type ReaderSuitable (ExceptT e m) a Source # 
type StateSuitable (ExceptT e m) a Source # 
type StateSuitable (ExceptT e m) a = (Suitable m (Either e a), StateSuitable m a)
type WriterSuitable (ExceptT e m) a Source # 

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.