[R] assigning from multiple return values

Gabor Grothendieck ggrothendieck at myway.com
Thu Jun 24 15:44:43 CEST 2004


Here is a minor update with support for empty arguments.  They
are just thrown away eliminating the need to use a dummy name
for them.

list <- structure(NA,class="result")
"[<-.result" <- function(x,...,value) {
   args <- as.list(match.call())
   args <- args[-c(1:2,length(args))]
   length(value) <- length(args)
   for(i in seq(along=args)) {
     a <- args[[i]]
     if(!missing(a)) eval.parent(substitute(a <- v,list(a=a,v=value[[i]])))
   }
   x
}

# it is used like this:

list[QR,,QRaux]  <- qr(c(1,1:3,3:1))
list[,Green,Blue]  <- col2rgb("aquamarine")


Gabor Grothendieck <ggrothendieck <at> myway.com> writes:

: 
: Just a few more examples:
: 
: # swap a and b without explicitly creating a temporary
: a <- 1; b <- 2
: list[a,b] <- list(b,a)
: 
: # get eigenvectors and eigenvalues
: list[eval, evec] <- eigen(cbind(1,1:3,3:1))
: 
: # get today's month, day, year
: require(chron)
: list[Month, Day, Year] <- month.day.year(unclass(Sys.Date()))
: 
: # get first two components of linear model ignoring rest
: list[Coef, Resid] <- lm(rnorm(10) ~ seq(10))
: 
: Gabor Grothendieck <ggrothendieck <at> myway.com> writes:
: 
: : 
: : I think I've found a workaround that avoids the two problems in the
: : replacement function approach.    With the definitions of list
: : and [<-.result shown, one can write list[a,b] on the
: : left side of an assignment where the right side of the assignment
: : evaluates to a list of the same length (or if the list on the right
: : side is shorter then the otherwise unfilled variables are set to NA and
: : if the list on the right side is longer the excess entries are ignored).   
: : Unlike the previous workaround using a replacement function, one
: : can have a variable number of arguments to list[] and the first 
: : argument to list[] no longer has to be predefined.
: : 
: : list <- structure(NA,class="result")
: : "[<-.result" <- function(x,...,value) {
: :    args <- as.list(match.call())
: :    args <- args[-c(1:2,length(args))]
: :    length(value) <- length(args)
: :    for(i in seq(along=args))
: :       eval(substitute(x <- v,list(x=args[[i]],v=value[[i]])),env=sys.frame
(-
: 1))
: :    x
: : }
: : 
: : # it is used like this:
: : 
: : x <- 1:4
: : fn <- function() list("zz",99)
: : list[a,x[2]] <- fn()
: : 
: : Gabor Grothendieck <ggrothendieck <at> myway.com> writes:
: : 
: : : 
: : : Here are two approaches assuming foo is "zz" and bar is 3.
: : : 
: : : FIRST
: : : 
: : : You could pass the return variables in the argument list and then
: : : assign them in the caller's frame like this:
: : : 
: : : fn <- function(x,y) {
: : : 	assign(as.character(substitute(x)), "zz", sys.frame(-1))
: : : 	assign(as.character(substitute(y)), 3, sys.frame(-1))
: : : }
: : : fn(a,b)  # sets a to "zz" and b to 3
: : : 
: : : SECOND
: : : 
: : : You can make this a bit prettier, though not perfect, like this:
: : : 
: : : "list2<-" <- function(x,y,value) {
: : : 	assign(as.character(substitute(y)), value[[2]], sys.frame(-1))
: : : 	value[[1]]
: : : }
: : : fn <- function()list("zz",3)
: : : a <- 1 # first arg must exist prior to invoking list2. Its value not 
: : important.
: : : list2(a,b) <- fn()
: : : 
: : : The two problems with list2 are:
: : : 
: : : 1. the first argument must exist prior to invoking list2 although its
: : : actual value is immaterial since it just gets overwritten anyways.
: : : 
: : : 2. It only works for 2 args although you could write a list3, list4, etc.
: : : 
: : : Maybe someone could comment on these deficiencies.
: : : 
: : : Jack Tanner <ihok <at> hotmail.com> writes:
: : : 
: : : : 
: : : : I know that if I have a function that returns multiple values, I should
: : : : do return(list(foo, bar)). But what do I do on the recieving end?
: : : : 
: : : : fn <- function(x) {
: : : :    return(list(foo, bar))
: : : : }
: : : : 
: : : : I know that at this point I could say
: : : : 
: : : : values.list <- fn(x)
: : : : 
: : : : and then access
: : : : 
: : : : values.list[1]
: : : : values.list[2]
: : : : 
: : : : But that's hideous. I'd rather be able to say something like
: : : : 
: : : : list(local_foo, local_bar) <- fn(x)
: : : : 
: : : : and have the right thing happen. I realize that it's my responsibility
: : : : to not screw up and say instead
: : : : 
: : : : list(local_bar, local_foo)
: : : : 
: : : : Any suggestions?
: : : : 
: : : : -JT
: : : :
: : : 
: : : ______________________________________________
: : : R-help <at> stat.math.ethz.ch mailing list
: : : https://www.stat.math.ethz.ch/mailman/listinfo/r-help
: : : PLEASE do read the posting guide! http://www.R-project.org/posting-
: guide.html
: : : 
: : :
: : 
: : ______________________________________________
: : R-help <at> stat.math.ethz.ch mailing list
: : https://www.stat.math.ethz.ch/mailman/listinfo/r-help
: : PLEASE do read the posting guide! http://www.R-project.org/posting-
guide.html
: : 
: :
: 
: ______________________________________________
: R-help <at> stat.math.ethz.ch mailing list
: https://www.stat.math.ethz.ch/mailman/listinfo/r-help
: PLEASE do read the posting guide! http://www.R-project.org/posting-guide.html
: 
:




More information about the R-help mailing list