I think you have missed the use of ..1 etc: see e.g. cBind() in package Matrix.

So x <- attr(list(...)[[1L]], "foo") can be x <- attr(..1, "foo")

As for 'extra copying', it all depends on exactly what you are doing, but compare

foo1 <- function(...) length(..1)
foo2 <- function(...) length(list(...)[[1L]])
tracemem(x <- runif(1000))
[1] "<0x1b27800>"
foo1(x)
[1] 1000
tracemem(x <- runif(1000))
[1] "<0x1b29800>"
foo2(x)
tracemem[0x1b29800 -> 0x10a2200]: foo2
[1] 1000


On Sat, 3 Jul 2010, Daniel Murphy wrote:

Hi Hadley,

My actual goal is to have a cbind method in the mondate package that behaves
just like the base cbind function: class and shape of the result, names,
etc. Perhaps it's due to the fact that 'cbind' uses its own internal
dispatching, but I have not found a way to implement a "true" S3-style cbind
method. (This is probably ancient news to the development team.) An S4 cbind
method will utilize callNextMethod with just setGeneric("cbind"), which has
no 'x' in the formal arguments. With no 'x', there's no "first argument" on
which to dispatch a "mondate" method. I can make the cbind of mondates also
be a mondate with an all-encompassing setMethod("cbind","ANY", etc) method,
but that wrests dispatch control from cbind which makes no sense whatsoever.
So, to make a long story even longer, I settled for a "cbindmondate
function" that utilizes the speed of base::cbind and (with one exception)
gives me the hoped-for "base cbind behavior."

I can send examples of my trial-and-error attempts under separate email if
you're interested.

Best regards,
Dan

On Sat, Jul 3, 2010 at 9:17 AM, Hadley Wickham <had...@rice.edu> wrote:

Hi Dan,

Is there a reason you can't change the function to

f <- function(x, ...) {}

?

Hadley

On Fri, Jul 2, 2010 at 4:26 PM, Daniel Murphy <chiefmur...@gmail.com>
wrote:
R-Devel:

I am trying to get an attribute of the first argument in a call to a
function whose formal arguments consist of dots only and do something,
e.g.,
call 'cbind', based on the attribute
f<- function(...) {get first attribute; maybe or maybe not call 'cbind'}

I thought of (ignoring "deparse.level" for the moment)

f<-function(...) {x <- attr(list(...)[[1L]], "foo"); if (x=="bar")
cbind(...) else x}

but I feared my solution might do some extra copying, with a performance
penalty if the dotted objects in the actual call to "f' are very large.

I thought the following alternative might avoid a potential performance
hit
by evaluating the attribute in the parent.frame (and therefore avoid
extra
copying?):

f<-function(...)
{
  L<-match.call(expand.dots=FALSE)[[2L]]
  x <- eval(substitute(attr(x,"foo"), list(x=L[[1L]])))
  if (x=="bar") cbind(...) else x
}

system.time tests showed this second form to be only marginally faster.

Is my fear about extra copying unwarranted? If not, is there a better way
to
get the "foo" attribute of the first argument other than my two
alternatives?

Thanks,
Dan Murphy

       [[alternative HTML version deleted]]

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel




--
Assistant Professor / Dobelman Family Junior Chair
Department of Statistics / Rice University
http://had.co.nz/


        [[alternative HTML version deleted]]

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


--
Brian D. Ripley,                  rip...@stats.ox.ac.uk
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford,             Tel:  +44 1865 272861 (self)
1 South Parks Road,                     +44 1865 272866 (PA)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to