1
1
mirror of https://github.com/kanaka/mal.git synced 2024-10-27 22:58:00 +03:00
mal/ocaml/step3_env.ml

61 lines
2.0 KiB
OCaml
Raw Normal View History

module T = Types.Types
let num_fun f = T.Fn
2015-01-23 16:17:35 +03:00
(function
| [(T.Int a); (T.Int b)] -> T.Int (f a b)
2015-01-23 16:17:35 +03:00
| _ -> raise (Invalid_argument "Numeric args required for this Mal builtin"))
let repl_env = Env.make None
let init_repl env = begin
Env.set env (Types.symbol "+") (num_fun ( + ));
Env.set env (Types.symbol "-") (num_fun ( - ));
Env.set env (Types.symbol "*") (num_fun ( * ));
Env.set env (Types.symbol "/") (num_fun ( / ));
2015-01-23 16:17:35 +03:00
end
let rec eval_ast ast env =
match ast with
| T.Symbol s -> Env.get env ast
| T.List { T.value = xs } -> Types.list (List.map (fun x -> eval x env) xs)
2015-01-23 16:17:35 +03:00
| _ -> ast
and eval ast env =
match ast with
| T.List { T.value = [(T.Symbol { T.value = "def!" }); key; expr] } ->
2015-01-23 16:17:35 +03:00
let value = (eval expr env) in
Env.set env key value; value
| T.List { T.value = [(T.Symbol { T.value = "let*" }); (T.List { T.value = bindings }); body] } ->
2015-01-23 16:17:35 +03:00
(let sub_env = Env.make (Some env) in
let rec bind_pairs = (function
| sym :: expr :: more ->
Env.set sub_env sym (eval expr sub_env);
bind_pairs more
| _::[] -> raise (Invalid_argument "let* bindings must be an even number of forms")
| [] -> ())
in bind_pairs bindings;
eval body sub_env)
| T.List _ ->
2015-01-23 16:17:35 +03:00
(match eval_ast ast env with
| T.List { T.value = ((T.Fn f) :: args) } -> f args
2015-01-23 16:17:35 +03:00
| _ -> raise (Invalid_argument "Cannot invoke non-function"))
| _ -> eval_ast ast env
let read str = Reader.read_str str
2015-01-24 04:05:03 +03:00
let print exp = Printer.pr_str exp true
2015-01-23 16:17:35 +03:00
let rep str env = print (eval (read str) env)
let rec main =
try
init_repl repl_env;
while true do
print_string "user> ";
let line = read_line () in
try
print_endline (rep line repl_env);
with End_of_file -> ()
| Invalid_argument x ->
output_string stderr ("Invalid_argument exception: " ^ x ^ "\n");
flush stderr
done
with End_of_file -> ()