################################################### ### chunk number 1: ################################################### #line 52 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" library(RTools4TB) args(getSignatures) ################################################### ### chunk number 2: eval=FALSE ################################################### ## #line 59 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## res <- getSignatures(field="gene", value="PCNA") ## head(res) ################################################### ### chunk number 3: ################################################### #line 67 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" res <- getSignatures(field="experiment", value="GSE2004") ################################################### ### chunk number 4: ################################################### #line 73 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" res <- getSignatures(field="platform", value="GPL96") ################################################### ### chunk number 5: ################################################### #line 79 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" data(annotationList) names(annotationList) attach(annotationList) annotationList[1:4,] table(TableName) ################################################### ### chunk number 6: ################################################### #line 89 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" #Signatures containing genes related to Cell-Cycle cc <- getSignatures(field="annotation", value="HSA04110:CELL CYCLE", qValue=20) ################################################### ### chunk number 7: ################################################### #line 96 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" query <- paste(grep("^8q", Keyword,val=T),collapse="|") query cc <- getSignatures(field="annotation", value=query, qValue=10) ################################################### ### chunk number 8: ################################################### #line 110 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" gl <- getSignatures(field="gene", value="CD3D CD3E CD4", nbMin=2) head(gl) ################################################### ### chunk number 9: ################################################### #line 128 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" res <- getSignatures(field="gene", value="CD4") ################################################### ### chunk number 10: ################################################### #line 135 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" res <- getSignatures(field="gene", value="CD4 & CD3E & !CD14") ################################################### ### chunk number 11: ################################################### #line 143 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" res <- getSignatures(field="gene", value="CD4 & CD3E & !(CD19 | IGHM)") ################################################### ### chunk number 12: ################################################### #line 154 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" TS <- getSignatures(field="gene", value="XBP1 & ESR1 & GATA3") head(TS) a <- getTBInfo(field="signature", value="3DE64836D", verbose=FALSE) exp <- a["Experiment",1] info <- getTBInfo(field="experiment", value=exp, verbose=TRUE) ################################################### ### chunk number 13: ################################################### #line 170 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" library(biocGraph) ################################################### ### chunk number 14: eval=FALSE ################################################### ## #line 174 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## adjMat <- createGraph4BioC(request="XBP1 & ESR1 & GATA3", prop=80) ################################################### ### chunk number 15: ################################################### #line 177 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" adjMat <- as.matrix(read.table("ftp://tagc.univ-mrs.fr/public/TranscriptomeBrowser/RTools4TB/adjMat.txt", sep="\t", quote="", head=TRUE, row=1)) ################################################### ### chunk number 16: graph ################################################### #line 180 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" g1 <- new("graphAM", adjMat=adjMat) nodes(g1) nAt <- makeNodeAttrs(g1) nAt$fillcolor[match(rownames(as.matrix(nAt$fillcolor)), c("GATA3", "XBP1", "ESR1"), nomatch=F)!=0] <- "green" nAt$fillcolor[match(rownames(as.matrix(nAt$fillcolor)), c("TBC1D9", "FOXA1"), nomatch=F)!=0] <- "yellow" plot(g1,"fdp",nodeAttrs=nAt) ################################################### ### chunk number 17: ################################################### #line 205 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" a <- getTBInfo(field="signature", value="3DE64836D", verbose=FALSE) exp <- a["Experiment",1] info <- getTBInfo(field="experiment", value=exp, verbose=TRUE) ################################################### ### chunk number 18: ################################################### #line 212 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" sampleInfo <- getTBInfo(field="samples", value = "3DE64836D") head(sampleInfo[,1:2]) ################################################### ### chunk number 19: ################################################### #line 220 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" em <- getExpressionMatrix(signatureID="3DE64836D") class(em) ################################################### ### chunk number 20: ################################################### #line 227 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" pdf(file="heat.pdf") ################################################### ### chunk number 21: ################################################### #line 231 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" library(RColorBrewer) col <- colorRampPalette(brewer.pal(10, "RdBu"))(256) geneNames <- paste(em[,1],em[,2],sep="||") em <- as.matrix(em[,-c(1,2)]) ind <- match(colnames(em), sampleInfo[,1]) colnames(em) <- sampleInfo[ind,2] row <- rep(1,nrow(em)) ind <- grep("(XBP1)|(ESR1)|(GATA3)", geneNames,perl=TRUE) row[ind] <- 2 rc <- rainbow(2, start=0, end=.3) rc <- rc[row] col <- colorRampPalette(brewer.pal(10, "RdBu"))(256) split <- strsplit(colnames(em)," (", fixed=TRUE) pheno <- unlist(lapply(split,"[",1)) pheno <- as.factor(pheno) levels(pheno) <- 1:5 cc <- rainbow(5, start=0, end=.3) cc <- cc[pheno] heatmap(em, col=col, RowSideColors=rc, ColSideColors=cc, labRow=geneNames, cexRow=0.3) ################################################### ### chunk number 22: ################################################### #line 253 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" dev.off() ################################################### ### chunk number 23: profil ################################################### #line 267 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" plotGeneExpProfiles(data=em, X11=FALSE) ################################################### ### chunk number 24: eval=FALSE ################################################### ## #line 305 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## library(ALL) ## data(ALL) ## sub <- exprs(ALL)[1:3000,] ################################################### ### chunk number 25: eval=FALSE ################################################### ## #line 313 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## subNorm <- doNormalScore(sub) ################################################### ### chunk number 26: ################################################### #line 320 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" args(DBFMCL) ################################################### ### chunk number 27: eval=FALSE ################################################### ## #line 328 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## res <- DBFMCL(subNorm, distance.method="pearson", memory=512) ################################################### ### chunk number 28: eval=FALSE ################################################### ## #line 334 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## class(res) ################################################### ### chunk number 29: eval=FALSE ################################################### ## #line 343 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## res ################################################### ### chunk number 30: eval=FALSE ################################################### ## #line 371 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## head(res@data[,1:2]) ################################################### ### chunk number 31: eval=FALSE ################################################### ## #line 386 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## slotNames(res) ################################################### ### chunk number 32: eval=FALSE ################################################### ## #line 396 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## res@size ################################################### ### chunk number 33: eval=FALSE ################################################### ## #line 405 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## res@data[res@cluster ==1,] ################################################### ### chunk number 34: eval=FALSE ################################################### ## #line 411 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## plotGeneExpProfiles(res, sign=1) ################################################### ### chunk number 35: eval=FALSE ################################################### ## #line 416 "vignettes/RTools4TB/inst/doc/RTools4TB.Rnw" ## writeDBFMCLresult(res, filename.out="ALL.sign.txt")