Merge pull request #440 from aasimk2000/add-nil-if-test
[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
f947d503 8# read
c30efef4
JM
9READ <- function(str) {
10 return(read_str(str))
11}
12
13eval_ast <- function(ast, env) {
14 if (.symbol_q(ast)) {
15 Env.get(env, ast)
16 } else if (.list_q(ast)) {
17 new.listl(lapply(ast, function(a) EVAL(a, env)))
18 } else if (.vector_q(ast)) {
19 new.vectorl(lapply(ast, function(a) EVAL(a, env)))
36737ae5
JM
20 } else if (.hash_map_q(ast)) {
21 lst <- list()
22 for(k in ls(ast)) {
23 lst[[length(lst)+1]] = k
24 lst[[length(lst)+1]] = EVAL(ast[[k]], env)
25 }
26 new.hash_mapl(lst)
c30efef4
JM
27 } else {
28 ast
29 }
30}
31
32EVAL <- function(ast, env) {
33 repeat {
34
35 #cat("EVAL: ", .pr_str(ast,TRUE), "\n", sep="")
36 if (!.list_q(ast)) {
37 return(eval_ast(ast, env))
38 }
39
40 # apply list
41 switch(paste("l",length(ast),sep=""),
42 l0={ return(ast) },
43 l1={ a0 <- ast[[1]]; a1 <- NULL; a2 <- NULL },
44 l2={ a0 <- ast[[1]]; a1 <- ast[[2]]; a2 <- NULL },
45 { a0 <- ast[[1]]; a1 <- ast[[2]]; a2 <- ast[[3]] })
46 if (length(a0) > 1) a0sym <- "__<*fn*>__"
47 else a0sym <- as.character(a0)
48 if (a0sym == "def!") {
49 res <- EVAL(a2, env)
50 return(Env.set(env, a1, res))
51 } else if (a0sym == "let*") {
52 let_env <- new.Env(env)
53 for(i in seq(1,length(a1),2)) {
54 Env.set(let_env, a1[[i]], EVAL(a1[[i+1]], let_env))
55 }
56 ast <- a2
57 env <- let_env
58 } else if (a0sym == "do") {
59 eval_ast(slice(ast,2,length(ast)-1), env)
60 ast <- ast[[length(ast)]]
61 } else if (a0sym == "if") {
62 cond <- EVAL(a1, env)
63 if (.nil_q(cond) || identical(cond, FALSE)) {
8128c69a 64 if (length(ast) < 4) return(nil)
c30efef4
JM
65 ast <- ast[[4]]
66 } else {
67 ast <- a2
68 }
69 } else if (a0sym == "fn*") {
8128c69a 70 return(malfunc(EVAL, a2, env, a1))
c30efef4
JM
71 } else {
72 el <- eval_ast(ast, env)
73 f <- el[[1]]
74 if (class(f) == "MalFunc") {
75 ast <- f$ast
76 env <- f$gen_env(slice(el,2))
77 } else {
78 return(do.call(f,slice(el,2)))
79 }
80 }
81
82 }
83}
84
f947d503 85# print
c30efef4
JM
86PRINT <- function(exp) {
87 return(.pr_str(exp, TRUE))
88}
89
f947d503 90# repl loop
c30efef4
JM
91repl_env <- new.Env()
92rep <- function(str) return(PRINT(EVAL(READ(str), repl_env)))
93
94# core.r: defined using R
95for(k in names(core_ns)) { Env.set(repl_env, k, core_ns[[k]]) }
96Env.set(repl_env, "eval", function(ast) EVAL(ast, repl_env))
f947d503 97Env.set(repl_env, "*ARGV*", new.list())
c30efef4
JM
98
99# core.mal: defined using the language itself
100. <- rep("(def! not (fn* (a) (if a false true)))")
e6d41de4 101. <- rep("(def! load-file (fn* (f) (eval (read-string (str \"(do \" (slurp f) \"\nnil)\")))))")
c30efef4 102
f947d503
JM
103args <- commandArgs(trailingOnly = TRUE)
104if (length(args) > 0) {
8a16f953 105 Env.set(repl_env, "*ARGV*", new.listl(slice(as.list(args),2)))
f947d503
JM
106 . <- rep(concat("(load-file \"", args[[1]], "\")"))
107 quit(save="no", status=0)
108}
c30efef4
JM
109
110repeat {
111 line <- readline("user> ")
112 if (is.null(line)) { cat("\n"); break }
113 tryCatch({
114 cat(rep(line),"\n", sep="")
115 }, error=function(err) {
116 cat("Error: ", get_error(err),"\n", sep="")
117 })
118 # R debug/fatal with tracebacks:
119 #cat(rep(line),"\n", sep="")
120}