mtl-2.1.2: Monad classes, using functional dependencies

Portabilitynon-portable (multi-param classes, functional dependencies)
Stabilityexperimental
Maintainerlibraries@haskell.org
Safe HaskellSafe-Infered

Control.Monad.Reader

Description

Computation type:
Computations which read values from a shared environment.
Binding strategy:
Monad values are functions from the environment to a value. The bound function is applied to the bound value, and both have access to the shared environment.
Useful for:
Maintaining variable bindings, or other shared environment.
Zero and plus:
None.
Example type:
Reader [(String,Value)] a

The Reader monad (also called the Environment monad). Represents a computation, which can read values from a shared environment, pass values from function to function, and execute sub-computations in a modified environment. Using Reader monad for such computations is often clearer and easier than using the State monad.

Inspired by the paper Functional Programming with Overloading and Higher-Order Polymorphism, Mark P Jones (http://web.cecs.pdx.edu/~mpj/) Advanced School of Functional Programming, 1995.

Synopsis

MonadReader class

class Monad m => MonadReader r m | m -> r whereSource

See examples in Control.Monad.Reader. Note, the partially applied function type (->) r is a simple reader monad. See the instance declaration below.

Methods

ask :: m rSource

Retrieves the monad environment.

local Source

Arguments

:: (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

:: (r -> a)

The selector function to apply to the environment.

-> m a

Retrieves a function of the current environment.

Instances

MonadReader r ((->) r)
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m)
(Monoid w, MonadReader r m) => MonadReader r (WriterT w m)
MonadReader r m => MonadReader r (StateT s m)
MonadReader r m => MonadReader r (StateT s m)
(Error e, MonadReader r m) => MonadReader r (ErrorT e m)
MonadReader r' m => MonadReader r' (ContT r m)
Monad m => MonadReader r (ReaderT r m)
(Monad m, Monoid w) => MonadReader r (RWST r w s m)
(Monad m, Monoid w) => MonadReader r (RWST r w s m)

asks Source

Arguments

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

The selector function to apply to the environment.

-> m a

Retrieves a function of the current environment.

The Reader monad

type Reader r = ReaderT r Identity

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

Arguments

:: Reader r a

A Reader to run.

-> r

An initial environment.

-> a

Runs a Reader and extracts the final value from it. (The inverse of reader .)

mapReader :: (a -> b) -> Reader r a -> Reader r b

Transform the value returned by a Reader.

withReader

Arguments

:: (r' -> r)

The function to modify the environment.

-> Reader r a

Computation to run in the modified environment.

-> Reader r' a

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

The ReaderT monad transformer

newtype ReaderT r m a

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.

Constructors

Fields

runReaderT :: r -> m a

The underlying computation, as a function of the environment.

Instances

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

Transform the computation inside a ReaderT.

withReaderT

Arguments

:: (r' -> r)

The function to modify the environment.

-> ReaderT r m a

Computation to run in the modified environment.

-> ReaderT r' m a

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

module Control.Monad

module Control.Monad.Fix

module Control.Monad.Trans

Example 1: Simple Reader Usage

In this example the Reader monad provides access to variable bindings. Bindings are a Map of integer variables. The variable count contains number of variables in the bindings. You can see how to run a Reader monad and retrieve data from it with runReader , how to access the Reader data with ask and asks .

 type Bindings = Map String Int;
-- Returns True if the "count" variable contains correct bindings size.
isCountCorrect :: Bindings -> Bool
isCountCorrect bindings = runReader calc_isCountCorrect bindings
-- The Reader monad, which implements this complicated check.
calc_isCountCorrect :: Reader Bindings Bool
calc_isCountCorrect = do
 count <- asks (lookupVar "count")
 bindings <- ask
 return (count == (Map.size bindings))
-- The selector function to use with 'asks'.
-- Returns value of the variable with specified name.
lookupVar :: String -> Bindings -> Int
lookupVar name bindings = fromJust (Map.lookup name bindings)
sampleBindings = Map.fromList [("count",3), ("1",1), ("b",2)]
main = do
 putStr $ "Count is correct for bindings " ++ (show sampleBindings) ++ ": ";
 putStrLn $ show (isCountCorrect sampleBindings);

Example 2: Modifying Reader Content With local

Shows how to modify Reader content with local .

calculateContentLen :: Reader String Int
calculateContentLen = do
 content <- ask
 return (length content);
-- Calls calculateContentLen after adding a prefix to the Reader content.
calculateModifiedContentLen :: Reader String Int
calculateModifiedContentLen = local ("Prefix " ++) calculateContentLen
main = do
 let s = "12345";
 let modifiedLen = runReader calculateModifiedContentLen s
 let len = runReader calculateContentLen s
 putStrLn $ "Modified 's' length: " ++ (show modifiedLen)
 putStrLn $ "Original 's' length: " ++ (show len)

Example 3: ReaderT Monad Transformer

Now you are thinking: 'Wow, what a great monad! I wish I could use Reader functionality in MyFavoriteComplexMonad!'. Don't worry. This can be easy done with the ReaderT monad transformer. This example shows how to combine ReaderT with the IO monad.

-- The Reader/IO combined monad, where Reader stores a string.
printReaderContent :: ReaderT String IO ()
printReaderContent = do
 content <- ask
 liftIO $ putStrLn ("The Reader Content: " ++ content)
main = do
 runReaderT printReaderContent "Some Content"

AltStyle によって変換されたページ (->オリジナル) /