week9 tweak
[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 C has explicit-style mutable variables, too, which it calls *pointers*. But simple variables in C are already mutable, in the implicit style. Scheme also has both styles of mutation. In addition to the explicit boxes, Scheme also lets you mutate unboxed variables:
104
105         (begin
106                 (define x 1)
107                 (set! x 2)
108                 x)
109         ; evaluates to 2
110
111 When dealing with explicit-style mutation, there's a difference between the types and values of `ycell` and `!ycell` (or in Scheme, `(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.
112
113
114 ##Controlling order##
115
116 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.
117
118 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`:
119
120         let triple = (expression_a, expression_b, expression_c)
121
122 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`:
123
124         let a = expression_a
125                 in let b = expression_b
126                         in expression_c
127
128 Scheme does the same. (*If* you use Scheme's `let*`, but not if you use its `let`. I agree this is annoying.)
129
130 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:
131
132         let () = expression_a
133                 in let () = expression_b
134                         in expression_c
135
136 And OCaml has a syntactic shorthand for this form, namely to use semi-colons:
137
138         expression_a; expression_b; expression_c
139
140 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:
141
142         (expression_a; expression_b; expression_c)
143
144         begin expression_a; expression_b; expression_c end
145
146 Scheme has a construction similar to the latter:
147
148         (begin (expression_a) (expression_b) (expression_c))
149
150 Though often in Scheme, the `(begin ...)` is implicit and doesn't need to be explicitly inserted, as here:
151
152         (lambda (x) (expression_a) (expression_b) (expression_c))
153
154 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:
155
156         let f () = ...
157
158 or this:
159
160         let f = fun () -> ...
161
162 In Scheme these are written as functions that take 0 arguments:
163
164         (lambda () ...)
165
166 or:
167
168         (define (f) ...)
169
170 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:
171
172         let ycell = ref 1
173         in let f () = ycell := !ycell + 1
174         in let z = !ycell
175         in f ()
176         in z;;
177
178 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.
179
180 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:
181
182         let factory (starting_value : int) =
183                 let free_var = ref starting_value
184                 in let getter () =
185                         !free_var
186                 in let setter (new_value : int) =
187                         free_var := new_value
188                 in (getter, setter)
189         in let (getter, setter) = factory 1
190         in let first = getter ()
191         in let () = setter 2
192         in let second = getter ()
193         in let () = setter 3
194         in let third = getter ()
195         in (first, second, third)
196         
197 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:
198
199         def factory (starting_value):
200                 free_var = starting_value
201                 def getter ():
202                         return free_var
203                 def setter (new_value):
204                         # the next line indicates that we're using the
205                         # free_var from the surrounding function, not
206                         # introducing a new local variable with the same name
207                         nonlocal free_var
208                         free_var = new_value
209                 return getter, setter
210         getter, setter = factory (1)
211         first = getter ()
212         setter (2)
213         second = getter ()
214         setter (3)
215         third = getter ()
216         (first, second, third)
217
218 Here, too, just as in the OCaml fragment, all the calls to getter and setter are working with a single mutable variable `free_var`.
219
220 If however you called `factory` twice, you'd have different `getter`/`setter` pairs, each of which had their own, independent `free_var`. In OCaml:
221
222         let factory (starting_val : int) =
223         ... (* as above *)
224         in let (getter, setter) = factory 1
225         in let (getter', setter') = factory 1
226         in let () = setter 2
227         in getter' ()
228
229 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.
230
231 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.
232
233 ##Referential opacity##
234
235 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.
236
237 The core idea to referential transparency is that when the same value is supplied to a context, the whole should always evaluate the same way. Mutation makes it possible to violate this. Consider:
238
239         let ycell = ref 1
240                 in let f x = x + !ycell
241                         in let first = f 1      (* first is assigned the value 2 *)
242                                 in ycell := 2; let second = f 1 (* second is assigned the value 3 *)
243                                         in first = second;; (* not true! *)
244
245 Notice that the two invocations of `f 1` yield different results, even though the same value is being supplied as an argument to the same function.
246
247 Similarly, functions like these:
248
249         let f cell = !cell;;
250
251         let g cell = cell := !cell + 1; !cell;;
252
253 may return different results each time they're invoked, even if they're always supplied one and the same reference cell as argument.
254
255 Computer scientists also associate referential transparency with a kind of substitution principle, illustrated here:
256
257         let x = 1
258                 in (x, x)
259
260 should evaluate the same as:
261
262         let x = 1
263                 in (x, 1)
264
265 or:
266
267         (1, 1)
268
269 Notice, however, that when mutable variables are present, the same substitution patterns can't always be relied on:
270
271         let ycell = ref 1
272                 in ycell := 2; !ycell
273         (* evaluates to 2 *)
274
275         (ref 1) := 2; !(ref 1)
276         (* creates a ref 1 cell and changes its contents *)
277         (* then creates a *new* ref 1 cell and returns *its* contents *)
278
279
280
281
282 ##How to implement explicit-style mutable variables##
283
284 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.
285
286 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.
287
288 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.
289
290 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.
291
292 Before we brought mutation on the scene, our language's semantics will have looked something like this:
293
294 >       \[[expression]]<sub>g</sub> = value
295
296 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:
297
298 >       \[[expression]]<sub>g s</sub> = (value, s')
299
300 For expressions we already know how to interpret, expect `s'` to just be `s`.
301 An exception is complex expressions like `let var = expr1 in expr2`. Part of
302 interpreting this will be to interpret the sub-expression `expr1`, and we have
303 to allow that in doing that, the store may have already been updated. We want
304 to use that possibly updated store when interpreting `expr2`. Like this:
305
306         let rec eval expression g s =
307                 match expression with
308                 ...
309                 | Let (c, expr1, expr2) ->
310                         let (value, s') = eval expr1 g s
311                         (* s' may be different from s *)
312                         (* now we evaluate expr2 in a new environment where c has been associated
313                            with the result of evaluating expr1 in the current environment *)
314                         eval expr2 ((c, value) :: g) s'
315                 ...
316
317 Similarly:
318
319                 ...
320                 | Addition (expr1, expr2) ->
321                         let (value1, s') = eval expr1 g s
322                         in let (value2, s'') = eval expr2 g s'
323                         in (value1 + value2, s'')
324                 ...
325
326 Let's consider how to interpet our new syntactic forms `newref`, `deref`, and `setref`:
327
328
329 1.      When `expr` evaluates to starting\_val, **newref expr** 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:
330
331                 let ycell = newref 1
332                 in ...
333
334         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:
335
336                 type store_index = Index of int;;
337
338         Our interpretation function will look something like this:
339                 
340                 let rec eval expression g s =
341                         match expression with
342                         ...
343                         | Newref (expr) ->
344                                 let (starting_val, s') = eval expr g s
345                                 (* note that s' may be different from s, if expr itself contained any mutation operations *)
346                                 (* now we want to retrieve the next free index in s' *)
347                                 in let new_index = List.length s'
348                                 (* now we want to insert starting_val there; the following is an easy but inefficient way to do it *)
349                                 in let s'' = List.append s' [starting_val]
350                                 (* now we return a pair of a wrapped new_index, and the new store *)
351                                 in (Index new_index, s'')
352                         ... 
353
354 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 (assuming it wasn't changed during the evaluation of `expr`).
355
356                 let rec eval expression g s =
357                         match expression with
358                         ...
359                         | Deref (expr) ->
360                                 let (Index n, s') = eval expr g s
361                                 (* note that s' may be different from s, if expr itself contained any mutation operations *)
362                                 in (List.nth s' n, s')
363                         ...
364
365 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`.
366
367                 let rec eval expression g s =
368                         match expression with
369                         ...
370                         | Setref (expr1, expr2) ->
371                                 let (Index n, s') = eval expr1 g s
372                                 (* note that s' may be different from s, if expr1 itself contained any mutation operations *)
373                                 in let (new_value, s'') = eval expr2 g s'
374                                 (* now we create a list which is just like s'' except it has new_value in index n *)
375                                 in let rec replace_nth lst m =
376                                         match lst with
377                                         | [] -> failwith "list too short"
378                                         | x::xs when m = 0 -> new_value :: xs
379                                         | x::xs -> x :: replace_nth xs (m - 1)
380                                 in let s''' = replace_nth s'' n
381                                 in (dummy, s''')
382                         ...
383
384
385
386
387
388 ##How to implement implicit-style mutable variables##
389
390 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.
391
392 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.
393
394 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`.
395
396 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`.
397
398 Here's how to implement these. We'll suppose that our assignment function is list of pairs, as above and as in [week7](/reader_monad_for_variable_binding).
399
400         let rec eval expression g s =
401                 match expression with
402                 ...
403                 | Var (c : char) ->
404                         let index = List.assoc c g
405                         (* retrieve the value at that index in the current store *)
406                         in let value = List.nth s index
407                         in (value, s)
408
409                 | Let ((c : char), expr1, expr2) ->
410                         let (starting_val, s') = eval expr1 g s
411                         (* get next free index in s' *)
412                         in let new_index = List.length s'
413                         (* insert starting_val there *)
414                         in let s'' = List.append s' [starting_val]
415                         (* evaluate expr2 using a new assignment function and store *)
416                         in eval expr2 ((c, new_index) :: g) s''
417
418                 | Change ((c : char), expr1, expr2) ->
419                         let (new_value, s') = eval expr1 g s
420                         (* lookup which index is associated with Var c *)
421                         in let index = List.assoc c g
422                         (* now we create a list which is just like s' except it has new_value at index *)
423                         in let rec replace_nth lst m =
424                                 match lst with
425                                 | [] -> failwith "list too short"
426                                 | x::xs when m = 0 -> new_value :: xs
427                                 | x::xs -> x :: replace_nth xs (m - 1)
428                         in let s'' = replace_nth s' index
429                         (* evaluate expr2 using original assignment function and new store *)
430                         in eval expr2 g s''
431
432
433 ##How to implement mutation with a State monad##
434
435 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.
436
437 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.
438
439 With a State monad, we call our book-keeping apparatus a "state" or "store" instead of an environment, 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.
440
441 Here's the implementation of the State monad, together with an implementation of the Reader monad for comparison:
442
443         type env = (char * int) list;;
444         (* alternatively, an env could be implemented as type char -> int *)
445
446         type 'a reader = env -> 'a;;
447         let unit_reader (value : 'a) : 'a reader =
448                 fun e -> value;;
449         let bind_reader (u : 'a reader) (f : 'a -> 'b reader) : 'b reader =
450                 fun e -> let a = u e
451                                  in let u' = f a
452                                  in u' e;;
453
454         type store = int;;
455         (* very simple store, holds only a single int *)
456         (* this corresponds to having only a single mutable variable *)
457
458         type 'a state = store -> ('a, store);;
459         let unit_state (value : 'a) : 'a state =
460                 fun s -> (value, s);;
461         let bind_state (u : 'a state) (f : 'a -> 'b state) : 'b state =
462                 fun s -> let (a, s') = u s
463                                  in let u' = f a
464                                  in u' s';;
465
466 Notice the similarities (and differences) between the implementation of these two monads.
467
468 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:
469
470         let get_state : store state =
471                         fun s -> (s, s);;
472
473 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:
474
475         some_existing_state_monad_box >>= fun _ -> get_state >>= (fun cur_store -> ...)
476
477 The `fun _ ->` part here discards the value wrapped by `some_existing_state_monad_box`. We're only going to pass through, unaltered, whatever *store* is generated by that monadic box. We also wrap that store as *our own value*, which can be retrieved by further operations in the `... >>= ...` chain, such as `(fun cur_store -> ...)`.
478
479 The other operation for the State monad will be to update the existing store to a new one. This operation looks like this:
480
481         let set_state (new_store : int) : dummy state =
482                 fun s -> (dummy, new_store);;
483
484 If we want to stick this in a `... >>= ...` chain, we'll need to prefix it with `fun _ ->` too, like this:
485
486         some_existing_state_monad_box >>= fun _ -> set_state 100 >>= ...
487
488 In this usage, we don't care what value is wrapped by `some_existing_state_monad_box`. 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:
489
490         some_existing_state_monad_box >>= fun _ -> get_state >>= (fun cur_store -> set_state (cur_store + 1) >>= ...
491
492 We can of course define more complex functions that perform the `get_state >>= (fun cur_store -> set_state (cur_store + 1)` as a single operation.
493
494 In general, a State monadic **box** (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 a static encoding of some computation on a store, which encoding is used as a box wrapped around a value of type `'a`. (And also it's a burrito.)
495
496 State monadic **operations** (type `'a -> 'b state`, what appears anywhere in the middle or end of a `... >>= ... >>= ...` chain) are operations that generate new State monad boxes, 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.
497
498 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:
499
500         let computation = some_state_monadic_box >>= operation >>= operation
501         in computation initial_store;;
502
503
504
505 ##Aliasing or Passing by reference##
506
507 -- FIXME --
508
509         [H] ; *** aliasing ***
510             let y be 2 in
511               let x be y in
512                 let w alias y in
513                   (y, x, w)
514                                                                 ; evaluates to (2, 2, 2)
515
516         [I] ; mutation plus aliasing
517             let y be 2 in
518               let x be y in
519                 let w alias y in
520                   change y to 3 then
521                     (y, x, w)
522                                                                 ; evaluates to (3, 2, 3)
523
524         [J] ; as we already know, these are all equivalent:
525         
526             let f be (lambda (y) -> BODY) in  ; #1
527               ... f (EXPRESSION) ...
528         
529             (lambda (y) -> BODY) EXPRESSION   ; #2
530         
531             let y be EXPRESSION in            ; #3
532               ... BODY ...
533
534         [K] ; *** passing by reference ***
535             ; now think: "[J#1] is to [J#3] as [K#1] is to [K#2]"
536         
537             ?                                 ; #1
538         
539             let w alias y in                  ; #2
540               ... BODY ...
541         
542             ; We introduce a special syntactic form to supply
543             ; the missing ?
544         
545             let f be (lambda (alias w) ->     ; #1
546               BODY
547             ) in
548               ... f (y) ...
549
550         [L] let f be (lambda (alias w) ->
551               change w to 2 then
552                 w + 2
553             ) in
554               let y be 1 in
555                 let z be f (y) in
556                   ; y is now 2, not 1
557                   (z, y)
558                                                                 ; evaluates to (4, 2)
559
560         [M] ; hyper-evaluativity
561             let h be 1 in
562               let p be 1 in
563                 let f be (lambda (alias x, alias y) ->
564                   ; contrast here: "let z be x + y + 1"
565                   change y to y + 1 then
566                     let z be x + y in
567                       change y to y - 1 then
568                         z
569                 ) in
570                   (f (h, p), f (h, h))
571                                                                 ; evaluates to (3, 4)
572
573 Notice: in [M], `h` and `p` have same value (1), but `f (h, p)` and `f (h, h)` differ.
574
575 See Pryor's "[Hyper-Evaluativity](http://www.jimpryor.net/research/papers/Hyper-Evaluativity.txt)".
576
577
578 ##Four grades of mutation involvement##
579
580 Programming languages tend to provide a bunch of mutation-related capabilities at once, if they provide any. For conceptual clarity, however, it's helped me to distill these into several small increments.
581
582 *       At the first stage, we have a purely functional language, like we've been working with up until this week.
583
584
585 *       One increment would be to add aliasing or passing by reference, as illustrated above. In the illustration, we relied on the combination of passing by reference and mutation to demonstrate how you could get different behavior depending on whether an argument was passed to a function by reference or instead passed in the more familiar way (called "passing by value"). However, it would be possible to have passing by reference in a language without having mutation. For it to make any difference whether an argument is passed by reference or by value, such a language would have to have some primitive predicates which are sensitive to whether their arguments are aliased or not. In Jim's paper linked above, he calls such predicates "hyper-evaluative."
586
587         The simplest such predicate we might call "hyperequals": `y hyperequals w` should evaluate to true when and only when the arguments `y` and `w` are aliased.
588
589
590 *       Another increment would be to add implicit-style mutable variables, as we explained above. You could do this with or without also adding passing-by-reference.
591
592         The semantic machinery for implicit-style mutable variables will have something playing the role of a reference cell. However these won't be **first-class values** in the language. For something to be a first-class value, it has to be possible to assign that value to variables, to pass it as an argument to functions, and to return it as the result of a function call. Now for some of these criteria it's debatable that they are already here satisfied. For example, in some sense the introduction of a new implicitly mutable variable (`let x = 1 in ...`) will associate a reference cell with `x`. That won't be what `x` evaluates to, but it will be what the assignment function *binds* `x` to, behind the scenes. Similarly, if we bring in passing by reference, then again in some sense we are passing reference cells as arguments to functions. Not explicitly---in a context like:
593
594                 let f = (lambda (alias w) -> ...)
595                         in let x = 1
596                                 in f (x)
597
598         the expression `w` won't evaluate to a reference cell anywhere inside the `...`. But it will be associated with a reference cell, in the same way that `x` is (and indeed, with the same reference cell).
599
600         However, in language with implicit-style mutation, even when combined with passing by reference, what you're clearly not able to do is to return a reference cell as the result of a function call, or indeed of any expression. This is connected to---perhaps it's the same point as---the fact that `x` and `w` don't evalute to reference cells, but rather to the values that the reference cell they're implicitly associated with contains, at that stage in the computation.
601
602 *       A third grade of mutation involvement is to have explicit-style mutation. Here we might say we have not just mutable variables but also first-class values whose contents can be altered. That is, we have not just mutable variables but **mutable values**.
603
604         This introduces some interesting new conceptual possibilities. For example, what should be the result of the following fragment?
605
606                 let ycell = ref 1
607                 in let xcell = ref 1
608                 in ycell = xcell
609
610         Are the two reference cell values equal or aren't they? Well, at this stage in the computation, they're qualitatively indiscernible. They're both `int ref`s containing the same `int`. And that is in fact the relation that `=` expresses in OCaml. In Scheme the analogous relation is spelled `equal?` Computer scientists sometimes call this relation "structural equality."
611
612         On the other hand, these are numerically *two* reference cells. If we mutate one of them, the other one doesn't change. For example:
613
614                 let ycell = ref 1
615                 in let xcell = ref 1
616                 in ycell := 2
617                 in !xcell;;
618                 (* evaluates to 1, not to 2 *)
619
620         So we have here the basis for introducing a new kind of equality predicate into our language, which tests not for qualitative indiscernibility but for numerical equality. In OCaml this relation is expressed by the double equals `==`. In Scheme it's spelled `eq?` Computer scientists sometimes call this relation "physical equality". Using this equality predicate, our comparison of `ycell` and `xcell` will be `false`, even if they then happen to contain the same `int`.
621
622         Isn't this interesting? Intuitively, elsewhere in math, you might think that qualitative indicernibility always suffices for numerical identity. Well, perhaps this needs discussion. In some sense the imaginary numbers &iota; and -&iota; are qualitatively indiscernible, but numerically distinct. However, arguably they're not *fully* qualitatively indiscernible. They don't both bear all the same relations to &iota; for instance. But then, if we include numerical identity as a relation, then `ycell` and `xcell` don't both bear all the same relations to `ycell`, either. Yet there is still a useful sense in which they can be understood to be qualitatively equal---at least, at a given stage in a computation.
623
624         Terminological note: in OCaml, `=` and `<>` express the qualitative (in)discernibility relations, also expressed in Scheme with `equal?`. In OCaml, `==` and `!=` express the numerical (non)identity relations, also expressed in Scheme with `eq?`. `=` also has other syntactic roles in OCaml, such as in the form `let x = value in ...`. In other languages, like C and Python, `=` is commonly used just for assignment (of either of the sorts we've now seen: `let x = value in ...` or `change x to value in ...`). The symbols `==` and `!=` are commonly used to express qualitative (in)discernibility in these languages. Python expresses numerical (non)identity with `is` and `is not`. What an unattractive mess. Don't get me started on Haskell (qualitative discernibility is `/=`) and Lua (physical (non)identity is `==` and `~=`).
625
626         Note that neither of the equality predicates here being considered are the same as the "hyperequals" predicate mentioned above. For example, in the following (fictional) language:
627
628                 let ycell = ref 1
629                 in let xcell = ref 1
630                 in let wcell alias ycell
631                 in let zcell = ycell
632                 in ...
633
634         at the end, `hyperequals ycell wcell` (and the converse) would be true, but no other non-reflexive hyperequality would be true. `hyperequals ycell zcell` for instance would be false. If we express numerical identity using `==`, as OCaml does, then both of these (and their converses) would be true:
635
636                 ycell == wcell
637                 ycell == zcell
638
639         but these would be false:
640
641                 xcell == ycell
642                 xcell == wcell
643                 xcell == zcell
644
645         If we express qualitative indiscernibility using `=`, as OCaml does, then all of the salient comparisons would be true:
646
647                 ycell = wcell
648                 ycell = zcell
649                 xcell = ycell
650                 ...
651
652         Another interesting example of "mutable values" that illustrate the coming apart of qualitative indiscernibility and numerical identity are the `getter`/`setter` pairs we discussed earlier. Recall:
653
654                 let factory (starting_val : int) =
655                         let free_var = ref starting_value
656                         in let getter () =
657                                 !free_var
658                         in let setter (new_value : int) =
659                                 free_var := new_value
660                         in (getter, setter)
661                 in let (getter, setter) = factory 1
662                 in let (getter', setter') = factory 1
663                 in ...
664
665         After this, `getter` and `getter'` would (at least, temporarily) be qualitatively indiscernible. They'd return the same value whenever called with the same argument (`()`). So too would `adder` and `adder'` in the following example:
666
667                 let factory (starting_val : int) =
668                         let free_var = ref starting_value
669                         in let adder x =
670                                 x + !free_var
671                         in let setter (new_value : int) =
672                                 free_var := new_value
673                         in (adder, setter)
674                 in let (adder, setter) = factory 1
675                 in let (adder', setter') = factory 1
676                 in ...
677
678         Of course, in most languages you wouldn't be able to evaluate a comparison like `getter = getter'`, because in general the question whether two functions always return the same values for the same arguments is not decidable. So typically languages don't even try to answer that question. However, it would still be true that `getter` and `getter'` (and `adder` and `adder'`) were extensionally equivalent.
679
680         However, they're not numerically identical, because by calling `setter 2` (but not calling `setter' 2`) we can mutate the function value `getter` (and `adder`) so that it's *no longer* qualitatively indiscernible from `getter'` (or `adder'`).
681
682
683  
684 *       A fourth grade of mutation involvement: (--- FIXME ---)
685
686         structured references
687         (a) if `a` and `b` are mutable variables that uncoordinatedly refer to numerically the same value
688             then mutating `b` won't affect `a` or its value
689         (b) if however their value has a mutable field `f`, then mutating `b.f` does
690             affect their shared value; will see a difference in what `a.f` now evaluates to
691                 (c) examples: Scheme mutable pairs, OCaml mutable arrays or records
692
693
694
695 ##Miscellany##
696
697 *       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:
698
699                 let rec factorial n =
700                         if n = 0 then 1 else n * factorial (n - 1)
701
702         or like this:
703
704                 let factorial n =
705                         let rec helper n sofar =
706                                 if n = 0 then sofar else helper (n - 1) (n * sofar)
707                         in helper n 1
708
709         (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.)
710
711         When using mutable variables, on the other hand, this may be written as:
712
713                 let factorial n =
714                         let current = ref n
715                         in let total = ref 1
716                         in while !current > 0 do
717                                 total := !total * !current; current := !current - 1
718                         done; !total
719
720
721 *       Mutable variables also give us a way to achieve recursion, in a language that doesn't already have it. For example:
722
723                 let fact_cell = ref None
724                 in let factorial n =
725                         if n = 0 then 1 else match !fact_cell with
726                                 | Some fact -> n * fact (n - 1)
727                                 | None -> failwith "can't happen"
728                 in let () = fact_cell := Some factorial
729                 in ...
730
731         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.
732
733
734 ##Offsite Reading##
735
736 *       [[!wikipedia Declarative programming]]
737 *       [[!wikipedia Functional programming]]
738 *       [[!wikipedia Purely functional]]
739 *       [[!wikipedia Side effect (computer science) desc="Side effects"]]
740 *       [[!wikipedia Referential transparency (computer science)]]
741 *       [[!wikipedia Imperative programming]]
742 *       [[!wikipedia Reference (computer science) desc="References"]]
743 *       [[!wikipedia Pointer (computing) desc="Pointers"]]
744 *       [Pointers in OCaml](http://caml.inria.fr/resources/doc/guides/pointers.html)
745
746 <!--
747 # General issues about variables and scope in programming languages #
748
749 *       [[!wikipedia Variable (programming) desc="Variables"]]
750 *       [[!wikipedia Free variables and bound variables]]
751 *       [[!wikipedia Variable shadowing]]
752 *       [[!wikipedia Name binding]]
753 *       [[!wikipedia Name resolution]]
754 *       [[!wikipedia Parameter (computer science) desc="Function parameters"]]
755 *       [[!wikipedia Scope (programming) desc="Variable scope"]]
756 *       [[!wikipedia Closure (computer science) desc="Closures"]]
757
758 -->
759