Hello, I wrote the following function to compute multiple comparisons in
a one way anova and randomized blocks anova.
aov1 <- function(y,g,s=NULL,comp="mca",meth="Sidak") {
#
  fun <- function(x)
    c(mean(x,na.rm=T),sd(x,na.rm=T),length(x[!is.na(x)]))
#
  li <- length(unique(g))
  cat("   Analysis of Variance with Multiple comparisons\n\n")
  cat(" Groups : ",li,"\n")
  t <- tapply(y,g,fun)
  a <- array(c(t,recursive=T),c(3,li))
  dimnames(a) <-
list(c("Mean","S.Dev","n"),1:li)
  df <- length(y)-li
  cat(" Means : ",a[1,],"\n")
  cat(" S.Dev : ",a[2,],"\n")
  cat("  n    : ",a[3,],"\n\n")
#
  if(is.null(s)) {
    b <- aov(y ~ as.factor(g))
    d <- summary(b)
    df <- b$df
    e <- d[[1]][3]
    sig <- e[[1]][2]
  }
  if(!is.null(s)) {
    b <- aov(y ~ as.factor(g) + Error(as.factor(s)))
    d <- summary(b)
    df <- b$Within[8]
    e <- sqrt(d[[2]][[1]][3])
    sig <- unlist(e[[1]][2])
  }
  cat("   Anova \n")
  print(d)
  cat("\n")
  b <- multicmp(a[1,],a[3,],sig,df.residual=df,method=meth)
  print(b$table)
}
If I call "aov1(x,g)" everything works as expected but with
"aov1(x,g,s=s)" or "aov1(x,g,s)" I get the error
Error in eval(expr, envir, enclos) : Object "y" not
found>
I am using R 1.3.1 on Win98. Can somebody explain why adding a parameter
makes the first parameter invisible?
Thanks
Heberto Ghezzo
Meakins-Christie Labs
McGill University
Montreal - Canada
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
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
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._
>>>>> "Heberto" == Heberto Ghezzo <heberto.ghezzo at mcgill.ca> writes:Heberto> Hello, I wrote the following function to compute Heberto> multiple comparisons in a one way anova and Heberto> randomized blocks anova. Heberto> aov1 <- Heberto> function(y,g,s=NULL,comp="mca",meth="Sidak") { # ..... Heberto> b <- multicmp(a[1,],a[3,],sig,df.residual=df,method=meth) ...... Heberto> If I call "aov1(x,g)" everything Heberto> works as expected but with "aov1(x,g,s=s)" or Heberto> "aov1(x,g,s)" I get the error Heberto> Error in eval(expr, envir, enclos) : Object "y" not Heberto> found we have no real chance of reproducing your problem. you use `data' -- your "x" and "g" and "s" that we don't have available and you use a function multicmp() which is not part of R (which might be not called before the error though). Typing traceback() after the error message would help potentially. Heberto> I am using R 1.3.1 on Win98. Can somebody explain Heberto> why adding a parameter makes the first parameter Heberto> invisible? Thanks well, it's a different model you are fitting,... maybe you could use a data frame to pass to aov(*, data = <data frame>) Heberto> Heberto Ghezzo Meakins-Christie Labs McGill Heberto> University Montreal - Canada -.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.- 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 _._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._