--- /dev/null
+`swank:completions` <- function(slimeConnection, sldbState, prefix, package) {
+ bits <- strsplit(prefix, "(?=[A-Z._])", perl=TRUE)[[1]];
+ lrx <- literal2rx(bits)
+ ## FIXME: this includes slightly too much .*, because the strsplit
+ ## seems to split before /and/ after the match.
+ rx <- paste(lrx, collapse=".*")
+ matches <- apropos(sprintf("^%s", rx), ignore.case=FALSE)
+ nmatches <- length(matches)
+ if((nmatches == 0) && ((dollar <- regexpr("$", prefix, fixed=TRUE)) > -1)) {
+
+ symbolFieldsCompletion(globalenv(), prefix, prefix)
+ } else {
+ returnMatches(matches)
+ }
+}
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)
}