Skip to content

Commit

Permalink
Merge pull request #1684 from MichaelChirico/GForce_I
Browse files Browse the repository at this point in the history
Closes #1683, .I[1L] is optimised for GForce.
  • Loading branch information
arunsrinivasan committed May 3, 2016
2 parents 30ad684 + 27bc48a commit d356700
Show file tree
Hide file tree
Showing 3 changed files with 28 additions and 2 deletions.
2 changes: 2 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -198,6 +198,8 @@
56. as.data.table's `data.table` method returns a copy as it should, [#1681](https://github.com/Rdatatable/data.table/issues/1681).

57. Grouped update operations, e.g., `DT[, y := val, by=x]` where `val` is an unsupported type errors *without adding an unnamed column*, [#1676](https://github.com/Rdatatable/data.table/issues/1676). Thanks @wligtenberg.

58. Handled use of `.I` in some `GForce` operations, [#1683](https://github.com/Rdatatable/data.table/issues/1683). Thanks gibbz00 from SO and @franknarf1 for reporting and @MichaelChirico for the PR.

#### NOTES

Expand Down
7 changes: 5 additions & 2 deletions R/data.table.R
Original file line number Diff line number Diff line change
Expand Up @@ -1000,6 +1000,7 @@ chmatch2 <- function(x, table, nomatch=NA_integer_) {
} # else empty list is needed for test 468: adding an empty list column
} # else maybe a call to transform or something which returns a list.
av = all.vars(jsub,TRUE) # TRUE fixes bug #1294 which didn't see b in j=fns[[b]](c)
use.I = ".I" %chin% av
# browser()
if (any(c(".SD","eval","get","mget") %chin% av)) {
if (missing(.SDcols)) {
Expand Down Expand Up @@ -1309,7 +1310,7 @@ chmatch2 <- function(x, table, nomatch=NA_integer_) {
# Binary search can return all 0 irows when none of the input matches. Instead of doing all(irows==0L) (previous method), which has to allocate a logical vector the size of irows, we can make use of 'max'. If max is 0, we return 0. The condition where only some irows > 0 won't occur.
}
# Temp fix for #921. Allocate `.I` only if j-expression uses it.
SDenv$.I = if (!missing(j) && ".I" %chin% av) seq_len(SDenv$.N) else 0L
SDenv$.I = if (!missing(j) && use.I) seq_len(SDenv$.N) else 0L
SDenv$.GRP = 1L
setattr(SDenv$.SD,".data.table.locked",TRUE) # used to stop := modifying .SD via j=f(.SD), bug#1727. The more common case of j=.SD[,subcol:=1] was already caught when jsub is inspected for :=.
setattr(SDenv$.SDall,".data.table.locked",TRUE)
Expand Down Expand Up @@ -1633,7 +1634,7 @@ chmatch2 <- function(x, table, nomatch=NA_integer_) {
# FR #971, GForce kicks in on all subsets, no joins yet. Although joins could work with
# nomatch=0L even now.. but not switching it on yet, will deal it separately.
if (getOption("datatable.optimize")>=2 && !is.data.table(i) && !byjoin && length(f__) && !length(lhs)) {
if (!length(ansvars)) {
if (!length(ansvars) && !use.I) {
GForce = FALSE
if ( (is.name(jsub) && jsub == ".N") || (is.call(jsub) && length(jsub)==2L && jsub[[1L]] == "list" && jsub[[2L]] == ".N") ) {
GForce = TRUE
Expand Down Expand Up @@ -1739,6 +1740,8 @@ chmatch2 <- function(x, table, nomatch=NA_integer_) {
thisEnv = new.env() # not parent=parent.frame() so that gsum is found
for (ii in ansvars) assign(ii, x[[ii]], thisEnv)
assign(".N", len__, thisEnv) # For #5760
#fix for #1683
if (use.I) assign(".I", seq_len(nrow(x)), thisEnv)
gstart(o__, f__, len__, irows) # irows needed for #971.
ans = eval(jsub, thisEnv)
if (is.atomic(ans)) ans=list(ans) # won't copy named argument in new version of R, good
Expand Down
21 changes: 21 additions & 0 deletions inst/tests/tests.Rraw
Original file line number Diff line number Diff line change
Expand Up @@ -8839,6 +8839,27 @@ test(1670.2, class(as.data.table(x)), class(x)[2:3])
dt = data.table(x=1, y=2)
test(1671, dt[, z := sd, by=x], error="invalid type/length (closure/1)")

# 1683
DT <- data.table(V1 = rep(1:2, 3), V2 = 1:6)
test(1672.1, capture.output(DT[ , .(.I[1L], V2[1L]), by = V1]),
c(" V1 V1 V2", "1: 1 1 1", "2: 2 2 2"))
#make sure GForce operating
test(1672.2, DT[ , .(.I[1L], V2[1L]), by = V1, verbose = TRUE],
output = "GForce optimized j")
#make sure works on .I by itself
test(1672.3, capture.output(DT[ , .I[1L], by = V1]),
c(" V1 V1", "1: 1 1", "2: 2 2"))
#make sure GForce here as well
test(1672.4, DT[ , .I[1L], by = V1, verbose = TRUE],
output = "GForce optimized j")
#make sure works with order
test(1672.5, capture.output(DT[order(V1), .I[1L], by = V1]),
c(" V1 V1", "1: 1 1", "2: 2 2"))
# should also work with subsetting
test(1672.6, capture.output(DT[1:5, .(.I[1L], V2[1L]), by = V1]),
c(" V1 V1 V2", "1: 1 1 1", "2: 2 2 2"))


##########################

# TODO: Tests involving GForce functions needs to be run with optimisation level 1 and 2, so that both functions are tested all the time.
Expand Down

0 comments on commit d356700

Please sign in to comment.