4e334a03d327df44f2bffc4ccb8c54f1131ec3bc
[lambda.git] / week9.mdwn
1 [[!toc]]
2
3 The seminar is now going to begin talking about more **imperatival** or **effect**-like elements in programming languages. The only effect-like element we've encountered so far is the possibility of divergence, in languages that permit fixed point combinators and so have the full power of recursion. What it means for something to be effect-like, and why this counts as an example of such, will emerge.
4
5 Other effect-like elements in a language include: printing (recall the [[damn]] example at the start of term); continuations (also foreshadowed in the [[damn]] example) and exceptions (foreshadowed in our discussion of abortable list traversals in [[week4]]); and **mutation**. This last notion is our topic this week.
6
7
8 ## Mutation##
9
10 What is mutation? It's helpful to build up to this in a series of fragments. For pedagogical purposes, we'll be using a made-up language that's syntactically similar to, but not quite the same as, OCaml.
11
12 Recall from earlier discussions that the following two forms are equivalent:
13
14         [A] let x be EXPRESSION in
15                   BODY
16
17                 (lambda (x) -> BODY) (EXPRESSION)
18
19 This should seem entirely familiar:
20
21         [B] let x be 1 + 2 in
22                   let y be 10 in
23                         (x + y, x + 20)
24                                                                 ; evaluates to (13, 23)
25
26 In fragment [B], we bound the variables `x` and `y` to `int`s. We can also bind variables to function values, as here:
27
28         [C] let f be (lambda (x, y) -> x + y + 1) in
29                   (f (10, 2), f (20, 2))
30                                                                 ; evaluates to (13, 23)
31
32 If the expression that evaluates to a function value has a free variable in it, like `y` in the next fragment, it's interpreted as bound to whatever value `y` has in the surrounding lexical context:
33
34         [D] let y be 3 in
35                   let f be (lambda (x) -> x + y) in
36                         (f (10), f (20))
37                                                                 ; evaluates to (13, 23)
38
39 Other choices about how to interpret free variables are also possible (you can read about "lexical scope" versus "dynamic scope"), but what we do here is the norm in functional programming languages, and seems to be easiest for programmers to reason about.
40
41 In our next fragment, we re-use a variable that had been bound to another value in a wider context:
42
43         [E] let y be 2 in
44                   let y be 3 in
45                         (y + 10, y + 20)
46                                                                 ; evaluates to (13, 23)
47
48 As you can see, the narrowest assignment is what's effective. This is just like in predicate logic: consider <code>&exist;y (Fy and &exist;y ~Fy)</code>. The computer-science terminology to describe this is that the narrower assignment of `y` to the value 3 **shadows** the wider assignment to 2.
49
50 I call attention to this because you might casually describe it as "changing the value that y is assigned to." What we'll go on to see is a more exotic phenomenon that merits that description better.
51
52 Sometimes the shadowing is merely temporary, as here:
53
54         [F] let y be 2 in
55                   let f be (lambda (x) ->
56                         let y be 3 in
57                           ; here the most local assignment to y applies
58                           x + y
59                   ) in
60                         ; here the assignment of 3 to y has expired
61                         (f (10), y, f (20))
62                                                                 ; evaluates to (13, 2, 23)
63
64 OK, now we're ready for our main event, **mutable variables.** We'll introduce new syntax to express an operation where we're not shadowing a wider assignment, but *changing* the original assignment:
65
66         [G] let y be 2 in
67                   let f be (lambda (x) ->
68                         change y to 3 then
69                           x + y
70                   ) in
71                         ; here the change in what value y was assigned *sticks*
72                         ; because we *updated* the value of the original variable y
73                         ; instead of introducing a new y with a narrower scope
74                         (f (10), y, f (19))
75                                                                 ; evaluates to (13, 3, 23)
76
77 In languages that have native syntax for this, there are two styles in which it can be expressed. The *implicit style* is exemplified in fragment [G] above, and also in languages like C:
78
79         {
80                 int y = 2;    // this is like "let y be 2 in ..."
81                 ...
82                 y = 3;        // this is like "change y to 3 then ..."
83                 return x + y; // this is like "x + y"
84         }
85
86 A different possibility is the *explicit style* for handling mutation. Here we explicitly create and refer to new "reference cells" to hold our values. When we change a variable's value, the variable stays associated with the same reference cell, but that reference cell's contents get modified. The same thing happens in the semantic machinery underlying implicit-style mutable variables, but there it's implicit---the reference cells aren't themselves expressed by any term in the object language. In explicit-style mutation, they are. OCaml has explicit-style mutation. It looks like this:
87
88         let ycell = ref 2       (* this creates a new reference cell *)
89         ...
90         in let () = ycell := 3  (* this changes the contents of that cell to 3 *)
91                                                         (* the return value of doing so is () *)
92                                                         (* other return values could also be reasonable: *)
93                                                         (* such as the old value of ycell, the new value, an arbitrary int, and so on *)
94         in x + !ycell;;                 (* the !ycell operation "dereferences" the cell---it retrieves the value it contains *)
95
96 Scheme is similar. There are various sorts of reference cells available in Scheme. The one most like OCaml's `ref` is a `box`. Here's how we'd write the same fragment in Scheme:
97
98         (let ([ycell (box 2)])
99                 ...
100                 (set-box! ycell 3)
101                 (+ x (unbox ycell)))
102
103 When dealing with explicit-style mutation, there's a difference between the types and values of `ycell` and `!ycell` (or `(unbox ycell)`). The former has the type `int ref`: the variable `ycell` is assigned a reference cell that contains an `int`. The latter has the type `int`, and has whatever value is now stored in the relevant reference cell. In an implicit-style framework though, we only have the resources to refer to the contents of the relevant reference cell. `y` in fragment [G] or the C snippet above has the type `int`, and only ever evaluates to `int` values.
104
105
106 ##Controlling order##
107
108 When we're dealing with mutable variables (or any other kind of effect), order matters. For example, it would make a big difference whether I evaluated `let z = !ycell` before or after evaluating `ycell := !ycell + 1`. Before this point, order never mattered except sometimes it played a role in avoiding divergence.
109
110 OCaml does *not* guarantee what order expressions will be evaluated in arbitrary contexts. For example, in the following fragment, you cannot rely on `expression_a` being evaluated before `expression_b` before `expression_c`:
111
112         let triple = (expression_a, expression_b, expression_c)
113
114 OCaml does however guarantee that different let-expressions are evaluated in the order they lexically appear. So in the following fragment, `expression_a` *will* be evaluated before `expression_b` and that before `expression_c`:
115
116         let a = expression_a
117                 in let b = expression_b
118                         in expression_c
119
120 Scheme does the same. (*If* you use Scheme's `let*`, but not if you use its `let`. I agree this is annoying.)
121
122 If `expression_a` and `expression_b` evaluate to (), for instance if they're something like `ycell := !ycell + 1`, that can also be expressed in OCaml as:
123
124         let () = expression_a
125                 in let () = expression_b
126                         in expression_c
127
128 And OCaml has a syntactic shorthand for this form, namely to use semi-colons:
129
130         expression_a; expression_b; expression_c
131
132 This is not the same role that semi-colons play in list expressions, like `[1; 2; 3]`. To be parsed correctly, these semi-colon'ed complexes sometimes need to be enclosed in parentheses or a `begin ... end` construction:
133
134         (expression_a; expression_b; expression_c)
135
136         begin expression_a; expression_b; expression_c end
137
138 Scheme has a construction similar to the latter:
139
140         (begin (expression_a) (expression_b) (expression_c))
141
142 Though often in Scheme, the `(begin ...)` is implicit and doesn't need to be explicitly inserted, as here:
143
144         (lambda (x) (expression_a) (expression_b) (expression_c))
145
146 Another way to control evaluation order, you'll recall from [[week6]], is to use **thunks**. These are functions that only take the uninformative `()` as an argument, such as this:
147
148         let f () = ...
149
150 or this:
151
152         let f = fun () -> ...
153
154 In Scheme these are written as functions that take 0 arguments:
155
156         (lambda () ...)
157
158 or:
159
160         (define (f) ...)
161
162 How could such functions be useful? Well, as always, the context in which you build a function need not be the same as the one in which you apply it to some arguments. So for example:
163
164         let ycell = ref 1
165         in let f () = ycell := !ycell + 1
166         in let z = !ycell
167         in f ()
168         in z;;
169
170 We don't apply (or call or execute or however you want to say it) the function `f` until after we've extracted `ycell`'s value and assigned it to `z`. So `z` will get assigned 1. If on the other hand we called `f ()` before evaluating `let z = !ycell`, then `z` would have gotten assigned a different value.
171
172 In languages with mutable variables, the free variables in a function definition are usually taken to refer back to the same *reference cells* they had in their lexical contexts, and not just their original value. So if we do this for instance:
173
174         let factory (starting_value : int) =
175                 let free_var = ref starting_value
176                 in let getter () =
177                         !free_var
178                 in let setter (new_value : int) =
179                         free_var := new_value
180                 in (getter, setter)
181         in let (getter, setter) = factory 1
182         in let first = getter ()
183         in let () = setter 2
184         in let second = getter ()
185         in let () = setter 3
186         in let third = getter ()
187         in (first, second, third)
188         
189 At the end, we'll get `(1, 2, 3)`. The reference cell that gets updated when we call `setter` is the same one that gets fetched from when we call `getter`. This should seem very intuitive here, since we're working with explicit-style mutation. When working with a language with implicit-style mutation, it can be more surprising. For instance, here's the same fragment in Python, which has implicit-style mutation:
190
191         def factory (starting_value):
192                 free_var = starting_value
193                 def getter ():
194                         return free_var
195                 def setter (new_value):
196                         # the next line indicates that we're using the
197                         # free_var from the surrounding function, not
198                         # introducing a new local variable with the same name
199                         nonlocal free_var
200                         free_var = new_value
201                 return getter, setter
202         getter, setter = factory (1)
203         first = getter ()
204         setter (2)
205         second = getter ()
206         setter (3)
207         third = getter ()
208         (first, second, third)
209
210 Here, too, just as in the OCaml fragment, all the calls to getter and setter are working with a single mutable variable `free_var`.
211
212 If however you called `factory` twice, you'd have different `getter`/`setter` pairs, each of which had their own, independent `free_var`. In OCaml:
213
214         let factory (starting_val : int) =
215         ... (* as above *)
216         in let (getter, setter) = factory 1
217         in let (getter', setter') = factory 1
218         in let () = setter 2
219         in getter' ()
220
221 Here, the call to `setter` only mutated the reference cell associated with the `getter`/`setter` pair. The reference cell associated with `getter'` hasn't changed, and so `getter' ()` will still evaluate to 1.
222
223 Notice in these fragments that once we return from inside the call to `factory`, the `free_var` mutable variable is no longer accessible, except through the helper functions `getter` and `setter` that we've provided. This is another way in which a thunk like `getter` can be useful: it still has access to the `free_var` reference cell that was created when it was, because its free variables are interpreted relative to the context in which `getter` was built, even if that context is otherwise no longer accessible. What `getter ()` evaluates to, however, will very much depend on *when* we evaluate it---in particular, it will depend on which calls to the corresponding `setter` were evaluated first.
224
225 ##Referential opacity##
226
227 In addition to order-sensitivity, when you're dealing with mutable variables you also give up a property that computer scientists call "referential transparency." It's not obvious whether they mean exactly the same by that as philosophers and linguists do, or only something approximately the same. What they do mean is a kind of substitution principle, illustrated here:
228
229         let x = 1
230                 in (x, x)
231
232 should evaluate the same as:
233
234         let x = 1
235                 in (x, 1)
236
237 or:
238
239         (1, 1)
240
241 Notice, however, that when mutable variables are present, the same substitution patterns can't always be relied on:
242
243         let ycell = ref 1
244                 in ycell := 2; !ycell
245         (* evaluates to 2 *)
246
247         (ref 1) := 2; !(ref 1)
248         (* creates a ref 1 cell and changes its contents *)
249         (* then creates a *new* ref 1 cell and returns *its* contents *)
250
251
252 ##How to implement explicit-style mutable variables##
253
254 We'll think about how to implement explicit-style mutation first. We suppose that we add some new syntactic forms to a language, let's call them `newref`, `deref`, and `setref`. And now we want to expand the semantics for the language so as to interpret these new forms.
255
256 Well, part of our semantic machinery will be an assignment function, call it `g`. Somehow we should keep track of the types of the variables and values we're working with, but we won't pay much attention to that now. In fact, we won't even bother much at this point with the assignment function. Below we'll pay more attention to it.
257
258 In addition to the assignment function, we'll also need a way to keep track of how many reference cells have been "allocated" (using `newref`), and what their current values are. We'll suppose all the reference cells are organized in a single data structure we'll call a **store**. This might be a big heap of memory. For our purposes, we'll suppose that reference cells only ever contain `int`s, and we'll let the store be a list of `int`s.
259
260 In many languages, including OCaml, the first position in a list is indexed `0`, the second is indexed `1` and so on. If a list has length 2, then there won't be any value at index `2`; that will be the "next free location" in the list.
261
262 Before we brought mutation on the scene, our language's semantics will have looked something like this:
263
264 >       \[[expression]]<sub>g</sub> = value
265
266 Now we're going to relativize our interpretations not only to the assignment function `g`, but also to the current store, which I'll label `s`. Additionally, we're going to want to allow that evaluating some functions might *change* the store, perhaps by allocating new reference cells or perhaps by updating the contents of some existing cells. So the interpretation of an expression won't just return a value; it will also return a possibly updated store. We'll suppose that our interpretation function does this quite generally, even though for many expressions in the language, the store that's returned will be the same one that the interpretation function started with:
267
268 >       \[[expression]]<sub>g s</sub> = (value, s')
269
270 With that kind of framework, we can interpret `newref`, `deref`, and `setref` as follows.
271
272 1.      \[[newref starting_val]] should allocate a new reference cell in the store and insert `starting_val` into that cell. It should return some "key" or "index" or "pointer" to the newly created reference cell, so that we can do things like:
273
274                 let ycell = newref 1
275                 in ...
276
277         and be able to refer back to that cell later by using the value that we assigned to the variable `ycell`. In our simple implementation, we're letting the store just be an `int list`, and we can let the "keys" be indexes in that list, which are (also) just `int`s. Somehow we should keep track of which variables are assigned `int`s as `int`s and which are assigned `int`s as indexes into the store. So we'll create a special type to wrap the latter:
278
279                 type store_index = Index of int;;
280
281         Our interpretation function will look something like this:
282                 
283                 let rec eval expression g s =
284                         match expression with
285                         ...
286                         | Newref expr ->
287                                 let (starting_val, s') = eval expr g s
288                                 (* note that s' may be different from s, if expr itself contained any mutation operations *)
289                                 (* now we want to retrieve the next free index in s' *)
290                                 in let new_index = List.length s'
291                                 (* now we want to insert starting_val there; the following is an easy but inefficient way to do it *)
292                                 in let s'' = List.append s' [starting_val]
293                                 (* now we return a pair of a wrapped new_index, and the new store *)
294                                 in (Index new_index, s'')
295                         ... 
296
297 2.      When `expr` evaluates to a `store_index`, then `deref expr` should evaluate to whatever value is at that index in the current store. (If `expr` evaluates to a value of another type, `deref expr` is undefined.) In this operation, we don't change the store at all; we're just reading from it. So we'll return the same store back unchanged.
298
299                 let rec eval expression g s =
300                         match expression with
301                         ...
302                         | Deref expr ->
303                                 let (Index n, s') = eval expr g s
304                                 (* note that s' may be different from s, if expr itself contained any mutation operations *)
305                                 in (List.nth s' n, s')
306                         ...
307
308 3.      When `expr1` evaluates to a `store_index` and `expr2` evaluates to an `int`, then `setref expr1 expr2` should have the effect of changing the store so that the reference cell at that index now contains that `int`. We have to make a decision about what value the `setref ...` call should itself evaluate to; OCaml makes this `()` but other choices are also possible. Here I'll just suppose we've got some appropriate value in the variable `dummy`.
309
310                 let rec eval expression g s =
311                         match expression with
312                         ...
313                         | Setref expr1 expr2
314                                 let (Index n, s') = eval expr1 g s
315                                 (* note that s' may be different from s, if expr itself contained any mutation operations *)
316                                 in let (new_value, s'') = eval expr2 g s'
317                                 (* now we create a list which is just like s'' except it has new_value in index n *)
318                                 in let rec replace_nth lst m =
319                                         match lst with
320                                         | [] -> failwith "list too short"
321                                         | x::xs when m = 0 -> new_value :: xs
322                                         | x::xs -> x :: replace_nth xs (m - 1)
323                                 in let s''' = replace_nth s'' n
324                                 in (dummy, s''')
325                         ...
326
327
328 ##How to implement implicit-style mutable variables##
329
330 With implicit-style mutation, we don't have new syntactic forms like `newref` and `deref`. Instead, we just treat ordinary variables as being mutable. You could if you wanted to have some variables be mutable and others not; perhaps the first sort are written in Greek and the second in Latin. But we will suppose all variables in our language are mutable.
331
332 We will still need a store to keep track of reference cells and their current values, just as in the explicit-style implementation. This time, every variable will be associated with an index into the store. So this is what we'll have our assignment function keep track of. The assignment function will bind variables to indexes into the store, rather than to the variables' current values. The variables will only indirectly be associated with "their values" by virtue of the joint work of the assignment function and the store.
333
334 This brings up an interesting conceptual distinction. Formerly, we'd naturally think that a variable `x` is associated with only one type, and that that's the type that the expression `x` would *evaluate to*, and also the type of value that the assignment function *bound* `x` to. However, in the current framework these two types come apart. The assignment function binds `x` to an index into the store, and what the expression `x` evaluates to will be the value at that location in the store, which will usually be some type other than an index into a store, such as a `bool` or a `string`.
335
336 To handle implicit-style mutation, we'll need to re-implement the way we interpret expressions like `x` and `let x = expr1 in expr2`. We will also have just one new syntactic form, `change x to expr1 then expr2`.
337
338 Here's how to implement these. We'll suppose that our assignment function is list of pairs, as in [week6](/reader_monad_for_variable_binding).
339
340         let rec eval expression g s =
341                 match expression with
342                 ...
343                 | Var (c : char) ->
344                         let index = List.assoc c g
345                         (* retrieve the value at that index in the current store *)
346                         in let value = List.nth s index
347                         in (value, s)
348
349                 | Let (c : char) expr1 expr2 ->
350                         let (starting_val, s') = eval expr1 g s
351                         (* get next free index in s' *)
352                         in let new_index = List.length s'
353                         (* insert starting_val there *)
354                         in let s'' = List.append s' [starting_val]
355                         (* evaluate expr2 using a new assignment function and store *)
356                         in eval expr2 ((c, new_index) :: g) s''
357
358                 | Change (c : char) expr1 expr2 ->
359                         let (new_value, s') = eval expr1 g s
360                         (* lookup which index is associated with Var c *)
361                         in let index = List.assoc c g
362                         (* now we create a list which is just like s' except it has new_value at index *)
363                         in let rec replace_nth lst m =
364                                 match lst with
365                                 | [] -> failwith "list too short"
366                                 | x::xs when m = 0 -> new_value :: xs
367                                 | x::xs -> x :: replace_nth xs (m - 1)
368                         in let s'' = replace_nth s' index
369                         (* evaluate expr2 using original assignment function and new store *)
370                         in eval expr2 g s''
371
372
373 ##How to implicit mutation with a State monad##
374
375 It's possible to do all of this monadically, and so using a language's existing resources, instead of adding new syntactic forms and new interpretation rules to the semantics. The patterns we use to do this in fact closely mirror the machinery described above.
376
377 We call this a State monad. It's a lot like the Reader monad, except that with the Reader monad, we could only read from the environment. We did have the possibility of interpreting sub-expressions inside a "shifted" environment, but as you'll see, that corresponds to the "shadowing" behavior described before, not to the mutation behavior that we're trying to implement now.
378
379 With a State monad, we call our book-keeping apparatus a "state" or "store" instead of an evironment, and this time we are able to both read from it and write to it. To keep things simple, we'll work here with the simplest possible kind of store, which only holds a single value. One could also have stores that were composed of a list of values, of a length that could expand or shrink, or even more complex structures.
380
381 Here's the implementation of the State monad, together with an implementation of the Reader monad for comparison:
382
383         type env = (char * int) list;;
384         (* alternatively, an env could be implemented as type char -> int *)
385
386         type 'a reader = env -> 'a;;
387         let unit_reader (value : 'a) : 'a reader =
388                 fun e -> value;;
389         let bind_reader (u : 'a reader) (f : 'a -> 'b reader) : 'b reader =
390                 fun e -> let a = u e
391                                  in let u' = f a
392                                  in u' e;;
393
394         type store = int;;
395         (* very simple store, holds only a single int *)
396         (* this corresponds to having only a single mutable variable *)
397
398         type 'a state = store -> ('a, store);;
399         let unit_state (value : 'a) : 'a state =
400                 fun s -> (value, s);;
401         let bind_state (u : 'a state) (f : 'a -> 'b state) : 'b state =
402                 fun s -> let (a, s') = u s
403                                  in let u' = f a
404                                  in u' s';;
405
406 Notice the similarities (and differences) between the implementation of these two monads.
407
408 With the Reader monad, we also had some special-purpose operations, beyond its general monadic operations. These were `lookup` and `shift`. With the State monad, we'll also have some special-purpose operations. We'll consider two basic ones here. One will be to retrieve what is the current store. This is like the Reader monad's `lookup`, except in this simple implementation there's only a single location for a value to be looked up from. Here's how we'll do it:
409
410         let get_state : store state =
411                         fun s -> (s, s);;
412
413 This passes through the current store unaltered, and also returns a copy of the store as its value. We can use this operation like this:
414
415         some_existing_state_monad >>= fun _ -> get_state >>= (fun cur_state -> ...)
416
417 The `fun _ ->` part here discards the value wrapped by `some_existing_state_monad`. We're only going to pass through, unaltered, whatever *store* is generated by that monadic value. We also wrap that store as *our own value*, which can be retrieved by further operations in the `... >>= ...` chain, such as `(fun cur_state -> ...)`.
418
419 The other operation for the State monad will be to update the existing store to a new one. This operation looks like this:
420
421         let set_state (value : int) : dummy state =
422                 fun s -> (dummy, value);;
423
424 If we want to stick this in a `... >>= ...` chain, we'll need to prefix it with `fun _ ->` too, like this:
425
426         some_existing_state_monad >>= fun _ -> set_state 100 >>= ...
427
428 In this usage, we don't care what value is wrapped by `some_existing_state_monad`. We don't even care what store it generates, since we're going to replace that store with our own new store. A more complex kind of `set_state` operation might insert not just some constant value as the new store, but rather the result of applying some function to the existing store. For example, we might want to increment the current store. Here's how we could do that:
429
430         some_existing_state_monad >>= fun _ -> get_state >>= (fun cur_state -> set_state (cur_state + 1) >>= ...
431
432 We can of course define more complex functions that perform the `get_state >>= (fun cur_state -> set_state (cur_state + 1)` as a single operation.
433
434 In general, a State monadic **value** (type `'a state`, what appears at the start of a `... >>= ... >>= ...` chain) is an operation that accepts some starting store as input---where the store might be simple as it is here, or much more complex---and returns a value plus a possibly modified store. This can be thought of as an encoding of some operation on a store serving as a box wrapped around a value.
435
436 State monadic **operations** (type `'a -> 'b state`, what appears anywhere in the middle or end of a `... >>= ... >>= ...` chain) are operations that generate new State monadic values, based on what value was wrapped by the preceding elements in the `... >>= ... >>= ...` chain. The computations on a store that these encode (which their values may or may not be sensitive to) will be chained in the order given by their position in the `... >>= ... >>= ...` chain. That is, the computation encoded by the first element in the chain will accept a starting store s0 as input, and will return (a value and) a new store s1 as output, the next computation will get s1 as input and will return s2 as output, the next computation will get s2 as input, ... and so on.
437
438 To get the whole process started, the complex computation so defined will need to be given a starting store. So we'd need to do something like this:
439
440         let computation = some_state_monadic_value >>= operation >>= operation
441         in computation initial_store;;
442
443
444
445 ##Aliasing or Passing by reference##
446
447 -- FIXME --
448
449     [H] ; *** aliasing ***
450         let y be 2 in
451           let x be y in
452             let w alias y in
453               (y, x, w)           ==> (2, 2, 2)
454
455     [I] ; mutation plus aliasing
456         let y be 2 in
457           let x be y in
458             let w alias y in
459               change y to 3 then
460                 (y, x, w)         ==> (3, 2, 3)
461
462     [J] let f be (lambda (y) -> BODY) in  ; a
463           ... f (EXPRESSION) ...
464
465         (lambda (y) -> BODY) EXPRESSION
466
467         let y be EXPRESSION in            ; b
468           ... BODY ...
469
470     [K] ; *** passing "by reference" ***
471         let f be (lambda (alias w) ->     ; ?
472           BODY
473         ) in
474           ... f (y) ...
475
476         let w alias y in                  ; d
477           ... BODY ...
478
479     [L] let f be (lambda (alias w) ->
480           change w to 2 then
481             w + 2
482         ) in
483           let y be 1 in
484             let z be f (y) in
485               ; y is now 2, not 1
486               (z, y)              ==> (4, 2)
487
488     [M] ; hyper-evaluativity
489         let h be 1 in
490           let p be 1 in
491             let f be (lambda (alias x, alias y) ->
492               ; contrast here: "let z be x + y + 1"
493               change y to y + 1 then
494                 let z be x + y in
495                   change y to y - 1 then
496                     z
497             ) in
498               (f (h, p), f (h, h))
499                                   ==> (3, 4)
500
501     Notice: h, p have same value (1), but f (h, p) and f (h, h) differ
502
503
504 ##Five grades of mutation involvement##
505
506 -- FIXME --
507
508     0. Purely functional languages
509     1. Passing by reference
510        need primitive hyper-evaluative predicates for it to make a difference
511     2. mutable variables
512     3. mutable values
513         - numerically distinct but indiscernible values
514         - two equality predicates
515         - examples: closures with currently-indiscernible but numerically distinct
516           environments, mutable lists
517     4. "references" as first-class values
518         - x not the same as !x, explicit deref operation
519         - can not only be assigned and passed as arguments, also returned (and manipulated?)
520         - can be compared for qualitative equality
521     5. structured references
522         (a) if `a` and `b` are mutable variables that uncoordinatedly refer to numerically the same value
523             then mutating `b` won't affect `a` or its value
524         (b) if however their value has a mutable field `f`, then mutating `b.f` does
525             affect their shared value; will see a difference in what `a.f` now evaluates to
526
527
528 ##Miscellany##
529
530 *       When using mutable variables, programmers will sometimes write using *loops* that repeatedly mutate a variable, rather than the recursive techniques we've been using so far. For example, we'd define the factorial function like this:
531
532                 let rec factorial n =
533                         if n = 0 then 1 else n * factorial (n - 1)
534
535         or like this:
536
537                 let factorial n =
538                         let rec helper n sofar =
539                                 if n = 0 then sofar else helper (n - 1) (n * sofar)
540                         in helper n 1
541
542         (The second version is more efficient than the first; so you may sometimes see this programming style. But for our purposes, these can be regarded as equivalent.)
543
544         When using mutable variables, on the other hand, this may be written as:
545
546                 let factorial n =
547                         let current = ref n
548                         in let total = ref 1
549                         in while !current > 0 do
550                                 total := !total * !current; current := !current - 1
551                         done; !total
552
553
554 *       Mutable variables also give us a way to achieve recursion, in a language that doesn't already have it. For example:
555
556                 let fact_cell = ref None
557                 in let factorial n =
558                         if n = 0 then 1 else match !fact_cell with
559                                 | Some fact -> n * fact (n - 1)
560                                 | None -> failwith "can't happen"
561                 in let () = fact_cell := Some factorial
562                 in ...
563
564         We use the `None`/`Some factorial` option type here just as a way to ensure that the contents of `fact_cell` are of the same type both at the start and the end of the block.
565
566
567 <!--
568 Fine and Pryor on "coordinated contents" (see, e.g., [Hyper-Evaluativity](http://www.jimpryor.net/research/papers/Hyper-Evaluativity.txt))
569 -->
570