Skip to content

Instantly share code, notes, and snippets.

@rajadain
Last active December 20, 2017 22:31
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save rajadain/c05a5673f8049519194ff7c80177dad3 to your computer and use it in GitHub Desktop.
Save rajadain/c05a5673f8049519194ff7c80177dad3 to your computer and use it in GitHub Desktop.
Notes and exercises for Haskell Book Chapter 22: Reader
module ExerciseChapter22 where
import Control.Applicative
import Data.Maybe
x = [1, 2, 3]
y = [4, 5, 6]
z = [7, 8, 9]
xs :: Maybe Integer
xs = lookup 3 $ zip x y
ys :: Maybe Integer
ys = lookup 6 $ zip y z
zs :: Maybe Integer
zs = lookup 4 $ zip x y
z' :: Integer -> Maybe Integer
z' n = lookup n $ zip x z
x1 :: Maybe (Integer, Integer)
x1 = Just (fromJust xs, fromJust ys)
-- x1 = traverse (,) ys (fromJust zs)
x2 :: Maybe (Integer, Integer)
x2 = do
y <- ys
z <- zs
return (y, z)
x3 :: Integer -> (Maybe Integer, Maybe Integer)
x3 = (,) <$> z' <*> z'
summed :: Num c => (c, c) -> c
summed = uncurry (+)
bolt :: Integer -> Bool
bolt = (&&) <$> (>3) <*> (<8)
sequA :: Integral a => a -> [Bool]
sequA m = sequenceA [(>3), (<8), even] m
s' :: Maybe Integer
s' = summed <$> ((,) <$> xs <*> ys)
main :: IO()
main = do
print $ sequenceA [Just 3, Just 2, Just 1]
print $ sequenceA [x, y]
print $ sequenceA [xs, ys]
print $ summed <$> ((,) <$> xs <*> ys)
print $ fmap summed ((,) <$> xs <*> zs)
print $ bolt 7
print $ fmap bolt z
print $ sequenceA [(>3), (<8), even] 7
print $ foldr (&&) True (sequA 7)
print $ sequA (fromMaybe 0 s')
print $ bolt (fromMaybe 0 ys)

Chapter 22: Reader

22.1 Reader

The next three chapters are going to focus on patterns that might still seem strange and difficult. We do have reasons for introducing them now, but those reasons might not seem clear to you for a while.

Good luck.

When writing applications, programmers often need to pass around some information that may be needed intermittently or universally throughout an entire application.

Like a global configuration object that has connection strings and spark contexts and such?

22.2 A new beginning

import Control.Applicative

boop = (*2)
doop = (+10)

-- Function Composition, sequential
bip :: Integer -> Integer
bip = boop . doop

-- Functorial Context, sequential
bloop :: Integer -> Integer
bloop = fmap boop doop

-- Applicative Context, parallel
bbop :: Integer -> Integer
bbop = (+) <$> boop <*> doop

-- Applicative Context, parallel
duwop :: Integer -> Integer
duwop = liftA2 (+) boop doop

-- Monadic Context, parallel
boopDoop :: Integer -> Integer
boopDoop = do
    a <- boop
    b <- doop
    return (a + b)

We can fmap over functions apparently.

Partially applied functions can be functorial contexts.

fmap boop doop x == (*2) ((+10) x)

Partially applied functions can have Functor, Applicative, and Monad.

The Functor for functions is function composition.

The Applicative and Monad chain the argument forward in addition to composition.

(<*>) :: Applicative f => f (a -> b) -> f a -> f b

For partially applied functions, f is (->) r, or r ->. Thus, the apply for functions becomes:

(<*>) :: (((->) r) (a -> b)) -> (((->) r) a) -> (((->) r) b)
-- or, more simply:
(<*>) :: (r -> a -> b) -> (r -> a) -> (r -> b)

This is the idea of Reader. It is a way of stringing functions together when all those functions are awaiting one input from a shared environment. ... Using Reader allows us to avoid passing that argument explicitly.

Exercise: Warming Up

import Control.Applicative
import Data.Char

cap :: [Char] -> [Char]
cap xs = map toUpper xs

rev :: [Char] -> [Char]
rev xs = reverse xs

composed :: [Char] -> [Char]
composed = cap . rev

fmapped :: [Char] -> [Char]
fmapped = fmap cap rev

tupled :: [Char] -> ([Char], [Char])
tupled = (,) <$> cap <*> rev

tupled' :: [Char] -> ([Char], [Char])
tupled' = liftA2 (,) cap rev

tupled'' :: [Char] -> ([Char], [Char])
tupled'' = do
    a <- cap
    b <- rev
    return (a, b)

tupled''' :: [Char] -> ([Char], [Char])
tupled''' = liftM2 (,) cap rev

tupled'''' :: [Char] -> ([Char], [Char])
tupled'''' =
    cap >>= \a ->
        rev >>= \b ->
            return (a, b)

22.3 This is Reader

Reader is a way of stringing together functions that are all waiting for one input from a shared environment. It allows us to setup chains of computation that rely on some constant value provided at runtime.

Reader usually refers to the Monad instance of Functions, not Functor or Applicative.

Giving it a name helps us know the what and why of what we’re doing: reading an argument from the environment into functions. It’ll be especially nice for clarity’s sake later when we make the ReaderT monad transformer.

22.4 Breaking down the Functor of Functions

   fmap (+1) (*2) 3
== fmap (+1) (*2) $ 3
== (fmap (+1) (*2)) 3
== ((+1) . (*2)) 3
== 7
(.) :: (b -> c) -> (a -> b) -> a -> c
-- or perhaps
(.) :: (b -> c) -> (a -> b) -> (a -> c)
-- compare to Functor
fmap :: Functor f => (a -> b) -> f a -> f b
-- or perhaps
fmap :: Functor f => (b -> c) -> f b -> f c
-- lining up with each other
fmap :: Functor f => (b -> c) ->     f b ->      f c
(.)  ::              (b -> c) -> (a -> b) -> (a -> c)
-- and replacing `f` with `a ->` for functions
fmap :: Functor (-> a) => (b -> c) -> (a -> b) -> (a -> c)
(.)  ::                   (b -> c) -> (a -> b) -> (a -> c)
instance Functor ((->) r) where
    fmap = (.)

22.5 But uh, Reader?

newtype Reader r a =
    Reader { runReader :: r -> a }
instance Functor (Reader r) where
    fmap f (Reader ra) = Reader $ (f . ra)

Exercise: Ask

ask :: Reader a a
ask = Reader $ id

22.6 Functions have an Applicative too

pure :: a ->     f a
pure :: a -> (r -> a)

(<*>) ::    f (a -> b) ->     f a  ->     f b
(<*>) :: (r -> a -> b) -> (r -> a) -> (r -> b)

Demonstrating the function Applicative

newtype HumanName = HumanName String deriving (Eq, Show)
newtype DogName = DogName String deriving (Eq, Show)
newtype Address = Address String deriving (Eq, Show)

data Person =
    Person {
        humanName :: HumanName,
        dogName :: DogName,
        address :: Address
    } deriving (Eq, Show)

data Dog =
    Dog {
        dogsName :: DogName,
        dogsAddress :: Address
    } deriving (Eq, Show)

mickey :: Person
mickey = Person (HumanName "Mickey")
                (DogName "Pluto")
                (Address "Disneyland")

-- without Reader
getDog :: Person -> Dog
getDog p = Dog (dogName p) (address p)

-- with Reader
getDogR :: Person -> Dog
getDogR = Dog <$> dogName <*> address

-- with Reader and liftA2
getDogR' :: Person -> Dog
getDogR' = liftA2 Dog dogName address

Exercise: Reading Comprehension

myLiftA2 :: Applicative f => (a -> b -> c) -> f a -> f b -> f c
myLiftA2 c f1 f2 = c <$> f1 <*> f2
asks :: (r -> a) -> Reader r a
asks f = Reader $ f
{-# LANGUAGE InstanceSigs #-}

instance Applicative (Reader r) where
    pure :: a -> Reader r a
    pure x = Reader $ \r -> x

    (<*>) :: Reader r (a -> b) -> Reader r a -> Reader r b
    (Reader rab) <*> (Reader ra) =
        Reader $ \r -> (rab r) (ra r)

22.7 The Monad of functions

(>>=) :: Monad m => m a -> (a -> m b) -> m b
-- replacing `m` with `r ->` and lining up, we have:
::     m a  -> (a ->    m b) ->     m b
:: (r -> a) -> (a -> r -> b) -> (r -> b)

Example use of Reader Monad

getDogRM :: Person -> Dog
getDogRM = do
    name <- dogName
    addy <- address
    return $ Dog name addy

Exercise: Reader Monad

{-# LANGUAGE InstanceSigs #-}

instance Monad (Reader r) where
    return = pure

    (>>=) :: Reader r a -> (a -> Reader r b) -> Reader r b
    (Reader ra) >>= aRb =
        Reader $ \r -> runReader (aRb (ra r)) r

22.8 Reader Monad by itself is boring

It can't do anything the Applicative cannot.

Generally speaking, you cannot derive a Monad from an Applicative, even though the other way is possible. However, for Reader, we can use flip and apply to make the Monad instance.

22.9 You can change what comes below, but not above

The “read-only” nature of the type argument r means that you can swap in a different type or value of r for functions that you call, but not for functions that call you.

In the next chapter, we’ll see the State monad where we can not only read in a value, but provide a new one which will change the value carried by the functions that called us, not only those we called.

22.10 You tend to see ReaderT, not Reader

Reader rarely stands alone. Usually it’s one Monad in a stack of multiple types providing a Monad instance such as with a web application that uses Reader to give you access to context about the HTTP request. When used in that fashion, it’s a monad transformer and we put a letter T after the type to indicate when we’re using it as such, so you’ll usually see ReaderT in production Haskell code rather than Reader.

Exercises: Chapter

(see attached file for full exercises)

Final output is:

*ExerciseChapter22> main
Just [3,2,1]
[[1,4],[1,5],[1,6],[2,4],[2,5],[2,6],[3,4],[3,5],[3,6]]
Just [6,9]
Just 15
Nothing
True
[True,False,False]
[True,True,False]
False
[True,False,False]
False
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment