expand calc improvements
[lambda.git] / code / calculator / calc4.ml
1 (* calc3.ml, enhanced with Mutable Cells *)
2
3         type term =
4                   Intconstant of int
5                 | Multiplication of (term * term)
6                 | Addition of (term * term)
7                 | Variable of char
8                 | Let of (char * term * term)
9                 | Iszero of term
10                 | If of (term * term * term)
11                 | Makepair of (term * term)
12                 | First of term
13                 | Lambda of (char * term)
14                 | Apply of (term * term)
15                 | Letrec of (char * term * term)
16                 | Newref of term
17                 | Deref of term
18                 | Setref of (term * term)
19         ;;
20
21         type index = int;;
22
23     type bound_value = Nonrecursive of expressed_value | Recursive_Closure of char * char * term * assignment
24         and assignment = (char * bound_value) list
25     and expressed_value = Int of int | Bool of bool | Pair of expressed_value * expressed_value | Closure of char * term * assignment | Mutcell of index;;
26
27         type store = expressed_value list;;
28
29         let rec eval (t : term) (g : assignment) (s : store) = match t with
30           Intconstant x -> (Int x, s)
31         | Multiplication (t1, t2) ->
32                 (* we don't handle cases where the subterms don't evaluate to Ints *)
33                 let (Int i1, s') = eval t1 g s
34                 in let (Int i2, s'') = eval t2 g s'
35                 (* Multiplication (t1, t2) should evaluate to an Int *)
36                 in (Int (i1 * i2), s'')
37         | Addition (t1, t2) ->
38                 let (Int i1, s') = eval t1 g s
39                 in let (Int i2, s'') = eval t2 g s'
40                 in (Int (i1 + i2), s'')
41         | Variable (var) -> (
42                 (* we don't handle cases where g doesn't bind var to any value *)
43                 match List.assoc var g with
44           | Nonrecursive value -> value
45           | Recursive_Closure (self_var, arg_var, body, savedg) as rec_closure ->
46                           (* we update savedg to bind self_var to rec_closure here *)
47               let savedg' = (self_var, rec_closure) :: savedg
48               in Closure (arg_var, body, savedg')
49         ), s
50         | Let (var_to_bind, t2, t3) ->
51                 (* evaluate t3 under a new assignment where var_to_bind has been bound to
52            the result of evaluating t2 under the current assignment *)
53                 let (value2, s') = eval t2 g s
54                 (* we have to wrap value2 in Nonrecursive *)
55                 in let g' = (var_to_bind, Nonrecursive value2) :: g
56                 in eval t3 g' s'
57         | Iszero (t1) ->
58                 (* we don't handle cases where t1 doesn't evaluate to an Int *)
59                 let (Int i1, s') = eval t1 g s
60                 (* Iszero t1 should evaluate to a Bool *)
61                 in (Bool (i1 = 0), s')
62         | If (t1, t2, t3) ->
63                 (* we don't handle cases where t1 doesn't evaluate to a boolean *)
64                 let (Bool b1, s') = eval t1 g s
65         (* note we thread s' through only one of the then/else clauses *)
66                 in if b1 then eval t2 g s'
67                 else eval t3 g s'
68         | Makepair (t1, t2) ->
69                 let (value1, s') = eval t1 g s
70                 in let (value2, s'') = eval t2 g s'
71                 in (Pair (value1, value2), s'')
72         | First (t1) ->
73                 (* we don't handle cases where t1 doesn't evaluate to a Pair *)
74                 let (Pair (value1, value2), s') = eval t1 g s
75                 in (value1, s')
76         | Lambda (arg_var, t2) -> (Closure (arg_var, t2, g), s)
77         | Apply (t1, t2) ->
78                 (* we don't handle cases where t1 doesn't evaluate to a function value *)
79                 let (Closure (arg_var, body, savedg), s') = eval t1 g s
80                 in let (value2, s'') = eval t2 g s'
81                 (* evaluate body under savedg, except with arg_var bound to Nonrecursive value2 *)
82                 in let savedg' = (arg_var, Nonrecursive value2) :: savedg
83                 in eval body savedg' s''
84         | Letrec (var_to_bind, t2, t3) ->
85                 (* we don't handle cases where t2 doesn't evaluate to a function value *)
86                 let (Closure (arg_var, body, savedg), s') = eval t2 g s
87         (* evaluate t3 under a new assignment where var_to_bind has been recursively bound to that function value *) 
88                 in let g' = (var_to_bind, Recursive_Closure (var_to_bind, arg_var, body, savedg)) :: g
89                 in eval t3 g' s'
90         | Newref (t1) ->
91                 let (starting_val, s') = eval t1 g s
92                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
93                 (* now we want to retrieve the next free index in s' *)
94                 in let new_index = List.length s'
95                 (* now we want to insert starting_val there; the following is an easy but inefficient way to do it *)
96                 in let s'' = List.append s' [starting_val]
97                 (* now we return a pair of a wrapped new_index, and the new store *)
98                 in (Mutcell new_index, s'')
99         | Deref (t1) ->
100                 (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
101                 let (Mutcell index1, s') = eval t1 g s
102                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
103                 in (List.nth s' index1, s')
104         | Setref (t1, t2) ->
105                 (* we don't handle cases where t1 doesn't evaluate to a Mutcell *)
106                 let (Mutcell index1, s') = eval t1 g s
107                 (* note that s' may be different from s, if t1 itself contained any mutation operations *)
108                 in let (new_value, s'') = eval t2 g s'
109                 (* now we create a list which is just like s'' except it has new_value in index1 *)
110                 in let rec replace_nth lst m =
111                         match lst with
112                         | [] -> failwith "list too short"
113                         | x::xs when m = 0 -> new_value :: xs
114                         | x::xs -> x :: replace_nth xs (m - 1)
115                 in let s''' = replace_nth s'' index1
116                 (* we'll arbitrarily return Int 42 as the expressed_value of a Setref operation *)
117                 in (Int 42, s''')
118     ;;