Skip to content.

bioconductor.org

Bioconductor is an open source and open development software project
for the analysis and comprehension of genomic data.

Sections

lab4Affy.R

################################################### ### chunk number 1: loadPacks ################################################### library(affy)

################################################### ### chunk number 2: loadData ################################################### data(Dilution)

################################################### ### chunk number 3: Dilution ################################################### class(Dilution) slotNames(Dilution) Dilution annotation(Dilution)

################################################### ### chunk number 4: phenoData ################################################### phenoData(Dilution) pData(Dilution)

################################################### ### chunk number 5: expr ################################################### e<-exprs(Dilution) nrow(Dilution)*ncol(Dilution) dim(e)

################################################### ### chunk number 6: PMMM ################################################### PM<-pm(Dilution) dim(PM) PM[1:5,]

################################################### ### chunk number 7: AffyID ################################################### gnames<-geneNames(Dilution) length(gnames) gnames[1:5] nrow(e)/length(gnames)

################################################### ### chunk number 8: subset ################################################### dil1<-Dilution[1] class(dil1) dil1 cel1<-Dilution[[1]] class(cel1) cel1

################################################### ### chunk number 9: image1 ################################################### # Log transformation image(Dilution[1])

################################################### ### chunk number 10: image2 ################################################### # No transformation image(cel1)

################################################### ### chunk number 11: boxplot1 ################################################### boxplot(Dilution,col=c(2,2,3,3))

################################################### ### chunk number 12: hist1 ################################################### hist(Dilution, type="l", col=c(2,2,3,3), lty=rep(1:2,2), lwd=3)

################################################### ### chunk number 13: normalization ################################################### Dil20 <- normalize(Dilution[1:2]) ##conc. group 20 micrograms Dil10 <- normalize(Dilution[3:4]) ##conc. group 10 micrograms normDil <- merge(Dil20,Dil10)

################################################### ### chunk number 14: hist2 ################################################### boxplot(normDil,col=c(2,2,3,3))

################################################### ### chunk number 15: methods ################################################### bgcorrect.methods normalize.AffyBatch.methods pmcorrect.methods express.summary.stat.methods

################################################### ### chunk number 16: rma ################################################### rmaDil<-rma(normDil,normalize=FALSE) class(rmaDil)

################################################### ### chunk number 17: cdf ################################################### annotation(Dilution) data(hgu95av2cdf) pnames<-ls(env=hgu95av2cdf) length(gnames) gnames[1:5] get(gnames[1],env=hgu95av2cdf)

################################################### ### chunk number 18: loc ################################################### plocs<-indexProbes(Dilution,which="both") plocs[[1]] pmindex(Dilution,genenames=gnames[1], xy=TRUE) pmindex(Dilution,genenames=gnames[1])

################################################### ### chunk number 19: PMvMM ################################################### plot(mm(Dilution[1]),pm(Dilution[1]),pch=".",log="xy") abline(0,1,col="red")

News
2009-10-26

BioC 2.5, consisting of 352 packages and designed to work with R 2.10.z, was released today.

2009-01-07

R, the open source platform used by Bioconductor, featured in a series of articles in the New York Times.