[R-sig-hpc] .combine in nested foreach loops !

Stephen Weston stephen.b.weston at gmail.com
Sun Apr 3 02:14:05 CEST 2011


I'm not sure exactly what you're trying to do, but I'm guessing that each
of the 3 lists that you speak of is supposed to contain two 3x3xn arrays,
where "two" is the number of lists of matrices that you're processing
("a" and "b"), and "n" is the length of "a" and "b".

If that's the case, then you can fix your code with a little bit of
post-processing to the results of the inner-foreach loop.  The inner-
foreach loop is returning a list containing two lists of n matrices.
You need to convert that into a list containing two 3x3xn arrays.
A simple way to do that is with a ".final" function.  The input to
the .final function is the final result from the .combine function.
The output from the .final function is returned by foreach.  That is
particularly useful with nested foreach loops.

So here's what I came up with, using the abind function from
the abind package to create the 3x3xn arrays:

library(abind)
library(foreach)
library(doMC)
registerDoMC()

cvec <- c(1, 2, 3)

n <- 2
s <- seq(length=n)
a <- lapply(s, function(i) matrix(rnorm(9), 3))
b <- lapply(s, function(i) matrix(rnorm(9), 3))

init <- list(a=list(), b=list())

comb <- function(accum, ...) {
  s <- seq(along=accum)
  names(s) <- names(accum)
  lapply(s, function(i) c(accum[[i]], lapply(list(...), function(a) a[[i]])))
}

# Convert a list of lists of matrices into a list of arrays
final <- function(r) {
  lapply(r, function(s) abind(s, along=3))
}

results <- foreach(c=cvec) %:%
  foreach(i=icount(length(a)), .combine=comb, .init=init,
            .final=final, .multicombine=TRUE) %dopar% {
    list(a=a[[i]]*c, b=b[[i]]*c)
  }

print(results)
str(results)


Note that this uses the default combine for the outer-foreach loop,
which returns the inner-foreach values in a list, which seems to be
what you want.

- Steve



On Thu, Mar 31, 2011 at 9:34 AM, Maas James Dr (MED) <J.Maas at uea.ac.uk> wrote:
> I'm attempting to use nested foreach loops.  My problem is trying to combine the results correctly from the outer foreach loop.  Stephen Weston very graciously worked up an example for me of how to get outputs, in the form of matrices, back from a single foreach loop.  I've changed the example to try to get it to work correctly for nested foreach loops.  In this example the "results" object contains 6 lists however what I would like to get is a result containing only 3 lists, corresponding to the length of cvec, each list would be a 3x3x2 array.  I've tried several things to combine the results in the outer loop, including functions using "abind",  and not got it to work out, perhaps it is not possible directly from nested foreach loops?
>
> BTW, is there a location/way to search the R-sig-hpc listserv?
>
> Thanks a bunch,
>
> Jim
>
> library(doMPI)
> cl <- startMPIcluster()
> registerDoMPI(cl)
> library(foreach)
>
> cvec <- c(1,2,3)
>
> n <- 2
> s <- seq(length=n)
> a <- lapply(s, function(i) matrix(rnorm(9), 3))
> b <- lapply(s, function(i) matrix(rnorm(9), 3))
>
> init <- list(a=list(), b=list())
>
> comb <- function(accum, ...) {
>  s <- seq(along=accum)
>  names(s) <- names(accum)
>  lapply(s, function(i) c(accum[[i]], lapply(list(...), function(a) a[[i]])))
> }
>
> results <- foreach (c=cvec, .combine="c") %:%
>    foreach(i=icount(length(a)), .combine=comb, .init=init,
>                  .multicombine=TRUE) %dopar% {
>  list(a=a[[i]]*c, b=b[[i]]*c)
> }
>
> results
> names(results)
>
> closeCluster(cl)
> mpi.quit()
>
> ===============================
> Dr. Jim Maas
> University of East Anglia
> _______________________________________________
> R-sig-hpc mailing list
> R-sig-hpc at r-project.org
> https://stat.ethz.ch/mailman/listinfo/r-sig-hpc
>



More information about the R-sig-hpc mailing list