Ocaml: Add string functions
[jackhill/mal.git] / ocaml / step2_eval.ml
1 module Env =
2 Map.Make (
3 String
4 (*(struct
5 type t = Types.Symbol
6 let compare (Types.Symbol a) (Types.Symbol b) = compare a b
7 end)*)
8 )
9
10 let num_fun f = Types.Fn
11 (function
12 | [(Types.Int a); (Types.Int b)] -> Types.Int (f a b)
13 | _ -> raise (Invalid_argument "Numeric args required for this Mal builtin"))
14
15 let repl_env = ref (List.fold_left (fun a b -> b a) Env.empty
16 [ Env.add "+" (num_fun ( + ));
17 Env.add "-" (num_fun ( - ));
18 Env.add "*" (num_fun ( * ));
19 Env.add "/" (num_fun ( / )) ])
20
21 let rec eval_ast ast env =
22 match ast with
23 | Types.Symbol s ->
24 (try Env.find s !env
25 with Not_found -> raise (Invalid_argument ("Symbol '" ^ s ^ "' not found")))
26 | Types.MalList xs -> Types.MalList (List.map (fun x -> eval x env) xs)
27 | _ -> ast
28 and eval ast env =
29 let result = eval_ast ast env in
30 match result with
31 | Types.MalList ((Types.Fn f) :: args) -> (f args)
32 | _ -> result
33
34 let read str = Reader.read_str str
35 let print exp = Printer.pr_str exp true
36 let rep str env = print (eval (read str) env)
37
38 let rec main =
39 try
40 while true do
41 print_string "user> ";
42 let line = read_line () in
43 try
44 print_endline (rep line repl_env);
45 with End_of_file -> ()
46 | Invalid_argument x ->
47 output_string stderr ("Invalid_argument exception: " ^ x ^ "\n");
48 flush stderr
49 done
50 with End_of_file -> ()