OCaml: Add step 9
[jackhill/mal.git] / ocaml / step2_eval.ml
CommitLineData
a878f3bb
C
1module T = Types.Types
2
921a951f
C
3module Env =
4 Map.Make (
5 String
6 (*(struct
7 type t = Types.Symbol
8 let compare (Types.Symbol a) (Types.Symbol b) = compare a b
9 end)*)
10 )
11
fb21afa7 12let num_fun f = Types.fn
921a951f 13 (function
a878f3bb 14 | [(T.Int a); (T.Int b)] -> T.Int (f a b)
921a951f
C
15 | _ -> raise (Invalid_argument "Numeric args required for this Mal builtin"))
16
81e073cf 17let repl_env = ref (List.fold_left (fun a b -> b a) Env.empty
921a951f
C
18 [ Env.add "+" (num_fun ( + ));
19 Env.add "-" (num_fun ( - ));
20 Env.add "*" (num_fun ( * ));
21 Env.add "/" (num_fun ( / )) ])
22
23let rec eval_ast ast env =
24 match ast with
a878f3bb 25 | T.Symbol { T.value = s } ->
04e33074
C
26 (try Env.find s !env
27 with Not_found -> raise (Invalid_argument ("Symbol '" ^ s ^ "' not found")))
28 | T.List { T.value = xs; T.meta = meta }
ecd3b6d8
C
29 -> T.List { T.value = (List.map (fun x -> eval x env) xs);
30 T.meta = meta;
31 T.is_macro = false}
04e33074 32 | T.Vector { T.value = xs; T.meta = meta }
ecd3b6d8
C
33 -> T.Vector { T.value = (List.map (fun x -> eval x env) xs);
34 T.meta = meta;
35 T.is_macro = false}
04e33074
C
36 | T.Map { T.value = xs; T.meta = meta }
37 -> T.Map {T.meta = meta;
ecd3b6d8 38 T.is_macro = false;
04e33074
C
39 T.value = (Types.MalMap.fold
40 (fun k v m
41 -> Types.MalMap.add (eval k env) (eval v env) m)
42 xs
43 Types.MalMap.empty)}
921a951f
C
44 | _ -> ast
45and eval ast env =
46 let result = eval_ast ast env in
47 match result with
ecd3b6d8 48 | T.List { T.value = ((T.Fn { T.value = f }) :: args) } -> (f args)
921a951f
C
49 | _ -> result
50
51let read str = Reader.read_str str
de04357c 52let print exp = Printer.pr_str exp true
921a951f
C
53let rep str env = print (eval (read str) env)
54
55let rec main =
56 try
57 while true do
58 print_string "user> ";
59 let line = read_line () in
60 try
81e073cf 61 print_endline (rep line repl_env);
921a951f
C
62 with End_of_file -> ()
63 | Invalid_argument x ->
64 output_string stderr ("Invalid_argument exception: " ^ x ^ "\n");
65 flush stderr
66 done
67 with End_of_file -> ()