r: Fix setting *ARGV*
[jackhill/mal.git] / r / step6_file.r
index d99110c..8ca13ff 100644 (file)
@@ -5,6 +5,7 @@ if(!exists("..printer..")) source("printer.r")
 if(!exists("..env..")) source("env.r")
 if(!exists("..core..")) source("core.r")
 
+# read
 READ <- function(str) {
     return(read_str(str))
 }
@@ -16,6 +17,13 @@ eval_ast <- function(ast, env) {
         new.listl(lapply(ast, function(a) EVAL(a, env)))
     } else if (.vector_q(ast)) {
         new.vectorl(lapply(ast, function(a) EVAL(a, env)))
+    } else if (.hash_map_q(ast)) {
+        lst <- list()
+        for(k in ls(ast)) {
+            lst[[length(lst)+1]] = k
+            lst[[length(lst)+1]] = EVAL(ast[[k]], env)
+        }
+        new.hash_mapl(lst)
     } else {
         ast
     }
@@ -53,13 +61,13 @@ EVAL <- function(ast, env) {
     } else if (a0sym == "if") {
         cond <- EVAL(a1, env)
         if (.nil_q(cond) || identical(cond, FALSE)) {
-            if (length(ast) < 4) return(NULL)
+            if (length(ast) < 4) return(nil)
             ast <- ast[[4]]
         } else {
             ast <- a2
         }
     } else if (a0sym == "fn*") {
-        return(malfunc(a2, env, a1))
+        return(malfunc(EVAL, a2, env, a1))
     } else {
         el <- eval_ast(ast, env)
         f <- el[[1]]
@@ -74,22 +82,30 @@ EVAL <- function(ast, env) {
     }
 }
 
+# print
 PRINT <- function(exp) {
     return(.pr_str(exp, TRUE))
 }
 
+# repl loop
 repl_env <- new.Env()
 rep <- function(str) return(PRINT(EVAL(READ(str), repl_env)))
 
 # core.r: defined using R
 for(k in names(core_ns)) { Env.set(repl_env, k, core_ns[[k]]) }
 Env.set(repl_env, "eval", function(ast) EVAL(ast, repl_env))
-Env.set(repl_env, "*ARGV*", function(ast) EVAL(ast, repl_env))
+Env.set(repl_env, "*ARGV*", new.list())
 
 # core.mal: defined using the language itself
 . <- rep("(def! not (fn* (a) (if a false true)))")
 . <- rep("(def! load-file (fn* (f) (eval (read-string (str \"(do \" (slurp f) \")\")))))")
 
+args <- commandArgs(trailingOnly = TRUE)
+if (length(args) > 0) {
+    Env.set(repl_env, "*ARGV*", new.listl(slice(as.list(args),2)))
+    . <- rep(concat("(load-file \"", args[[1]], "\")"))
+    quit(save="no", status=0)
+}
 
 repeat {
     line <- readline("user> ")