Christophe Weblog Wiki Code Publications Music
capture output from evaluating swank requests
[swankr.git] / swank.R
diff --git a/swank.R b/swank.R
index 22cec64d58f898fad9ce4c68b22110bdd4b4c103..0384004ac87866fdf79bc4b99d072f954fde17ae 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) {
@@ -266,7 +278,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()
@@ -377,7 +389,6 @@ computeRestartsForEmacs <- function (sldbState) {
 }
 
 `swank:frame-locals-and-catch-tags` <- function(slimeConnection, sldbState, index) {
-  str(sldbState$frames)
   frame <- sldbState$frames[[1+index]]
   objs <- ls(envir=frame)
   list(lapply(objs, function(name) { list(quote(`:name`), name,
@@ -402,11 +413,42 @@ computeRestartsForEmacs <- function (sldbState) {
 }
 
 `swank:compile-string-for-emacs` <- function(slimeConnection, sldbState, string, buffer, position, filename, policy) {
-  # FIXME: I think in parse() here we can use srcref to associate
-  # buffer/filename/position to the objects.  Or something.
-  withRestarts({ times <- system.time(eval(parse(text=string), envir = globalenv())) },
+  lineOffset <- charOffset <- colOffset <- NULL
+  for(pos in position) {
+    switch(as.character(pos[[1]]),
+           `:position` = {charOffset <- pos[[2]]},
+           `:line` = {lineOffset <- pos[[2]]; colOffset <- pos[[3]]},
+           warning("unknown content in pos", pos))
+  }
+  frob <- function(refs) {
+    lapply(refs,
+           function(x)
+           srcref(attr(x,"srcfile"),
+                  c(x[1]+lineOffset-1, ifelse(x[1]==1, x[2]+colOffset-1, x[2]),
+                    x[3]+lineOffset-1, ifelse(x[3]==1, x[4]+colOffset-1, x[4]),
+                    ifelse(x[1]==1, x[5]+colOffset-1, x[5]),
+                    ifelse(x[3]==1, x[6]+colOffset-1, x[6]))))
+  }
+  transformSrcrefs <- function(s) {
+    srcrefs <- attr(s, "srcref")
+    attribs <- attributes(s)
+    new <- 
+      switch(mode(s),
+             "call"=as.call(lapply(s, transformSrcrefs)),
+             "expression"=as.expression(lapply(s, transformSrcrefs)),
+             s)
+    attributes(new) <- attribs
+    if(!is.null(attr(s, "srcref"))) {
+      attr(new, "srcref") <- frob(srcrefs)
+    }
+    new
+  }
+  withRestarts({
+    times <- system.time({
+      exprs <- parse(text=string, srcfile=srcfile(filename))
+      eval(transformSrcrefs(exprs), envir = globalenv()) })},
                abort="abort compilation")
-  list(quote(`:compilation-result`), list(), TRUE, times[3])
+  list(quote(`:compilation-result`), list(), TRUE, times[3], FALSE, FALSE)
 }
 
 withRetryRestart <- function(description, expr) {
@@ -446,9 +488,16 @@ withRetryRestart <- function(description, expr) {
         list()
       } 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(list(sprintf("function %s", string),
                   list(quote(`:location`),
-                       list(quote(`:file`), sprintf("%s/%s", srcfile$wd, srcfile$filename)),
+                       list(quote(`:file`), file),
                        list(quote(`:line`), srcref[[2]][[1]], srcref[[2]][[2]]-1),
                        list())))
       }
@@ -629,10 +678,6 @@ emacsInspect.numeric <- function(numeric) {
 }
 
 `swank:compile-file-for-emacs` <- function(slimeConnection, sldbState, filename, loadp, ...) {
-  if(loadp==quote(`t`)) {
-    source(filename, local=FALSE)
-  } else {
-    parse(filename)
-  }
-  TRUE
+  times <- system.time(parse(filename))
+  list(quote(`:compilation-result`), list(), TRUE, times[3], substitute(loadp), filename)
 }