b36f6287da195cf8aec228023c1b10be7c140688
[lambda.git] / advanced_topics / calculator_improvements.mdwn
1 [[!toc]]
2
3 We're going to make gradual improvements to the calculator we developed in [week7](/reader_monad_for_variable_binding).
4
5 ##Original Calculator##
6
7 In a real programming application, one would usually start with a string that needs to be parsed and interpreted, such as:
8
9         let x = 1 in let y = x + 2 in x * y
10
11 The parsing phase converts this to an "abstract syntax tree" (AST), which in this case might be:
12
13         Let ('x', Constant 1,
14                  Let ('y', Addition (Variable 'x', Constant 2),
15                           Multiplication (Variable 'x', Variable 'y')))
16
17 Then the interpreter (or "evaluator") would convert that AST into an "expressed value": in this case, to the integer 3. We're not concerning ourselves with the parsing phase here, so we're just thinking about how to interpret expressions that are already in AST form.
18
19 The language we had in week 7 looked like this:
20
21         type term =
22           Constant of int
23         | Multiplication of (term * term)
24         | Addition of (term * term)
25         | Variable of char
26         | Let of (char * term * term)
27         ;;
28
29 and the evaluation function looked like this:
30
31         let rec eval (t : term) (e: (char * int) list) = match t with
32           Constant x -> x
33         | Multiplication (t1, t2) -> (eval t1 e) * (eval t2 e)
34         | Addition (t1, t2) -> (eval t1 e) + (eval t2 e)
35         | Variable c ->
36                 (* lookup the value of c in the current environment
37                    This will fail if c isn't assigned anything by e *)
38                 List.assoc c e
39         | Let (c, t1, t2) ->
40                 (* evaluate t2 in a new environment where c has been associated
41                    with the result of evaluating t1 in the current environment *)
42                 eval t2 ((c, eval t1 e) :: e)
43         ;;
44
45
46 ##Adding Booleans and Pairs##
47
48 Let's tweak this a bit.
49
50 First, let's abstract away from the assumption that our terms always evaluate to `int`s. Let's suppose they evaluate to a more general type, which might have an `int` payload, or might have, for example, a `bool` payload.
51
52         type expressed_value = Int of int | Bool of bool;;
53
54 We'll add one boolean predicate, `Iszero`, and an `If...` construction.
55
56 Similarly, we might allow for some terms to express pairs of other terms:
57
58         type expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value;;
59
60 We'd then want to add the ability to construct pairs, and extract their components.
61
62 We won't try here to catch any type errors, such as attempts to add a `bool` to an `int`, or attempts to check whether a `bool` iszero. Neither will we try here to monadize anything: these will be implementations of a calculator with all the plumbing exposed. What we will do is add more and more features to the calculator.
63
64 We'll switch over to using variable `g` for assignment functions, which is a convention many of you seem familiar with. As we mentioned a few times in [[week9]], for some purposes it's easier to implement environment or assignment functions as functions from `char`s to `int`s (or whatever variables are bound to), rather than as lists of pairs. However, we'll stick with this implementation for now. We will however abstract out the type that the variables are bound to. For now, we'll suppose that they're bound to the same types that terms can express.
65
66         type bound_value = expressed_value;;
67         type assignment = (char * bound_value) list;;
68
69 Here's where we should be now. We'll work with the language:
70
71         type term =
72           Intconstant of int
73         | Multiplication of (term * term)
74         | Addition of (term * term)
75         | Variable of char
76         | Let of (char * term * term)
77         | Iszero of term
78         | If of (term * term * term)
79         | Makepair of (term * term)
80         | First of term
81         ;;
82
83 Here is our evaluation function. We expand some of the clauses and rename a few variables for clarity. Our implementation should make it clear how to add additional constants or native predicates, such as a `Second` predicate for extracting the second element of a pair.
84
85         let rec eval (t : term) (g : assignment) = match t with
86           Intconstant x -> Int x
87         | Multiplication (t1, t2) ->
88                 (* we don't handle cases where the subterms don't evaluate to Ints *)
89                 let Int i1 = eval t1 g
90                 in let Int i2 = eval t2 g
91                 (* Multiplication (t1, t2) should evaluate to an Int *)
92                 in Int (i1 * i2)
93         | Addition (t1, t2) ->
94                 let Int i1 = eval t1 g
95                 in let Int i2 = eval t2 g
96                 in Int (i1 + i2)
97         | Variable (var) ->
98                 (* we don't handle cases where g doesn't bind var to any value *)
99                 List.assoc var g
100         | Let (var_to_bind, t2, t3) ->
101                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
102                    the result of evaluating t2 under the current assignment *)
103                 let value2 = eval t2 g
104                 in let g' = (var_to_bind, value2) :: g
105                 in eval t3 g'
106         | Iszero (t1) ->
107                 (* we don't handle cases where t1 doesn't evaluate to an Int *)
108                 let Int i1 = eval t1 g
109                 (* Iszero t1 should evaluate to a Bool *)
110                 in Bool (i1 = 0)
111         | If (t1, t2, t3) ->
112                 (* we don't handle cases where t1 doesn't evaluate to a boolean *)
113                 let Bool b1 = eval t1 g
114                 in if b1 then eval t2 g
115                 else eval t3 g
116         | Makepair (t1, t2) ->
117                 let value1 = eval t1 g
118                 in let value2 = eval t2 g
119                 in Pair (value1, value2)
120         | First (t1) ->
121                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
122                 let Pair (value1, value2) = eval t1 g
123                 in value1
124         ;;
125
126 The complete code is available [here](/code/calculator/calc1.ml).
127
128 ##Adding Function Values##
129
130 Now we want to add function values to our language, so that we can interpret (the abstract syntax trees of) expressions like this:
131
132         let x = 1 in let f = lambda y -> y + x in apply f 2
133
134 What changes do we need to handle this?
135
136 We can begin with our language:
137
138         type term =
139           Intconstant of int
140         | Multiplication of (term * term)
141         | Addition of (term * term)
142         | Variable of char
143         | Let of (char * term * term)
144         | Iszero of term
145         | If of (term * term * term)
146         | Makepair of (term * term)
147         | First of term
148         | Lambda of (char * term)
149         | Apply of (term * term)
150         ;;
151
152 Next, we need to expand our stock of `expressed_value`s to include function values as well. How should we think of these? We've several times mentioned the issue of how to handle free variables in a function's body, like the `x` in `lambda y -> y + x`. We'll follow the usual functional programming standard for these (known as "lexical scoping"), which keeps track of what value `x` has in the function declaration's lexical environment. That shouldn't get shadowed by any different value `x` may have when the function value is later applied. So:
153
154         let x = 1 in let f = lambda y -> y + x in let x = 2 in apply f 2
155
156 should evaluate to `3` not to `4`. To handle this, the function values we construct need to keep track of the present values of all free variables in the function's body. The combination of the function's body and the values of its free variables is called a "function closure." We'll implement these closures in a straightforward though inefficient way: we'll just stash away a copy of the assignment in effect when the function value is being constructed. Our function values also need to keep track of which of their variables are to be bound to the arguments they get applied to. All together, then, we need three pieces of information: which variables are to be bound to arguments, what the function's body is, and something that keeps track of the right values for the free variables in the function body. We'll pack this all together into an additional variant for our `expressed_value` type:
157
158         type expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
159
160 We'd like to define `bound_value`s and `assignment`s just as before:
161
162         type bound_value = expressed_value;;
163         type assignment = (char * bound_value) list;;
164
165 However, note that we have a recursive relation between these types: `expressed_value` is defined partly in terms of `assignment`, which is defined partly in terms of `bound_value`, which is equivalent to `expressed_value`. In OCaml one has to define such types using the following form:
166
167         type bound_value = expressed_value
168         and assignment = (char * bound_value) list
169         and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
170
171 Now our evaluation function needs two further clauses to interpret the two new expression forms `Lambda (...)` and `Apply (...)`:
172
173         let rec eval (t : term) (g : assignment) = match t with
174         ...
175         | Lambda (arg_var, t2) -> Closure (arg_var, t2, g)
176         | Apply (t1, t2) ->
177                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
178                 let Closure (arg_var, body, savedg) = eval t1 g
179                 in let value2 = eval t2 g
180                 (* evaluate body under savedg, except with arg_var bound to value2 *)
181                 in let savedg' = (arg_var, value2) :: savedg
182                 in eval body savedg'
183         ;;
184
185 The complete code is available [here](/code/calculator/calc2.ml).
186
187 ##Adding Recursive Functions##
188
189 There are different ways to include recursion in our calculator. First, let's imagine our language expanded like this:
190
191         let x = 1 in letrec f = lambda y -> if iszero y then x else y * apply f (y - 1) in apply f 3
192
193 where the AST would be:
194
195         Let ('x', Intconstant 1,
196                 Letrec ('f',
197                         Lambda ('y',
198                                 If (Iszero (Variable 'y'),
199                                         Variable 'x',
200                                         Multiplication (Variable 'y',
201                                                 Apply (Variable 'f',
202                                                         Addition (Variable 'y', Intconstant (-1)))))),
203                         Apply (Variable 'f', Intconstant 3)))
204
205 Here is the expanded definition for our language type:
206
207         type term =
208           Intconstant of int
209         | Multiplication of (term * term)
210         | Addition of (term * term)
211         | Variable of char
212         | Let of (char * term * term)
213         | Iszero of term
214         | If of (term * term * term)
215         | Makepair of (term * term)
216         | First of term
217         | Lambda of (char * term)
218         | Apply of (term * term)
219         | Letrec of (char * term * term)
220         ;;
221
222 Now consider what we'll need to do when evaluating a term like `Letrec ('f', Lambda (...), t2)`. The subterm `Lambda (...)` will evaluate to something of the form `Closure ('y', body, savedg)`, where `Variable 'f'` may occur free in `body`. What we'll want to do is to ensure that when `body` is applied, it's applied using not the assignment `savedg` but a modified assignment `savedg'` which binds `'f'` to this very function value. That is, we want to bind `'f'` not to:
223
224         Closure ('y', body, savedg)
225
226 but instead to:
227
228         let orig_closure = Closure ('y', body, savedg)
229         in let savedg' = ('f', orig_closure) :: savedg
230         in let new_closure = Closure ('y', body, savedg')
231         in new_closure
232
233 Except, this isn't quite right. It's almost what we want, but not exactly. Can you see the flaw?
234
235 The flaw is this: inside `new_closure`, what is `'f'` bound to? It's bound by `savedg'` to `orig_closure`, which in turn leaves `'f'` free (or bound to whatever existing value it had according to `savedg`). This isn't what we want. It'll break if we need to make applications of `Variable 'f'` which recurse more than once.
236
237 What we really want is for `'f'` to be bound to `new_closure`, something like this:
238
239         let rec new_closure = Closure ('y', body, ('f', new_closure) :: savedg)
240         in new_closure
241
242 And as a matter of fact, OCaml *does* permit us to recursively define cyclical lists in this way. So a minimal change to our evaluation function would suffice:
243
244         let rec eval (t : term) (g : assignment) = match t with
245         ...
246         | Letrec (var_to_bind, t2, t3) ->
247                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
248                 let Closure (arg_var, body, savedg) = eval t2 g
249         in let rec new_closure = Closure (arg_var, body, (var_to_bind, new_closure) :: savedg)
250         in let g' = (var_to_bind, new_closure) :: g
251                 in eval t3 g'
252         ;;
253          
254 However, this is a somewhat exotic ability in a programming language, so it would be good to work out how to interpret `Letrec (...)` forms without relying on it.
255
256 If we implemented assignments as functions rather than as lists of pairs, the corresponding move would be less exotic. In that case, our `Let (...)` and `Letrec (...)` clauses would look something like this:
257
258
259         | Let (var_to_bind, t2, t3) ->
260                 let value2 = eval t2 g
261                 in let g' = fun var -> if var = var_to_bind then value2 else g var
262                 in eval t3 g'
263         ...
264         | Letrec (var_to_bind, t2, t3) ->
265                 let Closure (arg_var, body, savedg) = eval t2 g
266                 in let rec savedg' = fun var -> if var = var_to_bind then Closure (arg_var, body, savedg') else savedg var
267                 in let g' = fun var -> if var = var_to_bind then Closure (arg_var, body, savedg') else g var
268                 in eval t3 g'
269         ;;
270
271 and this is just a run-of-the-mill use of recursive functions. However, for this exercise we'll continue using lists of pairs, and work out how to interpret `Letrec (...)` forms using them.
272
273 The way we'll do this is that, when we bind a variable to a value, we'll keep track of whether the term was bound via `Let` or `Letrec`. We'll rely on that to interpret pairs of terms like these differently:
274
275         Let ('f',
276                 Intconstant 1,
277                 Let ('f', Lambda ('y', Variable 'f')),
278                 ...)
279
280         Let ('f',
281                 Intconstant 1,
282                 Letrec ('f', Lambda ('y', Variable 'f')),
283                 ...)
284
285 In the first case, an application of `Variable 'f'` to any argument should evaluate to `Int 1`; in the second case, it should evaluate to the same function closure that `Variable 'f'` evaluates to. We'll keep track of which way a variable was bound by expanding our `bound_value` type:
286
287         type bound_value = Nonrecursive of expressed_value |
288                 Recursive_Closure of char * char * term * assignment
289         and assignment = (char * bound_value) list
290         and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
291
292
293 Since we're not permitting ourselves OCaml's ability to recursively define cyclical lists, we're not going to be able to update the saved assignment in a closure when that closure is recursively bound to a variable. Instead, we'll just make a note that variable `'f'` is supposed to be the recursively bound one---by binding it not to `Nonrecursive (Closure (arg_var, body, savedg))` but rather to `Recursive_Closure ('f', arg_var, body, savedg)`. We'll do the work to make the saved assignment recursive in the right way *later*, when we *evaluate* `Variable 'f'`. The result will look like this:
294
295         let rec eval (t : term) (g : assignment) = match t with
296         ...
297         | Variable (var) -> (
298                 (* we don't handle cases where g doesn't bind var to any value *)
299                 match List.assoc var g with
300           | Nonrecursive value -> value
301           | Recursive_Closure (self_var, arg_var, body, savedg) as rec_closure ->
302                           (* we update savedg to bind self_var to rec_closure here *)
303               let savedg' = (self_var, rec_closure) :: savedg
304               in Closure (arg_var, body, savedg')
305         )
306         | Let (var_to_bind, t2, t3) ->
307                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
308            the result of evaluating t2 under the current assignment *)
309                 let value2 = eval t2 g
310                 (* we have to wrap value2 in Nonrecursive *)
311                 in let g' = (var_to_bind, Nonrecursive value2) :: g
312                 in eval t3 g'
313         ...
314         | Lambda (arg_var, t2) -> Closure (arg_var, t2, g)
315         | Apply (t1, t2) ->
316                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
317                 let Closure (arg_var, body, savedg) = eval t1 g
318                 in let value2 = eval t2 g
319                 (* evaluate body under savedg, except with arg_var bound to Nonrecursive value2 *)
320                 in let savedg' = (arg_var, Nonrecursive value2) :: savedg
321                 in eval body savedg'
322         | Letrec (var_to_bind, t2, t3) ->
323                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
324                 let Closure (arg_var, body, savedg) = eval t2 g
325         (* evaluate t3 under a new assignment where var_to_bind has been recursively bound to that function value *) 
326                 in let g' = (var_to_bind, Recursive_Closure (var_to_bind, arg_var, body, savedg)) :: g
327                 in eval t3 g'
328         ;;
329
330 The complete code is available [here](/code/calculator/calc3.ml).
331
332 ##Adding Mutable Cells##
333
334 Next, we'll add mutable cells (explicit-style mutation) to our calculator, as we did in [[week9]].
335
336 We'll add a few more syntactic forms to the language:
337
338         type term =
339           Intconstant of int
340         | Multiplication of (term * term)
341         | Addition of (term * term)
342         | Variable of char
343         | Let of (char * term * term)
344         | Iszero of term
345         | If of (term * term * term)
346         | Makepair of (term * term)
347         | First of term
348         | Lambda of (char * term)
349         | Apply of (term * term)
350         | Letrec of (char * term * term)
351         | Newref of term
352         | Deref of term
353         | Setref of (term * term)
354         ;;
355
356 And we now have to allow for `Mutcell`s as an additional kind of `expressed_value`. These are implemented as wrappers around an index into a `store`:
357
358         type index = int;;
359
360         type bound_value = Nonrecursive of expressed_value |
361                 Recursive_Closure of char * char * term * assignment
362         and assignment = (char * bound_value) list
363         and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment | Mutcell of index;;
364
365         type store = expressed_value list;;
366  
367 Our evaluation function will now expect a `store` argument as well as an `assignment`, and will return an `expressed_value * store` pair:
368
369         let rec eval (t : term) (g : assignment) (s : store) = match t with
370           Intconstant x -> (Int x, s)
371           ...
372         | Variable (var) -> ((
373                 (* we don't handle cases where g doesn't bind var to any value *)
374                 match List.assoc var g with
375           | Nonrecursive value -> value
376           | Recursive_Closure (self_var, arg_var, body, savedg) as rec_closure ->
377                           (* we update savedg to bind self_var to rec_closure here *)
378               let savedg' = (self_var, rec_closure) :: savedg
379               in Closure (arg_var, body, savedg')
380         ), s)
381           ...
382         | Lambda (arg_var, t2) -> (Closure (arg_var, t2, g), s)
383           ...
384
385 also, we'll need to be sure to thread the store argument through the evaluation of any subterms, as here:
386
387         ...
388         | Multiplication (t1, t2) ->
389                 (* we don't handle cases where the subterms don't evaluate to Ints *)
390                 let (Int i1, s') = eval t1 g s
391                 in let (Int i2, s'') = eval t2 g s'
392                 (* Multiplication (t1, t2) should evaluate to an Int *)
393                 in (Int (i1 * i2), s'')
394         | Addition (t1, t2) ->
395                 let (Int i1, s') = eval t1 g s
396                 in let (Int i2, s'') = eval t2 g s'
397                 in (Int (i1 + i2), s'')
398         ...
399         | Let (var_to_bind, t2, t3) ->
400                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
401            the result of evaluating t2 under the current assignment *)
402                 let (value2, s') = eval t2 g s
403                 (* we have to wrap value2 in Nonrecursive *)
404                 in let g' = (var_to_bind, Nonrecursive value2) :: g
405                 in eval t3 g' s'
406         | Iszero (t1) ->
407                 (* we don't handle cases where t1 doesn't evaluate to an Int *)
408                 let (Int i1, s') = eval t1 g s
409                 (* Iszero t1 should evaluate to a Bool *)
410                 in (Bool (i1 = 0), s')
411         ...
412         | Makepair (t1, t2) ->
413                 let (value1, s') = eval t1 g s
414                 in let (value2, s'') = eval t2 g s'
415                 in (Pair (value1, value2), s'')
416         | First (t1) ->
417                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
418                 let (Pair (value1, value2), s') = eval t1 g s
419                 in (value1, s')
420         ...
421         | Apply (t1, t2) ->
422                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
423                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
424                 in let (value2, s'') = eval t2 g s'
425                 (* evaluate body under savedg, except with arg_var bound to Nonrecursive value2 *)
426                 in let savedg' = (arg_var, Nonrecursive value2) :: savedg
427                 in eval body savedg' s''
428         | Letrec (var_to_bind, t2, t3) ->
429                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
430                 let (Closure (arg_var, body, savedg), s') = eval t2 g s
431         (* evaluate t3 under a new assignment where var_to_bind has been recursively bound to that function value *) 
432                 in let g' = (var_to_bind, Recursive_Closure (var_to_bind, arg_var, body, savedg)) :: g
433                 in eval t3 g' s'
434         ...
435
436 The clause for `If (...)` is notable:
437
438         ...
439         | If (t1, t2, t3) ->
440                 (* we don't handle cases where t1 doesn't evaluate to a boolean *)
441                 let (Bool b1, s') = eval t1 g s
442         (* note we thread s' through only one of the then/else clauses *)
443                 in if b1 then eval t2 g s'
444                 else eval t3 g s'
445         ...
446
447 Now we need to formulate the clauses for evaluating the new forms `Newref (...)`, `Deref (...)`, and `Setref (...)`.
448
449         ...
450         | Newref (t1) ->
451                 let (value1, s') = eval t1 g s
452                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
453                 (* now we want to retrieve the next free index in s' *)
454                 in let new_index = List.length s'
455                 (* now we want to insert value1 there; the following is an easy but inefficient way to do it *)
456                 in let s'' = List.append s' [value1]
457                 (* now we return a pair of a wrapped new_index, and the new store *)
458                 in (Mutcell new_index, s'')
459         | Deref (t1) ->
460                 (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
461                 let (Mutcell index1, s') = eval t1 g s
462                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
463                 in (List.nth s' index1, s')
464         | Setref (t1, t2) ->
465                 (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
466                 let (Mutcell index1, s') = eval t1 g s
467                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
468                 in let (new_value, s'') = eval t2 g s'
469                 (* now we create a list which is just like s'' except it has new_value in index1 *)
470                 in let rec replace_nth lst m =
471                         match lst with
472                         | [] -> failwith "list too short"
473                         | x::xs when m = 0 -> new_value :: xs
474                         | x::xs -> x :: replace_nth xs (m - 1)
475                 in let s''' = replace_nth s'' index1
476                 (* we'll arbitrarily return Int 42 as the expressed_value of a Setref operation *)
477                 in (Int 42, s''')
478         ;;
479
480 The complete code is available [here](/code/calculator/calc4.ml).
481
482 ##Adding Mutable Pairs##
483
484 Suppose we wanted to work with pairs where we could mutate either component of the pair. Well, we've already given ourselves pairs, and mutable cells, so we could just work here with pairs of mutable cells. But it might sometimes be more wieldy to work with a structure that fused these two structures together, to give us a mutable pair. With the mutable pair, we wouldn't ask for the first element, and then apply `Deref` to it to get the value it then temporarily contains. Instead, asking for the first element would *constitute* asking for the value the mutable pair then temporarily contains in its first position.
485
486 This means a mutable pair is an interesting hybrid between explicit-style and implicit-style mutation. Looked at one way, it's just a generalization of an explicit mutable cell: it's just that where the mutable cells we implemented before were boxes with only one position, now we have boxes with two positions. Looked at another way, though, mutable pairs are similar to implicit-style mutation: for we don't have separate ways of referring to the first position of the mutable pair, and its dereferenced value. Peeking at the first position *just will be* peeking at its current dereferenced value.
487
488 To keep our codebase smaller, we'll implement mutable pairs instead of, not in addition to, the mutable cells from the previous section. Also, we'll leave out the immutable pairs we've been working with up to this point; in this implementation, all pairs will be mutable.
489
490 This implementation will largely parallel the previous one. Here are the differences. First, we remove the `Newref`, `Deref`, and `Setref` forms from the language. Our existing form `Makepair` will serve to create mutable pairs, and so will take over a role analogous to `Newref`. Our existing form `First` will take over a role analogous to `Deref`. We'll introduce one new form `Setfirst` that will take over a role analogous to `Setref`:
491
492         type term =
493           Intconstant of int
494         | Multiplication of (term * term)
495         | Addition of (term * term)
496         | Variable of char
497         | Let of (char * term * term)
498         | Iszero of term
499         | If of (term * term * term)
500         | Makepair of (term * term)
501         | First of term
502         | Lambda of (char * term)
503         | Apply of (term * term)
504         | Letrec of (char * term * term)
505         | Setfirst of (term * term)
506         ;;
507
508 Our `expressed_value` type changes in two ways: first, we eliminate the `Mutcell` variant added in the previous implementation. Instead, we now have our `Pair` variant wrap `index`es into the `store`:
509
510         type index = int;;
511
512         type bound_value = Nonrecursive of expressed_value |
513                 Recursive_Closure of char * char * term * assignment
514         and assignment = (char * bound_value) list
515         and expressed_value = Int of int | Bool of bool | Pair of index * index | Closure of char * term * assignment;;
516
517         type store = expressed_value list;;
518
519 Finally, here are the changed or added clauses to the evaluation function:
520
521         let rec eval (t : term) (g : assignment) (s : store) = match t with
522         ...
523         | Makepair (t1, t2) ->
524                 let (value1, s') = eval t1 g s
525                 in let (value2, s'') = eval t2 g s'
526         (* now we want to retrieve the next free index in s'' *)
527         in let new_index = List.length s''
528         (* now we want to insert value1 and value2 there; the following is an easy but inefficient way to do it *)
529         in let s''' = List.append s'' [value1; value2]
530                 in (Pair (new_index, new_index + 1), s''')
531         | First (t1) ->
532                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
533                 let (Pair (index1, index2), s') = eval t1 g s
534         (* note that s' may be different from s, if t1 itself contained any mutation operations *)
535         in (List.nth s' index1, s')
536         ...
537     | Setfirst (t1, t2) ->
538         (* we don't handle cases where t1 doesn't evaluate to a Pair *)
539         let (Pair (index1, index2), s') = eval t1 g s
540         (* note that s' may be different from s, if t1 itself contained any mutation operations *)
541         in let (new_value, s'') = eval t2 g s'
542         (* now we create a list which is just like s'' except it has new_value in index1 *)
543         in let rec replace_nth lst m =
544             match lst with
545             | [] -> failwith "list too short"
546             | x::xs when m = 0 -> new_value :: xs
547             | x::xs -> x :: replace_nth xs (m - 1)
548         in let s''' = replace_nth s'' index1
549         in (Int 42, s''')
550         ;;
551
552 Compare these to the clauses for `Newref`, `Deref`, and `Setref` in the previous implementation.
553
554 The complete code is available [here](/code/calculator/calc5.ml).
555
556 ##Adding Implicit Mutation##
557
558 Next we implement implicit-style mutation, as we did in [[week9]]. Here we don't have any explicit reference cells or mutable pairs; we'll return pairs back to their original immutable form. Instead, all variables will have mutable bindings. New reference cells will be implicitly introduced by the `Let` form. They'll also be implicitly introduced by the `Apply` form---we didn't have function values on the table during the [[week9]] discussion, so this didn't come up then. The reason we introduce new reference cells when `Apply`ing a function value to arguments is that we don't want mutation of those arguments inside the body of the function to propagate out and affect the reference cell that may have supplied the argument. When we call functions in this implementation, we just want to supply them with *values*, not with the reference cells we may be drawing those values from. Below, after we discuss *aliases*, we'll consider another strategy, where function bodies are given the ability to mutate the reference cells implicitly associated with the arguments they're supplied.
559
560 Our language for the present implementation will be the language for the calculator with recursive functions, with one added syntactic form, `Change (...)`:
561
562         type term =
563           Intconstant of int
564         | Multiplication of (term * term)
565         | Addition of (term * term)
566         | Variable of char
567         | Let of (char * term * term)
568         | Iszero of term
569         | If of (term * term * term)
570         | Makepair of (term * term)
571         | First of term
572         | Lambda of (char * term)
573         | Apply of (term * term)
574         | Letrec of (char * term * term)
575         | Change of (char * term * term)
576         ;;
577
578 In the present implementation, we separate the roles of the `bound_value` and `expressed_value` types. As we discussed in [[week9]], our assignment will bind all variables to indexes in the store, and the latter will contain the `expressed_value`s that the variables evaluate to. A consequence of this is that our definitions of the `bound_value` and `expressed_value` types no longer need to be mutually recursive:
579          
580         type index = int;;
581          
582         type bound_value = index;;
583         type assignment = (char * bound_value) list;;
584         type expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
585          
586         type store = expressed_value list;;
587
588 Our evaluation function still interacts with a `store` argument in much the same way it did with explicit-style mutation. The clause for `Variable ...` works differently, because all `expressed_value`s now need to be retrieved from the `store`:
589          
590         let rec eval (t : term) (g : assignment) (s : store) = match t with
591         ...
592         | Variable (var) ->
593                 (* we don't handle cases where g doesn't bind var to any value *)
594                 let index = List.assoc var g
595                 (* get value stored at location index in s *)
596                 in let value = List.nth s index
597                 in (value, s)
598         ...
599
600 So this clause takes over the roles that were separately played by `Variable` and `Deref` in the calculator with mutable cells. The role played by `Newref` is absorbed into `Let`, `Letrec`, and `Apply`:
601
602         ...
603         | Let (var_to_bind, t2, t3) ->
604                 let (value2, s') = eval t2 g s
605                 (* note that s' may be different from s, if t2 itself contained any mutation operations *)
606                 (* get next free index in s' *)
607                 in let new_index = List.length s'
608                 (* now we want to insert value2 there; the following is an easy but inefficient way to do it *)
609                 in let s'' = List.append s' [value2]
610                 (* bind var_to_bind to location new_index in the store *)
611                 in let g' = ((var_to_bind, new_index) :: g)
612                 in eval t3 g' s''
613         ...
614         | Apply (t1, t2) ->
615                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
616                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
617                 in let (value2, s'') = eval t2 g s'
618                 (* evaluate body under savedg, except with arg_var bound to a new location containing value2 *)
619                 in let new_index = List.length s''
620                 in let s''' = List.append s'' [value2]
621                 in let savedg' = (arg_var, new_index) :: savedg
622                 in eval body savedg' s'''
623         ...
624
625 `Letrec` requires some reworking from what we had before. Earlier, we resorted to a `Recursive_Closure` variant on `bound_value`s because it gave us a non-exotic way to update the `savedg` component of a `Closure` to refer to a `new_closure` that contained that very updated `savedg`. Now that we we've got a mutation-supporting infrastructure in place, we can do this directly, without needing the unwieldy `Recursive_Closure` wrapper:
626
627         ...
628         | Letrec (var_to_bind, t2, t3) ->
629                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
630                 let (Closure (arg_var, body, savedg), s') = eval t2 g s
631                 in let new_index = List.length s'
632                 in let savedg' = (var_to_bind, new_index) :: savedg
633                 in let new_closure = Closure (arg_var, body, savedg')
634                 in let s'' = List.append s' [new_closure]
635                 in let g' = (var_to_bind, new_index) :: g
636                 in eval t3 g' s''
637         ...
638
639 Finally, here is the clause for `Change (...)`, which takes over the role earlier played by `Setref`: 
640
641         ...
642         | Change (var, t2, t3) ->
643                 (* we don't handle cases where g doesn't bind var to any value *)
644                 let index = List.assoc var g
645                 in let (value2, s') = eval t2 g s
646                 (* note that s' may be different from s, if t2 itself contained any mutation operations *)
647                 (* now we create a list which is just like s' except it has value2 at index *)
648                 in let rec replace_nth lst m =
649                         match lst with
650                         | [] -> failwith "list too short"
651                         | x::xs when m = 0 -> value2 :: xs
652                         | x::xs -> x :: replace_nth xs (m - 1)
653                 in let s'' = replace_nth s' index
654                 (* evaluate t3 using original assignment function and new store *)
655                 in eval t3 g s''
656         ;;
657
658 Note that because the `savedg` component of a `Closure` keeps track of which `index`es in the store free variables were bound to, the values at those `index`es can later be changed, and later applications of the `Closure` will use the changed values.
659
660 The complete code is available [here](/code/calculator/calc6.ml).
661
662 ##Adding Aliasing and Passing by Reference##
663
664         type term =
665           Intconstant of int
666         | Multiplication of (term * term)
667         | Addition of (term * term)
668         | Variable of char
669         | Let of (char * term * term)
670         | Iszero of term
671         | If of (term * term * term)
672         | Makepair of (term * term)
673         | First of term
674         | Lambda of (char * term)
675         | Apply of (term * term)
676         | Letrec of (char * term * term)
677         | Change of (char * term * term)
678         | Alias of (char * char * term)
679         | Applyalias of (term * char)
680         ;;
681  
682         let rec eval (t : term) (g : assignment) (s : store) = match t with
683         ...
684         | Alias (var_to_bind, orig_var, t3) ->
685                 (* we don't handle cases where g doesn't bind orig_var to any value *)
686                 let index = List.assoc orig_var g
687                 (* bind var_to_bind to the same index in the store *)
688                 in let g' = ((var_to_bind, index) :: g)
689                 in eval t3 g' s
690         | Applyalias (t1, var) ->
691                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
692                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
693                 (* we don't handle cases where g doesn't bind var to any value *)
694                 in let index = List.assoc var g
695                 (* evaluate body under savedg, except with arg_var bound to existing index *)
696                 in let savedg' = (arg_var, index) :: savedg
697                 in eval body savedg' s'
698         ;;
699
700 The complete code is available [here](/code/calculator/calc7.ml).
701