Christophe Weblog Wiki Code Publications Music
return stack frames in slime's order (most recent first)
[swankr.git] / swank.R
diff --git a/swank.R b/swank.R
index a9b62c6737994c8184a0961f07d29d3d8f8717c2..c6a1ec2f0e0afe13d7e90a3910370bbb3dfe49ef 100644 (file)
--- a/swank.R
+++ b/swank.R
@@ -69,17 +69,25 @@ sldbLoop <- function(io, sldbState, id) {
 
 debuggerInfoForEmacs <- function(sldbState, from=0, to=NULL) {
   backtraceForEmacs <- function() {
-    calls <- sys.calls()
+    calls <- rev(sys.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),
+           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),
-       lapply(computeRestarts(), function(x) list(x[[1]][[1]], x[[1]][[1]])),
+       computeRestartsForEmacs(),
        backtraceForEmacs(),
        list(sldbState$id))
-#       lapply(calls[from:to], function(x) paste(format(x), sep="", collapse=" ")))
 }
 
 readPacket <- function(io) {
@@ -231,7 +239,7 @@ writeSexpToString <- function(obj) {
 }
 
 `swank:listener-eval` <- function(io, sldbState, string) {
-  val <- eval(parse(text=string))
+  val <- eval(parse(text=string), envir = globalenv())
   f <- fifo("")
   sink(f)
   print(val)
@@ -253,3 +261,9 @@ writeSexpToString <- function(obj) {
 `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(computeRestarts()[[n+1]])
+  }
+}