Last active
April 21, 2024 11:15
-
-
Save twopoint718/c02164137c6fca9e0c4c to your computer and use it in GitHub Desktop.
An article about the Reader type (functor, applicative, and monad instances)
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Okay, so I'll try and walk through the reader monad as best as I can. And | |
because I think it helps to de-mystify things a bit, I'll also go through | |
all of the "super classes" of monad: functor and applicative (because every | |
monad should also be an applicative and every applicative functor should be | |
a functor). This file is literate Haskell so you should just be able to | |
load it in the REPL or run it. It's also kinda/sorta markdown, so it should | |
render that way as well (but the code is formatted wrong). | |
> module Reader where | |
> import Text.Printf (printf) | |
This probably isn't clear right now, but the reader type is basically (or | |
_exactly_, I think) a partially applied function. It is a function from some | |
type `e` to some (possibly) other type, `a`. The type signature for something like | |
that is `e -> a` (because it takes some type `e` and then converts it to an | |
`a`). You can think of the type `e` as the wrapped read-only state, the `a` is | |
unspecified. To name this type and make it easier to work with, I'm going to use | |
`newtype` to wrap that function: | |
> newtype Reader e a = Reader { runReader :: e -> a } | |
All this says is that we're wrapping a function from `e` to `a`. Newtype | |
basically has the effect of defining two functions: `Reader` and `runReader` | |
which are inverses: | |
* `Reader :: (e -> a) -> Reader e a` - this _constructs_ a `Reader` value from | |
a function from `e -> a` | |
* `runReader :: Reader e a -> e -> a` - you can even fiddle with the | |
parentheses in the type signature to get this: `runReader :: Reader e a -> (e | |
-> a)` (because everything is curried in Haskell, `a -> b -> c` is the same as | |
`a -> (b -> c)`). | |
So those two type signatures are literally flipped versions of one another. | |
Now we have enough to write a `Functor` instance for `Reader`: | |
> instance Functor (Reader e) where | |
> fmap f mr = Reader (\r -> f (runReader mr r)) | |
Technically, we're not done because we need to make sure that these laws hold | |
for our implementation: | |
1. `fmap id = id` | |
2. `fmap (g . f) = fmap g . fmap f` | |
...but I'll skip them for now. | |
To be really clear, `fmap` has the type `Functor f => (a -> b) -> f a -> f b`. | |
That means that it allows us to swap out the value that's "contained" in | |
some context... Those are scare quotes, because this is a pretty flimsy | |
meaning of _container_... it translates to something like "has an eventual | |
return value of." Here's what the types would look like: | |
fmap :: (a -> b) -> Reader e a -> Reader e b | |
So we're mapping over the second type in `Reader e a`, that's the _final | |
returned value_ rather than the _contained_ value (notice how the `e` isn't | |
used anywhere). | |
Next, we can write the instance for `Applicative`: | |
> instance Applicative (Reader e) where | |
> pure x = Reader (\_ -> x) | |
> rf <*> rx = Reader (\r -> (runReader rf r) (runReader rx r)) | |
Here are what those two functions mean: | |
* `pure` - is a way of wrapping a value in a _minimal_ or _default_ | |
applicative context. We can use this to "lift" values that would | |
otherwise not be applicative so that we can work with them. | |
* `<*>` - if I were to give a name to this function, it would be "apply". | |
The intuition is that we have a function wrapped in a Reader and we want | |
to apply it to a value wrapped in a Reader. The result is also wrapped in | |
Reader. This lets us knit together bigger functions: | |
> equation :: Int -> Int | |
> equation x = runReader (pure (*) <*> Reader (+2) <*> Reader (+1)) x | |
So this function essentially rewrites to this: `equation x = (x+2) * (x+1)` | |
That's contrived, but the idea is that `<*>` lets you apply a function of any | |
arity to a bunch of values "inside" Readers. | |
Now we're finally ready to tackle monad. So monad is just two more functions: | |
`return` and `>>=` or sometimes called "bind". | |
> instance Monad (Reader e) where | |
> return = pure | |
> | |
> mr >>= f = | |
> let | |
> step1 r = runReader mr r -- unwrap inner reader | |
> step2 r = f (step1 r) -- apply function to that value | |
> step3 r = runReader (step2 r) r -- unwrap outer reader | |
> in | |
> Reader (\r -> step3 r) -- package up resulting reader value | |
A more recent thing (a big refactor in the standard libs known as the | |
Applicative Monad Proposal or _AMP_) that many tutorials won't cover is | |
that `return` is now the same as `pure` from the Applicative typeclass. So | |
we get that for free. That leaves `>>=`. The idea of bind is to thread or | |
chain computations. I think it is clearer to break up the implementation | |
above into a few stages. It's also helpful to think of `runReader` as being | |
a function which "unwraps" a Reader, exposing the underlying value. | |
Because, remember: | |
runReader [some reader] [initial state] => [final result] | |
Starting with the innermost expression: | |
* `(runReader mr r) :: a` -- call this `step1`, we need to get a value that | |
we can call `f` on. | |
* `f step1 :: Reader e b` -- because from the definition of bind: | |
`(>>=) :: Reader e a -> (a -> Reader e b) -> Reader e b` we applied | |
`a -> Reader e b` to an `a`, yielding `Reader e b`. Call this value `step2` | |
* `runReader step2 r` -- this reduces to `b`, again by the definition of | |
`runReader`. | |
The last thing that we need in order to work with readers comes from the | |
Monad Reader class. This is a function which can grab the underlying | |
read-only state so that we can work with it. I have to admit, that this is | |
one I'd never be able to come up with, but I think I can understand (I'm | |
not sure if there's a smarter way to figure this function out, I'm | |
definitely giving a _post hoc_ argument here): | |
The trick is to notice that Reader has a really funky type: `Reader :: (e -> a) | |
-> Reader e a` -- that first argument is just a function. If we could pass an | |
argument to `Reader` which would force the input to be the output, we could | |
gain access to the otherwise "hidden" state. There's just such a function, `id | |
:: a -> a`. Passing that to Reader leaves us with `Reader a a`! That means that | |
the result type (normally the `a`) _must_ be the same as the read-only state | |
type (what we`ve been calling `e`). That means we're left with a Reader which | |
will cough up the internal state. Here's the implementation: | |
> ask :: Reader a a | |
> ask = Reader id | |
I think that's pretty cool. We can use that to write `asks` really easily: | |
> asks :: (r -> a) -> Reader r a | |
> asks f = do | |
> x <- ask | |
> return (f x) | |
This is a handy function for calling an accessor function on the read-only | |
state: | |
> data Person = Person { name :: String, age :: Int, email :: String } | |
> | |
> ageInNYears :: Int -> Reader Person Int | |
> ageInNYears n = do | |
> currentAge <- asks age | |
> return (currentAge + n) | |
> | |
> formatEmail :: Reader Person String | |
> formatEmail = do | |
> name' <- asks name | |
> email' <- asks email | |
> return (printf "\"%s\" <%s>" name' email') | |
> | |
> chris :: Person | |
> chris = Person "Chris Wilson" 34 "[email protected]" | |
> | |
> report :: Reader Person String | |
> report = do | |
> five <- ageInNYears 5 | |
> mailto <- formatEmail | |
> let output = printf "Age in 5:\t%d\nEmail:\t\t%s" five mailto | |
> return output | |
> | |
> main :: IO () | |
> main = putStrLn (runReader report chris) | |
A few nice things about this is that it provides a way to factor out what | |
would otherwise be redundant arguments to functions. The `Reader State | |
String` declares that it uses state `State` and computes a `String`. As | |
long as several different functions share the `State` part, we can combine | |
them into bigger computations (what `report` does when it uses | |
`ageInNYears` and `formatEmail`). I think it is nice because it very | |
clearly threads the state into the series of functions at one point. Here, | |
`main` is the only place that I have to pass in `chris`. In more | |
complicated applications, I'd almost certainly be doing IO to be able to | |
construct that `Person` value. It's nice to have that quarantined off in | |
one spot. |
I’m so glad you found it useful!Sent from my iPhoneOn May 25, 2023, at 11:36, Ron Male ***@***.***> wrote:Re: ***@***.*** commented on this gist.That was very helpful. I had to fill in some extra notation, but you gave the foundation needed.—Reply to this email directly, view it on GitHub or unsubscribe.You are receiving this email because you authored the thread.Triage notifications on the go with GitHub Mobile for iOS or Android.
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment
That was very helpful. I had to fill in some extra notation, but you gave the foundation needed.