git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/rTRM@86453 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,12 +1,12 @@ |
1 | 1 |
Package: rTRM |
2 | 2 |
Type: Package |
3 | 3 |
Title: Identification of transcriptional regulatory modules from PPI networks |
4 |
-Version: 1.1.8 |
|
4 |
+Version: 1.1.9 |
|
5 | 5 |
Date: 2014-02-14 |
6 | 6 |
Author: Diego Diez |
7 |
-Depends: R (>= 2.10), igraph, RSQLite, annotate |
|
8 |
-Suggests: RUnit, BiocGenerics, MotifDb, graph, PWMEnrich, biomaRt, knitr, Biostrings, BSgenome.Mmusculus.UCSC.mm8, org.Mm.eg.db |
|
7 |
+Depends: R (>= 2.10), igraph, RSQLite |
|
9 | 8 |
Imports: AnnotationDbi |
9 |
+Suggests: RUnit, BiocGenerics, MotifDb, graph, PWMEnrich, biomaRt, knitr, Biostrings, BSgenome.Mmusculus.UCSC.mm8, org.Mm.eg.db |
|
10 | 10 |
Maintainer: Diego Diez <[email protected]> |
11 | 11 |
Description: rTRM identifies transcriptional regulatory modules (TRMs) from protein-protein interaction networks. |
12 | 12 |
License: GPL-3 |
... | ... |
@@ -105,8 +105,9 @@ getMotifsFromEntrezgene = function(e, organism) { |
105 | 105 |
|
106 | 106 |
# get corresponding motifs from entrezgene symbol |
107 | 107 |
getMotifsFromSymbol = function(s, organism) { |
108 |
- map = .getMapFromOrg(organism, "ALIAS2EG") |
|
109 |
- e = unlist(AnnotationDbi::mget(s, map)) |
|
108 |
+ map=.getMapFromOrg(organism) |
|
109 |
+ res=select(map,keys=s,columns="ENTREZID",keytype="ALIAS") |
|
110 |
+ e=unique(na.omit(res$ENTREZID)) |
|
110 | 111 |
|
111 | 112 |
o = getOrthologs(organism = organism) |
112 | 113 |
e_map = unique(o$entrezgene[o$map_entrezgene == e]) |
... | ... |
@@ -15,10 +15,10 @@ initBiomart = function(filter, biomart = "ensembl", host) { |
15 | 15 |
} |
16 | 16 |
|
17 | 17 |
|
18 |
-.getMapFromOrg = function(org, map = "SYMBOL") { |
|
18 |
+.getMapFromOrg = function(org) {#, map = "SYMBOL") { |
|
19 | 19 |
switch(org, |
20 |
- human = annotate::getAnnMap(map, "org.Hs.eg.db"), |
|
21 |
- mouse = annotate::getAnnMap(map, "org.Mm.eg.db") |
|
20 |
+ human = get("org.Hs.eg.db"), |
|
21 |
+ mouse = get("org.Mm.eg.db") |
|
22 | 22 |
) |
23 | 23 |
} |
24 | 24 |
|
... | ... |
@@ -35,8 +35,8 @@ getOrthologsFromBiomart = function(eg, target_org, mart) { |
35 | 35 |
res = res[!is.na(res)] |
36 | 36 |
res = unique(res[res != ""]) |
37 | 37 |
if(length(res) > 0) { |
38 |
- map = .getMapFromOrg(target_org, "ENSEMBL2EG") |
|
39 |
- res = unlist(AnnotationDbi::mget(res, map, ifnotfound = NA), use.names = FALSE) |
|
40 |
- unique(res[!is.na(res)]) |
|
38 |
+ map=.getMapFromOrg(target_org) |
|
39 |
+ res=select(map,keys=res,columns="ENTREZID",keytype="ENSEMBL") |
|
40 |
+ unique(na.omit(res$ENTREZID)) |
|
41 | 41 |
} |
42 | 42 |
} |
... | ... |
@@ -30,26 +30,6 @@ getBiogridData = function(release) { |
30 | 30 |
list(db = db, release = release, date = Sys.Date()) |
31 | 31 |
} |
32 | 32 |
|
33 |
-# getBiogridData = function(release) { |
|
34 |
-# tmp = tempfile() |
|
35 |
-# file = paste("BIOGRID-ALL-", release, ".tab2", sep = "") |
|
36 |
-# url = paste("http://thebiogrid.org/downloads/archives/Release%20Archive/BIOGRID-", release, "/", file, ".zip", sep = "") |
|
37 |
-# download.file(url, destfile = tmp) |
|
38 |
-# db = read.delim(unz(tmp, paste(file, ".txt", sep = "")), check.names = FALSE, colClasses = "character") |
|
39 |
-# unlink(tmp) |
|
40 |
-# list(db = db, release = release, date = Sys.Date()) |
|
41 |
-#} |
|
42 |
- |
|
43 |
-# getBiogridData = function(release) { |
|
44 |
-# tmp = tempfile() |
|
45 |
-# file = paste("BIOGRID-ALL-", release, ".tab2", sep = "") |
|
46 |
-# url = paste("http://thebiogrid.org/downloads/archives/Release%20Archive/BIOGRID-", release, "/", file, ".zip", sep = "") |
|
47 |
-# download.file(url, destfile = tmp) |
|
48 |
-# db = read.delim(unz(tmp, paste(file, ".txt", sep = "")), check.names = FALSE, colClasses = "character") |
|
49 |
-# unlink(tmp) |
|
50 |
-# list(db = db, release = release, date = Sys.Date()) |
|
51 |
-#} |
|
52 |
- |
|
53 | 33 |
processBiogrid = function(dblist, org = "human", simplify = TRUE, type = "physical", mimic.old = FALSE) { |
54 | 34 |
|
55 | 35 |
db = dblist$db |
... | ... |
@@ -72,10 +52,11 @@ processBiogrid = function(dblist, org = "human", simplify = TRUE, type = "physic |
72 | 52 |
|
73 | 53 |
biogrid = graph.edgelist(dbtmp, directed = FALSE) |
74 | 54 |
|
75 |
- # add gene annotations |
|
55 |
+ # add gene annotations |
|
76 | 56 |
map = .getMapFromOrg(org) |
77 |
- sym = unlist(AnnotationDbi::mget(V(biogrid)$name, map, ifnotfound = NA)) |
|
78 |
- sym[is.na(sym)] = paste("eg:", names(sym[is.na(sym)]), sep = "") |
|
57 |
+ res = select(map, keys=V(biogrid)$name, columns="SYMBOL") |
|
58 |
+ sym = res$SYMBOL |
|
59 |
+ sym[is.na(sym)] = paste("eg:", res$ENTREZID[is.na(sym)], sep="") |
|
79 | 60 |
|
80 | 61 |
V(biogrid)$label = sym[V(biogrid)$name] |
81 | 62 |
|
... | ... |
@@ -86,8 +67,6 @@ processBiogrid = function(dblist, org = "human", simplify = TRUE, type = "physic |
86 | 67 |
|
87 | 68 |
# create simplified graph. |
88 | 69 |
if (simplify) { |
89 |
- #E(biogrid)$biogrid_count <- count.multiple(biogrid) |
|
90 |
- #biogrid = simplify(biogrid) |
|
91 | 70 |
biogrid = igraph::simplify(biogrid,edge.attr.comb="concat") |
92 | 71 |
E(biogrid)$biogrid_count=sapply(E(biogrid)$pubmed_id,function(x) length(x)) |
93 | 72 |
} |
... | ... |
@@ -2,13 +2,14 @@ |
2 | 2 |
writeTRMreport = function(graph, file, organism, target, query, sort.by = "symbol") { |
3 | 3 |
x = V(graph)$name |
4 | 4 |
|
5 |
- smap = .getMapFromOrg(organism, "SYMBOL") |
|
6 |
- S = unlist(AnnotationDbi::mget(x, smap, ifnotfound = NA)) |
|
5 |
+ map=.getMapFromOrg(organism) |
|
6 |
+ res=select(map,keys=x,columns=c("SYMBOL","GENENAME")) |
|
7 |
+ |
|
8 |
+ S=res$SYMBOL |
|
7 | 9 |
S[is.na(S)] = "" |
8 |
- |
|
9 |
- dmap = .getMapFromOrg(organism, "GENENAME") |
|
10 |
- D = unlist(AnnotationDbi::mget(x, dmap, ifnotfound = NA)) |
|
11 |
- D[is.na(D)] = "" |
|
10 |
+ |
|
11 |
+ D=res$GENENAME |
|
12 |
+ D[is.na(D)] = "" |
|
12 | 13 |
|
13 | 14 |
grole = rep("bridge", length(x)) |
14 | 15 |
grole[x %in% query] = "enriched" |