[BioC] bioconductor GO data package
    Vincent Carey 525-2265 
    stvjc at channing.harvard.edu
       
    Mon Mar 24 07:59:41 MET 2003
    
    
  
The structure of the package has changed.  To get the
previous behavior you can use a function like
trace2root <- function(tag,env=GOMFID2TERM,parenv=GOMFPARENTS) {
 line <- get(tag,env)
 thistag <- tag
 tmp <- thistag
 while( !is.na(tmp <- get(thistag,parenv)) ) {
#
# following needs to be made a bigger OR clause with elements
# for BP and CC root tags
#
   if (tmp == "GO:0003674") break
   line <- c(line,get(tmp,env))  # ok because depth not so great
   thistag <- tmp
 }
 line
}
> trace2root( xx[12] )
[1] "alpha-1,3-mannosyltransferase"
[2] "mannosyltransferase"
[3] "transferase, transferring hexosyl groups"
[4] "transferase, transferring glycosyl groups"
[5] "transferase"
[6] "enzyme"
Jianhua Zhang who maintains this system is away but
can comment more fully on his return
> Hi,
>
> I'm a little confused about the location of the environments
> GOmolecularfunction, GObiologicalprocess, and GOcellularcomponent in release
> 1.1.1 of the GO data package.  I know they used to be there (1.1.0), but a
> few days ago I updated to 1.1.1 and now they seem to be missing.  Have they
> been replaced with other objects that I can use to translate GOID to the
> path of ontologies?
>
> For example (using 1.1.0),
> xx <- ls(env = GOMFID2TERM)
> get(xx[12], env=GOmolecularfunction)
> $ontology
> [1] "alpha-1,3-mannosyltransferase"
>
> $ontology
> [1] "mannosyltransferase"
>
> $ontology
> [1] "transferase, transferring hexosyl groups"
>
> $ontology
> [1] "transferase, transferring glycosyl groups"
>
> $ontology
> [1] "transferase"
>
> $ontology
> [1] "enzyme"
>
>
>
> Thanks,
>
>
> Mark Wilkinson
> Informatics Analyst
> St. Jude Children's Research Hospital
> Department of Pharmaceutical Sciences
>
> The opinions expressed here are my own and do not necessarily represent
> those of St. Jude Children's Research Hospital.
>
> _______________________________________________
> Bioconductor mailing list
> Bioconductor at stat.math.ethz.ch
> https://www.stat.math.ethz.ch/mailman/listinfo/bioconductor
>
    
    
More information about the Bioconductor
mailing list