X-Git-Url: http://christophe.rhodes.io/gitweb/?p=swankr.git;a=blobdiff_plain;f=swank.R;h=0684ab071366fca918bd5541c5aa2ed6e76f5b46;hp=1c1633d77ad8c7aa7fa8a709eb3a3bcd02e57e10;hb=98e89761b295de170b77d10779a979f9da1a3d84;hpb=5035036a7da09e17a5a70ea7ea15657d671e9c52 diff --git a/swank.R b/swank.R index 1c1633d..0684ab0 100644 --- a/swank.R +++ b/swank.R @@ -65,7 +65,7 @@ makeSldbState <- function(condition, level, id) { sldbLoop <- function(io, sldbState, id) { tryCatch({ - sendToEmacs(io, c(list(quote(`:debug`), id, sldbState$level), debuggerInfoForEmacs(sldbState))) + sendToEmacs(io, c(list(quote(`:debug`), id, sldbState$level), `swank:debugger-info-for-emacs`(io, sldbState))) sendToEmacs(io, list(quote(`:debug-activate`), id, sldbState$level, FALSE)) while(TRUE) { dispatch(io, readPacket(io), sldbState) @@ -73,29 +73,6 @@ sldbLoop <- function(io, sldbState, id) { }, 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 }}) - } - 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) { header <- readChunk(io, 6) len <- strtoi(header, base=16) @@ -230,10 +207,8 @@ writeSexpToString <- function(obj) { printToString <- function(val) { f <- fifo("") - sink(f) - print(val) - sink() - readLines(f) + tryCatch({ sink(f); print(val); sink(); readLines(f) }, + finally=close(f)) } `swank:connection-info` <- function (io, sldbState) { @@ -272,8 +247,35 @@ printToString <- function(val) { signalCondition(condition) } -`swank:debugger-info-for-emacs` <- function(io, sldbState, from, to) { - debuggerInfoForEmacs(sldbState, from=from, to=to) +`swank:backtrace` <- function(io, sldbState, from=0, to=NULL) { + 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 (sldbState) { + 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) + }) +} + +`swank:debugger-info-for-emacs` <- function(io, sldbState, from=0, to=NULL) { + list(list(as.character(sldbState$condition), sprintf(" [%s]", class(sldbState$condition)[[1]]), FALSE), + computeRestartsForEmacs(sldbState), + `swank:backtrace`(io, sldbState, from, to), + list(sldbState$id)) } `swank:invoke-nth-restart-for-emacs` <- function(io, sldbState, level, n) { @@ -318,3 +320,29 @@ printToString <- function(val) { abort="abort compilation") list(quote(`:compilation-result`), list(), TRUE, times[3]) } + +`swank:interactive-eval` <- function(io, sldbState, string) { + retry <- TRUE + value <- "" + while(retry) { + retry <- FALSE + withRestarts(value <- eval(parse(text=string), envir = globalenv()), + retry=list(description="retry SLIME interactive evaluation request", handler=function() retry <<- TRUE)) + } + printToString(value) +} + +`swank:eval-and-grab-output` <- function(io, sldbState, string) { + retry <- TRUE + value <- "" + output <- NULL + f <- fifo("") + tryCatch({ + sink(f) + while(retry) { + retry <- FALSE + withRestarts(value <- eval(parse(text=string), envir = globalenv()), + retry=list(description="retry SLIME interactive evaluation request", handler=function() retry <<- TRUE))}}, + finally={sink(); output <- readLines(f); close(f)}) + list(output, printToString(value)) +}