[Sciviews-commits] r306 - in pkg/svGUI: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Sat Sep 11 12:02:01 CEST 2010


Author: phgrosjean
Date: 2010-09-11 12:02:01 +0200 (Sat, 11 Sep 2010)
New Revision: 306

Added:
   pkg/svGUI/man/svGUI-package.Rd
Modified:
   pkg/svGUI/DESCRIPTION
   pkg/svGUI/NEWS
   pkg/svGUI/R/guiInstall.R
   pkg/svGUI/R/guiRefresh.R
   pkg/svGUI/R/guiUninstall.R
   pkg/svGUI/R/httpServer.R
   pkg/svGUI/R/koCmd.R
   pkg/svGUI/R/svGUI-internal.R
   pkg/svGUI/TODO
   pkg/svGUI/man/guiInstall.Rd
   pkg/svGUI/man/guiRefresh.Rd
   pkg/svGUI/man/httpServer.Rd
   pkg/svGUI/man/koCmd.Rd
Log:
HTTP server now uses parseText() of svMisc >= 0.9-60 instead of Parse()
added a svGUI-package help page
Stylistic reworking of code and help pages

Modified: pkg/svGUI/DESCRIPTION
===================================================================
--- pkg/svGUI/DESCRIPTION	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/DESCRIPTION	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,14 +1,14 @@
 Package: svGUI
 Type: Package
 Title: SciViews GUI API - Functions to manage GUI client
-Depends: R (>= 2.11.0), svMisc
+Depends: R (>= 2.11.0), svMisc (>= 0.9-60)
 Imports: tools
-Suggests: svSocket (>= 0.9-48)
+Suggests: svSocket (>= 0.9-50)
 SystemRequirements: Komodo Edit (http://www.openkomodo.com), SciViews-K (http://www.sciviews.org/SciViews-K)
 Description: Functions to manage the GUI client, like Komodo with the
   SciViews-K extension
-Version: 0.9-48
-Date: 2010-08-30
+Version: 0.9-49
+Date: 2010-09-11
 Author: Philippe Grosjean
 Maintainer: Philippe Grosjean <phgrosjean at sciviews.org>
 License: GPL-2

Modified: pkg/svGUI/NEWS
===================================================================
--- pkg/svGUI/NEWS	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/NEWS	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,5 +1,11 @@
 = svGUI News
 
+== Changes in svGUI 0.9-49
+
+* HTTP server code processing now uses parseText() of svMisc >= 0.9-60 instead
+  of the deprecated Parse() function.
+
+
 == Changes in svGUI 0.9-48
 
 * koCmd() now should prepend <<<js>>> to the JavaScript code to get it evaluated

Modified: pkg/svGUI/R/guiInstall.R
===================================================================
--- pkg/svGUI/R/guiInstall.R	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/R/guiInstall.R	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,8 +1,8 @@
-"guiInstall" <-
-function ()
+guiInstall <- function ()
 {
 	assignTemp(".guiCmd", function(command, ...) {
-		command <- switch(command, ## TODO: define these commands
+		## TODO: define these commands
+		command <- switch(command,
 			load = "",
 			source = "",
 			save = "",
@@ -13,28 +13,31 @@
 			"")
 	})
 	assignTemp(".guiObjBrowse", function(id, data) {
-		koCmd('sv.objBrowse("<<<id>>>", "<<<dat>>>");', list(id = id, dat = data))
+		koCmd('sv.objBrowse("<<<id>>>", "<<<dat>>>");',
+		list(id = id, dat = data))
 	})
 	assignTemp(".guiObjInfo", function(id, data) {
-		koCmd('sv.objInfo("<<<id>>>", "<<<dat>>>");', list(id = id, dat = data))
+		koCmd('sv.objInfo("<<<id>>>", "<<<dat>>>");',
+		list(id = id, dat = data))
 	})
 	assignTemp(".guiObjMenu", function(id, data) {
-		koCmd('sv.objMenu("<<<id>>>", "<<<dat>>>");', list(id = id, dat = data))
+		koCmd('sv.objMenu("<<<id>>>", "<<<dat>>>");',
+		list(id = id, dat = data))
 	})
 
-	# Functions specific to Komodo as a GUI client
+	## Functions specific to Komodo as a GUI client
 	assignTemp(".koCmd", function(command, ...) {
-		# This mechanism avoids dependence on svGUI for packages that provide
-		# functionalities that work with or without Komodo (like svUnit)
-		# Instead of calling koCmd() directly, we look if .koCmd is defined
-		# in tempenv and we run it.
-		# This allows also redefining koCmd() without changing code in the
-		# packages that depend on .koCmd()
+		## This mechanism avoids dependence on svGUI for packages that provide
+		## functionalities that work with or without Komodo (like svUnit)
+		## Instead of calling koCmd() directly, we look if .koCmd is defined
+		## in tempenv and we run it.
+		## This allows also redefining koCmd() without changing code in the
+		## packages that depend on .koCmd()
 		koCmd(command, ...)
 	})
 
-	# Register a TaskCallback to generate automatically informations for an
-	# object browser.
+	## Register a TaskCallback to generate automatically informations for an
+	## object browser.
 	h <- getTemp(".svTaskCallbackManager", default = NULL, mode = "list")
 	if (!is.null(h))
 		h$add(guiAutoRefresh, name = "guiAutoRefresh")

Modified: pkg/svGUI/R/guiRefresh.R
===================================================================
--- pkg/svGUI/R/guiRefresh.R	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/R/guiRefresh.R	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,3 +1,4 @@
+## TODO: rework this!
 .active.data.frame <- list(object = "",
     fun = function () {
         if (exists(.active.data.frame$object, envir = .GlobalEnv)) {
@@ -8,34 +9,37 @@
         } else return(.active.data.frame$cache <<- NULL)       
 	}, cache = "")
 
-guiRefresh <- function (force = FALSE) {    
-    # Refresh active items and the R Objects explorer
-    # If force == TRUE, do not compare with the cache
-    # Active items are represented by .active.xxx objects in .GlobalEnv
+guiRefresh <- function (force = FALSE)
+{    
+    ## Refresh active items and the R Objects explorer
+    ## If force == TRUE, do not compare with the cache
+    ## Active items are represented by .active.xxx objects in .GlobalEnv
     aObjs <- ls(pattern = "^\\.active\\.", envir = .GlobalEnv, all.names = TRUE)
     for (item in aObjs) {
         obj <- get(item, envir = .GlobalEnv, inherits = FALSE)
         if (mode(obj) == "list") {
             objclass <- sub("^\\.active\\.", "", item)
-            # JavaScript does not accept dots in function names. So, we have
-            # to remove them from class name (eg., data.frame => dataframe)
+            ## JavaScript does not accept dots in function names. So, we have
+            ## to remove them from class name (eg., data.frame => dataframe)
             objclass <- gsub("\\.", "", objclass)
             cache <- obj$cache
             res <- obj$fun()
-            if (is.null(res)) # Active object not found, remove obj
+            if (is.null(res))  # Active object not found, remove obj
                 rm(list = item, envir = .GlobalEnv)
-            if (isTRUE(force) || !identical(res, cache)) # Refresh in Komodo
+            if (isTRUE(force) || !identical(res, cache))  # Refresh in Komodo
                 koCmd(paste('sv.r.obj_refresh_', objclass, '("<<<data>>>");',
                     sep = ""), data = res)
         }
     }
-    # Make sure to clear active data frame and active lm object in case none
-    # are defined in the current session
+    
+	## Make sure to clear active data frame and active lm object in case none
+    ## are defined in the current session
     if (!".active.data.frame" %in% aObjs)
         koCmd('sv.r.obj_refresh_dataframe("<<<data>>>");');
     if (!".active.lm" %in% aObjs)
         koCmd('sv.r.obj_refresh_lm("<<<data>>>");');        
-    # Refresh object browser (only data from .GlobalEnv)
+    
+	## Refresh object browser (only data from .GlobalEnv)
     lst <- objList(envir = .GlobalEnv, all.info = FALSE, compare = TRUE)
     if (length(lst$Name) > 0) {
         msg <- paste("Env=.GlobalEnv\nObj=\n", 
@@ -46,7 +50,8 @@
     return(TRUE)
 }
 
-guiAutoRefresh <- function (...) {
+guiAutoRefresh <- function (...)
+{
     try(guiRefresh(force = FALSE), silent = TRUE)
-    return(TRUE) # We need to return TRUE for callback reschedule
-}
\ No newline at end of file
+    return(TRUE)  # We need to return TRUE for callback reschedule
+}

Modified: pkg/svGUI/R/guiUninstall.R
===================================================================
--- pkg/svGUI/R/guiUninstall.R	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/R/guiUninstall.R	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,7 +1,6 @@
-"guiUninstall" <-
-function ()
+guiUninstall <- function ()
 {
-	# Eliminate .guiCmd
+	## Eliminate .guiCmd
 	rmTemp(".guiCmd")
 	rmTemp(".guiObjBrowse")
 	rmTemp(".guiObjInfo")
@@ -9,7 +8,7 @@
 
 	rmTemp(".koCmd")
 
-	# Unregister our own TaskCallback
+	## Unregister our own TaskCallback
 	h <- getTemp(".svTaskCallbackManager", default = NULL, mode = "list")
 	if (!is.null(h))
 		h$remove("guiAutoRefresh")

Modified: pkg/svGUI/R/httpServer.R
===================================================================
--- pkg/svGUI/R/httpServer.R	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/R/httpServer.R	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,91 +1,92 @@
-# A SciViews R server using HTTP R help server and JSONP for communcation
-# Copyright (c) 2010, Ph. Grosjean (phgrosjean at sciviews.org)
-# Use a HTTP request like this in the client:
-# http://127.0.0.1:8888/custom/SciViews?msg&callback
-# We must return something like (in a correct RJSONp object):
-#<callback>({"result":{"String 1", "String 2", "..."}, "options":"<options>",
-#"name":"<server.name>","port":"<port>"})
-# Another (simpler) way to call it is by using
-# http://127.0.0.1:8888/custom/SciViews?msg
-# and in this case, the client must manage the simple string returned
+## A SciViews R server using HTTP R help server and JSONP for communcation
+## Copyright (c) 2010, Ph. Grosjean (phgrosjean at sciviews.org)
+## Use a HTTP request like this in the client:
+## http://127.0.0.1:8888/custom/SciViews?msg&callback
+## We must return something like (in a correct RJSONp object):
+## <callback>({"result":{"String 1", "String 2", "..."}, "options":"<options>",
+## "name":"<server.name>","port":"<port>"})
+## Another (simpler) way to call it is by using
+## http://127.0.0.1:8888/custom/SciViews?msg
+## and in this case, the client must manage the simple string returned
 
-# Get the list of all names of clients that already connected to the http server
-"HttpClientsNames" <- function ()
+## Get list of all names of clients that already connected to the http server
+HttpClientsNames <- function ()
 	sub("^HttpClient_", "", ls(envir = TempEnv(), pattern = "^HttpClient_"))
 
-# Get or change the port of the http server
-"HttpServerPort" <- function (port)
+## Get or change the port of the http server
+HttpServerPort <- function (port)
 {
 	if (!missing(port)) {
 		port <- as.integer(round(port[1]))
-		# This port is stored in 'ko.serve' option
+		## This port is stored in 'ko.serve' option
 		options(ko.serve = port)
-		# If the server is running on another port, restart it now
+		## If the server is running on another port, restart it now
 		curport <- tools:::httpdPort
 		if (curport > 0 && curport != port) startHttpServer(port = port)
 		return(port)
-	} else { # Get the server port
+	} else {  # Get the server port
 		port <- getOption("ko.serve")
 		if (is.null(port)) port <- 8888 else port <- as.integer(round(port[1]))
 		return(port)
 	}
 }
 
-# Get or change the name of the HTTP server
-"HttpServerName" <- function (name)
+## Get or change the name of the HTTP server
+HttpServerName <- function (name)
 {
 	if (!missing(name)) {
 		if (!is.character(name)) stop("'name' must be a string!")
 		name <- as.character(name)[1]
-		# This name is stored in the option R.id
+		## This name is stored in the option R.id
 		options(R.id = name)
 		return(name)
-	} else { # Get the server name
+	} else {  # Get the server name
 		name <- getOption("R.id")
 		if (is.null(name)) name <- "R"
 		return(name)
 	}
 }
 
-# Get or change http server options
-"parHttp" <- function (client, ...)
+## Get or change http server options
+parHttp <- function (client, ...)
 {
-	if (missing(client)) client <- "default" else client <- as.character(client)[1]
+	if (missing(client)) client <- "default" else
+		client <- as.character(client)[1]
 	
-	# Set or get parameters for a given HTTP client
+	## Set or get parameters for a given HTTP client
 	serverport <- HttpServerPort()
 	
-	# No attempt is made to make sure this client exists
+	## No attempt is made to make sure this client exists
 	sc <- paste("HttpClient", client, sep = "_")
 	if (!exists(sc, envir = TempEnv(), inherits = FALSE,
 		mode = "environment")) {
-		# Create a new environment with default values
+		## Create a new environment with default values
 		e <- new.env(parent = TempEnv())
 		e$client <- client
 		e$serverport <- serverport
 		e$prompt <- ":> "    # Default prompt
 		e$continue <- ":+ "  # Default continuation prompt
-		e$code <- ""        # Current partial code for multiline mode
-		e$last <- ""        # String to add at the end of evaluations
-		e$echo <- FALSE     # Don't echo commands to the console
-		e$flag <- FALSE     # Do not flag pieces of code (not used yet!)
-		e$multiline <- TRUE # Allow for multiline code
-		e$bare <- TRUE      # Always start in "bare" mode
-		# Note: in bare mode, all other parameters are inactive!
-		# and assign it to TempEnv
+		e$code <- ""         # Current partial code for multiline mode
+		e$last <- ""         # String to add at the end of evaluations
+		e$echo <- FALSE      # Don't echo commands to the console
+		e$flag <- FALSE      # Do not flag pieces of code (not used yet!)
+		e$multiline <- TRUE  # Allow for multiline code
+		e$bare <- TRUE       # Always start in "bare" mode
+		## Note: in bare mode, all other parameters are inactive!
+		## and assign it to TempEnv
 		assign(sc, e, envir = TempEnv())
 	} else e <- get(sc, envir = TempEnv(), mode = "environment")
 	
-	# Change or add parameters if they are provided
+	## Change or add parameters if they are provided
 	args <- list(...)
 	if (l <- length(args)) {
 		change.par <- function (x, val, env) {
-			if (is.null(x)) return(FALSE)    # Do nothing without a valid name
+			if (is.null(x)) return(FALSE)  # Do nothing without a valid name
 			if (is.null(val)) {
-				suppressWarnings(rm(list = x, envir = env))   # Remove it
+				suppressWarnings(rm(list = x, envir = env))  # Remove it
 				return(TRUE)
 			}
-			env[[x]] <- val    # Add or change this variable in the environment
+			env[[x]] <- val  # Add or change this variable in the environment
 			return(TRUE)
 		}
 		n <- names(args)
@@ -94,49 +95,50 @@
 		if (any(!res)) warning("Non named arguments are ignored")
 	}
 	
-	# If serverport has changed, update it now
+	## If serverport has changed, update it now
 	if (e$serverport != serverport) e$serverport <- serverport
 	
-	# Return e invisibly
+	## Return e invisibly
 	return(invisible(e))
 }
 
-# Stop the SciViews and R HTTP server and eliminate all tracks
-"stopHttpServer" <- function (remove.clients = FALSE) {
-	# Eliminate the SciViews custom process function for HTTP server
+## Stop the SciViews and R HTTP server and eliminate all tracks
+stopHttpServer <- function (remove.clients = FALSE)
+{
+	## Eliminate the SciViews custom process function for HTTP server
 	e <- tools:::.httpd.handlers.env
 	if ("SciViews" %in% ls(envir = e)) rm(list = "SciViews", envir = e)
 	
-	# Do we also remove persistent data for clients?
+	## Do we also remove persistent data for clients?
 	if (isTRUE(remove.clients))
 		rm(list = ls(envir = TempEnv(), pattern = "^HttpClient_"),
 			envir = TempEnv())
 	
-	# Stop the HTTP deamon
+	## Stop the HTTP deamon
 	tools::startDynamicHelp(FALSE)
 }
 
-# (Re)start HTTP help server on the choosen port
-# TODO: allowing asking and returning results in the RJSON object
-# TODO: conversion to UTF-8 encoding of the returned string
-"startHttpServer" <- function (port = HttpServerPort(),
+## (Re)start HTTP help server on the choosen port
+## TODO: allowing asking and returning results in the RJSON object
+## TODO: conversion to UTF-8 encoding of the returned string
+startHttpServer <- function (port = HttpServerPort(),
 name = HttpServerName())
 {
 	if (!is.character(name)) stop("'name' must be a string!")
 	name <- as.character(name)[1]
 	
-	# The port on which we want to run it
+	## The port on which we want to run it
 	if (!is.numeric(port[1]) || port[1] < 1)
 		stop("'port' must be a positive integer!")
 	port <- as.integer(round(port[1]))
-	# The port on which the server currently runs
+	## The port on which the server currently runs
 	curport <- tools:::httpdPort
 	
-	# Can we run the server?
+	## Can we run the server?
 	if (curport == -1L || nzchar(Sys.getenv("R_DISABLE_HTTPD")))
 		stop("R http server is disabled or cannot start")
 	
-	# If it is currently running, stop it now
+	## If it is currently running, stop it now
 	if (curport != 0L) {
 		if (curport != port)
 			warning("R http server currently running on port ", curport,
@@ -144,7 +146,7 @@
 		curport <- stopHttpServer()
 	}
 	
-	# Start the http server on the right port
+	## Start the http server on the right port
 	if (curport == 0L) {
 		oports <- getOption("help.ports")
 		(on.exit(options(help.ports = oports)))
@@ -152,53 +154,54 @@
 		curport <- tools::startDynamicHelp()
 	} else stop("Unable to start the http server")
 	
-	# Is the HTTP server running on the right port now?
+	## Is the HTTP server running on the right port now?
 	if (curport == port) {
-		# Set the name of the HTTP server (for easier identification)
+		## Set the name of the HTTP server (for easier identification)
 		HttpServerName(name)
 		
-		# Install the SciViews function that will process our requests
+		## Install the SciViews function that will process our requests
 		e <- tools:::.httpd.handlers.env
 		e[["SciViews"]] <- function (path, query, body) {
-			# Analyze the query: command + callback
+			## Analyze the query: command + callback
 			#cat(query, "\n", sep = " -- ")
 			msg <- query[1]
 			l <- length(query)
 			if (l > 1) callback <- query[l] else callback <- NULL
 			
-			# Get the server name and port, and R encoding
+			## Get the server name and port, and R encoding
 			servername <- HttpServerName()
 			serverport <- HttpServerPort()
 			
-			# Process the command in a similar way as processSocket() does
-			# in the svSocket package... but return a RJSONP object if callback is not NULL
-			# We use a custom function here to create this object faster than
-			# by converting an R object to RJSON
+			## Process the command in a similar way as processSocket() does
+			## in the svSocket package... but return a RJSONP object if callback
+			## is not NULL.
+			## We use a custom function here to create this object faster than
+			## by converting an R object to RJSON.
 			Rjsonp <- function (res, callback) {
-				# If no echo, return only a basic RJSONP object
+				## If no echo, return only a basic RJSONP object
 				if (!returnResults || is.null(res)) {
 					obj <- paste(callback,
 						'(list("result" := NA, ',
 						'"options" := list("echo" := FALSE), "name" := "',
 						servername, '", "port" := ', serverport, '))', sep = "")
 				} else {
-					# Return a more consistent RJSONP object
-					# Format main client options as a RJSON object
+					## Return a more consistent RJSONP object
+					## Format main client options as a RJSON object
 					options <- paste('list("echo" := ', pars$echo,
 						', "bare" := ', pars$bare,
 						', "partial" := ', (pars$code != ""), ')', sep = "")
 					
-					# Replace \n by \\n, etc. in res
+					## Replace \n by \\n, etc. in res
 					#res <- gsub("\n", "\\n", res, fixed = TRUE)
 					res <- encodeString(res, quote = '"')
 					
-					# Check encoding and provide it if it is not UTF-8
+					## Check encoding and provide it if it is not UTF-8
 					cs <- localeToCharset()[1]
 					if (cs != "UTF-8") {
 						encode <- paste (', "encoding" := "', cs, '"', sep = "")
 					} else encode <- ""
 					
-					# Format the answer as a RJSONP object and return it
+					## Format the answer as a RJSONP object and return it
 					obj <- paste(callback, '(list("result" := c(',
 						paste(shQuote(res, type = "cmd"), collapse = ", "),
 						'), "options" := ', options,
@@ -209,40 +212,41 @@
 				return(list(obj))
 			}
 			
-			# Do we receive an <<<id=myID>>> sequence (name of the client)?
+			## Do we receive an <<<id=myID>>> sequence (name of the client)?
 			if (regexpr("^<<<id=[a-zA-Z0-9]+>>>", msg) > 0) {
-				# get the identifier
+				## Get the identifier
 				client <- sub("^<<<id=([a-zA-Z0-9]+)>>>.*$", "\\1", msg)
-				# and eliminate that sequence
+				## ... and eliminate that sequence
 				msg <- sub("^<<<id=[a-zA-Z0-9]+>>>", "", msg)
 			} else {
-				# The client name is simply 'default'
+				## The client name is simply 'default'
 				client <- "default"
 			}
 			
-			# Do we receive <<<esc>>>? => break (currently, only break multiline mode)
+			## Do we receive <<<esc>>>? => break (currently, only breaks
+			## multiline mode)
 			if (substr(msg, 1, 9) == "<<<esc>>>") {
-				pars <- parHttp(client, code = "") # Reset multiline code
+				pars <- parHttp(client, code = "")  # Reset multiline code
 				msg <- substr(msg, 10, 1000000)
 			}
 			
-			# Replace <<<n>>> by \n (for multiline code)
+			## Replace <<<n>>> by \n (for multiline code)
 			msg <- gsub("<<<n>>>", "\n", msg)
 			
-			# Replace <<<s>>> by the corresponding client identifier and server port
+			## Replace <<<s>>> by the corresponding client id and server port
 			msg <- gsub("<<<s>>>", paste('"', client, '", ', serverport,
 				sep = ""), msg)
 			
 			hiddenMode <- FALSE
 			returnResults <- TRUE
-			# If msg starts with <<<Q>>> or <<<q>>>, then disconnect server
-			# before or after evaluation of the command, respectively
-			# Since we always disconnect AFTER with http server, these options
-			# have no effect here. They are used with the socket server only
-			# If msg starts with <<<e>>>, evaluate command in the console and
-			# disconnect
-			# If msg starts with <<<h>>> or <<<H>>>, evaluate in hidden mode
-			# and disconnect
+			## If msg starts with <<<Q>>> or <<<q>>>, then disconnect server
+			## before or after evaluation of the command, respectively
+			## Since we always disconnect AFTER with http server, these options
+			## have no effect here. They are used with the socket server only
+			## If msg starts with <<<e>>>, evaluate command in the console and
+			## disconnect
+			## If msg starts with <<<h>>> or <<<H>>>, evaluate in hidden mode
+			## and disconnect
 			startmsg <- substr(msg, 1, 7)
 			if (startmsg == "<<<Q>>>") {
 				msg <- substr(msg, 8, 1000000)
@@ -252,32 +256,32 @@
 				parHttp(client, last = "")
 			} else if (startmsg == "<<<e>>>") {
 				msg <- substr(msg, 8, 1000000)
-				# We just configure the server correctly
+				## We just configure the server correctly
 				parHttp(client, bare = FALSE, echo = TRUE, prompt = ":> ",
 					continue = ":+ ", multiline = TRUE, last = "")
-				# Add a command to the command history
+				## Add a command to the command history
 				#timestamp("my R command", "", "", quiet = TRUE)
 			} else if (startmsg == "<<<h>>>") {
 				msg <- substr(msg, 8, 1000000)
-				# Do not echo command on the server (silent execution)
+				## Do not echo command on the server (silent execution)
 				hiddenMode <- TRUE
 				parHttp(client, bare = TRUE, last = "")
 			} else if (startmsg == "<<<H>>>") {
 				msg <- substr(msg, 8, 1000000)
-				# Do not echo command on the server
+				## Do not echo command on the server
 				hiddenMode <- TRUE
 				returnResults <- FALSE
 				parHttp(client, bare = TRUE)
 			} else if (startmsg == "<<<u>>>") {
 				msg <- substr(msg, 8, 1000000)
-				# Silent execution, nothing is returned to the client
-				# (but still echoed to the server)
+				## Silent execution, nothing is returned to the client
+				## (but still echoed to the server)
 				hiddenMode <- FALSE
 				returnResults <- FALSE
 				parHttp(client, bare = TRUE)
 			}
 			
-			# Get parameters for the client
+			## Get parameters for the client
 			pars <- parHttp(client)
 			if (Bare <- pars$bare) {
 				Prompt <- ""
@@ -293,14 +297,14 @@
 					if (pars$code == "") Pre <- Prompt else Pre <- Continue
 					cat(Pre, msg, "\n", sep = "")
 				}
-				# Add previous content if we were in multiline mode
+				## Add previous content if we were in multiline mode
 				msg <- paste(pars$code, msg, sep = "\n")
-				pars$code <- "" # This changes the original data too!
+				pars$code <- ""  # This changes the original data too!
 			}
 			
-			# Parse the R code
-			expr <- Parse(msg)
-			# Is it a wrong code?
+			## Parse the R code
+			expr <- parseText(msg)
+			## Is it a wrong code?
 			if (inherits(expr, "try-error")) {
 			    res <- paste(ngettext(1, "Error: ", "", domain = "R"),
 			    sub("^[^:]+: ([^\n]+)\n[0-9]+:(.*)$", "\\1\\2", expr), sep = "")
@@ -308,12 +312,13 @@
 			    if (is.null(callback)) {
 					return(paste(res, pars$last, Prompt, sep = ""))
 				} else {
-					return(Rjsonp(paste(res, pars$last, Prompt, sep = ""), callback))
+					return(Rjsonp(paste(res, pars$last, Prompt, sep = ""),
+						callback))
 				}
 			}
-			# Is it incomplete code?
+			## Is it incomplete code?
 			if (!is.expression(expr)) {
-				# Is multiline mode allowed?
+				## Is multiline mode allowed?
 				if (!Bare && pars$multiline) {
 					pars$code <- msg
 					if (is.null(callback)) {
@@ -322,11 +327,13 @@
 						} else return(NULL)	
 					} else {
 						if (returnResults) {
-							return(Rjsonp(paste(pars$last, Continue, sep = ""), callback))
+							return(Rjsonp(paste(pars$last, Continue, sep = ""),
+								callback))
 						} else return(Rjsonp(NULL, callback))
 					}
-				} else {    # Multimode not allowed
-				    res <- paste(gettext("Error: incomplete command in single line mode"),
+				} else {  # Multimode not allowed
+				    res <- paste(
+						gettext("Error: incomplete command in single line mode"),
 						"\n", sep = "")
 					if (Echo) cat(res)
 					if (is.null(callback)) {
@@ -335,14 +342,15 @@
 						} else return(NULL)
 					} else {
 						if (returnResults) {
-							return(Rjsonp(paste(res, pars$last, Prompt, sep = ""), callback))
+							return(Rjsonp(paste(res, pars$last, Prompt,
+								sep = ""), callback))
 						} else return(Rjsonp(NULL, callback))
 					}
 				}
 			}
-			# Freeze parameters (unlinks from the environment)
+			## Freeze parameters (unlinks from the environment)
 			pars <- as.list(pars)
-			# Is it something to evaluate?
+			## Is it something to evaluate?
 			if (length(expr) < 1) {
 				if (is.null(callback)) {
 					return(paste(pars$last, Prompt, sep = ""))
@@ -350,16 +358,16 @@
 					return(Rjsonp(paste(pars$last, Prompt, sep = ""), callback))
 				}
 			}
-			# Correct code,... we evaluate it
+			## Correct code,... we evaluate it
 			## TODO: here, evaluate line by line and return result immediately!
 			results <- captureAll(expr)
-			# Should we run taskCallbacks?
+			## Should we run taskCallbacks?
 			if (!hiddenMode) {
 				h <- getTemp(".svTaskCallbackManager", default = NULL,
 					mode = "list")
 				if (!is.null(h)) h$evaluate()
 			}
-			# Collapse and add last and the prompt at the end
+			## Collapse and add last and the prompt at the end
 			results <- paste(results, collapse = "\n")
 			if (Echo) cat(results)
 			if (!returnResults) {
@@ -371,7 +379,7 @@
 			}
 			Prompt <- if (pars$bare) "" else pars$prompt
 			results <- paste(results, pars$last, Prompt, sep = "")
-			# Return the results in plain text, or RJSONP object
+			## Return the results in plain text, or RJSONP object
 			if (is.null(callback)) {
 				return(results)
 			} else {

Modified: pkg/svGUI/R/koCmd.R
===================================================================
--- pkg/svGUI/R/koCmd.R	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/R/koCmd.R	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,19 +1,18 @@
-"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,
+	type = c("js", "rjsonp", "output"), pad = NULL, ...)
 {
 
     type <- match.arg(type)
-	if (is.null(host)) host <- "localhost"	# Default value
-	if (is.null(port)) port <- 7052			# Idem
+	if (is.null(host)) host <- "localhost"  # Default value
+	if (is.null(port)) port <- 7052         # Idem
 	cmd <- gsub("\n", "\\\\n", cmd)
 	cmd <- paste(cmd, collapse = " ")
     if (is.na(cmd) || is.null(cmd) || length(cmd) == 0) {
 		warning("No command supplied in cmd argument")
 		return("")
     }
-    # Do we need to paste data in the command?
+    ## Do we need to paste data in the command?
 	if (!is.null(data)) {
 		"rework" <- function(data) {
 			data <- as.character(data)
@@ -24,16 +23,16 @@
 
 		n <- names(data)
 		if (is.null(n)) {
-			# We assume that we replace '<<<data>>>'
+			## We assume that we replace '<<<data>>>'
 			cmd <- gsub("<<<data>>>", rework(data), cmd)
 		} else {	# Named data
-			# We replace each <<<name>>> in turn
+			## We replace each <<<name>>> in turn
 			for (i in 1:length(n))
 				cmd <- gsub(paste("<<<", n[i], ">>>", sep = ""),
 					rework(data[[n[i]]]), cmd)
 		}
 	}
-	# What type of data do we send?
+	## What type of data do we send?
 	cmd <- switch(type,
 		js = paste("<<<js>>>", cmd, sep = ""),
 		rjsonp = paste("<<<rjsonp>>>", pad, "(",
@@ -41,11 +40,11 @@
 		cmd)
 		
 	otimeout <- getOption("timeout")
-	options(timeout = timeout) # Default timeout is 60 seconds
+	options(timeout = timeout)  # Default timeout is 60 seconds
 	tryCatch(con <- socketConnection(host = host, port = port, blocking = TRUE),
-			 warning = function(e) {
-				stop(simpleError("Komodo socket server is not available!", quote(koCmd)))
-				})
+		warning = function(e) {
+			stop(simpleError("Komodo socket server is not available!", quote(koCmd)))
+	})
     writeLines(cmd, con)
     res <- readLines(con)
     close(con)

Modified: pkg/svGUI/R/svGUI-internal.R
===================================================================
--- pkg/svGUI/R/svGUI-internal.R	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/R/svGUI-internal.R	2010-09-11 10:02:01 UTC (rev 306)
@@ -1,5 +1,4 @@
-".onLoad" <-
-function (lib, pkg)
+.onLoad <- function (lib, pkg)
 {
 	#serve <- getOption("ko.serve")
 	#if (!is.null(serve)) {
@@ -8,8 +7,7 @@
 	#}
 }
 
-".onUnload" <-
-function (libpath)
+.onUnload <- function (libpath)
 {
 	#serve <- getOption("ko.serve")
 	#if (!is.null(serve) && "package:svSocket" %in% search())
@@ -17,4 +15,4 @@
 	guiUninstall()
 }
 
-".packageName" <- "svGUI"
+.packageName <- "svGUI"

Modified: pkg/svGUI/TODO
===================================================================
--- pkg/svGUI/TODO	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/TODO	2010-09-11 10:02:01 UTC (rev 306)
@@ -3,8 +3,8 @@
 * A ko() function to manipulate komodo from the command line
   (+ correct installation under Mac OS X)
 
-* The svGUI-package.Rd man page
+* Rework thecode to manage active data frames
 
 * Write the whole API to access Komodo from R
 
-* Localize this package
\ No newline at end of file
+* Localize this package

Modified: pkg/svGUI/man/guiInstall.Rd
===================================================================
--- pkg/svGUI/man/guiInstall.Rd	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/man/guiInstall.Rd	2010-09-11 10:02:01 UTC (rev 306)
@@ -13,15 +13,16 @@
 }
 
 \value{
-  Nothing.
+  Returns nothing.
 }
 
 \details{
   The minimum instruction to install the communication with Komodo/SciViews-K
-  is to use: \code{options(ko.serve = 8888); require(svGUI)}. When the \code{ko.serve}
-  option is set, svGUI loads svSocket, starts the socket server litening to the
-  port you provide (8888 by default), and install the hooks and callbacks
-  required to fully communicate with Komodo.
+  (so called, SciViews Komodo) is to use:
+  \code{options(ko.serve = 8888); require(svGUI)}. When the \code{ko.serve}
+  option is set, svGUI loads svSocket, starts the socket server listening to the
+  port you have selected (8888 by default), and install the hooks and callbacks
+  required to communicate with SciViews Komodo.
 
   Before loading svGUI, you can also set \code{option(ko.port = 7052)} or
   another port number where the Komodo SciViews-K server is listening (7052 is
@@ -42,3 +43,5 @@
 \seealso{ \code{\link{koCmd}} }
 
 \keyword{misc}
+
+\concept{ interprocess commnunication Komodo }

Modified: pkg/svGUI/man/guiRefresh.Rd
===================================================================
--- pkg/svGUI/man/guiRefresh.Rd	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/man/guiRefresh.Rd	2010-09-11 10:02:01 UTC (rev 306)
@@ -10,12 +10,12 @@
 }
 \usage{
 guiRefresh(force = FALSE)
-guiAutoRefresh(...)
+guiAutoRefresh(\dots)
 }
 
 \arguments{
-  \item{force}{ Do we force refresh, even if data have not changed? }
-  \item{...}{ Any argument (ignored, but useful for \code{addTaskCallback()}) }
+  \item{force}{ do we force refresh, even if data have not changed? }
+  \item{\dots}{ any argument (ignored, but useful for \code{addTaskCallback()}). }
 }
 
 \value{
@@ -27,3 +27,5 @@
 \seealso{ \code{\link{koCmd}} }
 
 \keyword{misc}
+
+\concept{ interprocess commnunication Komodo }

Modified: pkg/svGUI/man/httpServer.Rd
===================================================================
--- pkg/svGUI/man/httpServer.Rd	2010-09-11 10:00:52 UTC (rev 305)
+++ pkg/svGUI/man/httpServer.Rd	2010-09-11 10:02:01 UTC (rev 306)
@@ -28,14 +28,14 @@
 \arguments{
   \item{port}{ port on which the server should run (both help and SciViews).
     By default, it is port 8888. Note that this server runs only locally and
-    can only serve requests from 127.0.0.1 }
+    can only serve requests from 127.0.0.1. }
   \item{name}{ the name given to the SciViews server. By default, it is
-    \code{R} }
-  \item{remove.clients}{ Do we remove also persistent data for the clients,
-    \code{FALSE} by default }
+    \code{R}. }
+  \item{remove.clients}{ do we remove also persistent data for the clients,
+    \code{FALSE} by default. }
   \item{client}{ the name of one client. A client that does not identify itself
-    is named \code{default} }
-  \item{\dots}{ named arguments specifying options to set or change }
+    is named \code{default}. }
+  \item{\dots}{ named arguments specifying options to set or change. }
 }
 
 \value{
@@ -58,3 +58,5 @@
 \seealso{ \code{\link[svSocket]{startSocketServer}} }
 
 \keyword{ IO }
+
+\concept{ interprocess commnunication Komodo }

[TRUNCATED]

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


More information about the Sciviews-commits mailing list