edits
[lambda.git] / topics / week9_mutable_state.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; continuations (which we'll study more in the coming weeks) and exceptions (like OCaml's `failwith "message"` or `raise Not_found`); 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 present pedagogical purposes, we'll be using a made-up language that's syntactically similar to, but not quite the same as, OCaml. (It's not quite Kapulet either.)
11
12 This should seem entirely familiar:
13
14     [A] let y = 1 + 2 in
15         let x = 10 in
16         (x + y, 20 + y)
17                                 ; evaluates to (13, 23)
18
19 In our next fragment, we re-use a variable that had been bound to another value in a wider context:
20
21     [B] let y = 2 in            ; will be shadowed by the binding on the next line
22         let y = 3 in
23         (10 + y, 20 + y)
24                                 ; evaluates to (13, 23)
25
26 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.
27
28 I call attention to this because you might casually describe it as "changing the value that y is assigned to." But what we'll see below is a more exotic phenomenon that merits that description better.
29
30 In the previous fragments, we bound the variables `x` and `y` to `int`s. We can also bind variables to function values, as here:
31
32     [C] let f = (\x y. x + y + 1) in
33         (f 10 2, f 20 2)
34                                 ; evaluates to (13, 23)
35
36 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 that expression's lexical context:
37
38     [D] let y = 3 in
39         let f = (\x. x + y) in
40         let y = 2 in
41         (f 10, y, f 20)
42                                 ; evaluates to (13, 2, 23)
43
44 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 contemporary norm in functional programming languages, and seems to be easiest for programmers to reason about.
45
46 Sometimes bindings are shadowed merely in a temporary, local context, as here:
47
48     [E] let y = 3 in
49         let f = (\x. let y = 2 in
50                       ; here the most local binding for y applies
51                       x + y) in
52         ; here the binding of y to 2 has expired
53         (y, f 10, y, f 20)
54                                 ; evaluates to (3, 12, 3, 22)
55
56 Notice that the `y`s in the tuple at the end use the outermost binding of `y` to `3`, but the `y` in `x + y` in the body of the `f` function uses the more local binding.
57
58 OK, now we're ready for our main event, **mutable variables.** We'll introduce new syntax to express an operation where we're not merely *shadowing* a wider binding, but *changing* or *mutating* that binding. The new syntax will show up both when we introduce the variable, using `var y = ...` rather than `let y = ...`; and also when we change `y`'s value using `set`.
59
60     [F] var y = 3 in
61         let f = (\x. set y to 2 then
62                      x + y) in
63         ; here the change in what value y is bound to *sticks*
64         ; because we *mutated* the value of the *original* variable y
65         ; instead of introducing a new y with a narrower scope
66         (y, f 10, y, f 20)
67                                 ; evaluates to (3, 12, 2, 22)
68
69 Notice the difference in the how the second `y` is evaluated in the tuple at the end. By the way, I am assuming here that the tuple gets evaluated left-to-right. Other languages may or may not conform to that. OCaml doesn't always.
70
71 In languages that have native syntax for mutation, there are two styles in which it can be expressed. The *implicit style* is exemplified in fragment [F] above, and also in languages like C:
72
73     {
74         int y = 3;    // this is like "var y = 3 in ..."
75         ...
76         y = 2;        // this is like "set y to 2 then ..."
77         return x + y; // this is like "x + y"
78     }
79
80 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 mutate a variable's value, we leave the variable assigned to the same reference cell, but we modify that reference cell's contents. 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:
81
82     let ycell = ref 3       (* this creates a new reference cell *)
83     ... in
84     let () = ycell := 2 in  (* this changes the contents of that cell to 2 *)
85                             (* the return value of doing so is () *)
86                             (* other return values could also be reasonable: *)
87                             (* such as the old value of ycell, the new value, an arbitrary int, and so on *)
88     x + !ycell              (* the !ycell operation "dereferences" the cell---it retrieves the value it contains *)
89
90 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:
91
92     (let ([ycell (box 3)])
93         ...
94         (set-box! ycell 2)
95         (+ x (unbox ycell)))
96
97 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:
98
99     (begin
100         (define y 3)
101         (set! y 2)
102         y)
103     ; evaluates to 2
104
105 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. The variables `y` in fragment [F] or in the C snippet above have the type `int`, and only ever evaluate to `int` values.
106
107
108 ##Controlling order##
109
110 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.
111
112 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`:
113
114     let triple = (expression_a, expression_b, expression_c)
115
116 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`:
117
118     let a = expression_a in
119     let b = expression_b in
120     expression_c
121
122 Scheme does the same. (*If* you use Scheme's `let*`, but not if you use its `let`. I agree this is annoying.)
123
124 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:
125
126     let () = expression_a in
127     let () = expression_b in
128     expression_c
129
130 And OCaml has a syntactic shorthand for this form, namely to use semi-colons:
131
132     expression_a; expression_b; expression_c
133
134 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:
135
136     (expression_a; expression_b; expression_c)
137
138     begin expression_a; expression_b; expression_c end
139
140 Scheme has a construction similar to the latter:
141
142     (begin (expression_a) (expression_b) (expression_c))
143
144 Though often in Scheme, the `(begin ...)` is implicit and doesn't need to be explicitly inserted, as here:
145
146     (lambda (x) (expression_a) (expression_b) (expression_c))
147
148 Another way to control evaluation order, you'll recall from previous discussion, is to use **thunks**. These are functions that only take the uninformative `()` as an argument, such as this:
149
150     let f () = ... in
151     ...
152
153 or this:
154
155     let f = fun () -> ... in
156     ...
157
158 In Scheme these are written as functions that take 0 arguments:
159
160     (let* ([f (lambda () ...)]) ...)
161
162 or:
163
164     (define (f) ...)
165     ...
166
167 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 arguments. So for example:
168
169     let ycell = ref 1 in
170     let incr_y () = ycell := !ycell + 1 in
171     let y = !ycell in
172     incr_y () in
173     y
174
175 We don't apply (or call or execute or however you want to say it) the function `incr_y` until after we've extracted `ycell`'s value and assigned it to `y`. So `y` will get assigned `1`. If on the other hand we called `incr_y ()` before evaluating `let y = !ycell`, then `y` would have gotten assigned a different value.
176
177 In languages with mutable variables, the free variables in a function definition are often 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:
178
179     let factory (starting_value : int) =
180         let free_var = ref starting_value in
181         (* `free_var` will be free in the bodies of the next two functions *)
182         let getter () = !free_var in
183         let setter (new_value : int) = free_var := new_value in
184         (* here's what `factory starting_value` returns *)
185         (getter, setter) in
186     let (getter, setter) = factory 1 in
187     let first = getter () in
188     let () = setter 2 in
189     let second = getter () in
190     let () = setter 3 in
191     let third = getter () in
192     (first, second, third)
193     
194 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:
195
196     def factory (starting_value):
197         free_var = starting_value
198         def getter ():
199             return free_var
200         def setter (new_value):
201             # the next line indicates that we're using the
202             # free_var from the surrounding function, not
203             # introducing a new local variable with the same name
204             nonlocal free_var
205             free_var = new_value
206         return getter, setter
207     getter, setter = factory (1)
208     first = getter ()
209     setter (2)
210     second = getter ()
211     setter (3)
212     third = getter ()
213     (first, second, third)
214
215 Here, too, just as in the OCaml fragment, all the calls to getter and setter are working with a single mutable variable `free_var`.
216
217 If you've got a copy of *The Seasoned Schemer*, which we recommended for the seminar, see the discussion at pp. 91-118 and 127-137.
218
219 If however you call the `factory` function twice, even if you supply the same `starting_value`, you'll get independent `getter`/`setter` pairs, each of which have their own, separate `free_var`. In OCaml:
220
221     let factory (starting_val : int) =
222       ... (* as above *) in
223     let (getter, setter) = factory 1 in
224     let (getter', setter') = factory 1 in
225     let () = setter 2 in
226     getter' ()
227
228 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`.
229
230 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.
231
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 in
240     let plus_y x = x + !ycell in
241     let first = plus_y 1 in              (* first is assigned the value 2 *)
242     ycell := 2; let second = plus_y 1 in (* second is assigned the value 3 *)
243     first = second                       (* not true! *)
244
245 Notice that the two invocations of `plus_y 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 in
258     (x, x)
259
260 should evaluate the same as:
261
262     let x = 1 in
263     (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 in
272     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     (* so evaluates to 1 *)
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`, `getref`, and `putref`. 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 or environment, call it `e`. Perhaps 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 might call a table or **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 We won't suppose that the metalanguage we use to express the semantics of our mutation-language itself has any mutation facilities. Instead, we'll think about how to model mutation in a wholly declarative or functional or *static* metalanguage.
291
292 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.
293
294 Before we brought mutation on the scene, our language's semantics will have looked something like this:
295
296 >    \[[expression]]<sub>e</sub> = result
297
298 Now we're going to relativize our interpretations not only to the environment `e`, 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 modifying the contents of some existing cells. So the interpretation of an expression won't just return a result; 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:
299
300 >    \[[expression]]<sub>e s</sub> = (result, s')
301
302 For expressions we already know how to interpret, you can by default expect `s'` to just be `s`.
303 An exception is complex expressions like `let var = expr1 in expr2`. Part of
304 interpreting this will be to interpret the sub-expression `expr1`, and we have
305 to allow that in doing that, the store may have already been updated. We want
306 to use that possibly updated store when interpreting `expr2`. Like this:
307
308     let rec eval term e s = match term with
309         ...
310         | Let (var, expr1, expr2) ->
311             let (res1, s') = eval expr1 e s
312             (* s' may be different from s *)
313             (* now we evaluate expr2 in a new environment where var has been associated
314                with the result of evaluating expr1 in the current environment *)
315             eval expr2 ((var, res1) :: e) s'
316         ...
317
318 Similarly:
319
320         ...
321         | Apply (Apply(PrimitiveAddition, expr1), expr2) ->
322             let (res1, s') = eval expr1 e s in
323             let (res2, s'') = eval expr2 e s' in
324             (res1 + res2, s'')
325         ...
326
327 Let's consider how to interpet our new syntactic forms `newref`, `getref`, and `putref`:
328
329
330 1.    When `expr` evaluates to `starting_val`, then **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:
331
332         let ycell = newref 1 in
333         ...
334
335     and be able to refer back to that cell later by using the result 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:
336
337         type store_index = Index of int
338
339     Our interpretation function will look something like this:
340         
341             let rec eval term e s = match term with
342             ...
343             | Newref (expr) ->
344                 let (starting_val, s') = eval expr e s in
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                 let new_index = List.length s' in
348                 (* now we want to insert starting_val there; the following is an easy but inefficient way to do it *)
349                 let s'' = List.append s' [starting_val] in
350                 (* now we return a pair of a wrapped new_index, and the new store *)
351                 (Index new_index, s'')
352             ... 
353
354 2.    When `expr` evaluates to a `store_index`, then **getref expr** should evaluate to whatever value is at that index in the current store. (If `expr` evaluates to a value of another type, `getref 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 term e s = match term with
357             ...
358             | Getref (expr) ->
359                 let (Index n, s') = eval expr e s in
360                 (* s' may be different from s, if expr itself contained any mutation operations *)
361                 (List.nth s' n, s')
362             ...
363
364 3.    When `expr1` evaluates to a `store_index` and `expr2` evaluates to an `int`, then **putref 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 result the `putref ...` 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`.
365
366             let rec eval term e s = match term with
367             ...
368             | Putref (expr1, expr2) ->
369                 let (Index n, s') = eval expr1 e s in
370                 (* note that s' may be different from s, if expr1 itself contained any mutation operations *)
371                 let (new_value, s'') = eval expr2 e s' in
372                 (* now we create a list which is just like s'' except it has new_value in index n *)
373                 (* the following could be expressed in Juli8 as `modify m (fun _ -> new_value) xs` *)
374                 let rec replace_nth xs m  = match xs with
375                   | [] -> failwith "list too short"
376                   | x::xs when m = 0 -> new_value :: xs
377                   | x::xs -> x :: replace_nth xs (m - 1) in
378                 let s''' = replace_nth s'' n in
379                 (dummy, s''')
380             ...
381
382
383
384
385 ##How to implement implicit-style mutable variables##
386
387 With implicit-style mutation, we don't have new syntactic forms like `newref` and `getref`. 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 for present purposes, we will suppose all variables in our language are mutable.
388
389 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.
390
391 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`.
392
393 To handle implicit-style mutation, we'll need to re-implement the way we interpret expressions like `x` and `var x = expr1 in expr2`. We will also have just one new syntactic form, `set x to expr1 then expr2`. (The `then` here is playing the role of the sequencing semicolon in OCaml.)
394
395 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). LINK TODO
396
397     let rec eval term e s = match term with
398         ...
399         | Var (var : identifier) ->
400             let index = List.assoc var e in
401             (* retrieve the value at that index in the current store *)
402             let res = List.nth s index in
403             (res, s)
404
405         (* instead of `let x = ...` we now have `var x = ...`, for which I'll use the `Letvar` tag *)
406         | Letvar ((var : identifier), expr1, expr2) ->
407             let (starting_val, s') = eval expr1 e s in
408             (* get next free index in s' *)
409             let new_index = List.length s' in
410             (* insert starting_val there *)
411             let s'' = List.append s' [starting_val] in
412             (* evaluate expr2 using a new assignment function and store *)
413             eval expr2 ((var, new_index) :: e) s''
414
415         | Set ((var : identifier), expr1, expr2) ->
416             let (new_value, s') = eval expr1 e s in
417             (* lookup which index is associated with Var var *)
418             let index = List.assoc var e in
419             (* now we create a list which is just like s' except it has new_value at index *)
420             let rec replace_nth xs m = match xs with
421                 | [] -> failwith "list too short"
422                 | x::xs when m = 0 -> new_value :: xs
423                 | x::xs -> x :: replace_nth xs (m - 1) in
424             let s'' = replace_nth s' index in
425             (* evaluate expr2 using original assignment function and new store *)
426             eval expr2 e s''
427
428
429 ##How to implement mutation with a State monad##
430
431 It's possible to do all of this monadically, instead of adding new syntactic forms and new interpretation rules to a language's semantics. The patterns we use to do this in fact closely mirror the machinery described above.
432
433 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.
434
435 With a State monad, we call our book-keeping apparatus a "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.
436
437 Here's the implementation of the State monad, together with an implementation of the Reader monad for comparison:
438
439     type env = (identifier * int) list
440     (* alternatively, an env could be implemented as type identifier -> int *)
441
442     type 'a reader = env -> 'a
443     let reader_mid (x : 'a) : 'a reader =
444         fun e -> x
445     let reader_mbind (xx : 'a reader) (k : 'a -> 'b reader) : 'b reader =
446         fun e -> let x = xx e in
447                  let yy = k x in
448                  yy e
449
450     type store = int
451     (* very simple store, holds only a single int *)
452     (* this corresponds to having only a single mutable variable *)
453
454     type 'a state = store -> ('a, store)
455     let state_mid (x : 'a) : 'a state =
456         fun s -> (x, s)
457     let state_mbind (xx : 'a state) (k : 'a -> 'b state) : 'b state =
458         fun s -> let (x, s') = xx s in
459                  let yy = k x in
460                  yy s'
461
462 Notice the similarities (and differences) between the implementation of these two monads.
463
464 With the Reader monad, we also had some special-purpose operations, beyond its general monadic operations. Two to focus on were `asks` and `shift`. We would call `asks` with a helper function like `lookup "x"` that looked up a given variable in an environment. And we would call `shift` with a helper function like `insert "x" new_value` that operated on an existing environment to return a new one.
465
466 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 `asks (lookup "x")`, 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:
467
468     let state_get : store state = fun s -> (s, s)
469
470 This passes through the current store unaltered, and also returns a copy of the store as its payload. (What exactly corresponds to this is the simpler Reader operation `ask`.) We can use the `state_get` operation like this:
471
472     some_existing_state_monad_value >>= fun _ -> state_get >>= (fun cur_store -> ...)
473
474 The `fun _ ->` part here discards the payload wrapped by `some_existing_state_monad_value`. We're only going to pass through, unaltered, whatever *store* is generated by that monadic box. We also wrap that store as *our own payload*, which can be retrieved by further operations in the `... >>= ...` chain, such as `(fun cur_store -> ...)`.
475
476 As we've mentioned elsewhere, `xx >>= fun _ -> yy` can be abbreviated as `xx >> yy`.
477
478 The other operation for the State monad will be to update the existing store to a new one. This operation looks like this:
479
480     let state_put (new_store : int) : dummy state =
481         fun s -> (dummy, new_store)
482
483 If we want to stick this in a `... >>= ...` chain, we'll need to prefix it with `fun _ ->` too, like this:
484
485     some_existing_state_monad_value >>= fun _ -> state_put 100 >>= ...
486
487 Or:
488
489     some_existing_state_monad_value >> state_put 100 >>= ...
490
491 In this usage, we don't care what payload is wrapped by `some_existing_state_monad_value`. 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 `state_put` 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:
492
493 <pre>
494 some_existing_state_monad_value >> <span class=ul>state_get >>= (fun cur_store -> state_put (succ cur_store))</span> >>= ...
495 </pre>
496
497 We can define more complex functions that perform the underlined part `state_get >>= (fun cur_store -> state_put (succ cur_store))` as a single operation. In the Juli8 and Haskell monad libraries, this is expressed by the State monad operation `modify succ`.
498
499 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 payload 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.)
500
501 State monadic **operations** or Kleisli arrows (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 payload was wrapped by the preceding elements in the `... >>= ... >>= ...` chain. The computations on a store that such operations encode (which their payloads 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 payload and) a new store `s1` as output, the next computation will get `s1` as input and will return `s2` as part of its output, the next computation will get `s2` as input, ... and so on.
502
503 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:
504
505     let computation = some_state_monad_value >>= operation >>= operation in
506     computation initial_store
507
508
509 *    See also our [[State Monad Tutorial]]. LINK TODO
510
511
512
513 ##Some grades of mutation involvement##
514
515 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. This is a list of some different ways in which languages might involve mutation-like idioms. (It doesn't exhaust all the interesting such ways, but only the ones we've so far touched on.)
516
517 *    At the zeroth stage, we have a purely functional language, like we've been working with up until this week.
518
519
520 *    One increment would be to add implicit-style mutable variables, as we explained above.
521
522     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 (`var 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.
523
524     However, in language with implicit-style mutation, 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` doesn't evalute to a reference cell, but rather to the value that the reference cell it's implicitly associated with contains, at that stage in the computation.
525
526 *    Another 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**.
527
528     This introduces some interesting new conceptual possibilities. For example, what should be the result of the following fragment?
529
530         let ycell = ref 1 in
531         let xcell = ref 1 in
532         ycell = xcell
533
534     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."
535
536     On the other hand, these are numerically *two* reference cells. If we mutate one of them, the other one doesn't change. For example:
537
538         let ycell = ref 1 in
539         let xcell = ref 1 in
540         ycell := 2; !xcell
541         (* evaluates to 1, not to 2 *)
542
543     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`.
544
545     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/physical 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.
546
547     **Terminological aside**: 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: `var x = value in ...` or `set 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 `~=`).
548
549     In the following fragment:
550
551         let ycell = ref 1 in
552         let xcell = ref 1 in
553         let zcell = ycell in
554         ...
555
556     If we express numerical identity using `==`, as OCaml does, then this (and its converse) would be true:
557
558         ycell == zcell
559
560     but these would be false:
561
562         xcell == ycell
563         xcell == zcell
564
565     If we express qualitative indiscernibility using `=`, as OCaml does, then all of the salient comparisons would be true:
566
567         ycell = zcell
568         xcell = ycell
569         xcell = zcell
570
571     Because of the particular way the numerical identity predicates are implemented in all of these languages, it doesn't quite match our conceptual expectations. For instance, For instance, if `ycell` is a reference cell, then `ref !ycell` will always be a numerically distinct reference cell containing the same value. We get this pattern of comparisons in OCaml:
572
573         ycell == ycell      (* of course true *)
574         ycell != ref !ycell (* true, these aren't numerically identical *)
575
576         ycell = ycell       (* of course true *)
577         ycell = ref !ycell  (* true, they are qualitatively indiscernible *)
578
579     But now what about?
580
581         (0, 1, ycell) ? (0, 1, ycell)
582         (0, 1, ycell) ? (0, 1, ref !ycell)
583
584     You might expect the first pair to be numerically identical too --- after all, they involve the same structure (an immutable triple) each of whose components is numerically identical. But OCaml's "physical identity" predicate `==` does not detect that identity. It counts both of these comparisons as false. OCaml's `=` predicate does count the first pair as equal, but only because it's insensitive to numerical identity; it also counts the second pair as equal. This odd pattern shows up in many other languages, too. In Python, `y = []; (0, 1, y) is (0, 1, y)` evaluates to false. In Racket, `(define y (box 1)) (eq? (cons 0 y) (cons 0 y))` also evaluates to false (and in Racket, unlike traditional Schemes, `cons` is creating immutable pairs). All these languages chose an implementation for their numerical identity predicates that is especially efficient and does the right thing in the common cases, but doesn't quite match our mathematical expectations.
585
586     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:
587
588         let factory (starting_val : int) =
589             let free_var = ref starting_value in
590             let getter () = !free_var in
591             let setter (new_value : int) = free_var := new_value in
592             (getter, setter) in
593         let (getter, setter) = factory 1 in
594         let (getter', setter') = factory 1 in
595         ...
596
597     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:
598
599         let factory (starting_val : int) =
600             let free_var = ref starting_value in
601             let adder x = x + !free_var in
602             let setter (new_value : int) = free_var := new_value in
603             (adder, setter) in
604         let (adder, setter) = factory 1 in
605         let (adder', setter') = factory 1 in
606         ...
607
608     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; you just wouldn't be able to establish so.
609
610     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'`).
611
612 There are several more layers and complexity to the way different languages engage with mutation. But this exhausts what we're in a position to consider now.
613
614
615 ##Miscellany##
616
617 *    When using mutable variables, programmers will often write using *imperatival 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:
618
619         let rec factorial n =
620           if n = 0 then 1 else n * factorial (n - 1)
621
622     or like this:
623
624         let factorial n =
625           let rec aux n sofar =
626             if n = 0 then sofar else aux (n - 1) (n * sofar) in
627           aux n 1
628
629     (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.)
630
631     When using mutable variables, on the other hand, this may be written as:
632
633         let factorial n =
634             let current = ref n in
635             let total = ref 1 in
636             while !current > 0 do
637               total := !total * !current; current := !current - 1
638             done; !total
639
640     This is often referred to as an *iterative* as opposed to a *recursive* algorithm.
641
642
643 *    Mutable variables also give us a way to achieve recursion, in a language that doesn't already have it. For example:
644
645         let fact_cell = ref None in
646         let factorial n =
647           if n = 0 then 1 else match !fact_cell with
648           | Some fact -> n * fact (n - 1)
649           | None -> failwith "can't happen" in
650         let () = fact_cell := Some factorial in
651         ...
652
653     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.
654
655     If you've got a copy of *The Seasoned Schemer*, which we recommended for the seminar, see the discussion at pp. 118-125.
656
657 <!--
658 *    Now would be a good time to go back and review some material from [[week1]], and seeing how much we've learned. There's discussion back then of declarative or functional languages versus languages using imperatival features, like mutation. Mutation is distinguished from shadowing. There's discussion of sequencing, and of what we mean by saying "order matters."
659
660     In point 7 of the Rosetta Stone discussion, the contrast between call-by-name and call-by-value evaluation order appears (though we don't yet call it that). We'll be discussing that more in coming weeks. In the [[damn]] example, continuations and other kinds of side effects (namely, printing) make an appearance. These too will be center-stage in coming weeks.
661
662 *    Now would also be a good time to read [Calculator Improvements](/week10). This reviews the different systems discussed above, as well as other capabilities we can add to the calculators introduced in [week7](/reader_monad_for_variable_binding). We will be building off of that in coming weeks.
663 -->
664
665
666 ##Offsite Reading##
667
668 *    [[!wikipedia Declarative programming]]
669 *    [[!wikipedia Functional programming]]
670 *    [[!wikipedia Purely functional]]
671 *    [[!wikipedia Side effect (computer science) desc="Side effects"]]
672 *    [[!wikipedia Referential transparency (computer science)]]
673 *    [[!wikipedia Imperative programming]]
674 *    [[!wikipedia Reference (computer science) desc="References"]]
675 *    [[!wikipedia Pointer (computing) desc="Pointers"]]
676 *    [Pointers in OCaml](http://caml.inria.fr/resources/doc/guides/pointers.html)
677
678 <!--
679 # General issues about variables and scope in programming languages #
680
681 *    [[!wikipedia Variable (programming) desc="Variables"]]
682 *    [[!wikipedia Free variables and bound variables]]
683 *    [[!wikipedia Variable shadowing]]
684 *    [[!wikipedia Name binding]]
685 *    [[!wikipedia Name resolution]]
686 *    [[!wikipedia Parameter (computer science) desc="Function parameters"]]
687 *    [[!wikipedia Scope (programming) desc="Variable scope"]]
688 *    [[!wikipedia Closure (computer science) desc="Closures"]]
689
690 -->
691
692
693