X-Git-Url: http://christophe.rhodes.io/gitweb/?p=swankr.git;a=blobdiff_plain;f=swank.R;h=57ead0ac9f803a1d2729f737d739c0d4a10fcb69;hp=67fdbbcfc9cdb1d63e72130a3e169176312f9584;hb=fc149c9eb2e0c2d1645f8ab3bfcd52eaaf823dab;hpb=fdb4f4d744580b9dc6db92489610f32e42cec15e diff --git a/swank.R b/swank.R index 67fdbbc..57ead0a 100644 --- a/swank.R +++ b/swank.R @@ -293,7 +293,7 @@ printToString <- function(val) { `swank:connection-info` <- function (slimeConnection, sldbState) { list(quote(`:pid`), Sys.getpid(), quote(`:package`), list(quote(`:name`), "R", quote(`:prompt`), "R> "), - quote(`:version`), "2012-04-23", + quote(`:version`), "2014-09-13", quote(`:encoding`), list(quote(`:coding-systems`), list("utf-8-unix")), quote(`:lisp-implementation`), list(quote(`:type`), "R", quote(`:name`), "R", @@ -314,6 +314,8 @@ printToString <- function(val) { list("R", "R") } +`swank-repl:create-repl` <- `swank:create-repl` + makeReplResult <- function(value) { string <- printToString(value) list(quote(`:write-string`), string, @@ -344,6 +346,12 @@ sendReplResultFunction <- sendReplResult list() } +`swank-repl:listener-eval` <- `swank:listener-eval` + +`swank:clear-repl-variables` <- function(slimeConnection, sldbState) { + list() +} + `swank:autodoc` <- function(slimeConnection, sldbState, rawForm, ...) { list("No Arglist Information", TRUE) } @@ -377,6 +385,25 @@ helpFilesWithTopicString <- function(value) { helpFilesWithTopicString(value) } +`swank:apropos-list-for-emacs` <- function(slimeConnection, sldbState, name, onlyExternal, package, caseSensitive) { + x <- help.search(name, fields="alias", package=.packages())$matches + brieflyDescribe <- function(name, title) { + if (exists(name, globalenv())) { + val <- get(name, globalenv()) + kind <- if("function" %in% class(val)) quote(`:function`) else quote(`:variable`) + list(quote(`:designator`), name, kind, title) + } else { + ## maybe + list(quote(`:designator`), name, quote(`:type`), title) + } + } + mapply(brieflyDescribe, x[,"name"], x[,"title"], SIMPLIFY=FALSE) +} + +`swank:describe-definition-for-emacs` <- function(slimeConnection, sldbState, name, kind) { + `swank:describe-symbol`(slimeConnection, sldbState, name, NULL) +} + `swank:throw-to-toplevel` <- function(slimeConnection, sldbState) { condition <- simpleCondition("Throw to toplevel") class(condition) <- c("swankTopLevel", class(condition)) @@ -470,43 +497,46 @@ computeRestartsForEmacs <- function (sldbState) { list()) } -`swank:simple-completions` <- function(slimeConnection, sldbState, prefix, package) { - symbolFieldsCompletion <- function(object, rest) { - ## FIXME: this is hacky, ignoring several syntax issues (use of - ## and/or necessity for backquoting identifiers: e.g. fields - ## containing hyphens) - if((dollar <- regexpr("$", rest, fixed=TRUE)) == -1) { - matches <- grep(sprintf("^%s", literal2rx(rest)), names(object), value=TRUE) - matches <- sprintf("%s$%s", gsub("\\$[^$]*$", "", prefix), matches) - returnMatches(matches) +symbolFieldsCompletion <- function(object, prefix, rest) { + ## FIXME: this is hacky, ignoring several syntax issues (use of + ## and/or necessity for backquoting identifiers: e.g. fields + ## containing hyphens) + if((dollar <- regexpr("$", rest, fixed=TRUE)) == -1) { + matches <- grep(sprintf("^%s", literal2rx(rest)), names(object), value=TRUE) + matches <- sprintf("%s$%s", gsub("\\$[^$]*$", "", prefix), matches) + returnMatches(matches) + } else { + if(exists(substr(rest, 1, dollar-1), object)) { + symbolFieldsCompletion(get(substr(rest, 1, dollar-1), object), prefix, substr(rest, dollar+1, nchar(rest))) } else { - if(exists(substr(rest, 1, dollar-1), object)) { - symbolFieldsCompletion(get(substr(rest, 1, dollar-1), object), substr(rest, dollar+1, nchar(rest))) - } else { - returnMatches(character(0)) - } + returnMatches(character(0)) } } - returnMatches <- function(matches) { - nmatches <- length(matches) - if(nmatches == 0) { - list(list(), "") - } else { - longest <- matches[order(nchar(matches))][1] - while(length(grep(sprintf("^%s", literal2rx(longest)), matches)) < nmatches) { - longest <- substr(longest, 1, nchar(longest)-1) - } - list(as.list(matches), longest) +} + +returnMatches <- function(matches) { + nmatches <- length(matches) + if(nmatches == 0) { + list(list(), "") + } else { + longest <- matches[order(nchar(matches))][1] + while(length(grep(sprintf("^%s", literal2rx(longest)), matches)) < nmatches) { + longest <- substr(longest, 1, nchar(longest)-1) } + list(as.list(matches), longest) } - literal2rx <- function(string) { - ## list of ERE metacharacters from ?regexp - gsub("([.\\|()[{^$*+?])", "\\\\\\1", string) - } +} + +literal2rx <- function(string) { + ## list of ERE metacharacters from ?regexp + gsub("([.\\|()[{^$*+?])", "\\\\\\1", string) +} + +`swank:simple-completions` <- function(slimeConnection, sldbState, prefix, package) { matches <- apropos(sprintf("^%s", literal2rx(prefix)), ignore.case=FALSE) nmatches <- length(matches) if((nmatches == 0) && ((dollar <- regexpr("$", prefix, fixed=TRUE)) > -1)) { - symbolFieldsCompletion(globalenv(), prefix) + symbolFieldsCompletion(globalenv(), prefix, prefix) } else { returnMatches(matches) }