git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/SplicingGraphs@73474 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -13,7 +13,7 @@ Depends: BiocGenerics, IRanges (>= 1.17.31), GenomicRanges, |
13 | 13 |
Imports: methods, utils, igraph, |
14 | 14 |
BiocGenerics, IRanges, GenomicRanges, |
15 | 15 |
graph, Rgraphviz, GenomicFeatures, Rsamtools |
16 |
-Suggests: Gviz, TxDb.Mmusculus.UCSC.mm9.knownGene, RUnit |
|
16 |
+Suggests: igraph, Gviz, TxDb.Mmusculus.UCSC.mm9.knownGene, RUnit |
|
17 | 17 |
Collate: utils.R |
18 | 18 |
splicingGraphs.R |
19 | 19 |
countReads.R |
... | ... |
@@ -420,20 +420,20 @@ setMethod("Sgdf", "data.frame", |
420 | 420 |
### |
421 | 421 |
|
422 | 422 |
setGeneric("Sgraph", signature="x", |
423 |
- function(x, gene_id=NA, keep.dup.edges=FALSE, as.Ragraph=FALSE) |
|
423 |
+ function(x, gene_id=NA, keep.dup.edges=FALSE, as.igraph=FALSE) |
|
424 | 424 |
standardGeneric("Sgraph") |
425 | 425 |
) |
426 | 426 |
|
427 | 427 |
setMethod("Sgraph", "ANY", |
428 |
- function(x, gene_id=NA, keep.dup.edges=FALSE, as.Ragraph=FALSE) |
|
428 |
+ function(x, gene_id=NA, keep.dup.edges=FALSE, as.igraph=FALSE) |
|
429 | 429 |
{ |
430 | 430 |
sgdf <- Sgdf(x, gene_id=gene_id, keep.dup.edges=keep.dup.edges) |
431 |
- Sgraph(sgdf, as.Ragraph=as.Ragraph) |
|
431 |
+ Sgraph(sgdf, as.igraph=as.igraph) |
|
432 | 432 |
} |
433 | 433 |
) |
434 | 434 |
|
435 | 435 |
setMethod("Sgraph", "data.frame", |
436 |
- function(x, gene_id=NA, keep.dup.edges=FALSE, as.Ragraph=FALSE) |
|
436 |
+ function(x, gene_id=NA, keep.dup.edges=FALSE, as.igraph=FALSE) |
|
437 | 437 |
{ |
438 | 438 |
if (!identical(gene_id, NA)) |
439 | 439 |
stop("the 'gene_id' arg is not supported ", |
... | ... |
@@ -442,12 +442,12 @@ setMethod("Sgraph", "data.frame", |
442 | 442 |
stop("the 'keep.dup.edges' arg is not supported ", |
443 | 443 |
"when 'x' is a data.frame") |
444 | 444 |
igraph <- .make_igraph_from_Sgdf0(x) |
445 |
- Sgraph(igraph, as.Ragraph=as.Ragraph) |
|
445 |
+ Sgraph(igraph, as.igraph=as.igraph) |
|
446 | 446 |
} |
447 | 447 |
) |
448 | 448 |
|
449 | 449 |
setMethod("Sgraph", "DataFrame", |
450 |
- function(x, gene_id=NA, keep.dup.edges=FALSE, as.Ragraph=FALSE) |
|
450 |
+ function(x, gene_id=NA, keep.dup.edges=FALSE, as.igraph=FALSE) |
|
451 | 451 |
{ |
452 | 452 |
if (!identical(gene_id, NA)) |
453 | 453 |
stop("the 'gene_id' arg is not supported ", |
... | ... |
@@ -456,12 +456,12 @@ setMethod("Sgraph", "DataFrame", |
456 | 456 |
stop("the 'keep.dup.edges' arg is not supported ", |
457 | 457 |
"when 'x' is a DataFrame") |
458 | 458 |
igraph <- .make_igraph_from_Sgdf(x) |
459 |
- Sgraph(igraph, as.Ragraph=as.Ragraph) |
|
459 |
+ Sgraph(igraph, as.igraph=as.igraph) |
|
460 | 460 |
} |
461 | 461 |
) |
462 | 462 |
|
463 | 463 |
setMethod("Sgraph", "igraph", |
464 |
- function(x, gene_id=NA, keep.dup.edges=FALSE, as.Ragraph=FALSE) |
|
464 |
+ function(x, gene_id=NA, keep.dup.edges=FALSE, as.igraph=FALSE) |
|
465 | 465 |
{ |
466 | 466 |
if (!identical(gene_id, NA)) |
467 | 467 |
stop("the 'gene_id' arg is not supported ", |
... | ... |
@@ -469,10 +469,14 @@ setMethod("Sgraph", "igraph", |
469 | 469 |
if (!identical(keep.dup.edges, FALSE)) |
470 | 470 |
stop("the 'keep.dup.edges' arg is not supported ", |
471 | 471 |
"when 'x' is an igraph object") |
472 |
- if (!isTRUEorFALSE(as.Ragraph)) |
|
473 |
- stop("'as.Ragraph' must be TRUE or FALSE") |
|
474 |
- if (!as.Ragraph) |
|
472 |
+ if (!isTRUEorFALSE(as.igraph)) |
|
473 |
+ stop("'as.igraph' must be TRUE or FALSE") |
|
474 |
+ if (as.igraph) { |
|
475 |
+ ## Need to load the igraph package so the user can display, plot, |
|
476 |
+ ## and manipulate the returned object. |
|
477 |
+ library(igraph) |
|
475 | 478 |
return(x) # no-op |
479 |
+ } |
|
476 | 480 |
make_Ragraph_from_igraph(x) |
477 | 481 |
} |
478 | 482 |
) |
... | ... |
@@ -575,11 +579,11 @@ Sgdf2 <- function(x, gene_id=NA) |
575 | 579 |
### Same as Sgraph() except that uninformative nodes (i.e. SSids) are removed. |
576 | 580 |
### |
577 | 581 |
|
578 |
-Sgraph2 <- function(x, gene_id=NA, as.Ragraph=FALSE) |
|
582 |
+Sgraph2 <- function(x, gene_id=NA, as.igraph=FALSE) |
|
579 | 583 |
{ |
580 | 584 |
if (!is(x, "DataFrame")) |
581 | 585 |
x <- Sgdf2(x, gene_id=gene_id) |
582 |
- Sgraph(x, as.Ragraph=as.Ragraph) |
|
586 |
+ Sgraph(x, as.igraph=as.igraph) |
|
583 | 587 |
} |
584 | 588 |
|
585 | 589 |
|
... | ... |
@@ -107,18 +107,24 @@ layout.Sgraph <- function(graph) |
107 | 107 |
.make_Ragraph_edgeAttrs_from_graphNEL <- function(graph_nel) |
108 | 108 |
{ |
109 | 109 |
attr_names <- names(edgeDataDefaults(graph_nel)) |
110 |
- edge_names <- edgeNames(graph_nel) |
|
111 |
- if (length(attr_names) == 0L || length(edge_names) == 0L) |
|
112 |
- return(list()) |
|
113 |
- if (anyDuplicated(edge_names)) |
|
114 |
- warning("graphNEL object has more than 1 edge between the same ", |
|
115 |
- "2 nodes. Plotting attributes for those edges (e.g. label, ", |
|
116 |
- "color, line width, line style, etc...) are likely to be ", |
|
117 |
- "wrong.") |
|
118 | 110 |
edge_data <- edgeData(graph_nel) |
119 |
- stopifnot(identical(.safeTranslateEdgeNames(names(edge_data)), |
|
120 |
- edge_names)) # sanity check |
|
121 |
- names(edge_data) <- edge_names |
|
111 |
+ edge_data_names <- names(edge_data) |
|
112 |
+ if (length(attr_names) == 0L || length(edge_data_names) == 0L) |
|
113 |
+ return(list()) |
|
114 |
+ if (anyDuplicated(edge_data_names)) |
|
115 |
+ warning("graph object has more than 1 edge between the same ", |
|
116 |
+ "2 nodes. Because setting plotting attributes for those ", |
|
117 |
+ "edges (e.g. label, color, line width, line style, etc...) ", |
|
118 |
+ "is not fully supported yet, they will end up with the same ", |
|
119 |
+ "attributes. Which is unlikely to be what you want.") |
|
120 |
+ edge_data_names <- .safeTranslateEdgeNames(edge_data_names) |
|
121 |
+ |
|
122 |
+ ## edgeNames() is broken on graphNEL objects that have more than 1 edge |
|
123 |
+ ## between the same 2 nodes, hence the use of unique() in the sanity check. |
|
124 |
+ edge_names <- edgeNames(graph_nel) |
|
125 |
+ stopifnot(identical(unique(edge_data_names), edge_names)) # sanity check |
|
126 |
+ |
|
127 |
+ names(edge_data) <- edge_data_names |
|
122 | 128 |
edge_attrs <- lapply(attr_names, |
123 | 129 |
function(attr_name) |
124 | 130 |
unlist(lapply(edge_data, `[[`, attr_name), |
... | ... |
@@ -128,8 +134,8 @@ layout.Sgraph <- function(graph) |
128 | 134 |
is_null <- sapply(edge_attrs, is.null) |
129 | 135 |
edge_attrs <- edge_attrs[!is_null] |
130 | 136 |
|
131 |
- edge_fontsize <- rep.int("10", length(edge_names)) |
|
132 |
- names(edge_fontsize) <- edge_names |
|
137 |
+ edge_fontsize <- rep.int("10", length(edge_data_names)) |
|
138 |
+ names(edge_fontsize) <- edge_data_names |
|
133 | 139 |
edge_attrs$fontsize <- edge_fontsize |
134 | 140 |
|
135 | 141 |
edge_attrs |
... | ... |
@@ -38,13 +38,13 @@ dim(TREM2sgdf) |
38 | 38 |
|
39 | 39 |
## Plot the splicing graphs: |
40 | 40 |
library(Rgraphviz) |
41 |
-plot(Sgraph(BAI1sgdf, as.Ragraph=TRUE)) |
|
42 |
-plot(Sgraph(CYB561sgdf, as.Ragraph=TRUE)) |
|
43 |
-plot(Sgraph(DAPL1sgdf, as.Ragraph=TRUE)) |
|
44 |
-plot(Sgraph(ITGB8sgdf, as.Ragraph=TRUE)) |
|
45 |
-plot(Sgraph(KIAA0319Lsgdf, as.Ragraph=TRUE)) |
|
46 |
-plot(Sgraph(LGSNsgdf, as.Ragraph=TRUE)) |
|
47 |
-plot(Sgraph(MKRN3sgdf, as.Ragraph=TRUE)) |
|
48 |
-plot(Sgraph(ST14sgdf, as.Ragraph=TRUE)) |
|
49 |
-plot(Sgraph(TREM2sgdf, as.Ragraph=TRUE)) |
|
41 |
+plot(Sgraph(BAI1sgdf)) |
|
42 |
+plot(Sgraph(CYB561sgdf)) |
|
43 |
+plot(Sgraph(DAPL1sgdf)) |
|
44 |
+plot(Sgraph(ITGB8sgdf)) |
|
45 |
+plot(Sgraph(KIAA0319Lsgdf)) |
|
46 |
+plot(Sgraph(LGSNsgdf)) |
|
47 |
+plot(Sgraph(MKRN3sgdf)) |
|
48 |
+plot(Sgraph(ST14sgdf)) |
|
49 |
+plot(Sgraph(TREM2sgdf)) |
|
50 | 50 |
} |
... | ... |
@@ -50,7 +50,7 @@ tx_by_gn <- transcriptsBy(toy_genes_txdb, by="gene") |
50 | 50 |
## Compute the splicing graphs (1 graph per gene): |
51 | 51 |
ex_by_tx2 <- splicingGraphs(ex_by_tx, tx_by_gn) |
52 | 52 |
names(ex_by_tx2) |
53 |
-plot(Sgraph(ex_by_tx2, "geneA", as.Ragraph=TRUE)) |
|
53 |
+plot(Sgraph(ex_by_tx2, gene_id="geneA")) |
|
54 | 54 |
|
55 | 55 |
## --------------------------------------------------------------------- |
56 | 56 |
## 2. Load toy reads and find the hits that are "compatible" with the |
... | ... |
@@ -91,7 +91,7 @@ UATXHcount <- countSubjectHits(ov2) |
91 | 91 |
mcols(ex_by_tx2)$UATXHcount <- UATXHcount |
92 | 92 |
|
93 | 93 |
names(ex_by_tx2) |
94 |
-plot(Sgraph(ex_by_tx2, "geneA", as.Ragraph=TRUE)) |
|
94 |
+plot(Sgraph(ex_by_tx2, gene_id="geneA")) |
|
95 | 95 |
|
96 | 96 |
## --------------------------------------------------------------------- |
97 | 97 |
## 4. Count nb of compatible hits per edge (NOTE: the same read can be |
... | ... |
@@ -106,5 +106,5 @@ ex_by_tx2 <- assignSubfeatureHits(grl, ex_by_tx2, ov1, ignore.strand=TRUE) |
106 | 106 |
in_by_tx2 <- psetdiff(range(ex_by_tx2), ex_by_tx2) |
107 | 107 |
in_by_tx2 <- assignSubfeatureHits(grl, in_by_tx2, ov1, ignore.strand=TRUE) |
108 | 108 |
|
109 |
-Sgdf(ex_by_tx2, "geneA", inbytx=in_by_tx2) |
|
109 |
+Sgdf(ex_by_tx2, gene_id="geneA", inbytx=in_by_tx2) |
|
110 | 110 |
} |
... | ... |
@@ -42,10 +42,10 @@ splicingGraphs(exbytx, grouping=NULL, check.introns=TRUE) |
42 | 42 |
Spath(x, gene_id=NA) |
43 | 43 |
UATXHcount(x, gene_id=NA) |
44 | 44 |
Sgdf(x, gene_id=NA, UATXHcount=NULL, inbytx=NULL, keep.dup.edges=FALSE) |
45 |
-Sgraph(x, gene_id=NA, keep.dup.edges=FALSE, as.Ragraph=FALSE) |
|
45 |
+Sgraph(x, gene_id=NA, keep.dup.edges=FALSE, as.igraph=FALSE) |
|
46 | 46 |
uninformativeSSids(x, gene_id=NA) |
47 | 47 |
Sgdf2(x, gene_id=NA) |
48 |
-Sgraph2(x, gene_id=NA, as.Ragraph=FALSE) |
|
48 |
+Sgraph2(x, gene_id=NA, as.igraph=FALSE) |
|
49 | 49 |
} |
50 | 50 |
|
51 | 51 |
\arguments{ |
... | ... |
@@ -76,7 +76,7 @@ Sgraph2(x, gene_id=NA, as.Ragraph=FALSE) |
76 | 76 |
\item{keep.dup.edges}{ |
77 | 77 |
TODO |
78 | 78 |
} |
79 |
- \item{as.Ragraph}{ |
|
79 |
+ \item{as.igraph}{ |
|
80 | 80 |
TODO |
81 | 81 |
} |
82 | 82 |
} |
... | ... |
@@ -199,14 +199,9 @@ sgdfA <- Sgdf(ex_by_tx2, gene_id="geneA") |
199 | 199 |
sgdfA |
200 | 200 |
|
201 | 201 |
if (interactive()) { |
202 |
- ## By default Sgraph() returns an igraph object so we need the igraph |
|
203 |
- ## package to plot it. |
|
204 |
- library(igraph) |
|
202 |
+ ## Edges are labeled with the transcript ids (or names), in blue. |
|
203 |
+ ## The green arrows are edges corresponding to exons. |
|
205 | 204 |
plot(Sgraph(sgdfA)) |
206 |
- |
|
207 |
- ## Plotting an Ragraph (Rgraphviz package) instead of an igraph object. |
|
208 |
- ## The graphviz layout engine seems to to a better job... |
|
209 |
- plot(Sgraph(sgdfA, as.Ragraph=TRUE)) |
|
210 | 205 |
} |
211 | 206 |
|
212 | 207 |
## --------------------------------------------------------------------- |
... | ... |
@@ -240,9 +235,9 @@ if (FALSE) { |
240 | 235 |
## --------------------------------------------------------------------- |
241 | 236 |
|
242 | 237 |
if (interactive()) { |
243 |
- plot(Sgraph(ex_by_tx2, gene_id="geneB", as.Ragraph=TRUE)) |
|
244 |
- plot(Sgraph(ex_by_tx2, gene_id="geneC", as.Ragraph=TRUE)) |
|
245 |
- plot(Sgraph(ex_by_tx2, gene_id="geneD", as.Ragraph=TRUE)) |
|
246 |
- plot(Sgraph(ex_by_tx2, gene_id="geneE", as.Ragraph=TRUE)) |
|
238 |
+ plot(Sgraph(ex_by_tx2, gene_id="geneB")) |
|
239 |
+ plot(Sgraph(ex_by_tx2, gene_id="geneC")) |
|
240 |
+ plot(Sgraph(ex_by_tx2, gene_id="geneD")) |
|
241 |
+ plot(Sgraph(ex_by_tx2, gene_id="geneE")) |
|
247 | 242 |
} |
248 | 243 |
} |