invoking parLapply without a cluster fails to find a previously
registered cluster
> library(parallel)
> setDefaultCluster(makePSOCKcluster(2))
> parLapply(X=1:2, fun=function(...) {})
Error in cut.default(i, breaks) : invalid number of intervals
This is because in parLapply length(cl) is determined before
defaultCluster(cl) is called. By inspection, this appears to be true of
other high-level functions, but ironically not of parApply.
In defaultCluster, t would also be helpful to check that the detected
cluster, user-supplied or other, is a valid cluster.
diff attached.
Martin
--
Computational Biology / Fred Hutchinson Cancer Research Center
1100 Fairview Ave. N.
PO Box 19024 Seattle, WA 98109
Location: Arnold Building M1 B861
Phone: (206) 667-2793
Index: src/library/parallel/R/clusterApply.R
===================================================================
--- src/library/parallel/R/clusterApply.R (revision 60336)
+++ src/library/parallel/R/clusterApply.R (working copy)
@@ -164,29 +164,37 @@
splitCols <- function(x, ncl)
lapply(splitIndices(ncol(x), ncl), function(i) x[, i, drop=FALSE])
-parLapply <- function(cl = NULL, X, fun, ...)
+parLapply <- function(cl = NULL, X, fun, ...) {
+ cl <- defaultCluster(cl)
do.call(c,
clusterApply(cl, x = splitList(X, length(cl)),
fun = lapply, fun, ...),
quote = TRUE)
+}
-parLapplyLB <- function(cl = NULL, X, fun, ...)
+parLapplyLB <- function(cl = NULL, X, fun, ...) {
+ cl <- defaultCluster(cl)
do.call(c,
clusterApplyLB(cl, x = splitList(X, length(cl)),
fun = lapply, fun, ...),
quote = TRUE)
+}
-parRapply <- function(cl = NULL, x, FUN, ...)
+parRapply <- function(cl = NULL, x, FUN, ...) {
+ cl <- defaultCluster(cl)
do.call(c,
clusterApply(cl = cl, x = splitRows(x, length(cl)),
fun = apply, MARGIN = 1L, FUN = FUN, ...),
quote = TRUE)
+}
-parCapply <- function(cl = NULL, x, FUN, ...)
+parCapply <- function(cl = NULL, x, FUN, ...) {
+ cl <- defaultCluster(cl)
do.call(c,
clusterApply(cl = cl, x = splitCols(x, length(cl)),
fun = apply, MARGIN = 2L, FUN = FUN, ...),
quote = TRUE)
+}
parSapply <-
@@ -216,7 +224,6 @@
parApply <- function(cl = NULL, X, MARGIN, FUN, ...)
{
- cl <- defaultCluster(cl) # initial sanity check
FUN <- match.fun(FUN) # should this be done on worker?
## Ensure that X is an array object
Index: src/library/parallel/R/snow.R
===================================================================
--- src/library/parallel/R/snow.R (revision 60336)
+++ src/library/parallel/R/snow.R (working copy)
@@ -25,6 +25,7 @@
{
if(is.null(cl)) cl <- get("default", envir = .reg)
if(is.null(cl)) stop("no cluster supplied and none is registered")
+ checkCluster(cl)
cl
}
______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel