Skip to content

Commit

Permalink
Fixed quotes showing in tables() output in dev. (#2565)
Browse files Browse the repository at this point in the history
  • Loading branch information
mattdowle authored Jan 15, 2018
1 parent 86e3786 commit 0c060fe
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 27 deletions.
4 changes: 3 additions & 1 deletion R/print.data.table.R
Original file line number Diff line number Diff line change
Expand Up @@ -110,7 +110,9 @@ format.data.table <- function (x, ..., justify="none") {
stop("Internal structure doesn't seem to be a list. Possibly corrupt data.table.")
}
format.item <- function(x) {
if (is.atomic(x) || inherits(x,"formula")) # FR #2591 - format.data.table issue with columns of class "formula"
if (is.null(x)) # NULL item in a list column
""
else if (is.atomic(x) || inherits(x,"formula")) # FR #2591 - format.data.table issue with columns of class "formula"
paste(c(format(head(x, 6L), justify=justify, ...), if (length(x) > 6L) "..."), collapse=",") # fix for #5435 - format has to be added here...
else
paste("<", class(x)[1L], ">", sep="")
Expand Down
34 changes: 13 additions & 21 deletions R/tables.R
Original file line number Diff line number Diff line change
Expand Up @@ -18,36 +18,28 @@ tables <- function(mb=TRUE, order.col="NAME", width=80,
data.table(NAME = dt_n,
NROW = nrow(DT),
NCOL = ncol(DT))
if (mb)
# mb is an option because object.size() appears to be slow.
# **TO DO: revisit**
set(info_i, , "MB",
#1048576 = 1024^2
round(as.numeric(object.size(DT))/1048576))
if (mb) set(info_i, , "MB", round(as.numeric(object.size(DT))/1024^2))
# mb is an option because object.size() appears to be slow. TO DO: revisit
set(info_i, , "COLS", list(list(names(DT))))
set(info_i, , "KEY", list(list(key(DT))))
if (index) set(info_i, , "INDICES", list(list(indices(DT))))
info_i
}))
info[ , NROW := format(sprintf("%4s", prettyNum(NROW, big.mark=",")), justify="right")] # %4s is for minimum width
info[ , NCOL := format(sprintf("%4s", prettyNum(NCOL, big.mark=",")), justify="right")]
if (mb) {
total = sum(info$MB)
info[ , MB := format(sprintf("%2s", prettyNum(MB, big.mark=",")), justify="right")]
}
if (!order.col %in% names(info)) stop("order.col='",order.col,"' not a column name of info")
info = info[base::order(info[[order.col]])] # base::order to maintain locale ordering of table names
m = as.matrix(info)
colnames(m)[2] = sprintf(paste("%",nchar(m[1,"NROW"]), "s", sep=""), "NROW")
colnames(m)[3] = sprintf(paste("%",nchar(m[1,"NCOL"]), "s", sep=""), "NCOL")
if (mb) colnames(m)[4] = sprintf(paste("%", nchar(m[1,"MB"]), "s", sep=""), "MB")
m[ , "COLS"] = substring(m[,"COLS"], 1L, width)
m[ , "KEY"] = substring(m[,"KEY"], 1L, width)
if (!silent) {
print(m, quote=FALSE, right=FALSE)
if (mb) cat("Total: ", prettyNum(as.character(total), big.mark=","), "MB\n", sep="")
# prettier printing on console
pretty_format = function(x, width) {
format(prettyNum(x, big.mark=","),
width=width, justify="right")
}
tt = copy(info)
tt[ , NROW := pretty_format(NROW, width=4L)]
tt[ , NCOL := pretty_format(NCOL, width=4L)]
if (mb) tt[ , MB := pretty_format(MB, width=2L)]
print(tt, class=FALSE, nrow=Inf)
if (mb) cat("Total: ", prettyNum(sum(info$MB), big.mark=","), "MB\n", sep="")
}
invisible(info)
}


8 changes: 3 additions & 5 deletions inst/tests/tests.Rraw
Original file line number Diff line number Diff line change
Expand Up @@ -242,11 +242,9 @@ xenv <- new.env()
xenv$TESTDT <- TESTDT
rm(TESTDT)
DT <- data.table(a = 1)
setnames(DT, paste(rev(LETTERS), collapse=""))
test(69.4, capture.output(tables(width = 10L)),
c(" NAME NROW NCOL MB COLS KEY ",
"[1,] \"DT\" \" 1\" \" 1\" \" 0\" \"ZYXWVUTSRQ\" \"NULL\"",
"Total: 0MB"))
test(69.4, tables(), output="NAME NROW NCOL MB COLS KEY1: DT 1 1 0 a.*Total: 0MB")
DT <- data.table(A=1:2, B=3:4, C=5:6, D=7:8, E=9:10, F=11:12, G=13:14, H=15:16, key="A,D,F,G")
test(69.5, tables(), output="NAME NROW NCOL MB COLS KEY1: DT 2 8 0 A,B,C,D,E,F,... A,D,F,G.*Total: 0MB")

nenv <- new.env()
nenv$DT <- data.table(a = 1)
Expand Down

0 comments on commit 0c060fe

Please sign in to comment.