@@ -2687,11 +2687,11 @@ for (ne in seq_along(eols)) {
26872687 # on unix we simulate Windows too. On Windows \n will write \r\n (and \r\n will write \r\r\n)
26882688 num_major = nr/100 + nc/1000 + ne/10000
26892689 # if (isTRUE(all.equal(testIDtail, 0.4103))) browser()
2690- test(894+ num_major+ 0.00001, fread(f,na.strings=""), headDT)
2691- cat(eol,file=f,append=TRUE) # now a normal file properly ending with final \n
2692- test(894+ num_major+ 0.00002, fread(f,na.strings=""), headDT)
2693- cat(eol,file=f,append=TRUE) # extra \n should be ignored other than for single columns where it is significant
2694- test(894+ num_major+ 0.00003, fread(f,na.strings=""), if (nc==1) rbind(headDT, list(NA)) else headDT)
2690+ test(894 + num_major + 0.00001, fread(f, na.strings=""), headDT, context=sprintf("nr=%d, nc=%d, ne=%d [I]", nr, nc, ne) )
2691+ cat(eol, file=f, append=TRUE) # now a normal file properly ending with final \n
2692+ test(894 + num_major + 0.00002, fread(f, na.strings=""), headDT, context=sprintf("nr=%d, nc=%d, ne=%d [II]", nr, nc, ne) )
2693+ cat(eol, file=f, append=TRUE) # extra \n should be ignored other than for single columns where it is significant
2694+ test(894 + num_major + 0.00003, fread(f, na.strings=""), if (nc==1) rbind(headDT, list(NA)) else headDT, context=sprintf("nr=%d, nc=%d, ne=%d [III]", nr, nc, ne) )
26952695 unlink(f)
26962696}}}
26972697if (test_bit64) {
@@ -4462,13 +4462,13 @@ old_rounding = getNumericRounding()
44624462DT = data.table(A=c(1,2,-Inf,+Inf,3,-1.1,NaN,NA,3.14,NaN,2.8,NA), B=1:12, key="A")
44634463for (i in 0:1) { # tests 1207 & 1208
44644464 setNumericRounding(if (i==0L) 0L else 2L)
4465- test(1207+i+ 0.1, DT[.(c(NA_real_,Inf)),B], INT(8,12,4 ))
4466- test(1207+i+ 0.2, DT[.(c(Inf,NA_real_)),B], INT(4,8,12 ))
4467- test(1207+i+ 0.3, DT[.(c(NaN,NA_real_)),B], INT(7,10,8,12 ))
4468- test(1207+i+ 0.4, DT[.(c(NA_real_,NaN)),B], INT(8,12,7,10 ))
4469- test(1207+i+ 0.5, DT[,sum(B),by=A]$V1, INT(20,17,3,6,1,2, 11,5,9,4 ))
4470- test(1207+i+ 0.6, DT[,sum(B),by=list(g=abs(trunc(A)))], data.table(g=c(NA,NaN,Inf,1,2, 3),V1=INT(20,17,7,7, 13,14)))
4471- test(1207+i+ 0.7, DT[,sum(B),keyby=list(g=abs(trunc(A)))], data.table(g=c(NA,NaN,1,2,3, Inf),V1=INT(20,17,7, 13,14,7),key="g"))
4465+ test(1207 + i + 0.1, DT[.(c(NA_real_,Inf)), B], INT(8, 12, 4), context=sprintf("setNumericRounding(%d) [I]", 2*i ))
4466+ test(1207 + i + 0.2, DT[.(c(Inf,NA_real_)), B], INT(4, 8, 12), context=sprintf("setNumericRounding(%d) [II]", 2*i ))
4467+ test(1207 + i + 0.3, DT[.(c(NaN,NA_real_)), B], INT(7, 10, 8, 12), context=sprintf("setNumericRounding(%d) [III]", 2*i ))
4468+ test(1207 + i + 0.4, DT[.(c(NA_real_,NaN)), B], INT(8, 12, 7, 10), context=sprintf("setNumericRounding(%d) [IV]", 2*i ))
4469+ test(1207 + i + 0.5, DT[, sum(B), by=A]$V1, INT(20, 17, 3, 6, 1, 2, 11, 5, 9, 4), context=sprintf("setNumericRounding(%d) [V]", 2*i ))
4470+ test(1207 + i + 0.6, DT[, sum(B), by=list(g=abs(trunc(A)))], data.table(g=c(NA, NaN, Inf, 1, 2, 3), V1=INT(20, 17, 7, 7, 13, 14)), context=sprintf("setNumericRounding(%d) [VI]", 2*i ))
4471+ test(1207 + i + 0.7, DT[, sum(B), keyby=list(g=abs(trunc(A)))], data.table(g=c(NA, NaN, 1, 2, 3, Inf), V1=INT(20, 17, 7, 13, 14, 7), key="g"), context=sprintf("setNumericRounding(%d) [VII]", 2*i ))
44724472 # test(1207+i+0.8, DT[.(-200.0),roll=TRUE]$B, 3L) # TO DO: roll to -Inf. Also remove -Inf and test rolling to NaN and NA
44734473}
44744474setNumericRounding(old_rounding)
@@ -4537,7 +4537,7 @@ seedInfo = paste(seedInfo, "colorder = ", paste(colorder, collapse=","), sep="")
45374537test_no = 0L
45384538oldnfail = nfail
45394539for (nvars in seq_along(names(DT))) {
4540- signs = expand.grid(replicate(nvars, c(-1L,1L), simplify=FALSE))
4540+ signs = expand.grid(replicate(nvars, c(-1L, 1L), simplify=FALSE))
45414541 combn(names(DT), nvars, simplify=FALSE, function(x) { # simplify=FALSE needed for R 3.1.0
45424542 for (i in seq_len(nrow(signs))) {
45434543 test_no <<- test_no + 1L
@@ -4555,7 +4555,7 @@ for (nvars in seq_along(names(DT))) {
45554555 }
45564556 })
45574557 ))
4558- test(1223.0 + test_no*0.001, forderv(DT, by=x, order=signs[i,]), with(DT, eval(ll)))
4558+ test(1223.0 + test_no*0.001, forderv(DT, by=x, order=signs[i,]), with(DT, eval(ll)), context=sprintf("signs[%d, ]==%s", i, paste(unlist(signs[i, ]), collapse=",")) )
45594559 }
45604560 integer()
45614561 })
@@ -4679,10 +4679,10 @@ for (i in seq_along(names(DT))) {
46794679 cc = combn(names(DT), i)
46804680 apply(cc, 2L, function(jj) {
46814681 test_no <<- test_no + 1L # first without key
4682- test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE))
4682+ test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE), context=sprintf("jj=%s", paste(jj, collapse=",")) )
46834683 test_no <<- test_no + 1L
46844684 setkeyv(DT, jj) # with key
4685- test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE))
4685+ test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE), context=sprintf("jj=%s", paste(jj, collapse=",")) )
46864686 })
46874687}
46884688if (nfail > oldnfail) cat(seedInfo, "\n") # to reproduce
@@ -4702,10 +4702,10 @@ for (i in seq_along(names(DT))) {
47024702 cc = combn(names(DT), i)
47034703 apply(cc, 2L, function(jj) {
47044704 test_no <<- test_no + 1L # first without key
4705- test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE))
4705+ test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE), context=sprintf("jj=%s", paste(jj, collapse=",")) )
47064706 test_no <<- test_no + 1L
47074707 setkeyv(DT, jj) # with key
4708- test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE))
4708+ test(1246.0 + test_no*0.01, duplicated(DT, by=jj, fromLast=TRUE), duplicated.data.frame(DT[, jj, with=FALSE], fromLast=TRUE), context=sprintf("jj=%s", paste(jj, collapse=",")) )
47094709 })
47104710}
47114711if (nfail > oldnfail) cat(seedInfo, "\n") # to reproduce
@@ -4801,22 +4801,23 @@ for (i in seq_along(names(DT))) {
48014801 as.name("base_order"),
48024802 method = "radix",
48034803 lapply(seq_along(x), function(j) {
4804+ x_nm = as.name(x[j])
48044805 if (y[j] == 1L)
4805- as.name(x[j])
4806+ x_nm
48064807 else {
48074808 if (is.character(DT[[x[j]]]))
4808- as.call(c(as.name("-"), as.call(list(as.name("xtfrm"), as.name(x[j]) ))))
4809+ as.call(c(as.name("-"), as.call(list(as.name("xtfrm"), x_nm ))))
48094810 else
4810- as.call(list(as.name("-"), as.name(x[j]) ))
4811+ as.call(list(as.name("-"), x_nm ))
48114812 }
48124813 })
48134814 ))
48144815 ans1 = forderv(DT, by=x, order=y, na.last=TRUE) # adding tests for both nalast=TRUE and nalast=NA
4815- test(1252.0 + test_no*0.001, ans1, with(DT, eval(ll)))
4816+ test(1252.0 + test_no*0.001, ans1, with(DT, eval(ll)), context=sprintf("ll=%s", format(ll)) )
48164817 test_no <<- test_no + 1L
48174818 ll <- as.call(c(as.list(ll), na.last=NA))
48184819 ans1 = forderv(DT, by=x, order=y, na.last=NA) # nalast=NA here.
4819- test(1252.0 + test_no*0.001, ans1[ans1 != 0], with(DT, eval(ll)))
4820+ test(1252.0 + test_no*0.001, ans1[ans1 != 0], with(DT, eval(ll)), context=sprintf("ll=%s", format(ll)) )
48204821 })
48214822 dim(tmp)=NULL
48224823 list(tmp)
@@ -4942,12 +4943,12 @@ setNumericRounding(old_rounding)
49424943# http://stackoverflow.com/questions/22290544/grouping-very-small-numbers-e-g-1e-28-and-0-0-in-data-table-v1-8-10-vs-v1-9-2
49434944old_rounding = getNumericRounding()
49444945test_no = 0L
4945- for (dround in c(0,2)) {
4946+ for (dround in c(0, 2)) {
49464947 setNumericRounding(dround) # rounding should not affect the result here because although small, it's very accurace (1 s.f.)
4947- for (i in c(-30:-1,1:30)) {
4948- DT = data.table(c(1 * (10^i),2, 9999,-1,0, 1))
4948+ for (i in c(-30:-1, 1:30)) {
4949+ DT = data.table(c(1 * (10^i), 2, 9999, -1, 0, 1))
49494950 test_no = test_no + 1L
4950- test(1278.0 + test_no*0.001, nrow(DT[, .N, by=V1]), 6L)
4951+ test(1278.0 + test_no*0.001, nrow(DT[, .N, by=V1]), 6L, context=sprintf("dround=%d, i=%d", dround, i) )
49514952 }
49524953}
49534954setNumericRounding(old_rounding)
@@ -5781,9 +5782,9 @@ for (i in seq_along(dt)) {
57815782 r4 = frankv(col, order=-1L, ties.method=k, na.last=j)
57825783
57835784 test_no = test_no + 1L
5784- test(1368.0 + test_no*0.0001, r1, r3)
5785+ test(1368.0 + test_no*0.0001, r1, r3, context=sprintf("i=%d, j=%s, k=%s [asc]", i, j, k) )
57855786 test_no = test_no + 1L
5786- test(1368.0 + test_no*0.0001, r2, r4)
5787+ test(1368.0 + test_no*0.0001, r2, r4, context=sprintf("i=%d, j=%s, k=%s [desc]", i, j, k) )
57875788 }
57885789 }
57895790}
@@ -5813,9 +5814,9 @@ for (i in seq_along(dt)) {
58135814 r4 = frankv(col, order=-1L, ties.method=k, na.last=NA)
58145815
58155816 test_no = test_no + 1L
5816- test(1369.0 + test_no*0.0001, r1, r3)
5817+ test(1369.0 + test_no*0.0001, r1, r3, context=sprintf("i=%d, k=%s [asc]", i, k) )
58175818 test_no = test_no + 1L
5818- test(1369.0 + test_no*0.0001, r2, r4)
5819+ test(1369.0 + test_no*0.0001, r2, r4, context=sprintf("i=%d, k=%s [desc]", i, k) )
58195820 }
58205821}
58215822
@@ -5838,13 +5839,13 @@ for (i in seq_along(dt)) {
58385839 ans1 = is_na(dt[cols])
58395840 ans2 = rowSums(is.na(as.data.table(dt[cols]))) > 0L
58405841 test_no <<- test_no + 1L
5841- test(1370.0 + test_no*0.0001, ans1, ans2)
5842+ test(1370.0 + test_no*0.0001, ans1, ans2, context=sprintf("cols=%s [is_na]", paste(cols, collapse=",")) )
58425843
58435844 # update: tests for any_na
58445845 test_no <<- test_no + 1L
5845- test(1370.0 + test_no*0.0001, any_na(dt[cols]), TRUE )
5846+ test(1370.0 + test_no*0.0001, any_na(dt[cols]), context=sprintf("cols=%s [any_na]", paste(cols, collapse=",")) )
58465847 test_no <<- test_no + 1L
5847- test(1370.0 + test_no*0.0001, any_na(ans[cols]), FALSE )
5848+ test(1370.0 + test_no*0.0001, ! any_na(ans[cols]), context=sprintf("cols=%s [!any_na]", paste(cols, collapse=",")) )
58485849 TRUE
58495850 })
58505851}
@@ -5971,7 +5972,7 @@ for (run in seq_len(times)) {
59715972 # cat("test =", test_no, ", run = ", run, ", type = ", type, ", mult = ", mult, "\n", sep="")
59725973 idx = paste(type, mult, run, sep="_")
59735974 # ans[[idx]] contains fo(gr(i), gr(x), type=type, select=mult)
5974- test(1372.0 + test_no*0.01, thisans, ans[[idx]])
5975+ test(1372.0 + test_no*0.01, thisans, ans[[idx]], context=sprintf("run=%d, type=%s, mult=%s", run, type, mult") )
59755976 this = this+1L
59765977 }
59775978 }
@@ -6197,7 +6198,7 @@ for (i in seq_along(DT)) {
61976198 ans1 = na.omit(DT, cols=cols)
61986199 ans2 = DT[stats::complete.cases(DT[, cols, with=FALSE])]
61996200 test_no <<- test_no + 1L
6200- test(1394.0 + test_no*0.001, ans1, ans2)
6201+ test(1394.0 + test_no*0.001, ans1, ans2, context=sprintf("cols=%s", paste(cols, collapse=",")) )
62016202 0L
62026203 })
62036204}
@@ -6566,32 +6567,32 @@ bys <- c("groupCol", "sortedGroupCol", character(0))
65666567test_no <- 1438.0000
65676568if (.Machine$sizeof.pointer>4) { # temporarily disabled for 32bit, #2767
65686569
6569- for(t in seq_len(nrow(all))){
6570+ for (t in seq_len(nrow(all))) {
65706571 ## test the query with missing j
65716572 thisQuery <- all$query[t]
65726573 options("datatable.optimize" = 3L)
65736574 ansOpt <- DT[eval(parse(text = thisQuery))]
65746575 options("datatable.optimize" = 2L)
65756576 ansRef <- DT[eval(parse(text = thisQuery))]
65766577 test_no <- test_no + 1L
6577- test(1438.0 + test_no*0.0001, ansOpt, ansRef)
6578+ test(1438.0 + test_no*0.0001, ansOpt, ansRef, context=sprintf("t=%d [I]", t) )
65786579 ## repeat the test with 'which = TRUE'
65796580 options("datatable.optimize" = 3L)
65806581 ansOpt <- DT[eval(parse(text = thisQuery)), which = TRUE]
65816582 options("datatable.optimize" = 2L)
65826583 ansRef <- DT[eval(parse(text = thisQuery)), which = TRUE]
65836584 test_no <- test_no + 1L
6584- test(1438.0 + test_no*0.0001, ansOpt, ansRef)
6585+ test(1438.0 + test_no*0.0001, ansOpt, ansRef, context=sprintf("t=%d [II]", t) )
65856586 ## repeat the test with the j queries
6586- for(thisJquery in jQueries) {
6587+ for (thisJquery in jQueries) {
65876588 ## do it with and without existing "by"
6588- for(thisBy in bys){
6589+ for (thisBy in bys) {
65896590 options("datatable.optimize" = 3L)
65906591 ansOpt <- DT[eval(parse(text = thisQuery)), eval(parse(text = thisJquery)), by = thisBy]
65916592 options("datatable.optimize" = 2L)
65926593 ansRef <- DT[eval(parse(text = thisQuery)), eval(parse(text = thisJquery)), by = thisBy]
65936594 test_no <- test_no + 1L
6594- test(1438.0 + test_no*0.0001, ansOpt, ansRef)
6595+ test(1438.0 + test_no*0.0001, ansOpt, ansRef, context=sprintf("t=%d, thisJquery=%s, thisBy=%s", t, thisJquery, thisBy) )
65956596 }
65966597 }
65976598}
@@ -6890,12 +6891,12 @@ test(1466.2, as.data.table(as.data.frame(x)), as.data.table(x)) # posix type
68906891# fix for #1001, #1002 and #759
68916892# When adding a column, even if i results in no rows, the RHS needs to evaluate so we can know the
68926893# column type to create. Always create the column for consistency that does not depend on the data in i
6893- for (bool in c(FALSE,TRUE)) {
6894+ for (bool in c(FALSE, TRUE)) {
68946895 options(datatable.auto.index=bool)
68956896 DT = data.table(a=1:2)
6896- test(1467.01 + bool*0.03, copy(DT)[a==3, b:=notExist+1], error="notExist")
6897- test(1467.02 + bool*0.03, copy(DT)[a==3, b:=a+5L], data.table(a=1:2, b=NA_integer_))
6898- test(1467.03 + bool*0.03, copy(DT)[a==3, b:=a+5], data.table(a=1:2, b=NA_real_))
6897+ test(1467.01 + bool*0.03, copy(DT)[a==3, b:=notExist+1], error="notExist", context=sprintf("bool=%s [I]", bool) )
6898+ test(1467.02 + bool*0.03, copy(DT)[a==3, b:=a+5L], data.table(a=1:2, b=NA_integer_), context=sprintf("bool=%s [II]", bool) )
6899+ test(1467.03 + bool*0.03, copy(DT)[a==3, b:=a+5], data.table(a=1:2, b=NA_real_), context=sprintf("bool=%s [III]", bool) )
68996900}
69006901test(1467.07, getOption("datatable.auto.index")) # ensure to leave TRUE
69016902
@@ -11365,9 +11366,12 @@ test(1750.07, # 0 length `by`, must also use `sets=list()`, so 0L rows result
1136511366# for any single value from dataset there should be always be the same aggregate result on any level of grouping
1136611367# changed from all(sapply()) to for() to save ram, #5517
1136711368for (i in seq_len(nrow(dt))) {
11368- test(1750.08+i/10000, uniqueN(
11369- groupingsets(dt[i], j = lapply(.SD, sum), by = c("color","year","status"), sets=list(c("color","year","status"), c("year"), c("status"), character())),
11370- by=c("amount","value")) == 1L)
11369+ test(1750.08 + i/10000,
11370+ uniqueN(
11371+ groupingsets(dt[i], j = lapply(.SD, sum), by = c("color", "year", "status"), sets=list(c("color", "year", "status"), "year", "status", character())),
11372+ by=c("amount", "value")),
11373+ 1L,
11374+ context = sprintf("dt[%d]", i))
1137111375}
1137211376# all grouping id matches in all totals
1137311377r = 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)
0 commit comments