monads-tf-0.0.0.1: Monad classes, using type familiesSource codeContentsIndex
Control.Monad.Reader
Portabilitynon-portable (type families)
Stabilityexperimental
Maintainerlibraries@haskell.org
Contents
MonadReader class
The Reader monad
The ReaderT monad transformer
Example 1: Simple Reader Usage
Example 2: Modifying Reader Content With local
Example 3: ReaderT Monad Transformer
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 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.

Synopsis
class Monad m => MonadReader m where
type EnvType m
ask :: m (EnvType m)
local :: (EnvType m -> EnvType m) -> m a -> m a
asks :: MonadReader m => (EnvType m -> a) -> m a
type Reader r = ReaderT r Identity
runReader :: Reader r a -> 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 r m a -> ReaderT r n b
withReaderT :: (r' -> r) -> ReaderT r m a -> ReaderT r' m a
module Control.Monad
module Control.Monad.Fix
module Control.Monad.Trans
MonadReader class
class Monad m => MonadReader m whereSource
See examples in Control.Monad.Reader. Note, the partially applied function type (->) r is a simple reader monad. See the instance declaration below.
Associated Types
type EnvType m Source
Methods
ask :: m (EnvType m)Source
Retrieves the monad environment.
localSource
::
=> EnvType m -> EnvType mReader to run in the modified environment.
-> m a
-> m a
Executes a computation in a modified environment.
show/hide Instances
asksSource
:: MonadReader m
=> EnvType m -> a
-> m a
Retrieves a function of the current environment.
The Reader monad
type Reader r = ReaderT r IdentitySource

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.

runReaderSource
::
=> Reader r aAn initial environment.
-> r
-> a
Runs a Reader and extracts the final value from it.
mapReader :: (a -> b) -> Reader r a -> Reader r bSource
Transform the value returned by a Reader.
withReaderSource
::
=> r' -> rComputation to run in the modified environment.
-> Reader r a
-> Reader r' a
Execute a computation in a modified environment (a specialization of withReaderT).
The ReaderT monad transformer
newtype ReaderT 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.

Constructors
ReaderT
runReaderT :: r -> m aThe underlying computation, as a function of the environment.
show/hide Instances
mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n bSource
Transform the computation inside a ReaderT.
withReaderTSource
::
=> r' -> rComputation to run in the modified environment.
-> ReaderT r m a
-> 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"
Produced by Haddock version 2.6.0