d6654db6101854ce5bcceaff8879cc647ef67a83
[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 week 9, 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 expand some of the clauses in the `eval` function for clarity, and we rename a few variables:
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         let rec eval (t : term) (g : assignment) = match t with
84           Intconstant x -> Int x
85         | Multiplication (t1, t2) ->
86                 (* we don't handle cases where the subterms don't evaluate to Ints *)
87                 let Int i1 = eval t1 g
88                 in let Int i2 = eval t2 g
89                 (* Multiplication (t1, t2) should evaluate to an Int *)
90                 in Int (i1 * i2)
91         | Addition (t1, t2) ->
92                 let Int i1 = eval t1 g
93                 in let Int i2 = eval t2 g
94                 in Int (i1 + i2)
95         | Variable (var) ->
96                 (* we don't handle cases where g doesn't bind var to any value *)
97                 List.assoc var g
98         | Let (var_to_bind, t2, t3) ->
99                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
100                    the result of evaluating t2 under the current assignment *)
101                 let value2 = eval t2 g
102                 in let g' = (var_to_bind, value2) :: g
103                 in eval t3 g'
104         | Iszero (t1) ->
105                 (* we don't handle cases where t1 doesn't evaluate to an Int *)
106                 let Int i1 = eval t1 g
107                 (* Iszero t1 should evaluate to a Bool *)
108                 in Bool (i1 = 0)
109         | If (t1, t2, t3) ->
110                 (* we don't handle cases where t1 doesn't evaluate to a boolean *)
111                 let Bool b1 = eval t1 g
112                 in if b1 then eval t2 g
113                 else eval t3 g
114         | Makepair (t1, t2) ->
115                 let value1 = eval t1 g
116                 in let value2 = eval t2 g
117                 in Pair (value1, value2)
118         | First (t1) ->
119                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
120                 let Pair (value1, value2) = eval t1 g
121                 in value1
122         ;;
123
124 The complete code is available [here](/code/calculator/calc1.ml).
125
126 ##Adding Function Values##
127
128 Now we want to add function values to our language, so that we can interpret (the abstract syntax trees of) expressions like this:
129
130         let x = 1 in let f = lambda y -> y + x in apply f 2
131
132 What changes do we need to handle this?
133
134 We can begin with our language:
135
136         type term =
137           Intconstant of int
138         | Multiplication of (term * term)
139         | Addition of (term * term)
140         | Variable of char
141         | Let of (char * term * term)
142         | Iszero of term
143         | If of (term * term * term)
144         | Makepair of (term * term)
145         | First of term
146         | Lambda of (char * term)
147         | Apply of (term * term)
148         ;;
149
150 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:
151
152         let x = 1 in let f = lambda y -> y + x in let x = 2 in apply f 2
153
154 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:
155
156         type expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
157
158 We'd like to define `bound_value`s and `assignment`s just as before:
159
160         type bound_value = expressed_value;;
161         type assignment = (char * bound_value) list;;
162
163 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:
164
165         type bound_value = expressed_value
166         and assignment = (char * bound_value) list
167         and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
168
169 Now our evaluation function needs two further clauses to interpret the two new expression forms `Lambda (...)` and `Apply (...)`:
170
171         let rec eval (t : term) (g : assignment) = match t with
172         ...
173         | Lambda (arg_var, t2) -> Closure (arg_var, t2, g)
174         | Apply (t1, t2) ->
175                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
176                 let Closure (arg_var, body, savedg) = eval t1 g
177                 in let value2 = eval t2 g
178                 (* evaluate body under savedg, except with arg_var bound to value2 *)
179                 in let savedg' = (arg_var, value2) :: savedg
180                 in eval body savedg'
181         ;;
182
183 The complete code is available [here](/code/calculator/calc2.ml).
184
185 ##Adding Recursive Functions##
186
187 There are different ways to include recursion in our calculator. First, let's imagine our language expanded like this:
188
189         let x = 1 in letrec f = lambda y -> if iszero y then x else y * apply f (y - 1) in apply f 3
190
191 where the AST would be:
192
193         Let ('x', Intconstant 1,
194                 Letrec ('f',
195                         Lambda ('y',
196                                 If (Iszero (Variable 'y'),
197                                         Variable 'x',
198                                         Multiplication (Variable 'y',
199                                                 Apply (Variable 'f',
200                                                         Addition (Variable 'y', Intconstant (-1)))))),
201                         Apply (Variable 'f', Intconstant 3)))
202
203 Here is the expanded definition for our language type:
204
205         type term =
206           Intconstant of int
207         | Multiplication of (term * term)
208         | Addition of (term * term)
209         | Variable of char
210         | Let of (char * term * term)
211         | Iszero of term
212         | If of (term * term * term)
213         | Makepair of (term * term)
214         | First of term
215         | Lambda of (char * term)
216         | Apply of (term * term)
217         | Letrec of (char * term * term)
218         ;;
219
220 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:
221
222         Closure ('y', body, savedg)
223
224 but instead to:
225
226         let orig_closure = Closure ('y', body, savedg)
227         in let savedg' = ('f', orig_closure) :: savedg
228         in let new_closure = Closure ('y', body, savedg')
229         in new_closure
230
231 Except, this isn't quite right. It's almost what we want, but not exactly. Can you see the flaw?
232
233 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.
234
235 What we really want is for `'f'` to be bound to `new_closure`, something like this:
236
237         let rec new_closure = Closure ('y', body, ('f', new_closure) :: savedg)
238         in new_closure
239
240 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:
241
242         let rec eval (t : term) (g : assignment) = match t with
243         ...
244         | Letrec (var_to_bind, t2, t3) ->
245                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
246                 let Closure (arg_var, body, savedg) = eval t2 g
247         in let rec new_closure = Closure (arg_var, body, (var_to_bind, new_closure) :: savedg)
248         in let g' = (var_to_bind, new_closure) :: g
249                 in eval t3 g'
250         ;;
251          
252 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.
253
254 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:
255
256
257         | Let (var_to_bind, t2, t3) ->
258                 let value2 = eval t2 g
259                 in let g' = fun var -> if var = var_to_bind then value2 else g var
260                 in eval t3 g'
261         ...
262         | Letrec (var_to_bind, t2, t3) ->
263                 let Closure (arg_var, body, savedg) = eval t2 g
264                 in let rec savedg' = fun var -> if var = var_to_bind then Closure (arg_var, body, savedg') else savedg var
265                 in let g' = fun var -> if var = var_to_bind then Closure (arg_var, body, savedg') else g var
266                 in eval t3 g'
267         ;;
268
269 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.
270
271 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:
272
273         Let ('f',
274                 Intconstant 1,
275                 Let ('f', Lambda ('y', Variable 'f')),
276                 ...)
277
278         Let ('f',
279                 Intconstant 1,
280                 Letrec ('f', Lambda ('y', Variable 'f')),
281                 ...)
282
283 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:
284
285         type bound_value = Nonrecursive of expressed_value |
286                 Recursive_Closure of char * char * term * assignment
287         and assignment = (char * bound_value) list
288         and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
289
290
291 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:
292
293         let rec eval (t : term) (g : assignment) = match t with
294         ...
295         | Variable (var) -> (
296                 (* we don't handle cases where g doesn't bind var to any value *)
297                 match List.assoc var g with
298           | Nonrecursive value -> value
299           | Recursive_Closure (self_var, arg_var, body, savedg) as rec_closure ->
300                           (* we update savedg to bind self_var to rec_closure here *)
301               let savedg' = (self_var, rec_closure) :: savedg
302               in Closure (arg_var, body, savedg')
303         )
304         | Let (var_to_bind, t2, t3) ->
305                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
306            the result of evaluating t2 under the current assignment *)
307                 let value2 = eval t2 g
308                 (* we have to wrap value2 in Nonrecursive *)
309                 in let g' = (var_to_bind, Nonrecursive value2) :: g
310                 in eval t3 g'
311         ...
312         | Lambda (arg_var, t2) -> Closure (arg_var, t2, g)
313         | Apply (t1, t2) ->
314                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
315                 let Closure (arg_var, body, savedg) = eval t1 g
316                 in let value2 = eval t2 g
317                 (* evaluate body under savedg, except with arg_var bound to Nonrecursive value2 *)
318                 in let savedg' = (arg_var, Nonrecursive value2) :: savedg
319                 in eval body savedg'
320         | Letrec (var_to_bind, t2, t3) ->
321                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
322                 let Closure (arg_var, body, savedg) = eval t2 g
323         (* evaluate t3 under a new assignment where var_to_bind has been recursively bound to that function value *) 
324                 in let g' = (var_to_bind, Recursive_Closure (var_to_bind, arg_var, body, savedg)) :: g
325                 in eval t3 g'
326         ;;
327
328 The complete code is available [here](/code/calculator/calc3.ml).
329
330 ##Adding Mutable Cells##
331
332 Next, we'll add mutable cells (explicit-style mutation) to our calculator, as we did in [[week9]].
333
334 We'll add a few more syntactic forms to the language:
335
336         type term =
337           Intconstant of int
338         | Multiplication of (term * term)
339         | Addition of (term * term)
340         | Variable of char
341         | Let of (char * term * term)
342         | Iszero of term
343         | If of (term * term * term)
344         | Makepair of (term * term)
345         | First of term
346         | Lambda of (char * term)
347         | Apply of (term * term)
348         | Letrec of (char * term * term)
349         | Newref of term
350         | Deref of term
351         | Setref of (term * term)
352         ;;
353
354 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`:
355
356         type index = int;;
357
358         type bound_value = Nonrecursive of expressed_value |
359                 Recursive_Closure of char * char * term * assignment
360         and assignment = (char * bound_value) list
361         and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment | Mutcell of index;;
362
363         type store = expressed_value list;;
364  
365 Our evaluation function will now expect a `store` argument as well as an `assignment`, and will return an `expressed_value * store` pair:
366
367         let rec eval (t : term) (g : assignment) (s : store) = match t with
368           Intconstant x -> (Int x, s)
369           ...
370         | Variable (var) -> (
371                 (* we don't handle cases where g doesn't bind var to any value *)
372                 match List.assoc var g with
373           | Nonrecursive value -> value
374           | Recursive_Closure (self_var, arg_var, body, savedg) as rec_closure ->
375                           (* we update savedg to bind self_var to rec_closure here *)
376               let savedg' = (self_var, rec_closure) :: savedg
377               in Closure (arg_var, body, savedg')
378         ), s
379           ...
380         | Lambda (arg_var, t2) -> (Closure (arg_var, t2, g), s)
381           ...
382
383 also, we'll need to be sure to thread the store argument through the evaluation of any subterms, as here:
384
385         ...
386         | Multiplication (t1, t2) ->
387                 (* we don't handle cases where the subterms don't evaluate to Ints *)
388                 let (Int i1, s') = eval t1 g s
389                 in let (Int i2, s'') = eval t2 g s'
390                 (* Multiplication (t1, t2) should evaluate to an Int *)
391                 in (Int (i1 * i2), s'')
392         | Addition (t1, t2) ->
393                 let (Int i1, s') = eval t1 g s
394                 in let (Int i2, s'') = eval t2 g s'
395                 in (Int (i1 + i2), s'')
396         ...
397         | Let (var_to_bind, t2, t3) ->
398                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
399            the result of evaluating t2 under the current assignment *)
400                 let (value2, s') = eval t2 g s
401                 (* we have to wrap value2 in Nonrecursive *)
402                 in let g' = (var_to_bind, Nonrecursive value2) :: g
403                 in eval t3 g' s'
404         | Iszero (t1) ->
405                 (* we don't handle cases where t1 doesn't evaluate to an Int *)
406                 let (Int i1, s') = eval t1 g s
407                 (* Iszero t1 should evaluate to a Bool *)
408                 in (Bool (i1 = 0), s')
409         ...
410         | Makepair (t1, t2) ->
411                 let (value1, s') = eval t1 g s
412                 in let (value2, s'') = eval t2 g s'
413                 in (Pair (value1, value2), s'')
414         | First (t1) ->
415                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
416                 let (Pair (value1, value2), s') = eval t1 g s
417                 in (value1, s')
418         ...
419         | Apply (t1, t2) ->
420                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
421                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
422                 in let (value2, s'') = eval t2 g s'
423                 (* evaluate body under savedg, except with arg_var bound to Nonrecursive value2 *)
424                 in let savedg' = (arg_var, Nonrecursive value2) :: savedg
425                 in eval body savedg' s''
426         | Letrec (var_to_bind, t2, t3) ->
427                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
428                 let (Closure (arg_var, body, savedg), s') = eval t2 g s
429         (* evaluate t3 under a new assignment where var_to_bind has been recursively bound to that function value *) 
430                 in let g' = (var_to_bind, Recursive_Closure (var_to_bind, arg_var, body, savedg)) :: g
431                 in eval t3 g' s'
432         ...
433
434 The clause for `If (...)` is notable:
435
436         ...
437         | If (t1, t2, t3) ->
438                 (* we don't handle cases where t1 doesn't evaluate to a boolean *)
439                 let (Bool b1, s') = eval t1 g s
440         (* note we thread s' through only one of the then/else clauses *)
441                 in if b1 then eval t2 g s'
442                 else eval t3 g s'
443         ...
444
445 Now we need to formulate the clauses for evaluating the new forms `Newref (...)`, `Deref (...)`, and `Setref (...)`.
446
447         ...
448         | Newref (t1) ->
449                 let (starting_val, s') = eval t1 g s
450                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
451                 (* now we want to retrieve the next free index in s' *)
452                 in let new_index = List.length s'
453                 (* now we want to insert starting_val there; the following is an easy but inefficient way to do it *)
454                 in let s'' = List.append s' [starting_val]
455                 (* now we return a pair of a wrapped new_index, and the new store *)
456                 in (Mutcell new_index, s'')
457         | Deref (t1) ->
458                 (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
459                 let (Mutcell index1, s') = eval t1 g s
460                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
461                 in (List.nth s' index1, s')
462         | Setref (t1, t2) ->
463                 (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
464                 let (Mutcell index1, s') = eval t1 g s
465                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
466                 in let (new_value, s'') = eval t2 g s'
467                 (* now we create a list which is just like s'' except it has new_value in index1 *)
468                 in let rec replace_nth lst m =
469                         match lst with
470                         | [] -> failwith "list too short"
471                         | x::xs when m = 0 -> new_value :: xs
472                         | x::xs -> x :: replace_nth xs (m - 1)
473                 in let s''' = replace_nth s'' index1
474                 (* we'll arbitrarily return Int 42 as the expressed_value of a Setref operation *)
475                 in (Int 42, s''')
476         ;;
477
478 The complete code is available [here](/code/calculator/calc4.ml).
479
480 ##Adding Mutable Pairs##
481
482 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.
483
484 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.
485
486 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.
487
488 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`:
489
490         type term =
491           Intconstant of int
492         | Multiplication of (term * term)
493         | Addition of (term * term)
494         | Variable of char
495         | Let of (char * term * term)
496         | Iszero of term
497         | If of (term * term * term)
498         | Makepair of (term * term)
499         | First of term
500         | Lambda of (char * term)
501         | Apply of (term * term)
502         | Letrec of (char * term * term)
503         | Setfirst of (term * term)
504         ;;
505
506 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`:
507
508         type index = int;;
509
510         type bound_value = Nonrecursive of expressed_value |
511                 Recursive_Closure of char * char * term * assignment
512         and assignment = (char * bound_value) list
513         and expressed_value = Int of int | Bool of bool | Pair of index * index | Closure of char * term * assignment;;
514
515         type store = expressed_value list;;
516
517 Finally, here are the changed or added clauses to the evaluation function:
518
519         let rec eval (t : term) (g : assignment) (s : store) = match t with
520         ...
521         | Makepair (t1, t2) ->
522                 let (value1, s') = eval t1 g s
523                 in let (value2, s'') = eval t2 g s'
524         (* now we want to retrieve the next free index in s'' *)
525         in let new_index = List.length s''
526         (* now we want to insert value1 and value2 there; the following is an easy but inefficient way to do it *)
527         in let s''' = List.append s'' [value1; value2]
528                 in (Pair (new_index, new_index + 1), s''')
529         | First (t1) ->
530                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
531                 let (Pair (index1, index2), s') = eval t1 g s
532         (* note that s' may be different from s, if t1 itself contained any mutation operations *)
533         in (List.nth s' index1, s')
534         ...
535     | Setfirst (t1, t2) ->
536         (* we don't handle cases where t1 doesn't evaluate to a Pair *)
537         let (Pair (index1, index2), s') = eval t1 g s
538         (* note that s' may be different from s, if t1 itself contained any mutation operations *)
539         in let (new_value, s'') = eval t2 g s'
540         (* now we create a list which is just like s'' except it has new_value in index1 *)
541         in let rec replace_nth lst m =
542             match lst with
543             | [] -> failwith "list too short"
544             | x::xs when m = 0 -> new_value :: xs
545             | x::xs -> x :: replace_nth xs (m - 1)
546         in let s''' = replace_nth s'' index1
547         in (Int 42, s''')
548         ;;
549
550 Compare these to the clauses for `Newref`, `Deref`, and `Setref` in the previous implementation.
551
552 The complete code is available [here](/code/calculator/calc5.ml).
553
554 ##Adding Implicit Mutation##
555
556 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.
557
558 Our language for the present implementation will be the language for the calculator with recursive functions, with one added syntactic form, `Change (...)`:
559
560         type term =
561           Intconstant of int
562         | Multiplication of (term * term)
563         | Addition of (term * term)
564         | Variable of char
565         | Let of (char * term * term)
566         | Iszero of term
567         | If of (term * term * term)
568         | Makepair of (term * term)
569         | First of term
570         | Lambda of (char * term)
571         | Apply of (term * term)
572         | Letrec of (char * term * term)
573         | Change of (char * term * term)
574         ;;
575
576 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:
577          
578         type index = int;;
579          
580         type bound_value = index;;
581         type assignment = (char * bound_value) list;;
582         type expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment;;
583          
584         type store = expressed_value list;;
585
586 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`:
587          
588         let rec eval (t : term) (g : assignment) (s : store) = match t with
589         ...
590         | Variable (var) ->
591                 (* we don't handle cases where g doesn't bind var to any value *)
592                 let index = List.assoc var g
593                 (* get value stored at location index in s *)
594                 in let value = List.nth s index
595                 in (value, s)
596         ...
597
598 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`:
599
600         ...
601         | Let (var_to_bind, t2, t3) ->
602                 let (value2, s') = eval t2 g s
603                 (* note that s' may be different from s, if t2 itself contained any mutation operations *)
604                 (* get next free index in s' *)
605                 in let new_index = List.length s'
606                 (* now we want to insert value2 there; the following is an easy but inefficient way to do it *)
607                 in let s'' = List.append s' [value2]
608                 (* bind var_to_bind to location new_index in the store *)
609                 in let g' = ((var_to_bind, new_index) :: g)
610                 in eval t3 g' s''
611         ...
612         | Apply (t1, t2) ->
613                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
614                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
615                 in let (value2, s'') = eval t2 g s'
616                 (* evaluate body under savedg, except with arg_var bound to a new location containing value2 *)
617                 in let new_index = List.length s''
618                 in let s''' = List.append s'' [value2]
619                 in let savedg' = (arg_var, new_index) :: savedg
620                 in eval body savedg' s'''
621         ...
622
623 `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:
624
625         ...
626         | Letrec (var_to_bind, t2, t3) ->
627                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
628                 let (Closure (arg_var, body, savedg), s') = eval t2 g s
629                 in let new_index = List.length s'
630                 in let savedg' = (var_to_bind, new_index) :: savedg
631                 in let new_closure = Closure (arg_var, body, savedg')
632                 in let s'' = List.append s' [new_closure]
633                 in let g' = (var_to_bind, new_index) :: g
634                 in eval t3 g' s''
635         ...
636
637 Finally, here is the clause for `Change (...)`, which takes over the role earlier played by `Setref`: 
638
639         ...
640         | Change (var, t2, t3) ->
641                 (* we don't handle cases where g doesn't bind var to any value *)
642                 let index = List.assoc var g
643                 in let (value2, s') = eval t2 g s
644                 (* note that s' may be different from s, if t2 itself contained any mutation operations *)
645                 (* now we create a list which is just like s' except it has value2 at index *)
646                 in let rec replace_nth lst m =
647                         match lst with
648                         | [] -> failwith "list too short"
649                         | x::xs when m = 0 -> value2 :: xs
650                         | x::xs -> x :: replace_nth xs (m - 1)
651                 in let s'' = replace_nth s' index
652                 (* evaluate t3 using original assignment function and new store *)
653                 in eval t3 g s''
654         ;;
655
656 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.
657
658 The complete code is available [here](/code/calculator/calc6.ml).
659
660 ##Adding Aliasing and Passing by Reference##
661
662         type term =
663           Intconstant of int
664         | Multiplication of (term * term)
665         | Addition of (term * term)
666         | Variable of char
667         | Let of (char * term * term)
668         | Iszero of term
669         | If of (term * term * term)
670         | Makepair of (term * term)
671         | First of term
672         | Lambda of (char * term)
673         | Apply of (term * term)
674         | Letrec of (char * term * term)
675         | Change of (char * term * term)
676         | Alias of (char * char * term)
677         | Applyalias of (term * char)
678         ;;
679  
680         let rec eval (t : term) (g : assignment) (s : store) = match t with
681         ...
682         | Alias (var_to_bind, orig_var, t3) ->
683                 (* we don't handle cases where g doesn't bind orig_var to any value *)
684                 let index = List.assoc orig_var g
685                 (* bind var_to_bind to the same index in the store *)
686                 in let g' = ((var_to_bind, index) :: g)
687                 in eval t3 g' s
688         | Applyalias (t1, var) ->
689                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
690                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
691                 (* we don't handle cases where g doesn't bind var to any value *)
692                 in let index = List.assoc var g
693                 (* evaluate body under savedg, except with arg_var bound to existing index *)
694                 in let savedg' = (arg_var, index) :: savedg
695                 in eval body savedg' s'
696         ;;
697
698 The complete code is available [here](/code/calculator/calc7.ml).
699