[rkward-cvs] SF.net SVN: rkward:[3973] trunk/rkward/packages/rkwarddev

m-eik at users.sourceforge.net m-eik at users.sourceforge.net
Wed Oct 19 16:03:47 UTC 2011


Revision: 3973
          http://rkward.svn.sourceforge.net/rkward/?rev=3973&view=rev
Author:   m-eik
Date:     2011-10-19 16:03:47 +0000 (Wed, 19 Oct 2011)
Log Message:
-----------
rkwarddev: changed rk.JS.vars() completely

Modified Paths:
--------------
    trunk/rkward/packages/rkwarddev/ChangeLog
    trunk/rkward/packages/rkwarddev/DESCRIPTION
    trunk/rkward/packages/rkwarddev/NAMESPACE
    trunk/rkward/packages/rkwarddev/R/id.R
    trunk/rkward/packages/rkwarddev/R/rk-internal.R
    trunk/rkward/packages/rkwarddev/R/rk.JS.vars.R
    trunk/rkward/packages/rkwarddev/R/rk.paste.JS.R
    trunk/rkward/packages/rkwarddev/R/rkwarddev-package.R
    trunk/rkward/packages/rkwarddev/R/show-methods.R
    trunk/rkward/packages/rkwarddev/inst/CITATION
    trunk/rkward/packages/rkwarddev/inst/doc/rkwarddev_vignette.pdf
    trunk/rkward/packages/rkwarddev/man/id.Rd
    trunk/rkward/packages/rkwarddev/man/rk.JS.vars.Rd
    trunk/rkward/packages/rkwarddev/man/rk.paste.JS.Rd
    trunk/rkward/packages/rkwarddev/man/rkwarddev-package.Rd
    trunk/rkward/packages/rkwarddev/man/show-methods.Rd

Added Paths:
-----------
    trunk/rkward/packages/rkwarddev/R/rk.JS.var-class.R

Modified: trunk/rkward/packages/rkwarddev/ChangeLog
===================================================================
--- trunk/rkward/packages/rkwarddev/ChangeLog	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/ChangeLog	2011-10-19 16:03:47 UTC (rev 3973)
@@ -1,5 +1,10 @@
 ChangeLog for package rkwarddev
 
+## 0.03-8 (2011-10-19)
+  - added class rk.JS.var, including show method
+  - added support for class rk.JS.var in rk.paste.JS() an id()
+  - rk.JS.vars() now returns a list of class rk.JS.var
+
 ## 0.03-7 (2011-10-18)
   - added "checkable" and "checked" options to rk.XML.frame()
   - set rk.paste.JS() default level to 2

Modified: trunk/rkward/packages/rkwarddev/DESCRIPTION
===================================================================
--- trunk/rkward/packages/rkwarddev/DESCRIPTION	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/DESCRIPTION	2011-10-19 16:03:47 UTC (rev 3973)
@@ -14,8 +14,8 @@
 URL: http://rkward.sourceforge.net
 Authors at R: c(person(given="Meik", family="Michalke",
     email="meik.michalke at hhu.de", role=c("aut", "cre")))
-Version: 0.03-7
-Date: 2011-10-18
+Version: 0.03-8
+Date: 2011-10-19
 Collate:
     'echo.R'
     'id.R'
@@ -31,6 +31,7 @@
     'rk.JS.options.R'
     'rk.JS.saveobj.R'
     'rk.JS.scan.R'
+    'rk.JS.var-class.R'
     'rk.JS.vars.R'
     'rk.paste.JS.R'
     'rk.plugin.skeleton.R'

Modified: trunk/rkward/packages/rkwarddev/NAMESPACE
===================================================================
--- trunk/rkward/packages/rkwarddev/NAMESPACE	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/NAMESPACE	2011-10-19 16:03:47 UTC (rev 3973)
@@ -1,6 +1,7 @@
 exportClasses(rk.JS.arr)
 exportClasses(rk.JS.ite)
 exportClasses(rk.JS.opt)
+exportClasses(rk.JS.var)
 export(echo)
 export(id)
 export(ite)

Modified: trunk/rkward/packages/rkwarddev/R/id.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/id.R	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/R/id.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -2,11 +2,12 @@
 #' 
 #' This function is intended to be used for generating JavaScript code for
 #' RKWard plugins. Its sole purpose is to replace objects of class \code{XiMpLe.node}
-#' which hold an XML node of some plugin GUI definition, and objects of classes \code{rk.JS.arr} or \code{rk.JS.opt}
-#' with their ID (or JS variable name), and combine these replacements with character strings.
+#' which hold an XML node of some plugin GUI definition, and objects of classes \code{rk.JS.arr},
+#' \code{rk.JS.opt} or \code{rk.JS.var} with their ID (or JS variable name), and combine these
+#' replacements with character strings.
 #' 
 #' @param ... One or several character strings and/or \code{XiMpLe.node} objects with plugin nodes,
-#' 	and/or objects of classes \code{rk.JS.arr} or \code{rk.JS.opt}, simply separated by comma.
+#' 	and/or objects of classes \code{rk.JS.arr}, \code{rk.JS.opt} or \code{rk.JS.var}, simply separated by comma.
 #' @param quote Logical, it the character strings sould be deparsed, so they come out "as-is" when
 #'		written to files, e.g. by \code{cat}.
 #' @param collapse Character string, defining if and how the individual elements should be glued together.
@@ -40,7 +41,23 @@
 			} else if(inherits(this.part, "rk.JS.opt")){
 				node.id <- this.part at var.name
 				return(node.id)
-			}else {
+			} else if(inherits(this.part, "rk.JS.var")){
+				# can hold multiple IDs, but we'll only return the first valid one
+				node.id <- this.part at JS.var
+				if(length(node.id) > 0){
+					if(length(this.part at vars) > 0){
+						warning(paste("Object contained more than one ID, only the first one was used: ", node.id, sep=""), call.=FALSE)
+					} else {}
+				} else {
+					if(length(this.part at vars) > 0){
+							node.id <- this.part at vars[[1]]@JS.var
+						if(length(this.part at vars) > 1){
+							warning(paste("Object contained more than one ID, only the first one was used: ", node.id, sep=""), call.=FALSE)
+						} else {}
+					} else {}
+				}
+				return(node.id)
+			} else {
 				if(isTRUE(quote)){
 					text.part <- deparse(this.part)
 				} else {

Modified: trunk/rkward/packages/rkwarddev/R/rk-internal.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/rk-internal.R	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/R/rk-internal.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -143,53 +143,60 @@
 #   <tag id="my.id" ...>
 # in XML will become
 #   var my.id = getValue("my.id");
-get.JS.vars <- function(JS.var, XML.var=NULL, JS.prefix="", indent.by="", names.only=FALSE, properties=NULL, default=FALSE){
+get.JS.vars <- function(JS.var, XML.var=NULL, JS.prefix="", names.only=FALSE, properties=NULL, default=FALSE, join=""){
 	# check for XiMpLe nodes
 	JS.var <- check.ID(JS.var)
 	if(!is.null(XML.var)){
 		# check validity of properties value
 		if(!is.null(properties)){
 			if(identical(properties, "all")){
-					if(inherits(XML.var, "XiMpLe.node")){
-						tag.name <- XML.var at name
-					} else {
-						tag.name <- XML.var
-					}
+				if(inherits(XML.var, "XiMpLe.node")){
+					tag.name <- XML.var at name
+				} else {
+					tag.name <- XML.var
+				}
 				if(tag.name %in% names(all.valid.props)){
 					properties <- all.valid.props[[tag.name]]
 				} else {
 					properties <- NULL
 				}
 			} else {
-				properties <- sapply(child.list(properties), function(this.prop){
-					prop.validity(XML.var, property=this.prop, warn.only=TRUE, bool=FALSE)
-				})
-				properties <- properties[!"" %in% properties]
+				if(inherits(XML.var, "XiMpLe.node")){
+					prop.tag.name <- tag.name
+				} else {
+					prop.tag.name <- "all"
+				}
+				properties <- properties[prop.validity(prop.tag.name, property=child.list(properties), warn.only=TRUE, bool=TRUE)]
 			}
 		} else {}
 		XML.var <- check.ID(XML.var)
 	} else {}
 
-	results <- c()
-	if(is.null(properties) | isTRUE(default)){
-		if(isTRUE(names.only)){
+	if(is.null(JS.prefix)){
+		JS.prefix <- ""
+	} else {}
+	if(is.null(properties)){
+		properties <- list()
+	} else {}
+
+	if(isTRUE(names.only)){
+		results <- c()
+		if(is.null(properties) | isTRUE(default)){
 			results <- camelCode(c(JS.prefix, JS.var))
-		} else {
-			results <- paste(indent.by, "var ", camelCode(c(JS.prefix, JS.var)), " = getValue(\"", XML.var, "\");\n", sep="")
-		}
-	} else {}
-	if(!is.null(properties)){
-		if(isTRUE(names.only)){
+		} else {}
+		if(!is.null(properties)){
 			results <- c(results,
 				sapply(properties, function(this.prop){camelCode(c(JS.prefix, JS.var, this.prop))})
 			)
-		} else {
-			results <- c(results,
-				sapply(properties, function(this.prop){
-					paste(indent.by, "var ", camelCode(c(JS.prefix, JS.var, this.prop)), " = getValue(\"", XML.var, ".", this.prop, "\");\n", sep="")
-				})
-			)
-		}
+		} else {}
+	} else {
+		results <- new("rk.JS.var",
+			JS.var=JS.var,
+			XML.var=XML.var,
+			prefix=JS.prefix,
+			properties=child.list(properties),
+			default=default,
+			join=join)
 	}
 
 	return(results)
@@ -300,7 +307,7 @@
 	all=c("visible", "enabled", "required"),
 	text=c("text"),
 	varselector=c("selected", "root"),
-	varslot=c("available", "selected", "source"),
+	varslot=c("available", "selected", "source", "shortname", "label"),
 	radio=c("string", "number"),
 	dropdown=c("string", "number"),
 	# option=c(),
@@ -329,6 +336,8 @@
 
 	if(inherits(source, "XiMpLe.node")){
 		tag.name <- source at name
+	} else if(identical(source, "all")){
+		tag.name <- "<any tag>"
 	} else {
 		if(isTRUE(bool)){
 			return(TRUE)
@@ -339,17 +348,19 @@
 
 	if(tag.name %in% names(all.valid.props)){
 		valid.props <- c(all.valid.props[["all"]], all.valid.props[[tag.name]])
+	} else if(identical(tag.name, "<any tag>")){
+		valid.props <- unique(unlist(all.valid.props))
 	} else {
 		valid.props <- c(all.valid.props[["all"]])
 	}
 
-	invalid.prop <- !property %in% valid.props
+	invalid.prop <- !unlist(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=""), call.=FALSE)
 			if(isTRUE(bool)){
-				return(FALSE)
+				return(!invalid.prop)
 			} else {
 				return("")
 			}
@@ -359,7 +370,7 @@
 		}
 	} else {
 		if(isTRUE(bool)){
-			return(TRUE)
+			return(!invalid.prop)
 		} else {
 			return(property)
 		}
@@ -550,3 +561,61 @@
 
 	return(JS.options)
 } ## end function paste.JS.options()
+
+## function paste.JS.var()
+paste.JS.var <- function(object, level=2, indent.by="\t", JS.prefix=NULL, properties=NULL, default=NULL, join=NULL){
+	# paste several objects
+	results <- paste(unlist(sapply(object at vars, function(this.obj){
+			paste.JS.var(this.obj,
+					level=level,
+					indent.by=indent.by,
+					JS.prefix=JS.prefix,
+					properties=properties,
+					default=default,
+					join=join)})),
+	collapse="")
+
+	stopifnot(inherits(object, "rk.JS.var"))
+	# check indentation
+	main.indent <- indent(level, by=indent.by)
+
+	JS.var         <- object at JS.var
+	XML.var        <- object at XML.var
+	if(is.null(JS.prefix)){
+		JS.prefix  <- object at prefix
+	} else {}
+	if(is.null(properties)){
+		properties  <- object at properties
+	} else {}
+	if(is.null(default)){
+		default     <- object at default
+	} else {}
+	if(is.null(join)){
+		join        <- object at join
+	} else {}
+
+	if(!identical(join, "")){
+		join.code <- paste(".split(\"\\n\").join(\"", join, "\")", sep="")
+	} else {
+		join.code <- ""
+	}
+
+	# only paste something if there's variables outside the 'vars' slot
+	if(length(nchar(JS.var)) > 0 & length(nchar(XML.var)) > 0){
+		if(length(properties) == 0 | isTRUE(default)){
+			results <- paste(results, main.indent, "var ", camelCode(c(JS.prefix, JS.var)), " = getValue(\"", XML.var, "\")", join.code, ";\n", sep="")
+		} else {}
+		if(length(properties) > 0){
+			# check properties
+			properties <- properties[prop.validity(source="all", property=properties, ignore.empty=TRUE, warn.only=TRUE, bool=TRUE)]
+			results <- c(results,
+				sapply(properties, function(this.prop){
+					paste(main.indent, "var ", camelCode(c(JS.prefix, JS.var, this.prop)), " = getValue(\"", XML.var, ".", this.prop, "\")", join.code, ";\n", sep="")
+				})
+			)
+		}
+	} else {}
+
+	results <- paste(results, collapse="")
+	return(results)
+} ## end function paste.JS.options()

Added: trunk/rkward/packages/rkwarddev/R/rk.JS.var-class.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/rk.JS.var-class.R	                        (rev 0)
+++ trunk/rkward/packages/rkwarddev/R/rk.JS.var-class.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -0,0 +1,35 @@
+#' @export
+
+# this simple class is for JavaScript generation,
+# produced by rk.JS.vars()
+
+setClass("rk.JS.var",
+	representation=representation(
+		JS.var="character",
+		XML.var="character",
+		prefix="character",
+		properties="list",
+		default="logical",
+		join="character",
+		vars="list"
+	),
+	prototype(
+		JS.var=character(),
+		XML.var=character(),
+		prefix=character(),
+		properties=list(),
+		default=FALSE,
+		join="",
+		vars=list()
+	)
+)
+
+setValidity("rk.JS.var", function(object){
+		# vars in this object must be of the same class
+		sapply(object at vars, function(this.var){
+			if(!inherits(this.var, "rk.JS.var")){
+				stop(simpleError("Slot 'vars' can only have a list of elements of class 'rk.JS.var'!"))
+			} else {}
+		})
+	return(TRUE)
+})

Modified: trunk/rkward/packages/rkwarddev/R/rk.JS.vars.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/rk.JS.vars.R	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/R/rk.JS.vars.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -1,15 +1,15 @@
 #' Define variables in JavaScript code
 #' 
-#' @param variables A list with either character strings (the names of the variables to define),
-#'		of objects of class \code{XiMpLe.node} with plugin XML nodes (whose ID will be extracted and used).
-#' @param var.prefix A character string. If \code{def.vars=TRUE}, this string will be used as a prefix
-#'		for the JS variable names.
+#' @param ... Either one or more character strings (the names of the variables to define),
+#'		or objects of class \code{XiMpLe.node} with plugin XML nodes (whose ID will be extracted and used).
+#' @param var.prefix A character string. will be used as a prefix for the JS variable names.
 #' @param properties A character vector with properties you'd like to get of the XML node.
 #' @param default Logical, if \code{TRUE} the default value (no special property) of the node will
 #'		also be defined. Does nothing if \code{properties=NULL}.
-#' @param level Integer, which indentation level to use, minimum is 1.
-#' @param indent.by A character string defining how indentation should be done.
-#' @return A character string.
+#' @param join A character string, useful for GUI elements which accept multiple objects (i.e., multi-varslots).
+#'		If \code{join} is something other than \code{""}, these objects will be collapsed into one string when pasted,
+#'		joined by this string.
+#' @return An object of class \code{rk.JS.var}.
 #' @export
 #' @seealso \code{\link[rkwarddev:rk.JS.array]{rk.JS.array}},
 #'		\code{\link[rkwarddev:echo]{echo}},
@@ -21,19 +21,20 @@
 #' checkB <- rk.XML.cbox(label="Run Test B", value="B")
 #' checkC <- rk.XML.cbox(label="Run Test C", value="C")
 #' # define them by their ID in JavaScript
-#' cat(rk.JS.vars(list(checkA, checkB, checkC)))
+#' cat(rk.paste.JS(rk.JS.vars(list(checkA, checkB, checkC))))
 
-rk.JS.vars <- function(variables, var.prefix=NULL, properties=NULL, default=FALSE, level=2, indent.by="\t"){
-	indent.by <- indent(level, by=indent.by)
+rk.JS.vars <- function(..., var.prefix=NULL, properties=NULL, default=FALSE, join=""){
+	variables <- list(...)
 
-	JS.vars <- paste(unlist(sapply(child.list(variables), function(this.var){get.JS.vars(
+	JS.vars <- new("rk.JS.var",
+				vars=sapply(child.list(variables), function(this.var){get.JS.vars(
 						JS.var=this.var,
 						XML.var=this.var,
 						JS.prefix=var.prefix,
-						indent.by=indent.by,
 						properties=properties,
-						default=default)
-				})), collapse="")
+						default=default,
+						join=join)
+				}))
 
 	return(JS.vars)
 }

Modified: trunk/rkward/packages/rkwarddev/R/rk.paste.JS.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/rk.paste.JS.R	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/R/rk.paste.JS.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -7,21 +7,32 @@
 #' 	to be called to combine the options, e.g. "list" for \code{list()}, or "c" for \code{c()}.
 #' @param array For \code{rk.JS.opt} objects only: Logical, whether the options should be collected
 #'		in an array or a concatenated character string.
+#' @param var.prefix For \code{rk.JS.var} objects only: A character string. will be used as a prefix
+#'		for the JS variable names.
+#' @param properties For \code{rk.JS.var} objects only: A character vector with properties you'd like to get of the XML node.
+#' @param default For \code{rk.JS.var} objects only: Logical, if \code{TRUE} the default value (no special property) of the node will
+#'		also be defined. Does nothing if \code{properties=NULL}.
+#' @param join For \code{rk.JS.var} objects only: A character string, useful for GUI elements which accept multiple objects
+#'		(i.e., multi-varslots). If \code{join} is something other than \code{""}, these objects will be collapsed into one string
+#'		when pasted, joined by this string.
 #' @return A character string.
+#' @include rk.JS.arr-class.R
 #' @include rk.JS.ite-class.R
-#' @include rk.JS.arr-class.R
 #' @include rk.JS.opt-class.R
+#' @include rk.JS.var-class.R
 #' @seealso
 #'		\code{\link[rkwarddev:rk.JS.array]{rk.JS.array}},
 #'		\code{\link[rkwarddev:rk.JS.options]{rk.JS.options}},
+#'		\code{\link[rkwarddev:rk.JS.vars]{rk.JS.vars}},
 #'		\code{\link[rkwarddev:ite]{ite}},
 #'		and the \href{help:rkwardplugins}{Introduction to Writing Plugins for RKWard}
 #' @export
 
-rk.paste.JS <- function(..., level=2, indent.by="\t", funct=NULL, array=NULL){
+rk.paste.JS <- function(..., level=2, indent.by="\t", funct=NULL, array=NULL,
+	var.prefix=NULL, properties=NULL, default=NULL, join=NULL){
 	stopifnot(level > 0)
 	all.objects <- list(...)
-	
+
 	paste.results <- paste(sapply(all.objects, function(this.object){
 		if(inherits(this.object, "rk.JS.ite")){
 			# done by an internal function, to ease handling of recursions
@@ -31,6 +42,9 @@
 			result <- paste.JS.array(this.object, level=level, indent.by=indent.by, funct=funct)
 		} else if(inherits(this.object, "rk.JS.opt")){
 			result <- paste.JS.options(this.object, level=level, indent.by=indent.by, array=array, funct=funct)
+		} else if(inherits(this.object, "rk.JS.var")){
+			result <- paste.JS.var(this.object, level=level, indent.by=indent.by, JS.prefix=var.prefix,
+				properties=properties, default=default, join=join)
 		} else {
 			result <- paste(indent(level, by=indent.by), this.object, sep="")
 		}

Modified: trunk/rkward/packages/rkwarddev/R/rkwarddev-package.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/rkwarddev-package.R	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/R/rkwarddev-package.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -3,8 +3,8 @@
 #' \tabular{ll}{
 #' Package: \tab rkwarddev\cr
 #' Type: \tab Package\cr
-#' Version: \tab 0.03-7\cr
-#' Date: \tab 2011-10-18\cr
+#' Version: \tab 0.03-8\cr
+#' Date: \tab 2011-10-19\cr
 #' Depends: \tab R (>= 2.9.0),XiMpLe,rkward (>= 0.5.7)\cr
 #' Enhances: \tab rkward\cr
 #' Encoding: \tab UTF-8\cr

Modified: trunk/rkward/packages/rkwarddev/R/show-methods.R
===================================================================
--- trunk/rkward/packages/rkwarddev/R/show-methods.R	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/R/show-methods.R	2011-10-19 16:03:47 UTC (rev 3973)
@@ -2,27 +2,32 @@
 #'
 #' @title Show methods for objects of class rk.JS.S
 #' @param object An object of class \code{rk.JS.*}
-#' @aliases show,-methods show,rk.JS.ite-method show,rk.JS.arr-method show,rk.JS.opt-method
+#' @aliases show,-methods show,rk.JS.ite-method show,rk.JS.arr-method show,rk.JS.opt-method show,rk.JS.var-method
 #' @keywords methods
 #' @import methods
+#' @include rk.JS.arr-class.R
 #' @include rk.JS.ite-class.R
-#' @include rk.JS.arr-class.R
 #' @include rk.JS.opt-class.R
+#' @include rk.JS.var-class.R
 #' @exportMethod show
 #' @rdname show-methods
 setGeneric("show")
 
 #' @rdname show-methods
+setMethod("show", signature(object="rk.JS.arr"), function(object){
+	cat(rk.paste.JS(object))
+})
+#' @rdname show-methods
 setMethod("show", signature(object="rk.JS.ite"), function(object){
 	cat(rk.paste.JS(object))
 })
 
 #' @rdname show-methods
-setMethod("show", signature(object="rk.JS.arr"), function(object){
+setMethod("show", signature(object="rk.JS.opt"), function(object){
 	cat(rk.paste.JS(object))
 })
 
 #' @rdname show-methods
-setMethod("show", signature(object="rk.JS.opt"), function(object){
+setMethod("show", signature(object="rk.JS.var"), function(object){
 	cat(rk.paste.JS(object))
 })

Modified: trunk/rkward/packages/rkwarddev/inst/CITATION
===================================================================
--- trunk/rkward/packages/rkwarddev/inst/CITATION	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/inst/CITATION	2011-10-19 16:03:47 UTC (rev 3973)
@@ -2,12 +2,12 @@
 		title="rkwarddev: A collection of tools for RKWard plugin development",
 		author="Meik Michalke",
 		year="2011",
-		note="(Version 0.03-7)",
+		note="(Version 0.03-8)",
 		url="http://rkward.sourceforge.net",
 
 		textVersion =
 		paste("Michalke, M. (2011). ",
-				"rkwarddev: A collection of tools for RKWard plugin development (Version 0.03-7). ",
+				"rkwarddev: A collection of tools for RKWard plugin development (Version 0.03-8). ",
 				"Available from http://rkward.sourceforge.net",
 				sep=""),
 

Modified: trunk/rkward/packages/rkwarddev/inst/doc/rkwarddev_vignette.pdf
===================================================================
(Binary files differ)

Modified: trunk/rkward/packages/rkwarddev/man/id.Rd
===================================================================
--- trunk/rkward/packages/rkwarddev/man/id.Rd	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/man/id.Rd	2011-10-19 16:03:47 UTC (rev 3973)
@@ -7,8 +7,8 @@
 \arguments{
   \item{...}{One or several character strings and/or
   \code{XiMpLe.node} objects with plugin nodes, and/or
-  objects of classes \code{rk.JS.arr} or \code{rk.JS.opt},
-  simply separated by comma.}
+  objects of classes \code{rk.JS.arr}, \code{rk.JS.opt} or
+  \code{rk.JS.var}, simply separated by comma.}
 
   \item{quote}{Logical, it the character strings sould be
   deparsed, so they come out "as-is" when written to files,
@@ -29,9 +29,9 @@
   JavaScript code for RKWard plugins. Its sole purpose is
   to replace objects of class \code{XiMpLe.node} which hold
   an XML node of some plugin GUI definition, and objects of
-  classes \code{rk.JS.arr} or \code{rk.JS.opt} with their
-  ID (or JS variable name), and combine these replacements
-  with character strings.
+  classes \code{rk.JS.arr}, \code{rk.JS.opt} or
+  \code{rk.JS.var} with their ID (or JS variable name), and
+  combine these replacements with character strings.
 }
 \examples{
 # an example checkbox XML node

Modified: trunk/rkward/packages/rkwarddev/man/rk.JS.vars.Rd
===================================================================
--- trunk/rkward/packages/rkwarddev/man/rk.JS.vars.Rd	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/man/rk.JS.vars.Rd	2011-10-19 16:03:47 UTC (rev 3973)
@@ -2,17 +2,16 @@
 \alias{rk.JS.vars}
 \title{Define variables in JavaScript code}
 \usage{
-  rk.JS.vars(variables, var.prefix = NULL, properties =
-  NULL, default = FALSE, level = 2, indent.by = "\t")
+  rk.JS.vars(..., var.prefix = NULL, properties = NULL,
+  default = FALSE, join = "")
 }
 \arguments{
-  \item{variables}{A list with either character strings
-  (the names of the variables to define), of objects of
-  class \code{XiMpLe.node} with plugin XML nodes (whose ID
-  will be extracted and used).}
+  \item{...}{Either one or more character strings (the
+  names of the variables to define), or objects of class
+  \code{XiMpLe.node} with plugin XML nodes (whose ID will
+  be extracted and used).}
 
-  \item{var.prefix}{A character string. If
-  \code{def.vars=TRUE}, this string will be used as a
+  \item{var.prefix}{A character string. will be used as a
   prefix for the JS variable names.}
 
   \item{properties}{A character vector with properties
@@ -22,14 +21,14 @@
   (no special property) of the node will also be defined.
   Does nothing if \code{properties=NULL}.}
 
-  \item{level}{Integer, which indentation level to use,
-  minimum is 1.}
-
-  \item{indent.by}{A character string defining how
-  indentation should be done.}
+  \item{join}{A character string, useful for GUI elements
+  which accept multiple objects (i.e., multi-varslots). If
+  \code{join} is something other than \code{""}, these
+  objects will be collapsed into one string when pasted,
+  joined by this string.}
 }
 \value{
-  A character string.
+  An object of class \code{rk.JS.var}.
 }
 \description{
   Define variables in JavaScript code
@@ -40,7 +39,7 @@
 checkB <- rk.XML.cbox(label="Run Test B", value="B")
 checkC <- rk.XML.cbox(label="Run Test C", value="C")
 # define them by their ID in JavaScript
-cat(rk.JS.vars(list(checkA, checkB, checkC)))
+cat(rk.paste.JS(rk.JS.vars(list(checkA, checkB, checkC))))
 }
 \seealso{
   \code{\link[rkwarddev:rk.JS.array]{rk.JS.array}},

Modified: trunk/rkward/packages/rkwarddev/man/rk.paste.JS.Rd
===================================================================
--- trunk/rkward/packages/rkwarddev/man/rk.paste.JS.Rd	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/man/rk.paste.JS.Rd	2011-10-19 16:03:47 UTC (rev 3973)
@@ -3,7 +3,8 @@
 \title{Paste JavaScript objects and character strings}
 \usage{
   rk.paste.JS(..., level = 2, indent.by = "\t", funct =
-  NULL, array = NULL)
+  NULL, array = NULL, var.prefix = NULL, properties = NULL,
+  default = NULL, join = NULL)
 }
 \arguments{
   \item{...}{Objects of class \code{rk.JS.ite},
@@ -23,6 +24,26 @@
   \item{array}{For \code{rk.JS.opt} objects only: Logical,
   whether the options should be collected in an array or a
   concatenated character string.}
+
+  \item{var.prefix}{For \code{rk.JS.var} objects only: A
+  character string. will be used as a prefix for the JS
+  variable names.}
+
+  \item{properties}{For \code{rk.JS.var} objects only: A
+  character vector with properties you'd like to get of the
+  XML node.}
+
+  \item{default}{For \code{rk.JS.var} objects only:
+  Logical, if \code{TRUE} the default value (no special
+  property) of the node will also be defined. Does nothing
+  if \code{properties=NULL}.}
+
+  \item{join}{For \code{rk.JS.var} objects only: A
+  character string, useful for GUI elements which accept
+  multiple objects (i.e., multi-varslots). If \code{join}
+  is something other than \code{""}, these objects will be
+  collapsed into one string when pasted, joined by this
+  string.}
 }
 \value{
   A character string.
@@ -33,6 +54,7 @@
 \seealso{
   \code{\link[rkwarddev:rk.JS.array]{rk.JS.array}},
   \code{\link[rkwarddev:rk.JS.options]{rk.JS.options}},
+  \code{\link[rkwarddev:rk.JS.vars]{rk.JS.vars}},
   \code{\link[rkwarddev:ite]{ite}}, and the
   \href{help:rkwardplugins}{Introduction to Writing Plugins
   for RKWard}

Modified: trunk/rkward/packages/rkwarddev/man/rkwarddev-package.Rd
===================================================================
--- trunk/rkward/packages/rkwarddev/man/rkwarddev-package.Rd	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/man/rkwarddev-package.Rd	2011-10-19 16:03:47 UTC (rev 3973)
@@ -8,8 +8,8 @@
 }
 \details{
   \tabular{ll}{ Package: \tab rkwarddev\cr Type: \tab
-  Package\cr Version: \tab 0.03-7\cr Date: \tab
-  2011-10-18\cr Depends: \tab R (>= 2.9.0),XiMpLe,rkward
+  Package\cr Version: \tab 0.03-8\cr Date: \tab
+  2011-10-19\cr Depends: \tab R (>= 2.9.0),XiMpLe,rkward
   (>= 0.5.7)\cr Enhances: \tab rkward\cr Encoding: \tab
   UTF-8\cr License: \tab GPL (>= 3)\cr LazyLoad: \tab
   yes\cr URL: \tab http://rkward.sourceforge.net\cr }

Modified: trunk/rkward/packages/rkwarddev/man/show-methods.Rd
===================================================================
--- trunk/rkward/packages/rkwarddev/man/show-methods.Rd	2011-10-19 16:02:19 UTC (rev 3972)
+++ trunk/rkward/packages/rkwarddev/man/show-methods.Rd	2011-10-19 16:03:47 UTC (rev 3973)
@@ -4,6 +4,7 @@
 \alias{show,rk.JS.arr-method}
 \alias{show,rk.JS.ite-method}
 \alias{show,rk.JS.opt-method}
+\alias{show,rk.JS.var-method}
 \title{Show methods for objects of class rk.JS.S}
 \arguments{
   \item{object}{An object of class \code{rk.JS.*}}

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