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