[Sciviews-commits] r438 - in komodo/SciViews-K-dev: R pylib

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Feb 20 22:46:57 CET 2012


Author: prezez
Date: 2012-02-20 22:46:57 +0100 (Mon, 20 Feb 2012)
New Revision: 438

Modified:
   komodo/SciViews-K-dev/R/completion.R
   komodo/SciViews-K-dev/pylib/lang_r.py
Log:
Code intelligence-2 for R: added implicit (while typing) completions


Modified: komodo/SciViews-K-dev/R/completion.R
===================================================================
--- komodo/SciViews-K-dev/R/completion.R	2012-02-20 18:35:33 UTC (rev 437)
+++ komodo/SciViews-K-dev/R/completion.R	2012-02-20 21:46:57 UTC (rev 438)
@@ -2,15 +2,27 @@
 #    is generic (either S3 or S4), returns only arguments for an appropriate
 #    method and/or default method if not found.
 # Usage:
-#    getFunArgs("anova", fm1) # if fm1 is glm returns argument names for 'anova.glm'
+#    getFunArgs("anova", fm1) # if 'fm1' is of class 'glm', it returns argument
+#    						  #names for 'anova.glm'
+#    getFunArgs("[", object)
+#    getFunArgs("stats::`anova`", fm1) # function names may be backtick quoted,
+#                                      # and have a namespace extractor
+# Note: the function assumes that method is dispatched based on the first
+#    argument which may be incorrect.
+#    TODO: should check whether the name of the argument is also the first
+#    argument for the generic function.
 
+# 'completeSpecial' prints newline separated completions for some special cases.
+#    currently package and namespace list
+
+
 # "imports":
 tail <- utils::tail
 getS3method <- utils::getS3method
 findGeneric <- utils:::findGeneric
 
 `getFunArgs` <- function(FUNC.NAME, ...) {
-	rx <- regexpr("^([\\w\\.]+):{2,3}(`|)([\\w\\.]+)\\2$", FUNC.NAME, perl = TRUE)
+	rx <- regexpr("^([\\w\\.]+):{2,3}(`|)([\\w\\.\\[\\%]+)\\2$", FUNC.NAME, perl = TRUE)
 	if (rx == 1L) {
 		cs <- attr(rx,"capture.start")
 		fn <- substring(FUNC.NAME, cs, cs - 1L + attr(rx,"capture.length"))[c(1,3)]
@@ -21,6 +33,7 @@
 		envir <- .GlobalEnv
 		inherit <- TRUE
 	}
+	#cat(FUNC.NAME, "\n")
 
 	if(exists(FUNC.NAME, envir = envir, mode = "function", inherits = inherit)) {
 		fun <- get(FUNC.NAME, envir = envir, mode = "function", inherits = inherit)
@@ -33,16 +46,18 @@
 		cls <- NA_character_
 		if(length(cl) > 2L){
 			object <- cl[[3L]]
-			if(mode(object) == "call") {
-				if ("~" %in% all.names(object, functions = TRUE, max.names = 4L))
-					cls <- "formula"
-			} else {
-				object <- tryCatch(eval(object), error = function(e) NULL)
-				cls <- class(object)
+			if (!missing(object)) {
+				if(mode(object) == "call") {
+					if ("~" %in% all.names(object, functions = TRUE, max.names = 4L))
+						cls <- "formula"
+				} else {
+					object <- tryCatch(eval(object), error = function(e) NULL)
+					cls <- class(object)
+				}
 			}
 		}
 
-		if(is.na(cls)) {
+		if(is.na(cls[1L])) {
 			ret <- names(formals(getS3method(FUNC.NAME, "default",
 				optional = TRUE)))
 		} else {
@@ -69,8 +84,9 @@
 `completeSpecial` <- function(what) {
 	res <- switch(what, search = {
 			res <- search()
-			res[!(res %in%  c(".GlobalEnv", "package:tcltk", "package:utils", "komodoConnection",
-				"package:methods", "TempEnv", "Autoloads", "package:base"))]
+			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))
 	   }, return(invisible(NULL)))
@@ -81,11 +97,11 @@
 
 
 
-# From svMisc::completion (simpllified)
+# From svMisc::completion (simplified)
 
 `completion` <- function (code, field.sep = "\x1e", sep = "\n",
-						  pos = nchar(code), min.length = 2,
-						  addition = FALSE, max.fun = 100,
+						  pos = nchar(code), min.length = 2L,
+						  addition = FALSE, max.fun = 100L,
 						  skip.used.args = FALSE) {
 
 	types <- list(fun = "function", var = "variable",
@@ -129,14 +145,14 @@
 	}
 
 	## If code ends with a single [, then look for names in the object
-	if (regexpr("[^[][[]$", code) > 0) {
+	if (regexpr("[^[][[]$", code) > 0L) {
 		## TODO: look for object names... currently, return nothing
 		return(invisible(""))
 	}
 
 	## If code ends with a double [[, then, substitute $ instead and indicate
 	## to quote returned arguments (otherwise, [[ is not correctly handled)!
-	if (regexpr("[[][[]$", code) > 0) {
+	if (regexpr("[[][[]$", code) > 0L) {
 		code <- sub("[[][[]$", "$", code)
 		dblBrackets <- TRUE
 	} else dblBrackets <- FALSE

Modified: komodo/SciViews-K-dev/pylib/lang_r.py
===================================================================
--- komodo/SciViews-K-dev/pylib/lang_r.py	2012-02-20 18:35:33 UTC (rev 437)
+++ komodo/SciViews-K-dev/pylib/lang_r.py	2012-02-20 21:46:57 UTC (rev 438)
@@ -5,7 +5,7 @@
 register() function called to register this language with the system. All
 Code Intelligence for this language is controlled through this module.
 """
-import os, sys, re
+import os, sys
 import logging
 import operator
 
@@ -53,6 +53,8 @@
 class RLexer(UDLLexer):
     lang = lang
 
+# TODO: how to update keyword lists dynamically?
+
     #def __init__(self):
     #self._properties = SilverCity.PropertySet()
     #self._keyword_lists = [
@@ -82,9 +84,6 @@
 ## completion for 'library(' or 'require(' R command :
 ## 'unique(unlist(lapply(.libPaths(), dir)))'
 
-# TODO: skip if completion is none, i.e. equals the text
-
-
 #---- LangIntel class
 # Dev Notes:
 # All language should define a LangIntel class. (In some rare cases it
@@ -149,26 +148,21 @@
         char = accessor.char_at_pos(last_pos)
         style = accessor.style_at_pos(last_pos)
         if style == self.operator_style:
-            if char in '(':
-                in_fun = self._in_func(pos, accessor)
-                if in_fun != None and in_fun[2] in ('library', 'require'):
-                    if(style == self.whitespace_style):
-                         text = ''
-                    else:
-                        start, end, text = self._get_word_back(last_pos, accessor)
-                    # lang, form, type, pos, implicit,
-                    return Trigger(self.lang, TRG_FORM_CPLN, "installed-pkgs", \
-                        pos, implicit=True)
-            else:
-                lw_start, lw_end, last_word = self._get_word_back(last_pos, accessor)
-                if last_word in ('@', '$', '::', ':::'):
-                    start, end, objname = self._get_word_back(lw_start - 1, accessor)
-                    style2 = accessor.style_at_pos(end - 1)
-                    if style2 in (self.keyword_style, self.identifier_style, self.variable_style):
-                        return Trigger(self.lang, TRG_FORM_CPLN, "list-elements", \
-                            start, False, obj_name = objname + last_word)
-            return None
+            if char in '[(,':
+                infun = self._in_func(pos, accessor)
+                if infun != None:
+                    s, e, funcname, nargs, argnames, firstarg = infun
+                    return Trigger(self.lang, TRG_FORM_CPLN, "args", pos, True,
+                        funcname = funcname, firstarg = firstarg, nargs = nargs,
+                        argnames = argnames)
+                return None
 
+            elif char in '@$:' and (char != ':' or \
+                accessor.char_at_pos(last_pos - 1) == ':'):
+                vr = self._get_var_back(last_pos, accessor)
+                if vr is not None:
+                    return Trigger(self.lang, TRG_FORM_CPLN, "variable", vr[4],
+                        True, obj_name = ''.join(vr[2]), cutoff = vr[3])
         return None
 
     def _unquote(self, text, quotes = '`"\''):
@@ -197,7 +191,8 @@
         ch = acc.char_at_pos(pos)
         prv_ch = acc.char_at_pos(last_pos)
         #print 'w = "%s", ' % (w, ch, )
-        log.debug('w = "%s", ch = "%s", prv_ch = "%s", pos = %d, curr_pos = %d ' % (w, ch, prv_ch, pos, curr_pos, ))
+        log.debug('w = "%s", ch = "%s", prv_ch = "%s", pos = %d, curr_pos = %d ' \
+                  % (w, ch, prv_ch, pos, curr_pos, ))
         if style in self.word_styles:
             if self._is_bquoted(w):
                 return None
@@ -272,10 +267,14 @@
             ctlr.done("error")
             return
 
-        if completions == None or completions[0] != "success":
+        if completions == None:
+            ctlr.done("not found")
+            return
+        if completions[0] == "error":
             ctlr.error("Nothing found" if completions is None else completions[1])
             ctlr.done("error")
-        else:
+            return
+        if completions[0] == "success":
             completions[1].sort(key = lambda x: x[1].lower() )
             ctlr.set_cplns(completions[1])
             ctlr.done(completions[0])
@@ -316,16 +315,19 @@
             argnames = ''
 
         else:
-            cmd = 'cat(getFunArgs("%s", %s), sep = "\\\n")' % (fname, frstarg, )
+            cmd = 'cat(getFunArgs("%s", %s), sep = "\\n")' % (fname, frstarg, )
             types = 'argument'
             sfx = ' ='
         res = R.execInR(cmd, "json h", .5)
-        if res.startswith(u'\x03') or not len(res.strip()):
+        if not len(res.strip()):
+            return ('none found', 'no completions found')
+
+        if res.startswith(u'\x03'):
             return ('error', res.strip("\x02\x03\r\n"))
 
         if len(argnames):
             return ('success', [(types, x + sfx) for x in res.splitlines()
-                if not x in argnames ])
+                if x not in argnames ])
         else:
             return ('success', [(types, x + sfx) for x in res.splitlines() ])
 
@@ -397,7 +399,7 @@
                 token += [ w, w2 ]
             else:
                 return None
-        elif not style in ( self.identifier_style, self.keyword_style ):
+        elif style not in ( self.identifier_style, self.keyword_style ):
             return None
         token.reverse()
 
@@ -424,12 +426,14 @@
                 return None
             elif ch == "[":
                 fn_start, fn_end, fn_word = self._get_word_back(p, acc)
-                # TODO: _get_var_back ===> (s, e0, token, cutoff, trg_pos)
-                start, end, word, x_, x_ = self._get_var_back(fn_start - 1, acc)
-                #start, end, word = self._get_word_back(fn_start - 1, acc)
-                if acc.style_at_pos(start) in self.word_styles:
-                    argnames.reverse()
-                    return (fn_start, p, fn_word, arg_count, argnames, ''.join(word) )
+                # _get_var_back ===> (s, e0, token, cutoff, trg_pos)
+                vr = self._get_var_back(fn_start - 1, acc)
+                if vr is not None:
+                    start, end, word, x_, x_ = self._get_var_back(fn_start - 1, acc)
+                    #start, end, word = self._get_word_back(fn_start - 1, acc)
+                    if acc.style_at_pos(start) in self.word_styles:
+                        argnames.reverse()
+                        return (fn_start, p, fn_word, arg_count, argnames, ''.join(word) )
                 return None
             elif ch == "(":
                 # function name:



More information about the Sciviews-commits mailing list