Skip to content

Commit

Permalink
BUG FIX: S4 methods defined locally, that is, not in a package, faile…
Browse files Browse the repository at this point in the history
…d to be found in sequential and multicore futures since future 1.22.0 [#615]
  • Loading branch information
HenrikBengtsson committed May 8, 2022
1 parent 9ae6841 commit a7b9835
Show file tree
Hide file tree
Showing 5 changed files with 8 additions and 15 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Package: future
Version: 1.25.0-9015
Version: 1.25.0-9016
Title: Unified Parallel and Distributed Processing in R for Everyone
Imports:
digest,
Expand Down
5 changes: 4 additions & 1 deletion NEWS
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
Package: future
===============

Version: 1.25.0-9015 [2022-05-07]
Version: 1.25.0-9016 [2022-05-08]

SIGNIFICANT CHANGES:

Expand Down Expand Up @@ -45,6 +45,9 @@ BUG FIXES:
setalloccol(ans) : verbose must be TRUE or FALSE". See above
'SIGNIFICANT CHANGES' for how this was fixed.

* S4 methods defined locally, that is, not in a package, failed to be
found in sequential and multicore futures since future 1.22.0.

* The deprecation warning for using local = FALSE was silenced for
sequential futures since future 1.25.0.

Expand Down
2 changes: 1 addition & 1 deletion R/globals.R
Original file line number Diff line number Diff line change
Expand Up @@ -387,7 +387,7 @@ getGlobalsAndPackages <- function(expr, envir = parent.frame(), tweak = tweakExp
pkgs <- pkgs[isAttached]
}

keepWhere <- getOption("future.globals.keepWhere", FALSE)
keepWhere <- getOption("future.globals.keepWhere", TRUE)
if (!keepWhere) {
where <- attr(globals, "where")
for (kk in seq_along(where)) where[[kk]] <- emptyenv()
Expand Down
3 changes: 0 additions & 3 deletions tests/globals,S4methods.R
Original file line number Diff line number Diff line change
@@ -1,9 +1,6 @@
source("incl/start.R")
library(methods)

## Required for S4 methods to work
options(future.globals.keepWhere = TRUE)

message("*** Globals - S4 methods ...")

setGeneric("my_fcn", function(x) standardGeneric("my_fcn"))
Expand Down
11 changes: 2 additions & 9 deletions tests/globals,locals.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,6 @@ oopts <- c(oopts, options(
future.globals.onMissing = "error"
))

okeep <- list()

message("*** Globals inside local() environments ...")

for (strategy in supportedStrategies()) {
Expand Down Expand Up @@ -68,7 +66,7 @@ for (strategy in supportedStrategies()) {
truth <- g() + h()
print(truth)

## Fixed in future (>= 1.25.0-9013) with globals (>= 0.14.0.9004):
## Fixed in future (>= 1.25.0-9016) with globals (>= 0.14.0.9004):
##
## f <- future(g() + h())
##
Expand All @@ -79,13 +77,10 @@ for (strategy in supportedStrategies()) {
##
## 'a' of h() would overwride 'a' of g() so that g() == 1
## https://github.com/HenrikBengtsson/future/issues/608
if (is.null(getOption("future.globals.keepWhere")) && packageVersion("globals") >= "0.14.0.9004") {
okeep <- options(future.globals.keepWhere = TRUE)
}
f <- future(g() + h())
v <- tryCatch(value(f), error = identity)
print(v)
if (isTRUE(getOption("future.globals.keepWhere")) || ! strategy %in% c("sequential", "multicore")) {
if (isTRUE(getOption("future.globals.keepWhere", TRUE)) || ! strategy %in% c("sequential", "multicore")) {
stopifnot(identical(v, truth))
} else {
if (packageVersion("globals") >= "0.14.0.9004") {
Expand All @@ -94,8 +89,6 @@ for (strategy in supportedStrategies()) {
stopifnot(identical(v, 4))
}
}

options(okeep)
} ## for (strategy ...)

message("*** Globals inside local() environments ... DONE")
Expand Down

0 comments on commit a7b9835

Please sign in to comment.