tweak posting week10
[lambda.git] / week9.mdwn
index ba99a79..546b2d2 100644 (file)
@@ -100,7 +100,15 @@ Scheme is similar. There are various sorts of reference cells available in Schem
                (set-box! ycell 3)
                (+ x (unbox ycell)))
 
-When dealing with explicit-style mutation, there's a difference between the types and values of `ycell` and `!ycell` (or `(unbox ycell)`). The former has the type `int ref`: the variable `ycell` is assigned a reference cell that contains an `int`. The latter has the type `int`, and has whatever value is now stored in the relevant reference cell. In an implicit-style framework though, we only have the resources to refer to the contents of the relevant reference cell. `y` in fragment [G] or the C snippet above has the type `int`, and only ever evaluates to `int` values.
+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:
+
+       (begin
+               (define x 1)
+               (set! x 2)
+               x)
+       ; evaluates to 2
+
+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.
 
 
 ##Controlling order##
@@ -224,7 +232,27 @@ Notice in these fragments that once we return from inside the call to `factory`,
 
 ##Referential opacity##
 
-In addition to order-sensitivity, when you're dealing with mutable variables you also give up a property that computer scientists call "referential transparency." It's not obvious whether they mean exactly the same by that as philosophers and linguists do, or only something approximately the same. What they do mean is a kind of substitution principle, illustrated here:
+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.
+
+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:
+
+       let ycell = ref 1
+               in let f x = x + !ycell
+                       in let first = f 1      (* first is assigned the value 2 *)
+                               in ycell := 2; let second = f 1 (* second is assigned the value 3 *)
+                                       in first = second;; (* not true! *)
+
+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.
+
+Similarly, functions like these:
+
+       let f cell = !cell;;
+
+       let g cell = cell := !cell + 1; !cell;;
+
+may return different results each time they're invoked, even if they're always supplied one and the same reference cell as argument.
+
+Computer scientists also associate referential transparency with a kind of substitution principle, illustrated here:
 
        let x = 1
                in (x, x)
@@ -249,6 +277,8 @@ Notice, however, that when mutable variables are present, the same substitution
        (* then creates a *new* ref 1 cell and returns *its* contents *)
 
 
+
+
 ##How to implement explicit-style mutable variables##
 
 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.
@@ -267,9 +297,36 @@ Now we're going to relativize our interpretations not only to the assignment fun
 
 >      \[[expression]]<sub>g s</sub> = (value, s')
 
-With that kind of framework, we can interpret `newref`, `deref`, and `setref` as follows.
+For expressions we already know how to interpret, expect `s'` to just be `s`.
+An exception is complex expressions like `let var = expr1 in expr2`. Part of
+interpreting this will be to interpret the sub-expression `expr1`, and we have
+to allow that in doing that, the store may have already been updated. We want
+to use that possibly updated store when interpreting `expr2`. Like this:
+
+       let rec eval expression g s =
+               match expression with
+               ...
+               | Let (c, expr1, expr2) ->
+                       let (value, s') = eval expr1 g s
+                       (* s' may be different from s *)
+                       (* now we evaluate expr2 in a new environment where c has been associated
+                          with the result of evaluating expr1 in the current environment *)
+                       eval expr2 ((c, value) :: g) s'
+               ...
+
+Similarly:
+
+               ...
+               | Addition (expr1, expr2) ->
+                       let (value1, s') = eval expr1 g s
+                       in let (value2, s'') = eval expr2 g s'
+                       in (value1 + value2, s'')
+               ...
+
+Let's consider how to interpet our new syntactic forms `newref`, `deref`, and `setref`:
+
 
-1.     \[[newref starting_val]] should allocate a new reference cell in the store and insert `starting_val` into that cell. It should return some "key" or "index" or "pointer" to the newly created reference cell, so that we can do things like:
+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:
 
                let ycell = newref 1
                in ...
@@ -283,7 +340,7 @@ With that kind of framework, we can interpret `newref`, `deref`, and `setref` as
                let rec eval expression g s =
                        match expression with
                        ...
-                       | Newref expr ->
+                       | Newref (expr) ->
                                let (starting_val, s') = eval expr g s
                                (* note that s' may be different from s, if expr itself contained any mutation operations *)
                                (* now we want to retrieve the next free index in s' *)
@@ -294,25 +351,25 @@ With that kind of framework, we can interpret `newref`, `deref`, and `setref` as
                                in (Index new_index, s'')
                        ... 
 
-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.
+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`).
 
                let rec eval expression g s =
                        match expression with
                        ...
-                       | Deref expr ->
+                       | Deref (expr) ->
                                let (Index n, s') = eval expr g s
                                (* note that s' may be different from s, if expr itself contained any mutation operations *)
                                in (List.nth s' n, s')
                        ...
 
-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`.
+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`.
 
                let rec eval expression g s =
                        match expression with
                        ...
-                       | Setref expr1 expr2
+                       | Setref (expr1, expr2) ->
                                let (Index n, s') = eval expr1 g s
-                               (* note that s' may be different from s, if expr itself contained any mutation operations *)
+                               (* note that s' may be different from s, if expr1 itself contained any mutation operations *)
                                in let (new_value, s'') = eval expr2 g s'
                                (* now we create a list which is just like s'' except it has new_value in index n *)
                                in let rec replace_nth lst m =
@@ -325,6 +382,9 @@ With that kind of framework, we can interpret `newref`, `deref`, and `setref` as
                        ...
 
 
+
+
+
 ##How to implement implicit-style mutable variables##
 
 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.
@@ -335,7 +395,7 @@ This brings up an interesting conceptual distinction. Formerly, we'd naturally t
 
 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`.
 
-Here's how to implement these. We'll suppose that our assignment function is list of pairs, as in [week6](/reader_monad_for_variable_binding).
+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).
 
        let rec eval expression g s =
                match expression with
@@ -346,7 +406,7 @@ Here's how to implement these. We'll suppose that our assignment function is lis
                        in let value = List.nth s index
                        in (value, s)
 
-               | Let (c : char) expr1 expr2 ->
+               | Let ((c : char), expr1, expr2) ->
                        let (starting_val, s') = eval expr1 g s
                        (* get next free index in s' *)
                        in let new_index = List.length s'
@@ -355,7 +415,7 @@ Here's how to implement these. We'll suppose that our assignment function is lis
                        (* evaluate expr2 using a new assignment function and store *)
                        in eval expr2 ((c, new_index) :: g) s''
 
-               | Change (c : char) expr1 expr2 ->
+               | Change ((c : char), expr1, expr2) ->
                        let (new_value, s') = eval expr1 g s
                        (* lookup which index is associated with Var c *)
                        in let index = List.assoc c g
@@ -369,6 +429,8 @@ Here's how to implement these. We'll suppose that our assignment function is lis
                        (* evaluate expr2 using original assignment function and new store *)
                        in eval expr2 g s''
 
+Note: Chris uses this kind of machinery on the third page of the Nov 22 handout. Except he implements `Let` the way we here implement `Change`. And he adds an implementation of `Alias` (see below). Some minor differences: on his handout (and following Groenendijk, Stockhof and Veltman), he uses `r` and `g` where we use `g` and `s` respectively. Also, he implements his `r` with a function from `char` to `int`, instead of a `(char * int) list`, as we do here. It should be obvious how to translate between these. His implementation requires that variables always already have an associated peg. So that when we call `Let(c, expr1, expr2)` for the first time with `c`, there's a peg whose value is to be updated. That's easier to ensure when you implement the assignment as a function than as a `(char * int) list`.
+
 
 ##How to implement mutation with a State monad##
 
@@ -376,7 +438,7 @@ It's possible to do all of this monadically, and so using a language's existing
 
 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.
 
-With a State monad, we call our book-keeping apparatus a "state" or "store" instead of an evironment, and this time we are able to both read from it and write to it. To keep things simple, we'll work here with the simplest possible kind of store, which only holds a single value. One could also have stores that were composed of a list of values, of a length that could expand or shrink, or even more complex structures.
+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.
 
 Here's the implementation of the State monad, together with an implementation of the Reader monad for comparison:
 
@@ -412,32 +474,32 @@ With the Reader monad, we also had some special-purpose operations, beyond its g
 
 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:
 
-       some_existing_state_monad >>= fun _ -> get_state >>= (fun cur_state -> ...)
+       some_existing_state_monad_box >>= fun _ -> get_state >>= (fun cur_store -> ...)
 
-The `fun _ ->` part here discards the value wrapped by `some_existing_state_monad`. We're only going to pass through, unaltered, whatever *store* is generated by that monadic value. We also wrap that store as *our own value*, which can be retrieved by further operations in the `... >>= ...` chain, such as `(fun cur_state -> ...)`.
+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 -> ...)`.
 
 The other operation for the State monad will be to update the existing store to a new one. This operation looks like this:
 
-       let set_state (value : int) : dummy state =
-               fun s -> (dummy, value);;
+       let set_state (new_store : int) : dummy state =
+               fun s -> (dummy, new_store);;
 
 If we want to stick this in a `... >>= ...` chain, we'll need to prefix it with `fun _ ->` too, like this:
 
-       some_existing_state_monad >>= fun _ -> set_state 100 >>= ...
+       some_existing_state_monad_box >>= fun _ -> set_state 100 >>= ...
 
-In this usage, we don't care what value is wrapped by `some_existing_state_monad`. We don't even care what store it generates, since we're going to replace that store with our own new store. A more complex kind of `set_state` operation might insert not just some constant value as the new store, but rather the result of applying some function to the existing store. For example, we might want to increment the current store. Here's how we could do that:
+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:
 
-       some_existing_state_monad >>= fun _ -> get_state >>= (fun cur_state -> set_state (cur_state + 1) >>= ...
+       some_existing_state_monad_box >>= fun _ -> get_state >>= (fun cur_store -> set_state (cur_store + 1) >>= ...
 
-We can of course define more complex functions that perform the `get_state >>= (fun cur_state -> set_state (cur_state + 1)` as a single operation.
+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.
 
-In general, a State monadic **value** (type `'a state`, what appears at the start of a `... >>= ... >>= ...` chain) is an operation that accepts some starting store as input---where the store might be simple as it is here, or much more complex---and returns a value plus a possibly modified store. This can be thought of as an encoding of some operation on a store serving as a box wrapped around a value.
+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.)
 
-State monadic **operations** (type `'a -> 'b state`, what appears anywhere in the middle or end of a `... >>= ... >>= ...` chain) are operations that generate new State monadic values, based on what value was wrapped by the preceding elements in the `... >>= ... >>= ...` chain. The computations on a store that these encode (which their values may or may not be sensitive to) will be chained in the order given by their position in the `... >>= ... >>= ...` chain. That is, the computation encoded by the first element in the chain will accept a starting store s0 as input, and will return (a value and) a new store s1 as output, the next computation will get s1 as input and will return s2 as output, the next computation will get s2 as input, ... and so on.
+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.
 
 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:
 
-       let computation = some_state_monadic_value >>= operation >>= operation
+       let computation = some_state_monadic_box >>= operation >>= operation
        in computation initial_store;;
 
 
@@ -446,83 +508,205 @@ To get the whole process started, the complex computation so defined will need t
 
 -- FIXME --
 
-    [H] ; *** aliasing ***
-        let y be 2 in
-          let x be y in
-            let w alias y in
-              (y, x, w)           ==> (2, 2, 2)
-
-    [I] ; mutation plus aliasing
-        let y be 2 in
-          let x be y in
-            let w alias y in
-              change y to 3 then
-                (y, x, w)         ==> (3, 2, 3)
-
-    [J] let f be (lambda (y) -> BODY) in  ; a
-          ... f (EXPRESSION) ...
-
-        (lambda (y) -> BODY) EXPRESSION
-
-        let y be EXPRESSION in            ; b
-          ... BODY ...
-
-    [K] ; *** passing "by reference" ***
-        let f be (lambda (alias w) ->     ; ?
-          BODY
-        ) in
-          ... f (y) ...
-
-        let w alias y in                  ; d
-          ... BODY ...
-
-    [L] let f be (lambda (alias w) ->
-          change w to 2 then
-            w + 2
-        ) in
-          let y be 1 in
-            let z be f (y) in
-              ; y is now 2, not 1
-              (z, y)              ==> (4, 2)
-
-    [M] ; hyper-evaluativity
-        let h be 1 in
-          let p be 1 in
-            let f be (lambda (alias x, alias y) ->
-              ; contrast here: "let z be x + y + 1"
-              change y to y + 1 then
-                let z be x + y in
-                  change y to y - 1 then
-                    z
-            ) in
-              (f (h, p), f (h, h))
-                                  ==> (3, 4)
-
-    Notice: h, p have same value (1), but f (h, p) and f (h, h) differ
-
-
-##Five grades of mutation involvement##
+       [H] ; *** aliasing ***
+           let y be 2 in
+             let x be y in
+               let w alias y in
+                 (y, x, w)
+                                                               ; evaluates to (2, 2, 2)
+
+       [I] ; mutation plus aliasing
+           let y be 2 in
+             let x be y in
+               let w alias y in
+                 change y to 3 then
+                   (y, x, w)
+                                                               ; evaluates to (3, 2, 3)
+
+       [J] ; as we already know, these are all equivalent:
+       
+           let f be (lambda (y) -> BODY) in  ; #1
+             ... f (EXPRESSION) ...
+       
+           (lambda (y) -> BODY) EXPRESSION   ; #2
+       
+           let y be EXPRESSION in            ; #3
+             ... BODY ...
 
--- FIXME --
+       [K] ; *** passing by reference ***
+           ; now think: "[J#1] is to [J#3] as [K#1] is to [K#2]"
+       
+           ?                                 ; #1
+       
+           let w alias y in                  ; #2
+             ... BODY ...
+       
+           ; We introduce a special syntactic form to supply
+           ; the missing ?
+       
+           let f be (lambda (alias w) ->     ; #1
+             BODY
+           ) in
+             ... f (y) ...
+
+       [L] let f be (lambda (alias w) ->
+             change w to 2 then
+               w + 2
+           ) in
+             let y be 1 in
+               let z be f (y) in
+                 ; y is now 2, not 1
+                 (z, y)
+                                                               ; evaluates to (4, 2)
+
+       [M] ; hyper-evaluativity
+           let h be 1 in
+             let p be 1 in
+               let f be (lambda (alias x, alias y) ->
+                 ; contrast here: "let z be x + y + 1"
+                 change y to y + 1 then
+                   let z be x + y in
+                     change y to y - 1 then
+                       z
+               ) in
+                 (f (h, p), f (h, h))
+                                                               ; evaluates to (3, 4)
+
+Notice: in [M], `h` and `p` have same value (1), but `f (h, p)` and `f (h, h)` differ.
+
+See Pryor's "[Hyper-Evaluativity](http://www.jimpryor.net/research/papers/Hyper-Evaluativity.txt)".
+
+
+##Four grades of mutation involvement##
+
+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.
+
+*      At the first stage, we have a purely functional language, like we've been working with up until this week.
+
+
+*      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."
 
-    0. Purely functional languages
-    1. Passing by reference
-       need primitive hyper-evaluative predicates for it to make a difference
-    2. mutable variables
-    3. mutable values
-        - numerically distinct but indiscernible values
-        - two equality predicates
-        - examples: closures with currently-indiscernible but numerically distinct
-          environments, mutable lists
-    4. "references" as first-class values
-        - x not the same as !x, explicit deref operation
-        - can not only be assigned and passed as arguments, also returned (and manipulated?)
-        - can be compared for qualitative equality
-    5. structured references
+       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.
+
+
+*      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.
+
+       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:
+
+               let f = (lambda (alias w) -> ...)
+                       in let x = 1
+                               in f (x)
+
+       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).
+
+       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.
+
+*      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**.
+
+       This introduces some interesting new conceptual possibilities. For example, what should be the result of the following fragment?
+
+               let ycell = ref 1
+               in let xcell = ref 1
+               in ycell = xcell
+
+       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."
+
+       On the other hand, these are numerically *two* reference cells. If we mutate one of them, the other one doesn't change. For example:
+
+               let ycell = ref 1
+               in let xcell = ref 1
+               in ycell := 2
+               in !xcell;;
+               (* evaluates to 1, not to 2 *)
+
+       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`.
+
+       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.
+
+       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 `~=`).
+
+       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:
+
+               ycell == ycell
+               ycell != ref !ycell (* true, these aren't numerically identical *)
+
+               ycell = ycell
+               ycell = ref !ycell (* true, they are qualitatively indiscernible *)
+
+       But now what about?
+
+               (0, 1, ycell) ? (0, 1, ycell)
+               (0, 1. ycell) ? (0, 1. ref !ycell)
+
+       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 shows up in all the other languages I know, as well. 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). They 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.
+
+       Additionally, note that none of the equality predicates so far considered is the same as the "hyperequals" predicate mentioned above. For example, in the following (fictional) language:
+
+               let ycell = ref 1
+               in let xcell = ref 1
+               in let wcell alias ycell
+               in let zcell = ycell
+               in ...
+
+       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:
+
+               ycell == wcell
+               ycell == zcell
+
+       but these would be false:
+
+               xcell == ycell
+               xcell == wcell
+               xcell == zcell
+
+       If we express qualitative indiscernibility using `=`, as OCaml does, then all of the salient comparisons would be true:
+
+               ycell = wcell
+               ycell = zcell
+               xcell = ycell
+               ...
+
+       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:
+
+               let factory (starting_val : int) =
+                       let free_var = ref starting_value
+                       in let getter () =
+                               !free_var
+                       in let setter (new_value : int) =
+                               free_var := new_value
+                       in (getter, setter)
+               in let (getter, setter) = factory 1
+               in let (getter', setter') = factory 1
+               in ...
+
+       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:
+
+               let factory (starting_val : int) =
+                       let free_var = ref starting_value
+                       in let adder x =
+                               x + !free_var
+                       in let setter (new_value : int) =
+                               free_var := new_value
+                       in (adder, setter)
+               in let (adder, setter) = factory 1
+               in let (adder', setter') = factory 1
+               in ...
+
+       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.
+
+       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'`).
+
+
+*      A fourth grade of mutation involvement: (--- FIXME ---)
+
+       structured references
         (a) if `a` and `b` are mutable variables that uncoordinatedly refer to numerically the same value
             then mutating `b` won't affect `a` or its value
         (b) if however their value has a mutable field `f`, then mutating `b.f` does
             affect their shared value; will see a difference in what `a.f` now evaluates to
+               (c) examples: Scheme mutable pairs, OCaml mutable arrays or records
+
 
 
 ##Miscellany##
@@ -563,8 +747,36 @@ To get the whole process started, the complex computation so defined will need t
 
        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.
 
+*      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."
+
+       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.
+*      Now would also be a good time to read [[Advanced Topics/Calculator Improvements]]. 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.
+
+
+##Offsite Reading##
+
+*      [[!wikipedia Declarative programming]]
+*      [[!wikipedia Functional programming]]
+*      [[!wikipedia Purely functional]]
+*      [[!wikipedia Side effect (computer science) desc="Side effects"]]
+*      [[!wikipedia Referential transparency (computer science)]]
+*      [[!wikipedia Imperative programming]]
+*      [[!wikipedia Reference (computer science) desc="References"]]
+*      [[!wikipedia Pointer (computing) desc="Pointers"]]
+*      [Pointers in OCaml](http://caml.inria.fr/resources/doc/guides/pointers.html)
 
 <!--
-Fine and Pryor on "coordinated contents" (see, e.g., [Hyper-Evaluativity](http://www.jimpryor.net/research/papers/Hyper-Evaluativity.txt))
+# General issues about variables and scope in programming languages #
+
+*      [[!wikipedia Variable (programming) desc="Variables"]]
+*      [[!wikipedia Free variables and bound variables]]
+*      [[!wikipedia Variable shadowing]]
+*      [[!wikipedia Name binding]]
+*      [[!wikipedia Name resolution]]
+*      [[!wikipedia Parameter (computer science) desc="Function parameters"]]
+*      [[!wikipedia Scope (programming) desc="Variable scope"]]
+*      [[!wikipedia Closure (computer science) desc="Closures"]]
+
 -->