This repository has been archived by the owner on Apr 9, 2024. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 10
/
Copy pathLec08.hs
393 lines (306 loc) · 14.9 KB
/
Lec08.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
module Lec08 where
{- LECTURE 08 : RECURSION SCHEMES
In Lecture 5, we covered how to define recursive functions --
functions that are defined in terms of themselves. Recursion is the
way that we write functional programs that compute with structures
whose size is unknown at the time of writing the program.
After writing a few recursive functions, we can see that they often
fall into a few standard "patterns". The pattern we will look at in
this lecture are recursive functions that systematically replace
the constructors of a recursive data type with values and
functions, building up a new value from a value of the
datatype. This pattern is called 'iteration' over the data type (it
is also sometimes called 'fold', but we reserve this for Foldable
we will see in Lecture 09). Iteration turns out to be surprisingly
expressive. -}
{- For the first example, we will use the type of natural numbers,
defined recursively in terms of 'Zero' and 'Succ': -}
data Nat
= Zero
| Succ Nat
deriving Show
{- Values of type 'Nat' are built by using the constructors. We can
check the types of the constructors by using GHCi:
λ> :t Zero
Zero :: Nat
λ> :t Succ
Succ :: Nat -> Nat
The idea is that 'Zero' represents '0' and 'Succ' represents
'+1'. So we can represent any positive whole number by starting
from Zero and using Succ as many times as we need.
Here are two example values of type 'Nat': 'one' and 'two'. -}
one = Succ Zero
two = Succ one
{- Addition of 'Nat's can be defined by the following recursively
defined function. We will look at the structure of this function to
see the underlying 'pattern' of recursion that is being used: -}
plus :: Nat -> Nat -> Nat
plus Zero n = n
plus (Succ m) n = Succ (plus m n)
{- Looking at 'plus' we can see that 'n' is left unchanged thoughout, so
we can rewrite it to make this clearer: -}
plus' :: Nat -> Nat -> Nat
plus' m n = plusHelper m
where plusHelper Zero = n
plusHelper (Succ m) = Succ (plusHelper m)
{- Looking at 'plusHelper', we can make two observations:
1. There is a line for each constructor of the 'Nat' type,
declaring what to do for each constructor.
2. The recursive call to 'plusHelper' in the 'Succ' case is on 'm'.
The function doesn't look at the value of 'm' directly, it only
uses the value recursively generated from it.
We can summarise 'plusHelper' by what it does on the two
constructors: On Zero, it returns 'n'. On (Succ m) it applies Succ
to the result of recursively processing 'm'.
This pattern of returning a value for 'Zero' and applying a
function for 'Succ' is very common, and we term this process
'iteration'. Iteration for natural numbers of expressed by the
'iterNat' function: -}
iterNat :: a -> (a -> a) -> Nat -> a
iterNat zero succ Zero = zero
iterNat zero succ (Succ n) = succ (iterNat zero succ n)
{- The type of 'iterNat' states:
iterNat :: a -- a value to use for 'Zero'
-> (a -> a) -- a function to use for 'Succ'
-> Nat -- a Nat to look at
-> a -- the value returned by looking at the Nat
See? We are systematically replacing the constructors in any value
of 'Nat' with the value and argument provided.
To see how to use 'iterNat', let's write 'plus' using it: -}
plus2 :: Nat -> Nat -> Nat
plus2 m n = iterNat -- 'a = Nat'
n -- zero case
Succ -- (\plus2_m_n -> Succ plus2_m_n) -- succ case
m
{- To use 'iterNat', we must provide the 'Zero' and 'Succ'
cases. Following the discussion above, we use 'n' for the 'Zero'
case, and 'Succ' for the 'Succ' case.
Another way to write 'plus' using 'iterNat' is to pass around 'n'
each time, just as we did in the original definition of 'plus'. We
accomplish this by using 'iterNat' to build a function 'Nat -> Nat'
instead of to build a 'Nat'. This means that we are using 'iterNat'
with type 'a = Nat -> Nat': -}
plus3 :: Nat -> (Nat -> Nat)
plus3 m = iterNat -- 'a = Nat -> Nat'
id -- zero case
(\plus3_m n -> Succ (plus3_m n)) -- succ case
m
{- In 'plus3', the 'Zero' case is the identity function 'id', which just
takes 'n' and returns 'n'. In the 'Succ' case, we are given the
result of computing 'plus3_m' and we are given 'n', so we use
'plus3_m n' to get the result of adding 'm' to 'n', and then apply
'Succ'.
Passing 'n' around gives us some more flexibility. Here is a
version of plus that modifies 'n' as it goes, adding one to 'n' for
every 'Succ' discovered in 'm': -}
plus4 :: Nat -> Nat -> Nat
plus4 m = iterNat -- 'a = Nat -> Nat'
id -- zero
(\plus4_m n -> plus4_m (Succ n)) -- succ
m
{- On natural numbers 'plus3' and 'plus4' are equivalent, because one
'Succ' looks like every other 'Succ'. However, if we attached
values to the 'Succ's (e.g. as we do in lists), then they would
have different behaviour. -}
{- The following function is an interesting special case. What happens
when we use 'Zero' as the value for 'Zero', and 'Succ' as the
function for 'Succ'? -}
thingy :: Nat -> Nat
thingy = iterNat Zero Succ
{- We get the identity function! 'thingy x' is always equal to
'x'. Replacing each constructor with itself gives us back the
original value. This may seem like just a useless way to compute
nothing, but this technique will be useful for keeping track of
where we are in a recursive computation. -}
{- Let's look at another example of a function on 'Nat's: the equality
testing function.
We can start to define this function using 'iterNat' as follows: -}
eqNat0 :: Nat -> Nat -> Bool
eqNat0 = iterNat -- 'a = Nat -> Bool'
undefined -- need an 'is this zero?' test
(\eqNat_m n -> undefined) -- need to determine whether Succ
-- m = n, given a function that
-- can answer is 'x' equal to
-- 'm'?
{- There are two holes left in the definition. To fill in the first one
we need to write a function that determines whether a 'Nat' is
'Zero'. We can do this with a 'case' expression: -}
eqNat1 :: Nat -> Nat -> Bool
eqNat1 = iterNat -- 'a = Nat -> Bool'
(\n -> case n of
Zero -> True
Succ _ -> False)
(\eqNat_m n -> undefined)
{- To fill in the second hole, we need a function that can answer "is
Succ m = n", given a test that can answer "is m = x", for any
"x". Thinking a bit, we can see that "Succ m = n" is only true if
"n = Succ n'" for some n'. So we use a 'case' expression again: -}
eqNat2 :: Nat -> Nat -> Bool
eqNat2 = iterNat -- 'a = Nat -> Bool'
(\n -> case n of
Zero -> True
Succ _ -> False)
(\eqNat_m n -> case n of
Zero -> False
Succ n' -> eqNat_m n')
{- Let's step through a run of 'eqNat2' to get a feel for what is going
on. We write
zeroCase = (\n -> case n of
Zero -> True
Succ _ -> False)
succCase = (\eqNat_m n -> case n of
Zero -> False
Succ n' -> eqNat_m n')
so that eqNat2 = iterNat zeroCase succCase.
eqNat2 (Succ Zero) (Succ (Succ Zero))
= { write superfluous brackets for emphasis }
(eqNat2 (Succ Zero)) (Succ (Succ Zero))
= { expand definition of eqNat2 }
(iterNat zeroCase succCase (Succ Zero)) (Succ (Succ Zero))
= { definition of iterNat ... (Suc Zero) }
(succCase (iterNat zeroCase succCase Zero)) (Succ (Succ Zero))
= { expand definition of succCase }
(\eqNat_m n -> case n of Zero -> False; Succ n' -> eqNat_m n')
(iterNat zeroCase succCase Zero)
(Succ (Succ Zero))
= { application of a lambda expression to arguments }
case (Suc (Suc Zero)) of
Zero -> False
Succ n' -> (iterNat zeroCase succCase Zero) n'
= { case expression of a constructor }
(iterNat zeroCase succCase Zero) (Suc Zero)
= { definition of iterNat ... Zero }
zeroCase (Suc Zero)
= { expand definition of zeroCase }
(\n -> case n of Zero -> True; Succ _ -> False) (Suc Zero)
= { application of a lambda expression to arguments }
case (Suc Zero) of Zero -> True; Succ _ -> False
= { case expression of a constructor }
False
So 'one' is not equal to 'two'. Try stepping through
eqNat2 (Suc Zero) (Suc Zero) yourself!
-}
{- Explicitly pattern matching seems to go against the spirit of
'iterNat'. Can we replace the 'case' expressions with uses of
'iterNat'?
For the 'Zero' case, where we need a 'is Zero' test, this is
possible. To identify 'Zero's, we replace every 'Zero' with 'True'
and every 'Succ' with the constantly 'False' function: -}
eqNat3 :: Nat -> Nat -> Bool
eqNat3 = iterNat -- 'a = Nat -> Bool'
(iterNat True (\_ -> False))
(\eqNat_m n -> case n of
Zero -> False
Succ n' -> eqNat_m n')
{- The 'Succ' case is more difficult. If we break it out into its own
function, we can see the problem. -}
succCase :: (Nat -> Bool) -> Nat -> Bool
succCase eqNat_m = iterNat False (\succCase_eqNat_m_n -> undefined)
{- To fill in the 'undefined' part, we have the following task. Given a
number 'Succ n', and the result of 'eqNat_m_n' we want to know
whether 'm' is equal to 'Succ n'. Working this out from the
available information is impossible!
The problem is that 'iterNat' doesn't give us the 'n' from the
'Succ n', only the result of recursively processing it. We seem to
need a new kind of recursion scheme to handle this case. We define
'caseNat' to capture the pattern being used in the 'case'
expressions: -}
caseNat :: a -> (Nat -> a) -> Nat -> a
caseNat zero succ Zero = zero
caseNat zero succ (Succ k) = succ k
{- 'caseNat' is similar to 'iterNat', except that it does not call
itself recursively. The 'Nat' 'k' is passed directly into the
'succ' function.
Using 'caseNat', we can write 'eqNat' without explicit recursion or
pattern matching: -}
eqNat :: Nat -> Nat -> Bool
eqNat = iterNat -- 'a = Nat -> Bool'
(iterNat True (\eq_Zero_k -> False))
(\ eqNat_m -> caseNat False
(\ k -> eqNat_m k))
{- The existence of 'iterNat' and 'caseNat' is unsatisfying. Is there a
recursion scheme that gives us access to both the recursive result
and the value being examined?
'recNat' is a recursion scheme that does this: -}
recNat :: a -> ((Nat,a) -> a) -> Nat -> a
recNat zero succ Zero = zero
recNat zero succ (Succ n) = succ (n, recNat zero succ n)
{- Compared to 'caseNat', 'recNat' calls itself recursively. Compared to
'iterNat', the 'Succ n' case passes 'n' to the 'succ' function.
Because it passes more information to 'succ', 'recNat' appears to
be more powerful than 'iterNat'. However, this extra power is
illusory because we can implement 'recNat' from 'iterNat' by
building a copy of the 'Nat' we are processing. This uses the same
technique as 'thingy' above.
The tricky to defining 'recNat' is to use 'iterNat' to compute a
pair (n,b) consisting of: 'n', a copy of the natural being
processes; and 'b' the result required. At the end of the
computation, we use 'snd' to get the final result, and discard the
'Nat', which was only needed for intermediate computations. -}
recNatFromIterNat :: b -> ((Nat,b) -> b) -> Nat -> b
recNatFromIterNat zero succ n
= snd (iterNat -- 'a = (Nat, b)'
(Zero, zero)
(\(n, rec_n) -> (Succ n, succ (n, rec_n)))
n)
{- See how the Zero and Succ cases return a 'Nat' built from 'Zero' and
'Succ', building a copy of the 'Nat' that was started with. Compare
this to the 'thingy' function above.
It is also possible to avoid the unpacking and repacking of the
pair in the 'Succ' case by using an "@ pattern" that makes 'x'
stand for the whole pair, while 'n' and 'n_rec' stand for the first
and second parts of the pair, respectively:
(\x@(n,rec_n) -> (Succ n, succ x))
Note that defining 'recNat' in this way is not necessarily
recommended, for efficiency reasons. This implementation builds a
data structure in memory that is an exact copy of the existing
structure, wasting memory. The point is that 'iterNat' is
expressive enough to capture this apparently more general recursion
scheme. This expressivity is important when using functions with
interfaces like 'iterNat's that don't operate over concrete data
structures, but operate over the output of some process where there
is not concrete data structure. -}
{- Now let's look at another example of iteration over data. Here is a
data type for describing arithmetic expressions consisting of
numbers and addition: -}
data Expr
= Number Int
| Add Expr Expr
deriving Show
{- Let's see now how to systematically derive the type of an 'iterExpr'
function from this data declaration.
1. We want a function that takes 'Expr's and returns values of any
type 't', but we don't know yet what the other argument types
are. So we write this down:
iterExpr :: ???? -> Expr -> t
2. Iteration works on a constructor-by-constructor basis --
replacing each use of a constructor by a function call. So, to
work out the other argument types, we take the types of the
constructors:
λ> :t Number
Number :: Int -> Expr
λ> :t Add
Add :: Expr -> Expr -> Expr
Plugging these types into the type of iterExpr gives:
iterExpr :: (Int -> Expr) -> (Expr -> Expr -> Expr) -> Expr -> t
\_ Number \_ Add
3. Now we systematically replace 'Expr' by 't' in the types taken
from the constructors. Why? Because we will be using these
functions to construct new values of type 't', following the
structure of the 'Expr' that is given to us. If we left them as
'Expr' then our function would be less general that it could be
-- we would only be able to construct 'Expr's from 'Expr's.
iterExpr :: (Int -> t) -> (t -> t -> t) -> Expr -> t
Performing this change gives us the type of 'iterExpr'.
EXERCISE: repeat this same process with the Nat type above and with
the List type ([a]). You should get the same answers as for
'iterNat' above and 'iterRight' in Ex3.
Now that we have the type of 'iterExpr', the implementation follows
the exact same pattern as 'iterNat' above: we match on the
constructors of 'Expr' and use the corresponding function: -}
iterExpr :: (Int -> t) -> (t -> t -> t) -> Expr -> t
iterExpr number add (Number i) = number i
iterExpr number add (Add d e) =
add (iterExpr number add d) (iterExpr number add e)
{- In Lecture 10 we will see some more functions that use
'iterExpr'. -}