R: add step8_macros and step9_try.
[jackhill/mal.git] / r / step6_file.r
CommitLineData
c30efef4
JM
1if(!exists("..readline..")) source("readline.r")
2if(!exists("..types..")) source("types.r")
3if(!exists("..reader..")) source("reader.r")
4if(!exists("..printer..")) source("printer.r")
5if(!exists("..env..")) source("env.r")
6if(!exists("..core..")) source("core.r")
7
8READ <- function(str) {
9 return(read_str(str))
10}
11
12eval_ast <- function(ast, env) {
13 if (.symbol_q(ast)) {
14 Env.get(env, ast)
15 } else if (.list_q(ast)) {
16 new.listl(lapply(ast, function(a) EVAL(a, env)))
17 } else if (.vector_q(ast)) {
18 new.vectorl(lapply(ast, function(a) EVAL(a, env)))
19 } else {
20 ast
21 }
22}
23
24EVAL <- function(ast, env) {
25 repeat {
26
27 #cat("EVAL: ", .pr_str(ast,TRUE), "\n", sep="")
28 if (!.list_q(ast)) {
29 return(eval_ast(ast, env))
30 }
31
32 # apply list
33 switch(paste("l",length(ast),sep=""),
34 l0={ return(ast) },
35 l1={ a0 <- ast[[1]]; a1 <- NULL; a2 <- NULL },
36 l2={ a0 <- ast[[1]]; a1 <- ast[[2]]; a2 <- NULL },
37 { a0 <- ast[[1]]; a1 <- ast[[2]]; a2 <- ast[[3]] })
38 if (length(a0) > 1) a0sym <- "__<*fn*>__"
39 else a0sym <- as.character(a0)
40 if (a0sym == "def!") {
41 res <- EVAL(a2, env)
42 return(Env.set(env, a1, res))
43 } else if (a0sym == "let*") {
44 let_env <- new.Env(env)
45 for(i in seq(1,length(a1),2)) {
46 Env.set(let_env, a1[[i]], EVAL(a1[[i+1]], let_env))
47 }
48 ast <- a2
49 env <- let_env
50 } else if (a0sym == "do") {
51 eval_ast(slice(ast,2,length(ast)-1), env)
52 ast <- ast[[length(ast)]]
53 } else if (a0sym == "if") {
54 cond <- EVAL(a1, env)
55 if (.nil_q(cond) || identical(cond, FALSE)) {
8128c69a 56 if (length(ast) < 4) return(nil)
c30efef4
JM
57 ast <- ast[[4]]
58 } else {
59 ast <- a2
60 }
61 } else if (a0sym == "fn*") {
8128c69a 62 return(malfunc(EVAL, a2, env, a1))
c30efef4
JM
63 } else {
64 el <- eval_ast(ast, env)
65 f <- el[[1]]
66 if (class(f) == "MalFunc") {
67 ast <- f$ast
68 env <- f$gen_env(slice(el,2))
69 } else {
70 return(do.call(f,slice(el,2)))
71 }
72 }
73
74 }
75}
76
77PRINT <- function(exp) {
78 return(.pr_str(exp, TRUE))
79}
80
81repl_env <- new.Env()
82rep <- function(str) return(PRINT(EVAL(READ(str), repl_env)))
83
84# core.r: defined using R
85for(k in names(core_ns)) { Env.set(repl_env, k, core_ns[[k]]) }
86Env.set(repl_env, "eval", function(ast) EVAL(ast, repl_env))
87Env.set(repl_env, "*ARGV*", function(ast) EVAL(ast, repl_env))
88
89# core.mal: defined using the language itself
90. <- rep("(def! not (fn* (a) (if a false true)))")
91. <- rep("(def! load-file (fn* (f) (eval (read-string (str \"(do \" (slurp f) \")\")))))")
92
93
94repeat {
95 line <- readline("user> ")
96 if (is.null(line)) { cat("\n"); break }
97 tryCatch({
98 cat(rep(line),"\n", sep="")
99 }, error=function(err) {
100 cat("Error: ", get_error(err),"\n", sep="")
101 })
102 # R debug/fatal with tracebacks:
103 #cat(rep(line),"\n", sep="")
104}