[Sciviews-commits] r173 - in pkg/svMisc: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Aug 10 18:59:21 CEST 2009


Author: phgrosjean
Date: 2009-08-10 18:59:20 +0200 (Mon, 10 Aug 2009)
New Revision: 173

Removed:
   pkg/svMisc/R/Complete2.R
   pkg/svMisc/man/Complete2.Rd
Modified:
   pkg/svMisc/DESCRIPTION
   pkg/svMisc/NAMESPACE
   pkg/svMisc/NEWS
   pkg/svMisc/R/Complete.R
   pkg/svMisc/R/CompletePlus.R
   pkg/svMisc/R/descFun.R
   pkg/svMisc/TODO
   pkg/svMisc/man/Complete.Rd
   pkg/svMisc/man/CompletePlus.Rd
Log:
Complete2() merged with Complete() and reworked a bit

Modified: pkg/svMisc/DESCRIPTION
===================================================================
--- pkg/svMisc/DESCRIPTION	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/DESCRIPTION	2009-08-10 16:59:20 UTC (rev 173)
@@ -3,8 +3,8 @@
 Imports: utils, methods
 Depends: R (>= 2.6.0)
 Description: Supporting functions for the GUI API (various utilitary functions)
-Version: 0.9-50
-Date: 2009-07-29
+Version: 0.9-52
+Date: 2009-08-10
 Author: Philippe Grosjean, Romain Francois & Kamil Barton
 Maintainer: Philippe Grosjean <phgrosjean at sciviews.org>
 License: GPL (>= 2)

Modified: pkg/svMisc/NAMESPACE
===================================================================
--- pkg/svMisc/NAMESPACE	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/NAMESPACE	2009-08-10 16:59:20 UTC (rev 173)
@@ -14,7 +14,6 @@
 		clipsource,
 		compareRVersion,
 		Complete,
-		Complete2,
 		CompletePlus,
 		def,
 		descArgs,

Modified: pkg/svMisc/NEWS
===================================================================
--- pkg/svMisc/NEWS	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/NEWS	2009-08-10 16:59:20 UTC (rev 173)
@@ -1,13 +1,30 @@
 = svMisc News
 
+== Changes in svMisc 0.9-52
+
+* Complete() now manages cases where code is like "iris[", "iris[[", or where
+  last parsed token is empty (in this case, it returns the list of objects
+  loaded in .GlobalEnv).
+
+
+== Changes in svMisc 0.9-51
+
+* Complete() now includes additions from Complete2() and CompletePlus()
+
+
 == Changes in svMisc 0.9-50
 
-* CompletePlus removes the weird object names ( .__M__, ...) which were 
+* CompletePlus removes the weird object names ( .__M__, ...) which were
   causing trouble
-  
+
 * CompletePlus handles completions like "a[m"
 
 
+== Changes in svMisc 0.9-49
+
+* Complete2() is a temporary new version of Complete()
+
+
 == Changes in svMisc 0.9-48
 
 * Parse() does not detect incomplete R code any more, fixed (PhG)

Modified: pkg/svMisc/R/Complete.R
===================================================================
--- pkg/svMisc/R/Complete.R	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/R/Complete.R	2009-08-10 16:59:20 UTC (rev 173)
@@ -1,27 +1,297 @@
 "Complete" <-
-function (code, givetype = FALSE, sep = "\t")
-{
-	### TODO: implement 'givetype'!
+function (code, print = FALSE, types = c("default", "scintilla"),
+addition = FALSE, skip.used.args = TRUE, sep = "\n", type.sep = "?") {
+	ComplEnv <- utils:::.CompletionEnv
 
-	# Get a completion list, given a part of the code
+	finalize <- function (completions) {
+		if (add.types) {
+			tl <- numeric(length(completions))
+			tl[grep(" = $", completions)] <- 4L
+			tl[grep("::$", completions)] <- 3L
+			tl[grep("<-$", completions)] <- 1L
+			tl[completions %in% .reserved.words] <- 5L
+			i <- !tl
+			tl[i] <- ifelse(sapply(completions[i],
+				function(x) existsFunction(x)), 1L, 2L)
+			tl <- factor(tl, levels = 1:5, labels = types)
+			ret <- data.frame(completion = completions, type = tl)
+		} else {
+			ret <- completions
+		}
+
+		attr(ret, "token") <- token
+		attr(ret, "triggerPos") <- triggerPos
+		attr(ret, "fguess") <- fguess
+		attr(ret, "funargs") <- funargs
+		attr(ret, "isFirstArg") <- isFirstArg
+
+		if (print) {
+			if (add.types)
+				completions <- paste(completions, tl, sep = type.sep)
+			cat(triggerPos, completions, sep = sep)
+			if (sep != "\n") cat("\n")
+			return(invisible(ret))
+		} else {
+			return(ret)
+		}
+	}
+
+	if (is.character(types[1L])) {
+		types <- switch(match.arg(types),
+			default = .default.completion.types,
+			scintilla = .scintilla.completion.types,
+			.default.completion.types)
+	}
+	add.types <- !is.na(types[1L])
+
+	# Default values for completion context
+	token <- ""
+	triggerPos <- 0L
+	fguess <- ""
+	funargs <- list()
+	isFirstArg <- FALSE
+
+	# Is there some code provided?
 	code <- paste(as.character(code), collapse = "\n")
-	if (is.null(code) || length(code) == 0 || code == "") return("")
+	if (is.null(code) || !length(code) || code == "") {
+		# Just return a list of objects in .GlobalEnv
+		return(finalize(ls(envir = .GlobalEnv)))
+	}
 
-	# Use the internal win32consoleCompletion function in utils package
-	res <- utils:::.win32consoleCompletion(code, nchar(code))
+	# If code ends with a single [, then nothing to return
+	if (regexpr("[^[][[]$", code) > 0)
+		return(invisible(""))
 
-	# Is there a single addition?
-	if (res$addition != "") {
-		res <- paste(sep, gsub("=", " = ", res$addition), sep = "")
-	} else if (res$comps != "") { # Is there a list of possible tokens?
-		# Replace space by fieldsep
-		if (sep != " ") res <- gsub(" ", sep, res$comps)
-		res <- gsub("=", " = ", res)
-	} else return("")
-	# Do we have to return something to complete?
-	if (regexpr(paste("\\", sep, sep = ""), res) == -1) {
-		return("")
+	# If code ends with a double [[, then, substitute $ instead and indicate
+	# to quote returned arguments (otherwise, [[ is not correctly handled)!
+	if (regexpr("[[][[]$", code) > 0) {
+		code <- sub("[[][[]$", "$", code)
+		dblBrackets <- TRUE
+	} else dblBrackets <- FALSE
+
+	# Save funarg.suffix and use " = " temporarily
+	opts <- ComplEnv$options
+	funarg.suffix <- opts$funarg.suffix
+	on.exit({
+		opts$funarg.suffix <- funarg.suffix
+		ComplEnv$options <- opts
+	})
+	opts$funarg.suffix <- " = "
+	ComplEnv$options <- opts
+
+	utils:::.assignLinebuffer(code)
+	pos <- nchar(code, type = "chars")
+	utils:::.assignEnd(pos)
+	utils:::.guessTokenFromLine()
+	#utils:::.completeToken()
+	.completeTokenExt()
+
+	completions <- utils:::.retrieveCompletions()
+
+	triggerPos <- pos - ComplEnv[["start"]]
+	token <- ComplEnv[["token"]]
+
+	# If token is empty, we complete by using objects in .GlobalEnv by default
+	if (!length(completions) && token == "") {
+		triggerPos <- nchar(code, type = "chars")
+		return(finalize(ls(envir = .GlobalEnv)))
+	}
+
+    # From CompletePlus() for a similar behaviour
+	# For tokens like "a[m", the actual token should be "m"
+    # completions are modified accordingly
+    rx <- regexpr("[[]+", ComplEnv$token)
+    if (rx > 0) {
+    	# then we need to trim out whatever is before the [ in the completion
+    	# and the token
+    	start <- rx + attr(rx, "match.length")
+    	ComplEnv$token <- substring(ComplEnv$token, start)
+    	completions <- substring(completions, start)
+    }
+	if (!length(completions)) return(invisible(""))
+
+	# remove weird object names (useful when the token starts with ".")
+    completions <- completions[!grepl("^[.]__[[:alpha:]]__", completions)]
+    if (!length(completions)) return(invisible(""))
+
+	fguess <- ComplEnv$fguess
+
+	if (skip.used.args && length(fguess) && nchar(fguess))
+		completions <- completions[!(completions %in% ComplEnv$funargs)]
+	if (!length(completions)) return(invisible(""))
+
+	i <- -grep("<-.+$", completions)
+	if (length(i) > 0)
+		completions <- completions[-grep("<-.+$", completions)]
+
+	if (addition && triggerPos > 0L)
+		completions <- substring(completions, triggerPos + 1)
+
+	if (dblBrackets) {
+		# Substitute var$name by var[["name"
+		completions <- sub("[$](.+)$", '[["\\1"', completions)
+		token <- sub("[$]$", "[[", token)
+		triggerPos <- triggerPos + 1
+	}
+	fguess <- ComplEnv$fguess
+	funargs <- ComplEnv$funargs
+	isFirstArg <- ComplEnv$isFirstArg
+	return(finalize(completions))
+}
+
+.reserved.words <- c("if", "else", "repeat", "while", "function", "for", "in",
+					  "next", "break", "TRUE", "FALSE", "NULL", "Inf", "NaN",
+					  "NA", "NA_integer_", "NA_real_", "NA_complex_",
+					  "NA_character_")
+
+.default.completion.types <- list(fun = "function",
+								  var = "variable",
+								  env = "environment",
+								  args = "arg",
+								  keyword = "keyword")
+
+.scintilla.completion.types <- list(fun = "1",
+									var = "3",
+									env = "8",
+									args = "11",
+									keyword = "13")
+
+# modified utils:::inFunction()
+# The only difference is that it also gets current arguments list (if applicable).
+# They are assigned to utils:::.CompletionEnv$funargs
+.inFunctionExt <-
+function (line = utils:::.CompletionEnv[["linebuffer"]],
+cursor = utils:::.CompletionEnv[["start"]])
+{
+	parens <- sapply(c("(", ")"), function(s)
+		gregexpr(s, substr(line, 1L, cursor), fixed = TRUE)[[1L]],
+			simplify = FALSE)
+	parens <- lapply(parens, function(x) x[x > 0])
+	temp <- data.frame(i = c(parens[["("]], parens[[")"]]),
+		c = rep(c(1, -1), sapply(parens, length)))
+	if (nrow(temp) == 0)
+		return(character(0L))
+	temp <- temp[order(-temp$i), , drop = FALSE]
+	wp <- which(cumsum(temp$c) > 0)
+	if (length(wp)) {
+		index <- temp$i[wp[1L]]
+		prefix <- substr(line, 1L, index - 1L)
+		suffix <- substr(line, index + 1L, cursor + 1L)
+		if ((length(grep("=", suffix, fixed = TRUE)) == 0L) &&
+			(length(grep(",", suffix, fixed = TRUE)) == 0L))
+			utils:::setIsFirstArg(v = TRUE)
+		if ((length(grep("=", suffix, fixed = TRUE))) && (length(grep(",",
+			substr(suffix, tail(gregexpr("=", suffix, fixed = TRUE)[[1L]],
+			1L), 1000000L), fixed = TRUE)) == 0L)) {
+			return(character(0L))
+		} else {
+
+			# This is the code added to utils:::inFunction()
+			wp2 <- rev(cumsum(temp$c[-(wp[1L]:nrow(temp))]))
+			# TODO: simplify this:
+			if (length(wp2)) {
+				funargs <- strsplit(sub("^\\s+", "", suffix, perl = TRUE),
+					"\\s*[\\(\\)][\\s,]*", perl = TRUE)[[1]]
+				funargs <- paste(funargs[wp2 == 0], collapse = ",")
+			} else {
+				funargs <- suffix
+			}
+			funargs <- strsplit(funargs, " *, *")[[1]]
+			funargs <- unname(sapply(funargs, sub, pattern = " *=.*$",
+				replacement = utils:::.CompletionEnv$options$funarg.suffix))
+			assign("funargs", funargs, utils:::.CompletionEnv)
+			# ... addition ends here
+
+			possible <- suppressWarnings(strsplit(prefix, utils:::breakRE,
+				perl = TRUE))[[1L]]
+			possible <- possible[possible != ""]
+			if (length(possible)) {
+				return(tail(possible, 1))
+			} else {
+				return(character(0L))
+			}
+		}
 	} else {
-		return(res)
+		return(character(0L))
 	}
 }
+
+# modified utils:::.completeToken()
+# main difference is that calls .inFunctionExt instead of utils:::inFunction.
+.completeTokenExt <- function () {
+	ComplEnv <- utils:::.CompletionEnv
+	text <- ComplEnv$token
+	linebuffer <- ComplEnv$linebuffer
+	st <- ComplEnv$start
+
+	if (utils:::isInsideQuotes()) {
+		probablyNotFilename <- (st > 2L &&
+			(substr(linebuffer, st - 1L, st - 1L) %in% c("[", ":", "$")))
+		if (ComplEnv$settings[["files"]]) {
+			if (probablyNotFilename) {
+				ComplEnv[["comps"]] <- character(0L)
+			} else {
+				ComplEnv[["comps"]] <- utils:::fileCompletions(text)
+			}
+			utils:::.setFileComp(FALSE)
+		} else {
+			ComplEnv[["comps"]] <- character(0L)
+			utils:::.setFileComp(TRUE)
+		}
+	} else {
+
+		#Completion does not a good job when there are quoted strings,
+		# e.g for linebuffer = "Complete2("anova(", )" would give arguments for anova
+		# rather than for Complete2.
+		# Code below replaces quoted strings with sequences of "_" of the same length.
+		# This is a temporary solution though, there should be a better way...
+		mt <- gregexpr('(?<!\\\\)(["\']).*?((?<!\\\\)\\1|$)', linebuffer,
+			perl = TRUE)[[1]]
+		if (mt[1L] != -1) {
+			ml <- attr(mt, "match.length")
+			y <- sapply(lapply(ml, rep, x = "a"), paste, collapse = "")
+			for (i in seq_along(mt))
+				substr(linebuffer, mt[i], mt[i] + ml[i]) <- y[i]
+		}
+		# ... additions until here
+
+		utils:::.setFileComp(FALSE)
+		utils:::setIsFirstArg(FALSE)
+		guessedFunction <- ""
+		if (ComplEnv$settings[["args"]]) {
+			# Call of .inFunctionExt() instead of utils:::inFunction()
+			guessedFunction <- .inFunctionExt(linebuffer, st)
+		} else {
+			guessedFunction <- ""
+		}
+
+		assign("fguess", guessedFunction, ComplEnv)
+		fargComps <- utils:::functionArgs(guessedFunction, text)
+
+		if (utils:::getIsFirstArg() && length(guessedFunction) &&
+			guessedFunction %in% c("library", "require", "data")) {
+			assign("comps", fargComps, ComplEnv)
+			return()
+		}
+		lastArithOp <- tail(gregexpr("[\"'^/*+-]", text)[[1L]], 1)
+		if (haveArithOp <- (lastArithOp > 0)) {
+			prefix <- substr(text, 1L, lastArithOp)
+			text <- substr(text, lastArithOp + 1L, 1000000L)
+		}
+		spl <- utils:::specialOpLocs(text)
+		if (length(spl)) {
+			comps <- utils:::specialCompletions(text, spl)
+		} else {
+			appendFunctionSuffix <- !any(guessedFunction %in%
+				c("help", "args", "formals", "example", "do.call",
+				"environment", "page", "apply", "sapply", "lapply",
+				"tapply", "mapply", "methods", "fix", "edit"))
+			comps <- utils:::normalCompletions(text,
+				check.mode = appendFunctionSuffix)
+		}
+		if (haveArithOp && length(comps))
+			comps <- paste(prefix, comps, sep = "")
+		comps <- c(comps, fargComps)
+		assign("comps", comps,  ComplEnv)
+	}
+}

Deleted: pkg/svMisc/R/Complete2.R
===================================================================
--- pkg/svMisc/R/Complete2.R	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/R/Complete2.R	2009-08-10 16:59:20 UTC (rev 173)
@@ -1,243 +0,0 @@
-
-.reserved.words <- c("if", "else", "repeat", "while", "function", "for", "in",
-					  "next", "break", "TRUE", "FALSE", "NULL", "Inf", "NaN",
-					  "NA", "NA_integer_", "NA_real_", "NA_complex_",
-					  "NA_character_")
-
-.scintilla.completion.types <- list(fun = "1",
-									var = "3",
-									env = "8",
-									args = "11",
-									keyword = "13")
-
-.default.completion.types <- list(fun = "function",
-								  var = "variable",
-								  env = "environment",
-								  args = "arg",
-								  keyword = "keyword")
-
-
-# modified utils:::.inFunction()
-# The only difference is that it also gets current arguments list (if applicable).
-# They are assigned to utils:::.CompletionEnv$funargs
-.inFunctionExt <- function (
-						   line = utils:::.CompletionEnv[["linebuffer"]],
-						   cursor = utils:::.CompletionEnv[["start"]]
-						   )
-{
-    parens <- sapply(c("(", ")"), function(s) gregexpr(s, substr(line,
-        1L, cursor), fixed = TRUE)[[1L]], simplify = FALSE)
-    parens <- lapply(parens, function(x) x[x > 0])
-    temp <- data.frame(i = c(parens[["("]], parens[[")"]]), c = rep(c(1,
-        -1), sapply(parens, length)))
-    if (nrow(temp) == 0)
-        return(character(0L))
-    temp <- temp[order(-temp$i), , drop = FALSE]
-    wp <- which(cumsum(temp$c) > 0)
-    if (length(wp)) {
-        index <- temp$i[wp[1L]]
-        prefix <- substr(line, 1L, index - 1L)
-        suffix <- substr(line, index + 1L, cursor + 1L)
-        if ((length(grep("=", suffix, fixed = TRUE)) == 0L) &&
-            (length(grep(",", suffix, fixed = TRUE)) == 0L))
-            utils:::setIsFirstArg(v = TRUE)
-        if ((length(grep("=", suffix, fixed = TRUE))) && (length(grep(",",
-            substr(suffix, tail(gregexpr("=", suffix, fixed = TRUE)[[1L]],
-                1L), 1000000L), fixed = TRUE)) == 0L)) {
-            return(character(0L))
-        } else {
-			wp2 <- rev(cumsum(temp$c[-(wp[1L]:nrow(temp))]))
-			# TODO: simplify this:
-			if (length(wp2)) {
-				funargs <- strsplit(sub("^\\s+", "", suffix, perl=T),
-									"\\s*[\\(\\)][\\s,]*", perl = T)[[1]]
-				funargs <- paste(funargs[wp2 == 0], collapse=",")
-			} else {
-				funargs <- suffix
-			}
-			funargs <- strsplit(funargs, " *, *")[[1]]
-
-			funargs <- unname(sapply(funargs,
-									 sub, pattern = " *=.*$",
-									 replacement = utils:::.CompletionEnv$
-									 options$funarg.suffix))
-
-			assign("funargs", funargs, utils:::.CompletionEnv)
-
-            possible <- suppressWarnings(strsplit(prefix, utils:::breakRE,
-                perl = TRUE))[[1L]]
-            possible <- possible[possible != ""]
-            if (length(possible))
-                return(tail(possible, 1))
-            else return(character(0L))
-        }
-    }
-    else {
-        return(character(0L))
-    }
-}
-
-
-
-# modified utils:::.completeToken()
-# main difference is that calls .inFunctionExt instead of utils:::inFunction.
-.completeTokenExt <- function () {
-
-	ComplEnv <- utils:::.CompletionEnv
-
-	text <- ComplEnv$token
-	linebuffer <- ComplEnv$linebuffer
-	st <- ComplEnv$start
-
-    if (utils:::isInsideQuotes()) {
-
-        probablyNotFilename <- (st > 2L && (substr(linebuffer,
-            st - 1L, st - 1L) %in% c("[", ":", "$")))
-        if (ComplEnv$settings[["files"]]) {
-            ComplEnv[["comps"]] <- if (probablyNotFilename)
-                character(0L)
-            else utils:::fileCompletions(text)
-            utils:::.setFileComp(FALSE)
-        }
-        else {
-            ComplEnv[["comps"]] <- character(0L)
-            utils:::.setFileComp(TRUE)
-        }
-    }
-    else {
-
-		#Completion does not do good job when there are quoted strings,
-		# e.g for linebuffer = "Complete2("anova(", )" would give arguments for anova
-		# rather than for Complete2.
-		# Code below replaces quoted strings with sequences of "_" of the same length.
-		# This is a temporary solution though, there should be a better way...
-		mt <- gregexpr('(?<!\\\\)(["\']).*?((?<!\\\\)\\1|$)', linebuffer, perl = T)[[1]]
-		if (mt[1L] != -1) {
-			ml <- attr(mt,"match.length")
-			y <- sapply(lapply(ml, rep, x = "a"), paste, collapse="")
-			for (i in seq_along(mt))
-				substr(linebuffer, mt[i], mt[i] + ml[i]) <- y[i]
-		}
-
-        utils:::.setFileComp(FALSE)
-        utils:::setIsFirstArg(FALSE)
-        guessedFunction <- if (ComplEnv$settings[["args"]])
-            .inFunctionExt(linebuffer, st)
-        else ""
-
-		assign("fguess", guessedFunction, ComplEnv)
-        fargComps <- utils:::functionArgs(guessedFunction, text)
-
-        if (utils:::getIsFirstArg() && length(guessedFunction) && guessedFunction %in%
-            c("library", "require", "data")) {
-			assign("comps", fargComps, ComplEnv)
-            return()
-        }
-        lastArithOp <- tail(gregexpr("[\"'^/*+-]", text)[[1L]],
-            1)
-        if (haveArithOp <- (lastArithOp > 0)) {
-            prefix <- substr(text, 1L, lastArithOp)
-            text <- substr(text, lastArithOp + 1L, 1000000L)
-        }
-        spl <- utils:::specialOpLocs(text)
-        comps <- if (length(spl))
-            utils:::specialCompletions(text, spl)
-        else {
-            appendFunctionSuffix <- !any(guessedFunction %in%
-                c("help", "args", "formals", "example", "do.call",
-                  "environment", "page", "apply", "sapply", "lapply",
-                  "tapply", "mapply", "methods", "fix", "edit"))
-            utils:::normalCompletions(text, check.mode = appendFunctionSuffix)
-        }
-        if (haveArithOp && length(comps)) {
-            comps <- paste(prefix, comps, sep = "")
-        }
-        comps <- c(comps, fargComps)
-        assign("comps", comps,  ComplEnv)
-    }
-}
-
-Complete2 <- function(code, print = FALSE, types = c("default", "scintilla"),
-					 addition = FALSE, skip.used.args = TRUE,
-					 sep = "\n", type.sep = "?") {
-
-	if (is.character(types[1L])) {
-		types <- switch(match.arg(types), default = .default.completion.types,
-				  scintilla = .scintilla.completion.types,
-				  .default.completion.types)
-	}
-
-
-	add.types <- !is.na(types[1L])
-
-
-	code <- paste(as.character(code), collapse = "\n")
-    if (is.null(code) || !length(code) || code == "")
-        return(invisible(""))
-
-	pos <- nchar(code, type = "chars")
-	utils:::.assignLinebuffer(code)
-	utils:::.assignEnd(pos)
-	utils:::.guessTokenFromLine()
-	#utils:::.completeToken()
-	.completeTokenExt()
-
-	ComplEnv <- utils:::.CompletionEnv
-	completions <-	utils:::.retrieveCompletions()
-
-	fguess <- ComplEnv$fguess
-
-	#print(c(skip.used.args, length(fguess), nchar(fguess)))
-
-	if (skip.used.args && length(fguess) && nchar(fguess)) {
-		completions <- completions [!(completions %in% ComplEnv$funargs)]
-	}
-
-	triggerPos <- pos - ComplEnv[["start"]]
-	token <- ComplEnv[["token"]]
-
-	if (!length(completions))
-		return(invisible(""))
-
-	i <- -grep("<-.+$", completions)
-	if (length(i) > 0)	completions <- completions[-grep("<-.+$", completions)]
-
-	if (add.types) {
-		tl <-  numeric(length(completions))
-		tl[grep("=$", completions)] <- 4L
-		tl[grep("::$", completions)] <- 3L
-		tl[grep("<-$", completions)] <- 1L
-		tl[completions %in% .reserved.words] <- 5L
-		i <- !tl
-		tl[i] <- ifelse(sapply(completions[i],
-							   function(x) existsFunction(x)), 1L, 2L)
-		tl <- factor(tl, levels= 1:5, labels = types)
-	}
-
-	if (addition && triggerPos > 0L)
-		completions <- substring(completions, triggerPos + 1)
-
-
-
-
-	if (add.types)
-		ret <- data.frame(completion = completions, type = tl)
-	else
-		ret <- completions
-
-	attr(ret, "token") <- token
-	attr(ret, "triggerPos") <- triggerPos
-	attr(ret, "fguess") <- ComplEnv$fguess
-	attr(ret, "funargs") <- ComplEnv$funargs
-	attr(ret, "isFirstArg") <- ComplEnv$isFirstArg
-
-	if (print) {
-		cat(triggerPos,
-			if (add.types) paste(completions, tl, sep=type.sep) else completions,
-			sep=sep)
-		if (sep != "\n") cat("\n")
-
-		invisible(ret)
-	} else
-		return(ret)
-}

Modified: pkg/svMisc/R/CompletePlus.R
===================================================================
--- pkg/svMisc/R/CompletePlus.R	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/R/CompletePlus.R	2009-08-10 16:59:20 UTC (rev 173)
@@ -13,19 +13,19 @@
     utils:::.completeToken()
     comps <- utils:::.retrieveCompletions()
     if (!length(comps)) return(invisible(NULL))
-    
-    # For tokens like "a[m", the actual yoken should be "m"
+
+    # For tokens like "a[m", the actual token should be "m"
     # completions are modified accordingly
-    rx <- regexpr( "[[]+", token )
-    if( rx > 0 ){
+    rx <- regexpr("[[]+", token)
+    if (rx > 0) {
     	# then we need to trim out whatever is before the [ in the completion
     	# and the token
-    	start <- rx + attr( rx, "match.length" )
-    	token <- substring( token, start )
-    	comps <- substring( comps, start )
+    	start <- rx + attr(rx, "match.length")
+    	token <- substring(token, start)
+    	comps <- substring(comps, start)
     }
-    
-    # remove weird object names ( useful when the token starts with "." ) 
+
+    # remove weird object names (useful when the token starts with ".")
     comps <- comps[ !grepl( "^[.]__[[:alpha:]]__", comps ) ]
     if (!length(comps))
 		return(invisible(NULL))
@@ -120,7 +120,7 @@
 
 	# Make sure that arguments are witten 'arg = ', and not 'arg='
 	out[, 1] <- sub("=$", " = ", out[, 1])
-	
+
 	attr( out, "token" ) <- token
 
 	if (simplify) {

Modified: pkg/svMisc/R/descFun.R
===================================================================
--- pkg/svMisc/R/descFun.R	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/R/descFun.R	2009-08-10 16:59:20 UTC (rev 173)
@@ -1,4 +1,4 @@
-# These are all hidden functions for the moment!
+# These are all hidden functions for the moment, except desArgs() and descFun()!
 "descFun" <-
 function (fun, package, lib.loc = NULL)
 {

Modified: pkg/svMisc/TODO
===================================================================
--- pkg/svMisc/TODO	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/TODO	2009-08-10 16:59:20 UTC (rev 173)
@@ -1,9 +1,5 @@
 = svMisc To Do list
 
-* CompletePlus() accelerate treatment (return completion and calculate desc
-later? limit the list to n entries?). Also, make sure that options for
-completion are correct for the given types
-
 * The svMisc-package.Rd man page
 
 * Write the code in objList() to list content inside objects

Modified: pkg/svMisc/man/Complete.Rd
===================================================================
--- pkg/svMisc/man/Complete.Rd	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/man/Complete.Rd	2009-08-10 16:59:20 UTC (rev 173)
@@ -3,70 +3,93 @@
 
 \title{ Get a completion list for a R code fragment }
 \description{
-  A list with matching items is returned in a string.
+  Returns names of objects/arguments/namespaces matching a code fragment.
 }
 \usage{
-Complete(code, givetype = FALSE, sep = "\t")
+Complete(code, print = FALSE, types = c("default", "scintilla"),
+    addition = FALSE, skip.used.args = TRUE, sep = "\n", type.sep = "?")
 }
 \arguments{
-  \item{code}{ A fraction of R code needing completion }
-  \item{givetype}{ Do we append the type of each entry to the list?
-    Not supported in this version }
-  \item{sep}{ The separator to use between returned items }
+  \item{code}{ A partial R code to be completed. }
+  \item{print}{ logical, print result and return invisibly. See details. }
+  \item{types}{ a named list giving names of types. Set to \code{NA} to give
+    only names. See details. }
+  \item{addition}{ should only addition string be returned? }
+  \item{skip.used.args}{ logical, in case if completion is within function
+    arguments, should the already used named arguments be omitted? }
+  \item{sep}{ The separator to use between returned items. }
+  \item{type.sep}{ Character string to separate types from names. }
 }
 
 \value{
-  A string with the completion list (items separated by 'sep'), or
-  an unique string completing unambiguously the current code, starting with
-  'sep'
+If \code{types} == \code{NA}, a character vector giving the completions,
+otherwise a data frame with two columns: "completion", and "type" (factor with
+levels given by \code{types} argument).\cr
+Attributes:\cr
+\code{attr(,"token")} - a completed token.\cr
+\code{attr(,"triggerPos")} - number of already typed characters.\cr
+\code{attr(,"fguess")} - name of guessed function.\cr
+\code{attr(,"isFirstArg")} - is this a first argument?
 }
 
 \details{
     The completion list is context-dependent, and it is calculated as if the
 	code was entered at the command line.
-    
-    If the code ends with \code{$}, then the function look for
-	items in a list or data.frame whose name is the last idfentifier.
-    
+
+    If the code ends with \code{$} or \code{[[}, then the function look for
+	items in a list or data.frame whose name is the last identifier.
+
     If the code ends with \code{@}, then the function look for slots of the
     corresponding S4 object.
-	
+
 	If the code ends with \code{::}, then it looks for objects in a namespace.
-    
+
     If the code ends with a partial identifier name, the function returns all
     visible matching keywords.
-    
+
+	If the code is empty or parses into an empty last token, the list of objects
+	currently in the global environment is returned. Take care: depending on the
+	context, this could be incorrect (but it should work for code entered or
+	sourced at the command line).
+
     There are other situations where the completion can be calculated, see
 	the help of \code{rc.settings()}.
-}
 
-\note{
-  This function uses \code{utils:::.win32consoleCompletion()} as completion
-  engine, then, it makes the result compatible with old version of
-  \code{Complete()}. 
+	If \code{print} == \code{TRUE}, results are returned invisibly, and printed
+	in a form: triggerPos[newline]completions separated by \code{sep}.\cr
+
+    If \code{types} are supplied, a completion will consist of name and type,
+	separated by \code{type.sep}. \code{types} may me a vector of length 5,
+	giving the type codes for "function", "variable", "environment", "argument"
+	and "keyword". If \code{types == "default"}, above type names are given;
+	\code{types == "scintilla"} will give numeric codes that can be used
+	with "scintilla.autoCShow" function (SciViews-K Komodo Edit plugin).
 }
 
-\author{ Philippe Grosjean <phgrosjean at sciviews.org> }
+\author{ Philippe Grosjean <phgrosjean at sciviews.org> & Kamil Barton }
 
-\seealso{ \code{\link{CallTip}}, \code{\link[utils]{rc.settings()}} }
+\seealso{ \code{\link{CompletePlus}}, \code{\link{CallTip}},
+  \code{\link[utils]{rc.settings()}} }
 \examples{
     ## a data.frame
     data(iris)
 	Complete("item <- iris$")
-	Complete("item <- iris[[", TRUE)
-	
+	Complete("item <- iris[[")
+
 	## An S4 object
     setClass("track", representation(x = "numeric", y = "numeric"))
-    t1 <- new("track", x=1:20, y=(1:20)^2)
-    Complete("item2 <- t1@", TRUE)
-    
+    t1 <- new("track", x = 1:20, y = (1:20)^2)
+    Complete("item2 <- t1@")
+
     ## A namespace
 	Complete("utils::")
-	
+
 	## A partial identifier
-    Complete("item3 <- va", TRUE)
-    
+    Complete("item3 <- va")
+
     ## Otherwise, a list with the content of .GlobalEnv
     Complete("item4 <- ")
+
+	## TODO: directory ad filename completion!
 }
 \keyword{ utilities }

Deleted: pkg/svMisc/man/Complete2.Rd
===================================================================
--- pkg/svMisc/man/Complete2.Rd	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/man/Complete2.Rd	2009-08-10 16:59:20 UTC (rev 173)
@@ -1,53 +0,0 @@
-\name{Complete2}
-\alias{Complete2}
-
-\title{ Get a completion list for a R code fragment }
-\description{
-  Returns names of objects/arguments/namespaces matching a code fragment.
-}
-\usage{
-
-Complete2(code, print = FALSE, types = c("default", "scintilla"), addition =
-FALSE, skip.used.args = TRUE, sep = "\n", type.sep = "?")
-
-}
-\arguments{
-  \item{code}{ A partial R code to be completed. }
-  \item{print}{ logical, print result and return invisibly. See details. }
-  \item{types}{ a named list giving names of types. Set to \code{NA} to give only names. See details. }
-  \item{addition}{ should only addition string be returned? }
-  \item{skip.used.args}{ logical, in case if completion is within function arguments, should the already used named arguments be omitted? }
-  \item{sep}{ The separator to use between returned items. }
-  \item{type.sep}{ Character string to separate types from name. }
-}
-
-\value{
-If \code{types} == \code{NA}, a character vector giving the completions,
-otherwise a data frame with two columns: "completion", and "type" (factor with
-levels given by \code{types} argument).\cr
-Attributes:\cr
-\code{attr(,"token")} - a completed token.\cr
-\code{attr(,"triggerPos")} - number of already typed characters.\cr
-\code{attr(,"fguess")} - name of guessed function.\cr
-\code{attr(,"isFirstArg")} - is this a first argument?
-
-}
-
-\details{
-If \code{print} == \code{TRUE}, results are returned invisibly, and printed in a form:
-triggerPos[newline]completions separated by \code{sep}.\cr
-If \code{types} are supplied, a completion will consist of name and type, separated by \code{type.sep}.
-\code{types} may me a vector of length 5, giving the type codes for "function", "variable", "environment", "argument" and "keyword". If \code{types == "default"}, above type names are given, \code{types == "scintilla"} will give numeric codes that can be used "with scintilla.autoCShow" function.
-
-}
-
-
-\author{ Kamil Barton }
-
-\seealso{ \code{\link{Complete}}, \code{\link[utils]{rc.settings()}} }
-\examples{
-
-## TODO
-
-}
-\keyword{ utilities }

Modified: pkg/svMisc/man/CompletePlus.Rd
===================================================================
--- pkg/svMisc/man/CompletePlus.Rd	2009-08-10 12:08:52 UTC (rev 172)
+++ pkg/svMisc/man/CompletePlus.Rd	2009-08-10 16:59:20 UTC (rev 173)
@@ -40,7 +40,9 @@
 \seealso{ \code{\link{Complete}}, \code{\link{descFun}} }
 
 \examples{
+\dontrun{
 CompletePlus("dn")
 CompletePlus("rnorm(10, me")
 }
+}
 \keyword{ utilities }



More information about the Sciviews-commits mailing list