Understanding the Reader Monad

The purpose of the Reader monad is to allow an "environment" (any value) to be passed to a set of functions (that all require access to the environment) without explicitly passing around the environment as an argument.

Each function that need the environment must return the Reader monad i.e. a function that takes the environment as argument and return a result from the function dependent on the environment. So you can have different functions depending on the same environment, but with different result values.

An example using Reader monad is shown below. The ReaderExample app makes a simple mathematical operation from the arguments passed to the application.

Example usage of the tool is shown below.

./ReaderExample div 4 2
"Result = 2"
./ReaderExample add 1 2 3 4 5
"Result = 15"

The source is shown below.

import Control.Monad.Reader 
import System.Environment   
import Data.List (elem)

{- An example to help understand how Reader monad can be used.
   It perform a simple calculation from command line arguments.
   Reader allow an environment to be implicitely passed to a number of functions
   Compile: ghc -O2 ReaderExample.hs -ignore-package monads-tf
   Run: ./ReaderExample -}

-- Determine if implicit (eventual) environment has the correct number of parameters
valid :: Reader [String] Bool
valid = do 
          (cmd, args) <- parseCmd       -- the implicit environment is passed along
          let len = length args
          return $ (len >  1 && cmd == "add") 
                || (len == 2 && elem cmd ["sub","div","mul"])

-- Parse command from implicit (eventual) environment (executed within a reader monad)
parseCmd :: Reader [String] (String, [Int])
parseCmd = do
             params <- ask              -- `ask` access the implicit environemtn
             return (head params, map read $ drop 1 params)

-- Perform calculation from (eventual) environment
doCalc :: Reader [String] Int
doCalc = do 
           (cmd, args) <- parseCmd      -- the implicit environment is passed along
           let (a:b:_) = args
           return $ case cmd of "add" -> sum args
                                "sub" -> a   -   b
                                "div" -> a `div` b
                                "mul" -> a   *   b

main = do
   args <- getArgs                      -- getArgs :: IO [String]
   let len = length args
   let isValid = runReader valid args   -- run a reader with explicit environment
   print $ if (len > 0) && isValid then "Result = " ++ show (runReader doCalc args)
                                   else "Invalid format"

In the example the "environment" that several function depend on is the command line arguments retrieved by getArgs command. runReader retrieves the Reader function (Reader is defined as e -> a i.e. environment to result) and applies that to the environment args.

Definition

In an old paper from the 90's Reader monad is defined as follows.

A Reader monad is used to allow a computation to access the values held
in some enclosing environment (represented by the type r in the following definitions).

instance Monad (r->) where
  result x = \r -> x
  x `bind` f = \r -> f (x r) r

It seems quite straight forward. Reader monad represent a function that takes a value (the environment) and produce another value (the result) of type a.

So, how do you bind two of these operations together. You have a first reader x and a function f that produce a second reader. The combined reader must be a function where r id fed into both readers to create the result .

(x r) is input r fed into first reader. The result is fed into the monadic function f which produce the second reader. The input r is fed into this second reader to produce the result of the combined reader function.

In a more modern definition the bind function is defined as follows, which is the same thing.

m >>= k  = Reader $ \r -> runReader (k (runReader m r)) r

Readers once more ...

Reader are obviously too hard for me to grasp. Some time later, I have once more come back to Readers and still don't fully understand them. Some further investigations ...

Explanation of reader monad definition.

instance Monad ((->) r) where  
    return x = \_ -> x  
    h >>= f = \e -> f (h e) e

(>>=)  :: (e -> a) -> (a -> (e -> b)) -> (e -> b)
return :: a -> (r -> a)

(h e)           :: a         apply environment (e) to h to get an intermediate result (a)
f (h e)         :: (e -> b)  apply intermediate result to monadic function to get second reader
                             (note: returned reader may depend on intermediate result) 
f (h e) e       :: b         apply environment (e) to second reader
\e -> f (h e) e :: e -> b    resulting type match

So my interpretation is that the monadic feature that intermediate results are passed on from monadic function to monadic function is valid. Additionally a constant environment variable is passed in to every reader.

So how could this be used? The following example is shown from LYAH.

addStuff :: Int -> Int  
addStuff = do  
    a <- (*2)  
    b <- (+10)  
    return (a+b)

addStuff 3  
19

( (*2) >>= \a -> (+10) >>= \b -> return (a+b) ) 3
19
  1. Here we have a reader applies *2 on any environment (in this example 3).
  2. We have a monadic function that return +10 reader. The returned reader is not dependent on any intermediate result, but could have been.
  3. We have a second monadic function that return a reader that return the previous two intermediate results independent on the environment. Note that return creates are reader that ignores the input and always output the supplied argument.
  4. The first reader is bound to first monadic function and second monadic function to create a composed reader.
  5. The composed reader take the environment (3) supply that to first reader (*2) and second generated reader ((+10)) and return the sum of those two intermediate results i.e. (3*2)+(3+10) = 19

Build a train

Another example would be to create a train manufacturing pipeline.

The idea is that we have workers that add diffrent kinds of wagons to a train. After each wagon is built, the wagon is colored by a color defined by the environment.

addWagon which is the builder "action" generator can be customized to build different kinds of wagons by specifying the first parameter. The second parameter is the train that comes on the previous pipeline step. It returns a builder action that takes the current train, add the specified wagon and paints it according to the environment color.

data Color = Black | Red | Green deriving Show
data Wagon = Locomotive | Passenger | Restaurant deriving Show
type Train :: [(Wagon,Color)]

addWagon :: Wagon -> Train -> (Color -> Train)
addWagon w t c = (w,c) : t

In the example below a pipeline is setup to build a complete train with three wagons.

( return [] >>= \a -> addWagon Locomotive a >>= \b -> addWagon Passenger b >>= \c -> addWagon Restaurant c) Red
[(Restaurant,Red),(Passenger,Red),(Locomotive,Red)]

The same builder pipeline can be used independent on the environment color used.

( return [] >>= \a -> addWagon Locomotive a >>= \b -> addWagon Passenger b >>= \c -> addWagon Restaurant c) Black
[(Restaurant,Black),(Passenger,Black),(Locomotive,Black)]

Sugered variant (not verfired!).

createTrain = do
    let a = return []
    b <- addWagon Locomotive a
    c <- addWagon Passenger b
    addWagon Locomotive c

References