(no commit message)
[lambda.git] / week2.mdwn
index 9bb13d4..b23d1a7 100644 (file)
@@ -1,23 +1,28 @@
+[[!toc]]
+
+
 Syntactic equality, reduction, convertibility
 =============================================
 
 Syntactic equality, reduction, convertibility
 =============================================
 
-Define T to be `(\x. x y) z`. Then T and `(\x. x y) z` are syntactically equal, and we're counting them as syntactically equal to `(\z. z y) z` as well. We write:
+Define T to be `(\x. x y) z`. Then T and `(\x. x y) z` are syntactically equal, and we're counting them as syntactically equal to `(\z. z y) z` as well, which we will write as:
 
 
-<pre>
-T &equiv; `(\x. x y) z` &equiv; `(\z. z y) z`
-</pre>
+<pre><code>T &equiv; (\x. x y) z &equiv; (\z. z y) z
+</code></pre>
+
+[Fussy note: the justification for counting `(\x. x y) z` as
+equivalent to `(\z. z y) z` is that when a lambda binds a set of
+occurrences, it doesn't matter which variable serves to carry out the
+binding.  Either way, the function does the same thing and means the
+same thing.  Look in the standard treatments for discussions of alpha
+equivalence for more detail.]
 
 This:
 
 
 This:
 
-<pre>
-T ~~> `z y`
-</pre>
+       T ~~> z y
 
 means that T beta-reduces to `z y`. This:
 
 
 means that T beta-reduces to `z y`. This:
 
-<pre>
-M <~~> T
-</pre>
+       M <~~> T
 
 means that M and T are beta-convertible, that is, that there's something they both reduce to in zero or more steps.
 
 
 means that M and T are beta-convertible, that is, that there's something they both reduce to in zero or more steps.
 
@@ -26,675 +31,339 @@ Combinators and Combinatorial Logic
 
 Lambda expressions that have no free variables are known as **combinators**. Here are some common ones:
 
 
 Lambda expressions that have no free variables are known as **combinators**. Here are some common ones:
 
-<pre>
-**I** is defined to be `\x x`<p>
-**K** is defined to be `\x y. x`, That is, it throws away its second argument. So `K x` is a constant function from any (further) argument to `x`. ("K" for "constant".) Compare K to our definition of **true**.<p>
-**get-first** was our function for extracting the first element of an ordered pair: `\fst snd. fst`. Compare this to K and true as well.<p>
-**get-second** was our function for extracting the second element of an ordered pair: `\fst snd. snd`. Compare this to our definition of false.<p>
-**&omega;** is defined to be: `\x. x x`<p>
-</pre>
+>      **I** is defined to be `\x x`
 
 
-It's possible to build a logical system equally powerful as the lambda calculus (and straightforwardly intertranslatable with it) using just combinators, considered as atomic operations. Such a language doesn't have any variables in it: not just no free variables, but no variables at all.
+>      **K** is defined to be `\x y. x`. That is, it throws away its
+           second argument. So `K x` is a constant function from any
+           (further) argument to `x`. ("K" for "constant".) Compare K
+           to our definition of `true`.
 
 
-One can do that with a very spare set of basic combinators. These days the standard base is just three combinators: K and I from above, and also one more, S, which behaves the same as the lambda expression  `\f g x. f x (g x)`. behaves.But it's possible to be even more minimalistic, and get by with only a single combinator. (And there are different single-combinator bases you can choose.)
+>      **get-first** was our function for extracting the first element of an ordered pair: `\fst snd. fst`. Compare this to K and `true` as well.
 
 
-These systems are Turing complete. In other words: every computation we know how to describe can be represented in a logical system consisting of only a single primitive operation!
+>      **get-second** was our function for extracting the second element of an ordered pair: `\fst snd. snd`. Compare this to our definition of `false`.
 
 
-Here's more to read about combinatorial logic:
+>      **B** is defined to be: `\f g x. f (g x)`. (So `B f g` is the composition `\x. f (g x)` of `f` and `g`.)
 
 
-MORE
+>   **C** is defined to be: `\f x y. f y x`. (So `C f` is a function like `f` except it expects its first two arguments in swapped order.)
 
 
-Evaluation strategies
-=====================
+>   **W** is defined to be: `\f x . f x x`. (So `W f` accepts one argument and gives it to `f` twice. What is the meaning of `W multiply`?)
 
 
-In the assignment we asked you to reduce various expressions until it wasn't possible to reduce them any further. For two of those expressions, this was impossible to do. One of them was this:
+>      **&omega;** (that is, lower-case omega) is defined to be: `\x. x x`
 
 
-       (\x. x x) (\x. x x)
+It's possible to build a logical system equally powerful as the lambda calculus (and readily intertranslatable with it) using just combinators, considered as atomic operations. Such a language doesn't have any variables in it: not just no free variables, but no variables at all.
 
 
-As we saw above, each of the halves of this formula are the combinator &omega;; so this can also be written:
+One can do that with a very spare set of basic combinators. These days the standard base is just three combinators: K and I from above, and also one more, **S**, which behaves the same as the lambda expression  `\f g x. f x (g x)`. behaves. But it's possible to be even more minimalistic, and get by with only a single combinator. (And there are different single-combinator bases you can choose.)
 
 
-<pre><code>&omega; &omega;</code></pre>
+There are some well-known linguistic applications of Combinatory
+Logic, due to Anna Szabolcsi, Mark Steedman, and Pauline Jacobson.
+Szabolcsi supposed that the meanings of certain expressions could be
+insightfully expressed in the form of combinators.
 
 
-This compound expression---the self-application of &omega;---is named &Omega;. It has the form of an application of an abstract (&omega;) to an argument (which also happens to be &omega;), so it's a redex and can be reduced. But when we reduce it, we get <code>&omega; &omega;</code> again. So there's no stage at which this expression has been reduced to a point where it can't be reduced any further. In other words, evaluation of this expression "never terminates." (This is standard language, however it has the unfortunate connotation that evaluation is a process or operation that is performed in time. You shouldn't think of it like that. Evaluation of this expression "never terminates" in the way that the decimal expansion of &pi; never terminates. This are static, atemporal facts about their mathematical properties.)
 
 
-There are infinitely many formulas in the lambda calculus that have this same property. &Omega; is the syntactically simplest of them. In our meta-theory, it's common to assign such formula a special value, <code>&perp;</code>, pronounced "bottom." When we get to discussing types, you'll see that this value is counted as belonging to every type. To say that a formula has the bottom value means that the computation that formula represents never terminates and so doesn't evaluate to any orthodox value.
+For instance, Szabolcsi argues that reflexive pronouns are argument
+duplicators.
 
 
-From a "Fregean" or "weak Kleene" perspective, if any component of an expression fails to be evaluable (to an orthodox, computed value), then the whole expression should be unevaluable as well.
+![reflexive](http://lambda.jimpryor.net/szabolcsi-reflexive.jpg)
 
 
-However, in some such cases it seems *we could* sensibly carry on evaluation. For instance, consider:
+Notice that the semantic value of *himself* is exactly `W`.
+The reflexive pronoun in direct object position combines first with the transitive verb (through compositional magic we won't go into here).  The result is an intransitive verb phrase that takes a subject argument, duplicates that argument, and feeds the two copies to the transitive verb meaning.  
 
 
-<pre><code>
-(\x. y) (&omega; &omega;)
-</code></pre>
+Note that `W <~~> S(CI)`:
 
 
-Should we count this as unevaluable, because the reduction of <code>&omega; &omega;</code> never terminates? Or should we count it as evaluating to `y`?
+<pre><code>S(CI) &equiv;
+S((\fxy.fyx)(\x.x)) ~~>
+S(\xy.(\x.x)yx) ~~>
+S(\xy.yx) &equiv;
+(\fgx.fx(gx))(\xy.yx) ~~>
+\gx.(\xy.yx)x(gx) ~~>
+\gx.(gx)x &equiv;
+W</code></pre>
 
 
-This question highlights that there are different choices to make about how evaluation or computation proceeds. It's helpful to think of three questions in this neighborhood:
+Ok, here comes a shift in thinking.  Instead of defining combinators as equivalent to certain lambda terms,
+we can define combinators by what they do.  If we have the I combinator followed by any expression X, 
+I will take that expression as its argument and return that same expression as the result.  In pictures,
 
 
->      Q1. When arguments are complex, as <code>&omega; &omega;</code>, do we reduce them before or after substituting them into the abstracts to which they are arguments?
+    IX ~~> X
 
 
->      Q2. Are we allowed to reduce inside abstracts? That is, can we reduce:
+Thinking of this as a reduction rule, we can perform the following computation
 
 
->              (\x y. x z) (\x. x)
+    II(IX) ~~> IIX ~~> IX ~~> X
 
 
->      only this far:
+The reduction rule for K is also straightforward:
 
 
->              \y. (\x. x) z
+    KXY ~~> X
 
 
->      or can we continue reducing to:
+That is, K throws away its second argument.  The reduction rule for S can be constructed by examining 
+the defining lambda term:
 
 
->              \y. z
+    S = \fgx.fx(gx)
 
 
->      Q3. Are we allowed to "eta-reduce"? That is, can we reduce expressions of the form:
+S takes three arguments, duplicates the third argument, and feeds one copy to the first argument and the second copy to the second argument.  So:
 
 
->              \x. M x
+    SFGX ~~> FX(GX)
 
 
->      where x does not occur free in `M`, to `M`? It should be intuitively clear that `\x. M x` and `M` will behave the same with respect to any arguments they are given. It can also be proven that no other functions can behave differently with respect to them. However, the logical system you get when eta-reduction is added to the proof theory is importantly different from the one where only beta-reduction is permitted.
+If the meaning of a function is nothing more than how it behaves with respect to its arguments, 
+these reduction rules capture the behavior of the combinators S, K, and I completely.
+We can use these rules to compute without resorting to beta reduction.  For instance, we can show how the I combinator is equivalent to a certain crafty combination of Ss and Ks:
 
 
+    SKKX ~~> KX(KX) ~~> X
 
 
-The evaluation strategy which answers Q1 by saying "reduce arguments first" is known as **call-by-value**. The evaluation strategy which answers Q1 by saying "substitute arguments in unreduced" is known as **call-by-name** or **call-by-need** (the difference between these has to do with efficiency, not semantics).
+So the combinator `SKK` is equivalent to the combinator I.
 
 
-When one has a call-by-value strategy that also permits reduction to continue inside unapplied abstracts, that's known as "applicative order" reduction. When one has a call-by-name stratehy that oermits reduction inside abstracts, that's known as "normal order" reduction. Consider an expression of the form:
+Combinatory Logic is what you have when you choose a set of combinators and regulate their behavior with a set of reduction rules.  The most common system uses S, K, and I as defined here.
 
 
-       ((A B) (C D)) (E F)
+###The equivalence of the untyped lambda calculus and combinatory logic###
 
 
-Its syntax has the following tree:
+We've claimed that Combinatory Logic is equivalent to the lambda calculus.  If that's so, then S, K, and I must be enough to accomplish any computational task imaginable.  Actually, S and K must suffice, since we've just seen that we can simulate I using only S and K.  In order to get an intuition about what it takes to be Turing complete, imagine what a text editor does:
+it transforms any arbitrary text into any other arbitrary text.  The way it does this is by deleting, copying, and reordering characters.  We've already seen that K deletes its second argument, so we have deletion covered.  S duplicates and reorders, so we have some reason to hope that S and K are enough to define arbitrary functions.  
 
 
-  ((A B) (C D)) (E F)
-       /     \
-      /       \
-((A B) (C D))  \
-    /\        (E F)
-   /  \        /\
-  /    \      E  F
-(A B) (C D)
- /\    /\
-/  \  /  \
-A   B C   D
+We've already established that the behavior of combinatory terms can be perfectly mimicked by lambda terms: just replace each combinator with its equivalent lambda term, i.e., replace I with `\x.x`, replace K with `\fxy.x`, and replace S with `\fgx.fx(gx)`.  How about the other direction?  Here is a method for converting an arbitrary lambda term into an equivalent Combinatory Logic term using only S, K, and I.  Besides the intrinsic beauty of this mapping, and the importance of what it says about the nature of binding and computation, it is possible to hear an echo of computing with continuations in this conversion strategy (though you would be able to hear these echos until we've covered a considerable portion of the rest of the course).
 
 
-Applicative order evaluation does what's called a "post-order traversal" of the tree: that is, we always go left and down whenever we can, and we process a node only after processing all its children. So `(C D)` gets processed before `((A B) (C D))` does, and `(E F)` gets processed before `((A B) (C D)) (E F)` does.
+Assume that for any lambda term T, [T] is the equivalent combinatory logic term.  The we can define the [.] mapping as follows:
 
 
-Normal order evaluation, on the other hand, will substitute the expresion `(C D)` into the abstract that `(A B)` evaluates to, without first trying to compute what `(C D)` evaluates to. That computation may be done later.
-
-When we have an expression like:
-
-       (\x. y) (C D)
+     1. [a]               a
+     2. [(M N)]           ([M][N])
+     3. [\a.a]            I
+     4. [\a.M]            KM                 assumption: a does not occur free in M
+     5. [\a.(M N)]        S[\a.M][\a.N]
+     6. [\a\b.M]          [\a[\b.M]]
 
 
-the computation of `(C D)` won't ever have to be performed, on a normal order or call by name evaluation strategy. Instead, that reduces directly to `y`. This is so even if `(C D)` is the non-evaluable <code>(&omega; &omega;)</code>!
+It's easy to understand these rules based on what S, K and I do.  The first rule says 
+that variables are mapped to themselves.
+The second rule says that the way to translate an application is to translate the 
+first element and the second element separately.
+The third rule should be obvious.
+The fourth rule should also be fairly self-evident: since what a lambda term such as `\x.y` does it throw away its first argument and return `y`, that's exactly what the combinatory logic translation should do.  And indeed, `Ky` is a function that throws away its argument and returns `y`.
+The fifth rule deals with an abstract whose body is an application: the S combinator takes its next argument (which will fill the role of the original variable a) and copies it, feeding one copy to the translation of \a.M, and the other copy to the translation of \a.N.  Finally, the last rule says that if the body of an abstract is itself an abstract, translate the inner abstract first, and then do the outermost.  (Since the translation of [\b.M] will not have any lambdas in it, we can be sure that we won't end up applying rule 6 again in an infinite loop.)
 
 
-Most programming languages, including Scheme and OCaml, use the call-by-value evaluation strategy. (But they don't permit evaluation to continue inside an unappplied function.) There are techniques for making them model the other sort of behavior.
+[Fussy notes: if the original lambda term has free variables in it, so will the combinatory logic translation.  Feel free to worry about this, though you should be confident that it makes sense.  You should also convince yourself that if the original lambda term contains no free variables---i.e., is a combinator---then the translation will consist only of S, K, and I (plus parentheses).  One other detail: this translation algorithm builds expressions that combine lambdas with combinators.  For instance, the translation of `\x.\y.y` is `[\x[\y.y]] = [\x.I] = KI`.  In that intermediate stage, we have `\x.I`.  It's possible to avoid this, but it takes some careful thought.  See, e.g., Barendregt 1984, page 156.]
 
 
-Some functional programming languages, such as Haskell, use the call-by-name evaluation strategy. Each has pros and cons.
+Here's an example of the translation:
 
 
-The lambda calculus can be evaluated either way. You have to decide what the rules shall be.
+    [\x\y.yx] = [\x[\y.yx]] = [\x.S[\y.y][\y.x]] = [\x.(SI)(Kx)] = S[\x.SI][\x.Kx] = S(K(SI))(S[\x.K][\x.x]) = S(K(SI))(S(KK)I)
 
 
-One important advantage of the normal-order evaluation strategy is that it can compute an orthodox value for:
+We can test this translation by seeing if it behaves like the original lambda term does.
+The orginal lambda term lifts its first argument (think of it as reversing the order of its two arguments):
 
 
-<pre><code>
-(\x. y) (&omega; &omega;)
-</code></pre>
+   S(K(SI))(S(KK)I) X Y =
+   (K(SI))X ((S(KK)I) X) Y = 
+   SI ((KK)X (IX)) Y = 
+   SI (KX) Y =
+   IY (KX)Y =
+   Y X
 
 
-Indeed, it's provable that if there's any reduction path that delivers a value for an expression, the normal-order evalutation strategy will terminate with that value.
+Viola: the combinator takes any X and Y as arguments, and returns Y applied to X.
 
 
-An expression is said to be in **normal form** when it's not possible to perform any more reductions. (EVEN INSIDE ABSTRACTS?) There's a sense in which you can't get anything more out of <code>&omega; &omega;</code>, but it's not in normal form because it still has the form of a redex.
+Back to linguistic applications: one consequence of the equivalence between the lambda calculus and combinatory 
+logic is that anything that can be done by binding variables can just as well be done with combinators.
+This has given rise to a style of semantic analysis called Variable Free Semantics (in addition to 
+Szabolcsi's papers, see, for instance,
+Pauline Jacobson's 1999 *Linguistics and Philosophy* paper, `Towards a variable-free Semantics').  
+Somewhat ironically, reading strings of combinators is so difficult that most practitioners of variable-free semantics 
+express there meanings using the lambda-calculus rather than combinatory logic; perhaps they should call their
+enterprise Free Variable Free Semantics.
 
 
-A computational system is said to be **confluent**, or to have the **Church-Rosser** or **diamond** property, if, whenever there are multiple possible evaluation paths, those that terminate always terminate in the same value. In such a system, the choice of which sub-expressions to evaluate first will only matter if some of them but not others might lead down a non-terminating path.
+A philosophical application: Quine went through a phase in which he developed a variable free logic.
 
 
-The untyped lambda calculus is confluent. So long as a computation terminates, it always terminates in the same way. It doesn't matter which order the sub-expressions are evaluated in.
+  Quine, Willard. 1960.  Variables explained away.  {\it Proceedings of                                                                                                                                
+  the American Philosophical Society}.  Volume 104: 343--347.  Also in
+  W.~V.~Quine.  1960. {\it Selected Logical Papers}.  Random House: New
+  York.  227--235.
 
 
-A computational system is said to be **strongly normalizing** if every permitted evaluation path is guaranteed to terminate. The untyped lambda calculus is not strongly normalizing: <code>&omega; &omega;</code> doesn't terminate by any evaluation path; and <code>(\x. y) (&omega; &omega;)</code> terminates only by some evaluation paths but not by others.
+The reason this was important to Quine is similar to the worries that Jim was talking about
+in the first class in which using non-referring expressions such as Santa Clause might commit 
+one to believing in non-existant things.  Quine's slogan was that `to be is to be the value of a variable'.
+What this was supposed to mean is that if and only if an object could serve as the value of some variable, we 
+are committed to recognizing the existence of that object in our ontology.
+Obviously, if there ARE no variables, this slogan has to be rethought.
 
 
-But the untyped lambda calculus enjoys some compensation for this weakness. It's Turing complete! It can represent any computation we know how to describe. (That's the cash value of being Turing complete, not the rigorous definition. We don't know how to rigorously define "any computation we know how to describe." There is however a rigorous definition for being Turing complete.) And in fact, it's been proven that you can't havee both. If a language is Turing complete, it cannot be strongly normalizing.
+Quine did not appear to appreciate that Shoenfinkel had already invented combinatory logic, though
+he later wrote an introduction to Shoenfinkel's key paper reprinted in Jean
+van Heijenoort (ed) 1967 *From Frege to Goedel,                                                                                                                               
+  a source book in mathematical logic, 1879--1931*.
+Cresswell has also developed a variable-free approach of some philosophical and linguistic interest
+in two books in the 1990's.
 
 
-A computational system is said to be **weakly normalizing** if there's always guaranteed to be *at least one* evaluation path that terminates. The untyped lambda calculus is not weakly normalizing either, as we've seen.
+A final linguistic application: Steedman's Combinatory Categorial Grammar, where the "Combinatory" is 
+from combinatory logic (see especially his 2000 book, *The Syntactic Process*).  Steedman attempts to build
+a syntax/semantics interface using a small number of combinators, including T = \xy.yx, B = \fxy.f(xy),
+and our friend S.  Steedman used Smullyan's fanciful bird 
+names for the combinators, Thrush, Bluebird, and Starling.
 
 
-The *typed* lambda calculus that linguists traditionally work with, on the other hand, is strongly normalizing. (And as a result, is not Turning complete.) It has expressive power that the untyped lambda calculus lacks, but it is also unable to represent some (terminating!) computations that the untyped lambda calculus can represent.
+Many of these combinatory logics, in particular, the SKI system, 
+are Turing complete. In other words: every computation we know how to describe can be represented in a logical system consisting of only a single primitive operation!
 
 
-Other more-powerful type systems we'll look at in the course will also fail to be Turing complete, though they will turn out to be pretty powerful.
+Here's more to read about combinatorial logic.
+Surely the most entertaining exposition is Smullyan's [[!wikipedia To_Mock_a_Mockingbird]].
+Other sources include
 
 
+*      [[!wikipedia Combinatory logic]] at Wikipedia
+*      [Combinatory logic](http://plato.stanford.edu/entries/logic-combinatory/) at the Stanford Encyclopedia of Philosophy
+*      [[!wikipedia SKI combinatory calculus]]
+*      [[!wikipedia B,C,K,W system]]
+*      [Chris Barker's Iota and Jot](http://semarch.linguistics.fas.nyu.edu/barker/Iota/)
+*      Jeroen Fokker, "The Systematic Construction of a One-combinator Basis for Lambda-Terms" <cite>Formal Aspects of Computing</cite> 4 (1992), pp. 776-780.
+<http://people.cs.uu.nl/jeroen/article/combinat/combinat.ps>
 
 
 
 
+Evaluation Strategies and Normalization
+=======================================
 
 
+In the assignment we asked you to reduce various expressions until it wasn't possible to reduce them any further. For two of those expressions, this was impossible to do. One of them was this:
 
 
+       (\x. x x) (\x. x x)
 
 
-K
-omega
-true/get-first/K
-false/get-second
-make-pair
-S,B,C,W/dup,Omega
-
-(( combinatorial logic ))
-
-
-
-
-We'll write that like this:
-
-       ((\x (y x)) z) ~~> (y z)
+As we saw above, each of the halves of this formula are the combinator <code>&omega;</code>; so this can also be written:
 
 
-Different authors use different notations. Some authors use the term "contraction" for a single reduction step, and reserve the term "reduction" for the reflexive transitive closure of that, that is, for zero or more reduction steps. Informally, it seems easiest to us to say "reduction" for one or more reduction steps. So when we write:
+<pre><code>&omega; &omega;</code></pre>
 
 
-       M ~~> N
+This compound expression---the self-application of <code>&omega;</code>---is named &Omega;. It has the form of an application of an abstract (<code>&omega;</code>) to an argument (which also happens to be <code>&omega;</code>), so it's a redex and can be reduced. But when we reduce it, we get <code>&omega; &omega;</code> again. So there's no stage at which this expression has been reduced to a point where it can't be reduced any further. In other words, evaluation of this expression "never terminates." (This is the standard language, however it has the unfortunate connotation that evaluation is a process or operation that is performed in time. You shouldn't think of it like that. Evaluation of this expression "never terminates" in the way that the decimal expansion of &pi; never terminates. These are static, atemporal facts about their mathematical properties.)
 
 
-We'll mean that you can get from M to N by one or more reduction steps. Hankin uses the symbol <code><big><big>&rarr;</big></big></code> for one-step contraction, and the symbol <code><big><big>&#8608;</big></big></code> for zero-or-more step reduction. Hindley and Seldin use <code><big><big><big>&#8883;</big></big></big><sub>1</sub></code> and <code><big><big><big>&#8883;</big></big></big></code>.
+There are infinitely many formulas in the lambda calculus that have this same property. &Omega; is the syntactically simplest of them. In our meta-theory, it's common to assign such formulas a special value, <big><code>&perp;</code></big>, pronounced "bottom." When we get to discussing types, you'll see that this value is counted as belonging to every type. To say that a formula has the bottom value means that the computation that formula represents never terminates and so doesn't evaluate to any orthodox, computed value.
 
 
-When M and N are such that there's some P that M reduces to by zero or more steps, and that N also reduces to by zero or more steps, then we say that M and N are **beta-convertible**. We'll write that like this:
+From a "Fregean" or "weak Kleene" perspective, if any component of an expression fails to be evaluable (to an orthodox, computed value), then the whole expression should be unevaluable as well.
 
 
-       M <~~> N
+However, in some such cases it seems *we could* sensibly carry on evaluation. For instance, consider:
 
 
-This is what plays the role of equality in the lambda calculus. Hankin uses the symbol `=` for this. So too do Hindley and Seldin. Personally, I keep confusing that with the relation to be described next, so let's use this notation instead. Note that `M <~~> N` doesn't mean that each of `M` and `N` are reducible to each other; that only holds when `M` and `N` are the same expression. (Or, with our convention of only saying "reducible" for one or more reduction steps, it never holds.)
+<pre><code>
+(\x. y) (&omega; &omega;)
+</code></pre>
 
 
-In the metatheory, it's also sometimes useful to talk about formulas that are syntactically equivalent *before any reductions take place*. Hankin uses the symbol <code>&equiv;</code> for this. So too do Hindley and Seldin. We'll use that too, and will avoid using `=` when discussing the metatheory. Instead we'll use `<~~>` as we said above. When we want to introduce a stipulative definition, we'll write it out longhand, as in:
+Should we count this as unevaluable, because the reduction of <code>(&omega; &omega;)</code> never terminates? Or should we count it as evaluating to `y`?
 
 
+This question highlights that there are different choices to make about how evaluation or computation proceeds. It's helpful to think of three questions in this neighborhood:
 
 
-combinators as lambda expressions
-combinatorial logic
+>      Q1. When arguments are complex, as <code>(&omega; &omega;)</code> is, do we reduce them before substituting them into the abstracts to which they are arguments, or later?
 
 
-tuples = possibly type-heterogenous ordered collections, different length -> different type
-lists = type-homogenous ordered collections, lists of different lengths >=0 can be of same type
+>      Q2. Are we allowed to reduce inside abstracts? That is, can we reduce:
 
 
+>              (\x y. x z) (\x. x)
 
 
+>      only this far:
 
 
+>              \y. (\x. x) z
 
 
-1.     Substitution; using alpha-conversion and other strategies
-1.     Conversion versus reduction
+>      or can we continue reducing to:
 
 
-1.     Different evaluation strategies (call by name, call by value, etc.)
-1.     Strongly normalizing vs weakly normalizing vs non-normalizing; Church-Rosser Theorem(s)
-1.     Lambda calculus compared to combinatorial logic<p>
-1.     Church-like encodings of numbers, defining addition and multiplication
-1.     Defining the predecessor function; alternate encodings for the numbers
-1.     Homogeneous sequences or "lists"; how they differ from pairs, triples, etc.
-1.     Representing lists as pairs
-1.     Representing lists as folds
-1.     Typical higher-order functions: map, filter, fold<p>
-1.     Recursion exploiting the fold-like representation of numbers and lists ([[!wikipedia Deforestation (computer science)]], [[!wikipedia Zipper (data structure)]])
-1.     General recursion using omega
+>              \y. z
 
 
-1.     Eta reduction and "extensionality" ??
-Undecidability of equivalence
+>      Q3. Are we allowed to "eta-reduce"? That is, can we reduce expressions of the form:
 
 
-There is no algorithm which takes as input two lambda expressions and outputs TRUE or FALSE depending on whether or not the two expressions are equivalent. This was historically the first problem for which undecidability could be proven. As is common for a proof of undecidability, the proof shows that no computable function can decide the equivalence. Church's thesis is then invoked to show that no algorithm can do so.
+>              \x. M x
 
 
-Church's proof first reduces the problem to determining whether a given lambda expression has a normal form. A normal form is an equivalent expression which cannot be reduced any further under the rules imposed by the form. Then he assumes that this predicate is computable, and can hence be expressed in lambda calculus. Building on earlier work by Kleene and constructing a Gödel numbering for lambda expressions, he constructs a lambda expression e which closely follows the proof of Gödel's first incompleteness theorem. If e is applied to its own Gödel number, a contradiction results.
+>      where x does not occur free in `M`, to `M`?
 
 
+With regard to Q3, it should be intuitively clear that `\x. M x` and `M` will behave the same with respect to any arguments they are given. It can also be proven that no other functions can behave differently with respect to them. However, the logical system you get when eta-reduction is added to the proof theory is importantly different from the one where only beta-reduction is permitted.
 
 
+MORE on extensionality
 
 
-1.     The Y combinator(s); more on evaluation strategies<p>
-1.     Introducing the notion of a "continuation", which technique we'll now already have used a few times
+If we answer Q2 by permitting reduction inside abstracts, and we also permit eta-reduction, then where neither `y` nor `z` occur in M, this:
 
 
+       \x y z. M y z
 
 
+will eta-reduce by two steps to:
 
 
-alpha-convertible
+       \x. M
 
 
-syntactic equality `===`
-contract/reduce/`~~>`
-convertible `<~~>`
+The evaluation strategy which answers Q1 by saying "reduce arguments first" is known as **call-by-value**. The evaluation strategy which answers Q1 by saying "substitute arguments in unreduced" is known as **call-by-name** or **call-by-need** (the difference between these has to do with efficiency, not semantics).
 
 
-normalizing
-       weakly normalizable
-       strongly normalizable
-       "normal order" reduction vs "applicative order"
-       eval strategy choices
+When one has a call-by-value strategy that also permits reduction to continue inside unapplied abstracts, that's known as "applicative order" reduction. When one has a call-by-name strategy that permits reduction inside abstracts, that's known as "normal order" reduction. Consider an expression of the form:
 
 
-                               Reduction strategies For more details on this topic, see Evaluation
-               strategy.
+       ((A B) (C D)) (E F)
 
 
-                               Whether a term is normalising or not, and how much work needs to be
-               done in normalising it if it is, depends to a large extent on the reduction
-               strategy used. The distinction between reduction strategies relates to the
-               distinction in functional programming languages between eager evaluation and
-               lazy evaluation.
+Its syntax has the following tree:
 
 
-                               Full beta reductions Any redex can be reduced at any time. This means
-               essentially the lack of any particular reduction strategy—with regard to
-               reducibility, "all bets are off". Applicative order The leftmost, innermost
-               redex is always reduced first. Intuitively this means a function's arguments
-               are always reduced before the function itself. Applicative order always
-               attempts to apply functions to normal forms, even when this is not possible.
-               Most programming languages (including Lisp, ML and imperative languages like C
-               and Java) are described as "strict", meaning that functions applied to
-               non-normalising arguments are non-normalising. This is done essentially using
-               applicative order, call by value reduction (see below), but usually called
-               "eager evaluation". Normal order The leftmost, outermost redex is always
-               reduced first. That is, whenever possible the arguments are substituted into
-               the body of an abstraction before the arguments are reduced. Call by name As
-               normal order, but no reductions are performed inside abstractions. For example
-               Î»x.(λx.x)x is in normal form according to this strategy, although it contains
-               the redex (λx.x)x. Call by value Only the outermost redexes are reduced: a
-               redex is reduced only when its right hand side has reduced to a value (variable
-               or lambda abstraction). Call by need As normal order, but function applications
-               that would duplicate terms instead name the argument, which is then reduced
-               only "when it is needed". Called in practical contexts "lazy evaluation". In
-               implementations this "name" takes the form of a pointer, with the redex
-               represented by a thunk.
-
-                               Applicative order is not a normalising strategy. The usual
-               counterexample is as follows: define Î© = Ď‰Ď‰ where Ď‰ = Î»x.xx. This entire
-               expression contains only one redex, namely the whole expression; its reduct is
-               again Î©. Since this is the only available reduction, Î© has no normal form
-               (under any evaluation strategy). Using applicative order, the expression KIΩ =
-               (λxy.x) (λx.x)Ω is reduced by first reducing Î© to normal form (since it is the
-               leftmost redex), but since Î© has no normal form, applicative order fails to
-               find a normal form for KIΩ.
-
-                               In contrast, normal order is so called because it always finds a
-               normalising reduction if one exists. In the above example, KIΩ reduces under
-               normal order to I, a normal form. A drawback is that redexes in the arguments
-               may be copied, resulting in duplicated computation (for example, (λx.xx)
-               ((λx.x)y) reduces to ((λx.x)y) ((λx.x)y) using this strategy; now there are two
-               redexes, so full evaluation needs two more steps, but if the argument had been
-               reduced first, there would now be none).
-
-                               The positive tradeoff of using applicative order is that it does not
-               cause unnecessary computation if all arguments are used, because it never
-               substitutes arguments containing redexes and hence never needs to copy them
-               (which would duplicate work). In the above example, in applicative order
-               (λx.xx) ((λx.x)y) reduces first to (λx.xx)y and then to the normal order yy,
-               taking two steps instead of three.
-
-                               Most purely functional programming languages (notably Miranda and its
-               descendents, including Haskell), and the proof languages of theorem provers,
-               use lazy evaluation, which is essentially the same as call by need. This is
-               like normal order reduction, but call by need manages to avoid the duplication
-               of work inherent in normal order reduction using sharing. In the example given
-               above, (λx.xx) ((λx.x)y) reduces to ((λx.x)y) ((λx.x)y), which has two redexes,
-               but in call by need they are represented using the same object rather than
-               copied, so when one is reduced the other is too.
-
-
-
-
-               Strict evaluation Main article: strict evaluation
-
-               In strict evaluation, the arguments to a function are always evaluated
-               completely before the function is applied.
-
-               Under Church encoding, eager evaluation of operators maps to strict evaluation
-               of functions; for this reason, strict evaluation is sometimes called "eager".
-               Most existing programming languages use strict evaluation for functions. [edit]
-               Applicative order
-
-               Applicative order (or leftmost innermost) evaluation refers to an evaluation
-               strategy in which the arguments of a function are evaluated from left to right
-               in a post-order traversal of reducible expressions (redexes). Unlike
-               call-by-value, applicative order evaluation reduces terms within a function
-               body as much as possible before the function is applied. [edit] Call by value
-
-               Call-by-value evaluation (also referred to as pass-by-value) is the most common
-               evaluation strategy, used in languages as different as C and Scheme. In
-               call-by-value, the argument expression is evaluated, and the resulting value is
-               bound to the corresponding variable in the function (frequently by copying the
-               value into a new memory region). If the function or procedure is able to assign
-               values to its parameters, only its local copy is assigned â€” that is, anything
-               passed into a function call is unchanged in the caller's scope when the
-               function returns.
-
-               Call-by-value is not a single evaluation strategy, but rather the family of
-               evaluation strategies in which a function's argument is evaluated before being
-               passed to the function. While many programming languages (such as Eiffel and
-               Java) that use call-by-value evaluate function arguments left-to-right, some
-               evaluate functions and their arguments right-to-left, and others (such as
-               Scheme, OCaml and C) leave the order unspecified (though they generally require
-               implementations to be consistent).
-
-               In some cases, the term "call-by-value" is problematic, as the value which is
-               passed is not the value of the variable as understood by the ordinary meaning
-               of value, but an implementation-specific reference to the value. The
-               description "call-by-value where the value is a reference" is common (but
-               should not be understood as being call-by-reference); another term is
-               call-by-sharing. Thus the behaviour of call-by-value Java or Visual Basic and
-               call-by-value C or Pascal are significantly different: in C or Pascal, calling
-               a function with a large structure as an argument will cause the entire
-               structure to be copied, potentially causing serious performance degradation,
-               and mutations to the structure are invisible to the caller. However, in Java or
-               Visual Basic only the reference to the structure is copied, which is fast, and
-               mutations to the structure are visible to the caller. [edit] Call by reference
-
-               In call-by-reference evaluation (also referred to as pass-by-reference), a
-               function receives an implicit reference to the argument, rather than a copy of
-               its value. This typically means that the function can modify the argument-
-               something that will be seen by its caller. Call-by-reference therefore has the
-               advantage of greater time- and space-efficiency (since arguments do not need to
-               be copied), as well as the potential for greater communication between a
-               function and its caller (since the function can return information using its
-               reference arguments), but the disadvantage that a function must often take
-               special steps to "protect" values it wishes to pass to other functions.
-
-               Many languages support call-by-reference in some form or another, but
-               comparatively few use it as a default; Perl and Visual Basic are two that do,
-               though Visual Basic also offers a special syntax for call-by-value parameters.
-               A few languages, such as C++ and REALbasic, default to call-by-value, but offer
-               special syntax for call-by-reference parameters. C++ additionally offers
-               call-by-reference-to-const. In purely functional languages there is typically
-               no semantic difference between the two strategies (since their data structures
-               are immutable, so there is no possibility for a function to modify any of its
-               arguments), so they are typically described as call-by-value even though
-               implementations frequently use call-by-reference internally for the efficiency
-               benefits.
-
-               Even among languages that don't exactly support call-by-reference, many,
-               including C and ML, support explicit references (objects that refer to other
-               objects), such as pointers (objects representing the memory addresses of other
-               objects), and these can be used to effect or simulate call-by-reference (but
-               with the complication that a function's caller must explicitly generate the
-               reference to supply as an argument). [edit] Call by sharing
-
-               Also known as "call by object" or "call by object-sharing" is an evaluation
-               strategy first named by Barbara Liskov et al. for the language CLU in 1974[1].
-               It is used by languages such as Python[2], Iota, Java (for object
-               references)[3], Ruby, Scheme, OCaml, AppleScript, and many other languages.
-               However, the term "call by sharing" is not in common use; the terminology is
-               inconsistent across different sources. For example, in the Java community, they
-               say that Java is pass-by-value, whereas in the Ruby community, they say that
-               Ruby is pass-by-reference, even though the two languages exhibit the same
-               semantics. Call-by-sharing implies that values in the language are based on
-               objects rather than primitive types.
-
-               The semantics of call-by-sharing differ from call-by-reference in that
-               assignments to function arguments within the function aren't visible to the
-               caller (unlike by-reference semantics)[citation needed]. However since the
-               function has access to the same object as the caller (no copy is made),
-               mutations to those objects within the function are visible to the caller, which
-               differs from call-by-value semantics.
-
-               Although this term has widespread usage in the Python community, identical
-               semantics in other languages such as Java and Visual Basic are often described
-               as call-by-value, where the value is implied to be a reference to the object.
-               [edit] Call by copy-restore
-
-               Call-by-copy-restore, call-by-value-result or call-by-value-return (as termed
-               in the Fortran community) is a special case of call-by-reference where the
-               provided reference is unique to the caller. If a parameter to a function call
-               is a reference that might be accessible by another thread of execution, its
-               contents are copied to a new reference that is not; when the function call
-               returns, the updated contents of this new reference are copied back to the
-               original reference ("restored").
-
-               The semantics of call-by-copy-restore also differ from those of
-               call-by-reference where two or more function arguments alias one another; that
-               is, point to the same variable in the caller's environment. Under
-               call-by-reference, writing to one will affect the other; call-by-copy-restore
-               avoids this by giving the function distinct copies, but leaves the result in
-               the caller's environment undefined (depending on which of the aliased arguments
-               is copied back first).
-
-               When the reference is passed to the callee uninitialized, this evaluation
-               strategy may be called call-by-result. [edit] Partial evaluation Main article:
-               Partial evaluation
-
-               In partial evaluation, evaluation may continue into the body of a function that
-               has not been applied. Any sub-expressions that do not contain unbound variables
-               are evaluated, and function applications whose argument values are known may be
-               reduced. In the presence of side-effects, complete partial evaluation may
-               produce unintended results; for this reason, systems that support partial
-               evaluation tend to do so only for "pure" expressions (expressions without
-               side-effects) within functions. [edit] Non-strict evaluation
-
-               In non-strict evaluation, arguments to a function are not evaluated unless they
-               are actually used in the evaluation of the function body.
-
-               Under Church encoding, lazy evaluation of operators maps to non-strict
-               evaluation of functions; for this reason, non-strict evaluation is often
-               referred to as "lazy". Boolean expressions in many languages use lazy
-               evaluation; in this context it is often called short circuiting. Conditional
-               expressions also usually use lazy evaluation, albeit for different reasons.
-               [edit] Normal order
-
-               Normal-order (or leftmost outermost) evaluation is the evaluation strategy
-               where the outermost redex is always reduced, applying functions before
-               evaluating function arguments. It differs from call-by-name in that
-               call-by-name does not evaluate inside the body of an unapplied
-               function[clarification needed]. [edit] Call by name
-
-               In call-by-name evaluation, the arguments to functions are not evaluated at all
-               â€” rather, function arguments are substituted directly into the function body
-               using capture-avoiding substitution. If the argument is not used in the
-               evaluation of the function, it is never evaluated; if the argument is used
-               several times, it is re-evaluated each time. (See Jensen's Device.)
-
-               Call-by-name evaluation can be preferable over call-by-value evaluation because
-               call-by-name evaluation always yields a value when a value exists, whereas
-               call-by-value may not terminate if the function's argument is a non-terminating
-               computation that is not needed to evaluate the function. Opponents of
-               call-by-name claim that it is significantly slower when the function argument
-               is used, and that in practice this is almost always the case as a mechanism
-               such as a thunk is needed. [edit] Call by need
-
-               Call-by-need is a memoized version of call-by-name where, if the function
-               argument is evaluated, that value is stored for subsequent uses. In a "pure"
-               (effect-free) setting, this produces the same results as call-by-name; when the
-               function argument is used two or more times, call-by-need is almost always
-               faster.
-
-               Because evaluation of expressions may happen arbitrarily far into a
-               computation, languages using call-by-need generally do not support
-               computational effects (such as mutation) except through the use of monads and
-               uniqueness types. This eliminates any unexpected behavior from variables whose
-               values change prior to their delayed evaluation.
-
-               This is a kind of Lazy evaluation.
-
-               Haskell is the most well-known language that uses call-by-need evaluation.
-
-               R also uses a form of call-by-need. [edit] Call by macro expansion
-
-               Call-by-macro-expansion is similar to call-by-name, but uses textual
-               substitution rather than capture-avoiding substitution. With uncautious use,
-               macro substitution may result in variable capture and lead to undesired
-               behavior. Hygienic macros avoid this problem by checking for and replacing
-               shadowed variables that are not parameters.
-
-
-
-
-               Eager evaluation or greedy evaluation is the evaluation strategy in most
-               traditional programming languages.
-
-               In eager evaluation an expression is evaluated as soon as it gets bound to a
-               variable. The term is typically used to contrast lazy evaluation, where
-               expressions are only evaluated when evaluating a dependent expression. Eager
-               evaluation is almost exclusively used in imperative programming languages where
-               the order of execution is implicitly defined by the source code organization.
-
-               One advantage of eager evaluation is that it eliminates the need to track and
-               schedule the evaluation of expressions. It also allows the programmer to
-               dictate the order of execution, making it easier to determine when
-               sub-expressions (including functions) within the expression will be evaluated,
-               as these sub-expressions may have side-effects that will affect the evaluation
-               of other expressions.
-
-               A disadvantage of eager evaluation is that it forces the evaluation of
-               expressions that may not be necessary at run time, or it may delay the
-               evaluation of expressions that have a more immediate need. It also forces the
-               programmer to organize the source code for optimal order of execution.
-
-               Note that many modern compilers are capable of scheduling execution to better
-               optimize processor resources and can often eliminate unnecessary expressions
-               from being executed entirely. Therefore, the notions of purely eager or purely
-               lazy evaluation may not be applicable in practice.
-
-
-
-               In computer programming, lazy evaluation is the technique of delaying a
-               computation until the result is required.
-
-               The benefits of lazy evaluation include: performance increases due to avoiding
-               unnecessary calculations, avoiding error conditions in the evaluation of
-               compound expressions, the capability of constructing potentially infinite data
-               structures, and the capability of defining control structures as abstractions
-               instead of as primitives.
-
-               Languages that use lazy actions can be further subdivided into those that use a
-               call-by-name evaluation strategy and those that use call-by-need. Most
-               realistic lazy languages, such as Haskell, use call-by-need for performance
-               reasons, but theoretical presentations of lazy evaluation often use
-               call-by-name for simplicity.
-
-               The opposite of lazy actions is eager evaluation, sometimes known as strict
-               evaluation. Eager evaluation is the evaluation behavior used in most
-               programming languages.
-
-               Lazy evaluation refers to how expressions are evaluated when they are passed as
-               arguments to functions and entails the following three points:[1]
-
-                  1. The expression is only evaluated if the result is required by the calling
-               function, called delayed evaluation.[2] 2. The expression is only evaluated to
-               the extent that is required by the calling function, called short-circuit
-               evaluation. 3. The expression is never evaluated more than once, called
-               applicative-order evaluation.[3]
-
-               Contents [hide]
-
-                       * 1 Delayed evaluation
-                                 o 1.1 Control structures
-                       * 2 Controlling eagerness in lazy languages 3 Other uses 4 See also 5
-                       * References 6 External links
-
-               [edit] Delayed evaluation
-
-               Delayed evaluation is used particularly in functional languages. When using
-               delayed evaluation, an expression is not evaluated as soon as it gets bound to
-               a variable, but when the evaluator is forced to produce the expression's value.
-               That is, a statement such as x:=expression; (i.e. the assignment of the result
-               of an expression to a variable) clearly calls for the expression to be
-               evaluated and the result placed in x, but what actually is in x is irrelevant
-               until there is a need for its value via a reference to x in some later
-               expression whose evaluation could itself be deferred, though eventually the
-               rapidly-growing tree of dependencies would be pruned in order to produce some
-               symbol rather than another for the outside world to see.
+         ((A B) (C D)) (E F)
+                  /     \
+                 /       \
+       ((A B) (C D))  \
+               /\        (E F)
+          /  \        /\
+         /    \      E  F
+       (A B) (C D)
+        /\    /\
+       /  \  /  \
+       A   B C   D
 
 
-               Some programming languages delay evaluation of expressions by default, and some
-               others provide functions or special syntax to delay evaluation. In Miranda and
-               Haskell, evaluation of function arguments is delayed by default. In many other
-               languages, evaluation can be delayed by explicitly suspending the computation
-               using special syntax (as with Scheme's "delay" and "force" and OCaml's "lazy"
-               and "Lazy.force") or, more generally, by wrapping the expression in a thunk.
-               The object representing such an explicitly delayed evaluation is called a
-               future or promise. Perl 6 uses lazy evaluation of lists, so one can assign
-               infinite lists to variables and use them as arguments to functions, but unlike
-               Haskell and Miranda, Perl 6 doesn't use lazy evaluation of arithmetic operators
-               and functions by default.
+Applicative order evaluation does what's called a "post-order traversal" of the tree: that is, we always go down when we can, first to the left, and we process a node only after processing all its children. So `(C D)` gets processed before `((A B) (C D))` does, and `(E F)` gets processed before `((A B) (C D)) (E F)` does.
 
 
-               Delayed evaluation has the advantage of being able to create calculable
-               infinite lists without infinite loops or size matters interfering in
-               computation. For example, one could create a function that creates an infinite
-               list (often called a stream) of Fibonacci numbers. The calculation of the n-th
-               Fibonacci number would be merely the extraction of that element from the
-               infinite list, forcing the evaluation of only the first n members of the list.
+Normal order evaluation, on the other hand, will substitute the expresion `(C D)` into the abstract that `(A B)` evaluates to, without first trying to compute what `(C D)` evaluates to. That computation may be done later.
 
 
-               For example, in Haskell, the list of all Fibonacci numbers can be written as
+With normal-order evaluation (or call-by-name more generally), if we have an expression like:
 
 
-                fibs = 0 : 1 : zipWith (+) fibs (tail fibs)
+       (\x. y) (C D)
 
 
-               In Haskell syntax, ":" prepends an element to a list, tail returns a list
-               without its first element, and zipWith uses a specified function (in this case
-               addition) to combine corresponding elements of two lists to produce a third.
+the computation of `(C D)` won't ever have to be performed. Instead, `(\x. y) (C D)` reduces directly to `y`. This is so even if `(C D)` is the non-evaluable <code>(&omega; &omega;)</code>!
 
 
-               Provided the programmer is careful, only the values that are required to
-               produce a particular result are evaluated. However, certain calculations may
-               result in the program attempting to evaluate an infinite number of elements;
-               for example, requesting the length of the list or trying to sum the elements of
-               the list with a fold operation would result in the program either failing to
-               terminate or running out of memory. [edit] Control structures
+Call-by-name evaluation is often called "lazy." Call-by-value evaluation is also often called "eager" or "strict". Some authors say these terms all have subtly different technical meanings, but I haven't been able to figure out what it is. Perhaps the technical meaning of "strict" is what I above called the "Fregean" or "weak Kleene" perspective: if any argument of a function is non-evaluable or non-normalizing, so too is the application of the function to that argument.
 
 
-               Even in most eager languages if statements evaluate in a lazy fashion.
 
 
-               if a then b else c
+Most programming languages, including Scheme and OCaml, use the call-by-value evaluation strategy. (But they don't permit evaluation to continue inside an unappplied function.) There are techniques for making them model call-by-name evaluation, when necessary. But by default, arguments will always be evaluated before being bound to the parameters (the `\x`s) of a function.
 
 
-               evaluates (a), then if and only if (a) evaluates to true does it evaluate (b),
-               otherwise it evaluates (c). That is, either (b) or (c) will not be evaluated.
-               Conversely, in an eager language the expected behavior is that
+For languages like Scheme that permit functions to take more than one argument at a time, a further question arises: whether the multiple arguments are evaluated left-to-right, or right-to-left, or nothing is guaranteed about what order they are evaluated in. Different languages make different choices about this.
 
 
-               define f(x,y) = 2*x set k = f(e,5)
+Some functional programming languages, such as Haskell, use the call-by-name evaluation strategy.
 
 
-               will still evaluate (e) and (f) when computing (k). However, user-defined
-               control structures depend on exact syntax, so for example
+The lambda calculus can be evaluated either way. You have to decide what the rules shall be.
 
 
-               define g(a,b,c) = if a then b else c l = g(h,i,j)
+As we'll see in several weeks, there are techniques for *forcing* call-by-value evaluation of a computation, and also techniques for forcing call-by-name evaluation. If you liked, you could even have a nested hierarchy, where blocks at each level were forced to be evaluated in alternating ways.
 
 
-               (i) and (j) would both be evaluated in an eager language. While in
+Call-by-value and call-by-name have different pros and cons.
 
 
-               l' = if h then i else j
+One important advantage of normal-order evaluation in particular is that it can compute orthodox values for:
 
 
-               (i) or (j) would be evaluated, but never both.
+<pre><code>
+(\x. y) (&omega; &omega;)<p>
+\z. (\x. y) (&omega; &omega;)
+</code></pre>
 
 
-               Lazy evaluation allows control structures to be defined normally, and not as
-               primitives or compile-time techniques. If (i) or (j) have side effects or
-               introduce run time errors, the subtle differences between (l) and (l') can be
-               complex. As most programming languages are Turing-complete, it is of course
-               possible to introduce lazy control structures in eager languages, either as
-               built-ins like C's ternary operator ?: or by other techniques such as clever
-               use of lambdas, or macros.
+Indeed, it's provable that if there's *any* reduction path that delivers a value for a given expression, the normal-order evalutation strategy will terminate with that value.
 
 
-               Short-circuit evaluation of Boolean control structures is sometimes called
-               "lazy". [edit] Controlling eagerness in lazy languages
+An expression is said to be in **normal form** when it's not possible to perform any more reductions (not even inside abstracts).
+There's a sense in which you *can't get anything more out of* <code>&omega; &omega;</code>, but it's not in normal form because it still has the form of a redex.
 
 
-               In lazy programming languages such as Haskell, although the default is to
-               evaluate expressions only when they are demanded, it is possible in some cases
-               to make code more eager—or conversely, to make it more lazy again after it has
-               been made more eager. This can be done by explicitly coding something which
-               forces evaluation (which may make the code more eager) or avoiding such code
-               (which may make the code more lazy). Strict evaluation usually implies
-               eagerness, but they are technically different concepts.
+A computational system is said to be **confluent**, or to have the **Church-Rosser** or **diamond** property, if, whenever there are multiple possible evaluation paths, those that terminate always terminate in the same value. In such a system, the choice of which sub-expressions to evaluate first will only matter if some of them but not others might lead down a non-terminating path.
 
 
-               However, there is an optimisation implemented in some compilers called
-               strictness analysis, which, in some cases, allows the compiler to infer that a
-               value will always be used. In such cases, this may render the programmer's
-               choice of whether to force that particular value or not, irrelevant, because
-               strictness analysis will force strict evaluation.
+The untyped lambda calculus is confluent. So long as a computation terminates, it always terminates in the same way. It doesn't matter which order the sub-expressions are evaluated in.
 
 
-               In Haskell, marking constructor fields strict means that their values will
-               always be demanded immediately. The seq function can also be used to demand a
-               value immediately and then pass it on, which is useful if a constructor field
-               should generally be lazy. However, neither of these techniques implements
-               recursive strictness—for that, a function called deepSeq was invented.
+A computational system is said to be **strongly normalizing** if every permitted evaluation path is guaranteed to terminate. The untyped lambda calculus is not strongly normalizing: <code>&omega; &omega;</code> doesn't terminate by any evaluation path; and <code>(\x. y) (&omega; &omega;)</code> terminates only by some evaluation paths but not by others.
 
 
-               Also, pattern matching in Haskell 98 is strict by default, so the ~ qualifier
-               has to be used to make it lazy. [edit] 
+But the untyped lambda calculus enjoys some compensation for this weakness. It's Turing complete! It can represent any computation we know how to describe. (That's the cash value of being Turing complete, not the rigorous definition. There is a rigrous definition. However, we don't know how to rigorously define "any computation we know how to describe.") And in fact, it's been proven that you can't have both. If a computational system is Turing complete, it cannot be strongly normalizing.
 
 
+A computational system is said to be **weakly normalizing** if there's always guaranteed to be *at least one* evaluation path that terminates. The untyped lambda calculus is not weakly normalizing either, as we've seen.
 
 
+The *typed* lambda calculus that linguists traditionally work with, on the other hand, is strongly normalizing. (And as a result, is not Turing complete.) It has expressive power (concerning types) that the untyped lambda calculus lacks, but it is also unable to represent some (terminating!) computations that the untyped lambda calculus can represent.
 
 
+Other more-powerful type systems we'll look at in the course will also fail to be Turing complete, though they will turn out to be pretty powerful.
 
 
-confluence/Church-Rosser
+Further reading:
 
 
+*      [[!wikipedia Evaluation strategy]]
+*      [[!wikipedia Eager evaluation]]
+*      [[!wikipedia Lazy evaluation]]
+*      [[!wikipedia Strict programming language]]<p>
+*      [[!wikipedia Church-Rosser theorem]]
+*      [[!wikipedia Normalization property]]
+*      [[!wikipedia Turing completeness]]
 
 
-"combinators", useful ones:
 
 
+Decidability
+============
 
 
-composition
-n-ary[sic] composition
-"fold-based"[sic] representation of numbers
-defining some operations, not yet predecessor
-       iszero,succ,add,mul,...?
+The question whether two formulas are syntactically equal is "decidable": we can construct a computation that's guaranteed to always give us the answer.
 
 
-lists?
-       explain differences between list and tuple (and stream)
-               FIFO queue,LIFO stack,etc...
-"pair-based" representation of lists (1,2,3)
-nil,cons,isnil,head,tail
+What about the question whether two formulas are convertible? Well, to answer that, we just need to reduce them to normal form, if possible, and check whether the results are syntactically equal. The crux is that "if possible." Some computations can't be reduced to normal form. Their evaluation paths never terminate. And if we just kept trying blindly to reduce them, our computation of what they're convertible to would also never terminate.
 
 
-explain operations like "map","filter","fold_left","fold_right","length","reverse"
-but we're not yet in position to implement them because we don't know how to recurse
+So it'd be handy to have some way to check in advance whether a formula has a normal form: whether there's any evaluation path for it that terminates.
 
 
-Another way to do lists is based on model of how we did numbers
-"fold-based" representation of lists
-One virtue is we can do some recursion by exploiting the fold-based structure of our implementation; don't (yet) need a general method for recursion
+Is it possible to do that? Sure, sometimes. For instance, check whether the formula is syntactically equal to &Omega;. If it is, it never terminates.
 
 
-Go back to numbers, how to do predecessor? (a few ways)
-For some purposes may be easier (to program,more efficient) to use "pair-based" representation of numbers
-("More efficient" but these are still base-1 representations of numbers!)
-In this case, too you'd need a general method for recursion
-(You could also have a hybrid, pair-and-fold based representation of numbers, and a hybrid, pair-and-fold based representation of lists. Works quite well.)
+But is there any method for doing this in general---for telling, of any given computation, whether that computation would terminate? Unfortunately, there is not. Church proved this in 1936; Turing also essentially proved it at the same time. Geoff Pullum gives a very reader-friendly outline of the proofs here:
 
 
-Recursion
-Even if we have fold-based representation of numbers, and predecessor/equal/subtraction, some recursive functions are going to be out of our reach
-Need a general method, where f(n) doesn't just depend on f(n-1) (or <f(n-1),f(n-2),...>). Example?
+*      [Scooping the Loop Snooper](http://www.cl.cam.ac.uk/teaching/0910/CompTheory/scooping.pdf), a proof of the undecidability of the halting problem in the style of Dr Seuss by Geoffrey K. Pullum
 
 
-How to do with recursion with omega.
 
 
 
 
-Next week: fixed point combinators
+##[[Lists and Numbers]]##