Skip to content

Commit

Permalink
Tests summary (#3307)
Browse files Browse the repository at this point in the history
  • Loading branch information
jangorecki authored and mattdowle committed Jan 29, 2019
1 parent cd279e1 commit a08547e
Show file tree
Hide file tree
Showing 5 changed files with 74 additions and 101 deletions.
71 changes: 70 additions & 1 deletion R/test.data.table.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,12 @@ test.data.table <- function(verbose=FALSE, pkg="pkg", silent=FALSE, with.other.p
fn = file.path(d, fn)
if (!file.exists(fn)) stop(fn," does not exist")

# From R 3.6.0 onwards, we can check that && and || are using only length-1 logicals (in the test suite)
# rather than relying on x && y being equivalent to x[[1L]] && y[[1L]] silently.
orig__R_CHECK_LENGTH_1_LOGIC2_ <- Sys.getenv("_R_CHECK_LENGTH_1_LOGIC2_", unset = NA_character_)
Sys.setenv("_R_CHECK_LENGTH_1_LOGIC2_" = TRUE)
# This environment variable is restored to its previous state (including not defined) after sourcing test script

oldverbose = options(datatable.verbose=verbose)
oldenc = options(encoding="UTF-8")[[1L]] # just for tests 708-712 on Windows
# TO DO: reinstate solution for C locale of CRAN's Mac (R-Forge's Mac is ok)
Expand Down Expand Up @@ -48,7 +54,70 @@ test.data.table <- function(verbose=FALSE, pkg="pkg", silent=FALSE, with.other.p
options(oldenc)
# Sys.setlocale("LC_CTYPE", oldlocale)
setDTthreads(0)
invisible(env$nfail==0)
ans = env$nfail==0

if (is.na(orig__R_CHECK_LENGTH_1_LOGIC2_)) {
Sys.unsetenv("_R_CHECK_LENGTH_1_LOGIC2_")
} else {
Sys.setenv("_R_CHECK_LENGTH_1_LOGIC2_" = orig__R_CHECK_LENGTH_1_LOGIC2_)
}

timings = get("timings", envir=env)
ntest = get("ntest", envir=env)
nfail = get("nfail", envir=env)
started.at = get("started.at", envir=env)
whichfail = get("whichfail", envir=env)

# Summary. This code originally in tests.Rraw and moved up here in #3307
plat = paste0("endian==", .Platform$endian,
", sizeof(long double)==", .Machine$sizeof.longdouble,
", sizeof(pointer)==", .Machine$sizeof.pointer,
", TZ=", suppressWarnings(Sys.timezone()),
", locale='", Sys.getlocale(), "'",
", l10n_info()='", paste0(names(l10n_info()), "=", l10n_info(), collapse="; "), "'")
DT = head(timings[-1L][order(-time)],10) # exclude id 1 as in dev that includes JIT
if ((x<-sum(timings[["nTest"]])) != ntest) warning("Timings count mismatch:",x,"vs",ntest)
cat("\n10 longest running tests took ", as.integer(tt<-DT[, sum(time)]), "s (", as.integer(100*tt/(ss<-timings[,sum(time)])), "% of ", as.integer(ss), "s)\n", sep="")
print(DT, class=FALSE)

## this chunk requires to include new suggested deps: graphics, grDevices
#memtest.plot = function(.inittime) {
# if (!all(requireNamespace(c("graphics","grDevices"), quietly=TRUE))) return(invisible())
# inittime=PS_rss=GC_used=GC_max_used=NULL
# m = fread("memtest.csv")[inittime==.inittime]
# if (nrow(m)) {
# ps_na = all(is.na(m[["PS_rss"]])) # OS with no 'ps -o rss R' support
# grDevices::png("memtest.png")
# p = graphics::par(mfrow=c(if (ps_na) 2 else 3, 2))
# if (!ps_na) {
# m[, graphics::plot(test, PS_rss, pch=18, xlab="test num", ylab="mem MB", main="ps -o rss R")]
# m[, graphics::plot(timestamp, PS_rss, type="l", xlab="timestamp", ylab="mem MB", main="ps -o rss R")]
# }
# m[, graphics::plot(test, GC_used, pch=18, xlab="test num", ylab="mem MB", main="gc used")]
# m[, graphics::plot(timestamp, GC_used, type="l", xlab="timestamp", ylab="mem MB", main="gc used")]
# m[, graphics::plot(test, GC_max_used, pch=18, xlab="test num", ylab="mem MB", main="gc max used")]
# m[, graphics::plot(timestamp, GC_max_used, type="l", xlab="timestamp", ylab="mem MB", main="gc max used")]
# graphics::par(p)
# grDevices::dev.off()
# } else {
# warning("test.data.table runs with memory testing but did not collect any memory statistics.")
# }
#}
#if (memtest<-get("memtest", envir=env)) memtest.plot(get("inittime", envir=env))

if (nfail > 0) {
if (nfail>1) {s1="s";s2="s: "} else {s1="";s2=" "}
cat("\r")
stop(nfail," error",s1," out of ",ntest," in ",timetaken(started.at)," on ",date(),". [",plat,"].",
" Search inst/tests/tests.Rraw for test number",s2,paste(whichfail,collapse=", "),".")
# important to stop() here, so that 'R CMD check' fails
}
cat(plat,"\n\nAll ",ntest," tests in inst/tests/tests.Rraw completed ok in ",timetaken(started.at)," on ",date(),"\n",sep="")
# date() is included so we can tell exactly when these tests ran on CRAN. Sometimes a CRAN log can show error but that can be just
# stale due to not updating yet since a fix in R-devel, for example.

#attr(ans, "details") <- env
invisible(ans)
}

# nocov start
Expand Down
43 changes: 1 addition & 42 deletions inst/tests/other.Rraw
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ loaded = sapply(pkgs, is.require)

if (sum(!loaded)) {
if (as.logical(Sys.getenv("_R_CHECK_FORCE_SUGGESTS_", "TRUE"))) {
stop(sprintf("Package suggested but not available: %s\n\nThe suggested packages are required for a complete check of data.table integration tests.\nChecking can be attempted without them by setting the environment variable _R_CHECK_FORCE_SUGGESTS_ to a false value.", paste("'", names(loaded)[!loaded], "'", sep="", collapse=", ")))
stop(sprintf("Package (extended) suggested but not available: %s\n\nThe (extended) suggested packages are required for a complete check of data.table integration tests.\nChecking can be attempted without them by setting the environment variable _R_CHECK_FORCE_SUGGESTS_ to a false value.\nList of extended suggested packages used for integration tests can be found in `system.file(file.path('tests','tests-DESCRIPTION'), package='data.table')`.", paste("'", names(loaded)[!loaded], "'", sep="", collapse=", ")))
} else {
invisible(sapply(names(loaded)[!loaded], function(s) cat("\n**** Other package",s,"is not installed. Tests using it will be skipped.\n")))
}
Expand Down Expand Up @@ -191,44 +191,3 @@ if (loaded[["parallel"]]) {
###################################
# Add new tests above this line #
###################################

plat = paste0("endian==", .Platform$endian,
", sizeof(long double)==", .Machine$sizeof.longdouble,
", sizeof(pointer)==", .Machine$sizeof.pointer,
", TZ=", suppressWarnings(Sys.timezone()),
", locale='", Sys.getlocale(), "'")
DT = head(timings[-1L][order(-time)],10) # exclude id 1 as in dev that includes JIT
if ((x<-timings[,sum(nTest)]) != ntest) warning("Timings count mismatch:",x,"vs",ntest)
cat("\n10 longest running tests took ", as.integer(tt<-DT[, sum(time)]), "s (", as.integer(100*tt/(ss<-timings[,sum(time)])), "% of ", as.integer(ss), "s)\n", sep="")
print(DT, class=FALSE)
..inittime = inittime
if (memtest) {
if (file.exists(fn<-"memtest.csv") && # if no tests were run there might be no timings
nrow(m<-fread(fn)[inittime==..inittime])) {
ps_na = all(is.na(m[["PS_rss"]])) # OS with no 'ps -o rss R' support
png("memtest-other.png")
p = par(mfrow=c(if (ps_na) 2 else 3, 2))
if (!ps_na) {
m[, plot(test, PS_rss, pch=18, xlab="test num", ylab="mem MB", main="ps -o rss R")]
m[, plot(timestamp, PS_rss, type="l", xlab="timestamp", ylab="mem MB", main="ps -o rss R")]
}
m[, plot(test, GC_used, pch=18, xlab="test num", ylab="mem MB", main="gc used")]
m[, plot(timestamp, GC_used, type="l", xlab="timestamp", ylab="mem MB", main="gc used")]
m[, plot(test, GC_max_used, pch=18, xlab="test num", ylab="mem MB", main="gc max used")]
m[, plot(timestamp, GC_max_used, type="l", xlab="timestamp", ylab="mem MB", main="gc max used")]
par(p)
dev.off()
} else {
warning("test.data.table runs with memory testing but did not collect any memory statistics.", call.=FALSE)
}
}
if (nfail > 0) {
if (nfail>1) {s1="s";s2="s: "} else {s1="";s2=" "}
cat("\r")
stop(nfail," error",s1," out of ",ntest," in ",timetaken(started.at)," on ",date(),". [",plat,"].",
" Search inst/tests/other.Rraw for test number",s2,paste(whichfail,collapse=", "),".")
# important to stop() here, so that 'R CMD check' fails
}
cat(plat,"\nAll ",ntest," tests in inst/tests/other.Rraw completed ok in ",timetaken(started.at)," on ",date(),"\n",sep="")
# date() is included so we can tell exactly when these tests ran on CRAN. Sometimes a CRAN log can show error but that can be just
# stale due to not updating yet since a fix in R-devel, for example.
2 changes: 1 addition & 1 deletion inst/tests/tests-DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -3,5 +3,5 @@ Version: 0.1
Type: Backend
Title: List of data.table dependencies used in integration tests
Authors@R: c(person("data.table team", role = c("aut", "cre", "cph"), email="[email protected]"))
Description: Standalone R DESCRIPTION file which defines R dependencies for integration tests of data.table package.
Description: Standalone R DESCRIPTION file which defines R dependencies for integration tests of data.table package. Integration tests are not part of main testing workflow. They are performed only when TEST_DATA_TABLE_WITH_OTHER_PACKAGES environment variable is set to true. This allows us to run those integration tests in our CI pipeline and not impose dependency chains on the user.
Suggests: ggplot2 (>= 0.9.0), reshape, hexbin, fastmatch, nlme, gdata, caret, plm, rmarkdown, parallel
55 changes: 1 addition & 54 deletions inst/tests/tests.Rraw
Original file line number Diff line number Diff line change
@@ -1,11 +1,5 @@
require(methods)

# From R 3.6.0 onwards, we can check that && and || are using only length-1 logicals (in the test suite)
# rather than relying on x && y being equivalent to x[[1L]] && y[[1L]] silently.
orig__R_CHECK_LENGTH_1_LOGIC2_ <- Sys.getenv("_R_CHECK_LENGTH_1_LOGIC2_", unset = NA_character_)
Sys.setenv("_R_CHECK_LENGTH_1_LOGIC2_" = TRUE)
# This environment variable is restored to its previous state (including not defined) at the end of this file

if (exists("test.data.table", .GlobalEnv, inherits=FALSE)) {
if (!identical(suppressWarnings(packageDescription("data.table")), NA)) {
remove.packages("data.table")
Expand Down Expand Up @@ -13321,51 +13315,4 @@ test(1980, names(data.table(x)), "x")
###################################

options(oldOptions) # set at top of this file

setDTthreads(0)
plat = paste0("endian==", .Platform$endian,
", sizeof(long double)==", .Machine$sizeof.longdouble,
", sizeof(pointer)==", .Machine$sizeof.pointer,
", TZ=", suppressWarnings(Sys.timezone()),
", locale='", Sys.getlocale(), "'",
", l10n_info()='", paste0(names(l10n_info()), "=", l10n_info(), collapse="; "), "'")
DT = head(timings[-1L][order(-time)],10) # exclude id 1 as in dev that includes JIT
if ((x<-timings[,sum(nTest)]) != ntest) warning("Timings count mismatch:",x,"vs",ntest)
cat("\n10 longest running tests took ", as.integer(tt<-DT[, sum(time)]), "s (", as.integer(100*tt/(ss<-timings[,sum(time)])), "% of ", as.integer(ss), "s)\n", sep="")
print(DT, class=FALSE)
if (memtest) {
..inittime = inittime
m = fread("memtest.csv")[inittime==..inittime]
if (nrow(m)) {
ps_na = all(is.na(m[["PS_rss"]])) # OS with no 'ps -o rss R' support
png("memtest.png")
p = par(mfrow=c(if (ps_na) 2 else 3, 2))
if (!ps_na) {
m[, plot(test, PS_rss, pch=18, xlab="test num", ylab="mem MB", main="ps -o rss R")]
m[, plot(timestamp, PS_rss, type="l", xlab="timestamp", ylab="mem MB", main="ps -o rss R")]
}
m[, plot(test, GC_used, pch=18, xlab="test num", ylab="mem MB", main="gc used")]
m[, plot(timestamp, GC_used, type="l", xlab="timestamp", ylab="mem MB", main="gc used")]
m[, plot(test, GC_max_used, pch=18, xlab="test num", ylab="mem MB", main="gc max used")]
m[, plot(timestamp, GC_max_used, type="l", xlab="timestamp", ylab="mem MB", main="gc max used")]
par(p)
dev.off()
} else {
warning("test.data.table runs with memory testing but did not collect any memory statistics.")
}
}
if (nfail > 0) {
if (nfail>1) {s1="s";s2="s: "} else {s1="";s2=" "}
cat("\r")
stop(nfail," error",s1," out of ",ntest," in ",timetaken(started.at)," on ",date(),". [",plat,"].",
" Search inst/tests/tests.Rraw for test number",s2,paste(whichfail,collapse=", "),".")
# important to stop() here, so that 'R CMD check' fails
}
cat(plat,"\n\nAll ",ntest," tests in inst/tests/tests.Rraw completed ok in ",timetaken(started.at)," on ",date(),"\n",sep="")
# date() is included so we can tell exactly when these tests ran on CRAN. Sometimes a CRAN log can show error but that can be just
# stale due to not updating yet since a fix in R-devel, for example.
if (is.na(orig__R_CHECK_LENGTH_1_LOGIC2_)) {
Sys.unsetenv("_R_CHECK_LENGTH_1_LOGIC2_")
} else {
Sys.setenv("_R_CHECK_LENGTH_1_LOGIC2_" = orig__R_CHECK_LENGTH_1_LOGIC2_)
}
setDTthreads(0) # this has not been altered directly before so not sure if we should really reset it here
4 changes: 1 addition & 3 deletions tests/main.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
require(data.table)

test.data.table() # runs the main test suite of 5,000+ tests in /inst/tests/tests.Rraw

# integration tests for packages excluded from Suggests in 1.10.5
Expand All @@ -10,6 +11,3 @@ if (with.other.packages) test.data.table(with.other.packages=with.other.packages
# test.data.table(verbose=TRUE)
# Calling it again in the past revealed some memory bugs but also verbose mode checks the verbose messages run ok
# TO DO: check we test each verbose message at least once, instead of a full repeat of all tests



0 comments on commit a08547e

Please sign in to comment.