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.

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.

Mutation

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.

Recall from earlier discussions that the following two forms are equivalent:

[A] let x be EXPRESSION in
      BODY

    (lambda (x) -> BODY) (EXPRESSION)

This should seem entirely familiar:

[B] let x be 1 + 2 in
      let y be 10 in
        (x + y, x + 20)
                            ; evaluates to (13, 23)

In fragment [B], we bound the variables x and y to ints. We can also bind variables to function values, as here:

[C] let f be (lambda (x, y) -> x + y + 1) in
      (f (10, 2), f (20, 2))
                            ; evaluates to (13, 23)

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:

[D] let y be 3 in
      let f be (lambda (x) -> x + y) in
        (f (10), f (20))
                            ; evaluates to (13, 23)

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.

In our next fragment, we re-use a variable that had been bound to another value in a wider context:

[E] let y be 2 in
      let y be 3 in
        (y + 10, y + 20)
                            ; evaluates to (13, 23)

As you can see, the narrowest assignment is what's effective. This is just like in predicate logic: consider ∃y (Fy and ∃y ~Fy). The computer-science terminology to describe this is that the narrower assignment of y to the value 3 shadows the wider assignment to 2.

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.

Sometimes the shadowing is merely temporary, as here:

[F] let y be 2 in
      let f be (lambda (x) ->
        let y be 3 in
          ; here the most local assignment to y applies
          x + y
      ) in
        ; here the assignment of 3 to y has expired
        (f (10), y, f (20))
                            ; evaluates to (13, 2, 23)

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:

[G] let y be 2 in
      let f be (lambda (x) ->
        change y to 3 then
          x + y
      ) in
        ; here the change in what value y was assigned *sticks*
        ; because we *updated* the value of the original variable y
        ; instead of introducing a new y with a narrower scope
        (f (10), y, f (19))
                            ; evaluates to (13, 3, 23)

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:

{
    int y = 2;    // this is like "let y be 2 in ..."
    ...
    y = 3;        // this is like "change y to 3 then ..."
    return x + y; // this is like "x + y"
}

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:

let ycell = ref 2       (* this creates a new reference cell *)
...
in let () = ycell := 3  (* this changes the contents of that cell to 3 *)
                        (* the return value of doing so is () *)
                        (* other return values could also be reasonable: *)
                        (* such as the old value of ycell, the new value, an arbitrary int, and so on *)
in x + !ycell;;         (* the !ycell operation "dereferences" the cell---it retrieves the value it contains *)

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:

(let ([ycell (box 2)])
    ...
    (set-box! ycell 3)
    (+ x (unbox ycell)))

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

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.

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:

let triple = (expression_a, expression_b, expression_c)

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:

let a = expression_a
    in let b = expression_b
        in expression_c

Scheme does the same. (If you use Scheme's let*, but not if you use its let. I agree this is annoying.)

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:

let () = expression_a
    in let () = expression_b
        in expression_c

And OCaml has a syntactic shorthand for this form, namely to use semi-colons:

expression_a; expression_b; expression_c

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:

(expression_a; expression_b; expression_c)

begin expression_a; expression_b; expression_c end

Scheme has a construction similar to the latter:

(begin (expression_a) (expression_b) (expression_c))

Though often in Scheme, the (begin ...) is implicit and doesn't need to be explicitly inserted, as here:

(lambda (x) (expression_a) (expression_b) (expression_c))

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:

let f () = ...

or this:

let f = fun () -> ...

In Scheme these are written as functions that take 0 arguments:

(lambda () ...)

or:

(define (f) ...)

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:

let ycell = ref 1
in let f () = ycell := !ycell + 1
in let z = !ycell
in f ()
in z;;

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.

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:

let factory (starting_value : 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 first = getter ()
in let () = setter 2
in let second = getter ()
in let () = setter 3
in let third = getter ()
in (first, second, third)

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:

def factory (starting_value):
    free_var = starting_value
    def getter ():
        return free_var
    def setter (new_value):
        # the next line indicates that we're using the
        # free_var from the surrounding function, not
        # introducing a new local variable with the same name
        nonlocal free_var
        free_var = new_value
    return getter, setter
getter, setter = factory (1)
first = getter ()
setter (2)
second = getter ()
setter (3)
third = getter ()
(first, second, third)

Here, too, just as in the OCaml fragment, all the calls to getter and setter are working with a single mutable variable free_var.

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.

If however you called factory twice, you'd have different getter/setter pairs, each of which had their own, independent free_var. In OCaml:

let factory (starting_val : int) =
... (* as above *)
in let (getter, setter) = factory 1
in let (getter', setter') = factory 1
in let () = setter 2
in getter' ()

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.

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.

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.

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)

should evaluate the same as:

let x = 1
    in (x, 1)

or:

(1, 1)

Notice, however, that when mutable variables are present, the same substitution patterns can't always be relied on:

let ycell = ref 1
    in ycell := 2; !ycell
(* evaluates to 2 *)

(ref 1) := 2; !(ref 1)
(* creates a ref 1 cell and changes its contents *)
(* 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.

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.

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 ints, and we'll let the store be a list of ints.

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.

Before we brought mutation on the scene, our language's semantics will have looked something like this:

[[expression]]g = value

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:

[[expression]]g s = (value, s')

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. 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 ...
    

    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 ints. Somehow we should keep track of which variables are assigned ints as ints and which are assigned ints as indexes into the store. So we'll create a special type to wrap the latter:

    type store_index = Index of int;;
    

    Our interpretation function will look something like this:

    let rec eval expression g s =
        match expression with
        ...
        | 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' *)
            in let new_index = List.length s'
            (* now we want to insert starting_val there; the following is an easy but inefficient way to do it *)
            in let s'' = List.append s' [starting_val]
            (* now we return a pair of a wrapped new_index, and the new store *)
            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 (assuming it wasn't changed during the evaluation of expr).

    let rec eval expression g s =
        match expression with
        ...
        | 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.

    let rec eval expression g s =
        match expression with
        ...
        | Setref (expr1, expr2) ->
            let (Index n, s') = eval expr1 g s
            (* 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 =
                match lst with
                | [] -> failwith "list too short"
                | x::xs when m = 0 -> new_value :: xs
                | x::xs -> x :: replace_nth xs (m - 1)
            in let s''' = replace_nth s'' n
            in (dummy, s''')
        ...
    

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.

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.

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.

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 above and as in week7.

let rec eval expression g s =
    match expression with
    ...
    | Var (c : char) ->
        let index = List.assoc c g
        (* retrieve the value at that index in the current store *)
        in let value = List.nth s index
        in (value, s)

    | 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'
        (* insert starting_val there *)
        in let s'' = List.append s' [starting_val]
        (* evaluate expr2 using a new assignment function and store *)
        in eval expr2 ((c, new_index) :: g) s''

    | 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
        (* now we create a list which is just like s' except it has new_value at index *)
        in let rec replace_nth lst m =
            match lst with
            | [] -> failwith "list too short"
            | x::xs when m = 0 -> new_value :: xs
            | x::xs -> x :: replace_nth xs (m - 1)
        in let s'' = replace_nth s' index
        (* 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, Stokhof 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

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.

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 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:

type env = (char * int) list;;
(* alternatively, an env could be implemented as type char -> int *)

type 'a reader = env -> 'a;;
let reader_unit (value : 'a) : 'a reader =
    fun e -> value;;
let reader_bind (u : 'a reader) (f : 'a -> 'b reader) : 'b reader =
    fun e -> let a = u e
             in let u' = f a
             in u' e;;

type store = int;;
(* very simple store, holds only a single int *)
(* this corresponds to having only a single mutable variable *)

type 'a state = store -> ('a, store);;
let state_unit (value : 'a) : 'a state =
    fun s -> (value, s);;
let state_bind (u : 'a state) (f : 'a -> 'b state) : 'b state =
    fun s -> let (a, s') = u s
             in let u' = f a
             in u' s';;

Notice the similarities (and differences) between the implementation of these two monads.

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:

let state_get : store state =
        fun s -> (s, s);;

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_box >>= fun _ -> state_get >>= (fun cur_store -> ...)

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 state_put (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_box >>= fun _ -> state_put 100 >>= ...

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 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:

some_existing_state_monad_box >>= fun _ -> state_get >>= (fun cur_store -> state_put (cur_store + 1) >>= ...

We can of course define more complex functions that perform the state_get >>= (fun cur_store -> state_put (cur_store + 1) as a single operation.

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 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_box >>= operation >>= operation
in computation initial_store;;

Aliasing or Passing by reference

-- FIXME --

[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 ...

[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".

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."

    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 refs 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 ι and -ι are qualitatively indiscernible, but numerically distinct. However, arguably they're not fully qualitatively indiscernible. They don't both bear all the same relations to ι 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; you just wouldn't be able to establish so.

    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

  • 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:

    let rec factorial n =
        if n = 0 then 1 else n * factorial (n - 1)
    

    or like this:

    let factorial n =
        let rec helper n sofar =
            if n = 0 then sofar else helper (n - 1) (n * sofar)
        in helper n 1
    

    (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.)

    When using mutable variables, on the other hand, this may be written as:

    let factorial n =
        let current = ref n
        in let total = ref 1
        in while !current > 0 do
            total := !total * !current; current := !current - 1
        done; !total
    
  • Mutable variables also give us a way to achieve recursion, in a language that doesn't already have it. For example:

    let fact_cell = ref None
    in let factorial n =
        if n = 0 then 1 else match !fact_cell with
            | Some fact -> n * fact (n - 1)
            | None -> failwith "can't happen"
    in let () = fact_cell := Some factorial
    in ...
    

    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.

    If you've got a copy of The Seasoned Schemer, which we recommended for the seminar, see the discussion at pp. 118-125.

  • 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 Calculator Improvements. This reviews the different systems discussed above, as well as other capabilities we can add to the calculators introduced in week7. We will be building off of that in coming weeks.

Offsite Reading