Christophe Weblog Wiki Code Publications Music
return properly from sldbLoop()
[swankr.git] / swank.R
diff --git a/swank.R b/swank.R
index 11d11359fd4ce557b7bd28a2293150ad57c8e196..f3a85ccc6a8b0d770b9273180bb179e717fc736d 100644 (file)
--- a/swank.R
+++ b/swank.R
@@ -17,29 +17,83 @@ serve <- function(io) {
 }
 
 mainLoop <- function(io) {
-  dispatch <- function(event) {
-    str(event)
-    kind <- event[[1]]
-    if(kind == quote(`:emacs-rex`)) {
-      do.call("emacsRex", event[-1])
-    }
+  while(TRUE) {
+    withRestarts(tryCatch(dispatch(io, readPacket(io)),
+                          swankTopLevel=function(c) NULL),
+                 abort="return to SLIME's toplevel")
   }
-  sendToEmacs <- function(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="")
+}
+
+dispatch <- function(io, event, sldbState=NULL) {
+  str(event)
+  kind <- event[[1]]
+  if(kind == quote(`:emacs-rex`)) {
+    do.call("emacsRex", c(list(io), list(sldbState), event[-1]))
   }
-  emacsRex <- function(form, pkg, thread, id) {
-    value <- do.call(eval(form[[1]]), form[-1])
-    sendToEmacs(list(quote(`:return`), list(quote(`:ok`), value), id))
+}
+
+sendToEmacs <- function(io, obj) {
+  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="")
+}
+
+emacsRex <- function(io, sldbState, form, pkg, thread, id, level=0) {
+  ok <- FALSE
+  value <- NULL
+  tryCatch({
+    withCallingHandlers({
+      value <- do.call(eval(form[[1]]), c(list(io), list(sldbState), form[-1]))
+      ok <- TRUE
+    }, error=function(c) {
+      newSldbState <- makeSldbState(c, if(is.null(sldbState)) 0 else sldbState$level+1, id)
+      withRestarts(sldbLoop(io, newSldbState, id), abort=paste("return to sldb level", newSldbState$level)) })},
+    finally=sendToEmacs(io, list(quote(`:return`), if(ok) list(quote(`:ok`), value) else list(quote(`:abort`)), id)))
+}
+
+makeSldbState <- function(condition, level, id) {
+  calls <- rev(sys.calls())[-1]
+  frames <- rev(sys.frames())[-1]
+  restarts <- rev(computeRestarts(condition))[-1]
+  ret <- list(condition=condition, level=level, id=id, restarts=restarts, calls=calls, frames=frames)
+  class(ret) <- c("sldbState", class(ret))
+  ret
+}
+
+sldbLoop <- function(io, sldbState, id) {
+  tryCatch({
+    sendToEmacs(io, c(list(quote(`:debug`), id, sldbState$level), debuggerInfoForEmacs(sldbState)))
+    sendToEmacs(io, list(quote(`:debug-activate`), id, sldbState$level, FALSE))
+    while(TRUE) {
+      dispatch(io, readPacket(io), sldbState)
+    }
+  }, finally=sendToEmacs(io, c(list(quote(`:debug-return`), id, sldbState$level, FALSE))))
+}
+
+debuggerInfoForEmacs <- function(sldbState, from=0, to=NULL) {
+  backtraceForEmacs <- function() {
+    calls <- sldbState$calls
+    if(is.null(to)) to <- length(calls)
+    from <- from+1
+    calls <- lapply(calls[from:to], { frameNumber <- from-1;
+                             function (x) { ret <- list(frameNumber, paste(format(x), sep="", collapse=" ")); frameNumber <<- 1+frameNumber; ret }})
   }
-  
-  while(TRUE) {
-    tryCatch(dispatch(readPacket(io)),
-             swankTopLevel=NULL)
+  computeRestartsForEmacs <- function () {
+    lapply(sldbState$restarts,
+           function(x) {
+             ## this is all a little bit internalsy
+             restartName <- x[[1]][[1]]
+             description <- restartDescription(x)
+             list(restartName, if(is.null(description)) restartName else description)
+           })
   }
+  list(list(as.character(sldbState$condition), sprintf("  [%s]", class(sldbState$condition)[[1]]), FALSE),
+       computeRestartsForEmacs(),
+       backtraceForEmacs(),
+       list(sldbState$id))
 }
 
 readPacket <- function(io) {
@@ -164,7 +218,7 @@ writeSexpToString <- function(obj) {
                     }
                     string <- paste(string, ")", sep="") },
            "symbol"={ string <- paste(string, as.character(obj), sep="") },
-           "logical"={ if(obj) { paste(string, "t", sep="") } else { paste(string, "nil", sep="") }},
+           "logical"={ string <- if(obj) { paste(string, "t", sep="") } else { paste(string, "nil", sep="") }},
            "double"={ string <- paste(string, as.character(obj), sep="") },
            "integer"={ string <- paste(string, as.character(obj), sep="") },
            stop(paste("can't write object ", obj, sep="")))
@@ -174,7 +228,15 @@ writeSexpToString <- function(obj) {
   writeSexpToStringLoop(obj)
 }
 
-`swank:connection-info` <- function () {
+printToString <- function(val) {
+  f <- fifo("")
+  sink(f)
+  print(val)
+  sink()
+  readLines(f)
+}
+
+`swank:connection-info` <- function (io, sldbState) {
   list(quote(`:pid`), Sys.getpid(),
        quote(`:package`), list(quote(`:name`), "R", quote(`:prompt`), "R> "),
        quote(`:lisp-implementation`), list(quote(`:type`), "R",
@@ -182,30 +244,50 @@ writeSexpToString <- function(obj) {
                                            quote(`:version`), paste(R.version$major, R.version$minor, sep=".")))
 }
 
-`swank:swank-require` <- function (contribs) {
+`swank:swank-require` <- function (io, sldbState, contribs) {
   list()
 }
 
-`swank:create-repl` <- function(env, ...) {
+`swank:create-repl` <- function(io, sldbState, env, ...) {
   list("R", "R")
 }
 
-`swank:listener-eval` <- function(string) {
-  val <- eval(parse(text=string))
-  f <- fifo("")
-  sink(f)
-  print(val)
-  sink()
-  lines <- readLines(f)
-  list(quote(`:values`), paste(lines, collapse="\n"))
+`swank:listener-eval` <- function(io, sldbState, string) {
+  val <- eval(parse(text=string), envir = globalenv())
+  string <- printToString(val)
+  list(quote(`:values`), paste(string, collapse="\n"))
 }
 
-`swank:autodoc` <- function(rawForm, ...) {
+`swank:autodoc` <- function(io, sldbState, rawForm, ...) {
   "No Arglist Information"
 }
 
-`swank:throw-to-toplevel` <- function() {
-  condition <- simpleError("Throw to toplevel")
+`swank:throw-to-toplevel` <- function(io, sldbState) {
+  condition <- simpleCondition("Throw to toplevel")
   class(condition) <- c("swankTopLevel", class(condition))
   signalCondition(condition)
 }
+
+`swank:debugger-info-for-emacs` <- function(io, sldbState, from, to) {
+  debuggerInfoForEmacs(sldbState, from=from, to=to)
+}
+
+`swank:invoke-nth-restart-for-emacs` <- function(io, sldbState, level, n) {
+  if(sldbState$level == level) {
+    invokeRestart(sldbState$restarts[[n+1]])
+  }
+}
+
+`swank:buffer-first-change` <- function(io, sldbState, filename) {
+  FALSE
+}
+
+`swank:frame-locals-and-catch-tags` <- function(io, sldbState, index) {
+  str(sldbState$frames)
+  frame <- sldbState$frames[[1+index]]
+  objs <- ls(envir=frame)
+  list(lapply(objs, function(name) { list(quote(`:name`), name,
+                                          quote(`:id`), 0,
+                                          quote(`:value`), paste(printToString(eval(parse(text=name), envir=frame)), sep="", collapse="\n")) }),
+       list())
+}