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