[R] Deparsing '...'

Gabor Grothendieck ggrothendieck at gmail.com
Thu Mar 2 19:42:55 CET 2006


Note that this still has the restriction that getdots must be used
directly in the function which is to be deparsed so one could not,
for example, put it in another utility function which deparses
the function and extracts the first component.  To do that you
need to pass the frame:

f <- function(n = sys.parent()) match.call(sys.function(n), call=sys.call(n))

# test - note that g calls first which calls f so f is not directly called by g
first <- function(n = sys.parent()) f(n)[1:2]
g <- function(x,...) first()
g(x,a,b,c)
g(x = x, a, b, c)


On 3/2/06, Matthew Dowle <mdowle at concordiafunds.com> wrote:
>
> That works well. So the final version is:
> getdots = function() as.character(match.call(sys.function(-1),
> call=sys.call(-1), expand.dots=FALSE)$...)
>
> Thank you both for your help.
>
> > -----Original Message-----
> > From: pd at pubhealth.ku.dk [mailto:pd at pubhealth.ku.dk] On
> > Behalf Of Peter Dalgaard
> > Sent: 02 March 2006 18:07
> > To: Matthew Dowle
> > Cc: 'Prof Brian Ripley'; 'r-help at stat.math.ethz.ch'
> > Subject: Re: [R] Deparsing '...'
> >
> >
> > Matthew Dowle <mdowle at concordiafunds.com> writes:
> >
> > > That's even neater.  But when its called from within
> > another function,
> > > this happens, see below.  I was planning to call f something like
> > > 'getdots' and use it in several functions that need to do this.
> > >
> > > > f <- function(...) as.character(match.call())[-1]
> > > > f(a,b,c)
> > > [1] "a" "b" "c"
> > > > g = function(x,...) f(...)
> > > > g(x,a,b,c)
> > > [1] "..1" "..2" "..3"
> >
> > Yes, that will (and must) happen. If you really want to go
> > that route, you need something in the veins of
> >
> > > f <- function() match.call(sys.function(-1), call=sys.call(-1)) g =
> > > function(x,...) f()
> > > g(x,a,b,c)
> > g(x = x, a, b, c)
> >
> > >
> > > > -----Original Message-----
> > > > From: Prof Brian Ripley [mailto:ripley at stats.ox.ac.uk]
> > > > Sent: 02 March 2006 17:18
> > > > To: Matthew Dowle
> > > > Cc: 'r-help at stat.math.ethz.ch'
> > > > Subject: Re: [R] Deparsing '...'
> > > >
> > > >
> > > > f <- function(...) as.character(match.call())[-1]
> > > > > f(x,a,b,c*d)
> > > > [1] "x"     "a"     "b"     "c * d"
> > > >
> > > > On Thu, 2 Mar 2006, Matthew Dowle wrote:
> > > >
> > > > >
> > > > > Hi,
> > > > >
> > > > > The following function works, but is there a neater way
> > to write
> > > > > it?
> > > > >
> > > > > f = function(x,...)
> > > > > {
> > > > >    # return a character vector of the arguments passed
> > in after 'x'
> > > > >    gsub("
> > > > >
> > ","",unlist(strsplit(deparse(substitute(list(...))),"[(,)]")))[-1]
> > > > > }
> > > > >
> > > > >> f(x,a,b,c*d)
> > > > > [1] "a"   "b"   "c*d"
> > > > >>
> > > > >
> > > > > Thanks.
> > > >
> > > > --
> > > > Brian D. Ripley,                  ripley at 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-help at stat.math.ethz.ch mailing list
> > > https://stat.ethz.ch/mailman/listinfo/r-help
> > > PLEASE do read the posting guide!
> > > http://www.R-project.org/posting-guide.html
> > >
> >
> > --
> >    O__  ---- Peter Dalgaard             Øster Farimagsgade 5, Entr.B
> >   c/ /'_ --- Dept. of Biostatistics     PO Box 2099, 1014 Cph. K
> >  (*) \(*) -- University of Copenhagen   Denmark          Ph:
> > (+45) 35327918
> > ~~~~~~~~~~ - (p.dalgaard at biostat.ku.dk)                  FAX:
> > (+45) 35327907
> >
> >
>
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://stat.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