Skip to content.

bioconductor.org

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

Sections

basicr.R

################################################### ### chunk number 1: lkcon ################################################### x <- c(1,2,3,4) x[2] y <- c(5,6,7,8) y[c(2,3)] m <- cbind(x,y) m m[,"x"]

################################################### ### chunk number 2: lkna ################################################### names(x) <- c("a", "b", "c", "d") x["b"] rownames(m) <- LETTERS[1:4] m m["A", "y"]

################################################### ### chunk number 3: lklit ################################################### litdf <- data.frame(samp1=c(33,22,12),samp2=c(44,111,13)) rownames(litdf) <- c("CRP", "BRCA1", "HOXA") litdf litdf["CRP",] litdf[,"samp1"] litdf["HOXA", "samp2"]

################################################### ### chunk number 4: lksel ################################################### x y keep <- c(TRUE, TRUE, FALSE, FALSE, TRUE) x[keep] x[y>6] which(y>6)

################################################### ### chunk number 5: lkoth ################################################### gender <- factor(c("M", "M", "F", "F")) gender season <- ordered(c("spring", "summer", "fall", "winter"), levels=c("spring", "summer", "fall", "winter")) season df <- data.frame(m,gender,season) df

################################################### ### chunk number 6: acc ################################################### df df$gender df["B",] z <- "season" df[[z]]

################################################### ### chunk number 7: mkdf2 ################################################### df2 <- data.frame(x=c(2,3,4,5), z=c(1,6,7,8))

################################################### ### chunk number 8: lkm1 ################################################### df df2 merge(df,df2)

################################################### ### chunk number 9: mkdf3 ################################################### merge(df,df2,all=TRUE)

################################################### ### chunk number 10: lklist ################################################### l1 <- list(df, x=x, fundem=mean) l1

################################################### ### chunk number 11: dosp ################################################### dx <- c("ALL", "ALL", "AML", "AML", "ALL", "ALL", "ALL", "AML") ddr1 <- c(12.2, 13.1, 7.2, 6.4, 14.2, 15.3, 9.2, 10.0) split(ddr1,dx)

################################################### ### chunk number 12: lkl ################################################### l1[[1]] l1$x l1$fund

################################################### ### chunk number 13: lkran ################################################### table(rpois(1000, 3)) table(rbinom(1000,5,.5)) sd(rnorm(1000,0,.4)) sd(rnorm(1000,0,.4)) set.seed(1234) sd(rnorm(1000,0,.4)) sd(rnorm(1000,0,.4)) set.seed(1234) sd(rnorm(1000,0,.4))

################################################### ### chunk number 14: lkfun ################################################### myfun1 <- function(x,y) { x+3*y } myfun1(2,3)

################################################### ### chunk number 15: lkfun2 ################################################### myfun1(2,c(3,4,5,6))

################################################### ### chunk number 16: lkb ################################################### 4 c(2,3,4,5) c(2,3) c(4,5,6)

################################################### ### chunk number 17: lkit ################################################### for (i in 1:2) print(i,season[i]) for (i in 1:3) print(l1[i]) for (s in season) print(s) for (s in as.character(season)) print(s)

################################################### ### chunk number 18: lkap ################################################### m apply(m,1,sum) apply(m,2,"^",3)

################################################### ### chunk number 19: eval=FALSE ################################################### ## date1 <- date()

################################################### ### chunk number 20: doitran ################################################### set.seed(1234) sink(file="sink1.txt") rnorm(5)

################################################### ### chunk number 21: eval=FALSE ################################################### ## sink() ## readLines("sink1.txt")

################################################### ### chunk number 22: eval=FALSE ################################################### ## length(letters)

################################################### ### chunk number 23: eval=FALSE ################################################### ## length(letters==LETTERS)

################################################### ### chunk number 24: eval=FALSE ################################################### ## all(letters==tolower(LETTERS))

################################################### ### chunk number 25: eval=FALSE ################################################### ## which( letters %in% c("a", "d") )

################################################### ### chunk number 26: eval=FALSE ################################################### ## which( c("a", "d") %in% letters )

################################################### ### chunk number 27: eval=FALSE ################################################### ## letters[ LETTERS > "W" ]

################################################### ### chunk number 28: eval=FALSE ################################################### ## letters[ !LETTERS > "C" ]

################################################### ### chunk number 29: eval=FALSE ################################################### ## sum(LETTERS > "c")

################################################### ### chunk number 30: eval=FALSE ################################################### ## seq(1,20,3)

################################################### ### chunk number 31: eval=FALSE ################################################### ## round(mean(rnorm(1000)),2)

################################################### ### chunk number 32: eval=FALSE ################################################### ## mean(rexp(1000,10))

################################################### ### chunk number 33: dopoi ################################################### kp <- rpois(100,5) table(kp) bp <- rbinom(100,4,.3) table(bp) table(bp, kp) cols <- sample(c("green", "blue"), replace=TRUE, size=100) table(cols,kp)

################################################### ### chunk number 34: domat ################################################### x <- matrix(1:10,nr=10,nc=4) x

################################################### ### chunk number 35: dodat ################################################### data(iris3) dim(iris3) dim(iris3[,,1])

################################################### ### chunk number 36: doex ################################################### expand.grid(c("M", "F"), c("trt", "control"))

################################################### ### chunk number 37: eval=FALSE ################################################### ## dim(cbind(x,x)) ## x + 4 ## x + x ## 2 x ## x / c(2,3) ## x + x[,-1] ## t(x) %% x ## row(x) ## nrow(x) ## x[ x[,3] > 5, ]

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.