Hi,

Here is a solution which is restricted to lists with identically shaped "branches" (like your example). The idea is to transform the list to an array and make use of the fact that unlist(x, use.names=FALSE) is much much faster for large lists than unlist(x).

# function which transforms a list whose skeleton is appropriate, i.e.
# at all levels of the list, the elements have the same skeleton
# NOTE that no check is implemented for this (should be added)
# NOTE that it also works if the final node is not a scalar but a
# matrix or array
list2array <- function(x) {
    recfn <- function(xx, dims, nms) {
        if (is.recursive(xx)) {
            dims <- c(dims, length(xx))
            nms <- c(nms, list(names(xx)))
            recfn(xx[[1]], dims, nms)
        } else {
            dims <- c(dim(xx), rev(dims))
            nms <- c(dimnames(xx), rev(nms))
            return(list(dims, nms))
        }
    }
    temp <- recfn(x, integer(), list())
    # return
    array(unlist(x, use.names=FALSE),
          temp[[1]],
          temp[[2]])
}

# create a list which is a collection of
# moderately large matrices
dimdat <- c(1e3, 5e2)
datgen <- function() array(rnorm(prod(dimdat)),
                           dimdat,
                           lapply(dimdat, function(i) letters[1:i]))
exlist <- list(
    f1=list(x1=list(A=datgen(), B=datgen()),
            x2=list(A=datgen(), B=datgen())),
    f2=list(x1=list(A=datgen(), B=datgen()),
            x2=list(A=datgen(), B=datgen()))
    )

# tranform the list to an array
system.time(exarray <- list2array(exlist))

# check if an arbitrary subview is identical
# to the original list element
identical(exarray[,,"B", "x2", "f1"], exlist$f1$x2$B)

# compare the time for unlist(x)
system.time(unlist(exlist))


HTH,
  Denes




Hi

Consider the following variable:

--8<---------------cut here---------------start------------->8---
x1 <- list(
     A = 11,
     B = 21,
     C = 31
)

x2 <- list(
     A = 12,
     B = 22,
     C = 32
)

x3 <- list(
     A = 13,
     B = 23,
     C = 33
)

x4 <- list(
     A = 14,
     B = 24,
     C = 34
)

y1 <- list(
     x1 = x1,
     x2 = x2
)

y2 <- list(
     x3 = x3,
     x4 = x4
)

x <- list(
     f1 = y1,
     f2 = y2
)
--8<---------------cut here---------------end--------------->8---


To extract all fields named "A" from y1, I can do

,----
| > sapply(y1, "[[", "A")
| x1 x2
| 11 12
`----

But how can I do the same for x?

I could put an sapply into an sapply, but this would be less then
elegant.

Is there an easier way of doing this?

Thanks,

Rainer




______________________________________________
R-help@r-project.org mailing list -- To UNSUBSCRIBE and more, see
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
and provide commented, minimal, self-contained, reproducible code.


______________________________________________
R-help@r-project.org mailing list -- To UNSUBSCRIBE and more, see
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
and provide commented, minimal, self-contained, reproducible code.

Reply via email to