[Rd] Using substitute from inside an S4 method
Gabor Grothendieck
ggrothendieck at gmail.com
Wed Jan 25 21:11:00 CET 2006
Try defining your method like this. I don't know how generally this
works but it seems to work here.
setMethod("A", signature(x="numeric"),
function(x, y) as.character(substitute(x, sys.frame(-1))))
On 1/25/06, Seth Falcon <sfalcon at fhcrc.org> wrote:
> Hi all,
>
> I would like to access the name of a variable passed to an S4 method.
> For a function, I would do this:
>
> f <- function(x) as.character(substitute(x))
>
> This also works for a the examples I have tried for methods that do
> not have extra, non-dispatch args:
>
> setGeneric("A", function(x, ...) standardGeneric("A"))
>
> setMethod("A", signature(x="character"),
> function(x) as.character(substitute(x)))
>
> However, I'm seeing strange behavior if the method uses an extra
> argument:
>
> setMethod("A", signature(x="numeric"),
> function(x, y) as.character(substitute(x)))
>
> num <- 1
>
> A(num)
> [1] "x"
>
> A(num, 2)
> [1] "x"
>
> Is there a way to make this work? I came up with one workaround that
> uses a non-standard generic (see below).
>
> It seems that when a method uses extra args matching '...' in the
> generic, an extra frame is used in the evaluation and so substitute()
> isn't reaching the same place as without extra args.
>
> Thanks in advance for pointers to doc or suggestions.
>
>
> + seth
>
> ## here is a non-standard generic that gives me the behavior I want
>
> setGeneric("B", function(x, ...) {
> x.name <- as.character(substitute(x))
> standardGeneric("B")
> })
>
> setMethod("B", signature(x="character"),
> function(x, y) {
> penv <- sys.frames()
> penv <- penv[[length(penv)-2]]
> get("x.name", envir=penv)
> })
>
> Observation: Without an extra arg in the method, the appropriate
> environment would be penv[[length(penv) - 1]], but the presence of the
> extra arg results in an extra environment in the evaluation, hence we
> need -2.
>
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>
More information about the R-devel
mailing list