On Tue, Jan 07, 2003 at 02:13:05PM -0500, Johanne Duhaime wrote:
> Hello
>
> I am a new user of Bioconductor. I just installed version 1.1 on R
> version 1.6.1. This is done on widows 2000.
> I want to reproduce section 3.3 "Expression measures" of the
document
> "Textual Description of affy". But I keep having the same error
whatever
> I tried.
> Can you help me? Thank you in advance.
>
>
> > ReadAffy()
> AffyBatch object
> size of arrays=640x640 features (16003 kb)
> cdf=MG_U74A (12654 affyids)
> number of samples=5
> number of genes=12654
> annotation=mgu74a
> notes=
> > ls()
> character(0)
> > eset <-
> expresso(affybatch,normalize.method="qspline",bg.method="rma",summar
y.method="liwong")
>
> Error in expresso(affybatch, normalize.method = "qspline", bg.method
=
> "rma", :
> unused argument(s) (bg.method ...)
>
Thanks for pointing it out. This part of the doc relates to the
previous version of the package. One should read:
eset <- expresso(affybatch.example, normalize.method="loess",
bgcorrect.method="rma", pmcorrect.method="pmonly",
summary.method="liwong")
Unfortunately, it revealed an another problem (particular to few
datasets, among which 'affybatch.example'). The fix should appear by
tomorrow in th repository. You can copy paste the following in your
session in the meanwhile:
(note 'qspline' is stil not very 'bugfree'... works for some sets,
crashes on others... we are on the case...)
Hopin' it helps,
L.
# ---------------------
library(affy)
where <- as.environment("package:affy")
setMethod("computeExprSet", signature(x="AffyBatch",
pmcorrect.method="character", summary.method="character"),
function(x, pmcorrect.method, summary.method, ids=NULL,
verbose=TRUE, summary.param=list(),
pmcorrect.param=list(), warnings=TRUE)
{
pmcorrect.method<- match.arg(pmcorrect.method,
pmcorrect.methods)
summary.method <- match.arg(summary.method,
express.summary.stat.methods)
n <- length(x)
## if NULL compute for all
if (is.null(ids))
ids <- geneNames(x)
m <- length(ids)
## cheap trick to (try to) save time
c.pps <- new("ProbeSet",
pm=matrix(),
mm=matrix())
## matrix to hold expression values
exp.mat <- matrix(NA, m, n)
se.mat <- matrix(NA, m, n)
if (verbose) {
cat(m, "ids to be processed\n")
countprogress <- 0
}
## loop over the ids
mycall <- as.call(c(getMethod("express.summary.stat",
signature=c("ProbeSet","character", "character")),
list(c.pps,
pmcorrect=pmcorrect.method, summary=summary.method,
summary.param=summary.param,
pmcorrect.param=pmcorrect.param))
)
##only one character cause no more bg correct
##bg.correct=bg.method, param.bg.correct=bg.param,
##WHy not show error? took it out cause sometimes we
##get errors and couldnt see them.
##options(show.error.messages = FALSE)
##on.exit(options(show.error.messages = TRUE))
CDFINFO <- getCdfInfo(x) ##do it once!
for (i in seq(along=ids)) {
id <- ids[i]
if (verbose) {
if ( round(m/10) == countprogress) {
cat(".")
countprogress <- 0
}
else
countprogress <- countprogress + 1
}
## locations for an id
##l.pm <- locate.name(ids[id], cdf, type="pm")
##l.mm <- locate.name(ids[id], cdf, type="mm")
loc <- get(id, envir=CDFINFO)
l.pm <- loc[, 1]
if (ncol(loc) == 2)
l.mm <- loc[ ,2]
else
l.mm <- integer()
np <- lengthl.pm)
##names are skipped
c.pps@pm <- intensity(x)[l.pm, , drop=FALSE]
c.pps@mm <- intensity(x)[l.mm, , drop=FALSE]
## generate expression values
## (wrapped in a sort of try/catch)
mycall[[2]] <- c.pps
ev <- try(eval(mycall))
if (! inherits(ev, "try-error")) {
exp.mat[i, ] <- ev$exprs
se.mat[i,] <- ev$se.exprs
} else if (warnings) {
warning(paste("Error with affyid:", id))
}
## no need for an 'else' branching since exp.mat was
initialized with NA
}
options(show.error.messages = TRUE)
on.exit(NULL)
if (verbose) cat("\n")
## instance exprSet
##if (verbose) cat("instancianting an exprSet.....")
dimnames(exp.mat) <- list(ids, sampleNames(x))
dimnames(se.mat) <- list(ids, sampleNames(x))
eset <- new("exprSet",
exprs=exp.mat,
se.exprs=se.mat, ##this changed
phenoData=phenoData(x))
##description=description(x)
##annotation=annotation(x),
##notes=notes(x))
##if (verbose) cat(".....done.\n")
return(eset)
},
where=where)