i dont think there is a package. below is a function i wrote for some
folks here at jhu. you need the makecdfenv and affy packages for it to
run. you need the TAG3 CDF and a TAG3info txt file with whats up and
whats
dn.
if you, or anybody out there,
wants to turn this into
a formal package, let me know.
##THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND.
ReadTAG3 <- function(filename="Tag3_ID.txt", CDFfile = "TAG_3.CDF",
CELfiles = NULL,
compress.cel = FALSE,
compress.cdf = FALSE, verbose = T, chip.names =
NULL,
rm.mask = FALSE, rm.outliers = FALSE, rm.extra =
FALSE,
cdf.name = NULL, ...)
{
##FIRST CHOOSE FILES
##with widget
##or without
files <- list.files(...)
if (is.null(CDFfile))
CDFfile <- files[grep(".[cC][dD][fF]", files)]
if (length(CDFfile) != 1)
stop(paste("CDFfile is not specified,exactly one CDF file must
exist in path.\n"))
if (is.null(CELfiles))
CELfiles <- files[grep(".[cC][eE][lL]", files)]
nchips <- length(CELfiles)
if (nchips < 1)
stop(paste("CELfiles is not specified, at least one CEL file must
exist in path.\n"))
if (is.null(chip.names)) {
chip.names <- CELfiles
chip.names <- as.character(sapply(chip.names, function(x)
strsplit(x,"\\.")[[1]][1]))
}
else {
if (length(chip.names) != nchips) {
warning("Not the same number of chips than chip names. Assigning
names from file.\n")
chip.names <- CELfiles
chip.names <- as.character(sapply(chip.names, function(x)
strsplit(x,"\\.")[[1]][1]))
}
}
if (verbose)
cat("reading CDF file\n")
cdf <- read.cdffile(CDFfile, compress = compress.cdf)
if (verbose)
cat("processing information\n")
info <- read.table(filename,header=T,sep="\t",as.is=T)
upordown <- info[,"Plate"]
upordown <- sapply(upordown,function(x)
if(length(grep("U",x)>0)) return("U")
else return("D"))
geneNames <- info[,"Name"]
tagNames <- info[,"Tag.name"]
names(geneNames) <- tagNames
names(upordown) <- tagNames
probeNames <- cdf@name.levels[as.vector(cdf@name)]
nrow <- dim(cdf@name)[1]
ncol <- dim(cdf@name)[2]
xs <- rep(0:(nrow-1), ncol)
ys <- rep(0:(ncol-1), rep(nrow, ncol))
Index <- probeNames%in%tagNames
mmindex <- which(ys%%4==2 & Index)
pmindex <- which(ys%%4==1 & Index)
cpmindex <- pmindex+2*nrow
cmmindex <- mmindex+2*nrow
probeNames <- probeNames[pmindex]
nprob <- length(pmindex)
x <- xs[pmindex]
y <- ys[pmindex]
pm <- matrix(0, nprob, nchips)
mm <- matrix(0, nprob, nchips)
cpm <- matrix(0,nprob, nchips)
cmm <- matrix(0,nprob, nchips)
if (verbose)
cat("reading", nchips, "CEL files")
for (i in 1:nchips) {
aux <- as.vector(read.affybatch(filenames=CELfiles[i])@exprs)
if (nrow * ncol != length(aux))
stop(paste(CELfiles[i], "doesn't match with CDFfile\n"))
pm[, i] <- aux[pmindex]
mm[, i] <- aux[mmindex]
cpm[, i] <- aux[cpmindex]
cmm[, i] <- aux[cmmindex]
if (verbose)
cat(".")
}
if (verbose)
cat("\npreparing probe level object\n")
## generate probenames for each probe using cdf@name.levels and
probe.ids
probe.ids <- as.vector(cdf@name)[pmindex]
probe.names <- cdf@name.levels[probe.ids]
colnames(pm) <- chip.names
rownames(pm) <- probeNames
colnames(mm) <- chip.names
rownames(mm) <- probeNames
colnames(cpm) <- chip.names
rownames(cpm) <- probeNames
colnames(cmm) <- chip.names
rownames(cmm) <- probeNames
list(pm=pm,mm=mm,cpm=cpm,cmm=cmm,geneNames=geneNames[probeNames],
probeNames=probeNames,upordown=upordown[probeNames],x=x,y=y)
}
On Mon, 19 Apr 2004, Julia Reid wrote:
> Can anyone point me to code designed specifically for analysis of
> Affymetrix Tag3 array data?
> Much appreciated,
> Julia Reid
>
> _______________________________________________
> Bioconductor mailing list
> Bioconductor@stat.math.ethz.ch
>
https://www.stat.math.ethz.ch/mailman/listinfo/bioconductor
>