Skip to content.

bioconductor.org

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

Sections

Lab1.R

################################################### ### chunk number 1: loadlib ################################################### library("Biobase") data(eset) eset

################################################### ### chunk number 2: exploringclass ###################################################

class(eset) slotNames(eset) eset$cov1 eset[1,] eset[,1]

################################################### ### chunk number 3: envEx ###################################################

e1 = new.env(hash=TRUE) e1$a = rnorm(10) e1$b = runif(20) ls(e1) xx = as.list(e1) names(xx)

################################################### ### chunk number 4: knn ################################################### library("class") apropos("knn")

################################################### ### chunk number 5: knnE1 ###################################################

exprsEset = exprs(eset) classEset = eset$cov2 esub = eset[,-1] pred1 = knn(t(exprs(esub)), exprs(eset)[,1], esub$cov2)

classEset[1]

################################################### ### chunk number 6: GOexample ################################################### library("GO") library("hgu95av2") affyGO = as.list(hgu95av2GO) #find the MF terms affyMF = lapply(affyGO, function(x) { onts = sapply(x, function(z) z$Ontology) if( is.null(onts) || is.na(onts) ) NA else unique(names(onts)[onts=="MF"]) })

################################################### ### chunk number 7: Q1 Data ################################################### x1 <- 1:10 y1 <- as.factor(rep(c("A","B"), c(5,5)))

################################################### ### chunk number 8: fig1 ###################################################

plot(x1, y1, ylim=c(0.5, 2.5), axes=FALSE) box() axis(1) axis(2, at=sort(as.numeric(unique(y1))), labels=levels(y1))

################################################### ### chunk number 9: Q2 Data ################################################### v <- rnorm(20) + 4 mean.8 <- rep(0, length(v) - 7) for (i in 1:length(mean.8)) mean.8[i] <- mean(v[i:(i+7)])

################################################### ### chunk number 10: fig2 ################################################### mp <- barplot(v, density=10, xlab="Week Number", ylab="Number of Viewers", col=1) lines(mp[8:length(v)], mean.8, lty=1, lwd=2, col=2) points(mp[8:length(v)], mean.8, pch=16, col=2) mtext(as.character(1:20), side=1, at=mp, line=0)

################################################### ### chunk number 11: chroms ################################################### whCHR = unlist(mget(geneNames(eset), hgu95av2CHR)) table(whCHR) max(table(whCHR))

################################################### ### chunk number 12: loadgp ################################################### library("geneplotter")

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.