Browse code

version 1.11.8

Add function to find ancestor GO IDs

Ge Tan authored on 12/04/2017 20:21:45
Showing 6 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: CNEr 
2
-Version: 1.11.7
3
-Date: 2017-02-23
2
+Version: 1.11.8
3
+Date: 2017-04-10
4 4
 Title: CNE Detection and Visualization
5 5
 Description: Large-scale identification and advanced visualization 
6 6
              of sets of conserved noncoding elements.
... ...
@@ -155,6 +155,9 @@ export(
155 155
   # CNE-utils.R
156 156
   plotCNEWidth, plotCNEDistribution,
157 157
   
158
+  # GO.R
159
+  addAncestorGO,
160
+  
158 161
   ## AssemblyStats.R
159 162
   N50, N90
160 163
 )
... ...
@@ -4,6 +4,7 @@ NEW FEATURES
4 4
     o Add function orgKEGGIds2EntrezIDs to fetch the mapping between KEGG IDs
5 5
       and Entrez IDs
6 6
     o Add function makeAxtTracks
7
+    o Add function addAncestorGO
7 8
     
8 9
 CHANGES IN Bioc 3.4
9 10
 ------------------------
... ...
@@ -127,4 +127,20 @@ readGAF <- function(fn){
127 127
   GOTerms <- sapply(strsplit(lines, "\t"), "[", 5)
128 128
   ans <- split(GOTerms, geneIDs)
129 129
   return(ans)
130
-}
131 130
\ No newline at end of file
131
+}
132
+
133
+### -----------------------------------------------------------------
134
+### Add ancestor GO
135
+### Exported!
136
+addAncestorGO <- function(go){
137
+  if(!is(go, "list")){
138
+    stop("`go` must be a list!")
139
+  }
140
+  goID2Ancestor <- c(as.list(GOBPANCESTOR), as.list(GOMFANCESTOR), 
141
+                     as.list(GOCCANCESTOR))
142
+  newGo <- lapply(relist(lapply(mapply(append, unlist(go), 
143
+                                       goID2Ancestor[unlist(go)]), 
144
+                                function(x){x[x!="all"]}), go), unlist)
145
+  newGo <- lapply(newGo, function(x){if(is.null(x)){character(0)}else{x}})
146
+  return(newGo)
147
+}
132 148
new file mode 100644
... ...
@@ -0,0 +1,37 @@
1
+\name{addAncestorGO}
2
+\alias{addAncestorGO}
3
+\title{
4
+  Add ancestor GO IDs
5
+}
6
+\description{
7
+  Given a list of GO IDs, add the corresponding ancestor GO IDs.
8
+}
9
+\usage{
10
+  addAncestorGO(go)
11
+}
12
+\arguments{
13
+  \item{go}{
14
+    A \code{list} of GO IDs. The elements of the list can be empty.
15
+  }
16
+}
17
+\details{
18
+  The ancestor GO IDs for each GO ID are added to the elements.
19
+}
20
+\value{
21
+  A \code{list} of GO IDs with their ancestor GO IDs.
22
+}
23
+\author{
24
+  Ge Tan
25
+}
26
+\note{
27
+  This function is mainly designed for processing the gff annotation generated
28
+  from interproscan, where for each gene, a set of GO IDs are assigned.
29
+  However, for GO enrichment analysis, we need a list of mapping from genes to
30
+  the GO IDs and their ancestor GO IDs as well.
31
+}
32
+
33
+\examples{
34
+  library(GO.db)
35
+  go <- list(c("GO:0005215", "GO:0006810", "GO:0016020"), "GO:0016579")
36
+  addAncestorGO(go)
37
+}
0 38
new file mode 100644
... ...
@@ -0,0 +1,6 @@
1
+test_that("test_addAncestorGO", {
2
+  library(GO.db)
3
+  go <- list(c("GO:0005215", "GO:0006810", "GO:0016020"), "GO:0016579")
4
+  newGO <- addAncestorGO(go)
5
+  expect_identical(lengths(newGO), c(8, 17))
6
+})
0 7
\ No newline at end of file