[BioC] Pathway Information
Ramsi Haddad
rhaddad at genetics.wayne.edu
Thu Jun 16 15:58:13 CEST 2005
Dear Michael,
There is a pretty good description in the globaltest vignette. Most of
the stuff shown below is based on it:
library(mgu74av2)
library(KEGG)
### this next line generates a list of kegg pathways and all
### the probe sets that belong in a given pathway.
mouse.kegg.sets <- as.list(mgu74av2PATH2PROBE)
### the next 3 lines give the names of the pathways from their
### kegg ID numbers
all.kegg.ids <- ls(KEGGPATHID2NAME)
all.kegg.names <- mget(all.kegg.ids, KEGGPATHID2NAME)
table.of.keggs <- as.matrix(unlist(all.kegg.names))
write.table(table.of.keggs, "keggs.csv", sep=",",col.names=NA,
row.names=T)
### here's how to get the name of a given kegg pathway:
what.is.00010 <- get("00010", KEGGPATHID2NAME) ## this is glycolysis.
### here's how to get the probesets in the Glycolysis Path from the
mouse array:
glycolysis.affyIDs <- get("00010", mgu74av2PATH2PROBE) ## there are 68
such probe sets.
another.glycolysis.affyIDs <- mouse.kegg.sets[["00010"]] ## more than
one way to skin a cat
### here's how to get the kegg pathway numbers for anything with
"Cholera"
colera.kegg.paths.index <- grep("Cholera", table.of.keggs) ## this
provides the index
colera.keggs <- table.of.keggs[colera.kegg.paths]
### here it is in one step:
### table.of.keggs[grep("Cholera", table.of.keggs)]
hope that gets you started.
Ramsi
> Hi
>
> Can anybody tell me the following
>
> I want to identify genes which are located on a certain pathway NF Kappa.
> How can I obtain such an information. Which package is appropriate and
> which commands are needed. If any body ever encounterd the same problem
> please let me know.
>
> Michael
--
Ramsi Haddad, Ph.D.
Center for Molecular Medicine and Genetics.
Functional Genomics Laboratory,
Perinatology Research Branch, NICHD, NIH.
259 Mack Avenue,
Room 3146 Applebaum Bldg.
Detroit, MI 48201, USA.
phone:(313) 577-2569 / fax:(313) 577-7736
More information about the Bioconductor
mailing list