[R] problem using evaluating a formula

Gavin Simpson gavin.simpson at ucl.ac.uk
Tue Aug 2 19:27:33 CEST 2005


##data
y1 <- matrix(c(3,1,0,1,0,1,1,0,0,0,1,0,0,0,1,1,0,1,1,1),
             nrow = 5, byrow = TRUE)
y2 <- matrix(c
(3,0,10,3,3,0,0,1,1,0,0,0,0,0,1,0,1,0,0,2,1,0,1,1,0,2,1,1,4,1),
             nrow = 5, byrow = TRUE)
y1 <- as.data.frame(y1)
y2 <- as.data.frame(y2)
rownames(y1) <- rownames(y2) <- paste("site", 1:5, sep = "")
colnames(y1) <- paste("spp", 1:4, sep = "")
colnames(y2) <- paste("spp", 1:6, sep = "")

##code
coca.formula <- function(formula, data, ...)
  {
    ##cat("\nusing formula method\n")
    ##browser()
    if (missing(data)) {
        data <- parent.frame()
    }
    m <- match.call(expand.dots = FALSE)
    m$... <- NULL
    m[[1]] <- as.name("model.frame")
## the next line fails
    m <- eval(m, sys.parent())
    Terms <- attr(m, "terms")
    Response <- model.extract(m, "response")
    attr(Terms, "intercept") <- 0
    Predictor <- model.matrix(Terms, m)
    retval <- list(m = m, Terms = Terms, Response = Response,
                   Predictor = Predictor)
    return(retval)
  }

coca(y1 ~ y2, method = "symmetric", symmetric= TRUE)

gives:

Error in model.frame(formula, rownames, variables, varnames, extras,
extranames,  : 
	invalid variable type

when executing the indicated line

now both y1 and y2 are data.frames - this is the natural way of
specifying the model I have in mind - and I think this is the problem as
it seems to be the rhs of the formula that is causing the error.

Is there an alternative way of handling and evaling formulae if the rhs
is a data.frame (if my assumption is correct of course)? I would like,
eventually, to have the option of specifying the predictors as either a
data.frame or via named variables found in the variable passed to data.

A simple alternative would be to do the following:

predictor <- get(as.character(formula[[3]]))
response <- get(as.character(formula[[2]]))

Would I be missing something vital that I'm not appreciating if I used
this simple method?

Any other suggestions gratefully received.

Many thanks in advance,

Gav
-- 
%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%~%
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-help mailing list