assignment 5 draft
[lambda.git] / exercises / assignment3_answers.mdwn
1 ## Lists and List Comprehensions
2
3 1.  In Kapulet, what does `[ [x, 2*x] | x from [1, 2, 3] ]` evaluate to?
4
5     >     [[1,2], [2,4], [3,6]]
6
7 2.  What does `[ 10*x + y | y from [4], x from [1, 2, 3] ]` evalaute to?
8
9     >     [14, 24, 34]
10
11 3.  Using either Kapulet's or Haskell's list comprehension syntax, write an expression that transforms `[3, 1, 0, 2]` into `[3, 3, 3, 1, 2, 2]`. [[Here is a hint|assignment3 hint1]], if you need it.
12
13     >     letrec
14     >       dup (n, x) = case n of
15     >                      0 then [];
16     >                      _ then x & dup (n-1, x)
17     >                    end;
18     >       # you can assume join is already defined, but we'll redefine it here anyway
19     >       join xss   = fold_right ((&&), []) xss    # we help ourselves to &&/append
20     >     in join [dup(x, x) | x from [3, 1, 0, 2]]
21
22 4.  Last week you defined `head` in terms of `fold_right`. Your solution should be straightforwardly translatable into one that uses our proposed right-fold encoding of lists in the Lambda Calculus. Now define `empty?` in the Lambda Calculus. (It should require only small modifications to your solution for `head`.)
23
24     >     let empty? = \xs. xs (\x z. false) true in
25     >     ...
26
27 5.  If we encode lists in terms of their *left*-folds, instead, `[a, b, c]` would be encoded as `\f z. f (f (f z a) b) c`. The empty list `[]` would still be encoded as `\f z. z`. What should `cons` be, for this encoding?
28
29     >     let left_cons = \x xs. \f z. xs f (f z x) in
30     >     ...
31
32 6.  Continuing to encode lists in terms of their left-folds, what should `last` be, where `last [a, b, c]` should result in `c`. Let `last []` result in whatever `err` is bound to.
33
34     >     let left_last = \xs. xs (\z x. x) err in
35     >     ...
36
37 7.  Continuing to encode lists in terms of their left-folds, how should we write `head`? This is challenging.
38
39     > The [[hint/solution|assignment3 hint2]] gave this answer:
40
41     >     let m = \a. \n b. n a in
42     >     let f = \w b. w m b in
43     >     let left_head = \xs. (xs f I) I err in
44     >     ...
45
46     > Here's another, more straightforward answer. We [[observed before|/topics/week2_encodings#flipped-cons]] that left-folding the `cons` function over a list reverses it. Hence, it is easy to reverse a list defined in terms of its left-fold:
47
48     >     let left_empty = \f z. z in    ; this the same as for the right-fold encoding of lists
49     >     let flipped_left_cons = \xs x. \f z. xs f (f z x) in    ; left-folding supplies arguments in a different order than cons expects
50     >     let left_reverse = \xs. xs flipped_left_cons left_empty in
51     >     ...
52
53     > Then we can get the list's head by reversing it and getting the last member of the result, which we saw in the previous problem is easy:
54
55     >     let left_head = \xs. left_last (left_reverse xs) in
56     >     ...
57
58     > I'm not sure which of the two solutions presented here is better. The one given in the hint traverses the list only once; whereas the one gotten by reversing the list and getting the last member of the result traverses the list twice. But the former strategy does more complicated stuff at each step of the traversal (both conceptually and more applications), so in the end it might be computationally "cheaper" to use the latter strategy.
59
60
61
62 8.  Suppose you have two lists of integers, `left` and `right`. You want to determine whether those lists are equal, that is, whether they have all the same members in the same order. How would you implement such a list comparison? You can write it in Scheme or Kapulet using `letrec`, or if you want more of a challenge, in the Lambda Calculus using your preferred encoding for lists. If you write it in Scheme, don't rely on applying the built-in comparison operator `equal?` to the lists themselves. (Nor on the operator `eqv?`, which might not do what you expect.) You can however rely on the comparison operator `=` which accepts only number arguments. If you write it in the Lambda Calculus, you can use your implementation of `leq?`, requested below, to write an equality operator for Church-encoded numbers. [[Here is a hint|assignment3 hint3]], if you need it.
63
64     (The function you're trying to define here is like `eqlist?` in Chapter 5 of *The Little Schemer*, though you are only concerned with lists of numbers, whereas the function from *The Little Schemer* also works on lists containing symbolic atoms --- and in the final version from that Chapter, also on lists that contain other, embedded lists.)
65
66     > In Kapulet:
67
68     >     letrec
69     >       list_eq? (left, right) = case (left, right) of
70     >                                  ([], []) then 'true;
71     >                                  ([],  _) then 'false;
72     >                                  (_,  []) then 'false;
73     >                                  (x&xs, y&ys) when x == y then list_eq? (xs, ys);
74     >                                  (_, _)   then 'false
75     >                                end
76     >     in list_eq?
77
78     > In Scheme:
79
80     >     (define list_eq? (lambda (left right)
81     >                        (cond
82     >                          ((null? left) (null? right))
83     >                          ((null? right) #f)
84     >                          ((= (car left) (car right)) (list_eq? (cdr left) (cdr right)))
85     >                          (else #f))))
86
87     > In the Lambda Calculus, helping ourselves to definitions of `leq?`, `0`, `succ`, `head`, `tail`, and `reverse`:
88
89     >     let true = \y n. y in
90     >     let and = \p q. p q p in
91     >     let pair = \a b. \f. f a b in
92     >     let fst = \x y. x in
93     >     let num_eq? = \l r. and (leq? l r) (leq? r l) in
94     >     let length = \xs. xs (\x z. succ z) 0 in
95     >     let check = \x p. p (\b ys. pair (and b (num_eq? x (head ys))) (tail ys)) in
96     >     let list_eq? = \xs ys. and (num_eq? (length xs) (length ys)) ; this step could be skipped
97     >                                                                  ; if you were prepared to assume the lists always have the same length
98     >                                (xs check (pair true (reverse ys)) fst) in
99     >     ...
100
101
102 ## Numbers
103
104 9.  Recall our proposed encoding for the numbers, called "Church's encoding". As we explained last week, it's similar to our proposed encoding of lists in terms of their folds. Give a Lambda Calculus definition of `zero?` for numbers so encoded. (It should require only small modifications to your solution for `empty?`, above.)
105
106     >     let zero? = \n. n (\z. false) true in
107     >     ...
108
109 10. In last week's homework, you gave a Lambda Calculus definition of `succ` for Church-encoded numbers. Can you now define `pred`? Let `pred 0` result in whatever `err` is bound to. This is challenging. For some time theorists weren't sure it could be done. (Here is [some interesting commentary](http://okmij.org/ftp/Computation/lambda-calc.html#predecessor).) However, in this week's notes we examined one strategy for defining `tail` for our chosen encodings of lists, and given the similarities we explained between lists and numbers, perhaps that will give you some guidance in defining `pred` for numbers.
110
111     > Here is the solution we were guiding you towards, due to Paul Bernays:
112
113     >     ; helping ourselves to 0 and succ
114     >     let pair = \a b. \f. f a b in
115     >     let snd = \x y. y in
116     >     let shift = \p. p (\x y. pair (succ x) x) in
117     >     let pred = \n. n shift (pair 0 err) snd in
118     >     ...
119
120     > Here is another solution, due to Martin Bunder and F. Urbanek:
121
122     >     let box = \a. \v. v a in
123     >     let pred = \n. \s z. n (\b. box (b s)) (K z) I in
124     >     ...
125
126     > That can be hard to wrap your head around. If you trace this expression through, you'll see that:
127
128     > * when `n == 0`, it reduces to `\s z. (K z) I`, or `\s z. z`
129     > * when `n == 1`, it reduces to `\s z. (box z) I`, or `\s z. z`
130     > * when `n == 2`, it reduces to `\s z. (box (s z)) I`, or `\s z. s z`
131     > * when `n == 3`, it reduces to `\s z. (box (s (s z))) I`, or `\s z. s (s z)`
132
133     > `box a` is `\v. v a`; this stands to `pair a b` as one stands to two. Since boxes (like pairs) are really just functions, the technique used in this definition of `pred` is akin to that used in [[the hint for last week's `reverse`|assignment2_answers#cps-reverse]].
134
135     (Want a further challenge? Define `map2` in the Lambda Calculus, using our right-fold encoding for lists, where `map2 g [a, b, c] [d, e, f]` should evaluate to `[g a d, g b e, g c f]`. Doing this will require drawing on a number of different tools we've developed, including that same strategy for defining `tail`. Purely extra credit.)
136
137     >     let next = \g. \x p. p (\zs ys. pair (cons (g x (head ys)) zs) (tail ys)) in
138     >     let finish = \zs ys. (empty? ys) zs
139     >                          ; else ys are too long
140     >                          err_different_lengths in
141     >     let map2 = \g. \xs ys. (leq? (length xs) (length ys))
142     >                            (xs (next g) (pair empty (reverse ys)) finish)
143     >                            ; else ys are too short
144     >                            err_different_lengths in
145     >     ...
146
147
148 11. Define `leq?` for numbers (that is, ≤) in the Lambda Calculus. Here is the expected behavior,
149 where `one` abbreviates `succ zero`, and `two` abbreviates `succ (succ zero)`.
150
151         leq? zero zero ~~> true
152         leq? zero one ~~> true
153         leq? zero two ~~> true
154         leq? one zero ~~> false
155         leq? one one ~~> true
156         leq? one two ~~> true
157         leq? two zero ~~> false
158         leq? two one ~~> false
159         leq? two two ~~> true
160         ...
161
162     You'll need to make use of the predecessor function, but it's not essential to understanding this problem that you have successfully implemented it yet. You can treat it as a black box.
163
164     > It's easiest to do this if you define `pred` so that `pred 0 ~~> 0`:
165
166     >      let pred = \n. n shift (pair 0 0) snd in
167     >      let sub = \l r. r pred l in
168     >      let leq? = \l r. zero? (sub l r) in
169     >      ...
170
171     > Here is another solution. Jim crafted this particular implementation, but like a great deal of the CS knowledge he's gained over the past eight years, Oleg Kiselyov pointed the way. <!-- see "lambda-calc-opposites.txt" at http://okmij.org/ftp/Computation/lambda-calc.html#neg -->
172
173     >     let leq? = (\base build consume. \l r. r consume (l build base) fst)
174     >             ; where base is
175     >             (pair true junk)
176     >             ; and build is
177     >             (\p. pair false p)
178     >             ; and consume is
179     >             (\p. p fst p (p snd)) in
180     >     ...
181
182     > That can be generalized to give this nice implementation of `num_eq?`:
183
184     >     ; `num_cmp x y lt eq gt` returns lt when x<y, eq when x==y, gt when x>y
185     >     let num_cmp = (\base build consume. \l r. r consume (l build base) fst)
186     >             ; where base is
187     >             (pair (\a b c. b) (K (\a b c. a)))
188     >             ; and build is
189     >             (\p. pair (\a b c. c) p)
190     >             ; and consume is
191     >             (\p. p fst p (p snd) (p snd)) in
192     >     let num_eq? = \x y. num_cmp x y false true false in
193     >     ...
194
195
196 ## Combinatory Logic
197
198 Reduce the following forms, if possible:
199
200 <ol start=12>
201 <li><code>Kxy ~~> x</code>
202 <li><code>KKxy ~~> Ky</code>
203 <li><code>KKKxy ~~> Kxy ~~> x</code>
204 <li><code>SKKxy ~~> Kx(Kx)y ~~> xy</code>
205 <li><code>SIII ~~> II(II) ~~> II ~~> I</code>
206 <li><code>SII(SII) ~~> I(SII)(I(SII)) ~~> SII(SII) ~~> ...</code>; the reduction never terminates
207 </ol>
208
209 <!-- -->
210
211 18. Give Combinatory Logic combinators (that is, expressed in terms of `S`, `K`, and `I`) that behave like our boolean functions. Provide combinators for `true`, `false`, `neg`, `and`, `or`, and `xor`.
212
213     > As Dan pointed out in the Wednesday session, this problem is easy to solve if you first come up with a Combinatory translation of the schema `\p. if p then M else N`:
214
215     >     [\p. p M N] =
216     >     @p. p [M] [N] =
217     >     S (@p. p [M]) (@p [N]) =
218     >     S (S (@p p) (@p [M])) (@p [N]) =
219     >     S (S I (@p [M])) (@p [N]) =
220     >     S (S I (K [M])) (K [N])
221
222     > The last step assumes that `p` does not occur free in the expressions `M` and `N`.
223         
224     > Next, we translate `true ≡ \y n. y` as `K`, and `false ≡ \y n. n` as `KI`. Then we rely on the following equivalences:
225
226     >     neg   ≡ \p. if p then false else true
227     >     and   ≡ \p. if p then I else K false
228     >     ; then:    and p q <~~> if p then I q else K false q ~~> if p then q else false
229     >     or    ≡ \p. if p then K true else I
230     >     ; then:    or p q  <~~> if p then K true q else I q  ~~> if p then true else q
231     >     xor   ≡ \p. if p then neg else I
232     >     ; then:    xor p q <~~> if p then neg q else I q     ~~> if p then neg q else q
233
234     > Then we just make use of the schema derived above to complete the translations. For example, `and ≡ \p. if p then I else K false` becomes <code>S (SI (K <b>I</b>)) (K <b>(K false)</b>) ≡ S (SI (K <b>I</b>)) (K <b>(K (KI))</b>)</code>.
235
236     > In the case of `neg`, this produces <code>S (SI (K <b>false</b>)) (K <b>true</b>) ≡ S (SI (K <b>(KI)</b>)) (K <b>K</b>)</code>. A more compact result here can be obtained here by observing that for boolean arguments, `neg` can also be defined as `\p y n. p n y`, which is just the `C` combinator.
237
238
239 Using the mapping specified in this week's notes, translate the following lambda terms into combinatory logic:
240
241
242 <ol start=19>
243 <li><code>[\x x] = @x x = I</code>
244 <li><code>[\x y. x] = @x [\y. x] = @x. (@y x) = @x (Kx) = S (@x K) (@x x) = S (KK) I</code>; in general expressions of this form <code>S(K<i>M</i>)I</code> will behave just like <code><i>M</i></code> for any expression <code><i>M</i></code>
245 <li><code>[\x y. y] = @x [\y. y] = @x (@y y) = @x I = KI</code>
246 <li><code>[\x y. y x] = @x [\y. y x] = @x (@y (y x)) = @x (S (@y y) (@y x)) = @x (S I (Kx)) = S (@x (SI)) (@x (Kx)) = S (K(SI)) K</code> ; this is the <b>T</b> combinator
247 <li><code>[\x. x x] = @x (x x) = S (@x x) (@x x) = SII</code>
248 <li><code>[\x y z. x (y z)] =<br>
249 @x (@y (@z (x (y z)))) =<br>
250 @x (@y (S (@z x) (@z (y z)))) =<br>
251 @x (@y (S (Kx) (@z (y z)))) =<br>
252 @x (@y (S (Kx) y)) =<br>
253 @x (S (@y (S (Kx))) (@y y)) =<br>
254 @x (S (K (S (Kx))) (@y y)) =<br>
255 @x (S (K (S (Kx))) I) =<br>
256 S (@x (S (K (S (Kx))))) (@x I) =<br>
257 S (S (@x S) (@x (K (S (Kx))))) (@x I) =<br>
258 S (S (KS) (@x (K (S (Kx))))) (@x I) =<br>
259 S (S (KS) (S (@x K) (@x (S (Kx))))) (@x I) =<br>
260 S (S (KS) (S (KK) (@x (S (Kx))))) (@x I) =<br>
261 S (S (KS) (S (KK) (S (@x S) (@x (Kx))))) (@x I) =<br>
262 S (S (KS) (S (KK) (S (KS) (@x (Kx))))) (@x I) =<br>
263 S (S (KS) (S (KK) (S (KS) K))) (@x I) =<br>
264 S (S (KS) (S (KK) (S (KS) K))) (KI)</code>; this is the <b>B</b> combinator, which can also be expressed more concisely as <code>S (K S) K</code>
265 </ol>
266
267 <!-- -->
268
269 25. For each of the above translations, how many `I`s are there? Give a rule for describing what each `I` corresponds to in the original lambda term.
270
271     This generalization depends on you omitting the translation rule:
272
273         6. @a(Xa)       =   X            if a is not in X
274
275     > With that shortcut rule omitted, then there turn out to be one `I` in the result corresponding to each occurrence of a bound variable in the original term.
276
277 Evaluation strategies in Combinatory Logic
278 ------------------------------------------
279
280 26. Find a term in CL that behaves like Omega does in the Lambda
281 Calculus.  Call it `Skomega`.
282
283     >     SII(SII)
284
285 27. Are there evaluation strategies in CL corresponding to leftmost
286 reduction and rightmost reduction in the Lambda Calculus?
287 What counts as a redex in CL?
288
289     > A redex is any `I` with one argument, or `K` with two arguments, or `S` with three arguments.
290
291     > Leftmost reduction corresponds to applying the rules for an `I` or `K` or `S` in head position *before* reducing any of their arguments; rightmost reduction corresponds to reducing the arguments first.
292
293 28. Consider the CL term `K I Skomega`.  Does leftmost (alternatively,
294 rightmost) evaluation give results similar to the behavior of `K I
295 Omega` in the Lambda Calculus, or different?  What features of the
296 Lambda Calculus and CL determine this answer?
297
298     > Leftmost reduction terminates with `I`; rightmost reduction never terminates. This is because "leftmost reduction" corresponds to "head-redex first", which gives the head combinator the opportunity to ignore some of its (in this case, unreducible) arguments without trying to reduce them. If the arguments are reduced first, the head combinator loses that opportunity.
299
300 29. What should count as a thunk in CL?  What is the equivalent
301 constraint in CL to forbidding evaluation inside of a lambda abstract?
302
303     > Recall that a thunk is a function of the form `\(). EXPRESSION`, where `EXPRESSION` won't be evaluated until the function is applied (to the uninformative argument `()`). We don't really have `()` in the Lambda Calculus. The closest approximation would be `I`, since a triple is `\f. f a b c`, a pair is `\f. f a b`, and following the same pattern a one-tuple would be `\f. f a` (not the same as `a`), and the zero-tuple would be `\f. f` or `I`. But really in the untyped Lambda Calculus, it doesn't matter whether you supply `I` to an abstract that's going to ignore its argument, or any other argument. Instead, you could get the same effect as a thunk by just using `\x. EXPRESSION`, where `x` is a variable that doesn't occur free in `EXPRESSION`.
304
305     > The way to do the same thing in Combinatory Logic is `K (EXPRESSION)`. The constraint we need is that arguments to `S` and `K` are never reduced until there are enough of them to apply the rule for `S` and `K`. (If we furthermore insist on leftmost reduction, then expressions will *never* be reduced when in the position of an argument to another combinator. Only the reduction rules for the outermost head combinator are ever followed.)
306
307
308 More Lambda Practice
309 --------------------
310
311 Reduce to beta-normal forms:
312
313 <OL start=30>
314 <LI><code>(\x. x (\y. y x)) (v w) ~~> v w (\y. y (v w))</code>
315 <LI><code>(\x. x (\x. y x)) (v w) ~~> v w (\x. y x)</code>
316 <LI><code>(\x. x (\y. y x)) (v x) ~~> v x (\y. y (v x))</code>
317 <LI><code>(\x. x (\y. y x)) (v y) ~~> v y (\u. u (v y))</code>
318
319 <LI><code>(\x y. x y y) u v ~~> u v v</code>
320 <LI><code>(\x y. y x) (u v) z w ~~> z (u v) w</code>
321 <LI><code>(\x y. x) (\u u) ~~> \y u. u</code>, also known as <code>false</code>
322 <LI><code>(\x y z. x z (y z)) (\u v. u) ~~> \y z. (\u v. u) z (y z) ~~> \y z. z</code>, also known as <code>false</code>
323 </OL>
324