[Rd] deparse(substitute(x)) and S3 methods

Gavin Simpson gavin.simpson at ucl.ac.uk
Wed Aug 3 17:28:17 CEST 2005


Dear List,

I have the following function:

coca <- function(x, ...)
  {
    if(is.null(class(x))) class(x) <- data.class(x)
    UseMethod("coca", x)
  }

and a default method

coca.default <- function(x, y, method = c("predictive", "symmetric"),
                         reg.method = c("simpls", "eigen"), weights =
NULL,
                         n.axes = NULL, symmetric = FALSE, ...)
  {
    ##some checking code here removed###
    nam.dat <- list(namY = deparse(substitute(y)),
                    namX = deparse(substitute(x)))
    method <- match.arg(method)
    if(method == "predictive")
      {
        reg.method <- match.arg(reg.method)
        retval <- switch(reg.method,
                         simpls = predcoca.simpls(y, x, R0 = weights,
                           n.axes = n.axes, nam.dat),
                         eigen = predcoca.eigen(y, x, R0 = weights,
                           n.axes = n.axes, nam.dat))
      } else {
        retval <- symcoca(y, x, n.axes = n.axes, R0 = weights,
                          symmetric = symmetric, nam.dat)
      }
    return(retval)
  }

My problem is with :
    nam.dat <- list(namY = deparse(substitute(y)),
                    namX = deparse(substitute(x)))

deparse(subsitute(x)) and deparse(subsitute(y)) return a textual
representation of x and y.

x and y are both data.frames. I assume this is because they are being
evaluated in coca() and passed on as something different to
coca.default.

I also have coca.formula() so I want to do method dispatch on whether x
is a formula or not, but I want to retain the ability to grab the names
of x and y as specified in the original call.

Can anyone suggest a way round this problem?

Thanks in advance,

Gavin
-- 
%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%
Gavin Simpson                     [T] +44 (0)20 7679 5522
ENSIS Research Fellow             [F] +44 (0)20 7679 7565
ENSIS Ltd. & ECRC                 [E] gavin.simpsonATNOSPAMucl.ac.uk
UCL Department of Geography       [W] http://www.ucl.ac.uk/~ucfagls/cv/
26 Bedford Way                    [W] http://www.ucl.ac.uk/~ucfagls/
London.  WC1H 0AP.
%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%



More information about the R-devel mailing list