... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: trackViewer |
2 | 2 |
Type: Package |
3 | 3 |
Title: A R/Bioconductor package with web interface for drawing elegant interactive tracks or lollipop plot to facilitate integrated analysis of multi-omics data |
4 |
-Version: 1.23.0 |
|
4 |
+Version: 1.23.1 |
|
5 | 5 |
Author@R: c(person(given="Jianhong", family="Ou", email="jianhong.ou@duke.edu", |
6 | 6 |
role=c("aut", "cre"), comment=c(ORCID="0000-0002-8652-2488")), |
7 | 7 |
person(given="Julie", family="Zhu", middle="Lihua", |
... | ... |
@@ -11,7 +11,7 @@ Maintainer: Jianhong Ou <jianhong.ou@duke.edu> |
11 | 11 |
Description: Visualize mapped reads along with annotation as track layers for NGS dataset |
12 | 12 |
such as ChIP-seq, RNA-seq, miRNA-seq, DNA-seq, SNPs and methylation data. |
13 | 13 |
License: GPL (>= 2) |
14 |
-Depends: R (>= 3.1.0), grDevices, methods, GenomicRanges, grid |
|
14 |
+Depends: R (>= 3.5.0), grDevices, methods, GenomicRanges, grid |
|
15 | 15 |
Imports: GenomeInfoDb, GenomicAlignments, GenomicFeatures, Gviz, Rsamtools, S4Vectors, |
16 | 16 |
rtracklayer, BiocGenerics, scales, tools, IRanges, AnnotationDbi, grImport, |
17 | 17 |
htmlwidgets, plotrix, Rgraphviz, InteractionSet, graph, utils |
... | ... |
@@ -19,5 +19,5 @@ Suggests: biomaRt, TxDb.Hsapiens.UCSC.hg19.knownGene, RUnit, org.Hs.eg.db, |
19 | 19 |
BiocStyle, knitr, VariantAnnotation, httr, htmltools |
20 | 20 |
biocViews: Visualization |
21 | 21 |
VignetteBuilder: knitr |
22 |
-RoxygenNote: 6.1.1 |
|
22 |
+RoxygenNote: 7.0.2 |
|
23 | 23 |
Encoding: UTF-8 |
... | ... |
@@ -11,6 +11,7 @@ export(geneModelFromTxdb) |
11 | 11 |
export(geneTrack) |
12 | 12 |
export(getCurTrackViewport) |
13 | 13 |
export(getLocation) |
14 |
+export(gi2track) |
|
14 | 15 |
export(gieStain) |
15 | 16 |
export(ideogramPlot) |
16 | 17 |
export(importBam) |
... | ... |
@@ -72,6 +73,8 @@ importFrom(GenomeInfoDb,seqnames) |
72 | 73 |
importFrom(Gviz,GeneRegionTrack) |
73 | 74 |
importFrom(Rgraphviz,layoutGraph) |
74 | 75 |
importFrom(Rgraphviz,renderGraph) |
76 |
+importFrom(S4Vectors,first) |
|
77 |
+importFrom(S4Vectors,second) |
|
75 | 78 |
importFrom(grDevices,as.raster) |
76 | 79 |
importFrom(grDevices,col2rgb) |
77 | 80 |
importFrom(grDevices,colorRampPalette) |
... | ... |
@@ -219,7 +219,7 @@ setClass("trackStyle", |
219 | 219 |
#' the scores of a given track. It should contain score metadata. When dat2 |
220 | 220 |
#' and dat is paired, dat will be drawn as positive value where dat2 will be |
221 | 221 |
#' drawn as negative value (-1 * score) |
222 |
-#' @slot type The type of track. It could be 'data', 'gene', 'transcript' or 'lollipopData'. |
|
222 |
+#' @slot type The type of track. It could be 'data', 'gene', 'transcript', 'lollipopData' or 'interactionData'. |
|
223 | 223 |
#' @slot format The format of the input. It could be "BED", "bedGraph", |
224 | 224 |
#' "WIG", "BigWig" or "BAM" |
225 | 225 |
#' @slot style Object of class \code{\link{trackStyle}} |
... | ... |
@@ -242,8 +242,8 @@ setClass("track", representation(dat="GRanges", |
242 | 242 |
style="trackStyle", |
243 | 243 |
name="character"), |
244 | 244 |
validity=function(object){ |
245 |
- if(!object@type %in% c("data", "gene", "transcript", "lollipopData")) |
|
246 |
- return("type must be 'data', 'transcript', 'gene', 'lollipopData'") |
|
245 |
+ if(!object@type %in% c("data", "gene", "transcript", "lollipopData", "interactionData")) |
|
246 |
+ return("type must be 'data', 'transcript', 'gene', 'lollipopData', 'interactionData'") |
|
247 | 247 |
if(object@type=="data"){ |
248 | 248 |
if(!object@format %in% c("BED", "bedGraph", "WIG", "BigWig", "BAM")) |
249 | 249 |
return("format must be one of \"BED\", |
... | ... |
@@ -276,13 +276,20 @@ setClass("track", representation(dat="GRanges", |
276 | 276 |
} |
277 | 277 |
} |
278 | 278 |
}else{ |
279 |
- if(is.null(mcols(object@dat)$feature)) |
|
280 |
- return("The metadata of dat must contain colnumn 'feature'") |
|
281 |
- if(length(object@dat2)>0){ |
|
282 |
- if(is.null(object@dat2$score)) |
|
283 |
- return("dat2 should contain score metadata.") |
|
284 |
- if(!all(width(object@dat2)==1)){ |
|
285 |
- return("Width for lollipop data must be 1") |
|
279 |
+ if(object@type=="interactionData"){ |
|
280 |
+ if(is.null(object@dat$score)) |
|
281 |
+ return("dat should contain score metadata.") |
|
282 |
+ if(length(object@dat2)!=length(object@dat)) |
|
283 |
+ return("dat2 should be same length of dat.") |
|
284 |
+ }else{ |
|
285 |
+ if(is.null(mcols(object@dat)$feature)) |
|
286 |
+ return("The metadata of dat must contain colnumn 'feature'") |
|
287 |
+ if(length(object@dat2)>0){ |
|
288 |
+ if(is.null(object@dat2$score)) |
|
289 |
+ return("dat2 should contain score metadata.") |
|
290 |
+ if(!all(width(object@dat2)==1)){ |
|
291 |
+ return("Width for lollipop data must be 1") |
|
292 |
+ } |
|
286 | 293 |
} |
287 | 294 |
} |
288 | 295 |
} |
289 | 296 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,20 @@ |
1 |
+#' convert GInteractions to track object |
|
2 |
+#' @description Convert GInteractions object to track object |
|
3 |
+#' @param gi an object of GInteractions |
|
4 |
+#' @return an track object |
|
5 |
+#' @importFrom S4Vectors first second |
|
6 |
+#' @export |
|
7 |
+#' @examples |
|
8 |
+#' gi <- readRDS(system.file("extdata", "nij.chr6.51120000.53200000.gi.rds", package="trackViewer")) |
|
9 |
+#' gi2track(gi) |
|
10 |
+gi2track <- function(gi){ |
|
11 |
+ stopifnot(is(gi, "GInteractions")) |
|
12 |
+ a <- first(gi) |
|
13 |
+ if(length(gi$score)==length(a)){ |
|
14 |
+ a$score <- gi$score |
|
15 |
+ }else{ |
|
16 |
+ a$score <- 1 |
|
17 |
+ } |
|
18 |
+ return(new("track", dat=a, dat2=second(gi), |
|
19 |
+ type="interactionData", format="BED")) |
|
20 |
+} |
|
0 | 21 |
\ No newline at end of file |
... | ... |
@@ -58,7 +58,7 @@ optimizeStyle <- function(trackList, viewerStyle=trackViewerStyle(), theme=NULL) |
58 | 58 |
stop("trackList must be an object of \"trackList\" |
59 | 59 |
(See ?trackList) or a list of track") |
60 | 60 |
} |
61 |
- if(trackList[[length(trackList)]]@type=="data" && viewerStyle@margin[3] < .02) |
|
61 |
+ if(trackList[[length(trackList)]]@type %in% c("data", "interactionData") && viewerStyle@margin[3] < .02) |
|
62 | 62 |
viewerStyle@margin[3] <- .02 |
63 | 63 |
##put x-axis? |
64 | 64 |
dataTracksIdx <- sapply(trackList, function(.ele) .ele@type=="data") |
... | ... |
@@ -87,14 +87,14 @@ optimizeStyle <- function(trackList, viewerStyle=trackViewerStyle(), theme=NULL) |
87 | 87 |
##put y-axis? |
88 | 88 |
if(all(!(sapply(trackList, function(.ele) .ele@style@yaxis@label)))){ |
89 | 89 |
for(i in 1:length(trackList)){ |
90 |
- if(trackList[[i]]@type=="data"){ |
|
90 |
+ if(trackList[[i]]@type %in% c("data")){ |
|
91 | 91 |
trackList[[i]]@style@yaxis@label <- TRUE |
92 | 92 |
trackList[[i]]@style@yaxis@gp <- |
93 | 93 |
c(trackList[[i]]@style@yaxis@gp, |
94 | 94 |
cex=optFontSize("y", viewerStyle)) |
95 | 95 |
trackList[[i]]@style@marginTop <- .1 |
96 | 96 |
} |
97 |
- if(trackList[[i]]@type=="lollipopData"){ |
|
97 |
+ if(trackList[[i]]@type %in% c("lollipopData", "interactionData")){ |
|
98 | 98 |
trackList[[i]]@style@yaxis@draw <- FALSE |
99 | 99 |
} |
100 | 100 |
} |
... | ... |
@@ -104,7 +104,7 @@ optimizeStyle <- function(trackList, viewerStyle=trackViewerStyle(), theme=NULL) |
104 | 104 |
if(!is.null(theme)){ |
105 | 105 |
if(theme=="bw"){ |
106 | 106 |
for(i in 1:length(trackList)){ |
107 |
- if(trackList[[i]]@type %in% c("data", "lollipopData")){ |
|
107 |
+ if(trackList[[i]]@type %in% c("data", "lollipopData", "interactionData")){ |
|
108 | 108 |
trackList[[i]]@style@ylabpos="bottomleft" |
109 | 109 |
trackList[[i]]@style@marginBottom=.2 |
110 | 110 |
trackList[[i]]@style@ylabgp= |
... | ... |
@@ -123,7 +123,7 @@ optimizeStyle <- function(trackList, viewerStyle=trackViewerStyle(), theme=NULL) |
123 | 123 |
} |
124 | 124 |
if(theme=="col"){ |
125 | 125 |
for(i in 1:length(trackList)){ |
126 |
- if(trackList[[i]]@type %in% c("data", "lollipopData")){ |
|
126 |
+ if(trackList[[i]]@type %in% c("data", "lollipopData", "interactionData")){ |
|
127 | 127 |
trackList[[i]]@style@ylabpos="bottomleft" |
128 | 128 |
trackList[[i]]@style@marginBottom=.2 |
129 | 129 |
trackList[[i]]@style@ylabgp= |
... | ... |
@@ -145,7 +145,7 @@ optimizeStyle <- function(trackList, viewerStyle=trackViewerStyle(), theme=NULL) |
145 | 145 |
safeColors <- c("#000000", "#D55E00", "#009E73", "#0072B2", |
146 | 146 |
"#56B4E9", "#CC79A7", "#E69F00", "#BEBEBE") |
147 | 147 |
for(i in 1:length(trackList)){ |
148 |
- if(trackList[[i]]@type %in% c("data", "lollipopData")){ |
|
148 |
+ if(trackList[[i]]@type %in% c("data", "lollipopData", "interactionData")){ |
|
149 | 149 |
trackList[[i]]@style@ylabpos="bottomleft" |
150 | 150 |
trackList[[i]]@style@marginBottom=.2 |
151 | 151 |
trackList[[i]]@style@ylabgp= |
152 | 152 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,58 @@ |
1 |
+plotInteractionDataTrack <- function(.dat, .dat2, chr, strand, scale, color, yscale){ |
|
2 |
+ names(.dat) <- NULL |
|
3 |
+ mcols(.dat) <- mcols(.dat)[, "score"] |
|
4 |
+ colnames(mcols(.dat)) <- "score" |
|
5 |
+ if(missing(yscale)) yscale <- c(0, 1) |
|
6 |
+ if(length(.dat)<1){ |
|
7 |
+ return() |
|
8 |
+ } |
|
9 |
+ ## plot rect at position |
|
10 |
+ ## x = (center1 + center2)/2 |
|
11 |
+ ## y = unit((x-scale[1]+1)/((scale[2] - scale[1] + 1)/2), "npc") |
|
12 |
+ ## width = width(x1) |
|
13 |
+ ## height = uint(width(x2)/(scale[2] - scale[1] + 1), "npc") |
|
14 |
+ ## rot = 45 degree |
|
15 |
+ ## color = colorRampPalette(color)(100) |
|
16 |
+ rg <- range(.dat$score[!is.na(.dat$score)]) |
|
17 |
+ if(length(rg)!=2){ |
|
18 |
+ return() |
|
19 |
+ } |
|
20 |
+ breaks <- seq(0, ceiling(rg[2]), length.out = 101) |
|
21 |
+ if(length(unique(color))==1){ |
|
22 |
+ if(!tolower(color[1]) %in% c("white", "#ffffff", "#fff")){ |
|
23 |
+ color <- c("white", color[1]) |
|
24 |
+ }else{ |
|
25 |
+ color <- c("black", color[1]) |
|
26 |
+ } |
|
27 |
+ } |
|
28 |
+ if(length(color)==0){ |
|
29 |
+ color <- c("white", "red") |
|
30 |
+ } |
|
31 |
+ crp <- colorRampPalette(color)(100) |
|
32 |
+ mc <- cut(.dat$score, breaks = breaks, labels = crp) |
|
33 |
+ mc <- as.character(mc) |
|
34 |
+ inRange <- function(x, scale){ |
|
35 |
+ x>=scale[1] & x<=scale[2] |
|
36 |
+ } |
|
37 |
+ ym <- (scale[2]-scale[1] + 1)/2 |
|
38 |
+ xa <- (end(.dat) + start(.dat2))/2 |
|
39 |
+ xb <- (start(.dat) + start(.dat2))/2 |
|
40 |
+ xc <- (start(.dat) + end(.dat2))/2 |
|
41 |
+ xd <- (end(.dat) + end(.dat2))/2 |
|
42 |
+ ya <- (xa-end(.dat)+1)/ym |
|
43 |
+ yb <- (xb-start(.dat)+1)/ym |
|
44 |
+ yc <- (xc-start(.dat)+1)/ym |
|
45 |
+ yd <- (xd-end(.dat)+1)/ym |
|
46 |
+ irx <- inRange(xa, scale) | inRange(xb, scale) | inRange(xc, scale) | inRange(xd, scale) |
|
47 |
+ iry <- inRange(ya, yscale) | inRange(yb, yscale) | inRange(yc, yscale) | inRange(yd, yscale) |
|
48 |
+ for(i in seq_along(.dat)){ |
|
49 |
+ if(irx[i] && iry[i]){ |
|
50 |
+ grid.polygon(x=c(xa[i], xb[i], xc[i], xd[i]), |
|
51 |
+ y=unit(c(ya[i], yb[i], yc[i], yd[i]), "npc"), |
|
52 |
+ default.units="native", |
|
53 |
+ gp = gpar(fill=mc[i], col = NA)) |
|
54 |
+ } |
|
55 |
+ } |
|
56 |
+ # legend |
|
57 |
+} |
|
58 |
+ |
... | ... |
@@ -145,7 +145,7 @@ plotTrack <- function(name, track, curViewStyle, curYpos, |
145 | 145 |
width=1, |
146 | 146 |
just=c(0,0))) ## vp2 |
147 | 147 |
xy <- list() |
148 |
- if(track@type %in% c("data", "lollipopData")){ |
|
148 |
+ if(track@type %in% c("data", "lollipopData", "interactionData")){ |
|
149 | 149 |
if(track@type=="data") { |
150 | 150 |
##plot yaxis |
151 | 151 |
drawYaxis(yscale, style@yaxis, curViewStyle) |
... | ... |
@@ -182,51 +182,68 @@ plotTrack <- function(name, track, curViewStyle, curYpos, |
182 | 182 |
drawXscale(style@xscale) |
183 | 183 |
} |
184 | 184 |
}else{ |
185 |
- pushViewport(viewport(x=curViewStyle@margin[2], y=0, |
|
186 |
- height=1, |
|
187 |
- width=1-curViewStyle@margin[2]-curViewStyle@margin[4], |
|
188 |
- clip="on", |
|
189 |
- just=c(0,0), |
|
190 |
- xscale=xscale)) |
|
191 |
- ybase <- ifelse(length(track@dat2)>0, .5, 0) |
|
192 |
- |
|
193 |
- LINEW <- as.numeric(convertX(unit(1, "line"), "npc")) |
|
194 |
- LINEH <- as.numeric(convertY(unit(1, "line"), "npc")) |
|
195 |
- ## GAP the gaps between any elements |
|
196 |
- GAP <- .2 * LINEH |
|
197 |
- ratio.yx <- 1/as.numeric(convertX(unit(1, "snpc"), "npc")) |
|
198 |
- getMaxHeight <- function(lollipopData){ |
|
199 |
- if(length(lollipopData)==0) return(0) |
|
200 |
- TYPES <- c("circle", "pie", "pin", "pie.stack", "flag") |
|
201 |
- type <- if(is.list(lollipopData$type)) lollipopData$type[[1]] else lollipopData$type[1] |
|
202 |
- if(length(type)==0) type <- "circle" |
|
203 |
- if(!type %in% TYPES) type <- "circle" |
|
204 |
- cex <- if(is.list(lollipopData$cex)) lollipopData$cex[[1]] else lollipopData$cex[1] |
|
205 |
- if(length(cex)==0) cex <- 1 |
|
206 |
- scoreMax0 <- scoreMax <- |
|
207 |
- if(length(lollipopData$score)>0) ceiling(max(c(lollipopData$score, 1), na.rm=TRUE)) else 1 |
|
208 |
- if(type=="pie.stack") scoreMax <- length(unique(lollipopData$stack.factor)) |
|
209 |
- if(!type %in% c("pie", "pie.stack")){ |
|
210 |
- if(scoreMax>10) { |
|
211 |
- scoreMax <- 10*scoreMax0/scoreMax |
|
212 |
- }else{ |
|
213 |
- scoreMax <- scoreMax0 |
|
185 |
+ if(track@type=="lollipopData"){ |
|
186 |
+ pushViewport(viewport(x=curViewStyle@margin[2], y=0, |
|
187 |
+ height=1, |
|
188 |
+ width=1-curViewStyle@margin[2]-curViewStyle@margin[4], |
|
189 |
+ clip="on", |
|
190 |
+ just=c(0,0), |
|
191 |
+ xscale=xscale)) |
|
192 |
+ ybase <- ifelse(length(track@dat2)>0, .5, 0) |
|
193 |
+ |
|
194 |
+ LINEW <- as.numeric(convertX(unit(1, "line"), "npc")) |
|
195 |
+ LINEH <- as.numeric(convertY(unit(1, "line"), "npc")) |
|
196 |
+ ## GAP the gaps between any elements |
|
197 |
+ GAP <- .2 * LINEH |
|
198 |
+ ratio.yx <- 1/as.numeric(convertX(unit(1, "snpc"), "npc")) |
|
199 |
+ getMaxHeight <- function(lollipopData){ |
|
200 |
+ if(length(lollipopData)==0) return(0) |
|
201 |
+ TYPES <- c("circle", "pie", "pin", "pie.stack", "flag") |
|
202 |
+ type <- if(is.list(lollipopData$type)) lollipopData$type[[1]] else lollipopData$type[1] |
|
203 |
+ if(length(type)==0) type <- "circle" |
|
204 |
+ if(!type %in% TYPES) type <- "circle" |
|
205 |
+ cex <- if(is.list(lollipopData$cex)) lollipopData$cex[[1]] else lollipopData$cex[1] |
|
206 |
+ if(length(cex)==0) cex <- 1 |
|
207 |
+ scoreMax0 <- scoreMax <- |
|
208 |
+ if(length(lollipopData$score)>0) ceiling(max(c(lollipopData$score, 1), na.rm=TRUE)) else 1 |
|
209 |
+ if(type=="pie.stack") scoreMax <- length(unique(lollipopData$stack.factor)) |
|
210 |
+ if(!type %in% c("pie", "pie.stack")){ |
|
211 |
+ if(scoreMax>10) { |
|
212 |
+ scoreMax <- 10*scoreMax0/scoreMax |
|
213 |
+ }else{ |
|
214 |
+ scoreMax <- scoreMax0 |
|
215 |
+ } |
|
214 | 216 |
} |
217 |
+ getHeight(lollipopData, |
|
218 |
+ ratio.yx, LINEW, GAP, cex, type, |
|
219 |
+ scoreMax=scoreMax, |
|
220 |
+ level="data") |
|
221 |
+ } |
|
222 |
+ maxHeight <- max(c(getMaxHeight(track@dat), getMaxHeight(track@dat2)), na.rm = TRUE) |
|
223 |
+ if(length(track@dat2)>0) maxHeight + .5 |
|
224 |
+ plotLollipopData(track@dat, xlim, chr, style@yaxis@draw, gpar(), |
|
225 |
+ ybase, side="top", main=style@yaxis@main, |
|
226 |
+ baselineCol=style@color[1], maxHeight=maxHeight) |
|
227 |
+ if(length(track@dat2)>0) { |
|
228 |
+ plotLollipopData(track@dat2, xlim, chr, style@yaxis@draw, gpar(), |
|
229 |
+ ybase, side="bottom", main=style@yaxis@main, |
|
230 |
+ baselineCol=style@color[2], maxHeight=maxHeight) |
|
231 |
+ } |
|
232 |
+ }else{##interactionData |
|
233 |
+ ##plot yaxis |
|
234 |
+ drawYaxis(yscale, style@yaxis, curViewStyle) |
|
235 |
+ pushViewport(viewport(x=curViewStyle@margin[2], y=0, |
|
236 |
+ height=1, |
|
237 |
+ width=1-curViewStyle@margin[2]-curViewStyle@margin[4], |
|
238 |
+ clip="on", |
|
239 |
+ just=c(0,0), |
|
240 |
+ xscale=xscale, |
|
241 |
+ yscale=yscale)) |
|
242 |
+ ##grid.clip() |
|
243 |
+ ##for dat interaction: dat, dat2, pair. |
|
244 |
+ if(length(track@dat)==length(track@dat2)){ |
|
245 |
+ plotInteractionDataTrack(track@dat, track@dat2, chr, strand, xlim, style@color[1], yscale=yscale) |
|
215 | 246 |
} |
216 |
- getHeight(lollipopData, |
|
217 |
- ratio.yx, LINEW, GAP, cex, type, |
|
218 |
- scoreMax=scoreMax, |
|
219 |
- level="data") |
|
220 |
- } |
|
221 |
- maxHeight <- max(c(getMaxHeight(track@dat), getMaxHeight(track@dat2)), na.rm = TRUE) |
|
222 |
- if(length(track@dat2)>0) maxHeight + .5 |
|
223 |
- plotLollipopData(track@dat, xlim, chr, style@yaxis@draw, gpar(), |
|
224 |
- ybase, side="top", main=style@yaxis@main, |
|
225 |
- baselineCol=style@color[1], maxHeight=maxHeight) |
|
226 |
- if(length(track@dat2)>0) { |
|
227 |
- plotLollipopData(track@dat2, xlim, chr, style@yaxis@draw, gpar(), |
|
228 |
- ybase, side="bottom", main=style@yaxis@main, |
|
229 |
- baselineCol=style@color[2], maxHeight=maxHeight) |
|
230 | 247 |
} |
231 | 248 |
} |
232 | 249 |
}else{##track@type=="transcript" or "gene" |
... | ... |
@@ -132,26 +132,44 @@ filterTracks <- function(tl, chrom, from, to, st){ |
132 | 132 |
} |
133 | 133 |
} |
134 | 134 |
}else{ |
135 |
- if(tl[[i]]@type=="lollipopData"){ |
|
135 |
+ if(tl[[i]]@type=="interactionData"){## dat, dat2 are paired |
|
136 | 136 |
dat <- tl[[i]]@dat |
137 |
+ dat2 <- tl[[i]]@dat2 |
|
138 |
+ keep <- ((end(dat)>=from & start(dat)<=to) | |
|
139 |
+ (end(dat2)>=from & start(dat2)<=to)) & |
|
140 |
+ seqnames(dat)==chrom & seqnames(dat2)==chrom |
|
141 |
+ ## remove duplicates |
|
142 |
+ idx1 <- paste(as.character(seqnames(dat)), start(dat), end(dat), |
|
143 |
+ as.character(seqnames(dat2)), start(dat2), end(dat2)) |
|
144 |
+ idx2 <- paste(as.character(seqnames(dat2)), start(dat2), end(dat2), |
|
145 |
+ as.character(seqnames(dat)), start(dat), end(dat)) |
|
146 |
+ idx <- ifelse(start(dat)<start(dat2), idx1, idx2) |
|
147 |
+ keep <- keep & (!duplicated(idx)) |
|
148 |
+ |
|
149 |
+ tl[[i]]@dat <- dat[keep] |
|
150 |
+ tl[[i]]@dat2 <- dat2[keep] |
|
137 | 151 |
}else{ |
138 |
- dat <- range(tl[[i]]@dat) |
|
139 |
- } |
|
152 |
+ if(tl[[i]]@type=="lollipopData"){ |
|
153 |
+ dat <- tl[[i]]@dat |
|
154 |
+ }else{ |
|
155 |
+ dat <- range(tl[[i]]@dat) |
|
156 |
+ } |
|
140 | 157 |
dat <- dat[end(dat)>=from & |
141 |
- start(dat)<=to & |
|
142 |
- seqnames(dat)==chrom] |
|
158 |
+ start(dat)<=to & |
|
159 |
+ seqnames(dat)==chrom] |
|
143 | 160 |
dat2 <- tl[[i]]@dat2 |
144 | 161 |
if(length(dat2)>0){ |
145 |
- dat2 <- dat2[end(dat2)>=from & |
|
146 |
- start(dat2)<=to & |
|
147 |
- seqnames(dat2)==chrom] |
|
162 |
+ dat2 <- dat2[end(dat2)>=from & |
|
163 |
+ start(dat2)<=to & |
|
164 |
+ seqnames(dat2)==chrom] |
|
148 | 165 |
} |
149 | 166 |
if(tl[[i]]@type=="lollipopData"){ |
150 | 167 |
tl[[i]]@dat <- dat |
151 | 168 |
tl[[i]]@dat2 <- dat2 |
152 | 169 |
} |
153 | 170 |
if(length(dat)==0 && length(dat2)==0) |
154 |
- tl[[i]]@style@height <- 0 |
|
171 |
+ tl[[i]]@style@height <- 0 |
|
172 |
+ } |
|
155 | 173 |
} |
156 | 174 |
} |
157 | 175 |
tl |
... | ... |
@@ -173,7 +191,12 @@ getYlim <- function(tl, op){ |
173 | 191 |
} |
174 | 192 |
ylim <- range(c(0, ylim)) |
175 | 193 |
}else{ |
194 |
+ if(.ele@type == "interactionData"){ |
|
195 |
+ ## max interaction height |
|
196 |
+ ylim <- c(0, 1) |
|
197 |
+ }else{ |
|
176 | 198 |
ylim <- c(0, 0) |
199 |
+ } |
|
177 | 200 |
} |
178 | 201 |
} |
179 | 202 |
ylim |
... | ... |
@@ -4,8 +4,13 @@ |
4 | 4 |
\alias{GRoperator} |
5 | 5 |
\title{GRanges operator} |
6 | 6 |
\usage{ |
7 |
-GRoperator(A, B, col = "score", operator = c("+", "-", "*", "/", "^", |
|
8 |
- "\%\%"), ignore.strand = TRUE) |
|
7 |
+GRoperator( |
|
8 |
+ A, |
|
9 |
+ B, |
|
10 |
+ col = "score", |
|
11 |
+ operator = c("+", "-", "*", "/", "^", "\%\%"), |
|
12 |
+ ignore.strand = TRUE |
|
13 |
+) |
|
9 | 14 |
} |
10 | 15 |
\arguments{ |
11 | 16 |
\item{A}{an object of GRanges} |
... | ... |
@@ -4,9 +4,17 @@ |
4 | 4 |
\alias{addArrowMark} |
5 | 5 |
\title{Add arrow mark to the figure at a given position} |
6 | 6 |
\usage{ |
7 |
-addArrowMark(pos = grid.locator(), label = NULL, angle = 15, |
|
8 |
- length = unit(0.25, "inches"), col = "red", cex = 1, |
|
9 |
- quadrant = 4, type = "closed", vp = NULL) |
|
7 |
+addArrowMark( |
|
8 |
+ pos = grid.locator(), |
|
9 |
+ label = NULL, |
|
10 |
+ angle = 15, |
|
11 |
+ length = unit(0.25, "inches"), |
|
12 |
+ col = "red", |
|
13 |
+ cex = 1, |
|
14 |
+ quadrant = 4, |
|
15 |
+ type = "closed", |
|
16 |
+ vp = NULL |
|
17 |
+) |
|
10 | 18 |
} |
11 | 19 |
\arguments{ |
12 | 20 |
\item{pos}{A unit object representing the location of arrow mark to be placed |
... | ... |
@@ -4,8 +4,7 @@ |
4 | 4 |
\alias{addGuideLine} |
5 | 5 |
\title{Add guide lines to the tracks} |
6 | 6 |
\usage{ |
7 |
-addGuideLine(guideLine, col = "gray", lty = "dashed", lwd = 1, |
|
8 |
- vp = NULL) |
|
7 |
+addGuideLine(guideLine, col = "gray", lty = "dashed", lwd = 1, vp = NULL) |
|
9 | 8 |
} |
10 | 9 |
\arguments{ |
11 | 10 |
\item{guideLine}{The genomic coordinates to draw the lines} |
... | ... |
@@ -4,8 +4,14 @@ |
4 | 4 |
\alias{browseTracks} |
5 | 5 |
\title{browse tracks} |
6 | 6 |
\usage{ |
7 |
-browseTracks(trackList, gr = GRanges(), ignore.strand = TRUE, |
|
8 |
- width = NULL, height = NULL, ...) |
|
7 |
+browseTracks( |
|
8 |
+ trackList, |
|
9 |
+ gr = GRanges(), |
|
10 |
+ ignore.strand = TRUE, |
|
11 |
+ width = NULL, |
|
12 |
+ height = NULL, |
|
13 |
+ ... |
|
14 |
+) |
|
9 | 15 |
} |
10 | 16 |
\arguments{ |
11 | 17 |
\item{trackList}{an object of \code{\link{trackList}}} |
... | ... |
@@ -4,12 +4,24 @@ |
4 | 4 |
\alias{dandelion.plot} |
5 | 5 |
\title{dandelion.plots} |
6 | 6 |
\usage{ |
7 |
-dandelion.plot(SNP.gr, features = NULL, ranges = NULL, |
|
8 |
- type = c("fan", "circle", "pie", "pin"), newpage = TRUE, |
|
9 |
- ylab = TRUE, ylab.gp = gpar(col = "black"), xaxis = TRUE, |
|
10 |
- xaxis.gp = gpar(col = "black"), yaxis = FALSE, yaxis.gp = gpar(col |
|
11 |
- = "black"), legend = NULL, cex = 1, maxgaps = 1/50, |
|
12 |
- heightMethod = NULL, ...) |
|
7 |
+dandelion.plot( |
|
8 |
+ SNP.gr, |
|
9 |
+ features = NULL, |
|
10 |
+ ranges = NULL, |
|
11 |
+ type = c("fan", "circle", "pie", "pin"), |
|
12 |
+ newpage = TRUE, |
|
13 |
+ ylab = TRUE, |
|
14 |
+ ylab.gp = gpar(col = "black"), |
|
15 |
+ xaxis = TRUE, |
|
16 |
+ xaxis.gp = gpar(col = "black"), |
|
17 |
+ yaxis = FALSE, |
|
18 |
+ yaxis.gp = gpar(col = "black"), |
|
19 |
+ legend = NULL, |
|
20 |
+ cex = 1, |
|
21 |
+ maxgaps = 1/50, |
|
22 |
+ heightMethod = NULL, |
|
23 |
+ ... |
|
24 |
+) |
|
13 | 25 |
} |
14 | 26 |
\arguments{ |
15 | 27 |
\item{SNP.gr}{A object of \link[GenomicRanges:GRanges-class]{GRanges} or |
... | ... |
@@ -4,8 +4,16 @@ |
4 | 4 |
\alias{geneModelFromTxdb} |
5 | 5 |
\title{Prepare gene model from an object of TxDb} |
6 | 6 |
\usage{ |
7 |
-geneModelFromTxdb(txdb, orgDb, gr, chrom, start, end, strand = c("*", |
|
8 |
- "+", "-"), txdump = NULL) |
|
7 |
+geneModelFromTxdb( |
|
8 |
+ txdb, |
|
9 |
+ orgDb, |
|
10 |
+ gr, |
|
11 |
+ chrom, |
|
12 |
+ start, |
|
13 |
+ end, |
|
14 |
+ strand = c("*", "+", "-"), |
|
15 |
+ txdump = NULL |
|
16 |
+) |
|
9 | 17 |
} |
10 | 18 |
\arguments{ |
11 | 19 |
\item{txdb}{An object of \code{\link[GenomicFeatures:TxDb-class]{TxDb}}} |
12 | 20 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,21 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/gi2track.R |
|
3 |
+\name{gi2track} |
|
4 |
+\alias{gi2track} |
|
5 |
+\title{convert GInteractions to track object} |
|
6 |
+\usage{ |
|
7 |
+gi2track(gi) |
|
8 |
+} |
|
9 |
+\arguments{ |
|
10 |
+\item{gi}{an object of GInteractions} |
|
11 |
+} |
|
12 |
+\value{ |
|
13 |
+an track object |
|
14 |
+} |
|
15 |
+\description{ |
|
16 |
+Convert GInteractions object to track object |
|
17 |
+} |
|
18 |
+\examples{ |
|
19 |
+gi <- readRDS(system.file("extdata", "nij.chr6.51120000.53200000.gi.rds", package="trackViewer")) |
|
20 |
+gi2track(gi) |
|
21 |
+} |
... | ... |
@@ -4,14 +4,20 @@ |
4 | 4 |
\alias{ideogramPlot} |
5 | 5 |
\title{plot ideogram with data} |
6 | 6 |
\usage{ |
7 |
-ideogramPlot(ideo, dataList, layout = NULL, horiz = TRUE, |
|
8 |
- parameterList = list(vp = plotViewport(margins = c(0.1, 4.1, 0.3, |
|
9 |
- 0.1)), ideoHeight = unit(1/(1 + length(dataList)), "npc"), vgap = |
|
10 |
- unit(0.3, "lines"), ylabs = "auto", ylabsRot = ifelse(horiz, 0, 90), |
|
11 |
- ylabsPos = unit(2.5, "lines"), xaxis = FALSE, yaxis = FALSE, xlab = "", |
|
12 |
- types = "barplot", heights = NULL, dataColumn = "score", gps = gpar(col = |
|
13 |
- "black", fill = "gray")), colorSheme = gieStain(), gp = gpar(fill = |
|
14 |
- NA, lwd = 2), ...) |
|
7 |
+ideogramPlot( |
|
8 |
+ ideo, |
|
9 |
+ dataList, |
|
10 |
+ layout = NULL, |
|
11 |
+ horiz = TRUE, |
|
12 |
+ parameterList = list(vp = plotViewport(margins = c(0.1, 4.1, 0.3, 0.1)), ideoHeight = |
|
13 |
+ unit(1/(1 + length(dataList)), "npc"), vgap = unit(0.3, "lines"), ylabs = "auto", |
|
14 |
+ ylabsRot = ifelse(horiz, 0, 90), ylabsPos = unit(2.5, "lines"), xaxis = FALSE, yaxis = |
|
15 |
+ FALSE, xlab = "", types = "barplot", heights = NULL, dataColumn = "score", gps = |
|
16 |
+ gpar(col = "black", fill = "gray")), |
|
17 |
+ colorSheme = gieStain(), |
|
18 |
+ gp = gpar(fill = NA, lwd = 2), |
|
19 |
+ ... |
|
20 |
+) |
|
15 | 21 |
} |
16 | 22 |
\arguments{ |
17 | 23 |
\item{ideo}{output of \link{loadIdeogram}.} |
... | ... |
@@ -4,8 +4,13 @@ |
4 | 4 |
\alias{importScore} |
5 | 5 |
\title{Reading data from a BED or WIG file} |
6 | 6 |
\usage{ |
7 |
-importScore(file, file2, format = c("BED", "bedGraph", "WIG", "BigWig"), |
|
8 |
- ranges = GRanges(), ignore.strand = TRUE) |
|
7 |
+importScore( |
|
8 |
+ file, |
|
9 |
+ file2, |
|
10 |
+ format = c("BED", "bedGraph", "WIG", "BigWig"), |
|
11 |
+ ranges = GRanges(), |
|
12 |
+ ignore.strand = TRUE |
|
13 |
+) |
|
9 | 14 |
} |
10 | 15 |
\arguments{ |
11 | 16 |
\item{file}{The path to the file to read.} |
... | ... |
@@ -4,12 +4,25 @@ |
4 | 4 |
\alias{lolliplot} |
5 | 5 |
\title{Lolliplots} |
6 | 6 |
\usage{ |
7 |
-lolliplot(SNP.gr, features = NULL, ranges = NULL, type = "circle", |
|
8 |
- newpage = TRUE, ylab = TRUE, ylab.gp = gpar(col = "black"), |
|
9 |
- yaxis = TRUE, yaxis.gp = gpar(col = "black"), xaxis = TRUE, |
|
10 |
- xaxis.gp = gpar(col = "black"), legend = NULL, cex = 1, |
|
11 |
- dashline.col = "gray80", jitter = c("node", "label"), |
|
12 |
- rescale = FALSE, ...) |
|
7 |
+lolliplot( |
|
8 |
+ SNP.gr, |
|
9 |
+ features = NULL, |
|
10 |
+ ranges = NULL, |
|
11 |
+ type = "circle", |
|
12 |
+ newpage = TRUE, |
|
13 |
+ ylab = TRUE, |
|
14 |
+ ylab.gp = gpar(col = "black"), |
|
15 |
+ yaxis = TRUE, |
|
16 |
+ yaxis.gp = gpar(col = "black"), |
|
17 |
+ xaxis = TRUE, |
|
18 |
+ xaxis.gp = gpar(col = "black"), |
|
19 |
+ legend = NULL, |
|
20 |
+ cex = 1, |
|
21 |
+ dashline.col = "gray80", |
|
22 |
+ jitter = c("node", "label"), |
|
23 |
+ rescale = FALSE, |
|
24 |
+ ... |
|
25 |
+) |
|
13 | 26 |
} |
14 | 27 |
\arguments{ |
15 | 28 |
\item{SNP.gr}{A object of \link[GenomicRanges:GRanges-class]{GRanges}, |
... | ... |
@@ -4,8 +4,7 @@ |
4 | 4 |
\alias{optimizeStyle} |
5 | 5 |
\title{Optimize the style of plot} |
6 | 6 |
\usage{ |
7 |
-optimizeStyle(trackList, viewerStyle = trackViewerStyle(), |
|
8 |
- theme = NULL) |
|
7 |
+optimizeStyle(trackList, viewerStyle = trackViewerStyle(), theme = NULL) |
|
9 | 8 |
} |
10 | 9 |
\arguments{ |
11 | 10 |
\item{trackList}{An object of \code{\link{trackList}}} |
... | ... |
@@ -4,8 +4,13 @@ |
4 | 4 |
\alias{plotGRanges} |
5 | 5 |
\title{plot GRanges data} |
6 | 6 |
\usage{ |
7 |
-plotGRanges(..., range = GRanges(), viewerStyle = trackViewerStyle(), |
|
8 |
- autoOptimizeStyle = FALSE, newpage = TRUE) |
|
7 |
+plotGRanges( |
|
8 |
+ ..., |
|
9 |
+ range = GRanges(), |
|
10 |
+ viewerStyle = trackViewerStyle(), |
|
11 |
+ autoOptimizeStyle = FALSE, |
|
12 |
+ newpage = TRUE |
|
13 |
+) |
|
9 | 14 |
} |
10 | 15 |
\arguments{ |
11 | 16 |
\item{\dots}{one or more objects of \code{\link[GenomicRanges:GRanges-class]{GRanges}}} |
... | ... |
@@ -4,8 +4,13 @@ |
4 | 4 |
\alias{plotIdeo} |
5 | 5 |
\title{plot ideogram} |
6 | 6 |
\usage{ |
7 |
-plotIdeo(ideo, chrom = seqlevels(ideo)[1], colorSheme = gieStain(), |
|
8 |
- gp = gpar(fill = NA), ...) |
|
7 |
+plotIdeo( |
|
8 |
+ ideo, |
|
9 |
+ chrom = seqlevels(ideo)[1], |
|
10 |
+ colorSheme = gieStain(), |
|
11 |
+ gp = gpar(fill = NA), |
|
12 |
+ ... |
|
13 |
+) |
|
9 | 14 |
} |
10 | 15 |
\arguments{ |
11 | 16 |
\item{ideo}{output of \link{loadIdeogram}.} |
... | ... |
@@ -4,14 +4,19 @@ |
4 | 4 |
\alias{plotOneIdeo} |
5 | 5 |
\title{plot ideogram with data for one chromosome} |
6 | 6 |
\usage{ |
7 |
-plotOneIdeo(ideo, dataList, parameterList = list(vp = |
|
8 |
- plotViewport(margins = c(0.1, 4.1, 1.1, 0.1)), ideoHeight = unit(1/(1 + |
|
9 |
- length(dataList)), "npc"), vgap = unit(1, "lines"), ylabs = |
|
10 |
- seqlevels(ideo)[1], ylabsRot = 90, ylabsPos = unit(2.5, "lines"), xaxis = |
|
11 |
- FALSE, yaxis = FALSE, xlab = "", types = "barplot", heights = NULL, |
|
12 |
- dataColumn = "score", gps = gpar(col = "black", fill = "gray")), |
|
13 |
- chrom = seqlevels(ideo)[1], colorSheme = gieStain(), gp = gpar(fill |
|
14 |
- = NA, lwd = 2), ...) |
|
7 |
+plotOneIdeo( |
|
8 |
+ ideo, |
|
9 |
+ dataList, |
|
10 |
+ parameterList = list(vp = plotViewport(margins = c(0.1, 4.1, 1.1, 0.1)), ideoHeight = |
|
11 |
+ unit(1/(1 + length(dataList)), "npc"), vgap = unit(1, "lines"), ylabs = |
|
12 |
+ seqlevels(ideo)[1], ylabsRot = 90, ylabsPos = unit(2.5, "lines"), xaxis = FALSE, yaxis |
|
13 |
+ = FALSE, xlab = "", types = "barplot", heights = NULL, dataColumn = "score", gps = |
|
14 |
+ gpar(col = "black", fill = "gray")), |
|
15 |
+ chrom = seqlevels(ideo)[1], |
|
16 |
+ colorSheme = gieStain(), |
|
17 |
+ gp = gpar(fill = NA, lwd = 2), |
|
18 |
+ ... |
|
19 |
+) |
|
15 | 20 |
} |
16 | 21 |
\arguments{ |
17 | 22 |
\item{ideo}{output of \link{loadIdeogram}.} |
... | ... |
@@ -101,7 +101,7 @@ the scores of a given track. It should contain score metadata. When dat2 |
101 | 101 |
and dat is paired, dat will be drawn as positive value where dat2 will be |
102 | 102 |
drawn as negative value (-1 * score)} |
103 | 103 |
|
104 |
-\item{\code{type}}{The type of track. It could be 'data', 'gene', 'transcript' or 'lollipopData'.} |
|
104 |
+\item{\code{type}}{The type of track. It could be 'data', 'gene', 'transcript', 'lollipopData' or 'interactionData'.} |
|
105 | 105 |
|
106 | 106 |
\item{\code{format}}{The format of the input. It could be "BED", "bedGraph", |
107 | 107 |
"WIG", "BigWig" or "BAM"} |
... | ... |
@@ -13,8 +13,7 @@ trackViewerStyle(...) |
13 | 13 |
|
14 | 14 |
setTrackViewerStyleParam(tvs, attr, value) |
15 | 15 |
|
16 |
-\S4method{setTrackViewerStyleParam}{trackViewerStyle,character}(tvs, attr, |
|
17 |
- value) |
|
16 |
+\S4method{setTrackViewerStyleParam}{trackViewerStyle,character}(tvs, attr, value) |
|
18 | 17 |
} |
19 | 18 |
\arguments{ |
20 | 19 |
\item{\dots}{Each argument in \dots becomes an slot in the new trackViewerStyle.} |
... | ... |
@@ -4,8 +4,17 @@ |
4 | 4 |
\alias{viewGene} |
5 | 5 |
\title{plot tracks based on gene name} |
6 | 6 |
\usage{ |
7 |
-viewGene(symbol, filenames, format, txdb, org, upstream = 1000, |
|
8 |
- downstream = 1000, anchor = c("gene", "TSS"), plot = FALSE) |
|
7 |
+viewGene( |
|
8 |
+ symbol, |
|
9 |
+ filenames, |
|
10 |
+ format, |
|
11 |
+ txdb, |
|
12 |
+ org, |
|
13 |
+ upstream = 1000, |
|
14 |
+ downstream = 1000, |
|
15 |
+ anchor = c("gene", "TSS"), |
|
16 |
+ plot = FALSE |
|
17 |
+) |
|
9 | 18 |
} |
10 | 19 |
\arguments{ |
11 | 20 |
\item{symbol}{Gene symbol} |
... | ... |
@@ -4,10 +4,20 @@ |
4 | 4 |
\alias{viewTracks} |
5 | 5 |
\title{plot the tracks} |
6 | 6 |
\usage{ |
7 |
-viewTracks(trackList, chromosome, start, end, strand, gr = GRanges(), |
|
8 |
- ignore.strand = TRUE, viewerStyle = trackViewerStyle(), |
|
9 |
- autoOptimizeStyle = FALSE, newpage = TRUE, operator = NULL, |
|
10 |
- smooth = FALSE) |
|
7 |
+viewTracks( |
|
8 |
+ trackList, |
|
9 |
+ chromosome, |
|
10 |
+ start, |
|
11 |
+ end, |
|
12 |
+ strand, |
|
13 |
+ gr = GRanges(), |
|
14 |
+ ignore.strand = TRUE, |
|
15 |
+ viewerStyle = trackViewerStyle(), |
|
16 |
+ autoOptimizeStyle = FALSE, |
|
17 |
+ newpage = TRUE, |
|
18 |
+ operator = NULL, |
|
19 |
+ smooth = FALSE |
|
20 |
+) |
|
11 | 21 |
} |
12 | 22 |
\arguments{ |
13 | 23 |
\item{trackList}{an object of \code{\link{trackList}}} |
... | ... |
@@ -962,6 +962,18 @@ ideogramPlot(ideo, dataList, |
962 | 962 |
|
963 | 963 |
# Plot genomic interactions data |
964 | 964 |
|
965 |
+Plot genomic interactions data as tracks. |
|
966 |
+ |
|
967 |
+```{r} |
|
968 |
+library(InteractionSet) |
|
969 |
+gi <- readRDS(system.file("extdata", "nij.chr6.51120000.53200000.gi.rds", package="trackViewer")) |
|
970 |
+range <- GRanges("chr6", IRanges(51120000, 53200000)) |
|
971 |
+tr <- gi2track(gi) |
|
972 |
+ctcf <- readRDS(system.file("extdata", "ctcf.sample.rds", package="trackViewer")) |
|
973 |
+viewTracks(trackList(ctcf, tr), gr=range, autoOptimizeStyle = TRUE) |
|
974 |
+``` |
|
975 |
+ |
|
976 |
+ |
|
965 | 977 |
Different from most of the available tools, plotGInteractions try to plot the data with the 2D structure. The nodes indicate the region with interactions and |
966 | 978 |
the edges indicates the interactions. The size of the nodes are relative to the width of the region. |
967 | 979 |
The features could be the enhancers, promoters or genes. The enhancer and promoter are shown as |