Christophe Weblog Wiki Code Publications Music
f395217bf92abe79767a55c5434bc015bb003781
[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     withRestarts(tryCatch(dispatch(io, readPacket(io)),
22                           swankTopLevel=function(c) NULL),
23                  abort="return to SLIME's toplevel")
24   }
25 }
26
27 dispatch <- function(io, event, sldbState=NULL) {
28   str(event)
29   kind <- event[[1]]
30   if(kind == quote(`:emacs-rex`)) {
31     do.call("emacsRex", c(list(io), list(sldbState), event[-1]))
32   }
33 }
34
35 sendToEmacs <- function(io, obj) {
36   str(obj)
37   payload <- writeSexpToString(obj)
38   writeChar(sprintf("%06x", nchar(payload)), io, eos=NULL)
39   writeChar(payload, io, eos=NULL)
40   flush(io)
41   cat(sprintf("%06x", nchar(payload)), payload, sep="")
42 }
43
44 emacsRex <- function(io, sldbState, form, pkg, thread, id, level=0) {
45   ok <- FALSE
46   value <- NULL
47   tryCatch({
48     withCallingHandlers({
49       value <- do.call(eval(form[[1]]), c(list(io), list(sldbState), form[-1]))
50       ok <- TRUE
51     }, error=function(c) {
52       newSldbState <- makeSldbState(c, if(is.null(sldbState)) 0 else sldbState$level+1, id)
53       withRestarts(sldbLoop(io, newSldbState, id), abort=paste("return to sldb level", newSldbState$level)) })},
54     finally=sendToEmacs(io, list(quote(`:return`), if(ok) list(quote(`:ok`), value) else list(quote(`:abort`)), id)))
55 }
56
57 makeSldbState <- function(condition, level, id) {
58   calls <- rev(sys.calls())[-1]
59   frames <- rev(sys.frames())[-1]
60   restarts <- rev(computeRestarts(condition))[-1]
61   ret <- list(condition=condition, level=level, id=id, restarts=restarts, calls=calls, frames=frames)
62   class(ret) <- c("sldbState", class(ret))
63   ret
64 }
65
66 sldbLoop <- function(io, sldbState, id) {
67   tryCatch({
68     sendToEmacs(io, c(list(quote(`:debug`), id, sldbState$level), `swank:debugger-info-for-emacs`(io, sldbState)))
69     sendToEmacs(io, list(quote(`:debug-activate`), id, sldbState$level, FALSE))
70     while(TRUE) {
71       dispatch(io, readPacket(io), sldbState)
72     }
73   }, finally=sendToEmacs(io, c(list(quote(`:debug-return`), id, sldbState$level, FALSE))))
74 }
75
76 readPacket <- function(io) {
77   header <- readChunk(io, 6)
78   len <- strtoi(header, base=16)
79   payload <- readChunk(io, len)
80   readSexpFromString(payload)
81 }
82
83 readChunk <- function(io, len) {
84   buffer <- readChar(io, len)
85   if(nchar(buffer) != len) {
86     stop("short read in readChunk")
87   }
88   buffer
89 }
90
91 readSexpFromString <- function(string) {
92   pos <- 1
93   read <- function() {
94     skipWhitespace()
95     char <- substr(string, pos, pos)
96     switch(char,
97            "("=readList(),
98            "\""=readString(),
99            "'"=readQuote(),
100            {
101              if(pos > nchar(string))
102                stop("EOF during read")
103              obj <- readNumberOrSymbol()
104              if(obj == quote(`.`)) {
105                stop("Consing dot not implemented")
106              }
107              obj
108            })
109   }
110   skipWhitespace <- function() {
111     while(substr(string, pos, pos) %in% c(" ", "\t", "\n")) {
112       pos <<- pos + 1
113     }
114   }
115   readList <- function() {
116     ret <- list()
117     pos <<- pos + 1
118     while(TRUE) {
119       skipWhitespace()
120       char <- substr(string, pos, pos)
121       if(char == ")") {
122         pos <<- pos + 1
123         break
124       } else {
125         obj <- read()
126         if(length(obj) == 1 && obj == quote(`.`)) {
127           stop("Consing dot not implemented")
128         }
129         ret <- c(ret, list(obj))
130       }
131     }
132     ret
133   }
134   readString <- function() {
135     ret <- ""
136     addChar <- function(c) { ret <<- paste(ret, c, sep="") }
137     while(TRUE) {
138       pos <<- pos + 1
139       char <- substr(string, pos, pos)
140       switch(char,
141              "\""={ pos <<- pos + 1; break },
142              "\\"={ pos <<- pos + 1
143                     char2 <- substr(string, pos, pos)
144                     switch(char2,
145                            "\""=addChar(char2),
146                            "\\"=addChar(char2),
147                            stop("Unrecognized escape character")) },
148              addChar(char))
149     }
150     ret
151   }
152   readNumberOrSymbol <- function() {
153     token <- readToken()
154     if(nchar(token)==0) {
155       stop("End of file reading token")
156     } else if(grepl("^[0-9]+$", token)) {
157       strtoi(token)
158     } else if(grepl("^[0-9]+\\.[0-9]+$", token)) {
159       as.double(token)
160     } else {
161       as.name(token)
162     }
163   }
164   readToken <- function() {
165     token <- ""
166     while(TRUE) {
167       char <- substr(string, pos, pos)
168       if(char == "") {
169         break;
170       } else if(char %in% c(" ", "\n", "\t", "(", ")", "\"", "'")) {
171         break;
172       } else {
173         token <- paste(token, char, sep="")
174         pos <<- pos + 1
175       }
176     }
177     token
178   }
179   read()
180 }
181
182 writeSexpToString <- function(obj) {
183   writeSexpToStringLoop <- function(obj) {
184     switch(typeof(obj),
185            "character"={ string <- paste(string, "\"", gsub("([\"\\])", "\\\\\\1", obj), "\"", sep="") },
186            "list"={ string <- paste(string, "(", sep="")
187                     max <- length(obj)
188                     if(max > 0) {
189                       for(i in 1:max) {
190                         string <- paste(string, writeSexpToString(obj[[i]]), sep="")
191                         if(i != max) {
192                           string <- paste(string, " ", sep="")
193                         }
194                       }
195                     }
196                     string <- paste(string, ")", sep="") },
197            "symbol"={ string <- paste(string, as.character(obj), sep="") },
198            "logical"={ string <- if(obj) { paste(string, "t", sep="") } else { paste(string, "nil", sep="") }},
199            "double"={ string <- paste(string, as.character(obj), sep="") },
200            "integer"={ string <- paste(string, as.character(obj), sep="") },
201            stop(paste("can't write object ", obj, sep="")))
202     string
203   }
204   string <- ""
205   writeSexpToStringLoop(obj)
206 }
207
208 printToString <- function(val) {
209   f <- fifo("")
210   tryCatch({ sink(f); print(val); sink(); readLines(f) },
211            finally=close(f))
212 }
213
214 `swank:connection-info` <- function (io, sldbState) {
215   list(quote(`:pid`), Sys.getpid(),
216        quote(`:package`), list(quote(`:name`), "R", quote(`:prompt`), "R> "),
217        quote(`:lisp-implementation`), list(quote(`:type`), "R",
218                                            quote(`:name`), "R",
219                                            quote(`:version`), paste(R.version$major, R.version$minor, sep=".")))
220 }
221
222 `swank:swank-require` <- function (io, sldbState, contribs) {
223   list()
224 }
225
226 `swank:create-repl` <- function(io, sldbState, env, ...) {
227   list("R", "R")
228 }
229
230 `swank:listener-eval` <- function(io, sldbState, string) {
231   val <- eval(parse(text=string), envir = globalenv())
232   string <- printToString(val)
233   list(quote(`:values`), paste(string, collapse="\n"))
234 }
235
236 `swank:autodoc` <- function(io, sldbState, rawForm, ...) {
237   "No Arglist Information"
238 }
239
240 `swank:operator-arglist` <- function(io, sldbState, op, package) {
241   list()
242 }
243
244 `swank:throw-to-toplevel` <- function(io, sldbState) {
245   condition <- simpleCondition("Throw to toplevel")
246   class(condition) <- c("swankTopLevel", class(condition))
247   signalCondition(condition)
248 }
249
250 `swank:backtrace` <- function(io, sldbState, from=0, to=NULL) {
251   calls <- sldbState$calls
252   if(is.null(to)) to <- length(calls)
253   from <- from+1
254   calls <- lapply(calls[from:to],
255                   { frameNumber <- from-1;
256                     function (x) {
257                       ret <- list(frameNumber, paste(format(x), sep="", collapse=" "))
258                       frameNumber <<- 1+frameNumber
259                       ret
260                     }
261                   })
262 }
263
264 computeRestartsForEmacs <- function (sldbState) {
265   lapply(sldbState$restarts,
266          function(x) {
267            ## this is all a little bit internalsy
268            restartName <- x[[1]][[1]]
269            description <- restartDescription(x)
270            list(restartName, if(is.null(description)) restartName else description)
271          })
272 }
273
274 `swank:debugger-info-for-emacs` <- function(io, sldbState, from=0, to=NULL) {
275   list(list(as.character(sldbState$condition), sprintf("  [%s]", class(sldbState$condition)[[1]]), FALSE),
276        computeRestartsForEmacs(sldbState),
277        `swank:backtrace`(io, sldbState, from, to),
278        list(sldbState$id))
279 }
280
281 `swank:invoke-nth-restart-for-emacs` <- function(io, sldbState, level, n) {
282   if(sldbState$level == level) {
283     invokeRestart(sldbState$restarts[[n+1]])
284   }
285 }
286
287 `swank:frame-source-location` <- function(io, sldbState, n) {
288   call <- sldbState$calls[[n+1]]
289   srcref <- attr(call, "srcref")
290   srcfile <- attr(srcref, "srcfile")
291   if(is.null(srcfile)) {
292     list(quote(`:error`), "no srcfile")
293   } else {
294     filename <- get("filename", srcfile)
295     list(quote(`:location`),
296          list(quote(`:file`), filename),
297          list(quote(`:line`), srcref[[1]], srcref[[2]]-1),
298          FALSE)
299   }
300 }
301
302 `swank:buffer-first-change` <- function(io, sldbState, filename) {
303   FALSE
304 }
305
306 `swank:frame-locals-and-catch-tags` <- function(io, sldbState, index) {
307   str(sldbState$frames)
308   frame <- sldbState$frames[[1+index]]
309   objs <- ls(envir=frame)
310   list(lapply(objs, function(name) { list(quote(`:name`), name,
311                                           quote(`:id`), 0,
312                                           quote(`:value`), paste(printToString(eval(parse(text=name), envir=frame)), sep="", collapse="\n")) }),
313        list())
314 }
315
316 `swank:simple-completions` <- function(io, sldbState, prefix, package) {
317   ## fails multiply if prefix contains regexp metacharacters
318   matches <- apropos(sprintf("^%s", prefix), ignore.case=FALSE)
319   nmatches <- length(matches)
320   if(nmatches == 0) {
321     list(list(), "")
322   } else {
323     longest <- matches[order(nchar(matches))][1]
324     while(length(grep(sprintf("^%s", longest), matches)) < nmatches) {
325       longest <- substr(longest, 1, nchar(longest)-1)
326     }
327     list(as.list(matches), longest)
328   }
329 }
330
331 `swank:compile-string-for-emacs` <- function(io, sldbState, string, buffer, position, filename, policy) {
332   # FIXME: I think in parse() here we can use srcref to associate
333   # buffer/filename/position to the objects.  Or something.
334   withRestarts({ times <- system.time(eval(parse(text=string), envir = globalenv())) },
335                abort="abort compilation")
336   list(quote(`:compilation-result`), list(), TRUE, times[3])
337 }
338
339 `swank:interactive-eval` <-  function(io, sldbState, string) {
340   retry <- TRUE
341   value <- ""
342   while(retry) {
343     retry <- FALSE
344     withRestarts(value <- eval(parse(text=string), envir = globalenv()),
345                  retry=list(description="retry SLIME interactive evaluation request", handler=function() retry <<- TRUE))
346   }
347   printToString(value)
348 }
349
350 `swank:eval-and-grab-output` <- function(io, sldbState, string) {
351   retry <- TRUE
352   value <- ""
353   output <- NULL
354   f <- fifo("")
355   tryCatch({
356     sink(f)
357     while(retry) {
358       retry <- FALSE
359       withRestarts(value <- eval(parse(text=string), envir = globalenv()),
360                    retry=list(description="retry SLIME interactive evaluation request", handler=function() retry <<- TRUE))}},
361            finally={sink(); output <- readLines(f); close(f)})
362   list(output, printToString(value))
363 }