git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/SplicingGraphs@75215 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
Package: SplicingGraphs |
2 | 2 |
Title: Tools for creating splicing graphs from annotations and RNA-Seq data |
3 |
-Version: 0.98.3 |
|
3 |
+Version: 0.98.4 |
|
4 | 4 |
Author: D. Bindreither, M. Carlson, M. Morgan, H. Pages |
5 | 5 |
License: Artistic-2.0 |
6 | 6 |
Description: This package allows the user to create and manipulate splicing |
... | ... |
@@ -2,32 +2,67 @@ |
2 | 2 |
### "plotTranscripts" methods |
3 | 3 |
### ------------------------------------------------------------------------- |
4 | 4 |
|
5 |
+.plotTranscripts.GRangesList <- function(x, reads=NULL, from=NULL, to=NULL) |
|
6 |
+{ |
|
7 |
+ ## Compute the genomic range of the transcripts. |
|
8 |
+ unlisted_x <- unlist(x, use.names=FALSE) |
|
9 |
+ strand(unlisted_x) <- "*" |
|
10 |
+ tx_range <- range(unlisted_x) |
|
11 |
+ if (length(tx_range) != 1L) |
|
12 |
+ stop("cannot plot transcripts that are on different chromosomes") |
|
5 | 13 |
|
6 |
-setGeneric("plotTranscripts", function(x) standardGeneric("plotTranscripts")) |
|
14 |
+ ## Genome axis. |
|
15 |
+ tracks <- list(Gviz::GenomeAxisTrack()) |
|
7 | 16 |
|
8 |
-setMethod("plotTranscripts", "GRangesList", |
|
9 |
- function(x) |
|
10 |
- { |
|
11 |
- track_names <- mcols(x)$tx_id |
|
12 |
- if (is.null(track_names)) |
|
13 |
- track_names <- names(x) |
|
14 |
- ### We create 1 track per transcript. |
|
15 |
- tx_tracks <- lapply(seq_along(x), |
|
16 |
- function(i) { |
|
17 |
- tx <- x[[i]] |
|
18 |
- Gviz::AnnotationTrack(tx, name=track_names[i], |
|
19 |
- fill="orange", shape="box") |
|
20 |
- }) |
|
21 |
- ax_track <- Gviz::GenomeAxisTrack() |
|
22 |
- Gviz::plotTracks(c(list(ax_track), tx_tracks)) |
|
17 |
+ ## Transcript tracks (we create 1 track per transcript). |
|
18 |
+ track_names <- mcols(x)$tx_id |
|
19 |
+ if (is.null(track_names)) |
|
20 |
+ track_names <- names(x) |
|
21 |
+ tx_tracks <- lapply(seq_along(x), |
|
22 |
+ function(i) { |
|
23 |
+ tx <- x[[i]] |
|
24 |
+ Gviz::AnnotationTrack(tx, name=track_names[i], |
|
25 |
+ fill="orange", shape="box") |
|
26 |
+ }) |
|
27 |
+ tracks <- c(tracks, tx_tracks) |
|
28 |
+ |
|
29 |
+ if (!is.null(reads)) { |
|
30 |
+ ## Reads track. |
|
31 |
+ reads <- grglist(reads, order.as.in.query=TRUE) |
|
32 |
+ gr <- unlist(reads) |
|
33 |
+ mcols(gr)$group <- names(gr) |
|
34 |
+ reads <- relist(unname(gr), reads) |
|
35 |
+ name <- if (length(reads) == 1L) names(reads)[1L] else "reads" |
|
36 |
+ reads_track <- Gviz::AnnotationTrack(reads, name=name, |
|
37 |
+ fill="blue", shape="box") |
|
38 |
+ tracks <- c(tracks, list(reads_track)) |
|
39 |
+ } |
|
40 |
+ |
|
41 |
+ if (is.null(from) || is.null(to)) { |
|
42 |
+ x_min_start <- start(tx_range) |
|
43 |
+ x_max_end <- end(tx_range) |
|
44 |
+ margin <- 0.10 * (x_max_end - x_min_start) |
|
45 |
+ if (is.null(from)) |
|
46 |
+ from <- x_min_start - margin |
|
47 |
+ if (is.null(to)) |
|
48 |
+ to <- x_max_end + margin |
|
23 | 49 |
} |
50 |
+ |
|
51 |
+ Gviz::plotTracks(tracks, from=from, to=to) |
|
52 |
+} |
|
53 |
+ |
|
54 |
+setGeneric("plotTranscripts", signature="x", |
|
55 |
+ function(x, reads=NULL, from=NULL, to=NULL) |
|
56 |
+ standardGeneric("plotTranscripts") |
|
24 | 57 |
) |
25 | 58 |
|
59 |
+setMethod("plotTranscripts", "GRangesList", .plotTranscripts.GRangesList) |
|
60 |
+ |
|
26 | 61 |
setMethod("plotTranscripts", "TranscriptDb", |
27 |
- function(x) |
|
62 |
+ function(x, reads=NULL, from=NULL, to=NULL) |
|
28 | 63 |
{ |
29 | 64 |
ex_by_tx <- exonsBy(x, by="tx", use.names=TRUE) |
30 |
- plotTranscripts(ex_by_tx) |
|
65 |
+ plotTranscripts(ex_by_tx, reads=reads, from=from, to=to) |
|
31 | 66 |
} |
32 | 67 |
) |
33 | 68 |
|
... | ... |
@@ -36,7 +71,7 @@ setMethod("plotTranscripts", "SplicingGraphs", |
36 | 71 |
{ |
37 | 72 |
if (length(x) != 1L) |
38 | 73 |
stop("'x' must be a SplicingGraphs object of length 1") |
39 |
- plotTranscripts(x[[1L]]) |
|
74 |
+ plotTranscripts(x[[1L]], reads=reads, from=from, to=to) |
|
40 | 75 |
} |
41 | 76 |
) |
42 | 77 |
|
... | ... |
@@ -52,26 +52,3 @@ if (FALSE) { |
52 | 52 |
from=1, to=9) |
53 | 53 |
} |
54 | 54 |
|
55 |
-### Uses the Gviz package. |
|
56 |
-plotToyReads <- function(gal, txdb, from=NULL, to=NULL) |
|
57 |
-{ |
|
58 |
- ax_track <- Gviz::GenomeAxisTrack() |
|
59 |
- txdb_track <- Gviz::GeneRegionTrack(txdb, name="genes") |
|
60 |
- grl <- grglist(gal) |
|
61 |
- gr <- unlist(grl) |
|
62 |
- mcols(gr)$group <- names(gr) |
|
63 |
- grl <- relist(unname(gr), grl) |
|
64 |
- name <- if (length(grl) == 1L) names(grl)[1L] else "reads" |
|
65 |
- gal_track <- Gviz::AnnotationTrack(grl, name=name, fill="blue", shape="box") |
|
66 |
- if (is.null(from) || is.null(to)) { |
|
67 |
- gal_min_start <- min(start(gal)) |
|
68 |
- gal_max_end <- max(end(gal)) |
|
69 |
- margin <- 0.10 * (gal_max_end - gal_min_start) |
|
70 |
- if (is.null(from)) |
|
71 |
- from <- gal_min_start - margin |
|
72 |
- if (is.null(to)) |
|
73 |
- to <- gal_max_end + margin |
|
74 |
- } |
|
75 |
- Gviz::plotTracks(list(ax_track, gal_track, txdb_track), from=from, to=to) |
|
76 |
-} |
|
77 |
- |
... | ... |
@@ -164,8 +164,8 @@ SplicingGraphs(x, grouping=NULL, min.ntx=2, max.ntx=NA, check.introns=TRUE) |
164 | 164 |
|
165 | 165 |
\seealso{ |
166 | 166 |
\itemize{ |
167 |
- \item \code{\link[GenomicFeatures]{exonsBy}}, |
|
168 |
- \code{\link[GenomicFeatures]{transcriptsBy}}, and the |
|
167 |
+ \item The \code{\link[GenomicFeatures]{exonsBy}} and |
|
168 |
+ \code{\link[GenomicFeatures]{transcriptsBy}} functions, and the |
|
169 | 169 |
\link[GenomicFeatures]{TranscriptDb} class in the GenomicFeatures |
170 | 170 |
package. |
171 | 171 |
|
... | ... |
@@ -194,6 +194,9 @@ SplicingGraphs(x, grouping=NULL, min.ntx=2, max.ntx=NA, check.introns=TRUE) |
194 | 194 |
|
195 | 195 |
\item \code{\link{countReads}} for assigning reads to the edges of a |
196 | 196 |
SplicingGraphs object and summarizing them. |
197 |
+ |
|
198 |
+ \item \code{\link{toy_genes_gff}} for details about the toy data included |
|
199 |
+ in the SplicingGraphs package. |
|
197 | 200 |
} |
198 | 201 |
} |
199 | 202 |
|
... | ... |
@@ -261,6 +264,4 @@ sg[["geneD"]] |
261 | 264 |
## by transcript. The names on the object are the gene ids: |
262 | 265 |
ex_by_tx <- unlist(sg) |
263 | 266 |
ex_by_tx |
264 |
- |
|
265 |
-## See '?plotTranscripts' for how to plot those transcripts. |
|
266 | 267 |
} |
... | ... |
@@ -56,6 +56,11 @@ countReads(sg) |
56 | 56 |
|
57 | 57 |
\seealso{ |
58 | 58 |
\itemize{ |
59 |
+ \item The \link[GenomicRanges]{GRangesList}, |
|
60 |
+ \link[GenomicRanges]{GappedAlignments}, and |
|
61 |
+ \link[GenomicRanges]{GappedAlignmentPairs} classes |
|
62 |
+ in the GenomicRanges package. |
|
63 |
+ |
|
59 | 64 |
\item The \link{SplicingGraphs} class. |
60 | 65 |
|
61 | 66 |
\item \code{\link{sgedgesByGene}} for extracting all the edges and |
... | ... |
@@ -18,7 +18,7 @@ |
18 | 18 |
} |
19 | 19 |
|
20 | 20 |
\usage{ |
21 |
-plotTranscripts(x) |
|
21 |
+plotTranscripts(x, reads=NULL, from=NULL, to=NULL) |
|
22 | 22 |
} |
23 | 23 |
|
24 | 24 |
\arguments{ |
... | ... |
@@ -28,6 +28,14 @@ plotTranscripts(x) |
28 | 28 |
\link[GenomicFeatures]{TranscriptDb} object, or a \link{SplicingGraphs} |
29 | 29 |
object of length 1. |
30 | 30 |
} |
31 |
+ \item{reads}{ |
|
32 |
+ A \link[GenomicRanges]{GappedAlignments} or |
|
33 |
+ \link[GenomicRanges]{GappedAlignmentPairs} object containing single-end |
|
34 |
+ or paired-end reads. |
|
35 |
+ } |
|
36 |
+ \item{from, to}{ |
|
37 |
+ TODO |
|
38 |
+ } |
|
31 | 39 |
} |
32 | 40 |
|
33 | 41 |
\author{ |
... | ... |
@@ -39,8 +47,10 @@ plotTranscripts(x) |
39 | 47 |
\item The \code{\link[Gviz]{plotTracks}} function in the Gviz package |
40 | 48 |
that \code{plotTranscripts} is based on. |
41 | 49 |
|
42 |
- \item The \link[GenomicRanges]{GRangesList} class in the GenomicRanges |
|
43 |
- package. |
|
50 |
+ \item The \link[GenomicRanges]{GRangesList}, |
|
51 |
+ \link[GenomicRanges]{GappedAlignments}, and |
|
52 |
+ \link[GenomicRanges]{GappedAlignmentPairs} classes |
|
53 |
+ in the GenomicRanges package. |
|
44 | 54 |
|
45 | 55 |
\item The \link[GenomicFeatures]{TranscriptDb} class in the GenomicFeatures |
46 | 56 |
package. |
... | ... |
@@ -49,10 +59,19 @@ plotTranscripts(x) |
49 | 59 |
|
50 | 60 |
\item \code{\link{sgraph}} for extracting a splicing graph as a |
51 | 61 |
plottable graph-like object. |
62 |
+ |
|
63 |
+ \item \code{\link{countReads}} for assigning reads to the edges of a |
|
64 |
+ \link{SplicingGraphs} object and summarizing them. |
|
65 |
+ |
|
66 |
+ \item \code{\link{toy_reads_bam}} for details about the toy data included |
|
67 |
+ in the SplicingGraphs package. |
|
52 | 68 |
} |
53 | 69 |
} |
54 | 70 |
|
55 | 71 |
\examples{ |
72 |
+## --------------------------------------------------------------------- |
|
73 |
+## A. PLOT TRANSCRIPTS |
|
74 |
+## --------------------------------------------------------------------- |
|
56 | 75 |
example(SplicingGraphs) # create SplicingGraphs object 'sg' |
57 | 76 |
sg |
58 | 77 |
|
... | ... |
@@ -71,4 +90,13 @@ plotTranscripts(sg[["geneD"]]) # requires the Gviz package |
71 | 90 |
ex_by_tx <- unlist(sg) |
72 | 91 |
ex_by_tx |
73 | 92 |
plotTranscripts(ex_by_tx) |
93 |
+ |
|
94 |
+## --------------------------------------------------------------------- |
|
95 |
+## B. PLOT TRANSCRIPTS AND READS |
|
96 |
+## --------------------------------------------------------------------- |
|
97 |
+gal <- readGappedAlignments(toy_reads_bam(), use.names=TRUE) |
|
98 |
+plotTranscripts(sg[["geneA"]], reads=gal) |
|
99 |
+plotTranscripts(ex_by_tx, reads=gal) |
|
100 |
+plotTranscripts(ex_by_tx, reads=gal, from=1, to=320) |
|
101 |
+plotTranscripts(ex_by_tx, reads=gal[21:26], from=1, to=320) |
|
74 | 102 |
} |
... | ... |
@@ -5,11 +5,10 @@ |
5 | 5 |
\alias{toy_reads_sam} |
6 | 6 |
\alias{toy_reads_bam} |
7 | 7 |
\alias{toy_overlaps} |
8 |
-\alias{plotToyReads} |
|
9 | 8 |
|
10 | 9 |
\title{ |
11 |
- Little helpers for quick access to (and plotting of) the toy data |
|
12 |
- included in the SplicingGraphs package |
|
10 |
+ Little helpers for quick access to the toy data included in the |
|
11 |
+ SplicingGraphs package |
|
13 | 12 |
} |
14 | 13 |
|
15 | 14 |
\description{ |
... | ... |
@@ -21,22 +20,6 @@ toy_genes_gff() |
21 | 20 |
toy_reads_sam() |
22 | 21 |
toy_reads_bam() |
23 | 22 |
toy_overlaps() |
24 |
-plotToyReads(gal, txdb, from=NULL, to=NULL) |
|
25 |
-} |
|
26 |
- |
|
27 |
-\arguments{ |
|
28 |
- \item{gal}{ |
|
29 |
- TODO |
|
30 |
- } |
|
31 |
- \item{txdb}{ |
|
32 |
- TODO |
|
33 |
- } |
|
34 |
- \item{from}{ |
|
35 |
- TODO |
|
36 |
- } |
|
37 |
- \item{to}{ |
|
38 |
- TODO |
|
39 |
- } |
|
40 | 23 |
} |
41 | 24 |
|
42 | 25 |
\author{ |
... | ... |
@@ -44,11 +27,20 @@ plotToyReads(gal, txdb, from=NULL, to=NULL) |
44 | 27 |
} |
45 | 28 |
|
46 | 29 |
\seealso{ |
47 |
- The toy data described here is used in the examples of the following |
|
48 |
- man pages: |
|
49 | 30 |
\itemize{ |
50 |
- \item \code{\link{SplicingGraphs}}: Tools for creating and |
|
51 |
- plotting splicing graphs from transcript annotations. |
|
31 |
+ \item The \link[GenomicRanges]{GRangesList}, |
|
32 |
+ \link[GenomicRanges]{GappedAlignments}, and |
|
33 |
+ \link[GenomicRanges]{GappedAlignmentPairs} classes |
|
34 |
+ in the GenomicRanges package. |
|
35 |
+ |
|
36 |
+ \item The \code{\link[GenomicFeatures]{makeTranscriptDbFromGFF}} |
|
37 |
+ function and the \link[GenomicFeatures]{TranscriptDb} class |
|
38 |
+ in the GenomicFeatures package. |
|
39 |
+ |
|
40 |
+ \item The \link{SplicingGraphs} class. |
|
41 |
+ |
|
42 |
+ \item \code{\link{plotTranscripts}} for plotting a set of transcripts |
|
43 |
+ along genomic coordinates. |
|
52 | 44 |
|
53 | 45 |
\item \code{\link{countReads}} for assigning reads to the edges of a |
54 | 46 |
\link{SplicingGraphs} object and summarizing them. |
... | ... |
@@ -70,9 +62,7 @@ suppressWarnings( |
70 | 62 |
) |
71 | 63 |
|
72 | 64 |
## Plot all the transcripts in the gene model: |
73 |
-if (interactive()) { |
|
74 |
- plotTranscripts(txdb) |
|
75 |
-} |
|
65 |
+plotTranscripts(txdb) |
|
76 | 66 |
|
77 | 67 |
## --------------------------------------------------------------------- |
78 | 68 |
## B. LOAD THE TOY READS AS A GappedAlignments OBJECT AND PLOT THEM |
... | ... |
@@ -84,19 +74,8 @@ toy_reads_sam() |
84 | 74 |
toy_reads_bam() |
85 | 75 |
gal <- readGappedAlignments(toy_reads_bam(), use.names=TRUE) |
86 | 76 |
|
87 |
-## Plot the reads: |
|
88 |
-if (interactive()) { |
|
89 |
- ## All of them: |
|
90 |
- plotToyReads(gal, txdb) |
|
91 |
- ## The first 11 only: |
|
92 |
- plotToyReads(head(gal, n=11), txdb) |
|
93 |
- ## The rest of them: |
|
94 |
- plotToyReads(tail(gal, n=-11), txdb) |
|
95 |
- ## Reads 21 to 26: |
|
96 |
- plotToyReads(gal[21:26], txdb) |
|
97 |
- ## Read 26 only: |
|
98 |
- plotToyReads(gal[26], txdb) |
|
99 |
-} |
|
77 |
+plotTranscripts(txdb, reads=gal) |
|
78 |
+plotTranscripts(txdb, reads=gal, from=1, to=320) |
|
100 | 79 |
|
101 | 80 |
## --------------------------------------------------------------------- |
102 | 81 |
## C. FIND THE OVERLAPS BETWEEN THE TOY READS AND THE TOY GENE MODEL |