ether-0.2.1.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trans.Ether.Reader

Contents

Description

Synopsis

The Reader monad

type Reader tag r = ReaderT tag r Identity Source

The parameterizable reader monad.

Computations are functions of a shared environment.

The return function ignores the environment, while >>= passes the inherited environment to both subcomputations.

reader :: Monad m => proxy tag -> (r -> a) -> ReaderT tag r m a Source

Constructor for computations in the reader monad (the inverse of runReader).

runReader :: proxy tag -> Reader tag r a -> r -> a Source

Runs a ReaderT with the given environment and returns the vinal value.

The ReaderT monad transformer

data ReaderT tag r m a Source

The reader monad transformer, which adds a read-only environment to the given monad.

The return function ignores the environment, while >>= passes the inherited environment to both subcomputations.

Instances

MonadReader tag r m => MonadReader tag r (ReaderT tag' r' m) 
Monad m => MonadReader tag r (ReaderT tag r m) 
MonadState tag s m => MonadState tag s (ReaderT tag' r m) 
MonadExcept tag e m => MonadExcept tag e (ReaderT tag' r m) 
MonadWriter tag w m => MonadWriter tag w (ReaderT tag' r m) 
MonadError e m => MonadError e (ReaderT tag r m) 
MonadReader r' m => MonadReader r' (ReaderT tag r m) 
MonadState s m => MonadState s (ReaderT tag r m) 
MonadWriter w m => MonadWriter w (ReaderT tag r m) 
MonadTrans (ReaderT tag r) 
Alternative m => Alternative (ReaderT tag r m) 
Monad m => Monad (ReaderT tag r m) 
Functor m => Functor (ReaderT tag r m) 
MonadFix m => MonadFix (ReaderT tag r m) 
MonadPlus m => MonadPlus (ReaderT tag r m) 
Applicative m => Applicative (ReaderT tag r m) 
MonadIO m => MonadIO (ReaderT tag r m) 
MonadCont m => MonadCont (ReaderT tag r m) 
Taggable (ReaderT tag r m) 
Tagged (ReaderT tag r m) tag 
Generic (ReaderT tag r m a) 
Newtype (ReaderT tag r m a) 
type Untagged (ReaderT tag r m) = ReaderT r m 
type Tag (ReaderT tag r m) = Just * tag 
type Inner (ReaderT tag r m) = Just (* -> *) m 
type Rep (ReaderT tag r m a) 
type O (ReaderT tag r m a) = GO (Rep (ReaderT tag r m a)) 

readerT :: proxy tag -> (r -> m a) -> ReaderT tag r m a Source

Constructor for computations in the reader monad transformer.

runReaderT :: proxy tag -> ReaderT tag r m a -> r -> m a Source

Runs a ReaderT with the given environment and returns the vinal value.

mapReaderT :: proxy tag -> (m a -> n b) -> ReaderT tag r m a -> ReaderT tag r n b Source

Transform the computation inside a ReaderT.

withReaderT Source

Arguments

:: proxy tag 
-> (r' -> r)

The function to modify the environment.

-> ReaderT tag r m a

Computation to run in the modified environment.

-> ReaderT tag r' m a 

Execute a computation in a modified environment (a more general version of local).

Reader operations

ask :: Monad m => proxy tag -> ReaderT tag r m r Source

Fetch the value of the environment.

local Source

Arguments

:: proxy tag 
-> (r -> r)

The function to modify the environment.

-> ReaderT tag r m a

Computation to run in the modified environment.

-> ReaderT tag r m a 

Execute a computation in a modified environment (a specialization of withReaderT).

Lifting other operations

liftCatch :: proxy tag -> Catch e m a -> Catch e (ReaderT tag r m) a Source

Lift a catchE operation to the new monad.

liftCallCC :: proxy tag -> CallCC m a b -> CallCC (ReaderT tag r m) a b Source

Lift a callCC operation to the new monad.