mtl-tf-0.2.1.0: Monad Transformer Library with Type Families

Copyright(c) Andy Gill 2001
(c) Oregon Graduate Institute of Science and Technology 2001
(c) Jeff Newbern 2003-2007
(c) Andriy Palamarchuk 2007
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilitynon-portable (multi-param classes, functional dependencies)
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Reader

Contents

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://www.cse.ogi.edu/~mpj/) Advanced School of Functional Programming, 1995.

Synopsis

Documentation

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.

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).

newtype ReaderT k r (m :: k -> *) (a :: k) :: forall k. * -> (k -> *) -> k -> * #

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 

Fields

Instances

MonadTrans (ReaderT * r) 

Methods

lift :: Monad m => m a -> ReaderT * r m a #

Monad m => Monad (ReaderT * r m) 

Methods

(>>=) :: ReaderT * r m a -> (a -> ReaderT * r m b) -> ReaderT * r m b #

(>>) :: ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m b #

return :: a -> ReaderT * r m a #

fail :: String -> ReaderT * r m a #

Functor m => Functor (ReaderT * r m) 

Methods

fmap :: (a -> b) -> ReaderT * r m a -> ReaderT * r m b #

(<$) :: a -> ReaderT * r m b -> ReaderT * r m a #

MonadFix m => MonadFix (ReaderT * r m) 

Methods

mfix :: (a -> ReaderT * r m a) -> ReaderT * r m a #

MonadFail m => MonadFail (ReaderT * r m) 

Methods

fail :: String -> ReaderT * r m a #

Applicative m => Applicative (ReaderT * r m) 

Methods

pure :: a -> ReaderT * r m a #

(<*>) :: ReaderT * r m (a -> b) -> ReaderT * r m a -> ReaderT * r m b #

liftA2 :: (a -> b -> c) -> ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m c #

(*>) :: ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m b #

(<*) :: ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m a #

MonadZip m => MonadZip (ReaderT * r m) 

Methods

mzip :: ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m (a, b) #

mzipWith :: (a -> b -> c) -> ReaderT * r m a -> ReaderT * r m b -> ReaderT * r m c #

munzip :: ReaderT * r m (a, b) -> (ReaderT * r m a, ReaderT * r m b) #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

Alternative m => Alternative (ReaderT * r m) 

Methods

empty :: ReaderT * r m a #

(<|>) :: ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a #

some :: ReaderT * r m a -> ReaderT * r m [a] #

many :: ReaderT * r m a -> ReaderT * r m [a] #

MonadPlus m => MonadPlus (ReaderT * r m) 

Methods

mzero :: ReaderT * r m a #

mplus :: ReaderT * r m a -> ReaderT * r m a -> ReaderT * r m a #

MonadState m => MonadState (ReaderT * r m) Source # 

Associated Types

type StateType (ReaderT * r m :: * -> *) :: * Source #

Methods

get :: ReaderT * r m (StateType (ReaderT * r m)) Source #

put :: StateType (ReaderT * r m) -> ReaderT * r m () Source #

Monad m => MonadReader (ReaderT * r m) Source # 

Associated Types

type EnvType (ReaderT * r m :: * -> *) :: * Source #

Methods

ask :: ReaderT * r m (EnvType (ReaderT * r m)) Source #

local :: (EnvType (ReaderT * r m) -> EnvType (ReaderT * r m)) -> ReaderT * r m a -> ReaderT * r m a Source #

MonadError m => MonadError (ReaderT * r m) Source # 

Associated Types

type ErrorType (ReaderT * r m :: * -> *) :: * Source #

Methods

throwError :: ErrorType (ReaderT * r m) -> ReaderT * r m a Source #

catchError :: ReaderT * r m a -> (ErrorType (ReaderT * r m) -> ReaderT * r m a) -> ReaderT * r m a Source #

MonadCont m => MonadCont (ReaderT * r m) Source # 

Methods

callCC :: ((a -> ReaderT * r m b) -> ReaderT * r m a) -> ReaderT * r m a Source #

MonadWriter m => MonadWriter (ReaderT * r m) Source # 

Associated Types

type WritType (ReaderT * r m :: * -> *) :: * Source #

Methods

tell :: WritType (ReaderT * r m) -> ReaderT * r m () Source #

listen :: ReaderT * r m a -> ReaderT * r m (a, WritType (ReaderT * r m)) Source #

pass :: ReaderT * r m (a, WritType (ReaderT * r m) -> WritType (ReaderT * r m)) -> ReaderT * r m a Source #

type StateType (ReaderT * r m) Source # 
type StateType (ReaderT * r m) = StateType m
type EnvType (ReaderT * r m) Source # 
type EnvType (ReaderT * r m) = r
type ErrorType (ReaderT * r m) Source # 
type ErrorType (ReaderT * r m) = ErrorType m
type WritType (ReaderT * r m) Source # 
type WritType (ReaderT * r m) = WritType m

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

Transform the computation inside a ReaderT.

withReaderT #

Arguments

:: (r' -> r)

The function to modify the environment.

-> ReaderT k r m a

Computation to run in the modified environment.

-> ReaderT k r' m a 

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

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"