Christophe Weblog Wiki Code Publications Music
srcrefs in swank:compile-string-for-emacs
[swankr.git] / swank.R
diff --git a/swank.R b/swank.R
index 5fe20bbefe633d6a9f1c1e0009f11e0cef32c9d6..fa22d64a89fbb81c7cbce794e5360a48870ad859 100644 (file)
--- a/swank.R
+++ b/swank.R
@@ -377,7 +377,6 @@ computeRestartsForEmacs <- function (sldbState) {
 }
 
 `swank:frame-locals-and-catch-tags` <- function(slimeConnection, sldbState, index) {
-  str(sldbState$frames)
   frame <- sldbState$frames[[1+index]]
   objs <- ls(envir=frame)
   list(lapply(objs, function(name) { list(quote(`:name`), name,
@@ -402,11 +401,42 @@ computeRestartsForEmacs <- function (sldbState) {
 }
 
 `swank:compile-string-for-emacs` <- function(slimeConnection, sldbState, string, buffer, position, filename, policy) {
-  # FIXME: I think in parse() here we can use srcref to associate
-  # buffer/filename/position to the objects.  Or something.
-  withRestarts({ times <- system.time(eval(parse(text=string), envir = globalenv())) },
+  lineOffset <- charOffset <- colOffset <- NULL
+  for(pos in position) {
+    switch(as.character(pos[[1]]),
+           `:position` = {charOffset <- pos[[2]]},
+           `:line` = {lineOffset <- pos[[2]]; colOffset <- pos[[3]]},
+           warning("unknown content in pos", pos))
+  }
+  frob <- function(refs) {
+    lapply(refs,
+           function(x)
+           srcref(attr(x,"srcfile"),
+                  c(x[1]+lineOffset-1, ifelse(x[1]==1, x[2]+colOffset-1, x[2]),
+                    x[3]+lineOffset-1, ifelse(x[3]==1, x[4]+colOffset-1, x[4]),
+                    ifelse(x[1]==1, x[5]+colOffset-1, x[5]),
+                    ifelse(x[3]==1, x[6]+colOffset-1, x[6]))))
+  }
+  transformSrcrefs <- function(s) {
+    srcrefs <- attr(s, "srcref")
+    attribs <- attributes(s)
+    new <- 
+      switch(mode(s),
+             "call"=as.call(lapply(s, transformSrcrefs)),
+             "expression"=as.expression(lapply(s, transformSrcrefs)),
+             s)
+    attributes(new) <- attribs
+    if(!is.null(attr(s, "srcref"))) {
+      attr(new, "srcref") <- frob(srcrefs)
+    }
+    new
+  }
+  withRestarts({
+    times <- system.time({
+      exprs <- parse(text=string, srcfile=srcfile(filename))
+      eval(transformSrcrefs(exprs), envir = globalenv()) })},
                abort="abort compilation")
-  list(quote(`:compilation-result`), list(), TRUE, times[3])
+  list(quote(`:compilation-result`), list(), TRUE, times[3], FALSE, FALSE)
 }
 
 withRetryRestart <- function(description, expr) {
@@ -446,9 +476,16 @@ withRetryRestart <- function(description, expr) {
         list()
       } else {
         filename <- get("filename", srcfile)
+        ## KLUDGE: what this means is "is the srcfile filename
+        ## absolute?"
+        if(substr(filename, 1, 1) == "/") {
+          file <- filename
+        } else {
+          file <- sprintf("%s/%s", srcfile$wd, filename)
+        }
         list(list(sprintf("function %s", string),
                   list(quote(`:location`),
-                       list(quote(`:file`), sprintf("%s/%s", srcfile$wd, srcfile$filename)),
+                       list(quote(`:file`), file),
                        list(quote(`:line`), srcref[[2]][[1]], srcref[[2]][[2]]-1),
                        list())))
       }
@@ -622,3 +659,13 @@ emacsInspect.numeric <- function(numeric) {
   setwd(directory)
   `swank:default-directory`(slimeConnection, sldbState)
 }
+
+`swank:load-file` <- function(slimeConnection, sldbState, filename) {
+  source(filename, local=FALSE)
+  TRUE
+}
+
+`swank:compile-file-for-emacs` <- function(slimeConnection, sldbState, filename, loadp, ...) {
+  times <- system.time(parse(filename))
+  list(quote(`:compilation-result`), list(), TRUE, times[3], substitute(loadp), filename)
+}