Christophe Weblog Wiki Code Publications Music
return properly from sldbLoop()
[swankr.git] / swank.R
diff --git a/swank.R b/swank.R
index c6a1ec2f0e0afe13d7e90a3910370bbb3dfe49ef..f3a85ccc6a8b0d770b9273180bb179e717fc736d 100644 (file)
--- a/swank.R
+++ b/swank.R
@@ -18,8 +18,9 @@ serve <- function(io) {
 
 mainLoop <- function(io) {
   while(TRUE) {
-    tryCatch(dispatch(io, readPacket(io)),
-             swankTopLevel=function(c) NULL)
+    withRestarts(tryCatch(dispatch(io, readPacket(io)),
+                          swankTopLevel=function(c) NULL),
+                 abort="return to SLIME's toplevel")
   }
 }
 
@@ -49,34 +50,39 @@ emacsRex <- function(io, sldbState, form, pkg, thread, id, level=0) {
       ok <- TRUE
     }, error=function(c) {
       newSldbState <- makeSldbState(c, if(is.null(sldbState)) 0 else sldbState$level+1, id)
-      sldbLoop(io, newSldbState, 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) {
-  ret <- list(condition=condition, level=level, id=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) {
-  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)
-  }
+  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 <- rev(sys.calls())
+    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 }})
   }
   computeRestartsForEmacs <- function () {
-    lapply(computeRestarts(sldbState$condition),
+    lapply(sldbState$restarts,
            function(x) {
              ## this is all a little bit internalsy
              restartName <- x[[1]][[1]]
@@ -222,6 +228,14 @@ writeSexpToString <- function(obj) {
   writeSexpToStringLoop(obj)
 }
 
+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> "),
@@ -240,12 +254,8 @@ writeSexpToString <- function(obj) {
 
 `swank:listener-eval` <- function(io, sldbState, string) {
   val <- eval(parse(text=string), envir = globalenv())
-  f <- fifo("")
-  sink(f)
-  print(val)
-  sink()
-  lines <- readLines(f)
-  list(quote(`:values`), paste(lines, collapse="\n"))
+  string <- printToString(val)
+  list(quote(`:values`), paste(string, collapse="\n"))
 }
 
 `swank:autodoc` <- function(io, sldbState, rawForm, ...) {
@@ -264,6 +274,20 @@ writeSexpToString <- function(obj) {
 
 `swank:invoke-nth-restart-for-emacs` <- function(io, sldbState, level, n) {
   if(sldbState$level == level) {
-    invokeRestart(computeRestarts()[[n+1]])
+    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())
+}