[Sciviews-commits] r443 - in komodo/SciViews-K-dev: . R content/js pylib skin/images

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Feb 24 17:07:19 CET 2012


Author: prezez
Date: 2012-02-24 17:07:18 +0100 (Fri, 24 Feb 2012)
New Revision: 443

Added:
   komodo/SciViews-K-dev/sciviewsk-1.1.4dev-ko.xpi
   komodo/SciViews-K-dev/skin/images/cb_file.png
Removed:
   komodo/SciViews-K-dev/sciviewsk-1.0.6dev-ko.xpi
   komodo/SciViews-K-dev/sciviewsk-1.1.1dev-ko.xpi
   komodo/SciViews-K-dev/sciviewsk-1.1.3dev-ko.xpi
Modified:
   komodo/SciViews-K-dev/
   komodo/SciViews-K-dev/R/
   komodo/SciViews-K-dev/R/.Rprofile
   komodo/SciViews-K-dev/R/completion.R
   komodo/SciViews-K-dev/R/rserver.R
   komodo/SciViews-K-dev/content/js/commands.js
   komodo/SciViews-K-dev/content/js/pref-R.js
   komodo/SciViews-K-dev/install.rdf
   komodo/SciViews-K-dev/pylib/lang_r.py
Log:
sciviewsk-dev: codeintel - filename autocompletion, special completion for 'options(', both variables and argument names are completed in a function call.
R functions are saved into RData at first use. completing functions are simplified (most calculations is done in python).
sv.commands.startR: if no R path is set in the preferences, ask user (restored)
Preferences: "No interpreter" message was not shown (fixed)
R/koCmd: restored R-only version. The one implemented in tcl caused crashes on R's exit with no Komodo available.



Property changes on: komodo/SciViews-K-dev
___________________________________________________________________
Modified: svn:ignore
   - !*
*-dev.*
*.xpi
build
sciviewsk-1.0.8dev-ko
arch
maya-1.1.1-ko
ko-Toolbox-Utilities
rbrowser-new.xul

   + !*
*-dev.*
*.xpi
build
sciviewsk-1.0.8dev-ko
arch
maya-1.1.1-ko
ko-Toolbox-Utilities
rbrowser-new.xul
_dev
r_cpl.py
*.RData



Property changes on: komodo/SciViews-K-dev/R
___________________________________________________________________
Modified: svn:ignore
   - init.R

   + init.R
startup.RData


Modified: komodo/SciViews-K-dev/R/.Rprofile
===================================================================
--- komodo/SciViews-K-dev/R/.Rprofile	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/R/.Rprofile	2012-02-24 16:07:18 UTC (rev 443)
@@ -43,12 +43,12 @@
 		require(utils)
 		`readline` <- function (prompt = "")
 			paste(koCmd(sprintf("ko.dialogs.prompt('%s', '', '', 'R asked a question', 'R-readline')", prompt),
-			timeout=0), collapse=" ")
-		unlockBinding("readline", env=baseenv())
-		bindingIsLocked("readline", env=baseenv())
+			timeout=0), collapse = " ")
+		unlockBinding("readline", env = baseenv())
+		bindingIsLocked("readline", env = baseenv())
 		assign("readline", value=readline, envir = baseenv())
-		utils::assignInNamespace("readline", value=readline, ns="base")
-		lockBinding("readline", env=baseenv())
+		utils::assignInNamespace("readline", value=readline, ns = "base")
+		lockBinding("readline", env = baseenv())
 	})
 
 	options(browser = svBrowser, pager = svPager)
@@ -73,11 +73,28 @@
 	}
 
 	require(utils)
-	require(stats)
+	#require(stats)
 
 	env <- as.environment("komodoConnection")
 	src <- dir(pattern = "\\.R$")
-	lapply(src[src != "init.R"], sys.source, envir = env, keep.source = FALSE)
+	src <- src[src != "init.R"]
+	Rdata <- "startup.RData"
+
+	if(file.exists(Rdata) && {
+		mtime <- file.info(c(Rdata, src))[, "mtime"]
+		all(mtime[-1] <= mtime[1])
+	}) {
+		cat('komodoConnection loaded from "startup.RData" \n')
+		load(Rdata, envir = env)
+		rm(mtime)
+		#sys.source("rserver.R", envir = env)
+	} else{
+		lapply(src, sys.source, envir = env, keep.source = FALSE)
+		suppressWarnings(save(list = ls(env), file = Rdata, envir = env))
+		cat('komodoConnection loaded from source files \n')
+	}
+	init.Rserver()
+	rm(env, Rdata, src)
 	invisible()
 })
 

Modified: komodo/SciViews-K-dev/R/completion.R
===================================================================
--- komodo/SciViews-K-dev/R/completion.R	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/R/completion.R	2012-02-24 16:07:18 UTC (rev 443)
@@ -13,8 +13,8 @@
 #    argument for the generic function.
 
 # 'completeSpecial' prints newline separated completions for some special cases.
-#    currently package, namespace, graphical parameters, and quoted items for 
-#    use with `[` or `[[`
+#    currently package, namespace, graphical parameters, 'options' names
+#    and quoted items for  use with `[` or `[[`
 
 
 # "imports":
@@ -22,7 +22,7 @@
 getS3method <- utils::getS3method
 findGeneric <- utils:::findGeneric
 
-`getFunArgs` <- function(FUNC.NAME, ...) {
+`completeArgs` <- function(FUNC.NAME, ..., field.sep = "\x1e") {
 	rx <- regexpr("^([\\w\\.]+):{2,3}(`|)([\\w\\.\\[\\%]+)\\2$", FUNC.NAME, perl = TRUE)
 	if (rx == 1L) {
 		cs <- attr(rx,"capture.start")
@@ -44,6 +44,7 @@
 	if(is.null(fun) || mode(fun) != "function") return(NULL)
 	if (findGeneric(FUNC.NAME, envir) != "" || is.primitive(fun)) {
 		cl <- sys.call()
+		cl$field.sep <- NULL
 		cls <- NA_character_
 		if(length(cl) > 2L){
 			object <- cl[[3L]]
@@ -78,25 +79,36 @@
 	ret <- unique(c(ret, names(formals(args(fun)))))
 	if (length(ret) > 1L && (FUNC.NAME == "[" || FUNC.NAME == "[["))
 		ret <- ret[-1L]
-	return(ret[ret != "..."])
+
+	cat(paste("argument", field.sep, ret[ret != "..."], " =", sep = ""), sep = "\n")
+	return(invisible(NULL))
 }
 
 # provide special completions
-`completeSpecial` <- function(what, object = NULL) {
+`completeSpecial` <- function(what, x = NULL, field.sep = "\x1e") {
 	res <- switch(what, search = {
+			type <- "namespace"
 			res <- search()
 			res[!(res %in% c(".GlobalEnv", "package:tcltk", "package:utils",
 				"komodoConnection", "package:methods", "TempEnv", "Autoloads",
 				"package:base"))]
 	   }, library = {
-			res <- unique(unlist(lapply(.libPaths(), dir), use.names = FALSE))
+			type <- "module"
+			unique(unlist(lapply(.libPaths(), dir), use.names = FALSE))
 	   }, par = {
-			res <- names(par())
+			type <- "argument"
+			res <- completion("par(", sep = NULL)[]
+			paste(substr(res, 1, nchar(res) - 1), "=")
+			#names(par())
+	   }, options = {
+			type <- "argument"
+			paste(names(options()), "=")
 	   }, "[" = {
-			res <- tryCatch(paste("\"", names(object), "\"", sep = ""),
+			type <- "$variable'"
+			tryCatch(paste("\"", names(x), "\"", sep = ""),
 							error = function(e) "")
 	   }, return(invisible(NULL)))
-	cat(res, sep = '\n')
+	cat(paste(type, res, sep = field.sep), sep = "\n")
 	return(invisible(NULL))
 }
 
@@ -110,42 +122,19 @@
 
 	types <- list(fun = "function", var = "variable",
 		env = "environment", args = "argument", keyword = "keyword")
-	finalize <- function (completions) {
-		## Construct a data frame with completions
-		ret <- data.frame(completion = completions,
-			stringsAsFactors = FALSE)
-			tl <- numeric(length(completions))
-			tl[grep(" = $", completions)] <- 4L
-			tl[grep("::$", completions)] <- 3L
-			tl[grep("<-$", completions)] <- 1L
-			tl[completions %in% .reserved.words] <- 5L
-			tl[!tl] <- ifelse(sapply(completions[!tl],
-				function(x) exists(x, where = .GlobalEnv, mode = "function")),
-							  1L, 2L)
-			tl <- factor(tl, levels = seq_len(5L), labels = types)
-			ret <- cbind(ret, data.frame(type = tl, stringsAsFactors = FALSE))
-			if (is.null(ret$desc)) cat(triggerPos, paste(ret$completion,
-				ret$type, sep = field.sep), sep = sep)
-			else cat(triggerPos, paste(ret$completion, ret$type, ret$desc,
-					ret$context, sep = field.sep), sep = sep)
-			invisible(NULL)
-	}
 
 	## Default values for completion context
 	token <- ""
-	triggerPos <- 0L
-	fguess <- ""
-	funargs <- list()
-	isFirstArg <- FALSE
+	#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) || code == "" ||
 		nchar(code, type = "chars") < min.length) {
-		## Just return a list of objects in .GlobalEnv
-		## TODO: look if we are inside a function and list
-		## local variables (code analysis is required!)
-		return(finalize(ls(envir = .GlobalEnv)))
+		return(invisible(NULL))
 	}
 
 	## If code ends with a single [, then look for names in the object
@@ -164,20 +153,22 @@
 	## Save funarg.suffix and use " = " locally
 	ComplEnv <- utils:::.CompletionEnv
 
+
 	## Calculate completion with standard R completion tools
 	utils:::.assignLinebuffer(code)
 	utils:::.assignEnd(pos)
 	utils:::.guessTokenFromLine()
 	## The standard utils:::.completeToken() is replaced by our own version:
-	.completeTokenExt()
+	#.completeTokenExt()
+	utils:::.completeToken()
 	completions <- utils:::.retrieveCompletions()
-	triggerPos <- pos - ComplEnv[["start"]]
+	#triggerPos <- pos - ComplEnv[["start"]]
 	token <- ComplEnv[["token"]]
 
 	## For tokens like "a[m", the actual token should be "m"
     ## completions are modified accordingly
     rx <- regexpr("[[]+", ComplEnv$token)
-    if (rx > 0) {
+    if (rx > 0L) {
     	## Then we need to trim out whatever is before the [ in the completion
     	## and the token
     	start <- rx + attr(rx, "match.length")
@@ -188,185 +179,55 @@
 
 	## Remove weird object names (useful when the token starts with ".")
     i <- grep("^[.]__[[:alpha:]]__", completions)
-	if (length(i) > 0) completions <- completions[-i]
+	if (length(i) > 0L) completions <- completions[-i]
     if (!length(completions)) return(invisible(""))
 
 	## Eliminate function arguments that are already used
-	fguess <- ComplEnv$fguess
-	if (skip.used.args && length(fguess) && nchar(fguess))
-		completions <- completions[!(completions %in% ComplEnv$funargs)]
-	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(""))
 
 	## Eliminate function names like `names<-`
 	i <- grep("<-.+$", completions)
 	if (length(i) > 0L) completions <- completions[-i]
 
 	## Do we return only additional strings for the completion?
-	if (isTRUE(addition) && triggerPos > 0L)
-		completions <- substring(completions, triggerPos + 1L)
+	#if (isTRUE(addition) && triggerPos > 0L)
+		#completions <- substring(completions, triggerPos + 1L)
 
 	## In case of [[, restore original code
 	if (dblBrackets) {  # Substitute var$name by var[["name"
 		completions <- sub("\\$(.+)$", '[["\\1"', completions)
-		token <- sub("\\$$", "[[", token)
-		triggerPos <- triggerPos + 1L
+		#token <- sub("\\$$", "[[", token)
+		#triggerPos <- triggerPos + 1L
 	}
 
 	## Finalize processing of the completion list
-	funargs <- ComplEnv$funargs
-	isFirstArg <- ComplEnv$isFirstArg
-	return(finalize(completions))
+	#funargs <- ComplEnv$funargs
+	#isFirstArg <- ComplEnv$isFirstArg
+
+	ret <- data.frame(completion = completions, stringsAsFactors = FALSE)
+	tl <- integer(length(completions))
+	tl[grep(" = $", completions)] <- 4L
+	tl[grep("::$", completions)] <- 3L
+	tl[grep("<-$", completions)] <- 1L
+	tl[completions %in% .reserved.words] <- 5L
+	tl[!tl] <- ifelse(sapply(strsplit(completions[!tl], ":::?"), function(x) {
+		if(length(x) == 2) exists(x[2], where = asNamespace(x[1]),
+								  mode = "function")
+		else exists(x, where = .GlobalEnv, mode = "function")	}),  1L, 2L)
+	tl <- factor(tl, levels = seq_len(5L), labels = types)
+
+	if(!is.null(sep)) cat(paste(tl, completions, sep = field.sep), sep = sep)
+	invisible(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_")
 
-## Modified utils:::inFunction()
-## (checked equivalent with R 2.11.1)
-## 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))]))
-			suffix <- sub("^\\s+", "", suffix, perl = TRUE)
-			## TODO: simplify this:
-			if (length(wp2)) {
-				funargs <- strsplit(suffix,	"\\s*[\\(\\)][\\s,]*",
-					perl = TRUE)[[1]]
-				funargs <- paste(funargs[wp2 == 0], collapse = ",")
-			} else {
-				funargs <- suffix
-			}
-			funargs <- strsplit(funargs, "\\s*,\\s*", perl=TRUE)[[1]]
-			funargs <- unname(sapply(funargs, sub, pattern = "\\s*=.*$",
-				replacement = utils:::.CompletionEnv$options$funarg.suffix,
-					perl=TRUE))
-			assign("funargs", funargs, utils:::.CompletionEnv)
-			## TODO: how to take non named arguments into account too?
-			## ... 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(character(0L))
-	}
-}
-
-## Modified utils:::.completeToken()
-## (checked equivalent with R 2.11.1)
-## Main difference is that calls .inFunctionExt instead of utils:::inFunction
-## and it also makes sure completion is for Complete in 'Complete("anova(", )'!
-.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 = "Complete("anova(", )" would give arguments for
-		## anova rather than for Complete.
-		# Replace 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)
-	}
-}
-
 ## Similar to "find" but `what` can be a vector
 ## also, this one only searches in packages (position of the search path
 ## matching '^package:') and only gives one result per what

Modified: komodo/SciViews-K-dev/R/rserver.R
===================================================================
--- komodo/SciViews-K-dev/R/rserver.R	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/R/rserver.R	2012-02-24 16:07:18 UTC (rev 443)
@@ -21,7 +21,9 @@
 # The connection can be permanent.
 # TODO: how to send user interrupt?
 
-options(json.method="R")
+# the (faster?) alternative would be 'json.method' = "tcl", but it is faulty
+# currently.
+options(json.method = "R")
 
 require(tcltk)
 
@@ -38,32 +40,26 @@
 # # then, include it the 'retval' argument
 # tclfun(funTest, retval="retval")
 # .Tcl("funTest 5")
-`tclfun` <- function(f, fname=deparse(substitute(f)),
-	retval=NA, body="%s") {
+`tclfun` <- function(f, fname = deparse(substitute(f)), retval = NA,
+					 body = "%s") {
 	cmd <- .Tcl.callback(f)
 	if (is.character(retval))
-		body <- paste("%s; return $", retval, sep="")
+		body <- paste("%s; return $", retval, sep = "")
 	cmd2 <- sprintf(paste("proc %s {%s} {", body, "}"),
 		fname,
-		paste(names(formals(f)), collapse=" "),
-		gsub("%", "$", cmd, fixed=TRUE))
+		paste(names(formals(f)), collapse = " "),
+		gsub("%", "$", cmd, fixed = TRUE))
 	.Tcl(cmd2)
 	cmd2
 }
 
 #-------------------------------------------------------------------------------
 
-if(!file.exists("rserver.tcl")) stop("Cannot find file 'rserver.tcl'")
-tcl('source', "rserver.tcl")
-tcl('source', "compile_json.tcl")
 
-
-#-------------------------------------------------------------------------------
-
 `TempEnv` <- function() {
 	srch <- search()
     if (is.na(match("TempEnv", srch)))
-        attach(NULL, name="TempEnv", pos = length(srch) - 1L)
+        attach(NULL, name = "TempEnv", pos = length(srch) - 1L)
     as.environment("TempEnv")
 }
 
@@ -77,7 +73,9 @@
 
 
 `getTemp` <- function (x, default = NULL, mode = "any", item = NULL) {
-    if (is.null(item)) Mode <- mode else Mode <- "any"
+    if (is.null(item))
+		Mode <- mode else
+		Mode <- "any"
     if  (exists(x, envir = TempEnv(), mode = Mode, inherits = FALSE)) {
         dat <- get(x, envir = TempEnv(), mode = Mode, inherits = FALSE)
         if (is.null(item)) return(dat) else {
@@ -87,7 +85,7 @@
                 if (mode != "any" && mode(dat) != mode) dat <- default
                 return(dat)
             } else {
-                return(default)
+				return(default)
             }
         }
     } else { # Variable not found, return the default value
@@ -134,6 +132,7 @@
 		if (mode != "h") cat(":> ", c(prevcode, x), "\n") # if mode in [e,u]
 
 		expr <- parseText(c(prevcode, x))
+
 		if(!is.expression(expr) && is.na(expr)) {
 			ret <- ''
 			msg <- 'Want more'
@@ -143,7 +142,7 @@
 				ret <- c('\x03', c(expr), '\x02')
 				msg <- 'Parse error'
 			} else {
-				ret <- captureAll(expr, markStdErr=TRUE)
+				ret <- captureAll(expr, markStdErr = TRUE)
 				#browser()
 				#ret <- eval(call("captureAll", expr, markStdErr=TRUE), envir=.GlobalEnv)
 				msg <- 'Done'
@@ -153,13 +152,13 @@
 			}
 
 			if(exists(prevcodeVarName, .tempEnv, inherits = FALSE))
-				rm(list=prevcodeVarName, envir=.tempEnv)
+				rm(list = prevcodeVarName, envir = .tempEnv)
 		}
 		###########
 
 
 		if (identical(getOption("json.method"), "R")) {
-			tcl("set", "retval", simpsON(list(result=c(ret), message=msg)))
+			tcl("set", "retval", simpsON(list(result = c(ret), message = msg)))
 		} else {
 			tcl(if(length(ret) == 1) "lappend" else "set", "result", ret)
 			.Tcl("set result {}")
@@ -172,18 +171,7 @@
 		tcl("set", "retval", "") # is set in the function scope
 	}
 }
-tclfun(TclReval, "Rserver::Reval", retval="retval")
 
-tcJSON <- function(x, msg = "Done") {
-	.Tcl("set result {}")
-	tcl(if(length(x) == 1) "lappend" else "set", "result", x)
-	.Tcl("set retval [dict create]")
-	.Tcl("dict set retval result $result")
-	tcl("dict", "set", "retval", "message", msg)
-	.Tcl("set retval [compile_json {dict result list message string} $retval]")
-}
-tclfun(tcJSON, "TestJSON", retval="retval")
-
 #-------------------------------------------------------------------------------
 
 `enumServers` <-
@@ -191,14 +179,13 @@
 
 #-------------------------------------------------------------------------------
 
-`TclRprint` <- function(x, debug=0) {
+`TclRprint` <- function(x, debug = 0) {
 	if(debug < getOption('warn')) {
 		Encoding(x) <- "UTF-8"
 		cat(sprintf("[[ %s ]]", x), "\n")
 	}
 	invisible(x)
 }
-tclfun(TclRprint, 'Rserver::Rprint')
 #-------------------------------------------------------------------------------
 
 `startServer` <-
@@ -222,39 +209,100 @@
 	return(num)
 }
 
-`koCmd` <- function (cmd, data = NULL, async = FALSE, host = getOption("ko.host"),
-    port = getOption("ko.port"), timeout = 1, type = c("js",
-        "rjsonp", "output"), pad = NULL, ...) {
+#`koCmd` <- function (cmd, data = NULL, async = FALSE,
+#					 host = getOption("ko.host"),
+#					 port = getOption("ko.port"),
+#					 timeout = 1,	# not really used
+#					 ...) {
+#
+#	if(!is.numeric(port)) stop("Invalid port: ", port)
+#
+#    #type <- match.arg(type)
+#	conn <- .Tcl(sprintf("set ko_Conn1 [::Rclient::Start %d {%s} %d]", port,
+#						 host, timeout))
+#	if(as.character(conn) == "-1") {
+#		warning("timeout")
+#		return(NULL)
+#	}
+#	res <- as.character(.Tcl(sprintf("Rclient::Ask {%s} $ko_Conn1 {%s}", cmd,
+#									 "<<<js>>>")))
+#	.Tcl("close $ko_Conn1")
+#	res
+#}
 
-	if(is.na(port) || !is.numeric(port)) stop("Invalid port: ", port)
+# from svGUI::koCmd (modified)
+`koCmd` <- function (cmd, data = NULL, async = FALSE, # 'data' is not used
+				   host = getOption("ko.host"),
+				   port = getOption("ko.port"),
+				   timeout = 1,
+				   #type = c("js", "rjsonp", "output"), # type is always 'js'
+				   ...)
+{
+	if(!is.numeric(port)) stop("Invalid port: ", port)
 
-    type <- match.arg(type)
-	conn <- .Tcl(sprintf("set ko_Conn1 [::Rclient::Start %d {%s} %d]", port, host, timeout))
-	if(as.character(conn) == "-1") {
-		warning("timeout")
-		return(NULL)
-	}
-	res <- as.character(.Tcl(sprintf("Rclient::Ask {%s} $ko_Conn1 {%s}", cmd, "<<<js>>>")))
-	.Tcl("close $ko_Conn1")
-	res
+
+    cmd <- paste(gsub("\f", "\\f", gsub("\r", "\\r", gsub("\n", "\\n",
+				gsub("\\", "\\\\", cmd, fixed = TRUE), fixed = TRUE),
+				fixed = TRUE), fixed = TRUE),
+				collapse = "\\n")
+
+	#set command [string map [list "\\" {\\} "\n" {\n} "\r" {\r} "\f" {\f}] $command]
+    prevopt <- options(timeout = max(1, floor(timeout)))
+
+	tryCatch(con <- socketConnection(host = host, port = port, blocking = !async),
+		warning = function(e) stop(simpleError(paste("timeout on ", host, ":",
+													 port, sep = ""))))
+
+    writeLines(paste("<<<js>>>", cmd, sep = ""), con)
+    res <- readLines(con)
+    close(con)
+    options(prevopt)
+    return(res)
 }
 
+
 # simple-JSON for lists containing character strings
 simpsON <- function(x) {
-	if(!is.list(x) && length(x) == 1L) return(encodeString(x, quote='"'))
+	if(!is.list(x) && length(x) == 1L) return(encodeString(x, quote = '"'))
 	x <- lapply(x, simpsON)
 	x <- if(is.list(x) || length(x) > 1L) {
 		nms <- names(x)
 		if(is.null(nms))
-			paste('[', paste(x, collapse=','), ']', sep="")
+			paste('[', paste(x, collapse = ','), ']', sep = "")
 		else
-			paste("{", paste(paste(encodeString(make.unique(nms, sep='#'), quote='"'),
-			":", x, sep=""), collapse=","),"}", sep="")
+			paste("{", paste(paste(encodeString(make.unique(nms, sep = '#'),
+				quote = '"'), ":", x, sep = ""), collapse = ","),"}",
+				  sep = "")
 	}
 	x
 }
 
+# tcl-based JSON - not working properly so far.
+tcJSON <- function(x, msg = "Done") {
+	.Tcl("set result {}")
+	tcl(if(length(x) == 1) "lappend" else "set", "result", x)
+	.Tcl("set retval [dict create]")
+	.Tcl("dict set retval result $result")
+	tcl("dict", "set", "retval", "message", msg)
+	.Tcl("set retval [compile_json {dict result list message string} $retval]")
+}
+
+init.Rserver <- function() {
+	if(!file.exists("rserver.tcl")) stop("Cannot find file 'rserver.tcl'")
+	tcl('source', "rserver.tcl")
+	tcl('source', "compile_json.tcl")
+	tclfun(TclReval, "Rserver::Reval", retval = "retval")
+	tclfun(TclRprint, 'Rserver::Rprint')
+	tclfun(tcJSON, "TestJSON", retval = "retval")
+	cat("tcl functions defined")
+
+}
+
 #===============================================================================
+
+#.init.Rserver()
+
+#===============================================================================
 #startServer(11111)
 #listConnections()
 #listServers()

Modified: komodo/SciViews-K-dev/content/js/commands.js
===================================================================
--- komodo/SciViews-K-dev/content/js/commands.js	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/content/js/commands.js	2012-02-24 16:07:18 UTC (rev 443)
@@ -134,7 +134,18 @@
 	this.startR = function () {
 		var svfile = sv.tools.file;
 		var svstr = sv.tools.string;
-
+		
+	
+		if (!sv.pref.getPref("svRCommand")) {
+		    if(ko.dialogs.okCancel(
+			sv.translate("R interpreter is not set in " +
+				     "Preferences. Would you like to do it now?"),
+				"OK", null, "SciViews-K") == "OK") {
+			prefs_doGlobalPrefs("svPrefRItem", true);
+		    }
+		    return;
+		}		
+		
 		var rDir = svfile.path("ProfD", "extensions", "sciviewsk at sciviews.org", "R");
 
 		svfile.write(svfile.path(rDir, "init.R"),
@@ -159,7 +170,7 @@
 				var XEnv = Components.classes["@activestate.com/koEnviron;1"]
 					.createInstance(Components.interfaces.koIEnviron);
 				if (!XEnv.has("DISPLAY"))	env.push("DISPLAY=:0");
-				delete(XEnv);
+				XEnv = null;
 			break;
 			//case "r-terminal":
 				//runIn = "new-console";
@@ -433,7 +444,7 @@
 		function _getSvKeys (data, pattern) {
 			if (!pattern) pattern = "";
 			var keys = data.match(new RegExp("^binding " + pattern +
-			".*$", "gm"));
+				".*$", "gm"));
 			var res = {};
 			for (var j in keys) {
 			try {
@@ -572,16 +583,24 @@
 									//at startup...
 		_this.updateRStatus(sv.rconn.testRAvailability(false));
 		if(sv.r.running) sv.rbrowser.smartRefresh(true);
+		
+		
+		// For completions
+		var cuih = ko.codeintel.CompletionUIHandler;
+		cuih.prototype.types.argument = cuih.prototype.types.interface;
+		cuih.prototype.types.environment = cuih.prototype.types.namespace;
+		cuih.prototype.types.file = "chrome://sciviewsk/skin/images/cb_file.png";
+		//alert(cuih.prototype.types)		
+		
+		
 
 	}, 600);
 	 _setKeybindings();
 
 	sv.rconn.startSocketServer();
 
-	// For completions
-	var cuihproto = ko.codeintel.CompletionUIHandler.prototype;
-	cuihproto.types.argument = cuihproto.types.interface;
-	cuihproto.types.environment = cuihproto.types.namespace;
+
+
 }
 
 // Just in case, run a clean-up before quitting Komodo:

Modified: komodo/SciViews-K-dev/content/js/pref-R.js
===================================================================
--- komodo/SciViews-K-dev/content/js/pref-R.js	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/content/js/pref-R.js	2012-02-24 16:07:18 UTC (rev 443)
@@ -164,7 +164,7 @@
 
 //TODO: check if there is new R version installed and ask whether to switch to it.
 function PrefR_PopulateRInterps() {
-	var prefset = parent.hPrefWindow.prefset;
+    var prefset = parent.hPrefWindow.prefset;
 
     var prefExecutable = prefset.getStringPref('svRDefaultInterpreter');
 
@@ -209,9 +209,9 @@
         menu.appendItem(rs[i], rs[i], null);
     }
 
-    if (rs.length > 0) {
-        document.getElementById("no-avail-interps-message").hidden = true;
-    }
+    document.getElementById("no-avail-interps-message").hidden =
+		!rs.every(function(x) !x);
+
 }
 
 function OnPreferencePageLoading(prefset) {}

Modified: komodo/SciViews-K-dev/install.rdf
===================================================================
--- komodo/SciViews-K-dev/install.rdf	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/install.rdf	2012-02-24 16:07:18 UTC (rev 443)
@@ -4,8 +4,8 @@
     <Description about="urn:mozilla:install-manifest">
 		<em:unpack>true</em:unpack>
         <em:id>sciviewsk at sciviews.org</em:id>
-        <em:name>SciViews-K</em:name>
-        <em:version>1.1.3dev</em:version>
+        <em:name>SciViews-K (dev)</em:name>
+        <em:version>1.1.4dev</em:version>
         <em:description>Edit R code with Komodo</em:description>
         <em:creator>Philippe Grosjean</em:creator>
         <em:contributor>Romain Francois</em:contributor>

Modified: komodo/SciViews-K-dev/pylib/lang_r.py
===================================================================
--- komodo/SciViews-K-dev/pylib/lang_r.py	2012-02-22 12:52:40 UTC (rev 442)
+++ komodo/SciViews-K-dev/pylib/lang_r.py	2012-02-24 16:07:18 UTC (rev 443)
@@ -35,11 +35,11 @@
 R = components.classes["@sciviews.org/svUtils;1"].\
     getService(components.interfaces.svIUtils)
 
-
 #---- Globals
 lang = "R"
 log = logging.getLogger("R-codeintel")
 log.setLevel(logging.WARNING)
+log.setLevel(logging.DEBUG)
 
 # These keywords and builtin functions are copied from "Rlex.udl".
 # Reserved keywords
@@ -119,8 +119,12 @@
     word_styles      = ( variable_style, identifier_style, keyword_style)
 
     type_sep = u'\u001e'
+    pathsep = os.sep + ("" if(os.altsep is None) else os.altsep)
 
 
+    koPrefs = components.classes["@activestate.com/koPrefService;1"] \
+        .getService(components.interfaces.koIPrefService).prefs
+
     #def __init__:
     #    CitadelLangIntel.__init__(self)
     #    ParenStyleCalltipIntelMixin.__init__(self)
@@ -143,14 +147,14 @@
         if pos < 3:
             return None
 
-        accessor = buf.accessor
+        acc = buf.accessor
         last_pos = pos - 1
-        char = accessor.char_at_pos(last_pos)
-        style = accessor.style_at_pos(last_pos)
+        char = acc.char_at_pos(last_pos)
+        style = acc.style_at_pos(last_pos)
         if style == self.operator_style:
             if char in '[(,':
-                infun = self._in_func(pos, accessor)
-                if infun != None:
+                infun = self._in_func(pos, acc)
+                if infun is not None:
                     s, e, funcname, nargs, argnames, firstarg = infun
                     return Trigger(self.lang, TRG_FORM_CPLN, "args", pos, True,
                         funcname = funcname, firstarg = firstarg, nargs = nargs,
@@ -158,13 +162,19 @@
                 return None
 
             elif char in '@$:' and (char != ':' or \
-                accessor.char_at_pos(last_pos - 1) == ':'):
-                vr = self._get_var_back(last_pos, accessor)
+                acc.char_at_pos(last_pos - 1) == ':'):
+                vr = self._get_var_back(last_pos, acc)
                 if vr is not None:
                     return Trigger(self.lang, TRG_FORM_CPLN, "variable", vr[4],
                         True, obj_name = ''.join(vr[2]), cutoff = vr[3])
+        if style == self.string_style and char in self.pathsep:
+            s, e, w = self._get_word_back(last_pos, acc)
+            if len(w) < 2:
+                return None
+            return self._trg_complete_path(w, pos)
         return None
 
+
     def _unquote(self, text, quotes = '`"\''):
         if(text[0] in quotes and text[-1] == text[0]):
             return text[1:len(text) - 1]
@@ -205,7 +215,7 @@
                     s2, e2, funcname, nargs, argnames, firstarg = infun
                     return Trigger(self.lang, TRG_FORM_CPLN, "args", s, False,
                         funcname = funcname, firstarg = firstarg, nargs = nargs,
-                        argnames = argnames)
+                        argnames = argnames, text = w)
                 else:
                     return None
             else:
@@ -215,6 +225,11 @@
                     return Trigger(self.lang, TRG_FORM_CPLN, "variable", vr[4],
                         False, obj_name = ''.join(vr[2]), cutoff = vr[3])
                 return None
+        if style == self.string_style:
+            if len(w) < 2:
+                return None
+            return self._trg_complete_path(w, pos)
+
         if w[-1] in ',(':
             infun = self._in_func(pos, acc)
             if infun is not None:
@@ -254,22 +269,26 @@
             ctlr = UnwrapObject(ctlr)
         pos = trg.pos
         ctlr.start(buf, trg)
+        extra = trg.extra
 
+
         if trg.id == (self.lang, TRG_FORM_CPLN, "args") or \
             trg.id == (self.lang, TRG_FORM_CPLN, "variable-or-args") :
-            completions = self._get_completions_args(trg.extra.get('funcname'),
-                trg.extra.get('firstarg'), trg.extra.get('nargs'),
-                trg.extra.get('argnames'))
+            completions = self._get_completions_args(
+                extra.get('funcname'), extra.get('firstarg'), extra.get('nargs'),
+                extra.get('argnames'), extra.get("text"))
         elif trg.id == (self.lang, TRG_FORM_CPLN, "variable") or \
             trg.id == (self.lang, TRG_FORM_CPLN, "sub-items") :
             completions = self._get_completions_default(
-                trg.extra.get('obj_name'), trg.extra.get('cutoff'))
+                extra.get('obj_name'), extra.get('cutoff'))
+        elif trg.id == (self.lang, TRG_FORM_CPLN, "path"):
+            completions = self._get_completions_path(extra.get('text'))
         else:
             ctlr.error("Unknown trigger type: %r" % (trg, ))
             ctlr.done("error")
             return
 
-        if completions == None:
+        if completions is None:
             ctlr.done("not found")
             return
         if completions[0] == "error":
@@ -297,44 +316,75 @@
     #  ctlr.set_cplns() or ctlr.set_calltips().
     #- Must call ctlr.done(some_reason_string) when done.
 
-    def _get_completions_args(self, fname, frstarg, nargs, argnames):
+    def _trg_complete_path(self, w, pos):
+        path = w.lstrip('\'\"')
+        abspath = os.path.expanduser(path)
+        isabs = os.path.isabs(abspath)
+        #posoff = 1 if all([ path.find(x) == -1 for x in self.pathsep ]) else 1
+        # append /
+        tokenlen = len(os.path.basename(abspath))
+        abspath = os.path.dirname(abspath)
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/sciviews -r 443


More information about the Sciviews-commits mailing list