Hi Mark,
"mark salsburg" <mark.salsburg at="" gmail.com=""> writes:
> I have a plain text file with 12,000 probe id names from an
> affymetrix chip.
If it is a chip for which a Bioconductor annotation package exists,
then you can do this easily with Bioconductor.
For example, if you have probes from the hgu95av2 chip, then the
following is a *sketch* of what you would do:
library(hgu95av2)
probeIds <- read.table(someFileWith12kIds)
syms <- mget(probeIds, hgu95av2SYMBOL, ifnotfound=NA)
if anyis.na(syms))) cat("a probeId didn't map to a symbol!\n")
write.table(unlist(syms), row.names=FALSE)
> I am using AffyNet from Affymetrix.net and going to Batch Query in
the
> Expression section where it says
> "Retrieve annotation for a probe list", where I search for "probe
set id"
> and view the list with "gene list". Is this
> correct?
>
> Some problems encountered so far:
>
> 1) affynet tells me it can only export 3000 genes
> 2) afffynet changes the order of the outputted genes by putting
probe ids
> that start with AFFY last. (they are in fact first)
> 2) affynet exports out more information than I need, I just need the
gene
> symbol.
>
> Can someone please lead me through the procedure to output out a
simple text
> file of gene symbol?
If you are looking for help using affynet, I think you haven't read
the posting guide :-) That is, this is a place to ask about
Bioconductor packages.
+ seth
Hi, Mark. What chip are you using? If you are using hgu133a, for
example,
you can do:
library(hgu133a) # after installing the hgu133a package from bioC
metadata
probeIDs <- ls(hgu133aSYMBOL)
symbols <- mget(probeIDs,hgu133aSYMBOL)
You probably want to look at the annotate and annaffy packages to
learn some
more detail.
Hope this gets you started.
Sean
On 3/21/06 12:24 PM, "mark salsburg" <mark.salsburg at="" gmail.com="">
wrote:
> I have a plain text file with 12,000 probe id names from an
affymetrix chip.
>
> Can someone please review the details of how to output out a plain
text file
> with the GENE SYMBOLS
>
> I am using AffyNet from Affymetrix.net and going to Batch Query in
the
> Expression section where it says
> "Retrieve annotation for a probe list", where I search for "probe
set id"
> and view the list with "gene list". Is this
> correct?
>
> Some problems encountered so far:
>
> 1) affynet tells me it can only export 3000 genes
> 2) afffynet changes the order of the outputted genes by putting
probe ids
> that start with AFFY last. (they are in fact first)
> 2) affynet exports out more information than I need, I just need the
gene
> symbol.
>
> Can someone please lead me through the procedure to output out a
simple text
> file of gene symbol?
>
> thank you in advance
>
> [[alternative HTML version deleted]]
>
> _______________________________________________
> Bioconductor mailing list
> Bioconductor at stat.math.ethz.ch
> https://stat.ethz.ch/mailman/listinfo/bioconductor