tweak calc improvements
[lambda.git] / advanced_topics / calculator_improvements.mdwn
index d6654db..d3beef1 100644 (file)
@@ -61,12 +61,12 @@ We'd then want to add the ability to construct pairs, and extract their componen
 
 We won't try here to catch any type errors, such as attempts to add a `bool` to an `int`, or attempts to check whether a `bool` iszero. Neither will we try here to monadize anything: these will be implementations of a calculator with all the plumbing exposed. What we will do is add more and more features to the calculator.
 
 
 We won't try here to catch any type errors, such as attempts to add a `bool` to an `int`, or attempts to check whether a `bool` iszero. Neither will we try here to monadize anything: these will be implementations of a calculator with all the plumbing exposed. What we will do is add more and more features to the calculator.
 
-We'll switch over to using variable `g` for assignment functions, which is a convention many of you seem familiar with. As we mentioned a few times in week 9, for some purposes it's easier to implement environment or assignment functions as functions from `char`s to `int`s (or whatever variables are bound to), rather than as lists of pairs. However, we'll stick with this implementation for now. We will however abstract out the type that the variables are bound to. For now, we'll suppose that they're bound to the same types that terms can express.
+We'll switch over to using variable `g` for assignment functions, which is a convention many of you seem familiar with. As we mentioned a few times in [[week9]], for some purposes it's easier to implement environment or assignment functions as functions from `char`s to `int`s (or whatever variables are bound to), rather than as lists of pairs. However, we'll stick with this implementation for now. We will however abstract out the type that the variables are bound to. For now, we'll suppose that they're bound to the same types that terms can express.
 
        type bound_value = expressed_value;;
        type assignment = (char * bound_value) list;;
 
 
        type bound_value = expressed_value;;
        type assignment = (char * bound_value) list;;
 
-Here's where we should be now. We expand some of the clauses in the `eval` function for clarity, and we rename a few variables:
+Here's where we should be now. We'll work with the language:
 
        type term =
          Intconstant of int
 
        type term =
          Intconstant of int
@@ -80,6 +80,8 @@ Here's where we should be now. We expand some of the clauses in the `eval` funct
        | First of term
        ;;
 
        | First of term
        ;;
 
+Here is our evaluation function. We expand some of the clauses and rename a few variables for clarity. Our implementation should make it clear how to add additional constants or native predicates, such as a `Second` predicate for extracting the second element of a pair.
+
        let rec eval (t : term) (g : assignment) = match t with
          Intconstant x -> Int x
        | Multiplication (t1, t2) ->
        let rec eval (t : term) (g : assignment) = match t with
          Intconstant x -> Int x
        | Multiplication (t1, t2) ->
@@ -367,7 +369,7 @@ Our evaluation function will now expect a `store` argument as well as an `assign
        let rec eval (t : term) (g : assignment) (s : store) = match t with
          Intconstant x -> (Int x, s)
          ...
        let rec eval (t : term) (g : assignment) (s : store) = match t with
          Intconstant x -> (Int x, s)
          ...
-       | Variable (var) -> (
+       | Variable (var) -> ((
                (* we don't handle cases where g doesn't bind var to any value *)
                match List.assoc var g with
           | Nonrecursive value -> value
                (* we don't handle cases where g doesn't bind var to any value *)
                match List.assoc var g with
           | Nonrecursive value -> value
@@ -375,7 +377,7 @@ Our evaluation function will now expect a `store` argument as well as an `assign
                          (* we update savedg to bind self_var to rec_closure here *)
               let savedg' = (self_var, rec_closure) :: savedg
               in Closure (arg_var, body, savedg')
                          (* we update savedg to bind self_var to rec_closure here *)
               let savedg' = (self_var, rec_closure) :: savedg
               in Closure (arg_var, body, savedg')
-        ), s
+        ), s)
          ...
        | Lambda (arg_var, t2) -> (Closure (arg_var, t2, g), s)
          ...
          ...
        | Lambda (arg_var, t2) -> (Closure (arg_var, t2, g), s)
          ...
@@ -446,12 +448,12 @@ Now we need to formulate the clauses for evaluating the new forms `Newref (...)`
 
        ...
        | Newref (t1) ->
 
        ...
        | Newref (t1) ->
-               let (starting_val, s') = eval t1 g s
+               let (value1, s') = eval t1 g s
                (* note that s' may be different from s, if t1 itself contained any mutation operations *)
                (* now we want to retrieve the next free index in s' *)
                in let new_index = List.length s'
                (* note that s' may be different from s, if t1 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 want to insert value1 there; the following is an easy but inefficient way to do it *)
+               in let s'' = List.append s' [value1]
                (* now we return a pair of a wrapped new_index, and the new store *)
                in (Mutcell new_index, s'')
        | Deref (t1) ->
                (* now we return a pair of a wrapped new_index, and the new store *)
                in (Mutcell new_index, s'')
        | Deref (t1) ->
@@ -463,12 +465,12 @@ Now we need to formulate the clauses for evaluating the new forms `Newref (...)`
                (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
                let (Mutcell index1, s') = eval t1 g s
                (* note that s' may be different from s, if t1 itself contained any mutation operations *)
                (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
                let (Mutcell index1, s') = eval t1 g s
                (* note that s' may be different from s, if t1 itself contained any mutation operations *)
-               in let (new_value, s'') = eval t2 g s'
-               (* now we create a list which is just like s'' except it has new_value in index1 *)
+               in let (value2, s'') = eval t2 g s'
+               (* now we create a list which is just like s'' except it has value2 in index1 *)
                in let rec replace_nth lst m =
                        match lst with
                        | [] -> failwith "list too short"
                in let rec replace_nth lst m =
                        match lst with
                        | [] -> failwith "list too short"
-                       | x::xs when m = 0 -> new_value :: xs
+                       | x::xs when m = 0 -> value2 :: xs
                        | x::xs -> x :: replace_nth xs (m - 1)
                in let s''' = replace_nth s'' index1
                (* we'll arbitrarily return Int 42 as the expressed_value of a Setref operation *)
                        | x::xs -> x :: replace_nth xs (m - 1)
                in let s''' = replace_nth s'' index1
                (* we'll arbitrarily return Int 42 as the expressed_value of a Setref operation *)
@@ -536,12 +538,12 @@ Finally, here are the changed or added clauses to the evaluation function:
         (* we don't handle cases where t1 doesn't evaluate to a Pair *)
         let (Pair (index1, index2), s') = eval t1 g s
         (* note that s' may be different from s, if t1 itself contained any mutation operations *)
         (* we don't handle cases where t1 doesn't evaluate to a Pair *)
         let (Pair (index1, index2), s') = eval t1 g s
         (* note that s' may be different from s, if t1 itself contained any mutation operations *)
-        in let (new_value, s'') = eval t2 g s'
-        (* now we create a list which is just like s'' except it has new_value in index1 *)
+        in let (value2, s'') = eval t2 g s'
+        (* now we create a list which is just like s'' except it has value2 in index1 *)
         in let rec replace_nth lst m =
             match lst with
             | [] -> failwith "list too short"
         in let rec replace_nth lst m =
             match lst with
             | [] -> failwith "list too short"
-            | x::xs when m = 0 -> new_value :: xs
+            | x::xs when m = 0 -> value2 :: xs
             | x::xs -> x :: replace_nth xs (m - 1)
         in let s''' = replace_nth s'' index1
         in (Int 42, s''')
             | x::xs -> x :: replace_nth xs (m - 1)
         in let s''' = replace_nth s'' index1
         in (Int 42, s''')
@@ -583,7 +585,7 @@ In the present implementation, we separate the roles of the `bound_value` and `e
         
        type store = expressed_value list;;
 
         
        type store = expressed_value list;;
 
-Our evaluation function still interacts with a `store` argument in much the same way it did with explicit-style mutation. The clause for `Variable ...` works differently, because all `expressed_value`s now need to be retrieved from the `store`:
+Our evaluation function still interacts with a `store` argument in much the same way it did with explicit-style mutation. The clause for `Variable (...)` works differently, because all `expressed_value`s now need to be retrieved from the `store`:
         
        let rec eval (t : term) (g : assignment) (s : store) = match t with
        ...
         
        let rec eval (t : term) (g : assignment) (s : store) = match t with
        ...
@@ -653,12 +655,51 @@ Finally, here is the clause for `Change (...)`, which takes over the role earlie
                in eval t3 g s''
        ;;
 
                in eval t3 g s''
        ;;
 
-Note that because the `savedg` component of a `Closure` keeps track of which `index`es in the store free variables were bound to, the values at those `index`es can later be changed, and later applications of the `Closure` will use the changed values.
+Note that because the `savedg` component of a `Closure` keeps track of which `index`es in the store---rather than which values---free variables were bound to, the values at those `index`es can later be changed, and later applications of the `Closure` will use the changed values.
 
 The complete code is available [here](/code/calculator/calc6.ml).
 
 ##Adding Aliasing and Passing by Reference##
 
 
 The complete code is available [here](/code/calculator/calc6.ml).
 
 ##Adding Aliasing and Passing by Reference##
 
+Next we'll add aliasing as described at the end of [[week9]]. We'll also add the ability to pass (implicit) reference cells as arguments to a function, which lets changes made within the function body be effective in the outside environment. When we discussed this in [[week9]], we proposed a different syntactic form for the function values that get called in this way. Instead of:
+
+       let f = lambda (y) -> ...
+       ...
+       in f x
+
+one would write:
+
+       let f = lambda (alias y) -> ...
+       ...
+       in f x
+
+Real programming languages that have this ability, such as C++, do something analagous. Here the function is declared so that *all* of its applications are expected to alias the supplied argument. You can always work around that in a particular case, though, like this:
+
+       let f = lambda (alias y) -> ...
+       ...
+       in let y = x ; creates new (implicit) reference cell with x's value
+       in f y
+
+In our present framework, it will be easier to do things differently. We will
+introduce a new syntactic form at the location where a function value is
+applied, rather than in the function's declaration. We say:
+
+       Let ('f',
+               Lambda ('y', ...),
+               ...
+               Apply(Variable 'f', Variable 'x')...)
+
+for the familiar, passing-by-value behavior, and will instead say:
+
+       Let ('f',
+               Lambda ('y', ...),
+               ...
+               Applyalias(Variable 'f', 'x')...)
+
+for the proposed new, passing-by-reference behavior. (Besides being easier to implement here, this strategy also has the advantage of more closely aligning with the formal system Jim discusses in his "Hyper-evaluativity" paper.) Note that the second parameter to the `Applyalias` form is just `'x'`, not `Variable 'x'`. This is because (1) only variables are acceptable there, not arbitrary expressions, and (2) we don't need at that point to compute the variable's present value.
+
+Here is our expanded language:
+
        type term =
          Intconstant of int
        | Multiplication of (term * term)
        type term =
          Intconstant of int
        | Multiplication of (term * term)
@@ -677,6 +718,8 @@ The complete code is available [here](/code/calculator/calc6.ml).
        | Applyalias of (term * char)
        ;;
  
        | Applyalias of (term * char)
        ;;
  
+The definitions of `index`, `bound_value`, `assignment`, `expressed_value`, and `store` can remain as they were in the implementation of implicit-style mutation. Here are the changes to our evaluation function:
+
        let rec eval (t : term) (g : assignment) (s : store) = match t with
        ...
        | Alias (var_to_bind, orig_var, t3) ->
        let rec eval (t : term) (g : assignment) (s : store) = match t with
        ...
        | Alias (var_to_bind, orig_var, t3) ->