Christophe Weblog Wiki Code Publications Music
The beginnings of a vaguely-useful sldb
[swankr.git] / swank.R
1 swank <- function(port=4005) {
2   acceptConnections(port, FALSE)
3 }
4
5 startSwank <- function(portFile) {
6   acceptConnections(FALSE, portFile)
7 }
8
9 acceptConnections <- function(port, portFile) {
10   s <- socketConnection(host="localhost", server=TRUE, port=port, open="r+b")
11   on.exit(close(s))
12   serve(s)
13 }
14
15 serve <- function(io) {
16   mainLoop(io)
17 }
18
19 mainLoop <- function(io) {
20   while(TRUE) {
21     tryCatch(dispatch(io, readPacket(io)),
22              swankTopLevel=function(c) NULL)
23   }
24 }
25
26 dispatch <- function(io, event, sldbState=NULL) {
27   str(event)
28   kind <- event[[1]]
29   if(kind == quote(`:emacs-rex`)) {
30     do.call("emacsRex", c(list(io), list(sldbState), event[-1]))
31   }
32 }
33
34 sendToEmacs <- function(io, obj) {
35   str(obj)
36   payload <- writeSexpToString(obj)
37   writeChar(sprintf("%06x", nchar(payload)), io, eos=NULL)
38   writeChar(payload, io, eos=NULL)
39   flush(io)
40   cat(sprintf("%06x", nchar(payload)), payload, sep="")
41 }
42
43 emacsRex <- function(io, sldbState, form, pkg, thread, id, level=0) {
44   ok <- FALSE
45   value <- NULL
46   tryCatch({
47     withCallingHandlers({
48       value <- do.call(eval(form[[1]]), c(list(io), list(sldbState), form[-1]))
49       ok <- TRUE
50     }, error=function(c) {
51       newSldbState <- makeSldbState(c, if(is.null(sldbState)) 0 else sldbState$level+1, id)
52       sldbLoop(io, newSldbState, id) })},
53     finally=sendToEmacs(io, list(quote(`:return`), if(ok) list(quote(`:ok`), value) else list(quote(`:abort`)), id)))
54 }
55
56 makeSldbState <- function(condition, level, id) {
57   calls <- rev(sys.calls())[-1]
58   frames <- rev(sys.frames())[-1]
59   ret <- list(condition=condition, level=level, id=id, calls=calls, frames=frames)
60   class(ret) <- c("sldbState", class(ret))
61   ret
62 }
63
64 sldbLoop <- function(io, sldbState, id) {
65   sendToEmacs(io, c(list(quote(`:debug`), id, sldbState$level), debuggerInfoForEmacs(sldbState)))
66   sendToEmacs(io, list(quote(`:debug-activate`), id, sldbState$level, FALSE))
67   while(TRUE) {
68     dispatch(io, readPacket(io), sldbState)
69   }
70 }
71
72 debuggerInfoForEmacs <- function(sldbState, from=0, to=NULL) {
73   backtraceForEmacs <- function() {
74     calls <- sldbState$calls
75     if(is.null(to)) to <- length(calls)
76     from <- from+1
77     calls <- lapply(calls[from:to], { frameNumber <- from-1;
78                              function (x) { ret <- list(frameNumber, paste(format(x), sep="", collapse=" ")); frameNumber <<- 1+frameNumber; ret }})
79   }
80   computeRestartsForEmacs <- function () {
81     lapply(computeRestarts(sldbState$condition),
82            function(x) {
83              ## this is all a little bit internalsy
84              restartName <- x[[1]][[1]]
85              description <- restartDescription(x)
86              list(restartName, if(is.null(description)) restartName else description)
87            })
88   }
89   list(list(as.character(sldbState$condition), sprintf("  [%s]", class(sldbState$condition)[[1]]), FALSE),
90        computeRestartsForEmacs(),
91        backtraceForEmacs(),
92        list(sldbState$id))
93 }
94
95 readPacket <- function(io) {
96   header <- readChunk(io, 6)
97   len <- strtoi(header, base=16)
98   payload <- readChunk(io, len)
99   readSexpFromString(payload)
100 }
101
102 readChunk <- function(io, len) {
103   buffer <- readChar(io, len)
104   if(nchar(buffer) != len) {
105     stop("short read in readChunk")
106   }
107   buffer
108 }
109
110 readSexpFromString <- function(string) {
111   pos <- 1
112   read <- function() {
113     skipWhitespace()
114     char <- substr(string, pos, pos)
115     switch(char,
116            "("=readList(),
117            "\""=readString(),
118            "'"=readQuote(),
119            {
120              if(pos > nchar(string))
121                stop("EOF during read")
122              obj <- readNumberOrSymbol()
123              if(obj == quote(`.`)) {
124                stop("Consing dot not implemented")
125              }
126              obj
127            })
128   }
129   skipWhitespace <- function() {
130     while(substr(string, pos, pos) %in% c(" ", "\t", "\n")) {
131       pos <<- pos + 1
132     }
133   }
134   readList <- function() {
135     ret <- list()
136     pos <<- pos + 1
137     while(TRUE) {
138       skipWhitespace()
139       char <- substr(string, pos, pos)
140       if(char == ")") {
141         pos <<- pos + 1
142         break
143       } else {
144         obj <- read()
145         if(length(obj) == 1 && obj == quote(`.`)) {
146           stop("Consing dot not implemented")
147         }
148         ret <- c(ret, list(obj))
149       }
150     }
151     ret
152   }
153   readString <- function() {
154     ret <- ""
155     addChar <- function(c) { ret <<- paste(ret, c, sep="") }
156     while(TRUE) {
157       pos <<- pos + 1
158       char <- substr(string, pos, pos)
159       switch(char,
160              "\""={ pos <<- pos + 1; break },
161              "\\"={ pos <<- pos + 1
162                     char2 <- substr(string, pos, pos)
163                     switch(char2,
164                            "\""=addChar(char2),
165                            "\\"=addChar(char2),
166                            stop("Unrecognized escape character")) },
167              addChar(char))
168     }
169     ret
170   }
171   readNumberOrSymbol <- function() {
172     token <- readToken()
173     if(nchar(token)==0) {
174       stop("End of file reading token")
175     } else if(grepl("^[0-9]+$", token)) {
176       strtoi(token)
177     } else if(grepl("^[0-9]+\\.[0-9]+$", token)) {
178       as.double(token)
179     } else {
180       as.name(token)
181     }
182   }
183   readToken <- function() {
184     token <- ""
185     while(TRUE) {
186       char <- substr(string, pos, pos)
187       if(char == "") {
188         break;
189       } else if(char %in% c(" ", "\n", "\t", "(", ")", "\"", "'")) {
190         break;
191       } else {
192         token <- paste(token, char, sep="")
193         pos <<- pos + 1
194       }
195     }
196     token
197   }
198   read()
199 }
200
201 writeSexpToString <- function(obj) {
202   writeSexpToStringLoop <- function(obj) {
203     switch(typeof(obj),
204            "character"={ string <- paste(string, "\"", gsub("([\"\\])", "\\\\\\1", obj), "\"", sep="") },
205            "list"={ string <- paste(string, "(", sep="")
206                     max <- length(obj)
207                     if(max > 0) {
208                       for(i in 1:max) {
209                         string <- paste(string, writeSexpToString(obj[[i]]), sep="")
210                         if(i != max) {
211                           string <- paste(string, " ", sep="")
212                         }
213                       }
214                     }
215                     string <- paste(string, ")", sep="") },
216            "symbol"={ string <- paste(string, as.character(obj), sep="") },
217            "logical"={ string <- if(obj) { paste(string, "t", sep="") } else { paste(string, "nil", sep="") }},
218            "double"={ string <- paste(string, as.character(obj), sep="") },
219            "integer"={ string <- paste(string, as.character(obj), sep="") },
220            stop(paste("can't write object ", obj, sep="")))
221     string
222   }
223   string <- ""
224   writeSexpToStringLoop(obj)
225 }
226
227 printToString <- function(val) {
228   f <- fifo("")
229   sink(f)
230   print(val)
231   sink()
232   readLines(f)
233 }
234
235 `swank:connection-info` <- function (io, sldbState) {
236   list(quote(`:pid`), Sys.getpid(),
237        quote(`:package`), list(quote(`:name`), "R", quote(`:prompt`), "R> "),
238        quote(`:lisp-implementation`), list(quote(`:type`), "R",
239                                            quote(`:name`), "R",
240                                            quote(`:version`), paste(R.version$major, R.version$minor, sep=".")))
241 }
242
243 `swank:swank-require` <- function (io, sldbState, contribs) {
244   list()
245 }
246
247 `swank:create-repl` <- function(io, sldbState, env, ...) {
248   list("R", "R")
249 }
250
251 `swank:listener-eval` <- function(io, sldbState, string) {
252   val <- eval(parse(text=string), envir = globalenv())
253   string <- printToString(val)
254   list(quote(`:values`), paste(string, collapse="\n"))
255 }
256
257 `swank:autodoc` <- function(io, sldbState, rawForm, ...) {
258   "No Arglist Information"
259 }
260
261 `swank:throw-to-toplevel` <- function(io, sldbState) {
262   condition <- simpleCondition("Throw to toplevel")
263   class(condition) <- c("swankTopLevel", class(condition))
264   signalCondition(condition)
265 }
266
267 `swank:debugger-info-for-emacs` <- function(io, sldbState, from, to) {
268   debuggerInfoForEmacs(sldbState, from=from, to=to)
269 }
270
271 `swank:invoke-nth-restart-for-emacs` <- function(io, sldbState, level, n) {
272   if(sldbState$level == level) {
273     invokeRestart(computeRestarts()[[n+1]])
274   }
275 }
276
277 `swank:buffer-first-change` <- function(io, sldbState, filename) {
278   FALSE
279 }
280
281 `swank:frame-locals-and-catch-tags` <- function(io, sldbState, index) {
282   str(sldbState$frames)
283   frame <- sldbState$frames[[1+index]]
284   objs <- ls(envir=frame)
285   list(lapply(objs, function(name) { list(quote(`:name`), name,
286                                           quote(`:id`), 0,
287                                           quote(`:value`), paste(printToString(eval(parse(text=name), envir=frame)), sep="", collapse="\n")) }),
288        list())
289 }