[rkward-cvs] SF.net SVN: rkward:[3832] trunk/rkward/rkward/rbackend/rpackages/rkwarddev

m-eik at users.sourceforge.net m-eik at users.sourceforge.net
Sun Sep 25 19:37:29 UTC 2011


Revision: 3832
          http://rkward.svn.sourceforge.net/rkward/?rev=3832&view=rev
Author:   m-eik
Date:     2011-09-25 19:37:29 +0000 (Sun, 25 Sep 2011)
Log Message:
-----------
rkwarddev: added missing element properties to logic functions

Modified Paths:
--------------
    trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk-internal.R
    trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.connect.R
    trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.convert.R
    trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.connect.Rd
    trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.convert.Rd

Modified: trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk-internal.R
===================================================================
--- trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk-internal.R	2011-09-25 17:04:25 UTC (rev 3831)
+++ trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk-internal.R	2011-09-25 19:37:29 UTC (rev 3832)
@@ -161,3 +161,74 @@
 	return(node.ID)
 }
 ## end function check.ID()
+
+## function prop.validity()
+# checks if a property is valid for an XML node, if source is XiMpLe.node
+# if bool=FALSE, returns the property or ""
+prop.validity <- function(source, property, ignore.empty=TRUE, warn.only=TRUE, bool=TRUE){
+	if(identical(property, "") & isTRUE(ignore.empty)){
+		if(isTRUE(bool)){
+			return(TRUE)
+		} else {
+			return(property)
+		}
+	} else {}
+
+	if(inherits(source, "XiMpLe.node")){
+		tag.name <- source at name
+	} else {
+		if(isTRUE(bool)){
+			return(TRUE)
+		} else {
+			return(property)
+		}
+	}
+
+	all.valid.props <- list(
+			all=c("visible", "enabled", "required"),
+			text=c("text"),
+			varselector=c("selected", "root"),
+			varslot=c("available", "selected", "source"),
+			radio=c("string", "number"),
+			dropdown=c("string", "number"),
+			# option=c(),
+			checkbox=c("state"),
+			frame=c("checked"),
+			input=c("text"),
+			browser=c("selection"),
+			saveobject=c("selection", "parent", "objectname", "active"),
+			spinbox=c("int", "real"),
+			formula=c("model", "table", "labels", "fixed_factors", "dependent"),
+			embed=c("code"),
+			preview=c("state")
+		)
+
+	if(tag.name %in% names(all.valid.props)){
+		valid.props <- c(all.valid.props[["all"]], all.valid.props[[tag.name]])
+	} else {
+		valid.props <- c(all.valid.props[["all"]])
+	}
+
+	invalid.prop <- !property %in% valid.props
+	if(any(invalid.prop)){
+		if(isTRUE(warn.only)){
+			warning(paste("Some property you provided is invalid for '",tag.name,"' and was ignored: ",
+				paste(property[invalid.prop], collapse=", "), sep=""))
+			if(isTRUE(bool)){
+				return(FALSE)
+			} else {
+				return("")
+			}
+		} else {
+			stop(simpleError(paste("Some property you provided is invalid for '",tag.name,"' and was ignored: ",
+				paste(property[invalid.prop], collapse=", "), sep="")))
+		}
+	} else {
+		if(isTRUE(bool)){
+			return(TRUE)
+		} else {
+			return(property)
+		}
+	}
+}
+## end function prop.validity()
\ No newline at end of file

Modified: trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.connect.R
===================================================================
--- trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.connect.R	2011-09-25 17:04:25 UTC (rev 3831)
+++ trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.connect.R	2011-09-25 19:37:29 UTC (rev 3832)
@@ -1,7 +1,7 @@
 #' Create XML node "connect" for RKWard plugins
 #'
-#' If you define a \code{XiMpLe.node} object as \code{governor} which is not a \code{<convert>} node,
-#' the function will automatically append ".state" to its \code{id}.
+#' If you define a \code{XiMpLe.node} object as \code{governor} which is not a \code{<convert>} node
+#' and \code{not=FALSE}, the function will automatically append ".state" to its \code{id}.
 #'
 #' @param governor Either a character string (the \code{id} of the property whose state should control
 #'		the \code{client}), or an object of class \code{XiMpLe.node} (whose \code{id} will be extracted
@@ -9,6 +9,7 @@
 #'		\code{\link[rkwarddev:rk.XML.convert]{rk.XML.convert}}), or the ".state" value of some
 #'		apropriate node.
 #' @param client Character string, the \code{id} if the element to be controlled by \code{governor}.
+#' @param not Logical, if \code{TRUE}, the state of \code{governor} (\code{TRUE/FALSE}) will be inversed.
 #' @param set Character string, one of the following values:
 #'		\itemize{
 #'			\item{\code{"enabled"}}{If \code{governor} becomes true, \code{client} is enabled.}
@@ -28,7 +29,7 @@
 #' test.connect <- rk.XML.connect(governor="lgc_foobar", client="frame_bar")
 #' cat(pasteXMLNode(test.connect, shine=1))
 
-rk.XML.connect <- function(governor, client, set="enabled", reconcile=FALSE){
+rk.XML.connect <- function(governor, client, set="enabled", not=FALSE, reconcile=FALSE){
 
 	if(length(governor) > 1 | length(client) > 1){
 		stop(simpleError("'governor' and 'client' must be of length 1!"))
@@ -39,10 +40,13 @@
 	governor.id <- check.ID(governor)
 	# if governor is an XML node but not <convert>, append ".state"
 	if(inherits(governor, "XiMpLe.node")){
-		if(!identical(governor at name, "convert")){
+		if(!identical(governor at name, "convert") & !isTRUE(not)){
 			governor.id <- paste(governor.id, "state", sep=".")
 		} else {}
 	} else {}
+	if(isTRUE(not)){
+		governor.id <- paste(governor.id, "not", sep=".")
+	} else {}
 
 	attr.list <- list(governor=as.character(governor.id))
 

Modified: trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.convert.R
===================================================================
--- trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.convert.R	2011-09-25 17:04:25 UTC (rev 3831)
+++ trunk/rkward/rkward/rbackend/rpackages/rkwarddev/R/rk.XML.convert.R	2011-09-25 19:37:29 UTC (rev 3832)
@@ -1,9 +1,18 @@
 #' Create XML node convert for RKWard plugins
 #'
+#' The recognized property names for \code{sources} are the following:
+#' \code{string}, \code{state}, \code{text}, \code{selected}, \code{root},
+#' \code{available}, \code{source}, \code{number}, \code{enabled}, \code{checked}, \code{selection},
+#' \code{parent}, \code{objectname}, \code{active}, \code{int}, \code{real}, \code{model},
+#' \code{table}, \code{labels}, \code{fixed_factors}, \code{dependent} and \code{code}.
+#' They are not globally valid for all XML elements, see the section on "Properties of plugin elements"
+#' to see which is useful for what tag. If \code{sources} holds \code{XiMpLe.node}
+#' objects, the validity of properties is automatically checked for that tag.
+#'
 #' @param sources A list with at least one value, either resembling the \code{id} of
 #'		an existing element to be queried as a character string, or a previously defined object
 #'		of class \code{XiMpLe.node} (whose \code{id} will be extracted and used). If you want
-#'		to examine the state or string value specificly, just name the value accoringly, e.g.,
+#'		to examine e.g. the state or string value specificly, just name the value accoringly, e.g.,
 #'		\code{sources=list("vars0", string="input1", state="chkbx2")}.
 #' @param mode A named vector with either exactly one of the following elements:
 #'		\itemize{
@@ -63,17 +72,21 @@
 	# for RKWard, like string="foo" should actually be "foo.string"
 	src.names <- names(sources)
 	if(!is.null(src.names)){
-		# check these names if they're valid here
-		invalid.names <- !src.names %in% c("", "string", "state")
+		# check these names if they're valid properties here
+		invalid.names <- !src.names %in% c("", "string", "state", "text", "selected", "root",
+			"available", "source", "number", "enabled", "checked", "selection", "parent",
+			"objectname", "active", "int", "real", "model", "table", "labels",
+			"fixed_factors", "dependent", "code")
 		if(any(invalid.names)){
-			warning(paste("Some of the names you provided are invalid and were ignored: ",
+			warning(paste("Some of the property names you provided are invalid and were ignored: ",
 				paste(src.names[invalid.names], collapse=", "), sep=""))
 				src.names[invalid.names] <- ""
 		} else {}
 		sources <- as.character(sapply(1:length(src.names), function(src.no){
-				this.modifier <- src.names[src.no]
-				if(nchar(this.modifier) > 0){
-					new.value <- paste(check.ID(sources[[src.no]]), this.modifier, sep=".")
+				this.prop <- src.names[src.no]
+				valid.prop <- prop.validity(source=sources[[src.no]], property=this.prop, bool=FALSE)
+				if(nchar(valid.prop) > 0){
+					new.value <- paste(check.ID(sources[[src.no]]), this.prop, sep=".")
 				} else {
 					new.value <- check.ID(sources[[src.no]])
 				}

Modified: trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.connect.Rd
===================================================================
--- trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.connect.Rd	2011-09-25 17:04:25 UTC (rev 3831)
+++ trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.connect.Rd	2011-09-25 19:37:29 UTC (rev 3832)
@@ -2,8 +2,8 @@
 \alias{rk.XML.connect}
 \title{Create XML node "connect" for RKWard plugins}
 \usage{
-  rk.XML.connect(governor, client, set = "enabled",
-  reconcile = FALSE)
+  rk.XML.connect(governor, client, set = "enabled", not =
+  FALSE, reconcile = FALSE)
 }
 \arguments{
   \item{governor}{Either a character string (the \code{id}
@@ -17,6 +17,9 @@
   \item{client}{Character string, the \code{id} if the
   element to be controlled by \code{governor}.}
 
+  \item{not}{Logical, if \code{TRUE}, the state of
+  \code{governor} (\code{TRUE/FALSE}) will be inversed.}
+
   \item{set}{Character string, one of the following values:
   \itemize{ \item{\code{"enabled"}}{If \code{governor}
   becomes true, \code{client} is enabled.}
@@ -34,9 +37,9 @@
 }
 \description{
   If you define a \code{XiMpLe.node} object as
-  \code{governor} which is not a \code{<convert>} node, the
-  function will automatically append ".state" to its
-  \code{id}.
+  \code{governor} which is not a \code{<convert>} node and
+  \code{not=FALSE}, the function will automatically append
+  ".state" to its \code{id}.
 }
 \examples{
 test.connect <- rk.XML.connect(governor="lgc_foobar", client="frame_bar")

Modified: trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.convert.Rd
===================================================================
--- trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.convert.Rd	2011-09-25 17:04:25 UTC (rev 3831)
+++ trunk/rkward/rkward/rbackend/rpackages/rkwarddev/man/rk.XML.convert.Rd	2011-09-25 19:37:29 UTC (rev 3832)
@@ -10,8 +10,8 @@
   resembling the \code{id} of an existing element to be
   queried as a character string, or a previously defined
   object of class \code{XiMpLe.node} (whose \code{id} will
-  be extracted and used). If you want to examine the state
-  or string value specificly, just name the value
+  be extracted and used). If you want to examine e.g. the
+  state or string value specificly, just name the value
   accoringly, e.g., \code{sources=list("vars0",
   string="input1", state="chkbx2")}.}
 
@@ -44,7 +44,19 @@
   A list of objects of class \code{XiMpLe.node}.
 }
 \description{
-  Create XML node convert for RKWard plugins
+  The recognized property names for \code{sources} are the
+  following: \code{string}, \code{state}, \code{text},
+  \code{selected}, \code{root}, \code{available},
+  \code{source}, \code{number}, \code{enabled},
+  \code{checked}, \code{selection}, \code{parent},
+  \code{objectname}, \code{active}, \code{int},
+  \code{real}, \code{model}, \code{table}, \code{labels},
+  \code{fixed_factors}, \code{dependent} and \code{code}.
+  They are not globally valid for all XML elements, see the
+  section on "Properties of plugin elements" to see which
+  is useful for what tag. If \code{sources} holds
+  \code{XiMpLe.node} objects, the validity of properties is
+  automatically checked for that tag.
 }
 \examples{
 test.convert <- rk.XML.convert(c(string="foo"), mode=c(notequals="bar"))

This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.





More information about the rkward-tracker mailing list