In looking at this once more I realize that I did not really answer
the question which was how to get the getFunNames function that
you defined to run in another funciton.  Use do.call with match.call
to replicate the calling sequence:

myfun <- function(x) {
        do.call(getFunNames, list(match.call()[-1][[1]]))
}
myfun(mean)
myfun(list(mean, sd))


On 10/5/06, Gabor Grothendieck <[EMAIL PROTECTED]> wrote:
> I should have mentioned is that the way it works is that
> it uses the name of the list component, if any, otherwise
> it uses the name of the function if its given as a name
> and otherwise it uses the function itself or possibly the
> name of the list.
>
> >
> > On 10/5/06, Gabor Grothendieck <[EMAIL PROTECTED]> wrote:
> > > Probably the best you can hope for is to cover
> > > most cases.  This one uses match.call and handles
> > > a number of cases and perhaps if you spend more time
> > > on it might be able to add some cases where it fails
> > > such as the second L below:
> > >
> > > f <- function(x) {
> > >        if (!is.list(x)) x <- list(x)
> > >        if (is.null(names(x))) names(x) <- ""
> > >        names(x)[names(x) == ""] <- NA
> > >        mc <- match.call()[-1][[1]]
> > >        if (length(mc) > 1) mc <- mc[-1]
> > >        ifelse(is.na(names(x)), as.character(mc), names(x))
> > > }
> > >
> > > f(c(a = mean))
> > > f(list(a = mean, b = sd))
> > > f(c(f = function(x)x*x))
> > > f(list(f = function(x)x*x, function(x)1-x))
> > > L <- list(a = mean, b = sd)
> > > f(L)
> > > L <- list(a = mean, function(x)x)
> > > f(L)
> > >
> > > f(mean)
> > > f(list(a = mean, sd))
> > > f(list(mean, sd))
> > > f(function(x)x*x)
> > > f(list(function(x)x*x, function(y)y-1))
> > >
> > >
> > > On 10/5/06, Søren Højsgaard <[EMAIL PROTECTED]> wrote:
> > > > I've defined the function
> > > >
> > > > getFunNames <- function(FUN){
> > > >  if (!is.list(FUN))
> > > >    fun.names <- paste(deparse(substitute(FUN)), collapse = " ")
> > > >  else
> > > >    fun.names <- unlist(lapply(substitute(FUN)[-1], function(a) 
> > > > paste(a)))
> > > >  fun.names
> > > > }
> > > >
> > > > which gives what I want :
> > > > > getFunNames(mean)
> > > > [1] "mean"
> > > > > getFunNames(ff)
> > > > [1] "ff"
> > > > > getFunNames(c(mean,ff))
> > > > [1] "mean" "ff"
> > > >
> > > > If I call this within a function, things go wrong:
> > > > 1] "FUN"
> > > > > foo(ff)
> > > > [1] "FUN"
> > > > > foo(c(mean,ff))
> > > > Error in substitute(FUN)[-1] : object is not subsettable
> > > >
> > > > Obviously there are some things (quite a few things) which I have not 
> > > > understood. Can anyone help?
> > > > Thanks
> > > > Søren
> > > >
> > > > ______________________________________________
> > > > R-help@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
> > > > and provide commented, minimal, self-contained, reproducible code.
> > > >
> > >
> >
>

______________________________________________
R-help@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
and provide commented, minimal, self-contained, reproducible code.

Reply via email to