[Rd] relist, an inverse operator to unlist
    Martin Maechler 
    maechler at stat.math.ethz.ch
       
    Mon May 14 09:53:31 CEST 2007
    
    
  
Nice ideas, Gabor and Andrew.
While I agree with Andrew that such a utility makes for nicer
and considerably better maintainable code in examples like his,
and I do like to provide "inverse operator functions" in R
whenever sensible,
OTOH, we have strived to keep R's "base" package as lean and
clean as possible, so I think this had to go to "utils".
One further small proposal: I'd use class name  "relistable"
since that's what the object of this class are
and hence as.relistable().
What do other R-develers think?
Martin
>>>>> "GaGr" == Gabor Grothendieck <ggrothendieck at gmail.com>
>>>>>     on Mon, 14 May 2007 02:54:22 -0400 writes:
    GaGr> unlist would not attach a skeleton to every vector it
    GaGr> returns, only the relist method of unlist would.
    GaGr> That way just that method needs to be added and no
    GaGr> changes to unlist itself are needed.
    GaGr> Before applying unlist to an object you would coerce
    GaGr> the object to class "relist" to force the relist
    GaGr> method of unlist to be invoked.
    GaGr> Here is an outline of the code:
    GaGr> as.relist <- function(x) {
    GaGr>  if (!inherits(x, "relist")) class(x) <- c("relist", class(x))
    GaGr>  x
    GaGr> }
    GaGr> unlist.relist <- function(x, ...) {
    GaGr>  y <- x
    GaGr>  cl <- class(y)
    GaGr>  class(y) <- cl[- grep("relist", cl)]
    GaGr>  z <- unlist(y)
    GaGr>  attr(z, "relist") <- y
    GaGr>  as.relist(z)
    GaGr> }
    GaGr> relist <- function(x, skeleton = attr(x, "relist")) {
    GaGr>  # simpler version of relist so test can be executed
    GaGr>  skeleton
    GaGr> }
    GaGr> # test
    GaGr> x <- list(a = 1:2, b = 3)
    GaGr> class(as.relist(x))
    GaGr> unlist(as.relist(x))
    GaGr> relist(unlist(as.relist(x)))
    GaGr> On 5/14/07, Andrew Clausen <clausen at econ.upenn.edu> wrote:
    >> Hi GaGr,
    >> 
    >> Thanks for the interesting suggestion.  I must confess I got lost -- is
    >> it something like this?
    >> * unlist() could attach skeleton to every vector it returns.
    >> * relist() could then use the skeleton attached to the vector to reconstruct
    >> the object.  The interface might be
    >> 
    >> relist <- function(flesh, skeleton=attributes(flesh)$skeleton)
    >> 
    >> For example:
    >> 
    >> par <- list(mean=c(0, 0), vcov(rbind(c(1, 1), c(1, 1))))
    >> vector.for.optim <- unlist(par)
    >> print(attributes(vector.optim)$skeleton)    # the skeleton is stored!
    >> converted.back.again <- relist(par)
    >> 
    >> Some concerns:
    >> * the metadata might get lost in some applications -- although it seems
    >> to work fine with optim().  But, if we provide both interfaces (where
    >> skeleton=flesh$skeleton is the default), then there should be no problem.
    >> * would there be any bad side-effects of changing the existing unlist
    >> interface?  I suppose an option like "save.skeleton" could be added to unlist.
    >> I expect there would be some objections to enabling this as default behaviour,
    >> as it would significantly increase the storage requirements of the output.
    >> 
    >> Cheers,
    >> Andrew
    >> 
    >> On Sun, May 13, 2007 at 07:02:37PM -0400, GaGr Grothendieck wrote:
    >> > I suggest you define a "relist" class and then define an unlist
    >> > method for it which stores the skeleton as an attribute.  Then
    >> > one would not have to specify skeleton in the relist command
    >> > so
    >> >
    >> > relist(unlist(relist(x))) === x
    >> >
    >> > 1. relist(x) is the same as x except it gets an additional class "relist".
    >> > 2. unlist(relist(x)) invokes the relist method of unlist on relist(x)
    >> > returning another relist object
    >> > 3. relist(unlist(relist(x))) then recreates relist(x)
    >> >
    >> >
    >> > On 5/13/07, Andrew Clausen <clausen at econ.upenn.edu> wrote:
    >> > >Hi all,
    >> > >
    >> > >I wrote a function called relist, which is an inverse to the existing
    >> > >unlist function:
    >> > >
    >> > >       http://www.econ.upenn.edu/~clausen/computing/relist.R
    >> > >
    >> > >Some functions need many parameters, which are most easily represented in
    >> > >complex structures.  Unfortunately, many mathematical functions in R,
    >> > >including optim, nlm, and grad can only operate on functions whose domain
    >> > >is
    >> > >a vector.  R has a function to convert complex objects into a vector
    >> > >representation.  This file provides an inverse operation called "unlist" to
    >> > >convert vectors back to the convenient structural representation.
    >> > >Together,
    >> > >these functions allow structured functions to have simple mathematical
    >> > >interfaces.
    >> > >
    >> > >For example, a likelihood function for a multivariate normal model needs a
    >> > >variance-covariance matrix and a mean vector.  It would be most convenient
    >> > >to
    >> > >represent it as a list containing a vector and a matrix.  A typical
    >> > >parameter
    >> > >might look like
    >> > >
    >> > >       list(mean=c(0, 1), vcov=cbind(c(1, 1), c(1, 0)))
    >> > >
    >> > >However, optim can't operate on functions that take lists as input; it
    >> > >only likes vectors.  The solution is conversion:
    >> > >
    >> > >        initial.param <- list(mean=c(0, 1), vcov=cbind(c(1, 1), c(1, 0)))
    >> > >
    >> > >        ll <- function(param.vector)
    >> > >        {
    >> > >               param <- relist(initial.param, param.vector)
    >> > >               -sum(dnorm(x, mean=param$mean, vcov=param$vcov, log=TRUE))
    >> > >               # note: dnorm doesn't do vcov... but I hope you get the
    >> > >               point
    >> > >        }
    >> > >
    >> > >        optim(unlist(initial.param), ll)
    >> > >
    >> > >"relist" takes two parameters: skeleton and flesh.  Skeleton is a sample
    >> > >object that has the right "shape" but the wrong content.  "flesh" is a
    >> > >vector
    >> > >with the right content but the wrong shape.  Invoking
    >> > >
    >> > >       relist(skeleton, flesh)
    >> > >
    >> > >will put the content of flesh on the skeleton.
    >> > >
    >> > >As long as "skeleton" has the right shape, it should be a precise inverse
    >> > >of unlist.  These equalities hold:
    >> > >
    >> > >       relist(skeleton, unlist(x)) == x
    >> > >       unlist(relist(skeleton, y)) == y
    >> > >
    >> > >Is there any easy way to do this without my new relist function?  Is there
    >> > >any
    >> > >interest in including this in R's base package?  (Or anywhere else?)  Any
    >> > >comments on the implementation?
    >> > >
    >> > >Cheers,
    >> > >Andrew
    
    
More information about the R-devel
mailing list