Merge branch 'working'
authorJim <jim.pryor@nyu.edu>
Fri, 20 Feb 2015 14:19:33 +0000 (09:19 -0500)
committerJim <jim.pryor@nyu.edu>
Fri, 20 Feb 2015 14:19:33 +0000 (09:19 -0500)
* working:
  tweak comment

content.mdwn
index.mdwn
topics/week4_fixed_point_combinators.mdwn
topics/week4_more_about_fixed_point_combinators.mdwn [new file with mode: 0644]
topics/week4_more_fixed_points.mdwn [deleted file]

index cb67dcf..a546e9d 100644 (file)
@@ -37,6 +37,7 @@ week in which they were introduced.
         *   [[Some other list encodings|topics/week3 lists#other-lists]]
     *    Reduction Strategies and Normal Forms
     *   [[Fixed point combinators|topics/week4_fixed_point_combinators]]
+    *   [[More about fixed point combinators|topics/week4_more_about_fixed_point_combinators]]
 
 
 *    [[Combinatory Logic|topics/week3 combinatory logic]]
@@ -77,6 +78,6 @@ Introduces list comprehensions, discusses how to get the `tail` of lists in the
 Week 4:
 
 *   [[Fixed point combinators|topics/week4_fixed_point_combinators]]
-*   More on fixed point combinators (in progress)
+*   [[More about fixed point combinators|topics/week4_more_about_fixed_point_combinators]]
 *   Towards types (in progress)
 
index 73f77f2..8f0e0c6 100644 (file)
@@ -122,7 +122,7 @@ Reduction Strategies and Normal Forms (in progress);
 
 > Topics: [[!img images/tabletop_roleplaying.png size="240x240" alt="Hey, no recursing"]]
 [[Yes, recursing|topics/week4_fixed_point_combinators]];
-More on fixed point combinators (in progress);
+[[More about fixed point combinators|topics/week4_more_about_fixed_point_combinators]];
 Towards types (in progress)
 
 > Now you can read Sections 3.1 and 6.1 of Hankin; and browse the rest of Hankin Chapter 6, which should look somewhat familiar.
index 601ad81..b20212d 100644 (file)
@@ -553,9 +553,9 @@ then this is a fixed-point combinator:
 For those of you who like to watch ultra slow-mo movies of bullets
 piercing apples, here's a stepwise computation of the application of a
 recursive function.  We'll use a function `sink`, which takes one
-argument.  If the argument is boolean true (i.e., `\x y. x`), it
+argument.  If the argument is boolean true (i.e., `\y n. y`), it
 returns itself (a copy of `sink`); if the argument is boolean false
-(`\x y. y`), it returns `I`.  That is, we want the following behavior:
+(`\y n. n`), it returns `I`.  That is, we want the following behavior:
 
     sink false <~~> I
     sink true false <~~> I
diff --git a/topics/week4_more_about_fixed_point_combinators.mdwn b/topics/week4_more_about_fixed_point_combinators.mdwn
new file mode 100644 (file)
index 0000000..33c2f07
--- /dev/null
@@ -0,0 +1,312 @@
+[[!toc levels=3]]
+
+## Application to the truth teller/liar paradoxes ##
+
+Curry originally called `Y` the "paradoxical" combinator, and discussed
+it in connection with certain well-known paradoxes from the philosophy
+literature.  The truth-teller paradox has the flavor of a recursive
+function without a base case:
+
+(1)    This sentence meaning is true.
+
+If we assume that the complex demonstrative "this sentence meaning" can refer
+to the very meaning displayed in (1), then that meaning (1) will be true just in
+case the thing referred to by *this sentence meaning* is true.  Thus, (1) will
+be true just in case (1) is true, and (1) is true just in case (1) is
+true, and so on.  If (1) is true, then (1) is true; but if (1) is not
+true, then (1) is not true.
+
+Without pretending to give a serious analysis of the paradox, let's
+assume that sentences can have for their meaning boolean values
+like the ones we have been working with in the Lambda Calculus.  Then the sentence *John
+is John* might have as its meaning our `true`, namely `\y n. y`.
+
+Now, the verb phrase in (1) expresses a function from whatever the referent of *this
+sentence meaning* is to a boolean.  That is, `\m. m true false`, where
+the argument `m` is the referent of *this sentence meaning*.  Of course, if
+`m` is a boolean, `m true false <~~> m`, so for our purposes, we can
+assume that the verb phrase of (1) denotes the identity function `I`.
+
+If we use (1) in a context in which *this sentence meaning* refers to the
+meaning expressed by the very sentence in which that demonstrative occurs, then we must find a
+meaning `m` such that it is equivalent to the application of the verb phrase meaning to itself.
+That is, `m <~~> I m`. In other words, `m` is
+a fixed point for the meaning of the verb phrase.
+
+That means that in a context in which *this sentence meaning* refers to the
+meaning expressed by the sentence in which it occurs, the sentence's meaning is a fixed point for
+the identity function. As we observed earlier, *anything* is a fixed point for the identity function.
+In particular, each of the boolean values `true` and `false` are fixed points for the identity
+function. What fixed point does `Y` give us?
+
+    Y I ≡
+    (\h. (\u. h (u u)) (\u. h (u u))) I ~~>
+    (\u. I (u u)) (\u. I (u u))) ~~>
+    (\u. (u u)) (\u. (u u))) ≡
+    ω ω
+    Ω
+
+Well!  That feels right.  The meaning of *This sentence meaning is true*
+could be `Ω`, our prototypical infinite loop...
+
+### What about the liar? ###
+
+Let's consider:
+
+(2)  This sentence meaning is false.
+
+Used in a context in which *this sentence meaning* refers to the meaning expressed by the utterance of
+(2) in which that noun phrase occurs, (2) will denote a fixed point for `\m. neg m`,
+or `\m y n. m n y`, which is the `C` combinator.  So in such a
+context, (2) might denote
+
+     Y C
+     (\h. (\u. h (u u)) (\u. h (u u))) C
+     (\u. C (u u)) (\u. C (u u)))
+     C ((\u. C (u u)) (\u. C (u u)))
+     C (C ((\u. C (u u)) (\u. C (u u))))
+     C (C (C ((\u. C (u u)) (\u. C (u u)))))
+     ...
+
+And infinite sequence of `C`s, each one negating the remainder of the
+sequence.  Yep, that feels like a reasonable representation of the
+liar paradox.
+
+See Barwise and Etchemendy's 1987 OUP book, [The Liar: an essay on
+truth and circularity](http://tinyurl.com/2db62bk) for an approach
+that is similar, but expressed in terms of non-well-founded sets
+rather than recursive functions.
+
+### However... ###
+
+You should be cautious about feeling too comfortable with
+these results.  Thinking again of the truth-teller paradox, yes,
+`Ω` is *a* fixed point for `I`, and perhaps it has
+some privileged status among all the fixed points for `I`, being the
+one delivered by `Y` and all (though it is not obvious why `Y` should have
+any special status, versus other fixed point combinators).
+
+But one could observe: look, literally every formula is a fixed point for
+`I`, since
+
+    X <~~> I X
+
+for any choice of `X` whatsoever.
+
+So the `Y` combinator is only guaranteed to give us one fixed point out
+of infinitely many --- and not always the intuitively most useful
+one. (For instance, the squaring function `\x. mul x x` has `0` as a fixed point,
+since `square 0 <~~> 0`, and `1` as a fixed point, since `square 1 <~~> 1`, but `Y
+(\x. mul x x)` doesn't give us `0` or `1`.) So with respect to the
+truth-teller paradox, why in the reasoning we've
+just gone through should we be reaching for just this fixed point at
+just this juncture?
+
+One obstacle to thinking this through is the fact that a sentence
+normally has only two truth values.  We might consider instead a noun
+phrase such as
+
+(3)  the entity that this noun phrase refers to
+
+The reference of (3) depends on the reference of the embedded noun
+phrase *this noun phrase*. As with (1), it will again need to be some fixed
+point of `I`. It's easy to see that any object is a
+fixed point for this referential function: if this pen cap is the
+referent of the demonstrated noun phrase, then it is the referent of (3), and so on
+for any object.
+
+<!--
+The chameleon nature of (3), by the way (a description that is equally
+good at describing any object), makes it particularly well suited as a
+gloss on pronouns such as *it*.  In the system of
+[Jacobson 1999](http://www.springerlink.com/content/j706674r4w217jj5/),
+pronouns denote (you guessed it!) identity functions...
+
+TODO: We haven't made clear how we got from the self-referential (3) to I. We've so far only motivated
+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.
+-->
+
+
+Ultimately, in the context of this course, these paradoxes are more
+useful as a way of gaining leverage on the concepts of fixed points
+and recursion, rather than the other way around.
+
+
+## Q: How do you know that every term in the untyped lambda calculus has a fixed point? ##
+
+A: That's easy: let `N` be an arbitrary term in the lambda calculus.  If
+`N` has a fixed point, then there exists some `ξ` such that `ξ <~~>
+N ξ` (that's what it means to *have* a fixed point).
+
+<!-- L is \h u. h (u u); H here is L N -->
+
+    let H = \u. N (u u) in
+    let ξ = H H in
+    ξ ≡ H H ≡ (\u. N (u u)) H ~~> N (H H) ≡ N ξ
+
+
+Please slow down and make sure that you understand what justified each
+of the equalities in the last line.
+
+## Q: How do you know that for any term `N`, `Y N` is a fixed point of `N`? ##
+
+A: Note that in the proof given in the previous answer, we chose `N`
+and then set `ξ ≡ H H ≡ (\u. N (u u)) (\u. N (u u))`.  If we abstract over
+`N`, we get the Y combinator, `\N. (\u. N (u u)) (\u. N (u u))`.  No matter
+what argument `N` we feed `Y`, it returns some `ξ` that is a fixed point
+of `N`, by the reasoning in the previous answer.
+
+
+## Q: So if every term has a fixed point, even `Y` has fixed point. ##
+
+A: Right:
+
+    let Y = \N. (\u. N (u u)) (\u. N (u u)) in
+    Y Y
+    ≡   \N. (\u. N (u u)) (\u. N (u u)) Y
+    ~~>     (\u. Y (u u)) (\u. Y (u u))
+    ~~>          Y ((\u. Y (u u)) (\u. Y (u u)))
+    ~~>          Y (     Y ((\u. Y (u u)) (\u. Y (u u))))
+    ~~> Y (Y (Y (...(Y (Y Y))...)))
+
+
+
+## Q: Ouch!  Stop hurting my brain. ##
+
+A: Is that a question?
+
+Let's come at it from the direction of arithmetic.  Recall that we
+claimed that even `succ`---the function that added one to any
+number---had a fixed point.  How could there be an `ξ` such that `ξ <~~> succ ξ`?
+That would imply that
+
+    ξ <~~> succ ξ <~~> succ (succ ξ) <~~> succ (succ (succ ξ)) <~~> succ (...(succ ξ)...)
+
+In other words, the fixed point of `succ` is a term that is its own
+successor.  Let's just check that `ξ = succ ξ`:
+
+    let succ = \n s z. s (n s z) in
+    let ξ = (\u. succ (u u)) (\u. succ (u u)) in
+    succ ξ
+    ≡   succ ((\u. succ (u u)) (\u. succ (u u))) 
+    ~~> succ (succ ((\u. succ (u u)) (\u. succ (u u))))
+    ≡   succ (succ ξ)
+
+You should see the close similarity with `Y Y` here.
+
+
+## Q. So `Y` applied to `succ` returns a number that is not finite? ##
+
+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:
+
+    ; assume same definitions as before
+    succ ξ
+    ≡    (\n s z. s (n s z)) ξ
+    ~~>  \s z. s (ξ s z)
+    <~~> succ (\s z. s (ξ s z)) ; using fixed-point reasoning
+    ≡    (\n s z. s (n s z)) (\s z. s (ξ s z))
+    ~~>  \s z. s ((\s z. s (ξ s z)) s z)
+    ~~>  \s z. s (s (ξ s z))
+
+So `succ ξ` looks something like a Church number: it takes two arguments, `s` and `z`,
+and returns a sequence of nested applications of `s`...
+
+You should be able to prove that `add 2 (Y succ) <~~> Y succ`,
+likewise for `mul`, `sub`, `pow`.  What happens if we try `sub (Y
+succ) (Y succ)`?  What would you expect infinity minus infinity to be?
+(Hint: choose your evaluation strategy so that you add two `s`s to the
+first number for every `s` that you add to the second number.)
+
+This is amazing, by the way: we're proving things about a term that
+represents arithmetic infinity.  
+
+It's important to bear in mind the simplest, least-evaluated term we begin with is not
+infinitely long:
+
+       Y succ = (\h. (\u. h (u u)) (\u. h (u u))) (\n s z. s (n s z))
+
+The way that infinity enters into the picture is that this term has
+no normal form: no matter how many times we perform beta reduction,
+there will always be an opportunity for more beta reduction.  (Lather,
+rinse, repeat!)
+
+
+## Q. That reminds me, what about [[evaluation order]]? ##
+
+A. For a recursive function that has a well-behaved base case, such as
+the factorial function, evaluation order is crucial.  In the following
+computation, we will arrive at a normal form.  Watch for the moment at
+which we have to make a choice about which beta reduction to perform
+next: one choice leads to a normal form, the other choice leads to
+endless reduction:
+
+    let prefact = \fact n. (zero? n) 1 (mul n (fact (pred n))) in
+    let fact = Y prefact in
+    fact 2
+    ≡   [(\h. (\u. h (u u)) (\u. h (u u))) prefact] 2
+    ~~> [(\u. prefact (u u)) (\u. prefact (u u))] 2
+    ~~> [prefact ((\u. prefact (u u)) (\u. prefact (u u)))] 2
+    ~~> [prefact (prefact ((\u. prefact (u u)) (\u. prefact (u u))))] 2
+    ≡   [(\fact n. (zero? n) 1 (mul n (fact (pred n)))) (prefact ((\u. prefact (u u)) (\u. prefact (u u))))] 2
+    ~~> [\n. (zero? n) 1 (mul n ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] (pred n)))] 2
+    ~~> (zero? 2) 1 (mul 2 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] (pred 2)))
+    ~~> mul 2 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] 1)
+    ...
+    ~~> mul 2 (mul 1 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] 0))
+    ≡   mul 2 (mul 1 ((zero? 0) 1 (mul 1 ([prefact ((\u. prefact (u u)) (\u. prefact (u u)))] (pred 0)))))
+    ~~> mul 2 (mul 1 1)
+    ~~> mul 2 1
+    ~~> 2
+
+The crucial step is the third from the last.  We have our choice of
+either evaluating the test `(zero? 0) 1 ...`, which evaluates to `1`,
+no matter what the ... contains;
+or we can evaluate the `Y` pump, `(\u. prefact (u u)) (\u. prefact (u u))`, to
+produce another copy of `prefact`.  If we postpone evaluating the
+`zero?` test, we'll pump out copy after copy of `prefact`, and never
+realize that we've bottomed out in the recursion.  But if we adopt a
+leftmost/call-by-name/normal-order evaluation strategy, we'll always
+start with the `zero?` predicate, and only produce a fresh copy of
+`prefact` if we are forced to. 
+
+
+## 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. ##
+
+
+A. OK:
+  
+       A(m,n) =
+               | when m == 0 -> n + 1
+               | else when n == 0 -> A(m-1, 1)
+               | else -> A(m-1, A(m,n-1))
+
+       let A = Y (\A m n. (zero? m) (succ n) ((zero? n) (A (pred m) 1) (A (pred m) (A m (pred n)))))
+
+So for instance:
+
+       A 1 2
+       ~~> A 0 (A 1 1)
+       ~~> A 0 (A 0 (A 1 0))
+       ~~> A 0 (A 0 (A 0 1))
+       ~~> A 0 (A 0 2)
+       ~~> A 0 3
+       ~~> 4
+
+`A 1 x` is to `A 0 x` as addition is to the successor function;
+`A 2 x` is to `A 1 x` as multiplication is to addition;
+`A 3 x` is to `A 2 x` as exponentiation is to multiplication---
+so `A 4 x` is to `A 3 x` as hyper-exponentiation is to exponentiation...
+
+## Q. What other questions should I be asking? ##
+
+*    What is it about the variant fixed-point combinators that makes
+     them compatible with a call-by-value evaluation strategy?
+
+*    How do you know that the Ackermann function can't be computed
+     using primitive recursion techniques?
+
+*    What *exactly* is primitive recursion?
+
+*    I hear that `Y` delivers the/a *least* fixed point.  Least
+     according to what ordering?  How do you know it's least?
+     Is leastness important?
diff --git a/topics/week4_more_fixed_points.mdwn b/topics/week4_more_fixed_points.mdwn
deleted file mode 100644 (file)
index ae6653b..0000000
+++ /dev/null
@@ -1,182 +0,0 @@
-#Q: How do you know that every term in the untyped lambda calculus has a fixed point?#
-
-A: That's easy: let `T` be an arbitrary term in the lambda calculus.  If
-`T` has a fixed point, then there exists some `X` such that `X <~~>
-TX` (that's what it means to *have* a fixed point).
-
-<pre><code>let L = \x. T (x x) in
-let X = L L in
-X &equiv; L L &equiv; (\x. T (x x)) L ~~> T (L L) &equiv; T X
-</code></pre>
-
-Please slow down and make sure that you understand what justified each
-of the equalities in the last line.
-
-#Q: How do you know that for any term `T`, `Y T` is a fixed point of `T`?#
-
-A: Note that in the proof given in the previous answer, we chose `T`
-and then set <code>X &equiv; L L &equiv; (\x. T (x x)) (\x. T (x x))</code>.  If we abstract over
-`T`, we get the Y combinator, `\T. (\x. T (x x)) (\x. T (x x))`.  No matter
-what argument `T` we feed `Y`, it returns some `X` that is a fixed point
-of `T`, by the reasoning in the previous answer.
-
-#Q: So if every term has a fixed point, even `Y` has fixed point.#
-
-A: Right:
-
-<pre><code>let Y = \T. (\x. T (x x)) (\x. T (x x)) in
-Y Y
-&equiv;   \T. (\x. T (x x)) (\x. T (x x)) Y
-~~> (\x. Y (x x)) (\x. Y (x x))
-~~> Y ((\x. Y (x x)) (\x. Y (x x)))
-~~> Y (Y ((\x. Y (x x)) (\x. Y (x x))))
-~~> Y (Y (Y (...(Y (Y Y))...)))
-</code></pre>
-
-
-#Q: Ouch!  Stop hurting my brain.#
-
-A: Is that a question?
-
-Let's come at it from the direction of arithmetic.  Recall that we
-claimed that even `succ`---the function that added one to any
-number---had a fixed point.  How could there be an X such that X = X+1?
-That would imply that
-
-    X <~~> succ X <~~> succ (succ X) <~~> succ (succ (succ X)) <~~> succ (... (succ X)...)
-
-In other words, the fixed point of `succ` is a term that is its own
-successor.  Let's just check that `X = succ X`:
-
-<pre><code>let succ = \n s z. s (n s z) in
-let X = (\x. succ (x x)) (\x. succ (x x)) in
-succ X 
-&equiv;   succ ( (\x. succ (x x)) (\x. succ (x x)) ) 
-~~> succ (succ ( (\x. succ (x x)) (\x. succ (x x)) ))
-&equiv;   succ (succ X)
-</code></pre>
-
-You should see the close similarity with `Y Y` here.
-
-
-#Q. So `Y` applied to `succ` returns a number that is not finite!#
-
-A. Yes!  Let's see why it makes sense to think of `Y succ` as a Church
-numeral:
-
-<pre><code>[same definitions]
-succ X
-&equiv;    (\n s z. s (n s z)) X 
-~~>  \s z. s (X s z)
-<~~> succ (\s z. s (X s z)) ; using fixed-point reasoning
-&equiv;    (\n s z. s (n s z)) (\s z. s (X s z))
-~~>  \s z. s ((\s z. s (X s z)) s z)
-~~>  \s z. s (s (X s z))
-</code></pre>
-
-So `succ X` looks like a numeral: it takes two arguments, `s` and `z`,
-and returns a sequence of nested applications of `s`...
-
-You should be able to prove that `add 2 (Y succ) <~~> Y succ`,
-likewise for `mul`, `sub`, `pow`.  What happens if we try `sub (Y
-succ) (Y succ)`?  What would you expect infinity minus infinity to be?
-(Hint: choose your evaluation strategy so that you add two `s`s to the
-first number for every `s` that you add to the second number.)
-
-This is amazing, by the way: we're proving things about a term that
-represents arithmetic infinity.  
-
-It's important to bear in mind the simplest term in question is not
-infinite:
-
-       Y succ = (\f. (\x. f (x x)) (\x. f (x x))) (\n s z. s (n s z))
-
-The way that infinity enters into the picture is that this term has
-no normal form: no matter how many times we perform beta reduction,
-there will always be an opportunity for more beta reduction.  (Lather,
-rinse, repeat!)
-
-
-#Q. That reminds me, what about [[evaluation order]]?#
-
-A. For a recursive function that has a well-behaved base case, such as
-the factorial function, evaluation order is crucial.  In the following
-computation, we will arrive at a normal form.  Watch for the moment at
-which we have to make a choice about which beta reduction to perform
-next: one choice leads to a normal form, the other choice leads to
-endless reduction:
-
-<pre><code>let prefact = \f n. iszero n 1 (mul n (f (pred n))) in
-let fact = Y prefact in
-fact 2
-&equiv;   [(\f. (\x. f (x x)) (\x. f (x x))) prefact] 2
-~~> [(\x. prefact (x x)) (\x. prefact (x x))] 2
-~~> [prefact ((\x. prefact (x x)) (\x. prefact (x x)))] 2
-~~> [prefact (prefact ((\x. prefact (x x)) (\x. prefact (x x))))] 2
-&equiv;   [ (\f n. iszero n 1 (mul n (f (pred n)))) (prefact ((\x. prefact (x x)) (\x. prefact (x x))))] 2
-~~> [\n. iszero n 1 (mul n ([prefact ((\x. prefact (x x)) (\x. prefact (x x)))] (pred n)))] 2
-~~> iszero 2 1 (mul 2 ([prefact ((\x. prefact (x x)) (\x. prefact (x x)))] (pred 2)))
-~~> mul 2 ([prefact ((\x. prefact (x x)) (\x. prefact (x x)))] 1)
-...
-~~> mul 2 (mul 1 ([prefact ((\x. prefact (x x)) (\x. prefact (x x)))] 0))
-&equiv;   mul 2 (mul 1 (iszero 0 1 (mul 1 ([prefact ((\x. prefact (x x)) (\x. prefact (x x)))] (pred 0)))))
-~~> mul 2 (mul 1 1)
-~~> mul 2 1
-~~> 2
-</code></pre>
-
-The crucial step is the third from the last.  We have our choice of
-either evaluating the test `iszero 0 1 ...`, which evaluates to `1`,
-no matter what the ... contains;
-or we can evaluate the `Y` pump, `(\x. prefact (x x)) (\x. prefact (x x))`, to
-produce another copy of `prefact`.  If we postpone evaluting the
-`iszero` test, we'll pump out copy after copy of `prefact`, and never
-realize that we've bottomed out in the recursion.  But if we adopt a
-leftmost/call-by-name/normal-order evaluation strategy, we'll always
-start with the `iszero` predicate, and only produce a fresh copy of
-`prefact` if we are forced to. 
-
-
-#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.#
-
-
-A. OK:
-  
-       A(m,n) =
-               | when m == 0 -> n + 1
-               | else when n == 0 -> A(m-1,1)
-               | else -> A(m-1, A(m,n-1))
-
-       let A = Y (\A m n. iszero m (succ n) (iszero n (A (pred m) 1) (A (pred m) (A m (pred n)))))
-
-So for instance:
-
-       A 1 2
-       ~~> A 0 (A 1 1)
-       ~~> A 0 (A 0 (A 1 0))
-       ~~> A 0 (A 0 (A 0 1))
-       ~~> A 0 (A 0 2)
-       ~~> A 0 3
-       ~~> 4
-
-`A 1 x` is to `A 0 x` as addition is to the successor function;
-`A 2 x` is to `A 1 x` as multiplication is to addition;
-`A 3 x` is to `A 2 x` as exponentiation is to multiplication---
-so `A 4 x` is to `A 3 x` as hyper-exponentiation is to exponentiation...
-
-#Q. What other questions should I be asking?#
-
-*    What is it about the variant fixed-point combinators that makes
-     them compatible with a call-by-value evaluation strategy?
-
-*    How do you know that the Ackermann function can't be computed
-     using primitive recursion techniques?
-
-*    What *exactly* is primitive recursion?
-
-*    I hear that `Y` delivers the *least* fixed point.  Least
-     according to what ordering?  How do you know it's least?
-     Is leastness important?
-
-
-