aa167a4b3f1a20f26a1cebc5e1944d1b87d3c966
[lambda.git] / list_monad_as_continuation_monad.mdwn
1
2
3 Rethinking the list monad
4 -------------------------
5
6 To construct a monad, the key element is to settle on a type
7 constructor, and the monad naturally follows from that.  We'll remind
8 you of some examples of how monads follow from the type constructor in
9 a moment.  This will involve some review of familair material, but
10 it's worth doing for two reasons: it will set up a pattern for the new
11 discussion further below, and it will tie together some previously
12 unconnected elements of the course (more specifically, version 3 lists
13 and monads).
14
15 For instance, take the **Reader Monad**.  Once we decide that the type
16 constructor is
17
18     type 'a reader = env -> 'a
19
20 then the choice of unit and bind is natural:
21
22     let r_unit (a : 'a) : 'a reader = fun (e : env) -> a
23
24 Since the type of an `'a reader` is `env -> 'a` (by definition),
25 the type of the `r_unit` function is `'a -> env -> 'a`, which is a
26 specific case of the type of the *K* combinator.  So it makes sense
27 that *K* is the unit for the reader monad.
28
29 Since the type of the `bind` operator is required to be
30
31     r_bind : ('a reader) -> ('a -> 'b reader) -> ('b reader)
32
33 We can reason our way to the correct `bind` function as follows. We
34 start by declaring the types determined by the definition of a bind operation:
35
36     let r_bind (u : 'a reader) (f : 'a -> 'b reader) : ('b reader) = ...
37
38 Now we have to open up the `u` box and get out the `'a` object in order to
39 feed it to `f`.  Since `u` is a function from environments to
40 objects of type `'a`, the way we open a box in this monad is
41 by applying it to an environment:
42
43         ... f (u e) ...
44
45 This subexpression types to `'b reader`, which is good.  The only
46 problem is that we invented an environment `e` that we didn't already have ,
47 so we have to abstract over that variable to balance the books:
48
49         fun e -> f (u e) ...
50
51 This types to `env -> 'b reader`, but we want to end up with `env ->
52 'b`.  Once again, the easiest way to turn a `'b reader` into a `'b` is to apply it to an environment.  So we end up as follows:
53
54     r_bind (u : 'a reader) (f : 'a -> 'b reader) : ('b reader) =
55                 f (u e) e         
56
57 And we're done. This gives us a bind function of the right type. We can then check whether, in combination with the unit function we chose, it satisfies the monad laws, and behaves in the way we intend. And it does.
58
59 [The bind we cite here is a condensed version of the careful `let a = u e in ...`
60 constructions we provided in earlier lectures.  We use the condensed
61 version here in order to emphasize similarities of structure across
62 monads.]
63
64 The **State Monad** is similar.  Once we've decided to use the following type constructor:
65
66     type 'a state = store -> ('a, store)
67
68 Then our unit is naturally:
69
70     let s_unit (a : 'a) : ('a state) = fun (s : store) -> (a, s)
71
72 And we can reason our way to the bind function in a way similar to the reasoning given above. First, we need to apply `f` to the contents of the `u` box:
73
74     let s_bind (u : 'a state) (f : 'a -> 'b state) : 'b state = 
75                 ... f (...) ...
76
77 But unlocking the `u` box is a little more complicated.  As before, we
78 need to posit a state `s` that we can apply `u` to.  Once we do so,
79 however, we won't have an `'a`, we'll have a pair whose first element
80 is an `'a`.  So we have to unpack the pair:
81
82         ... let (a, s') = u s in ... (f a) ...
83
84 Abstracting over the `s` and adjusting the types gives the result:
85
86         let s_bind (u : 'a state) (f : 'a -> 'b state) : 'b state = 
87                 fun (s : store) -> let (a, s') = u s in f a s'
88
89 The **Option/Maybe Monad** doesn't follow the same pattern so closely, so we
90 won't pause to explore it here, though conceptually its unit and bind
91 follow just as naturally from its type constructor.
92
93 Our other familiar monad is the **List Monad**, which we were told
94 looks like this:
95
96     type 'a list = ['a];;
97     l_unit (a : 'a) = [a];;
98     l_bind u f = List.concat (List.map f u);;
99
100 Thinking through the list monad will take a little time, but doing so
101 will provide a connection with continuations.
102
103 Recall that `List.map` takes a function and a list and returns the
104 result to applying the function to the elements of the list:
105
106     List.map (fun i -> [i;i+1]) [1;2] ~~> [[1; 2]; [2; 3]]
107
108 and List.concat takes a list of lists and erases the embdded list
109 boundaries:
110
111     List.concat [[1; 2]; [2; 3]] ~~> [1; 2; 2; 3]
112
113 And sure enough, 
114
115     l_bind [1;2] (fun i -> [i, i+1]) ~~> [1; 2; 2; 3]
116
117 Now, why this unit, and why this bind?  Well, ideally a unit should
118 not throw away information, so we can rule out `fun x -> []` as an
119 ideal unit.  And units should not add more information than required,
120 so there's no obvious reason to prefer `fun x -> [x,x]`.  In other
121 words, `fun x -> [x]` is a reasonable choice for a unit.
122
123 As for bind, an `'a list` monadic object contains a lot of objects of
124 type `'a`, and we want to make some use of each of them (rather than
125 arbitrarily throwing some of them away).  The only
126 thing we know for sure we can do with an object of type `'a` is apply
127 the function of type `'a -> 'a list` to them.  Once we've done so, we
128 have a collection of lists, one for each of the `'a`'s.  One
129 possibility is that we could gather them all up in a list, so that
130 `bind' [1;2] (fun i -> [i;i]) ~~> [[1;1];[2;2]]`.  But that restricts
131 the object returned by the second argument of `bind` to always be of
132 type `'b list list`.  We can elimiate that restriction by flattening
133 the list of lists into a single list: this is
134 just List.concat applied to the output of List.map.  So there is some logic to the
135 choice of unit and bind for the list monad.  
136
137 Yet we can still desire to go deeper, and see if the appropriate bind
138 behavior emerges from the types, as it did for the previously
139 considered monads.  But we can't do that if we leave the list type 
140 as a primitive Ocaml type.  However, we know several ways of implementing
141 lists using just functions.  In what follows, we're going to use type
142 3 lists (the right fold implementation), though it's important to
143 wonder how things would change if we used some other strategy for
144 implementating lists.  These were the lists that made lists look like
145 Church numerals with extra bits embdded in them:
146
147     empty list:                fun f z -> z
148     list with one element:     fun f z -> f 1 z
149     list with two elements:    fun f z -> f 2 (f 1 z)
150     list with three elements:  fun f z -> f 3 (f 2 (f 1 z))
151
152 and so on.  To save time, we'll let the OCaml interpreter infer the
153 principle types of these functions (rather than inferring what the
154 types should be ourselves):
155
156         # fun f z -> z;;
157         - : 'a -> 'b -> 'b = <fun>
158         # fun f z -> f 1 z;;
159         - : (int -> 'a -> 'b) -> 'a -> 'b = <fun>
160         # fun f z -> f 2 (f 1 z);;
161         - : (int -> 'a -> 'a) -> 'a -> 'a = <fun>
162         # fun f z -> f 3 (f 2 (f 1 z))
163         - : (int -> 'a -> 'a) -> 'a -> 'a = <fun>
164
165 We can see what the consistent, general principle types are at the end, so we
166 can stop. These types should remind you of the simply-typed lambda calculus
167 types for Church numerals (`(o -> o) -> o -> o`) with one extra type
168 thrown in, the type of the element a the head of the list
169 (in this case, an int).
170
171 So here's our type constructor for our hand-rolled lists:
172
173     type 'b list' = (int -> 'b -> 'b) -> 'b -> 'b
174
175 Generalizing to lists that contain any kind of element (not just
176 ints), we have
177
178     type ('a, 'b) list' = ('a -> 'b -> 'b) -> 'b -> 'b
179
180 So an `('a, 'b) list'` is a list containing elements of type `'a`,
181 where `'b` is the type of some part of the plumbing.  This is more
182 general than an ordinary OCaml list, but we'll see how to map them
183 into OCaml lists soon.  We don't need to fully grasp the role of the `'b`'s
184 in order to proceed to build a monad:
185
186     l'_unit (a : 'a) : ('a, 'b) list = fun a -> fun f z -> f a z
187
188 No problem.  Arriving at bind is a little more complicated, but
189 exactly the same principles apply, you just have to be careful and
190 systematic about it.
191
192     l'_bind (u : ('a,'b) list') (f : 'a -> ('c, 'd) list') : ('c, 'd) list'  = ...
193
194 Unpacking the types gives:
195
196     l'_bind (u : ('a -> 'b -> 'b) -> 'b -> 'b)
197             (f : 'a -> ('c -> 'd -> 'd) -> 'd -> 'd)
198             : ('c -> 'd -> 'd) -> 'd -> 'd = ...
199
200 Perhaps a bit intimiating.
201 But it's a rookie mistake to quail before complicated types. You should
202 be no more intimiated by complex types than by a linguistic tree with
203 deeply embedded branches: complex structure created by repeated
204 application of simple rules.
205
206 [This would be a good time to try to build your own term for the types
207 just given.  Doing so (or attempting to do so) will make the next
208 paragraph much easier to follow.]
209
210 As usual, we need to unpack the `u` box.  Examine the type of `u`.
211 This time, `u` will only deliver up its contents if we give `u` an
212 argument that is a function expecting an `'a` and a `'b`. `u` will 
213 fold that function over its type `'a` members, and that's how we'll get the `'a`s we need. Thus:
214
215         ... u (fun (a : 'a) (b : 'b) -> ... f a ... ) ...
216
217 In order for `u` to have the kind of argument it needs, the `... (f a) ...` has to evaluate to a result of type `'b`. The easiest way to do this is to collapse (or "unify") the types `'b` and `'d`, with the result that `f a` will have type `('c -> 'b -> 'b) -> 'b -> 'b`. Let's postulate an argument `k` of type `('c -> 'b -> 'b)` and supply it to `(f a)`:
218
219         ... u (fun (a : 'a) (b : 'b) -> ... f a k ... ) ...
220
221 Now we have an argument `b` of type `'b`, so we can supply that to `(f a) k`, getting a result of type `'b`, as we need:
222
223         ... u (fun (a : 'a) (b : 'b) -> f a k b) ...
224
225 Now, we've used a `k` that we pulled out of nowhere, so we need to abstract over it:
226
227         fun (k : 'c -> 'b -> 'b) -> u (fun (a : 'a) (b : 'b) -> f a k b)
228
229 This whole expression has type `('c -> 'b -> 'b) -> 'b -> 'b`, which is exactly the type of a `('c, 'b) list'`. So we can hypothesize that we our bind is:
230
231     l'_bind (u : ('a -> 'b -> 'b) -> 'b -> 'b)
232             (f : 'a -> ('c -> 'b -> 'b) -> 'b -> 'b)
233             : ('c -> 'b -> 'b) -> 'b -> 'b = 
234       fun k -> u (fun a b -> f a k b)
235
236 That is a function of the right type for our bind, but to check whether it works, we have to verify it (with the unit we chose) against the monad laws, and reason whether it will have the right behavior.
237
238 Here's a way to persuade yourself that it will have the right behavior. First, it will be handy to eta-expand our `fun k -> u (fun a b -> f a k b)` to:
239
240       fun k z -> u (fun a b -> f a k b) z
241
242 Now let's think about what this does. It's a wrapper around `u`. In order to behave as the list which is the result of mapping `f` over each element of `u`, and then joining (`concat`ing) the results, this wrapper would have to accept arguments `k` and `z` and fold them in just the same way that the list which is the result of mapping `f` and then joining the results would fold them. Will it?
243
244 Suppose we have a list' whose contents are `[1; 2; 4; 8]`---that is, our list' will be `fun f z -> f 1 (f 2 (f 4 (f 8 z)))`. We call that list' `u`. Suppose we also have a function `f` that for each `int` we give it, gives back a list of the divisors of that `int` that are greater than 1. Intuitively, then, binding `u` to `f` should give us:
245
246         concat (map f u) =
247         concat [[]; [2]; [2; 4]; [2; 4; 8]] =
248         [2; 2; 4; 2; 4; 8]
249
250 Or rather, it should give us a list' version of that, which takes a function `k` and value `z` as arguments, and returns the right fold of `k` and `z` over those elements. What does our formula
251
252       fun k z -> u (fun a b -> f a k b) z
253         
254 do? Well, for each element `a` in `u`, it applies `f` to that `a`, getting one of the lists:
255
256         []
257         [2]
258         [2; 4]
259         [2; 4; 8]
260
261 (or rather, their list' versions). Then it takes the accumulated result `b` of previous steps in the fold, and it folds `k` and `b` over the list generated by `f a`. The result of doing so is passed on to the next step as the accumulated result so far.
262
263 So if, for example, we let `k` be `+` and `z` be `0`, then the computation would proceed:
264
265         0 ==>
266         right-fold + and 0 over [2; 4; 8] = 2+4+8+0 ==>
267         right-fold + and 2+4+8+0 over [2; 4] = 2+4+2+4+8+0 ==>
268         right-fold + and 2+4+2+4+8+0 over [2] = 2+2+4+2+4+8+0 ==>
269         right-fold + and 2+2+4+2+4+8+0 over [] = 2+2+4+2+4+8+0
270
271 which indeed is the result of right-folding + and 0 over `[2; 2; 4; 2; 4; 8]`. If you trace through how this works, you should be able to persuade yourself that our formula:
272
273       fun k z -> u (fun a b -> f a k b) z
274
275 will deliver just the same folds, for arbitrary choices of `k` and `z` (with the right types), and arbitrary list's `u` and appropriately-typed `f`s, as
276
277         fun k z -> List.fold_right k (concat (map f u)) z
278
279 would.
280
281 For future reference, we might make two eta-reductions to our formula, so that we have instead:
282
283       let l'_bind = fun k -> u (fun a -> f a k);;
284
285 Let's make some more tests:
286
287
288     l_bind [1;2] (fun i -> [i, i+1]) ~~> [1; 2; 2; 3]
289
290     l'_bind (fun f z -> f 1 (f 2 z)) 
291             (fun i -> fun f z -> f i (f (i+1) z)) ~~> <fun>
292
293 Sigh.  OCaml won't show us our own list.  So we have to choose an `f`
294 and a `z` that will turn our hand-crafted lists into standard OCaml
295 lists, so that they will print out.
296
297         # let cons h t = h :: t;;  (* OCaml is stupid about :: *)
298         # l'_bind (fun f z -> f 1 (f 2 z)) 
299                           (fun i -> fun f z -> f i (f (i+1) z)) cons [];;
300         - : int list = [1; 2; 2; 3]
301
302 Ta da!
303