anova.lm bug

Jean Meloche jean@stat.ubc.ca
Thu, 25 Mar 1999 17:12:05 -0800


anova.lm does not work on a lm fit with singularities (using singular.ok=TRUE)
because of mismatch between the anova table length and fit$terms lebgth.
The following works for me:

anova.lm <- function(object, ...)
{
    if(length(list(object, ...)) > 1)
        return(anovalist.lm(object, ...))
    w <- weights(object)
    ssr <- sum(if(is.null(w)) resid(object)^2 else w*resid(object)^2)
    p1 <- 1:object$rank
    comp <- object$effects[p1]
    tlabels <- names(object$effects[p1])                        <- get the matching labels
    asgn <- object$assign[object$qr$pivot][p1]
    dfr <- df.residual(object)
    ss <- c(as.numeric(lapply(split(comp^2,asgn),sum)),ssr)
    df <- c(as.numeric(lapply(split(asgn,  asgn),length)), dfr)
    if(attr(object$terms,"intercept")) {
        ss <- ss[-1]
        df <- df[-1]
        tlabels <- tlabels[-1]                                  <- remove intercept
    }
    ms <- ss/df
    f <- ms/(ssr/dfr)
    p <- 1 - pf(f,df,dfr)
    table <- data.frame(df,ss,ms,f,p)
    table[length(p),4:5] <- NA
    dimnames(table) <- list(c(tlabels, "Residuals"),            <- use the right labels
                            c("Df","Sum Sq", "Mean Sq", "F value", "Pr(>F)"))

    structure(table, heading = c("Analysis of Variance Table\n",
                     paste("Response:", formula(object)[[2]])),
              class= c("anova", "data.frame"))# was "tabular"
}

-- 
Jean Meloche
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-devel mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !)  To: r-devel-request@stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._