@@ -7594,7 +7594,7 @@ dt = data.table(x=1:5, y=6:10)
75947594test(1536, duplicated(dt, incomparables=TRUE), error = base_messages$not_yet_used('incomparables != FALSE'))
75957595
75967596# test for covering melt 100%
7597- test(1537 , names(melt(dt, id.vars=1L, variable.name = "x", value.name="x")), c("x", "x.1", "x.2"), output = "Duplicate column names")
7597+ test(1537, names(melt(dt, id.vars=1L, variable.name = "x", value.name="x")), c("x", "x.1", "x.2"), output = "Duplicate column names")
75987598
75997599# test for tables()
76007600test(1538.1, tables(), output="Total:")
@@ -7899,20 +7899,20 @@ DT = data.table(int = 1:K,
78997899 bool = sample( c(TRUE, FALSE), K, replace = TRUE))
79007900
79017901DT_NA = DT
7902- for (j in seq_len( ncol(DT) )) {
7902+ for (j in seq_len(ncol(DT))) {
79037903 set(x = DT_NA, i = j, j = j, value = NA)
79047904}
79057905
7906- for(k in seq_along(nastrings)) {
7906+ for (k in seq_along(nastrings)) {
79077907 dt0 = copy(DT)
7908- for (j in seq_len( ncol(DT) )) {
7908+ for (j in seq_len(ncol(DT))) {
79097909 set(x = dt0, i = NULL, j = j, value = as.character(dt0[[j]]))
79107910 set(x = dt0, i = j, j = j, value = nastrings[[k]])
79117911 }
79127912 str = do.call(paste, c(dt0, collapse="\n", sep=","))
79137913 str = paste(paste(names(dt0), collapse=","), str, sep="\n")
79147914 DT_fread = fread(str, na.strings = nastrings, verbose = FALSE)
7915- test(1550 + k * 0.1, DT_fread, DT_NA)
7915+ test(1550 + k * 0.1, DT_fread, DT_NA, context=sprintf("nastrings=%s", nastrings[k]) )
79167916}
79177917
79187918# FR #568
@@ -11371,7 +11371,7 @@ for (i in seq_len(nrow(dt))) {
1137111371 groupingsets(dt[i], j = lapply(.SD, sum), by = c("color", "year", "status"), sets=list(c("color", "year", "status"), "year", "status", character())),
1137211372 by=c("amount", "value")),
1137311373 1L,
11374- context = sprintf("dt[%d]", i))
11374+ context= sprintf("dt[%d]", i))
1137511375}
1137611376# all grouping id matches in all totals
1137711377r = groupingsets(dt, j = c(list(cnt=.N), lapply(.SD, sum)), by = c("color","year","status"), sets=list(c("color","year","status"), c("year"), c("status"), character()), id=TRUE)
@@ -11616,7 +11616,7 @@ test(1762, DT[ , {}], NULL)
1161611616# rbindlist empty items segfault, #2019
1161711617x = list(list(a = 1), list(), list(a = 2))
1161811618ans = data.table(id=c(1L,3L),a=c(1,2))
11619- for (i in 1:100) test(1763+i/1000, rbindlist(x, idcol="id"), ans)
11619+ for (i in 1:100) test(1763+i/1000, rbindlist(x, idcol="id"), ans, context=sprintf("i=%d", i) )
1162011620
1162111621# as.ITime(character(0)) used to fail, #2032
1162211622test(1764.1, format(as.ITime(character(0))), character(0))
@@ -11989,8 +11989,8 @@ for (mul in c(16, 128, 512, 1024, 2048)) {
1198911989 cat(strrep("1234,5678,9012,3456,7890,abcd,4\x0A", mul), file=ff)
1199011990 close(ff)
1199111991 DT = data.table(V1=rep(1234L, mul), V2=5678L, V3=9012L, V4=3456L, V5=7890L, V6="abcd", V7=4L)
11992- test(1801 + log2(mul)/100 + 0.001, file.info(f)$size, mul*32)
11993- test(1801 + log2(mul)/100 + 0.002, fread(f), DT)
11992+ test(1801 + log2(mul)/100 + 0.001, file.info(f)$size, mul*32, context=sprintf("mul=%d [file size]", mul) )
11993+ test(1801 + log2(mul)/100 + 0.002, fread(f), DT, context=sprintf("mul=%d [fread]", mul) )
1199411994}
1199511995# Test without the newline
1199611996ff = file(f<-tempfile(), open="wb")
@@ -12444,7 +12444,7 @@ DTs = list( # passed fread(fwrite(DT))==DT
1244412444f = tempfile()
1244512445for (i in seq_along(DTs)) {
1244612446 fwrite(DTs[[i]], file=f)
12447- test(1857.0 + i/100, fread(f), DTs[[i]])
12447+ test(1857.0 + i/100, fread(f), DTs[[i]], context=sprintf("%d", i) )
1244812448}
1244912449unlink(f)
1245012450
@@ -12624,7 +12624,7 @@ test(1871.13, fread("A\n100\n200", verbose=TRUE), data.table(A=c(100L,200L)), ou
1262412624test(1871.14, fread("col1, col2, col3\n1, 2, 3\n3, 5, 6\n7, 8, 9\n\nsome text to ignore", nrows = 3L), data.table(col1=INT(1,3,7), col2=INT(2,5,8), col3=INT(3,6,9))) # from #1671 (no warning expected)
1262512625for (i in 100:1) {
1262612626 lines <- paste(c(rep("2,3,4",i), "2,3"), collapse='\n')
12627- test(1871.2 + (100-i)/1000, fread(lines, nrows=i), data.table(V1=rep.int(2L,i), V2=3L, V3=4L))
12627+ test(1871.2 + (100-i)/1000, fread(lines, nrows=i), data.table(V1=rep.int(2L,i), V2=3L, V3=4L), context=sprintf("i=%d", i) )
1262812628}
1262912629
1263012630# miscellaneous missing tests uncovered by CodeCov difference in the process of PR #2573
@@ -13084,7 +13084,7 @@ test(1913.10, all(names(M) %in% union(names(M), names(m))))
1308413084test_no = 0L
1308513085for (name in names(m)) {
1308613086 test_no = test_no + 1L
13087- test(1913.11 + test_no*0.0001, M[[name]], m[[name]])
13087+ test(1913.11 + test_no*0.0001, M[[name]], m[[name]], context=sprintf("name=%s", name) )
1308813088}
1308913089#
1309013090# Original example that smoked out the bug
@@ -13102,7 +13102,7 @@ test(1913.13, all(names(M) %in% union(names(M), names(m))))
1310213102test_no = 0L
1310313103for (name in names(m)) {
1310413104 test_no = test_no + 1L
13105- test(1913.14 + test_no*0.0001, M[[name]], m[[name]])
13105+ test(1913.14 + test_no*0.0001, M[[name]], m[[name]], context=sprintf("name=%s", name) )
1310613106}
1310713107#
1310813108# simple subset maintains keys
@@ -13140,7 +13140,7 @@ test(1913.23, is.null(key(t2))) # transforming a key column nukes the key
1314013140test_no = 0L
1314113141for (col in c('b', 'c')) {
1314213142 test_no = test_no + 1L
13143- test(1913.24 + test_no*0.0001, t2[[col]], dt[[col]]) # mutating-key-transform maintains other columns
13143+ test(1913.24 + test_no*0.0001, t2[[col]], dt[[col]], context=sprintf("col=%s", col) ) # mutating-key-transform maintains other columns
1314413144}
1314513145
1314613146# Test 1914 of S4 compatibility was moved to S4.Rraw for #3808
@@ -13513,7 +13513,7 @@ eols = c("\n", "\r\n", "\r", "\n\r")
1351313513for (i in 1:4) {
1351413514 eol = eols[i]
1351513515 src = paste(c("A", "B", "...", ",,,,,", "c1,c2,c3", "1,2,3"), collapse=eol)
13516- test(1959 + (i*0.1), fread(text=src, skip=4), data.table(c1=1L, c2=2L, c3=3L))
13516+ test(1959 + (i*0.1), fread(text=src, skip=4), data.table(c1=1L, c2=2L, c3=3L), context=sprintf("i=%d", i) )
1351713517}
1351813518test(1959.5, fread("A\n\nB\n\nC\n1\n", skip=2), data.table(B=c("", "C", "1")))
1351913519test(1959.6, fread("A,B\r\r\nX,Y\r\r\nB,C\r\r\n1,2", skip=4), data.table(B=1L, C=2L))
@@ -14872,17 +14872,17 @@ f = tempfile()
1487214872for (nNUL in 0:3) {
1487314873 writeBin(c(charToRaw("a=b\nA B C\n1 3 5\n"), rep(as.raw(0), nNUL), charToRaw("2 4 6\n")), con=f)
1487414874 num_major = (1+nNUL)/10
14875- test(2025 + num_major + .01, fread(f, skip=1, header=TRUE), ans<-data.table(A=1:2, B=3:4, C=5:6))
14876- test(2025 + num_major + .02, fread(f), ans) # auto detect skip and header works too
14875+ test(2025 + num_major + .01, fread(f, skip=1, header=TRUE), ans<-data.table(A=1:2, B=3:4, C=5:6), context=sprintf("nNul=%d [I]", nNul) )
14876+ test(2025 + num_major + .02, fread(f), ans, context=sprintf("nNul=%d [II]", nNul) ) # auto detect skip and header works too
1487714877 writeBin(c(charToRaw("a=b\nA,B,C\n1,3,5\n"), rep(as.raw(0), nNUL), charToRaw("2,4,6\n")), con=f)
14878- test(2025 + num_major + .03, fread(f, skip=1, header=TRUE), ans)
14879- test(2025 + num_major + .04, fread(f), ans)
14878+ test(2025 + num_major + .03, fread(f, skip=1, header=TRUE), ans, context=sprintf("nNul=%d [III]", nNul) )
14879+ test(2025 + num_major + .04, fread(f), ans, context=sprintf("nNul=%d [IV]", nNul) )
1488014880 writeBin(c(charToRaw("a=b\n"), rep(as.raw(0), nNUL), charToRaw("A B C\n1 3 5\n2 4 6\n")), con=f)
14881- test(2025 + num_major + .05, fread(f, skip=1, header=TRUE), ans)
14882- test(2025 + num_major + .06, fread(f), ans)
14881+ test(2025 + num_major + .05, fread(f, skip=1, header=TRUE), ans, context=sprintf("nNul=%d [V]", nNul) )
14882+ test(2025 + num_major + .06, fread(f), ans, context=sprintf("nNul=%d [VI]", nNul) )
1488314883 writeBin(c(charToRaw("a=b\n"), rep(as.raw(0), nNUL), charToRaw("A,B,C\n1,3,5\n2,4,6\n")), con=f)
14884- test(2025 + num_major + .07, fread(f, skip=1, header=TRUE), ans)
14885- test(2025 + num_major + .08, fread(f), ans)
14884+ test(2025 + num_major + .07, fread(f, skip=1, header=TRUE), ans, context=sprintf("nNul=%d [VII]", nNul) )
14885+ test(2025 + num_major + .08, fread(f), ans, context=sprintf("nNul=%d [VIII]", nNul) )
1488614886}
1488714887makeNul = function(str){ tt=charToRaw(str); tt[tt==42L]=as.raw(0); writeBin(tt, con=f)} # "*" (42) represents NUL
1488814888makeNul("A,B,C\n1,foo,5\n2,*bar**,6\n")
@@ -17148,8 +17148,8 @@ DT = data.table(A=INT(1,1,2,3,3,4,5,5,6,7),
1714817148 B=lapply(1:10, function(x) structure(rnorm(90), foo=c(42,12,36))))
1714917149for (i in 0:4) test(2155+i/10,
1715017150 { gctorture2(step=20); ans=DT[, .(attr(B[[1L]],"foo")[1L]), by=A]; gctorture2(step=0); gc(); ans },
17151- data.table(A=1:7, V1=42)
17152- )
17151+ data.table(A=1:7, V1=42),
17152+ context=sprintf("i=%d", i) )
1715317153
1715417154# dogroups.c eval(j) could create list columns containing altrep references to the specials, #4759
1715517155# thanks to revdep testing of 1.13.2 where package tstools revealed this via ts() creating ALTREP, #4758
@@ -17791,27 +17791,36 @@ test(2210.26, DT[-c(1L,0L), nomatch=0], data.table(x=2:4), warning="Please use n
1779117791# NA in i would segfault gforce, #1994
1779217792DT = data.table(a=1L, b=2, c="a", grp=1L)
1779317793i = c(1L,NA,NA,NA) # 3 NA to trigger segfault in var (min 3 obs) otherwise just c(1L,NA) is enough to trigger the others
17794- funs = c("sum","mean","var","sd","median","prod","min","max","`[`","first","last","head","tail")
17794+ funs = list(
17795+ supports_na_rm = list(
17796+ no_character = c("sum", "mean", "var", "sd", "median", "prod"),
17797+ supports_character = c("min", "max")),
17798+ needs_index = c("`[`", "first", "last", "head", "tail")
17799+ )
17800+ n_numeric_only = length(funs$supports_na_rm$no_character)
17801+ n_supporting_na_rm = sum(lengths(funs$supports_na_rm))
17802+ funs = unlist(funs)
1779517803EVAL = function(...) {
1779617804 e = paste0(...)
17797- # cat(e,"\n") # uncomment to check the queries tested
1779817805 eval(parse(text=e))
1779917806}
1780017807testnum = 0L
17801- for (col in c("a","b","c")) {
17808+ for (col in c("a", "b", "c")) {
1780217809 testnum = testnum + 100L
1780317810 for (fi in seq_along(funs)) {
17804- if (col== "c" && fi<=6L ) next # first 6 funs don't support type character
17811+ if (col == "c" && fi <= n_numeric_only ) next
1780517812 f = funs[fi]
1780617813 testnum = testnum + 1L
1780717814 test(2211.0 + testnum*0.001,
17808- EVAL("DT[i, ",f,"(",col, if(fi>8L)", 1L","), by=grp]"), # segfault before when NA in i
17809- EVAL("DT[i][, ",f,"(",col, if(fi>8L)", 1L","), by=grp]")) # ok before by taking DT[i] subset first
17810- if (fi<=8L) {
17815+ EVAL("DT[i, ",f,"(",col, if(fi > n_supporting_na_rm)", 1L","), by=grp]"), # segfault before when NA in i
17816+ EVAL("DT[i][, ",f,"(",col, if(fi > n_supporting_na_rm)", 1L","), by=grp]"), # ok before by taking DT[i] subset first
17817+ context=sprintf("col=%s, f=%s", col, f))
17818+ if (fi <= n_supporting_na_rm) {
1781117819 testnum = testnum + 1L
1781217820 test(2211.0 + testnum*0.001,
1781317821 EVAL("DT[i, ",f,"(",col,", na.rm=TRUE), by=grp]"),
17814- EVAL("DT[i][, ",f,"(",col,", na.rm=TRUE), by=grp]"))
17822+ EVAL("DT[i][, ",f,"(",col,", na.rm=TRUE), by=grp]"),
17823+ context=sprintf("col=%s, f=%s [na.rm=TRUE]", col, f))
1781517824 }
1781617825 }
1781717826}
0 commit comments