Thread: [R-gregmisc-users] SF.net SVN: r-gregmisc:[1314] trunk/gdata/R
Brought to you by:
warnes
|
From: <ar...@us...> - 2009-04-19 23:25:17
|
Revision: 1314
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1314&view=rev
Author: arnima
Date: 2009-04-19 23:25:04 +0000 (Sun, 19 Apr 2009)
Log Message:
-----------
Changed object.size(object) to unclass(object.size(object)).
Modified Paths:
--------------
trunk/gdata/R/env.R
trunk/gdata/R/ll.R
Modified: trunk/gdata/R/env.R
===================================================================
--- trunk/gdata/R/env.R 2009-02-16 15:34:40 UTC (rev 1313)
+++ trunk/gdata/R/env.R 2009-04-19 23:25:04 UTC (rev 1314)
@@ -3,7 +3,7 @@
get.object.size <- function(object.name, pos)
{
object <- get(object.name, pos=pos)
- size <- try(object.size(object), silent=TRUE)
+ size <- try(unclass(object.size(object)), silent=TRUE)
if(class(size) == "try-error")
size <- 0
return(size)
Modified: trunk/gdata/R/ll.R
===================================================================
--- trunk/gdata/R/ll.R 2009-02-16 15:34:40 UTC (rev 1313)
+++ trunk/gdata/R/ll.R 2009-04-19 23:25:04 UTC (rev 1314)
@@ -23,7 +23,7 @@
get.object.size <- function(object.name, pos)
{
object <- get(object.name, pos=pos)
- size <- try(object.size(object), silent=TRUE)
+ size <- try(unclass(object.size(object)), silent=TRUE)
if(class(size) == "try-error")
size <- 0
return(size)
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2010-01-22 12:45:31
|
Revision: 1370
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1370&view=rev
Author: warnes
Date: 2010-01-22 12:45:21 +0000 (Fri, 22 Jan 2010)
Log Message:
-----------
- Move xls2csv(), xls2tab(), xls2sep() to a separate file
- Move qQuote.ascii to a separate file
- Bug Fix: xls2csv(), xls2tab() failed to pass the provided 'perl'
parameter to xls2sep()
- New Feature: xls2sep() (and hence xls2csv, xls2tab, and read.xls)
now supports ftp URLs.
Modified Paths:
--------------
trunk/gdata/R/read.xls.R
Added Paths:
-----------
trunk/gdata/R/dQuote.ascii.R
trunk/gdata/R/sheetCount.R
trunk/gdata/R/xls2sep.R
Added: trunk/gdata/R/dQuote.ascii.R
===================================================================
--- trunk/gdata/R/dQuote.ascii.R (rev 0)
+++ trunk/gdata/R/dQuote.ascii.R 2010-01-22 12:45:21 UTC (rev 1370)
@@ -0,0 +1,9 @@
+## s$Id: read.xls.R 1342 2009-07-16 02:49:11Z warnes $
+
+## Double quote string using *ASCII* double quotes.
+##
+## (The base 'dQuote' uses local-specific quotes (e.g UTF-8 quotes)
+## which Unix command line doesn't like.)
+##
+dQuote.ascii <- function(x) paste('"',x,'"',sep='')
+
Modified: trunk/gdata/R/read.xls.R
===================================================================
--- trunk/gdata/R/read.xls.R 2009-12-06 22:34:29 UTC (rev 1369)
+++ trunk/gdata/R/read.xls.R 2010-01-22 12:45:21 UTC (rev 1370)
@@ -1,106 +1,5 @@
## s$Id$
-## Creating a temporary function to quote the string
-dQuote.ascii <- function(x) paste('"',x,'"',sep='')
-
-
-xls2csv <- function(xls, sheet=1, verbose=FALSE, ..., perl="perl")
- xls2sep(xls=xls, sheet=sheet, verbose=verbose, ..., method="csv",
- perl="perl")
-
-xls2tab <- function(xls, sheet=1, verbose=FALSE, ..., perl="perl")
- xls2sep(xls=xls, sheet=sheet, verbose=verbose, ..., method="tab",
- perl="perl")
-
-xls2sep <- function(xls, sheet = 1, verbose=FALSE, ...,
- method=c("csv","tab"), perl="perl")
- {
-
- method <- match.arg(method)
-
- ##
- ## directories
- package.dir <- .path.package('gdata')
- perl.dir <- file.path(package.dir,'perl')
- ##
-
- ##
- ## files
- tf <- NULL
- if (substring(xls, 1, 7) == "http://") {
- tf <- paste(tempfile(), "xls", sep = ".")
- if(verbose)
- cat("Downloading",
- dQuote.ascii(xls), " to ",
- dQuote.ascii(tf), "...\n")
- else
- cat("Downloading...\n")
- download.file(xls, tf, mode = "wb")
- cat("Done.\n")
- xls <- tf
- }
-
- if(file.access(xls, 4)!=0)
- stop("Unable to read xls file '", xls, "'." )
-
- if(method=="csv")
- {
- script <- file.path(perl.dir,'xls2csv.pl')
- targetFile <- paste(tempfile(), "csv", sep = ".")
- }
- else if(method=="tab")
- {
- script <- file.path(perl.dir,'xls2tab.pl')
- targetFile <- paste(tempfile(), "tab", sep = ".")
- }
- else
- {
- stop("Unknown method", method)
- }
-
- ##
- ##
-
- ##
- ## execution command
- cmd <- paste(perl, script, dQuote.ascii(xls), dQuote.ascii(targetFile),
- sheet, sep=" ")
- ##
- ##
-
- if(verbose)
- {
- cat("\n")
- cat("Converting xls file\n")
- cat(" ", dQuote.ascii(xls), "\n")
- cat("to", method, " file \n")
- cat(" ", dQuote.ascii(targetFile), "\n")
- cat("... \n\n")
- }
- else
- cat("Converting xls file to", method, "file... ")
-
- ##
- ## do the translation
- if(verbose) cat("Executing ", cmd, "... \n\n")
- #
- results <- system(cmd, intern=!verbose)
- #
- if (verbose) cat("Done.\n\n")
- #
- ##
-
- if(file.access(targetFile, 4)!=0)
- stop("Unable to read translated", method, "file '", targetFile, "'." )
-
- cat("Done.\n")
-
-
- ## prepare for cleanup now, in case of error reading file
- file(targetFile)
- }
-
-
read.xls <- function(xls, sheet = 1, verbose=FALSE, pattern, ...,
method=c("csv","tab"), perl="perl")
{
Added: trunk/gdata/R/sheetCount.R
===================================================================
--- trunk/gdata/R/sheetCount.R (rev 0)
+++ trunk/gdata/R/sheetCount.R 2010-01-22 12:45:21 UTC (rev 1370)
@@ -0,0 +1,58 @@
+sheetCount <- function(xls, verbose = FALSE, perl = "perl")
+{
+
+ ##
+ ## directories
+ package.dir <- .path.package('gdata')
+ perl.dir <- file.path(package.dir,'perl')
+ ##
+ ##
+
+ ##
+ ## files
+ tf <- NULL
+ if ( substring(xls, 1, 7) == "http://" ||
+ substring(xls, 1, 6) == "ftp://" )
+ {
+ tf <- paste(tempfile(), "xls", sep = ".")
+ if(verbose)
+ cat("Downloading",
+ dQuote.ascii(xls), " to ",
+ dQuote.ascii(tf), "...\n")
+ else
+ cat("Downloading...\n")
+ download.file(xls, tf, mode = "wb")
+ cat("Done.\n")
+ xls <- tf
+ }
+ ##
+
+ sc <- file.path(perl.dir,'sheetCount.pl')
+
+ ##
+ ##
+
+ ##
+ ## execution command
+ cmd <- paste(perl, sc, dQuote.ascii(xls), sep=" ")
+ ##
+ ##
+
+ ##
+ ## do the translation
+ if(verbose)
+ {
+ cat("\n")
+ cat("Extracting sheet count from\n")
+ cat(" ", dQuote.ascii(xls), "\n")
+ cat("... \n\n")
+ }
+ ##
+ results <- system(cmd, intern=TRUE)
+ ##
+ if (verbose) cat("Done.\n\n")
+
+ as.numeric(results)
+}
+
+
Copied: trunk/gdata/R/xls2sep.R (from rev 1342, trunk/gdata/R/read.xls.R)
===================================================================
--- trunk/gdata/R/xls2sep.R (rev 0)
+++ trunk/gdata/R/xls2sep.R 2010-01-22 12:45:21 UTC (rev 1370)
@@ -0,0 +1,100 @@
+## s$Id$
+
+xls2csv <- function(xls, sheet=1, verbose=FALSE, ..., perl="perl")
+ xls2sep(xls=xls, sheet=sheet, verbose=verbose, ..., method="csv",
+ perl=perl)
+
+xls2tab <- function(xls, sheet=1, verbose=FALSE, ..., perl="perl")
+ xls2sep(xls=xls, sheet=sheet, verbose=verbose, ..., method="tab",
+ perl=perl)
+
+xls2sep <- function(xls, sheet = 1, verbose=FALSE, ...,
+ method=c("csv","tab"), perl="perl")
+ {
+
+ method <- match.arg(method)
+
+ ##
+ ## directories
+ package.dir <- .path.package('gdata')
+ perl.dir <- file.path(package.dir,'perl')
+ ##
+
+ ##
+ ## files
+ tf <- NULL
+ if ( substring(xls, 1, 7) == "http://" ||
+ substring(xls, 1, 6) == "ftp://" )
+ {
+ tf <- paste(tempfile(), "xls", sep = ".")
+ if(verbose)
+ cat("Downloading",
+ dQuote.ascii(xls), " to ",
+ dQuote.ascii(tf), "...\n")
+ else
+ cat("Downloading...\n")
+ download.file(xls, tf, mode = "wb")
+ cat("Done.\n")
+ xls <- tf
+ }
+
+ if(file.access(xls, 4)!=0)
+ stop("Unable to read xls file '", xls, "'." )
+
+ if(method=="csv")
+ {
+ script <- file.path(perl.dir,'xls2csv.pl')
+ targetFile <- paste(tempfile(), "csv", sep = ".")
+ }
+ else if(method=="tab")
+ {
+ script <- file.path(perl.dir,'xls2tab.pl')
+ targetFile <- paste(tempfile(), "tab", sep = ".")
+ }
+ else
+ {
+ stop("Unknown method", method)
+ }
+
+ ##
+ ##
+
+ ##
+ ## execution command
+ cmd <- paste(perl, script, dQuote.ascii(xls), dQuote.ascii(targetFile),
+ dQuote.ascii(sheet), sep=" ")
+ ##
+ ##
+
+ if(verbose)
+ {
+ cat("\n")
+ cat("Converting xls file\n")
+ cat(" ", dQuote.ascii(xls), "\n")
+ cat("to", method, " file \n")
+ cat(" ", dQuote.ascii(targetFile), "\n")
+ cat("... \n\n")
+ }
+ else
+ cat("Converting xls file to", method, "file... ")
+
+ ##
+ ## do the translation
+ if(verbose) cat("Executing ", cmd, "... \n\n")
+ ##
+ results <- system(cmd, intern=!verbose)
+ ##
+ if (verbose) cat("Done.\n\n")
+ ##
+ ##
+
+ if(file.access(targetFile, 4)!=0)
+ stop("Unable to read translated", method, "file '", targetFile, "'." )
+
+ cat("Done.\n")
+
+
+ ## prepare for cleanup now, in case of error reading file
+ file(targetFile)
+ }
+
Property changes on: trunk/gdata/R/xls2sep.R
___________________________________________________________________
Added: svn:keywords
+ Author Date Id Revision
Added: svn:mergeinfo
+
Added: svn:eol-style
+ native
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2010-01-23 05:50:16
|
Revision: 1383
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1383&view=rev
Author: warnes
Date: 2010-01-23 05:50:10 +0000 (Sat, 23 Jan 2010)
Log Message:
-----------
Update to match new xls2csv.pl code, allow specification of sheets by name, support CSV and TAB delimited files using the same code, other minor changes.
Modified Paths:
--------------
trunk/gdata/R/read.xls.R
trunk/gdata/R/xls2sep.R
Modified: trunk/gdata/R/read.xls.R
===================================================================
--- trunk/gdata/R/read.xls.R 2010-01-23 05:45:13 UTC (rev 1382)
+++ trunk/gdata/R/read.xls.R 2010-01-23 05:50:10 UTC (rev 1383)
@@ -1,7 +1,7 @@
## s$Id$
read.xls <- function(xls, sheet = 1, verbose=FALSE, pattern, ...,
- method=c("csv","tab"), perl="perl")
+ method=c("csv","tsv","tab"), perl="perl")
{
con <- tfn <- NULL
on.exit({
@@ -15,13 +15,8 @@
xls <- path.expand(xls)
- ## translate from xls to csv/tab format (returns csv file name)
- if(method=="csv")
- con <- xls2csv(xls, sheet, verbose=verbose, ..., perl = perl)
- else if(method=="tab")
- con <- xls2tab(xls, sheet, verbose=verbose, ..., perl = perl)
- else
- stop("Unknown method", method)
+ ## translate from xls to csv/tsv/tab format (returns name of created file)
+ con <- xls2sep(xls, sheet, verbose=verbose, ..., method=method, perl = perl)
## load the csv file
open(con)
@@ -35,7 +30,7 @@
if(method=="csv")
retval <- read.csv(con, ...)
- else if (method=="tab")
+ else if (method %in% c("tsv","tab") )
retval <- read.delim(con, ...)
else
stop("Unknown method", method)
@@ -60,7 +55,7 @@
if(method=="csv")
retval <- read.csv(con, skip = idx[1]-1, ...)
- else if (method=="tab")
+ else if (method %in% c("tsv","tab") )
retval <- read.delim(con, skip = idx[1]-1, ...)
else
stop("Unknown method", method)
Modified: trunk/gdata/R/xls2sep.R
===================================================================
--- trunk/gdata/R/xls2sep.R 2010-01-23 05:45:13 UTC (rev 1382)
+++ trunk/gdata/R/xls2sep.R 2010-01-23 05:50:10 UTC (rev 1383)
@@ -9,7 +9,7 @@
perl=perl)
xls2sep <- function(xls, sheet = 1, verbose=FALSE, ...,
- method=c("csv","tab"), perl="perl")
+ method=c("csv","tsv","tab"), perl="perl")
{
method <- match.arg(method)
@@ -51,6 +51,11 @@
script <- file.path(perl.dir,'xls2tab.pl')
targetFile <- paste(tempfile(), "tab", sep = ".")
}
+ else if(method=="tsv")
+ {
+ script <- file.path(perl.dir,'xls2tsv.pl')
+ targetFile <- paste(tempfile(), "tsv", sep = ".")
+ }
else
{
stop("Unknown method", method)
@@ -89,7 +94,7 @@
##
if(file.access(targetFile, 4)!=0)
- stop("Unable to read translated", method, "file '", targetFile, "'." )
+ stop("Unable to read translated ", method, " file '", targetFile, "'." )
cat("Done.\n")
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2010-01-24 18:19:39
|
Revision: 1403
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1403&view=rev
Author: warnes
Date: 2010-01-24 18:19:33 +0000 (Sun, 24 Jan 2010)
Log Message:
-----------
Close connections when done.
Modified Paths:
--------------
trunk/gdata/R/read.xls.R
trunk/gdata/R/sheetCount.R
Modified: trunk/gdata/R/read.xls.R
===================================================================
--- trunk/gdata/R/read.xls.R 2010-01-24 18:17:26 UTC (rev 1402)
+++ trunk/gdata/R/read.xls.R 2010-01-24 18:19:33 UTC (rev 1403)
@@ -60,6 +60,8 @@
else
stop("Unknown method", method)
+ close(con)
+
cat("Done.\n")
}
retval
Modified: trunk/gdata/R/sheetCount.R
===================================================================
--- trunk/gdata/R/sheetCount.R 2010-01-24 18:17:26 UTC (rev 1402)
+++ trunk/gdata/R/sheetCount.R 2010-01-24 18:19:33 UTC (rev 1403)
@@ -57,6 +57,7 @@
results <- system(cmd, intern=TRUE)
tc <- textConnection(results)
results <- read.table(tc, as.is=TRUE, header=FALSE)
+ close(tc)
results <- unlist(results)
names(results) <- NULL
##
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2010-01-24 19:13:29
|
Revision: 1406
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1406&view=rev
Author: warnes
Date: 2010-01-24 19:13:22 +0000 (Sun, 24 Jan 2010)
Log Message:
-----------
Make read.xls() and xls2sep() quieter when verbose=FALSE
Modified Paths:
--------------
trunk/gdata/R/read.xls.R
trunk/gdata/R/xls2sep.R
Modified: trunk/gdata/R/read.xls.R
===================================================================
--- trunk/gdata/R/read.xls.R 2010-01-24 19:12:07 UTC (rev 1405)
+++ trunk/gdata/R/read.xls.R 2010-01-24 19:13:22 UTC (rev 1406)
@@ -25,8 +25,6 @@
{
if(verbose)
cat("Reading", method, "file ", dQuote.ascii(tfn), "...\n")
- else
- cat("Reading", method, "file... ")
if(method=="csv")
retval <- read.csv(con, ...)
@@ -35,23 +33,24 @@
else
stop("Unknown method", method)
- cat("Done.\n")
+ if(verbose)
+ cat("Done.\n")
}
else {
- cat("Searching for lines containing pattern ", pattern, "... ")
+ if(verbose)
+ cat("Searching for lines containing pattern ", pattern, "... ")
idx <- grep(pattern, readLines(con))
if (length(idx) == 0) {
warning("pattern not found")
return(NULL)
}
- cat("Done.\n")
+ if(verbose)
+ cat("Done.\n")
seek(con, 0)
if(verbose)
cat("Reading", method, "file ", dQuote.ascii(tfn), "...\n")
- else
- cat("Reading", method, "file... ")
if(method=="csv")
retval <- read.csv(con, skip = idx[1]-1, ...)
@@ -62,7 +61,8 @@
close(con)
- cat("Done.\n")
+ if(verbose)
+ cat("Done.\n")
}
retval
}
Modified: trunk/gdata/R/xls2sep.R
===================================================================
--- trunk/gdata/R/xls2sep.R 2010-01-24 19:12:07 UTC (rev 1405)
+++ trunk/gdata/R/xls2sep.R 2010-01-24 19:13:22 UTC (rev 1406)
@@ -35,10 +35,8 @@
cat("Downloading",
dQuote.ascii(xls), " to ",
dQuote.ascii(tf), "...\n")
- else
- cat("Downloading...\n")
download.file(xls, tf, mode = "wb")
- cat("Done.\n")
+ if(verbose) cat("Done.\n")
xls <- tf
}
@@ -88,8 +86,6 @@
cat(" ", dQuote.ascii(targetFile), "\n")
cat("... \n\n")
}
- else
- cat("Converting xls file to", method, "file... ")
##
## do the translation
@@ -104,7 +100,7 @@
if(file.access(targetFile, 4)!=0)
stop("Unable to read translated ", method, " file '", targetFile, "'." )
- cat("Done.\n")
+ if (verbose) cat("Done.\n")
## prepare for cleanup now, in case of error reading file
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2010-10-19 22:04:55
|
Revision: 1452
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1452&view=rev
Author: warnes
Date: 2010-10-19 22:04:49 +0000 (Tue, 19 Oct 2010)
Log Message:
-----------
Avoid use of file.access() which is unreliable on Windows network shares.
Modified Paths:
--------------
trunk/gdata/R/onAttach.R
trunk/gdata/R/xls2sep.R
Modified: trunk/gdata/R/onAttach.R
===================================================================
--- trunk/gdata/R/onAttach.R 2010-08-14 19:28:55 UTC (rev 1451)
+++ trunk/gdata/R/onAttach.R 2010-10-19 22:04:49 UTC (rev 1452)
@@ -1,8 +1,13 @@
.onAttach <- function(libname, pkgname)
{
show <- function(...)
- writeLines(strwrap( x=list(...), prefix="gdata: " ))
-
+ packageStartupMessage(
+ paste(
+ strwrap(x = list(...),
+ prefix = "gdata: "),
+ collapse="\n",sep="\n"
+ )
+ )
try(
{
Modified: trunk/gdata/R/xls2sep.R
===================================================================
--- trunk/gdata/R/xls2sep.R 2010-08-14 19:28:55 UTC (rev 1451)
+++ trunk/gdata/R/xls2sep.R 2010-10-19 22:04:49 UTC (rev 1452)
@@ -45,9 +45,6 @@
xls <- tf
}
- if(file.access(xls, 4)!=0)
- stop("Unable to read xls file '", xls, "'." )
-
if(method=="csv")
{
script <- file.path(perl.dir,'xls2csv.pl')
@@ -95,21 +92,29 @@
##
## do the translation
if(verbose) cat("Executing '", cmd, "'... \n\n")
- ##
- results <- system(cmd, intern=!verbose)
+
+ results <- try(system(cmd, intern=!verbose))
+
+ if(inherits(results, "try-error"))
+ stop( "Unable to read xls file '", xls, "':", results )
+
if(verbose) cat(results,"\n\n")
- ##
if (verbose) cat("Done.\n\n")
+
##
+ ## check that the target file was created
##
+ if(!file.exists(targetFile))
+ stop( "Intermediate file '", targetFile, "' missing!" )
- if(file.access(targetFile, 4)!=0)
- stop("Unable to read translated ", method, " file '", targetFile, "'." )
-
- if (verbose) cat("Done.\n")
+ ## Creae a file object to hand to the next stage..
+ retval <- try(file(targetFile))
+ if(inherits(retval, "try-error"))
+ stop("Unable to open intermediate file '", targetFile, "':",
+ retval)
- ## prepare for cleanup now, in case of error reading file
- file(targetFile)
+ return(retval)
+
}
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2011-04-15 20:25:30
|
Revision: 1468
http://r-gregmisc.svn.sourceforge.net/r-gregmisc/?rev=1468&view=rev
Author: warnes
Date: 2011-04-15 20:25:24 +0000 (Fri, 15 Apr 2011)
Log Message:
-----------
Fix errors on windows when R or Perl install path includes spaces by properly quoting the path.
Modified Paths:
--------------
trunk/gdata/R/installXLSXsupport.R
trunk/gdata/R/read.xls.R
trunk/gdata/R/sheetCount.R
trunk/gdata/R/xls2sep.R
Removed Paths:
-------------
trunk/gdata/R/dQuote.ascii.R
Deleted: trunk/gdata/R/dQuote.ascii.R
===================================================================
--- trunk/gdata/R/dQuote.ascii.R 2011-04-15 19:43:55 UTC (rev 1467)
+++ trunk/gdata/R/dQuote.ascii.R 2011-04-15 20:25:24 UTC (rev 1468)
@@ -1,9 +0,0 @@
-## s$Id: read.xls.R 1342 2009-07-16 02:49:11Z warnes $
-
-## Double quote string using *ASCII* double quotes.
-##
-## (The base 'dQuote' uses local-specific quotes (e.g UTF-8 quotes)
-## which Unix command line doesn't like.)
-##
-dQuote.ascii <- function(x) paste('"',x,'"',sep='')
-
Modified: trunk/gdata/R/installXLSXsupport.R
===================================================================
--- trunk/gdata/R/installXLSXsupport.R 2011-04-15 19:43:55 UTC (rev 1467)
+++ trunk/gdata/R/installXLSXsupport.R 2011-04-15 20:25:24 UTC (rev 1468)
@@ -24,7 +24,7 @@
##
## execution command
- cmd <- paste(perl, sc, sep=" ")
+ cmd <- paste(shQuote(perl), shQuote(sc), sep=" ")
##
Modified: trunk/gdata/R/read.xls.R
===================================================================
--- trunk/gdata/R/read.xls.R 2011-04-15 19:43:55 UTC (rev 1467)
+++ trunk/gdata/R/read.xls.R 2011-04-15 20:25:24 UTC (rev 1468)
@@ -33,7 +33,7 @@
if (missing(pattern))
{
if(verbose)
- cat("Reading", method, "file ", dQuote.ascii(tfn), "...\n")
+ cat("Reading", method, "file ", dQuote(tfn), "...\n")
if(method=="csv")
retval <- read.csv(con, ...)
@@ -59,7 +59,7 @@
seek(con, 0)
if(verbose)
- cat("Reading", method, "file ", dQuote.ascii(tfn), "...\n")
+ cat("Reading", method, "file ", dQuote(tfn), "...\n")
if(method=="csv")
retval <- read.csv(con, skip = idx[1]-1, ...)
Modified: trunk/gdata/R/sheetCount.R
===================================================================
--- trunk/gdata/R/sheetCount.R 2011-04-15 19:43:55 UTC (rev 1467)
+++ trunk/gdata/R/sheetCount.R 2011-04-15 20:25:24 UTC (rev 1468)
@@ -29,8 +29,8 @@
tf <- paste(tempfile(), "xls", sep = ".")
if(verbose)
cat("Downloading",
- dQuote.ascii(xls), " to ",
- dQuote.ascii(tf), "...\n")
+ dQuote(xls), " to ",
+ dQuote(tf), "...\n")
else
cat("Downloading...\n")
download.file(xls, tf, mode = "wb")
@@ -47,7 +47,7 @@
##
## execution command
- cmd <- paste(perl, sc, dQuote.ascii(xls), sep=" ")
+ cmd <- paste(shQuote(perl), shQuote(sc), shQuote(xls), sep=" ")
##
##
@@ -57,7 +57,7 @@
{
cat("\n")
cat("Extracting sheet information from\n")
- cat(" ", dQuote.ascii(xls), "\n")
+ cat(" ", dQuote(xls), "\n")
cat("... \n\n")
}
##
Modified: trunk/gdata/R/xls2sep.R
===================================================================
--- trunk/gdata/R/xls2sep.R 2011-04-15 19:43:55 UTC (rev 1467)
+++ trunk/gdata/R/xls2sep.R 2011-04-15 20:25:24 UTC (rev 1468)
@@ -38,8 +38,8 @@
tf <- paste(tempfile(), "xls", sep = ".")
if(verbose)
cat("Downloading",
- dQuote.ascii(xls), " to ",
- dQuote.ascii(tf), "...\n")
+ dQuote(xls), " to ",
+ dQuote(tf), "...\n")
download.file(xls, tf, mode = "wb")
if(verbose) cat("Done.\n")
xls <- tf
@@ -70,11 +70,11 @@
##
## execution command
- cmd <- paste(dQuote.ascii(perl),
- dQuote.ascii(script),
- dQuote.ascii(xls),
- dQuote.ascii(targetFile),
- dQuote.ascii(sheet),
+ cmd <- paste(shQuote(perl),
+ shQuote(script),
+ shQuote(xls),
+ shQuote(targetFile),
+ shQuote(sheet),
sep=" ")
##
##
@@ -83,9 +83,9 @@
{
cat("\n")
cat("Converting xls file\n")
- cat(" ", dQuote.ascii(xls), "\n")
+ cat(" ", dQuote(xls), "\n")
cat("to", method, " file \n")
- cat(" ", dQuote.ascii(targetFile), "\n")
+ cat(" ", dQuote(targetFile), "\n")
cat("... \n\n")
}
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2013-01-14 20:47:59
|
Revision: 1639
http://sourceforge.net/p/r-gregmisc/code/1639
Author: warnes
Date: 2013-01-14 20:47:57 +0000 (Mon, 14 Jan 2013)
Log Message:
-----------
Replace (obsolete) '.path.package' with 'find.package' function.
Modified Paths:
--------------
trunk/gdata/R/installXLSXsupport.R
trunk/gdata/R/sheetCount.R
trunk/gdata/R/xls2sep.R
trunk/gdata/R/xlsFormats.R
Modified: trunk/gdata/R/installXLSXsupport.R
===================================================================
--- trunk/gdata/R/installXLSXsupport.R 2012-12-14 22:50:47 UTC (rev 1638)
+++ trunk/gdata/R/installXLSXsupport.R 2013-01-14 20:47:57 UTC (rev 1639)
@@ -10,7 +10,7 @@
##
## directories
- package.dir <- .path.package('gdata')
+ package.dir <- find.package('gdata')
perl.dir <- file.path(package.dir,'perl')
##
##
Modified: trunk/gdata/R/sheetCount.R
===================================================================
--- trunk/gdata/R/sheetCount.R 2012-12-14 22:50:47 UTC (rev 1638)
+++ trunk/gdata/R/sheetCount.R 2013-01-14 20:47:57 UTC (rev 1639)
@@ -15,7 +15,7 @@
##
## directories
- package.dir <- .path.package('gdata')
+ package.dir <- find.package('gdata')
perl.dir <- file.path(package.dir,'perl')
##
##
Modified: trunk/gdata/R/xls2sep.R
===================================================================
--- trunk/gdata/R/xls2sep.R 2012-12-14 22:50:47 UTC (rev 1638)
+++ trunk/gdata/R/xls2sep.R 2013-01-14 20:47:57 UTC (rev 1639)
@@ -36,7 +36,7 @@
##
## directories
- package.dir <- .path.package('gdata')
+ package.dir <- find.package('gdata')
perl.dir <- file.path(package.dir,'perl')
##
Modified: trunk/gdata/R/xlsFormats.R
===================================================================
--- trunk/gdata/R/xlsFormats.R 2012-12-14 22:50:47 UTC (rev 1638)
+++ trunk/gdata/R/xlsFormats.R 2013-01-14 20:47:57 UTC (rev 1639)
@@ -10,7 +10,7 @@
##
## directories
- package.dir <- .path.package('gdata')
+ package.dir <- find.package('gdata')
perl.dir <- file.path(package.dir,'perl')
##
##
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2014-04-05 18:19:52
|
Revision: 1797
http://sourceforge.net/p/r-gregmisc/code/1797
Author: warnes
Date: 2014-04-05 18:19:49 +0000 (Sat, 05 Apr 2014)
Log Message:
-----------
Don't use gdata:::<foo> prefix to access gdata function <foo>
Modified Paths:
--------------
trunk/gdata/R/mapLevels.R
trunk/gdata/R/unknown.R
Modified: trunk/gdata/R/mapLevels.R
===================================================================
--- trunk/gdata/R/mapLevels.R 2014-04-05 17:01:31 UTC (rev 1796)
+++ trunk/gdata/R/mapLevels.R 2014-04-05 18:19:49 UTC (rev 1797)
@@ -99,7 +99,7 @@
print.levelsMap <- function(x, ...)
{
- x <- gdata:::.unlistLevelsMap(x)
+ x <- .unlistLevelsMap(x)
print(x, ...)
}
@@ -159,7 +159,7 @@
as.levelsMap <- function(x, check=TRUE, ...)
{
if(check)
- gdata:::.checkLevelsMap(x, method="raw")
+ .checkLevelsMap(x, method="raw")
class(x) <- "levelsMap"
unique(x, ...)
}
@@ -167,7 +167,7 @@
as.listLevelsMap <- function(x, check=TRUE)
{
if(check)
- gdata:::.checkListLevelsMap(x, method="raw")
+ .checkListLevelsMap(x, method="raw")
class(x) <- "listLevelsMap"
x
}
@@ -203,7 +203,7 @@
if(!is.list(x) || any(!sapply(x, FUN=is.levelsMap)))
stop(sprintf("'%s' must be %s a list of %s", xLab, also,
dQuote("levelsMap")))
- lapply(x, FUN=gdata:::.checkLevelsMap, method=method)
+ lapply(x, FUN=.checkLevelsMap, method=method)
}
### }}}
@@ -221,12 +221,12 @@
c.listLevelsMap <- function(..., sort=TRUE, recursive=FALSE)
{
x <- list(...)
- lapply(x, FUN=gdata:::.checkListLevelsMap, method="class")
+ lapply(x, FUN=.checkListLevelsMap, method="class")
x <- unlist(x, recursive=FALSE)
if(!recursive) {
class(x) <- "listLevelsMap"
} else {
- if(any(!sapply(x, FUN=gdata:::.isCharacterMap)))
+ if(any(!sapply(x, FUN=.isCharacterMap)))
stop(sprintf("can not combine integer %s", dQuote("levelsMaps")))
if(!is.null(names(x))) names(x) <- NULL
x <- unlist(x, recursive=FALSE)
@@ -252,7 +252,7 @@
unique.levelsMap <- function(x, incomparables=FALSE, ...)
{
## Find duplicates
- y <- gdata:::.unlistLevelsMap(x, ind=TRUE)
+ y <- .unlistLevelsMap(x, ind=TRUE)
## Duplicates for values and names combinations
test <- duplicated(cbind(y[[1]], names(y[[1]])),
incomparables=incomparables, ...)
@@ -296,7 +296,7 @@
if(any(!(class(x) %in% classX)))
stop(sprintf("'x' must be either: %s", paste(dQuote(classX), collapse=", ")))
- gdata:::.checkLevelsMap(x=value, method="class")
+ .checkLevelsMap(x=value, method="class")
## --- Mapping levels in x ---
Modified: trunk/gdata/R/unknown.R
===================================================================
--- trunk/gdata/R/unknown.R 2014-04-05 17:01:31 UTC (rev 1796)
+++ trunk/gdata/R/unknown.R 2014-04-05 18:19:49 UTC (rev 1797)
@@ -40,7 +40,7 @@
}
isUnknown.list <- function(x, unknown=NA, ...) {
- unknown <- gdata:::.unknownList(x=x, unknown=unknown)
+ unknown <- .unknownList(x=x, unknown=unknown)
x <- mapply(FUN="isUnknown", x=x, unknown=unknown, ..., SIMPLIFY=FALSE)
x
}
@@ -90,7 +90,7 @@
unknownToNA.list <- function(x, unknown, warning=FALSE, ...)
{
- unknown <- gdata:::.unknownList(x=x, unknown=unknown)
+ unknown <- .unknownList(x=x, unknown=unknown)
x <- mapply(FUN="unknownToNA", x=x, unknown=unknown, warning=warning,
SIMPLIFY=FALSE)
return(x)
@@ -148,7 +148,7 @@
NAToUnknown.list <- function(x, unknown, force=FALSE, call.=FALSE, ...)
{
- unknown <- gdata:::.unknownList(x=x, unknown=unknown)
+ unknown <- .unknownList(x=x, unknown=unknown)
x <- mapply(FUN="NAToUnknown", x=x, unknown=unknown, force=force,
call.=call., SIMPLIFY=FALSE)
x
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|
|
From: <wa...@us...> - 2015-04-25 07:57:23
|
Revision: 1960
http://sourceforge.net/p/r-gregmisc/code/1960
Author: warnes
Date: 2015-04-25 07:57:16 +0000 (Sat, 25 Apr 2015)
Log Message:
-----------
Add 'justify' argument to print and format object_sizes methods
Modified Paths:
--------------
trunk/gdata/R/humanReadable.R
trunk/gdata/R/object.size.R
Modified: trunk/gdata/R/humanReadable.R
===================================================================
--- trunk/gdata/R/humanReadable.R 2015-04-25 07:56:23 UTC (rev 1959)
+++ trunk/gdata/R/humanReadable.R 2015-04-25 07:57:16 UTC (rev 1960)
@@ -4,8 +4,7 @@
digits=1,
width=NULL,
sep=" ",
- justify = c("right", "left"),
- ...
+ justify = c("right", "left")
)
{
## --- Setup ---
Modified: trunk/gdata/R/object.size.R
===================================================================
--- trunk/gdata/R/object.size.R 2015-04-25 07:56:23 UTC (rev 1959)
+++ trunk/gdata/R/object.size.R 2015-04-25 07:57:16 UTC (rev 1960)
@@ -16,6 +16,7 @@
digits=1,
width=NULL,
sep=" ",
+ justify = c("right", "left"),
...)
{
print(format(x,
@@ -24,7 +25,8 @@
units=units,
digits=digits,
width=width,
- sep=sep),
+ sep=sep,
+ justify=justify),
quote=quote,
...)
@@ -39,6 +41,7 @@
digits=1,
width=NULL,
sep=" ",
+ justify = c("right", "left"),
...)
{
if( !missing(units) )
@@ -51,7 +54,8 @@
units=units,
digits=digits,
width=width,
- sep=sep
+ sep=sep,
+ justify=justify
)
}
else if( is.null(humanReadable) || humanReadable==FALSE )
@@ -62,7 +66,8 @@
units=units,
digits=digits,
width=width,
- sep=sep)
+ sep=sep,
+ justify=justify)
}
This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site.
|