rename topics/_coroutines_and_aborts.mdwn to topics/week13_coroutines_exceptions_and_...
[lambda.git] / topics / week4_more_about_fixed_point_combinators.mdwn
1 [[!toc levels=3]]
2
3 ## Application to the truth teller/liar paradoxes ##
4
5 Curry originally called `Y` the "paradoxical" combinator, and discussed
6 it in connection with certain well-known paradoxes from the philosophy
7 literature.  The truth-teller paradox has the flavor of a recursive
8 function without a base case:
9
10 (1)    This sentence meaning is true.
11
12 If we assume that the complex demonstrative "this sentence meaning" can refer
13 to the very meaning displayed in (1), then that meaning (1) will be true just in
14 case the thing referred to by *this sentence meaning* is true.  Thus, (1) will
15 be true just in case (1) is true, and (1) is true just in case (1) is
16 true, and so on.  If (1) is true, then (1) is true; but if (1) is not
17 true, then (1) is not true.
18
19 Without pretending to give a serious analysis of the paradox, let's
20 assume that sentences can have for their meaning boolean values
21 like the ones we have been working with in the Lambda Calculus.  Then the sentence *John
22 is John* might have as its meaning our `true`, namely `\y n. y`.
23
24 Now, the verb phrase in (1) expresses a function from whatever the referent of *this
25 sentence meaning* is to a boolean.  That is, `\m. m true false`, where
26 the argument `m` is the referent of *this sentence meaning*.  Of course, if
27 `m` is a boolean, `m true false <~~> m`, so for our purposes, we can
28 assume that the verb phrase of (1) denotes the identity function `I`.
29
30 If we use (1) in a context in which *this sentence meaning* refers to the
31 meaning expressed by the very sentence in which that demonstrative occurs, then we must find a
32 meaning `m` such that it is equivalent to the application of the verb phrase meaning to itself.
33 That is, `m <~~> I m`. In other words, `m` is
34 a fixed point for the meaning of the verb phrase.
35
36 That means that in a context in which *this sentence meaning* refers to the
37 meaning expressed by the sentence in which it occurs, the sentence's meaning is a fixed point for
38 the identity function. As we observed earlier, *anything* is a fixed point for the identity function.
39 In particular, each of the boolean values `true` and `false` are fixed points for the identity
40 function. What fixed point does `Y` give us?
41
42     Y I ≡
43     (\h. (\u. h (u u)) (\u. h (u u))) I ~~>
44     (\u. I (u u)) (\u. I (u u))) ~~>
45     (\u. (u u)) (\u. (u u))) ≡
46     ω ω
47     Ω
48
49 Well!  That feels right.  The meaning of *This sentence meaning is true*
50 could be `Ω`, our prototypical infinite loop...
51
52 ### What about the liar? ###
53
54 Let's consider:
55
56 (2)  This sentence meaning is false.
57
58 Used in a context in which *this sentence meaning* refers to the meaning expressed by the utterance of
59 (2) in which that noun phrase occurs, (2) will denote a fixed point for `\m. neg m`,
60 or `\m y n. m n y`, which is the `C` combinator.  So in such a
61 context, (2) might denote
62
63      Y C ≡
64      (\h. (\u. h (u u)) (\u. h (u u))) C ~~>
65      (\u. C (u u)) (\u. C (u u))) ~~>
66      C ((\u. C (u u)) (\u. C (u u))) ~~>
67      C (C ((\u. C (u u)) (\u. C (u u)))) ~~>
68      C (C (C ((\u. C (u u)) (\u. C (u u))))) ~~>
69      ...
70
71 An infinite sequence of `C`s, each one negating the remainder of the
72 sequence.  Yep, that feels like a reasonable representation of the
73 liar paradox.
74
75 See Barwise and Etchemendy's 1987 OUP book, [The Liar: an essay on
76 truth and circularity](http://tinyurl.com/2db62bk) for an approach
77 that is similar, but expressed in terms of non-well-founded sets
78 rather than recursive functions.
79
80 ### However... ###
81
82 You should be cautious about feeling too comfortable with
83 these results.  Thinking again of the truth-teller paradox, yes,
84 `Ω` is *a* fixed point for `I`, and perhaps it has
85 some privileged status among all the fixed points for `I`, being the
86 one delivered by `Y` and all (though it is not obvious why `Y` should have
87 any special status, versus other fixed point combinators).
88
89 But one could observe: look, literally every formula is a fixed point for
90 `I`, since
91
92     X <~~> I X
93
94 for any choice of `X` whatsoever.
95
96 So the `Y` combinator is only guaranteed to give us one fixed point out
97 of infinitely many --- and not always the intuitively most useful
98 one. (For instance, the squaring function `\x. mul x x` has `0` as a fixed point,
99 since `square 0 <~~> 0`, and `1` as a fixed point, since `square 1 <~~> 1`, but `Y
100 (\x. mul x x)` doesn't give us `0` or `1`.) So with respect to the
101 truth-teller paradox, why in the reasoning we've
102 just gone through should we be reaching for just this fixed point at
103 just this juncture?
104
105 One obstacle to thinking this through is the fact that a sentence
106 normally has only two truth values.  We might consider instead a noun
107 phrase such as
108
109 (3)  the entity that this noun phrase refers to
110
111 The reference of (3) depends on the reference of the embedded noun
112 phrase *this noun phrase*. As with (1), it will again need to be some fixed
113 point of `I`. It's easy to see that any object is a
114 fixed point for this referential function: if this pen cap is the
115 referent of the demonstrated noun phrase, then it is the referent of (3), and so on
116 for any object.
117
118 <!--
119 The chameleon nature of (3), by the way (a description that is equally
120 good at describing any object), makes it particularly well suited as a
121 gloss on pronouns such as *it*.  In the system of
122 [Jacobson 1999](http://www.springerlink.com/content/j706674r4w217jj5/),
123 pronouns denote (you guessed it!) identity functions...
124
125 TODO: We haven't made clear how we got from the self-referential (3) to I. We've so far only motivated
126 that the meaning of (3) should be *a fixed point* of I, but now you are saying this suggests Jacobson's idea to let it be I itself. Why? Sure that is *a* fixed point for I, but so is everything.
127 -->
128
129
130 Ultimately, in the context of this course, these paradoxes are more
131 useful as a way of gaining leverage on the concepts of fixed points
132 and recursion, rather than the other way around.
133
134
135 ## Q: How do you know that every term in the untyped lambda calculus has a fixed point? ##
136
137 A: That's easy: let `N` be an arbitrary term in the lambda calculus.  If
138 `N` has a fixed point, then there exists some `ξ` such that `ξ <~~>
139 N ξ` (that's what it means to *have* a fixed point).
140
141 <!-- L is \h u. h (u u); H here is L N -->
142
143     let H = \u. N (u u) in
144     let ξ = H H in
145     ξ ≡ H H ≡ (\u. N (u u)) H ~~> N (H H) ≡ N ξ
146
147
148 Please slow down and make sure that you understand what justified each
149 of the equalities in the last line.
150
151 ## Q: How do you know that for any term `N`, `Y N` is a fixed point of `N`? ##
152
153 A: Note that in the proof given in the previous answer, we chose `N`
154 and then set `ξ ≡ H H ≡ (\u. N (u u)) (\u. N (u u))`.  If we abstract over
155 `N`, we get the Y combinator, `\N. (\u. N (u u)) (\u. N (u u))`.  No matter
156 what argument `N` we feed `Y`, it returns some `ξ` that is a fixed point
157 of `N`, by the reasoning in the previous answer.
158
159
160 ## Q: So if every term has a fixed point, even `Y` has fixed point. ##
161
162 A: Right:
163
164     let Y = \h. (\u. h (u u)) (\u. h (u u)) in
165     Y Y ≡
166     \h. (\u. h (u u)) (\u. h (u u)) Y ~~>
167         (\u. Y (u u)) (\u. Y (u u)) ~~>
168              Y ((\u. Y (u u)) (\u. Y (u u))) ~~>
169              Y (     Y ((\u. Y (u u)) (\u. Y (u u)))) <~~>
170              Y (     Y (     Y (...(Y (Y Y))...)))
171
172
173
174 ## Q: Ouch!  Stop hurting my brain. ##
175
176 A: Is that a question?
177
178 Let's come at it from the direction of arithmetic.  Recall that we
179 claimed that even `succ` --- the function that added one to any
180 number --- had a fixed point.  How could there be an `ξ` such that `ξ <~~> succ ξ`?
181 That would imply that
182
183     ξ <~~> succ ξ <~~> succ (succ ξ) <~~> succ (succ (succ ξ)) <~~> succ (...(succ ξ)...)
184
185 In other words, the fixed point of `succ` is a term that is its own
186 successor.  Let's just check that `ξ = succ ξ`:
187
188     let succ = \n s z. s (n s z) in
189     let ξ = (\u. succ (u u)) (\u. succ (u u)) in
190     succ ξ
191     ≡   succ ((\u. succ (u u)) (\u. succ (u u))) 
192     ~~> succ (succ ((\u. succ (u u)) (\u. succ (u u))))
193     ≡   succ (succ ξ)
194
195 You should see the close similarity with `Y Y` here.
196
197
198 ## Q: So `Y` applied to `succ` returns a number that is not finite? ##
199
200 A: Well, if it makes sense to think of it as a number at all. It doesn't have the same structure as our encodings of finite Church numbers. But let's see if it behaves like they do:
201
202     ; assume same definitions as before
203     succ ξ
204     ≡    (\n s z. s (n s z)) ξ
205     ~~>  \s z. s (ξ s z)
206     <~~> succ (\s z. s (ξ s z)) ; using fixed-point reasoning
207     ≡    (\n s z. s (n s z)) (\s z. s (ξ s z))
208     ~~>  \s z. s ((\s z. s (ξ s z)) s z)
209     ~~>  \s z. s (s (ξ s z))
210
211 So `succ ξ` looks something like a Church number: it takes two arguments, `s` and `z`,
212 and returns a sequence of nested applications of `s`...
213
214 You should be able to prove that `add 2 (Y succ) <~~> Y succ`,
215 likewise for `mul`, `sub`, `pow`.  What happens if we try `sub (Y
216 succ) (Y succ)`?  What would you expect infinity minus infinity to be?
217 (Hint: choose your evaluation strategy so that you add two `s`s to the
218 first number for every `s` that you add to the second number.)
219
220 This is amazing, by the way: we're proving things about a term that
221 represents arithmetic infinity.  
222
223 It's important to bear in mind the simplest, least-evaluated term we begin with is not
224 infinitely long:
225
226         Y succ = (\h. (\u. h (u u)) (\u. h (u u))) (\n s z. s (n s z))
227
228 The way that infinity enters into the picture is that this term has
229 no normal form: no matter how many times we perform beta reduction,
230 there will always be an opportunity for more beta reduction.  (Lather,
231 rinse, repeat!)
232
233
234 ## Q: That reminds me, what about [[evaluation order]]? ##
235
236 A: For a recursive function that has a well-behaved base case, such as
237 the factorial function, evaluation order is crucial.  In the following
238 computation, we will arrive at a normal form.  Watch for the moment at
239 which we have to make a choice about which beta reduction to perform
240 next: one choice leads to a normal form, the other choice leads to
241 endless reduction:
242
243     let prefact = \fact n. (zero? n) 1 (mul n (fact (pred n))) in
244     let fact = Y prefact in
245     fact 2
246     ≡   [(\h. (\u. h (u u)) (\u. h (u u))) prefact] 2
247     ~~> [(\u. prefact (u u)) (\u. prefact (u u))] 2
248     ~~> [prefact ((\u. prefact (u u)) (\u. prefact (u u)))] 2
249     ~~> [prefact (prefact ((\u. prefact (u u)) (\u. prefact (u u))))] 2
250     ≡   [(\fact n. (zero? n) 1 (mul n (fact (pred n)))) (prefact ((\u. prefact (u u)) (\u. prefact (u u))))] 2
251     ~~> [\n. (zero? n) 1 (mul n ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] (pred n)))] 2
252     ~~> (zero? 2) 1 (mul 2 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] (pred 2)))
253     ~~> mul 2 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] 1)
254     ...
255     ~~> mul 2 (mul 1 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] 0))
256     ≡   mul 2 (mul 1 ((zero? 0) 1 (mul 1 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] (pred 0)))))
257     ~~> mul 2 (mul 1 1)
258     ~~> mul 2 1
259     ~~> 2
260
261 The crucial step is the third from the last.  We have our choice of
262 either evaluating the test `(zero? 0) 1 ...`, which evaluates to `1`,
263 no matter what the ... contains;
264 or we can evaluate the `Y` pump, `(\u. prefact (u u)) (\u. prefact (u u))`, to
265 produce another copy of `prefact`.  If we postpone evaluating the
266 `zero?` test, we'll pump out copy after copy of `prefact`, and never
267 realize that we've bottomed out in the recursion.  But if we adopt a
268 leftmost/call-by-name/normal-order evaluation strategy, we'll always
269 start with the `zero?` predicate, and only produce a fresh copy of
270 `prefact` if we are forced to. 
271
272
273 ## Q:  You claimed that the Ackermann function couldn't be implemented using our primitive recursion techniques (such as the techniques that allow us to define addition and multiplication).  But you haven't shown that it is possible to define the Ackermann function using full recursion. ##
274
275
276 A: OK:
277   
278         A(m,n) =
279                 | when m == 0 -> n + 1
280                 | else when n == 0 -> A(m-1, 1)
281                 | else -> A(m-1, A(m,n-1))
282
283         let A = Y (\A m n. (zero? m) (succ n) ((zero? n) (A (pred m) 1) (A (pred m) (A m (pred n)))))
284
285 So for instance:
286
287         A 1 2
288         ~~> A 0 (A 1 1)
289         ~~> A 0 (A 0 (A 1 0))
290         ~~> A 0 (A 0 (A 0 1))
291         ~~> A 0 (A 0 2)
292         ~~> A 0 3
293         ~~> 4
294
295 `A 1 x` is to `A 0 x` as addition is to the successor function;
296 `A 2 x` is to `A 1 x` as multiplication is to addition;
297 `A 3 x` is to `A 2 x` as exponentiation is to multiplication ---
298 so `A 4 x` is to `A 3 x` as hyper-exponentiation is to exponentiation...
299
300 ## Q: What other questions should I be asking? ##
301
302 *    What is it about the "primed" fixed-point combinators `Θ′` and `Y′` that
303      makes them compatible with a call-by-value evaluation strategy?
304
305 *    What *exactly* is primitive recursion?
306
307 *    How do you know that the Ackermann function can't be computed
308      using primitive recursion techniques?
309
310 *    I hear that `Y` delivers the/a *least* fixed point.  Least
311      according to what ordering?  How do you know it's least?
312      Is leastness important?
313
314 ## Q: I still don't fully understand the Y combinator.  Can you explain it in a different way?
315
316 Sure!  Here is another way to derive `Y`.  We'll start by choosing a
317 specific goal, and at each decision point, we'll make a reasonable
318 guess.  The guesses will all turn out to be lucky, and we'll arrive at
319 a fixed point combinator.
320
321 Given an arbitrary term `h`, we want to find a fixed point `X` such that:
322
323     X <~~> h X
324
325 Our strategy will be to seek an `X` such that `X ~~> h X` (this is just a guess). Because `X` and
326 `h X` are syntactically different, the only way that `X` can reduce to `h X` is if `X`
327 contains at least one redex.  The simplest way to satisfy this
328 constraint would be for the fixed point to itself be a redex (again, just a guess):
329
330     X ≡ ((\u. M) N) ~~> h X
331
332 The result of beta reduction on this redex will be `M` with some
333 substitutions.  We know that after these substitutions, `M` will have
334 the form `h X`, since that is what the reduction arrow tells us. So we
335 can refine the picture as follows:
336
337     X ≡ ((\u. h (___)) N) ~~> h X
338
339 Here, the `___` has to be something that reduces to the fixed point `X`.
340 It's natural to assume that there will be at least one occurrence of
341 `u` in the body of the head abstract:
342
343     X ≡ ((\u. h (__u__)) N) ~~> h X
344
345 After reduction of the redex, we're going to have
346
347     X ≡ h (__N__) ~~> h X
348
349 Apparently, `__N__` will have to reduce to `X`.  Therefore we should
350 choose a skeleton for `N` that is consistent with what we have decided
351 so far about the internal structure of `X`.  We might like for `N` to
352 syntactically match the whole of `X`, but this would require `N` to contain itself as
353 a subpart.  So we'll settle for the more modest assumption (or guess) that `N`
354 matches the head of `X`:
355
356     X ≡ ((\u. h (__u__)) (\u. h (__u__))) ~~> h X
357
358 At this point, we've derived a skeleton for X on which it contains two
359 so-far identical halves.  We'll guess that the halves will be exactly
360 identical.  Note that at the point at which we perform the first
361 reduction, `u` will get bound to `N`, which now corresponds to a term
362 representing one of the halves of `X`.  So in order to produce a full `X`,
363 we simply make a second copy of `u`:
364
365     X ≡ ((\u. h (u u)) (\u. h (u u)))
366     ~~>       h ((\u. h (u u)) (\u. h (u u)))
367       ≡       h X
368
369 Success.  
370
371 So the function `\h. (\u. h (u u)) (\u. h (u u))` maps an arbitrary term
372 `h` to a fixed point for `h`.
373
374
375 ## Q: How does this relate to the discussion in Chapter 9 of The Little Schemer? ##
376
377 A: Pages 160-172 of *The Little Schemer* introduce you to how to implement recursion in Scheme, without relying on the native capacity to do this expressed in `letrec` or `define`. The expression:
378
379     (lambda (length)
380       (lambda (l)
381         (cond
382           ((null? l) 0)
383           (else (add1 (length (cdr l)))))))
384
385 that occurs starting on p. 162 and on several pages following corresponds to `h` in [[our exposition|week4_fixed_point_combinators#little-h]]. The authors of *The Little Schemer* begin by applying that abstract to the argument `eternity`, which is a function that never returns; then they instead apply it to the argument `h eternity`, which is a function that works for lists of length zero, but otherwise never returns; then to the argument `h (h eternity)`, which works for lists of length zero or one, but otherwise never returns; and so on.
386
387 They work their way towards the realization that they want an "infinite tower" of applications of `h`, except they don't really need an infinite tower, but rather just a finite tower whose height can't be bounded in advance. This is essentially the observation that they need a fixed point for `h`.
388
389 The authors attempt to self-apply `h` on p. 165, just as we did. As we explained in [[our exposition|week4_fixed_point_combinators#deriving-y]], though, that doesn't quite work.
390
391 On the top of p. 167, the authors have instead moved to our `H`, and attempt to self-apply that, instead. And this works.
392
393 However, on p. 168, they attempt to abstract out the part that in our `H` looks like `(u u)` and in their exposition looks like `(mk-length mk-length)`. Doing that *would* work in our lambda evaluator, but you can't do it in Scheme, because Scheme has call-by-value evaluation order, which will try to fully reduce this expression before substituting it back into the term it's been abstracted out of. But it can't be fully reduced. Pages 168--170 explore this problem, and pp. 170--172 hit upon the solution of using what we called in our exposition the `Y′` fixed-point combinator, rather than the `Y` combinator that we derived. The authors of *The Little Schemer* call `Y′` the "applicative-order Y combinator".
394