[R-gregmisc-users] SF.net SVN: r-gregmisc:[1957] trunk/gdata
Brought to you by:
warnes
From: <wa...@us...> - 2015-04-25 05:54:38
|
Revision: 1957 http://sourceforge.net/p/r-gregmisc/code/1957 Author: warnes Date: 2015-04-25 05:54:28 +0000 (Sat, 25 Apr 2015) Log Message: ----------- Complete work on object.size(), object_sizes methods, and humanReadable. Modified Paths: -------------- trunk/gdata/NAMESPACE trunk/gdata/R/humanReadable.R trunk/gdata/R/object.size.R trunk/gdata/man/humanReadable.Rd trunk/gdata/man/object.size.Rd Added Paths: ----------- trunk/gdata/tests/test.humanReadable.R trunk/gdata/tests/test.humanReadable.Rout.save Modified: trunk/gdata/NAMESPACE =================================================================== --- trunk/gdata/NAMESPACE 2015-04-25 02:52:53 UTC (rev 1956) +++ trunk/gdata/NAMESPACE 2015-04-25 05:54:28 UTC (rev 1957) @@ -129,8 +129,11 @@ S3method(nobs, lm) # now provided by stats package ## Object size stuff -S3method(print, object_sizes) -S3method(c, object_sizes) +S3method(c, object_sizes) +S3method(as, object_sizes) +S3method(format, object_sizes) +S3method(is, object_sizes) +S3method(print, object_sizes) ## unknown stuff S3method(isUnknown, default) Modified: trunk/gdata/R/humanReadable.R =================================================================== --- trunk/gdata/R/humanReadable.R 2015-04-25 02:52:53 UTC (rev 1956) +++ trunk/gdata/R/humanReadable.R 2015-04-25 05:54:28 UTC (rev 1957) @@ -1,61 +1,89 @@ -humanReadable <- function(x, standard=c("SI", "IEC"), units, digits=1, width=3, sep=" ") +humanReadable <- function(x, + units="auto", + standard=c("IEC", "SI", "Unix"), + digits=1, + width=NULL, + sep=" ", + justify = c("right", "left"), + ... + ) { ## --- Setup --- - suffix.decimal <- c("B", "kB", "MB", "GB", "TB", "PB", "EB", "ZB", "YB") - suffix.binary <- c("B", "KiB", "MiB", "GiB", "TiB", "PiB", "EiB", "ZiB", "YiB") + suffix.SI <- c("B", "kB", "MB", "GB", "TB", "PB", "EB", "ZB", "YB") + suffix.IEC <- c("B", "KiB", "MiB", "GiB", "TiB", "PiB", "EiB", "ZiB", "YiB") + suffix.Unix <- c("B" , "K", "M", "G", "T", "P", "E", "Z", "Y") standard <- match.arg(standard) - + if(length(justify)==1) justfy <- c(justify, justify) + ## --- Functions --- .applyHuman <- function(x, base, suffix, digits, width, sep) { ## Which suffix should we use? n <- length(suffix) - for(i in 1:n) { - if(x >= base) { - if(i < n) x <- x / base - } else { - break - } - } + i <- pmax(pmin(floor(log(x, base)), n-1),0) + if(!is.finite(i)) i <- 0 + x <- x / base^i ## Formatting - if(is.null(width)) { ## the same formatting for all - x <- format(round(x=x, digits=digits), nsmall=digits) - } else { ## similar to ls, du, and df - lenX <- nchar(x) - if(lenX > width) { - digitsMy <- width - (lenX - (lenX - (nchar(round(x)) + 1))) - digits <- ifelse(digitsMy > digits, digits, digitsMy) - } - if(i == 1) digits <- 0 - x <- round(x, digits=digits) - } - paste(x, suffix[i], sep=sep) + if(is.null(width)) + ## the same formatting for all + x <- format(round(x=x, digits=digits), nsmall=digits) + else + { + ## similar to ls, du, and df + lenX <- nchar(x) + if(lenX > width) { + digits <- pmax( width - nchar(round(x)) - 1, 0) + } + if(i == 0) digits <- 0 + x <- round(x, digits=digits) + } + c(x, suffix[i+1]) } ## -- Work - + if(any(x < 0)) stop("'x' must be positive") - if(standard == "SI") { - suffix <- suffix.decimal - base <- 10^3 - } else { - suffix <- suffix.binary - base <- 2^10 - } + if(standard == "SI") + { + suffix <- suffix.SI + base <- 10^3 + } + else if (standard=="IEC") + { + suffix <- suffix.IEC + base <- 2^10 + } + else # (standard=="Unix) + { + suffix <- suffix.Unix + base <- 2^10 + } - if(!missing(units)) + if(!missing(units) && units=="bytes") { - units <- match.arg( units, suffix ) + retval <- rbind(x, "bytes") + } + else if(!missing(units) && units!="auto") + { + units <- suffix[match( toupper(units), toupper(suffix) )] power <- match(units, suffix ) -1 X <- x/(base^power) - X <- format.default(round(x=X, digits=digits), nsmall=digits) - X <- paste(X, units) - X + X <- format.default(x=X, digits=digits, nsmall=digits) + retval <- rbind(X, rep(units, length(X))) } else - sapply(X=x, FUN=".applyHuman", base=base, suffix=suffix, digits=digits, - width=width, sep=sep) + retval <- sapply(X=x, FUN=".applyHuman", base=base, suffix=suffix, + digits=digits, width=width, sep=sep) + + if(all(justify == "none")) + paste(trim(retval[1,]), trim(retval[2,]), sep=sep) + else + paste(format(trim(retval[1,]), justify=justify[1]), + format(trim(retval[2,]), justify=justify[2]), + sep=sep) + } + Modified: trunk/gdata/R/object.size.R =================================================================== --- trunk/gdata/R/object.size.R 2015-04-25 02:52:53 UTC (rev 1956) +++ trunk/gdata/R/object.size.R 2015-04-25 05:54:28 UTC (rev 1957) @@ -1,38 +1,79 @@ -### object.size.R ###------------------------------------------------------------------------ ### What: Print object size in human readable format - code -### $Id$ -### Time-stamp: <2008-12-30 08:05:43 ggorjan> ###------------------------------------------------------------------------ -object.size <- function(...) +object.size <- function(...) { structure(sapply(list(...), utils::object.size), class=c("object_sizes", "numeric")) } -print.object_sizes <- function(x, quote=FALSE, units, - humanReadable, ...) -{ - xOrig <- x - if(missing(humanReadable)) { - opt <- getOption("humanReadable") - humanReadable <- ifelse(!is.null(opt), opt, FALSE) - } - if(humanReadable) { - print(humanReadable(x), quote=quote, ...) - } else { - class(x) <- "numeric" - NextMethod() - } - invisible(xOrig) +print.object_sizes <- function(x, + quote=FALSE, + humanReadable=getOption("humanReadable"), + standard="IEC", + units, + digits=1, + width=NULL, + sep=" ", + ...) +{ + print(format(x, + humanReadable=humanReadable, + standard=standard, + units=units, + digits=digits, + width=width, + sep=sep), + quote=quote, + ...) + + + invisible(x) } +format.object_sizes <- function(x, + humanReadable=getOption("humanReadable"), + standard="IEC", + units, + digits=1, + width=NULL, + sep=" ", + ...) +{ + if( !missing(units) ) + { + if (units=="bytes") + paste(x, "bytes") + else + humanReadable(x, + standard=standard, + units=units, + digits=digits, + width=width, + sep=sep + ) + } + else if( is.null(humanReadable) || humanReadable==FALSE ) + paste(x, "bytes") + else + humanReadable(x, + standard=standard, + units=units, + digits=digits, + width=width, + sep=sep) + +} + + + is.object_sizes <- function(x) inherits(x, what="object_sizes") - + as.object_sizes <- function(x) { - if(!is.numeric(x)) stop("'x' must be numeric/integer") + if(!is.numeric(x) || any(x<0)) stop("'x' must be a positive numeric vector") + class(x) <- c("object_sizes", "numeric") x } @@ -44,66 +85,5 @@ x } -humanReadable <- function(x, standard="SI", units, digits=1, width=3, sep=" ") -{ - ## --- Setup --- - - suffix.decimal <- c("B", "kB", "MB", "GB", "TB", "PB", "EB", "ZB", "YB") - suffix.binary <- c("B", "KiB", "MiB", "GiB", "TiB", "PiB", "EiB", "ZiB", "YiB") - - ## --- Functions --- - - .applyHuman <- function(x, base, suffix, digits, width, sep) - { - ## Which suffix should we use? - n <- length(suffix) - for(i in 1:n) { - if(x >= base) { - if(i < n) x <- x / base - } else { - break - } - } - ## Formatting - if(is.null(width)) { ## the same formatting for all - x <- format(round(x=x, digits=digits), nsmall=digits) - } else { ## similar to ls, du, and df - lenX <- nchar(x) - if(lenX > width) { - digitsMy <- width - (lenX - (lenX - (nchar(round(x)) + 1))) - digits <- ifelse(digitsMy > digits, digits, digitsMy) - } - if(i == 1) digits <- 0 - x <- round(x, digits=digits) - } - paste(x, suffix[i], sep=sep) - } - - ## -- Work - - if(any(x < 0)) stop("'x' must be positive") - if(standard == "SI") { - suffix <- suffix.decimal - base <- 10^3 - } else { - suffix <- suffix.binary - base <- 2^10 - } - - if(!missing(units)) - { - units <- match.arg( units, suffix ) - power <- which( units %in% suffix ) -1 - X <- x/(base^power) - X <- format.default(round(x=x, digits=digits), nsmall=digits) - X <- paste(X, units) - X - } - else - sapply(X=x, FUN=".applyHuman", base=base, suffix=suffix, digits=digits, - width=width, sep=sep) -} - - ###------------------------------------------------------------------------ ### object.size.R ends here Modified: trunk/gdata/man/humanReadable.Rd =================================================================== --- trunk/gdata/man/humanReadable.Rd 2015-04-25 02:52:53 UTC (rev 1956) +++ trunk/gdata/man/humanReadable.Rd 2015-04-25 05:54:28 UTC (rev 1957) @@ -1,43 +1,44 @@ -% humanReadable.Rd -%-------------------------------------------------------------------------- -% What: Print byte size in human readable format man page -% $Id$ -% Time-stamp: <2008-12-30 13:26:35 ggorjan> -%-------------------------------------------------------------------------- - \name{humanReadable} \alias{humanReadable} -\title{Print byte size in human readable format} +\title{Print Byte Size in Human Readable Format} \description{ -\code{humanReadable} converts byte size in human readable format such as +\code{humanReadable} converts integer byte sizes to a human readable units such as kB, MB, GB, etc. } \usage{ -humanReadable(x, standard=c("SI","IEC"), units, digits=1, width=3, sep=" ") +humanReadable(x, units="auto", standard=c("IEC", "SI", "Unix"), + digits=1, width=NULL, sep=" ", justify=c("right", "left"), + \dots) } \arguments{ \item{x}{integer, byte size} - \item{standard}{character, either "SI" for powers of 1000 or "IEC" for - powers of 1024, see details} - \item{units}{character, unit to use for all values (optional)} + \item{standard}{character, "IEC" for powers of 1024 ('MiB'), "SI" for + powers of 1000 ('MB'), or "Unix" for powers of 1024 ('M'). See + details.} + \item{units}{character, unit to use for all values (optional), one of + "auto", "bytes", or an appropriate unit corresponding to + \code{standard}.} \item{digits}{integer, number of digits after decimal point} \item{width}{integer, width of number string} \item{sep}{character, separator between number and unit} + \item{justify}{two-element vector specifiy the alignment for the number + and unit components of the size. Each element should be one of + "none", "left", "right", or "center"} } \details{ -Basic unit used to store information in computers is a bit. Bits are +The basic unit used to store information in computers is a bit. Bits are represented as zeroes and ones - binary number system. Although, the binary number system is not the same as the decimal number system, decimal prefixes -for binary multiples such as kilo and mega are often used. In the decimal system +for binary multiples such as kilo and mega are often used. In the decimal system kilo represent 1000, which is close to \eqn{1024 = 2^{10}} in the binary system. This sometimes causes problems as it is not clear which powers (2 or 10) are used in a notation like 1 kB. To overcome this problem International Electrotechnical @@ -65,14 +66,30 @@ } where Zi and Yi are GNU extensions to IEC. To get the output in the decimal -system (powers of 1000) use \code{standard="SI"}. Otherwise IEC standard -(powers of 1024) is used. +system (powers of 1000) use \code{standard="SI"}. To obtain IEC standard +(powers of 1024) use \code{standard="IEC"}. +In addition, single-character units are provided that follow (and +extend) the Unix pattern (use \code{standard="Unix"}): + +\tabular{lrcll}{ +Name \tab System \tab Symbol \tab Size \tab Conversion \cr +byte \tab binary \tab B \tab \eqn{2^3} \tab 8 bits \cr +kibibyte \tab binary \tab K \tab \eqn{2^{10}} \tab 1024 bytes \cr +mebibyte \tab binary \tab M \tab \eqn{(2^{10})^2} \tab 1024 kibibytes\cr +gibibyte \tab binary \tab G \tab \eqn{(2^{10})^3} \tab 1024 mebibytes\cr +tebibyte \tab binary \tab T \tab \eqn{(2^{10})^4} \tab 1024 gibibytes\cr +pebibyte \tab binary \tab P \tab \eqn{(2^{10})^5} \tab 1024 tebibytes\cr +exbibyte \tab binary \tab E \tab \eqn{(2^{10})^6} \tab 1024 pebibytes\cr +zebibyte \tab binary \tab Z \tab \eqn{(2^{10})^7} \tab 1024 exbibytes\cr +yottabyte \tab binary \tab Y \tab \eqn{(2^{10})^8} \tab 1024 zebibytes\cr +} + For printout both \code{digits} and \code{width} can be specified. If \code{width} is \code{NULL}, all values have given number of digits. If \code{width} is not \code{NULL}, output is rounded to a given width and -formated similar to human readable format of \code{ls}, \code{df} or -\code{du} shell commands. +formated similar to human readable format of the Unix \code{ls}, +\code{df} or \code{du} shell commands. } @@ -95,51 +112,40 @@ } -\author{Ales Korosec and Gregor Gorjanc} +\author{Ales Korosec, Gregor Gorjanc, and Gregory R. Warnes + \email{gr...@wa...}} + \seealso{ - \code{\link{object.size}}, \code{\link[gdata]{ll}} + \code{\link{object.size}} in package 'gdata', + \code{\link[utils]{object.size}} in package 'utils', + \code{\link[gdata]{ll}} } \examples{ # Simple example: maximum addressible size of 32 bit pointer +humanReadable(2^32-1) +humanReadable(2^32-1, standard="IEC") humanReadable(2^32-1, standard="SI") -humanReadable(2^32-1, standard="IEC") +humanReadable(2^32-1, standard="Unix") -humanReadable(2^32-1, standard="SI", unit="MB") -humanReadable(2^32-1, standard="IEC", unit="MiB") +humanReadable(2^32-1, unit="MiB") +humanReadable(2^32-1, standard="IEC", unit="MiB") +humanReadable(2^32-1, standard="SI", unit="MB") +humanReadable(2^32-1, standard="Unix", unit="M") +# Vector of sizes +matrix(humanReadable(c(60810, 124141, 124, 13412513), width=4)) +matrix(humanReadable(c(60810, 124141, 124, 13412513), width=4, unit="KiB")) -baseSI <- 10 -powerSI <- seq(from=3, to=27, by=3) -SI0 <- (baseSI)^powerSI -k <- length(SI0) - 1 -SI1 <- SI0 - SI0 / c(2, runif(n=k, min=1.01, max=5.99)) -SI2 <- SI0 + SI0 / c(2, runif(n=k, min=1.01, max=5.99)) +# Specify digits rather than width +matrix(humanReadable(c(60810, 124141, 124, 13412513), width=NULL, digits=2)) -baseIEC <- 2 -powerIEC <- seq(from=10, to=90, by=10) -IEC0 <- (baseIEC)^powerIEC -IEC1 <- IEC0 - IEC0 / c(2, runif(n=k, min=1.01, max=5.99)) -IEC2 <- IEC0 + IEC0 / c(2, runif(n=k, min=1.01, max=5.99)) +# Change the justification +matrix(humanReadable(c(60810, 124141, 124, 13412513), width=NULL, + justify=c("right", "right") )) -# Auto units -cbind(humanReadable(x=SI1, width=NULL, digits=3), - humanReadable(x=SI0, width=NULL, digits=2), - humanReadable(x=SI2, width=NULL, digits=1), - humanReadable(x=IEC1, standard="IEC", width=7, digits=3), - humanReadable(x=IEC0, standard="IEC", width=7, digits=2), - humanReadable(x=IEC2, standard="IEC", width=7, digits=1)) - -# Single unit -cbind(humanReadable(x=SI1, units="GB", width=NULL, digits=3), - humanReadable(x=SI0, units="GB", width=NULL, digits=2), - humanReadable(x=SI2, units="GB", width=NULL, digits=1), - humanReadable(x=IEC1, units="GiB", standard="IEC", width=7, digits=3), - humanReadable(x=IEC0, units="GiB", standard="IEC", width=7, digits=2), - humanReadable(x=IEC2, units="GiB", standard="IEC", width=7, digits=1)) - } \keyword{misc} Modified: trunk/gdata/man/object.size.Rd =================================================================== --- trunk/gdata/man/object.size.Rd 2015-04-25 02:52:53 UTC (rev 1956) +++ trunk/gdata/man/object.size.Rd 2015-04-25 05:54:28 UTC (rev 1957) @@ -1,70 +1,95 @@ -% File src/library/utils/man/object.size.Rd +% Come material taken from src/library/utils/man/object.size.Rd % Part of the R package, http://www.R-project.org % Copyright 1995-2007 R Core Development Team % Distributed under GPL 2 or later \name{object.size} \alias{object.size} -\alias{print.object_sizes} \alias{c.object_sizes} \alias{as.object_sizes} \alias{is.object_sizes} +\alias{format.object_sizes} +\alias{print.object_sizes} -\title{Report the Space Allocated for an Object} +\title{Report the Space Allocated for Objects} \description{ - Provides an estimate of the memory that is being used to store an \R object. + Provides an estimate of the memory that is being used to store \R objects. } \usage{ object.size(\dots) -\method{print}{object_sizes}(x, quote=FALSE, humanReadable, \dots) +\method{is}{object_sizes}(x) + +\method{as}{object_sizes}(x) + +\method{c}{object_sizes}(x) + +\method{format}{object_sizes}(x, humanReadable=getOption("humanReadable"), standard="IEC", units, + digits=1, width=NULL, sep=" ", \dots) + +\method{print}{object_sizes}x, quote=FALSE, humanReadable=getOption("humanReadable"), + standard="IEC", units, digits=1, width=NULL, sep=" ", \dots) + } \arguments{ - \item{\dots}{\code{object.size}: \R objects; \code{print}; arguments - to be passed to or from other methods.} + \item{\dots}{\code{object.size}: \R objects; + \code{print}: arguments to be passed to other methods.} \item{x}{output from \code{object.size}} \item{quote}{logical, indicating whether or not the result should be printed with surrounding quotes.} \item{humanReadable}{logical, use the \dQuote{human readable} format.} + \item{standard,units,digits,width,sep,justify}{arguments passed to + \code{\link{humanReadable}}. See the \code{\link{humanReadable}} + man page for details. + } } \details{ - This is a modified copy from the utils package in R as fo 2008-12-15. + \emph{This is a modified copy of the man page for utils::object.size in R + 2.2.1.} - Exactly which parts of the memory allocation should be attributed to - which object is not clear-cut. This function merely provides a rough - indication: it should be reasonably accurate for atomic vectors, but - does not detect if elements of a list are shared, for example. - (Sharing amongst elements of a character vector is taken into account, - but not that between character vectors in a single object.) - - The calculation is of the size of the object, and excludes the space - needed to store its name in the symbol table. + Exactly which parts of the memory allocation should be attributed + to which object is not clear-cut. This function merely provides a + rough indication: it should be reasonably accurate for atomic + vectors, but does not detect if elements of a list are shared, for + example. (Sharing amongst elements of a character vector is taken + into account, but not that between character vectors in a single + object.) - Associated space (e.g. the environment of a function and what the - pointer in a \code{EXTPTRSXP} points to) is not included in the + The calculation is of the size of the object, and excludes the + space needed to store its name in the symbol table. + + Associated space (e.g., the environment of a function and what the + pointer in a ‘EXTPTRSXP’ points to) is not included in the calculation. - Object sizes are larger on 64-bit platforms than 32-bit ones, but will - very likely be the same on different platforms with the same word - length and pointer size. + Object sizes are larger on 64-bit builds than 32-bit ones, but + will very likely be the same on different platforms with the same + word length and pointer size. % Modificitaion start - Class of returned object is \code{c("byte", "numeric")} with + \emph{Changes} + + Class of returned object is \code{c("object_sizes", "numeric")} with appropriate \code{print} and \code{c} methods. By default \code{object.size} outputs size in bytes, but human readable format similar to \code{ls}, \code{df} or \code{du} shell - commands can be invoked with \code{options(humanReadable=TRUE)}. + commands can be displayed by calling \code{humanReadable} directly, + calling \code{print} with the argument \code{humanReadable=TRUE}, or + by setting \code{options(humanReadable=TRUE)}. + % Modificitaion end } \value{ - An object of class \code{"object.size"} with a length-one double value, - an estimate of the memory allocation attributable to the object in bytes. + A numeric vector class \code{c("object_sizes", "numeric")} containing + estimated memory allocation attributable to the objects in bytes. } \seealso{ - \code{\link{Memory-limits}} for the design limitations on object size. + \code{\link[utils]{object.size}} in package 'utils' for the standard + version of this function, + \code{\link{Memory-limits}} for the design limitations on object size, \code{\link{humanReadable}} for human readable format. } @@ -72,14 +97,35 @@ object.size(letters) object.size(ls) ## find the 10 largest objects in the base package -z <- sapply(ls("package:base"), function(x) - object.size(get(x, envir = baseenv()))) -(tmp <- as.matrix(rev(sort(z))[1:10])) +allObj <- sapply(ls("package:base"), + function(x) + object.size(get(x, envir = baseenv())) + ) +( bigObj <- as.object_sizes(rev(sort(allObj))[1:10] ) ) +print(bigObj, humanReadable=TRUE) + + as.object_sizes(14567567) + +\dontshow{ + optionsOrig <- options("humanReadable") +} + options(humanReadable=TRUE) -(z <- object.size(letters, c(letters, letters), rep(letters, 100), rep(letters, 10000))) +( + z <- object.size(letters, + c(letters, letters), + rep(letters, 100), + rep(letters, 10000) + ) +) is.object_sizes(z) as.object_sizes(14567567) + +\dontshow{ + options(optionsOrig) } + +} \keyword{utilities} Added: trunk/gdata/tests/test.humanReadable.R =================================================================== --- trunk/gdata/tests/test.humanReadable.R (rev 0) +++ trunk/gdata/tests/test.humanReadable.R 2015-04-25 05:54:28 UTC (rev 1957) @@ -0,0 +1,91 @@ +library(gdata) + +options(humanReadable=FALSE) + +baseSI <- 10 +powerSI <- seq(from=0, to=27, by=3) +SI0 <- (baseSI)^powerSI +k <- length(SI0) - 1 +SI1 <- SI0 - SI0 / c(2, runif(n=k, min=1.01, max=5.99)) +SI2 <- SI0 + SI0 / c(2, runif(n=k, min=1.01, max=5.99)) + +baseIEC <- 2 +powerIEC <- seq(from=0, to=90, by=10) +IEC0 <- (baseIEC)^powerIEC +IEC1 <- IEC0 - IEC0 / c(2, runif(n=k, min=1.01, max=5.99)) +IEC2 <- IEC0 + IEC0 / c(2, runif(n=k, min=1.01, max=5.99)) + +# Auto units, specify width +cbind(humanReadable(x=SI2, standard="SI", width=7), + humanReadable(x=SI2, standard="SI", width=5), + humanReadable(x=SI2, standard="SI", width=3), + humanReadable(x=IEC2, standard="IEC", width=7), + humanReadable(x=IEC2, standard="IEC", width=5), + humanReadable(x=IEC2, standard="IEC", width=3), + humanReadable(x=IEC2, standard="Unix", width=7), + humanReadable(x=IEC2, standard="Unix", width=5), + humanReadable(x=IEC2, standard="Unix", width=3)) + +# Auto units, specify digits +cbind(humanReadable(x=SI2, standard="SI", width=NULL, digits=7), + humanReadable(x=SI2, standard="SI", width=NULL, digits=3), + humanReadable(x=SI2, standard="SI", width=NULL, digits=2), + humanReadable(x=SI2, standard="SI", width=NULL, digits=1), + humanReadable(x=IEC2, standard="IEC", width=NULL, digits=7), + humanReadable(x=IEC2, standard="IEC", width=NULL, digits=3), + humanReadable(x=IEC2, standard="IEC", width=NULL, digits=2), + humanReadable(x=IEC2, standard="IEC", width=NULL, digits=1), + humanReadable(x=IEC2, standard="Unix", width=NULL, digits=7), + humanReadable(x=IEC2, standard="Unix", width=NULL, digits=3), + humanReadable(x=IEC2, standard="Unix", width=NULL, digits=2), + humanReadable(x=IEC2, standard="Unix", width=NULL, digits=1)) + +# Single unit, specify width +cbind(humanReadable(x=SI1, units="GB", standard="SI", width=7), + humanReadable(x=SI1, units="GB", standard="SI", width=5), + humanReadable(x=SI1, units="GB", standard="SI", width=3), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=7), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=5), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=3), + humanReadable(x=IEC1, units="G", standard="Unix", width=7), + humanReadable(x=IEC1, units="G", standard="Unix", width=5), + humanReadable(x=IEC1, units="G", standard="Unix", width=3) + ) + +# Single unit, specify digits +cbind(humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=7), + humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=3), + humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=2), + humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=1), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=7), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=3), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=2), + humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=1), + humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=7), + humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=3), + humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=2), + humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=1) + ) + + +stopifnot( is.object_sizes(as.object_sizes( 2^(1:30) ) ) ) +stopifnot( format(as.object_sizes(124)) == "124 bytes") +stopifnot( format(as.object_sizes(124e8), units="auto") == "11.5 GiB") +stopifnot( format(as.object_sizes(124e8), humanReadable=TRUE) == "11.5 GiB") +stopifnot( format(as.object_sizes(124e8), units="bytes") == "1.24e+10 bytes") + +tools::assertError( as.object_sizes(-1) ) +tools::assertError( as.object_sizes('a') ) +tools::assertError( as.object_sizes(list()) ) +tools::assertError( as.object_sizes(NULL) ) +tools::assertError( as.object_sizes(0+1i) ) + +stopifnot( format(as.object_sizes(1e40) ) == "1e+40 bytes" ) +stopifnot( format(as.object_sizes(1e40), units="auto" ) == "8.271806e+15 YiB") +stopifnot( format(as.object_sizes(1e40), units="bytes") == "1e+40 bytes" ) +stopifnot( format(as.object_sizes(1e40), humanReadable=TRUE) == "8.271806e+15 YiB") +stopifnot( format(as.object_sizes(1e40), humanReadable=FALSE) == "1e+40 bytes") + +options(humanReadable=TRUE) +stopifnot( format(as.object_sizes(1e40) ) == "8.271806e+15 YiB") +options(humanReadable=FALSE) Added: trunk/gdata/tests/test.humanReadable.Rout.save =================================================================== --- trunk/gdata/tests/test.humanReadable.Rout.save (rev 0) +++ trunk/gdata/tests/test.humanReadable.Rout.save 2015-04-25 05:54:28 UTC (rev 1957) @@ -0,0 +1,243 @@ + +R version 3.1.2 (2014-10-31) -- "Pumpkin Helmet" +Copyright (C) 2014 The R Foundation for Statistical Computing +Platform: x86_64-apple-darwin13.4.0 (64-bit) + +R is free software and comes with ABSOLUTELY NO WARRANTY. +You are welcome to redistribute it under certain conditions. +Type 'license()' or 'licence()' for distribution details. + + Natural language support but running in an English locale + +R is a collaborative project with many contributors. +Type 'contributors()' for more information and +'citation()' on how to cite R or R packages in publications. + +Type 'demo()' for some demos, 'help()' for on-line help, or +'help.start()' for an HTML browser interface to help. +Type 'q()' to quit R. + +> library(gdata) +gdata: read.xls support for 'XLS' (Excel 97-2004) files ENABLED. + +gdata: Unable to load perl libaries needed by read.xls() +gdata: to support 'XLSX' (Excel 2007+) files. + +gdata: Run the function 'installXLSXsupport()' +gdata: to automatically download and install the perl +gdata: libaries needed to support Excel XLS and XLSX formats. + +Attaching package: ‘gdata’ + +The following object is masked from ‘package:stats’: + + nobs + +The following object is masked from ‘package:utils’: + + object.size + +> +> options(humanReadable=FALSE) +> +> baseSI <- 10 +> powerSI <- seq(from=0, to=27, by=3) +> SI0 <- (baseSI)^powerSI +> k <- length(SI0) - 1 +> SI1 <- SI0 - SI0 / c(2, runif(n=k, min=1.01, max=5.99)) +> SI2 <- SI0 + SI0 / c(2, runif(n=k, min=1.01, max=5.99)) +> +> baseIEC <- 2 +> powerIEC <- seq(from=0, to=90, by=10) +> IEC0 <- (baseIEC)^powerIEC +> IEC1 <- IEC0 - IEC0 / c(2, runif(n=k, min=1.01, max=5.99)) +> IEC2 <- IEC0 + IEC0 / c(2, runif(n=k, min=1.01, max=5.99)) +> +> # Auto units, specify width +> cbind(humanReadable(x=SI2, standard="SI", width=7), ++ humanReadable(x=SI2, standard="SI", width=5), ++ humanReadable(x=SI2, standard="SI", width=3), ++ humanReadable(x=IEC2, standard="IEC", width=7), ++ humanReadable(x=IEC2, standard="IEC", width=5), ++ humanReadable(x=IEC2, standard="IEC", width=3), ++ humanReadable(x=IEC2, standard="Unix", width=7), ++ humanReadable(x=IEC2, standard="Unix", width=5), ++ humanReadable(x=IEC2, standard="Unix", width=3)) + [,1] [,2] [,3] [,4] [,5] [,6] + [1,] " 2 B " " 2 B " " 2 B " " 2 B " " 2 B " " 2 B " + [2,] "1.26838 kB" "1.268 kB" " 1.3 kB" "1.25729 KiB" "1.257 KiB" " 1.3 KiB" + [3,] " 1.2285 MB" "1.228 MB" " 1.2 MB" "1.83751 MiB" "1.838 MiB" " 1.8 MiB" + [4,] "1.24401 GB" "1.244 GB" " 1.2 GB" "1.26666 GiB" "1.267 GiB" " 1.3 GiB" + [5,] "1.47565 TB" "1.476 TB" " 1.5 TB" " 1.4234 TiB" "1.423 TiB" " 1.4 TiB" + [6,] "1.36687 PB" "1.367 PB" " 1.4 PB" "1.32499 PiB" "1.325 PiB" " 1.3 PiB" + [7,] "1.21324 EB" "1.213 EB" " 1.2 EB" "1.54391 EiB" "1.544 EiB" " 1.5 EiB" + [8,] "1.37186 ZB" "1.372 ZB" " 1.4 ZB" " 1.233 ZiB" "1.233 ZiB" " 1.2 ZiB" + [9,] "1.19468 YB" "1.195 YB" " 1.2 YB" "1.21258 YiB" "1.213 YiB" " 1.2 YiB" +[10,] "1201.13 YB" " 1201 YB" "1201 YB" "1489.01 YiB" " 1489 YiB" "1489 YiB" + [,7] [,8] [,9] + [1,] " 2 B" " 2 B" " 2 B" + [2,] "1.25729 K" "1.257 K" " 1.3 K" + [3,] "1.83751 M" "1.838 M" " 1.8 M" + [4,] "1.26666 G" "1.267 G" " 1.3 G" + [5,] " 1.4234 T" "1.423 T" " 1.4 T" + [6,] "1.32499 P" "1.325 P" " 1.3 P" + [7,] "1.54391 E" "1.544 E" " 1.5 E" + [8,] " 1.233 Z" "1.233 Z" " 1.2 Z" + [9,] "1.21258 Y" "1.213 Y" " 1.2 Y" +[10,] "1489.01 Y" " 1489 Y" "1489 Y" +> +> # Auto units, specify digits +> cbind(humanReadable(x=SI2, standard="SI", width=NULL, digits=7), ++ humanReadable(x=SI2, standard="SI", width=NULL, digits=3), ++ humanReadable(x=SI2, standard="SI", width=NULL, digits=2), ++ humanReadable(x=SI2, standard="SI", width=NULL, digits=1), ++ humanReadable(x=IEC2, standard="IEC", width=NULL, digits=7), ++ humanReadable(x=IEC2, standard="IEC", width=NULL, digits=3), ++ humanReadable(x=IEC2, standard="IEC", width=NULL, digits=2), ++ humanReadable(x=IEC2, standard="IEC", width=NULL, digits=1), ++ humanReadable(x=IEC2, standard="Unix", width=NULL, digits=7), ++ humanReadable(x=IEC2, standard="Unix", width=NULL, digits=3), ++ humanReadable(x=IEC2, standard="Unix", width=NULL, digits=2), ++ humanReadable(x=IEC2, standard="Unix", width=NULL, digits=1)) + [,1] [,2] [,3] [,4] + [1,] " 1.5000000 B " " 1.500 B " " 1.50 B " " 1.5 B " + [2,] " 1.2683780 kB" " 1.268 kB" " 1.27 kB" " 1.3 kB" + [3,] " 1.2284981 MB" " 1.228 MB" " 1.23 MB" " 1.2 MB" + [4,] " 1.2440094 GB" " 1.244 GB" " 1.24 GB" " 1.2 GB" + [5,] " 1.4756474 TB" " 1.476 TB" " 1.48 TB" " 1.5 TB" + [6,] " 1.3668711 PB" " 1.367 PB" " 1.37 PB" " 1.4 PB" + [7,] " 1.2132416 EB" " 1.213 EB" " 1.21 EB" " 1.2 EB" + [8,] " 1.3718619 ZB" " 1.372 ZB" " 1.37 ZB" " 1.4 ZB" + [9,] " 1.1946775 YB" " 1.195 YB" " 1.19 YB" " 1.2 YB" +[10,] "1201.1346574 YB" "1201.135 YB" "1201.13 YB" "1201.1 YB" + [,5] [,6] [,7] [,8] + [1,] " 1.5000000 B " " 1.500 B " " 1.50 B " " 1.5 B " + [2,] " 1.2572859 KiB" " 1.257 KiB" " 1.26 KiB" " 1.3 KiB" + [3,] " 1.8375086 MiB" " 1.838 MiB" " 1.84 MiB" " 1.8 MiB" + [4,] " 1.2666626 GiB" " 1.267 GiB" " 1.27 GiB" " 1.3 GiB" + [5,] " 1.4234036 TiB" " 1.423 TiB" " 1.42 TiB" " 1.4 TiB" + [6,] " 1.3249855 PiB" " 1.325 PiB" " 1.32 PiB" " 1.3 PiB" + [7,] " 1.5439083 EiB" " 1.544 EiB" " 1.54 EiB" " 1.5 EiB" + [8,] " 1.2329980 ZiB" " 1.233 ZiB" " 1.23 ZiB" " 1.2 ZiB" + [9,] " 1.2125791 YiB" " 1.213 YiB" " 1.21 YiB" " 1.2 YiB" +[10,] "1489.0123170 YiB" "1489.012 YiB" "1489.01 YiB" "1489.0 YiB" + [,9] [,10] [,11] [,12] + [1,] " 1.5000000 B" " 1.500 B" " 1.50 B" " 1.5 B" + [2,] " 1.2572859 K" " 1.257 K" " 1.26 K" " 1.3 K" + [3,] " 1.8375086 M" " 1.838 M" " 1.84 M" " 1.8 M" + [4,] " 1.2666626 G" " 1.267 G" " 1.27 G" " 1.3 G" + [5,] " 1.4234036 T" " 1.423 T" " 1.42 T" " 1.4 T" + [6,] " 1.3249855 P" " 1.325 P" " 1.32 P" " 1.3 P" + [7,] " 1.5439083 E" " 1.544 E" " 1.54 E" " 1.5 E" + [8,] " 1.2329980 Z" " 1.233 Z" " 1.23 Z" " 1.2 Z" + [9,] " 1.2125791 Y" " 1.213 Y" " 1.21 Y" " 1.2 Y" +[10,] "1489.0123170 Y" "1489.012 Y" "1489.01 Y" "1489.0 Y" +> +> # Single unit, specify width +> cbind(humanReadable(x=SI1, units="GB", standard="SI", width=7), ++ humanReadable(x=SI1, units="GB", standard="SI", width=5), ++ humanReadable(x=SI1, units="GB", standard="SI", width=3), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=7), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=5), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=3), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=7), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=5), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=3) ++ ) + [,1] [,2] [,3] [,4] [,5] [,6] + [1,] "5e-10 GB" "5e-10 GB" "5e-10 GB" "5e-10 GiB" "5e-10 GiB" "5e-10 GiB" + [2,] "6e-07 GB" "6e-07 GB" "6e-07 GB" "6e-07 GiB" "6e-07 GiB" "6e-07 GiB" + [3,] "7e-04 GB" "7e-04 GB" "7e-04 GB" "7e-04 GiB" "7e-04 GiB" "7e-04 GiB" + [4,] "8e-01 GB" "8e-01 GB" "8e-01 GB" "8e-01 GiB" "8e-01 GiB" "8e-01 GiB" + [5,] "7e+02 GB" "7e+02 GB" "7e+02 GB" "3e+02 GiB" "3e+02 GiB" "3e+02 GiB" + [6,] "8e+05 GB" "8e+05 GB" "8e+05 GB" "7e+05 GiB" "7e+05 GiB" "7e+05 GiB" + [7,] "8e+08 GB" "8e+08 GB" "8e+08 GB" "8e+08 GiB" "8e+08 GiB" "8e+08 GiB" + [8,] "8e+11 GB" "8e+11 GB" "8e+11 GB" "5e+11 GiB" "5e+11 GiB" "5e+11 GiB" + [9,] "7e+14 GB" "7e+14 GB" "7e+14 GB" "9e+14 GiB" "9e+14 GiB" "9e+14 GiB" +[10,] "8e+17 GB" "8e+17 GB" "8e+17 GB" "6e+17 GiB" "6e+17 GiB" "6e+17 GiB" + [,7] [,8] [,9] + [1,] "5e-10 G" "5e-10 G" "5e-10 G" + [2,] "6e-07 G" "6e-07 G" "6e-07 G" + [3,] "7e-04 G" "7e-04 G" "7e-04 G" + [4,] "8e-01 G" "8e-01 G" "8e-01 G" + [5,] "3e+02 G" "3e+02 G" "3e+02 G" + [6,] "7e+05 G" "7e+05 G" "7e+05 G" + [7,] "8e+08 G" "8e+08 G" "8e+08 G" + [8,] "5e+11 G" "5e+11 G" "5e+11 G" + [9,] "9e+14 G" "9e+14 G" "9e+14 G" +[10,] "6e+17 G" "6e+17 G" "6e+17 G" +> +> # Single unit, specify digits +> cbind(humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=7), ++ humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=3), ++ humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=2), ++ humanReadable(x=SI1, units="GB", standard="SI", width=NULL, digits=1), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=7), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=3), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=2), ++ humanReadable(x=IEC1, units="GiB", standard="IEC", width=NULL, digits=1), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=7), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=3), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=2), ++ humanReadable(x=IEC1, units="G", standard="Unix", width=NULL, digits=1) ++ ) + [,1] [,2] [,3] [,4] + [1,] "5.000000e-10 GB" "5.00e-10 GB" "5.0e-10 GB" "5e-10 GB" + [2,] "6.388137e-07 GB" "6.39e-07 GB" "6.4e-07 GB" "6e-07 GB" + [3,] "7.101117e-04 GB" "7.10e-04 GB" "7.1e-04 GB" "7e-04 GB" + [4,] "8.188110e-01 GB" "8.19e-01 GB" "8.2e-01 GB" "8e-01 GB" + [5,] "6.706597e+02 GB" "6.71e+02 GB" "6.7e+02 GB" "7e+02 GB" + [6,] "8.067884e+05 GB" "8.07e+05 GB" "8.1e+05 GB" "8e+05 GB" + [7,] "7.758668e+08 GB" "7.76e+08 GB" "7.8e+08 GB" "8e+08 GB" + [8,] "7.861707e+11 GB" "7.86e+11 GB" "7.9e+11 GB" "8e+11 GB" + [9,] "7.495958e+14 GB" "7.50e+14 GB" "7.5e+14 GB" "7e+14 GB" +[10,] "7.655714e+17 GB" "7.66e+17 GB" "7.7e+17 GB" "8e+17 GB" + [,5] [,6] [,7] [,8] + [1,] "4.656613e-10 GiB" "4.66e-10 GiB" "4.7e-10 GiB" "5e-10 GiB" + [2,] "6.058649e-07 GiB" "6.06e-07 GiB" "6.1e-07 GiB" "6e-07 GiB" + [3,] "7.437373e-04 GiB" "7.44e-04 GiB" "7.4e-04 GiB" "7e-04 GiB" + [4,] "7.890501e-01 GiB" "7.89e-01 GiB" "7.9e-01 GiB" "8e-01 GiB" + [5,] "2.665461e+02 GiB" "2.67e+02 GiB" "2.7e+02 GiB" "3e+02 GiB" + [6,] "6.781352e+05 GiB" "6.78e+05 GiB" "6.8e+05 GiB" "7e+05 GiB" + [7,] "7.658425e+08 GiB" "7.66e+08 GiB" "7.7e+08 GiB" "8e+08 GiB" + [8,] "4.681329e+11 GiB" "4.68e+11 GiB" "4.7e+11 GiB" "5e+11 GiB" + [9,] "8.705167e+14 GiB" "8.71e+14 GiB" "8.7e+14 GiB" "9e+14 GiB" +[10,] "6.227605e+17 GiB" "6.23e+17 GiB" "6.2e+17 GiB" "6e+17 GiB" + [,9] [,10] [,11] [,12] + [1,] "4.656613e-10 G" "4.66e-10 G" "4.7e-10 G" "5e-10 G" + [2,] "6.058649e-07 G" "6.06e-07 G" "6.1e-07 G" "6e-07 G" + [3,] "7.437373e-04 G" "7.44e-04 G" "7.4e-04 G" "7e-04 G" + [4,] "7.890501e-01 G" "7.89e-01 G" "7.9e-01 G" "8e-01 G" + [5,] "2.665461e+02 G" "2.67e+02 G" "2.7e+02 G" "3e+02 G" + [6,] "6.781352e+05 G" "6.78e+05 G" "6.8e+05 G" "7e+05 G" + [7,] "7.658425e+08 G" "7.66e+08 G" "7.7e+08 G" "8e+08 G" + [8,] "4.681329e+11 G" "4.68e+11 G" "4.7e+11 G" "5e+11 G" + [9,] "8.705167e+14 G" "8.71e+14 G" "8.7e+14 G" "9e+14 G" +[10,] "6.227605e+17 G" "6.23e+17 G" "6.2e+17 G" "6e+17 G" +> +> +> stopifnot( is.object_sizes(as.object_sizes( 2^(1:30) ) ) ) +> stopifnot( format(as.object_sizes(124)) == "124 bytes") +> stopifnot( format(as.object_sizes(124e8), units="auto") == "11.5 GiB") +> stopifnot( format(as.object_sizes(124e8), humanReadable=TRUE) == "11.5 GiB") +> stopifnot( format(as.object_sizes(124e8), units="bytes") == "1.24e+10 bytes") +> +> tools::assertError( as.object_sizes(-1) ) +> tools::assertError( as.object_sizes('a') ) +> tools::assertError( as.object_sizes(list()) ) +> tools::assertError( as.object_sizes(NULL) ) +> tools::assertError( as.object_sizes(0+1i) ) +> +> stopifnot( format(as.object_sizes(1e40) ) == "1e+40 bytes" ) +> stopifnot( format(as.object_sizes(1e40), units="auto" ) == "8.271806e+15 YiB") +> stopifnot( format(as.object_sizes(1e40), units="bytes") == "1e+40 bytes" ) +> stopifnot( format(as.object_sizes(1e40), humanReadable=TRUE) == "8.271806e+15 YiB") +> stopifnot( format(as.object_sizes(1e40), humanReadable=FALSE) == "1e+40 bytes") +> +> options(humanReadable=TRUE) +> stopifnot( format(as.object_sizes(1e40) ) == "8.271806e+15 YiB") +> options(humanReadable=FALSE) +> +> proc.time() + user system elapsed + 0.411 0.048 0.455 This was sent by the SourceForge.net collaborative development platform, the world's largest Open Source development site. |