ether-0.3.1.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Ether.Reader

Contents

Description

Synopsis

MonadReader class

class Monad m => MonadReader tag r m | m tag -> r where Source

Minimal complete definition

(ask | reader), local

Methods

ask :: proxy tag -> m r Source

Retrieves the monad environment.

local Source

Arguments

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

The function to modify the environment.

-> m a

Reader to run in the modified environment.

-> m a 

Executes a computation in a modified environment.

reader Source

Arguments

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

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

Instances

(LiftLocal t, Monad (t m), MonadReader tag r m) => MonadReader tag r (t m) Source 
MonadReader tag r m => MonadReader tag r (WrappedEther tag' m) Source 
Monad m => MonadReader tag r (ReaderT tag r m) Source 

asks Source

Arguments

:: MonadReader tag r m 
=> proxy tag 
-> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

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.

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

Monad m => MonadReader tag r (ReaderT tag r m) Source 
MonadBase b m => MonadBase b (ReaderT tag r m) Source 
MonadBaseControl b m => MonadBaseControl b (ReaderT tag r m) Source 
MonadError e m => MonadError e (ReaderT tag r m) Source 
MonadReader r' m => MonadReader r' (ReaderT tag r m) Source 
MonadState s m => MonadState s (ReaderT tag r m) Source 
MonadWriter w m => MonadWriter w (ReaderT tag r m) Source 
MFunctor (ReaderT tag r) Source 
MMonad (ReaderT tag r) Source 
MonadTrans (ReaderT tag r) Source 
MonadTransControl (ReaderT tag r) Source 
LiftLocal (ReaderT tag r) Source 
LiftCallCC (ReaderT tag r) Source 
LiftPass (ReaderT tag r) Source 
LiftListen (ReaderT tag r) Source 
LiftCatch (ReaderT tag r) Source 
Monad m => Monad (ReaderT tag r m) Source 
Functor m => Functor (ReaderT tag r m) Source 
MonadFix m => MonadFix (ReaderT tag r m) Source 
Applicative m => Applicative (ReaderT tag r m) Source 
Alternative m => Alternative (ReaderT tag r m) Source 
MonadPlus m => MonadPlus (ReaderT tag r m) Source 
MonadIO m => MonadIO (ReaderT tag r m) Source 
MonadCont m => MonadCont (ReaderT tag r m) Source 
Taggable (ReaderT tag r m) Source 
Tagged (ReaderT tag r m) tag Source 
Generic (ReaderT tag r m a) Source 
Newtype (ReaderT tag r m a) Source 
type StT (ReaderT tag r) a = StT (ReaderT r) a Source 
type StT (ReaderT tag r) a = StT (ReaderT tag r) a Source 
type Untagged (ReaderT tag r m) = ReaderT r m Source 
type Tag (ReaderT tag r m) = Just * tag Source 
type Inner (ReaderT tag r m) = Just (* -> *) m Source 
type StM (ReaderT tag r m) a = ComposeSt (ReaderT tag r) m a Source 
type Rep (ReaderT tag r m a) Source 
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.