Portability | non-portable (multi-param classes, functional dependencies) |
---|---|
Stability | experimental |
Maintainer | libraries@haskell.org |
- 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 Control.Monad.State.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.
- module Control.Monad.Reader.Class
- newtype Reader r a = Reader {
- runReader :: r -> a
- mapReader :: (a -> b) -> Reader r a -> Reader r b
- withReader :: (r' -> r) -> Reader r a -> Reader r' a
- newtype ReaderT r m a = ReaderT {
- runReaderT :: r -> m a
- mapReaderT :: (m a -> n b) -> ReaderT w m a -> ReaderT w n b
- withReaderT :: (r' -> r) -> ReaderT r m a -> ReaderT r' m a
- module Control.Monad
- module Control.Monad.Fix
- module Control.Monad.Trans
Documentation
module Control.Monad.Reader.Class
The parameterizable reader monad.
The return
function creates a Reader
that ignores the environment,
and produces the given value.
The binding operator >>=
produces a Reader
that uses the environment
to extract the value its left-hand side,
and then applies the bound function to that value in the same environment.
withReader :: (r' -> r) -> Reader r a -> Reader r' aSource
A more general version of local
.
The reader monad transformer. Can be used to add environment reading functionality to other monads.
ReaderT | |
|
MonadWriter w m => MonadWriter w (ReaderT r m) | |
MonadError e m => MonadError e (ReaderT r m) | |
MonadState s m => MonadState s (ReaderT r m) | |
Monad m => MonadReader r (ReaderT r m) | |
MonadTrans (ReaderT r) | |
Monad m => Monad (ReaderT r m) | |
Monad m => Functor (ReaderT r m) | |
MonadFix m => MonadFix (ReaderT r m) | |
MonadPlus m => MonadPlus (ReaderT r m) | |
MonadIO m => MonadIO (ReaderT r m) | |
MonadCont m => MonadCont (ReaderT r m) |
mapReaderT :: (m a -> n b) -> ReaderT w m a -> ReaderT w n bSource
withReaderT :: (r' -> r) -> ReaderT r m a -> ReaderT r' m aSource
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"