R-beta: bug report

Kung-Sik Chan kchan at stat.uiowa.edu
Mon Aug 18 04:51:20 CEST 1997


The following seems to be a bug when I tried to use the predict function.

> forbes
      boil.pt pressure log.pressure
 [1,]   194.5    20.79     303.4472
 [2,]   194.3    20.79     303.4472
 [3,]   197.9    22.40     310.9061
 [4,]   198.4    22.67     312.1042
 [5,]   199.4    23.15     314.1995
 [6,]   199.9    23.35     315.0597
 [7,]   200.9    23.89     317.3460
 [8,]   201.1    23.99     317.7637
 [9,]   201.4    24.02     317.8887
[10,]   201.3    24.01     317.8470
[11,]   203.6    25.14     322.4460
[12,]   204.6    26.57     327.9783
[13,]   209.5    28.49     334.9553
[14,]   208.6    27.76     332.3596
[15,]   210.7    29.04     336.8674
[16,]   211.9    29.88     339.7189
[17,]   212.2    30.06     340.3195
> lm3                               

Call:
lm(formula = log.pressure ~ boil.pt, subset = c(-12))

Coefficients:
(Intercept)     boil.pt
 -95.176624    2.051855  
> forbes.pred
    boil.pt
190     190
200     200  
> predict(lm3,newdata=forbes.pred)
Error in if (object$intercept) X <- cbind(rep(1, NROW(X)), X) : missing value wh
ere logical needed   


For this problem, I have fixed the predict function in src/library/base/funs as follows:
And the predict function now seems to work ok.

predict <- function(fit,...) UseMethod("predict")

predict.default <- function (object, ...) {
                 namelist <- list(...)
                 names(namelist) <- substitute(list(...))[-1]
                 m <- length(namelist)
                 X <- as.matrix(namelist[[1]])
                 if (m > 1) 
                   for (i in (2:m)) X <- cbind(X, namelist[[i]])
                 if (attr(object$terms,'intercept')) 
                   X <- cbind(rep(1, NROW(X)), X)
                 k <- NCOL(X)
                 if (length(object$coef) != k) 
                   stop("Wrong number of predictors")
                 predictor <- X %*% object$coef
                 ip <- real(NROW(X))
		 sum1_summary(object)
		 covmat_sum1$cov.unscaled*sum1$sigma^2
                 for (i in (1:NROW(X))) ip[i] <- sum(X[i, ] * 
                       (covmat %*% X[i, ]))
                 stderr1 <- sqrt(ip)
                 stderr2 <- sqrt(sum1$sigma^2 + ip)
                 tt <- qt(0.975, object$df)
                 conf.l <- predictor - tt * stderr1
                 conf.u <- predictor + tt * stderr1
                 pred.l <- predictor - tt * stderr2
                 pred.u <- predictor + tt * stderr2
                 z <- cbind(predictor, conf.l, conf.u, pred.l, pred.u)
                 rownames(z) <- paste("P", 1:NROW(X), sep = "")
                 colnames(z) <- c("Predicted", "Conf lower", "Conf upper",
                                  "Pred lower", "Pred upper")
                 z
}
******************

Another problem I have is that when I use the sink function to divert output
to an external file, I used the command options(echo=T) so that the commands
will be echoed in the external file. However, the echo command doesn't seem
to work. Any suggestions?

Thanks.

Kung-Sik

=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=
r-help 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-help-request at stat.math.ethz.ch
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=



More information about the R-help mailing list