trackViewer 1.16.1
There are two packages available in Bioconductor for visualizing genomic data: rtracklayer and Gviz. rtracklayer provides an interface to genome browsers and associated annotation tracks. Gviz plots data and annotation information along genomic coordinates. TrackViewer is a light-weighted visualization tool for generating neat figures for publication. It utilizes Gviz, is easy to use, and has a low memory and cpu consumption.
library(Gviz)
library(rtracklayer)
library(trackViewer)
extdata <- system.file("extdata", package="trackViewer",
                       mustWork=TRUE)
gr <- GRanges("chr11", IRanges(122929275, 122930122), strand="-")
fox2 <- importScore(file.path(extdata, "fox2.bed"), format="BED",
                    ranges=gr)
fox2$dat <- coverageGR(fox2$dat)
viewTracks(trackList(fox2), gr=gr, autoOptimizeStyle=TRUE, newpage=FALSE)
dt <- DataTrack(range=fox2$dat[strand(fox2$dat)=="-"] , 
                genome="hg19", type="hist", name="fox2", 
                window=-1, chromosome="chr11", 
                fill.histogram="black", col.histogram="NA",
                background.title="white",
                col.frame="white", col.axis="black",
                col="black", col.title="black")
plotTracks(dt, from=122929275, to=122930122, strand="-")
Figure 1: Plot data with Gviz and trackViewer
 Note that trackViewer can generate similar figure as Gviz with several lines of simple codes.
TrackViewer not only has the functionalities to plot the figures generated by Gviz, as shown in Figure above, but also provides additional plotting styles as shown in Figure below. The mimimalist design requires minimum input from users while retaining the flexibility to change output style easily.
gr <- GRanges("chr1", IRanges(c(1, 6, 10), c(3, 6, 12)), score=c(3, 4, 1))
dt <- DataTrack(range=gr, data="score", type="hist")
plotTracks(dt, from=2, to=11)
tr <- new("track", dat=gr, type="data", format="BED")
viewTracks(trackList(tr), chromosome="chr1", start=2, end=11)
Figure 2: Plot data with Gviz and trackViewer
 Note that trackViewer is not only including more details but also showing all the data involved in the given range.
It requires huge memory space to handle big wig files. To solve this problem, trackViewer rewrote the import function to import whole file first and parse it later when plot. trackViewer provides higher import speed (21 min vs. over 180 min) and acceptable memory cost (5.32G vs. over 10G) for a half giga wig file (GSM917672) comparing to Gviz.
Function importScore is used to import BED, WIG, bedGraph or BigWig files. Function importBam is employed to import bam file. Here is the example.
library(trackViewer)
extdata <- system.file("extdata", package="trackViewer",
                       mustWork=TRUE)
repA <- importScore(file.path(extdata, "cpsf160.repA_-.wig"),
                    file.path(extdata, "cpsf160.repA_+.wig"),
                    format="WIG")
## because the wig file does not contain strand info, 
## we need to set it manually
strand(repA$dat) <- "-"
strand(repA$dat2) <- "+"Function coverageGR could be used to calculate coverage after importing if needed.
fox2 <- importScore(file.path(extdata, "fox2.bed"), format="BED",
                    ranges=GRanges("chr11", IRanges(122929000, 122931000)))
dat <- coverageGR(fox2$dat)
## we can split the data by strand into two different track channels
## here we set the dat2 slot to save the negative strand info, 
## reverse order as previous. 
fox2$dat <- dat[strand(dat)=="+"]
fox2$dat2 <- dat[strand(dat)=="-"]The gene model can be built for a given genomic range using geneModelFromTxdb function which uses TranscriptDb object as input.
library(TxDb.Hsapiens.UCSC.hg19.knownGene)
library(org.Hs.eg.db)
gr <- GRanges("chr11", IRanges(122929275, 122930122), strand="-")
trs <- geneModelFromTxdb(TxDb.Hsapiens.UCSC.hg19.knownGene,
                         org.Hs.eg.db,
                         gr=gr)Use viewTracks function to plot data and annotation information along genomic coordinates. addGuideLine or addArrowMark can be used to highlight the peaks.
viewerStyle <- trackViewerStyle()
setTrackViewerStyleParam(viewerStyle, "margin", c(.1, .05, .02, .02))
vp <- viewTracks(trackList(repA, fox2, trs), 
                 gr=gr, viewerStyle=viewerStyle, 
                 autoOptimizeStyle=TRUE)
addGuideLine(c(122929767, 122929969), vp=vp)
addArrowMark(list(x=122929650, 
                  y=2), # 2 means track 2 from bottom.
             label="label",
             col="blue",
             vp=vp)
Figure 3: plot data and annotation information along genomic coordinates
In most cases, researchers are interested in the relative position of peaks in the gene. Sometimes, margin needs to be adjusted to be able to show the entire gene model. Figure below shows how to add an x-scale and remove x-axis using addGuideLine Function .
optSty <- optimizeStyle(trackList(repA, fox2, trs))
trackList <- optSty$tracks
viewerStyle <- optSty$stylesetTrackViewerStyleParam(viewerStyle, "xaxis", FALSE)
setTrackViewerStyleParam(viewerStyle, "margin", c(.01, .05, .01, .01))
setTrackXscaleParam(trackList[[1]], "draw", TRUE)
setTrackXscaleParam(trackList[[1]], "gp", list(cex=.5))
viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
Figure 4: plot data with x-scale
y-axis can be put to right side of the track by setting main slot to FALSE in y-axis slot of each track. And ylim can be set by setTrackStyleParam.
setTrackViewerStyleParam(viewerStyle, "margin", c(.01, .05, .01, .05))
for(i in 1:2){
    setTrackYaxisParam(trackList[[i]], "main", FALSE)
}
## adjust y scale
setTrackStyleParam(trackList[[1]], "ylim", c(0, 25))
setTrackStyleParam(trackList[[2]], "ylim", c(-25, 0))
viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
Figure 5: plot data with y-axis in right side
Y label style can be changed by setting the ylabgp slot in style of each track.
setTrackStyleParam(trackList[[1]], "ylabgp", list(cex=.8, col="green"))
## set cex to avoid automatic adjust
setTrackStyleParam(trackList[[2]], "ylabgp", list(cex=.8, col="blue"))
setTrackStyleParam(trackList[[2]], "marginBottom", .2)
viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
Figure 6: plot data with adjusted color and size of y label
Y label can be also put to top or bottom of each track.
setTrackStyleParam(trackList[[1]], "ylabpos", "bottomleft")
setTrackStyleParam(trackList[[2]], "ylabpos", "topright")
setTrackStyleParam(trackList[[2]], "marginTop", .2)
viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
Figure 7: plot data with adjusted y label position
For each transcript, the transcript name can be put to upstream or downstream of the transcript.
trackListN <- trackList
setTrackStyleParam(trackListN[[3]], "ylabpos", "upstream")
setTrackStyleParam(trackListN[[4]], "ylabpos", "downstream")
## set cex to avoid automatic adjust
setTrackStyleParam(trackListN[[3]], "ylabgp", list(cex=.6))
setTrackStyleParam(trackListN[[4]], "ylabgp", list(cex=.6))
gr1 <- range(unlist(GRangesList(sapply(trs, function(.ele) .ele$dat))))
start(gr1) <- start(gr1) - 2000
end(gr1) <- end(gr1) + 2000
viewTracks(trackListN, gr=gr1, viewerStyle=viewerStyle)
Figure 8: plot data with adjusted transcripts name position
The track color can be changed by setting the color slot in style of each track. The first color is for dat slot of track and seconde color is for dat2 slot.
setTrackStyleParam(trackList[[1]], "color", c("green", "black"))
setTrackStyleParam(trackList[[2]], "color", c("black", "blue"))
for(i in 3:length(trackList)) 
    setTrackStyleParam(trackList[[i]], "color", "black")
viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
Figure 9: plot data with adjusted track color
The track height can be changed by setting the height slot in style of each track. However, the total height for all the tracks should be 1.
trackListH <- trackList
setTrackStyleParam(trackListH[[1]], "height", .1)
setTrackStyleParam(trackListH[[2]], "height", .44)
for(i in 3:length(trackListH)){
    setTrackStyleParam(trackListH[[i]], "height", 
                       (1-(0.1+0.44))/(length(trackListH)-2))
}
viewTracks(trackListH, gr=gr, viewerStyle=viewerStyle)
Figure 10: plot data with adjusted track height
The track names such as gene model names can also be edited easily by changing the names of trackList.
names(trackList) <- c("cpsf160", "fox2", rep("HSPA8", 5))
viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
Figure 11: change the track names
trackViewer can be used to show to-be-compared data in the same track side by side.
cpsf160 <- importScore(file.path(extdata, "cpsf160.repA_-.wig"),
                       file.path(extdata, "cpsf160.repB_-.wig"),
                       format="WIG")
strand(cpsf160$dat) <- strand(cpsf160$dat2) <- "-"
setTrackStyleParam(cpsf160, "color", c("black", "red"))
viewTracks(trackList(trs, cpsf160), gr=gr, viewerStyle=viewerStyle)
Figure 12: show two data in the same track
The x-axis can be horizotally flipped for the genes in negative strand.
viewerStyleF <- viewerStyle
setTrackViewerStyleParam(viewerStyleF, "flip", TRUE)
setTrackViewerStyleParam(viewerStyleF, "xaxis", TRUE)
setTrackViewerStyleParam(viewerStyleF, "margin", c(.1, .05, .01, .01))
vp <- viewTracks(trackList, gr=gr, viewerStyle=viewerStyleF)
addGuideLine(c(122929767, 122929969), vp=vp)
addArrowMark(list(x=122929650,
                  y=2),
             label="label",
             col="blue",
             vp=vp)
Figure 13: show data in the flipped track
We support two themes now: bw and col.
optSty <- optimizeStyle(trackList(repA, fox2, trs), theme="bw")
trackList <- optSty$tracks
viewerStyle <- optSty$style
vp <- viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)(#fig:theme_bw)theme_bw
optSty <- optimizeStyle(trackList(repA, fox2, trs), theme="col")
trackList <- optSty$tracks
viewerStyle <- optSty$style
vp <- viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)(#fig:theme_col)theme_col
We could plot the tracks with breaks by set multiple genomic ranges.
gr.breaks <- GRanges("chr11", 
                     IRanges(c(122929275, 122929575, 122929775), 
                             c(122929555, 122929725, 122930122)), 
                     strand="-", percentage=c(.4, .2, .4))
vp <- viewTracks(trackList, gr=gr.breaks, viewerStyle=viewerStyle)(#fig:axis.break)axis.break
To change the parameter may be complicated for users.
Users may want to have a try function browseTracks.
browseTracks(trackList, gr=gr)
Figure 14: browseTrack
If there are two tracks and we want to draw the two track by adding or substract one from another, we can try operators.
newtrack <- repA
## must keep same format for dat and dat2
newtrack <- parseWIG(newtrack, "chr11", 122929275, 122930122)
newtrack$dat2 <- newtrack$dat
newtrack$dat <- fox2$dat2
setTrackStyleParam(newtrack, "color", c("blue", "red"))
viewTracks(trackList(newtrack, trs), 
           gr=gr, viewerStyle=viewerStyle, operator="+")
Figure 15: show data with operator “+”
viewTracks(trackList(newtrack, trs), gr=gr, viewerStyle=viewerStyle, operator="-")
Figure 16: show data with operator “-”
Or try GRoperator before view tracks.
newtrack$dat <- GRoperator(newtrack$dat, newtrack$dat2, col="score", operator="-")
newtrack$dat2 <- GRanges()
viewTracks(trackList(newtrack, trs), gr=gr, viewerStyle=viewerStyle)
Figure 17: show data with operator “-”
Lolliplot is a mutation distribution graphics tool.
SNP <- c(10, 12, 1400, 1402)
sample.gr <- GRanges("chr1", IRanges(SNP, width=1, names=paste0("snp", SNP)))
features <- GRanges("chr1", IRanges(c(1, 501, 1001), 
                                    width=c(120, 400, 405),
                                    names=paste0("block", 1:3)))
lolliplot(sample.gr, features)## more SNPs
SNP <- c(10, 100, 105, 108, 400, 410, 420, 600, 700, 805, 840, 1400, 1402)
sample.gr <- GRanges("chr1", IRanges(SNP, width=1, names=paste0("snp", SNP)))
lolliplot(sample.gr, features)## define the range
lolliplot(sample.gr, features, ranges = GRanges("chr1", IRanges(104, 109)))features$fill <- c("#FF8833", "#51C6E6", "#DFA32D")
lolliplot(sample.gr, features)sample.gr$color <- sample.int(6, length(SNP), replace=TRUE)
sample.gr$border <- sample(c("gray80", "gray30"), length(SNP), replace=TRUE)
lolliplot(sample.gr, features)sample.gr$label <- as.character(1:length(sample.gr))
sample.gr$label.col <- "white"
lolliplot(sample.gr, features)features$height <- c(0.02, 0.05, 0.08)
lolliplot(sample.gr, features)## keep the height by giving the unit
features$height <- list(unit(1/16, "inches"), 
                     unit(3, "mm"), 
                     unit(12, "points"))
lolliplot(sample.gr, features)The metadata ‘featureLayerID’ are used for drawing features in different layers.
features.mul <- rep(features, 2)
features.mul$height[4:6] <- list(unit(1/8, "inches"),
                                 unit(0.5, "lines"),
                                 unit(.2, "char"))
features.mul$fill <- c("#FF8833", "#F9712A", "#DFA32D", 
                       "#51C6E6", "#009DDA", "#4B9CDF")
end(features.mul)[5] <- end(features.mul[5])+50
features.mul$featureLayerID <- 
    paste("tx", rep(1:2, each=length(features)), sep="_")
names(features.mul) <- 
    paste(features.mul$featureLayerID, 
          rep(1:length(features), 2), sep="_")
lolliplot(sample.gr, features.mul)## one name per transcripts
names(features.mul) <- features.mul$featureLayerID
lolliplot(sample.gr, features.mul)#Note: the score value is integer less than 10
sample.gr$score <- sample.int(5, length(sample.gr), replace = TRUE)
lolliplot(sample.gr, features)##remove yaxis
lolliplot(sample.gr, features, yaxis=FALSE)#Try score value greater than 10
sample.gr$score <- sample.int(20, length(sample.gr), replace=TRUE)
lolliplot(sample.gr, features)#Try float numeric score
sample.gr$score <- runif(length(sample.gr))*10
lolliplot(sample.gr, features)# score should not be smaller than 1xaxis <- c(1, 200, 400, 701, 1000, 1200, 1402) ## define the position
lolliplot(sample.gr, features, xaxis=xaxis)names(xaxis) <- xaxis # define the labels
names(xaxis)[4] <- "center" 
lolliplot(sample.gr, features, xaxis=xaxis)yaxis <- c(0, 5) ## define the position
lolliplot(sample.gr, features, yaxis=yaxis)yaxis <- c(0, 5, 10, 15)
names(yaxis) <- yaxis # define the labels
names(yaxis)[3] <- "yaxis" 
lolliplot(sample.gr, features, yaxis=yaxis)sample.gr$dashline.col <- sample.gr$color
lolliplot(sample.gr, features, jitter="label")legend <- 1:6 ## legend fill color
names(legend) <- paste0("legend", letters[1:6]) ## legend labels
lolliplot(sample.gr, features, legend=legend)## use list to define more attributes. see ?grid::gpar to get more details.
legend <- list(labels=paste0("legend", LETTERS[1:6]), 
               col=palette()[6:1], 
               fill=palette()[legend])
lolliplot(sample.gr, features, legend=legend)## if you have multiple tracks, try to set the legend by list.
## see more in section [Plot multiple samples](#plot-multiple-samples)
legend <- list(legend)
lolliplot(sample.gr, features, legend=legend)Use can control the paramters of labels by name the metadata start as
label.parameter.
sample.gr.rot <- sample.gr
sample.gr.rot$label.parameter.rot <- 45
lolliplot(sample.gr.rot, features, legend=legend)sample.gr.rot$label.parameter.rot <- 60
sample.gr.rot$label.parameter.gp <- gpar(col="brown")
lolliplot(sample.gr.rot, features, legend=legend)If you want to change the text in ylab, please try to set the labels in ylab. lolliplot does not support the parameters for title and xlab. If you want to add title and xlab, please try to add them by .
lolliplot(sample.gr.rot, features, legend=legend, ylab="y label here")
grid.text("x label here", x=.5, y=.01, just="bottom")
grid.text("title here", x=.5, y=.98, just="top", 
          gp=gpar(cex=1.5, fontface="bold"))lolliplot(sample.gr, features, type="pin")sample.gr$color <- lapply(sample.gr$color, function(.ele) c(.ele, sample.int(6, 1)))
sample.gr$border <- sample.int(6, length(SNP), replace=TRUE)
lolliplot(sample.gr, features, type="pin")sample.gr$score <- NULL ## must be removed, because pie will consider all the numeric columns except column "color", "fill", "lwd", "id" and "id.col".
sample.gr$label <- NULL
sample.gr$label.col <- NULL
x <- sample.int(100, length(SNP))
sample.gr$value1 <- x
sample.gr$value2 <- 100 - x
## the length of color should be no less than the values number
sample.gr$color <- rep(list(c("#87CEFA", '#98CE31')), length(SNP))
sample.gr$border <- "gray30"
lolliplot(sample.gr, features, type="pie")SNP2 <- sample(4000:8000, 30)
x2 <- sample.int(100, length(SNP2), replace=TRUE)
sample2.gr <- GRanges("chr3", IRanges(SNP2, width=1, names=paste0("snp", SNP2)), 
             value1=x2, value2=100-x2)
sample2.gr$color <- rep(list(c('#DB7575', '#FFD700')), length(SNP2))
sample2.gr$border <- "gray30"
features2 <- GRanges("chr3", IRanges(c(5001, 5801, 7001), 
                                    width=c(500, 500, 405),
                                    names=paste0("block", 4:6)),
                    fill=c("orange", "gray30", "lightblue"),
                    height=unit(c(0.5, 0.3, 0.8), "cm"))
legends <- list(list(labels=c("WT", "MUT"), fill=c("#87CEFA", '#98CE31')), 
                list(labels=c("WT", "MUT"), fill=c('#DB7575', '#FFD700')))
lolliplot(list(A=sample.gr, B=sample2.gr), 
          list(x=features, y=features2), 
          type="pie", legend=legends)Different layouts are also be possible.
sample2.gr$score <- sample2.gr$value1 ## circle layout need score column 
lolliplot(list(A=sample.gr, B=sample2.gr), 
          list(x=features, y=features2), 
          type=c("pie", "circle"), legend=legends)rand.id <- sample.int(length(sample.gr), 3*length(sample.gr), replace=TRUE)
rand.id <- sort(rand.id)
sample.gr.mul.patient <- sample.gr[rand.id]
## pie.stack require metadata "stack.factor", and the metadata can not be 
## stack.factor.order or stack.factor.first
len.max <- max(table(rand.id))
stack.factors <- paste0("patient", formatC(1:len.max, 
                                           width=nchar(as.character(len.max)), 
                                           flag="0"))
sample.gr.mul.patient$stack.factor <- 
    unlist(lapply(table(rand.id), sample, x=stack.factors))
sample.gr.mul.patient$value1 <- 
    sample.int(100, length(sample.gr.mul.patient), replace=TRUE)
sample.gr.mul.patient$value2 <- 100 - sample.gr.mul.patient$value1
patient.color.set <- as.list(as.data.frame(rbind(rainbow(length(stack.factors)), 
                                                 "#FFFFFFFF"), 
                                           stringsAsFactors=FALSE))
names(patient.color.set) <- stack.factors
sample.gr.mul.patient$color <- 
    patient.color.set[sample.gr.mul.patient$stack.factor]
legend <- list(labels=stack.factors, col="gray80", 
               fill=sapply(patient.color.set, `[`, 1))
lolliplot(sample.gr.mul.patient, features, type="pie.stack", 
          legend=legend, dashline.col="gray")Metadata SNPsideID is used to trigger caterpillar layout. SNPsideID must be ‘top’ or ‘bottom’.
sample.gr$SNPsideID <- sample(c("top", "bottom"), 
                               length(sample.gr),
                               replace=TRUE)
lolliplot(sample.gr, features, type="pie", 
          legend=legends[[1]])## two layers
sample2.gr$SNPsideID <- "top"
idx <- sample.int(length(sample2.gr), 15)
sample2.gr$SNPsideID[idx] <- "bottom"
sample2.gr$color[idx] <- '#FFD700'
lolliplot(list(A=sample.gr, B=sample2.gr), 
          list(x=features.mul, y=features2), 
          type=c("pie", "circle"), legend=legends)library(VariantAnnotation)
library(TxDb.Hsapiens.UCSC.hg19.knownGene)
library(org.Hs.eg.db)
fl <- system.file("extdata", "chr22.vcf.gz", package="VariantAnnotation")
gr <- GRanges("22", IRanges(50968014, 50970514, names="TYMP"))
tab <- TabixFile(fl)
vcf <- readVcf(fl, "hg19", param=gr)
mutation.frequency <- rowRanges(vcf)
mcols(mutation.frequency) <- cbind(mcols(mutation.frequency), 
                                   VariantAnnotation::info(vcf))
mutation.frequency$border <- "gray30"
mutation.frequency$color <- 
    ifelse(grepl("^rs", names(mutation.frequency)), "lightcyan", "lavender")
## plot Global Allele Frequency based on AC/AN
mutation.frequency$score <- mutation.frequency$AF*100
seqlevelsStyle(gr) <- seqlevelsStyle(mutation.frequency) <- "UCSC" 
trs <- geneModelFromTxdb(TxDb.Hsapiens.UCSC.hg19.knownGene,
                         org.Hs.eg.db,
                         gr=gr)
features <- c(range(trs[[1]]$dat), range(trs[[5]]$dat))
names(features) <- c(trs[[1]]$name, trs[[5]]$name)
features$fill <- c("lightblue", "mistyrose")
features$height <- c(.02, .04)
lolliplot(mutation.frequency, features, ranges=gr)library(rtracklayer)
session <- browserSession()
query <- ucscTableQuery(session, track="HAIB Methyl RRBS", 
                        range=GRangesForUCSCGenome("hg19", seqnames(gr), ranges(gr)))
tableName(query) <- tableNames(query)[1]
methy <- track(query)
methy <- GRanges(methy)lolliplot(methy, features, ranges=gr, type="pin")In above sample, some of the nodes overlap each other. To change the node size, cex prameter could be used.
methy$lwd <- .5
lolliplot(methy, features, ranges=gr, type="pin", cex=.5)lolliplot(methy, features, ranges=gr, type="circle", cex=.5)methy$score2 <- max(methy$score) - methy$score
lolliplot(methy, features, ranges=gr, type="pie", cex=.5)## we can change it one by one
methy$cex <- runif(length(methy))
lolliplot(methy, features, ranges=gr, type="pin")lolliplot(methy, features, ranges=gr, type="circle")In above samples, some of the nodes are moved too far from the original coordinates. To rescale the xaxis could be used.
methy$cex <- 1
lolliplot(methy, features, ranges=gr, rescale = TRUE)rescale <- data.frame(
  from.start = c(50968014, 50968515, 50968838), 
  from.end   = c(50968514, 50968837, 50970514),
  to.start   = c(50968014, 50968838, 50969501), 
  to.end     = c(50968837, 50969500, 50970514)
)
xaxis <- c(50968014, 50968514, 50968710, 50968838, 50970514)
lolliplot(methy, features, ranges=gr, type="pin",
          rescale = rescale, xaxis = xaxis)Sometimes, there are too many SNPs invoved in one gene. If you want to plot such as more than handred SNPs, Dandelion plot may be the good chioce. Please note, the height of the dandelion means the desity of the SNPs.
dandelion.plot(methy, features, ranges=gr, type="pin")There are one more type for dandelion plot, type “fan”. The area of the fan indicate the percentage of methylation or rate of mutation.
methy$color <- 3
methy$border <- "gray"
## score info is required, the score must be a number in [0, 1]
m <- max(methy$score)
methy$score <- methy$score/m
dandelion.plot(methy, features, ranges=gr, type="fan")methy$color <- rep(list(c(3, 5)), length(methy))
methy$score2 <- methy$score2/m
legends <- list(list(labels=c("s1", "s2"), fill=c(3, 5)))
dandelion.plot(methy, features, ranges=gr, type="pie", legend=legends)## want less
dandelion.plot(methy, features, ranges=gr, type="circle", maxgaps=1/10)## want more
dandelion.plot(methy, features, ranges=gr, type="circle", maxgaps=1/100)gene <- geneTrack(get("HSPA8", org.Hs.egSYMBOL2EG), TxDb.Hsapiens.UCSC.hg19.knownGene)[[1]]
SNPs <- GRanges("chr11", IRanges(sample(122929275:122930122, size = 20), width = 1), strand="-")
SNPs$score <- sample.int(5, length(SNPs), replace = TRUE)
SNPs$color <- sample.int(6, length(SNPs), replace=TRUE)
SNPs$border <- "gray80"
SNPs$feature.height = .1
SNPs$cex <- .5
gene$dat2 <- SNPs
optSty <- optimizeStyle(trackList(repA, fox2, gene), theme="col")
trackList <- optSty$tracks
viewerStyle <- optSty$style
gr <- GRanges("chr11", IRanges(122929275, 122930122))
setTrackStyleParam(trackList[[3]], "ylabgp", list(cex=.8))
vp <- viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)## lollipopData track
SNPs2 <- GRanges("chr11", IRanges(sample(122929275:122930122, size = 30), width = 1), strand="-")
SNPs2 <- c(SNPs2, promoters(gene$dat, upstream = 0, downstream = 1))
SNPs2$score <- sample.int(3, length(SNPs2), replace = TRUE)
SNPs2$color <- sample.int(6, length(SNPs2), replace=TRUE)
SNPs2$border <- "gray30"
SNPs2$feature.height = .1
SNPs2$cex <- .5
SNPs$cex <- .5
lollipopData <- new("track", dat=SNPs, dat2=SNPs2, type="lollipopData")
gene <- geneTrack(get("HSPA8", org.Hs.egSYMBOL2EG), TxDb.Hsapiens.UCSC.hg19.knownGene)[[1]]
optSty <- optimizeStyle(trackList(repA, lollipopData, gene, heightDist = c(3, 3, 1)), theme="col")
trackList <- optSty$tracks
viewerStyle <- optSty$style
gr <- GRanges("chr11", IRanges(122929275, 122930122))
setTrackStyleParam(trackList[[2]], "ylabgp", list(cex=.8))
vp <- viewTracks(trackList, gr=gr, viewerStyle=viewerStyle)
addGuideLine(122929538, vp=vp)Plot ideograms with data.
ideo <- loadIdeogram("hg38")dataList <- ideo
dataList$score <- as.numeric(dataList$gieStain)
dataList <- dataList[dataList$gieStain!="gneg"]
dataList <- GRangesList(dataList)
ideogramPlot(ideo, dataList, 
            layout=list("chr1", c("chr3", "chr22"), 
                        c("chr4", "chr21")))Plot GInteractions. Different from most of the available tools, plotGInteractions try to plot the data with 2D structure. The nodes indicate the region with interactions and the edges indicates the interactions. The size of the nodes are relative to the width of the region. The features could be enhancer, promoter or gene. The enhancer and promoter are shown as points with symbol 11 and 13.
library(TxDb.Hsapiens.UCSC.hg19.knownGene)
library(InteractionSet)
gi <- readRDS(system.file("extdata", "gi.rds", package="trackViewer"))
range <- GRanges("chr2", IRanges(234500000, 235000000))
feature.gr <- genes(TxDb.Hsapiens.UCSC.hg19.knownGene)
feature.gr <- subsetByOverlaps(feature.gr, regions(gi))
feature.gr$col <- sample(1:7, length(feature.gr), replace=TRUE)
feature.gr$type <- sample(c("promoter", "enhancer", "gene"), 
                          length(feature.gr), replace=TRUE, 
                          prob=c(0.1, 0.2, 0.7))
plotGInteractions(gi, range, feature.gr)sessionInfo()R version 3.5.1 Patched (2018-07-12 r74967) Platform: x86_64-pc-linux-gnu (64-bit) Running under: Ubuntu 16.04.5 LTS
Matrix products: default BLAS: /home/biocbuild/bbs-3.7-bioc/R/lib/libRblas.so LAPACK: /home/biocbuild/bbs-3.7-bioc/R/lib/libRlapack.so
locale:
[1] LC_CTYPE=en_US.UTF-8 LC_NUMERIC=C
[3] LC_TIME=en_US.UTF-8 LC_COLLATE=C
[5] LC_MONETARY=en_US.UTF-8 LC_MESSAGES=en_US.UTF-8
[7] LC_PAPER=en_US.UTF-8 LC_NAME=C
[9] LC_ADDRESS=C LC_TELEPHONE=C
[11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C
attached base packages:
[1] grid parallel stats4 stats graphics grDevices utils
[8] datasets methods base
other attached packages:
[1] InteractionSet_1.8.0
[2] VariantAnnotation_1.26.1
[3] Rsamtools_1.32.3
[4] Biostrings_2.48.0
[5] XVector_0.20.0
[6] SummarizedExperiment_1.10.1
[7] DelayedArray_0.6.6
[8] BiocParallel_1.14.2
[9] matrixStats_0.54.0
[10] org.Hs.eg.db_3.6.0
[11] TxDb.Hsapiens.UCSC.hg19.knownGene_3.2.2
[12] GenomicFeatures_1.32.2
[13] AnnotationDbi_1.42.1
[14] Biobase_2.40.0
[15] Gviz_1.24.0
[16] rtracklayer_1.40.6
[17] trackViewer_1.16.1
[18] GenomicRanges_1.32.7
[19] GenomeInfoDb_1.16.0
[20] IRanges_2.14.12
[21] S4Vectors_0.18.3
[22] BiocGenerics_0.26.0
[23] BiocStyle_2.8.2
loaded via a namespace (and not attached):
[1] ProtGenerics_1.12.0 bitops_1.0-6
[3] bit64_0.9-7 RColorBrewer_1.1-2
[5] progress_1.2.0 httr_1.3.1
[7] rprojroot_1.3-2 Rgraphviz_2.24.0
[9] tools_3.5.1 backports_1.1.2
[11] R6_2.2.2 rpart_4.1-13
[13] Hmisc_4.1-1 DBI_1.0.0
[15] lazyeval_0.2.1 colorspace_1.3-2
[17] nnet_7.3-12 tidyselect_0.2.4
[19] gridExtra_2.3 prettyunits_1.0.2
[21] curl_3.2 bit_1.1-14
[23] compiler_3.5.1 graph_1.58.0
[25] htmlTable_1.12 grImport_0.9-1
[27] bookdown_0.7 scales_1.0.0
[29] checkmate_1.8.5 stringr_1.3.1
[31] digest_0.6.17 foreign_0.8-71
[33] rmarkdown_1.10 base64enc_0.1-3
[35] dichromat_2.0-0 pkgconfig_2.0.2
[37] htmltools_0.3.6 plotrix_3.7-3
[39] highr_0.7 ensembldb_2.4.1
[41] BSgenome_1.48.0 htmlwidgets_1.2
[43] rlang_0.2.2 rstudioapi_0.7
[45] RSQLite_2.1.1 bindr_0.1.1
[47] jsonlite_1.5 acepack_1.4.1
[49] dplyr_0.7.6 RCurl_1.95-4.11
[51] magrittr_1.5 GenomeInfoDbData_1.1.0
[53] Formula_1.2-3 Matrix_1.2-14
[55] Rcpp_0.12.18 munsell_0.5.0
[57] stringi_1.2.4 yaml_2.2.0
[59] zlibbioc_1.26.0 plyr_1.8.4
[61] blob_1.1.1 crayon_1.3.4
[63] lattice_0.20-35 splines_3.5.1
[65] hms_0.4.2 knitr_1.20
[67] pillar_1.3.0 biomaRt_2.36.1
[69] XML_3.98-1.16 glue_1.3.0
[71] evaluate_0.11 biovizBase_1.28.2
[73] latticeExtra_0.6-28 data.table_1.11.6
[75] gtable_0.2.0 purrr_0.2.5
[77] assertthat_0.2.0 ggplot2_3.0.0
[79] xfun_0.3 AnnotationFilter_1.4.0
[81] survival_2.42-6 tibble_1.4.2
[83] GenomicAlignments_1.16.0 memoise_1.1.0
[85] bindrcpp_0.2.2 cluster_2.0.7-1