Christophe Weblog Wiki Code Publications Music
put abort restarts around the main and sldb loops
[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   sendToEmacs(io, c(list(quote(`:debug`), id, sldbState$level), debuggerInfoForEmacs(sldbState)))
68   sendToEmacs(io, list(quote(`:debug-activate`), id, sldbState$level, FALSE))
69   while(TRUE) {
70     dispatch(io, readPacket(io), sldbState)
71   }
72 }
73
74 debuggerInfoForEmacs <- function(sldbState, from=0, to=NULL) {
75   backtraceForEmacs <- function() {
76     calls <- sldbState$calls
77     if(is.null(to)) to <- length(calls)
78     from <- from+1
79     calls <- lapply(calls[from:to], { frameNumber <- from-1;
80                              function (x) { ret <- list(frameNumber, paste(format(x), sep="", collapse=" ")); frameNumber <<- 1+frameNumber; ret }})
81   }
82   computeRestartsForEmacs <- function () {
83     lapply(sldbState$restarts,
84            function(x) {
85              ## this is all a little bit internalsy
86              restartName <- x[[1]][[1]]
87              description <- restartDescription(x)
88              list(restartName, if(is.null(description)) restartName else description)
89            })
90   }
91   list(list(as.character(sldbState$condition), sprintf("  [%s]", class(sldbState$condition)[[1]]), FALSE),
92        computeRestartsForEmacs(),
93        backtraceForEmacs(),
94        list(sldbState$id))
95 }
96
97 readPacket <- function(io) {
98   header <- readChunk(io, 6)
99   len <- strtoi(header, base=16)
100   payload <- readChunk(io, len)
101   readSexpFromString(payload)
102 }
103
104 readChunk <- function(io, len) {
105   buffer <- readChar(io, len)
106   if(nchar(buffer) != len) {
107     stop("short read in readChunk")
108   }
109   buffer
110 }
111
112 readSexpFromString <- function(string) {
113   pos <- 1
114   read <- function() {
115     skipWhitespace()
116     char <- substr(string, pos, pos)
117     switch(char,
118            "("=readList(),
119            "\""=readString(),
120            "'"=readQuote(),
121            {
122              if(pos > nchar(string))
123                stop("EOF during read")
124              obj <- readNumberOrSymbol()
125              if(obj == quote(`.`)) {
126                stop("Consing dot not implemented")
127              }
128              obj
129            })
130   }
131   skipWhitespace <- function() {
132     while(substr(string, pos, pos) %in% c(" ", "\t", "\n")) {
133       pos <<- pos + 1
134     }
135   }
136   readList <- function() {
137     ret <- list()
138     pos <<- pos + 1
139     while(TRUE) {
140       skipWhitespace()
141       char <- substr(string, pos, pos)
142       if(char == ")") {
143         pos <<- pos + 1
144         break
145       } else {
146         obj <- read()
147         if(length(obj) == 1 && obj == quote(`.`)) {
148           stop("Consing dot not implemented")
149         }
150         ret <- c(ret, list(obj))
151       }
152     }
153     ret
154   }
155   readString <- function() {
156     ret <- ""
157     addChar <- function(c) { ret <<- paste(ret, c, sep="") }
158     while(TRUE) {
159       pos <<- pos + 1
160       char <- substr(string, pos, pos)
161       switch(char,
162              "\""={ pos <<- pos + 1; break },
163              "\\"={ pos <<- pos + 1
164                     char2 <- substr(string, pos, pos)
165                     switch(char2,
166                            "\""=addChar(char2),
167                            "\\"=addChar(char2),
168                            stop("Unrecognized escape character")) },
169              addChar(char))
170     }
171     ret
172   }
173   readNumberOrSymbol <- function() {
174     token <- readToken()
175     if(nchar(token)==0) {
176       stop("End of file reading token")
177     } else if(grepl("^[0-9]+$", token)) {
178       strtoi(token)
179     } else if(grepl("^[0-9]+\\.[0-9]+$", token)) {
180       as.double(token)
181     } else {
182       as.name(token)
183     }
184   }
185   readToken <- function() {
186     token <- ""
187     while(TRUE) {
188       char <- substr(string, pos, pos)
189       if(char == "") {
190         break;
191       } else if(char %in% c(" ", "\n", "\t", "(", ")", "\"", "'")) {
192         break;
193       } else {
194         token <- paste(token, char, sep="")
195         pos <<- pos + 1
196       }
197     }
198     token
199   }
200   read()
201 }
202
203 writeSexpToString <- function(obj) {
204   writeSexpToStringLoop <- function(obj) {
205     switch(typeof(obj),
206            "character"={ string <- paste(string, "\"", gsub("([\"\\])", "\\\\\\1", obj), "\"", sep="") },
207            "list"={ string <- paste(string, "(", sep="")
208                     max <- length(obj)
209                     if(max > 0) {
210                       for(i in 1:max) {
211                         string <- paste(string, writeSexpToString(obj[[i]]), sep="")
212                         if(i != max) {
213                           string <- paste(string, " ", sep="")
214                         }
215                       }
216                     }
217                     string <- paste(string, ")", sep="") },
218            "symbol"={ string <- paste(string, as.character(obj), sep="") },
219            "logical"={ string <- if(obj) { paste(string, "t", sep="") } else { paste(string, "nil", sep="") }},
220            "double"={ string <- paste(string, as.character(obj), sep="") },
221            "integer"={ string <- paste(string, as.character(obj), sep="") },
222            stop(paste("can't write object ", obj, sep="")))
223     string
224   }
225   string <- ""
226   writeSexpToStringLoop(obj)
227 }
228
229 printToString <- function(val) {
230   f <- fifo("")
231   sink(f)
232   print(val)
233   sink()
234   readLines(f)
235 }
236
237 `swank:connection-info` <- function (io, sldbState) {
238   list(quote(`:pid`), Sys.getpid(),
239        quote(`:package`), list(quote(`:name`), "R", quote(`:prompt`), "R> "),
240        quote(`:lisp-implementation`), list(quote(`:type`), "R",
241                                            quote(`:name`), "R",
242                                            quote(`:version`), paste(R.version$major, R.version$minor, sep=".")))
243 }
244
245 `swank:swank-require` <- function (io, sldbState, contribs) {
246   list()
247 }
248
249 `swank:create-repl` <- function(io, sldbState, env, ...) {
250   list("R", "R")
251 }
252
253 `swank:listener-eval` <- function(io, sldbState, string) {
254   val <- eval(parse(text=string), envir = globalenv())
255   string <- printToString(val)
256   list(quote(`:values`), paste(string, collapse="\n"))
257 }
258
259 `swank:autodoc` <- function(io, sldbState, rawForm, ...) {
260   "No Arglist Information"
261 }
262
263 `swank:throw-to-toplevel` <- function(io, sldbState) {
264   condition <- simpleCondition("Throw to toplevel")
265   class(condition) <- c("swankTopLevel", class(condition))
266   signalCondition(condition)
267 }
268
269 `swank:debugger-info-for-emacs` <- function(io, sldbState, from, to) {
270   debuggerInfoForEmacs(sldbState, from=from, to=to)
271 }
272
273 `swank:invoke-nth-restart-for-emacs` <- function(io, sldbState, level, n) {
274   if(sldbState$level == level) {
275     invokeRestart(sldbState$restarts[[n+1]])
276   }
277 }
278
279 `swank:buffer-first-change` <- function(io, sldbState, filename) {
280   FALSE
281 }
282
283 `swank:frame-locals-and-catch-tags` <- function(io, sldbState, index) {
284   str(sldbState$frames)
285   frame <- sldbState$frames[[1+index]]
286   objs <- ls(envir=frame)
287   list(lapply(objs, function(name) { list(quote(`:name`), name,
288                                           quote(`:id`), 0,
289                                           quote(`:value`), paste(printToString(eval(parse(text=name), envir=frame)), sep="", collapse="\n")) }),
290        list())
291 }