Christophe Weblog Wiki Code Publications Music
implement swank:interactive-eval-region
[swankr.git] / swank.R
diff --git a/swank.R b/swank.R
index fa22d64a89fbb81c7cbce794e5360a48870ad859..8c5bafdccd1d5d198f534d971db0455fba703095 100644 (file)
--- a/swank.R
+++ b/swank.R
@@ -42,7 +42,6 @@ mainLoop <- function(io) {
 }
 
 dispatch <- function(slimeConnection, event, sldbState=NULL) {
-  str(event)
   kind <- event[[1]]
   if(kind == quote(`:emacs-rex`)) {
     do.call("emacsRex", c(list(slimeConnection), list(sldbState), event[-1]))
@@ -51,12 +50,10 @@ dispatch <- function(slimeConnection, event, sldbState=NULL) {
 
 sendToEmacs <- function(slimeConnection, obj) {
   io <- slimeConnection$io
-  str(obj)
   payload <- writeSexpToString(obj)
   writeChar(sprintf("%06x", nchar(payload)), io, eos=NULL)
   writeChar(payload, io, eos=NULL)
   flush(io)
-  cat(sprintf("%06x", nchar(payload)), payload, sep="")
 }
 
 callify <- function(form) {
@@ -81,15 +78,30 @@ callify <- function(form) {
 emacsRex <- function(slimeConnection, sldbState, form, pkg, thread, id, level=0) {
   ok <- FALSE
   value <- NULL
+  conn <- textConnection(NULL, open="w")
+  condition <- NULL
   tryCatch({
     withCallingHandlers({
       call <- callify(form)
-      value <- eval(call)
+      capture.output(value <- eval(call), file=conn)
+      string <- paste(textConnectionValue(conn), sep="", collapse="\n")
+      if(nchar(string) > 0) {
+        sendToEmacs(slimeConnection, list(quote(`:write-string`), string))
+        sendToEmacs(slimeConnection, list(quote(`:write-string`), "\n"))
+      }
+      close(conn)
       ok <- TRUE
     }, error=function(c) {
+      condition <<- c
+      string <- paste(textConnectionValue(conn), sep="", collapse="\n")
+      if(nchar(string) > 0) {
+        sendToEmacs(slimeConnection, list(quote(`:write-string`), string))
+        sendToEmacs(slimeConnection, list(quote(`:write-string`), "\n"))
+      }
+      close(conn)
       newSldbState <- makeSldbState(c, if(is.null(sldbState)) 0 else sldbState$level+1, id)
       withRestarts(sldbLoop(slimeConnection, newSldbState, id), abort=paste("return to sldb level", newSldbState$level)) })},
-    finally=sendToEmacs(slimeConnection, list(quote(`:return`), if(ok) list(quote(`:ok`), value) else list(quote(`:abort`)), id)))
+    finally=sendToEmacs(slimeConnection, list(quote(`:return`), if(ok) list(quote(`:ok`), value) else list(quote(`:abort`), as.character(condition)), id)))
 }
 
 makeSldbState <- function(condition, level, id) {
@@ -198,7 +210,14 @@ readSexpFromString <- function(string) {
     } else if(grepl("^[0-9]+\\.[0-9]+$", token)) {
       as.double(token)
     } else {
-      as.name(token)
+      name <- as.name(token)
+      if(name == quote(t)) {
+        TRUE
+      } else if(name == quote(nil)) {
+        FALSE
+      } else {
+        name
+      }
     }
   }
   readToken <- function() {
@@ -266,7 +285,7 @@ printToString <- function(val) {
   for(contrib in contribs) {
     filename <- sprintf("%s.R", as.character(contrib))
     if(file.exists(filename)) {
-      source(filename, verbose=TRUE)
+      source(filename)
     }
   }
   list()
@@ -292,8 +311,10 @@ sendReplResult <- function(slimeConnection, value) {
 sendReplResultFunction <- sendReplResult
 
 `swank:listener-eval` <- function(slimeConnection, sldbState, string) {
+  ## O how ugly
   string <- gsub("#\\.\\(swank:lookup-presented-object-or-lose([^)]*)\\)", ".(`swank:lookup-presented-object-or-lose`(slimeConnection, sldbState,\\1))", string)
   expr <- parse(text=string)[[1]]
+  ## O maybe this is even uglier
   lookedup <- do.call("bquote", list(expr))
   value <- eval(lookedup, envir = globalenv())
   sendReplResultFunction(slimeConnection, value)
@@ -358,8 +379,16 @@ computeRestartsForEmacs <- function (sldbState) {
   if(is.null(srcfile)) {
     list(quote(`:error`), "no srcfile")
   } else {
+    filename <- get("filename", srcfile)
+    ## KLUDGE: what this means is "is the srcfile filename
+    ## absolute?"
+    if(substr(filename, 1, 1) == "/") {
+      file <- filename
+    } else {
+      file <- sprintf("%s/%s", srcfile$wd, filename)
+    }
     list(quote(`:location`),
-         list(quote(`:file`), sprintf("%s/%s", srcfile$wd, srcfile$filename)),
+         list(quote(`:file`), file),
          list(quote(`:line`), srcref[[1]], srcref[[2]]-1),
          FALSE)
   }
@@ -465,6 +494,12 @@ withRetryRestart <- function(description, expr) {
   list(output, prin1ToString(value))
 }
 
+`swank:interactive-eval-region` <- function(slimeConnection, sldbState, string) {
+  withRetryRestart("retry SLIME interactive evaluation request",
+                   value <- eval(parse(text=string), envir=globalenv()))
+  prin1ToString(value)
+}
+
 `swank:find-definitions-for-emacs` <- function(slimeConnection, sldbState, string) {
   if(exists(string, envir = globalenv())) {
     thing <- get(string, envir = globalenv())
@@ -661,11 +696,21 @@ emacsInspect.numeric <- function(numeric) {
 }
 
 `swank:load-file` <- function(slimeConnection, sldbState, filename) {
-  source(filename, local=FALSE)
+  source(filename, local=FALSE, keep.source=TRUE)
   TRUE
 }
 
 `swank:compile-file-for-emacs` <- function(slimeConnection, sldbState, filename, loadp, ...) {
-  times <- system.time(parse(filename))
+  times <- system.time(parse(filename, srcfile=srcfile(filename)))
+  if(loadp) {
+    ## KLUDGE: inelegant, but works.  It might be more in the spirit
+    ## of things to keep the result of the parse above around to
+    ## evaluate.
+    `swank:load-file`(slimeConnection, sldbState, filename)
+  }
   list(quote(`:compilation-result`), list(), TRUE, times[3], substitute(loadp), filename)
 }
+
+`swank:quit-lisp` <- function(slimeConnection, sldbState) {
+  quit()
+}