... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: chromstaR |
2 | 2 |
Type: Package |
3 | 3 |
Title: Combinatorial and Differential Chromatin State Analysis for ChIP-Seq Data |
4 |
-Version: 1.6.0 |
|
4 |
+Version: 1.6.1 |
|
5 | 5 |
Author: Aaron Taudt, Maria Colome Tatche, Matthias Heinig, Minh Anh Nguyen |
6 | 6 |
Maintainer: Aaron Taudt <aaron.taudt@gmail.com> |
7 | 7 |
Description: This package implements functions for combinatorial and differential analysis of ChIP-seq data. It includes uni- and multivariate peak-calling, export to genome browser viewable files, and functions for enrichment analyses. |
... | ... |
@@ -59,6 +59,7 @@ importFrom(Rsamtools,indexBam) |
59 | 59 |
importFrom(Rsamtools,scanBamFlag) |
60 | 60 |
importFrom(S4Vectors,Rle) |
61 | 61 |
importFrom(S4Vectors,as.factor) |
62 |
+importFrom(S4Vectors,endoapply) |
|
62 | 63 |
importFrom(S4Vectors,queryHits) |
63 | 64 |
importFrom(S4Vectors,runmean) |
64 | 65 |
importFrom(S4Vectors,subjectHits) |
... | ... |
@@ -1,3 +1,21 @@ |
1 |
+CHANGES IN VERSION 1.6.1 |
|
2 |
+------------------------ |
|
3 |
+ |
|
4 |
+BUGFIXES |
|
5 |
+ |
|
6 |
+ o Compatibility fixes for the new release of ggplot2 (3.0.0). |
|
7 |
+ |
|
8 |
+ o seqlevels() that are smaller than binsize are dropped properly in fixedWidthBins() and variableWidthBins(). |
|
9 |
+ |
|
10 |
+ |
|
11 |
+CHANGES IN VERSION 1.5.3 |
|
12 |
+------------------------ |
|
13 |
+ |
|
14 |
+SIGNIFICANT USER-LEVEL CHANGES |
|
15 |
+ |
|
16 |
+ o Function 'changePostCutoff()' works on univariate peak calls without posterior needing to be present. |
|
17 |
+ |
|
18 |
+ |
|
1 | 19 |
CHANGES IN VERSION 1.5.1 |
2 | 20 |
------------------------ |
3 | 21 |
|
... | ... |
@@ -241,11 +241,13 @@ binReads <- function(file, experiment.table=NULL, ID=NULL, assembly, bamindex=fi |
241 | 241 |
|
242 | 242 |
if (format == 'bam' & use.bamsignals) { |
243 | 243 |
ptm <- startTimedMessage("Counting overlaps for binsize ", binsize, " with offset ", offset, " ...") |
244 |
+ suppressWarnings( # suppress warning due to offset over seqlength |
|
244 | 245 |
bins.offset$counts <- tryCatch({ |
245 | 246 |
bins.offset$counts <- bamsignals::bamCount(file, bins.offset, mapqual=min.mapq, paired.end=paired.end, tlenFilter=c(0, max.fragment.width), verbose=FALSE) |
246 | 247 |
}, error = function(err) { |
247 | 248 |
bins.offset$counts <<- bamsignals::bamCount(file, bins.offset, mapqual=min.mapq, paired.end=paired.end, paired.end.max.frag.length=max.fragment.width, verbose=FALSE) |
248 | 249 |
}) |
250 |
+ ) |
|
249 | 251 |
stopTimedMessage(ptm) |
250 | 252 |
|
251 | 253 |
} else { |
... | ... |
@@ -6,6 +6,7 @@ |
6 | 6 |
#' @param mode Mode of combination. See \code{\link{Chromstar}} for a description of the \code{mode} parameter. |
7 | 7 |
#' @return A \code{\link{combinedMultiHMM}} objects with combinatorial states for each condition. |
8 | 8 |
#' @author Aaron Taudt |
9 |
+#' @importFrom S4Vectors endoapply |
|
9 | 10 |
#' @export |
10 | 11 |
#' @examples |
11 | 12 |
#'### Multivariate peak calling for spontaneous hypertensive rat (SHR) ### |
... | ... |
@@ -277,7 +278,7 @@ combineMultivariates <- function(hmms, mode) { |
277 | 278 |
# Reassign levels such that all conditions have the same levels |
278 | 279 |
ptm <- startTimedMessage("Reassigning levels ...") |
279 | 280 |
comblevels <- sort(unique(unlist(lapply(combs.df, levels)))) |
280 |
- combs.df <- endoapply(combs.df, function(x) { x <- factor(x, levels=comblevels) }) |
|
281 |
+ combs.df <- S4Vectors::endoapply(combs.df, function(x) { x <- factor(x, levels=comblevels) }) |
|
281 | 282 |
names(combs.df) <- paste0('combination.', names(combs.df)) |
282 | 283 |
stopTimedMessage(ptm) |
283 | 284 |
|
... | ... |
@@ -28,6 +28,8 @@ |
28 | 28 |
#' ranges=IRanges(start=genes$start, end=genes$end), |
29 | 29 |
#' strand=genes$strand, |
30 | 30 |
#' name=genes$external_gene_id, biotype=genes$gene_biotype) |
31 |
+#'# Rename chrMT to chrM |
|
32 |
+#'seqlevels(genes)[seqlevels(genes)=='chrMT'] <- 'chrM' |
|
31 | 33 |
#'print(genes) |
32 | 34 |
#' |
33 | 35 |
#'### Make the enrichment plots ### |
... | ... |
@@ -227,10 +229,12 @@ plotFoldEnrichHeatmap <- function(hmm, annotations, what="combinations", combina |
227 | 229 |
minfold <- min(unlist(minfolds), na.rm=TRUE) |
228 | 230 |
limits <- max(abs(maxfold), abs(minfold)) |
229 | 231 |
if (logscale) { |
230 |
- ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_fill_gradientn(name='log(observed/expected)', colors=grDevices::colorRampPalette(c("blue","white","red"))(20), values=c(seq(-limits,0,length.out=10), seq(0,limits,length.out=10)), rescaler=function(x,...) {x}, oob=identity, limits=c(-limits, limits)) }) |
|
232 |
+ # ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_fill_gradientn(name='log(observed/expected)', colors=grDevices::colorRampPalette(c("blue","white","red"))(20), values=c(seq(-limits,0,length.out=10), seq(0,limits,length.out=10)), rescaler=function(x,...) {x}, oob=identity, limits=c(-limits, limits)) }) # broke in ggplot2 3.0.0 |
|
233 |
+ ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_fill_gradientn(name='log(observed/expected)', colors=grDevices::colorRampPalette(c("blue","white","red"))(20), values=c(seq(-limits,0,length.out=10), seq(0,limits,length.out=10)), rescaler=function(x,...) {x}, limits=c(-limits, limits)) }) |
|
231 | 234 |
ggplts <- lapply(ggplts, function(ggplt) { ggplt$data$foldEnrichment[ggplt$data$foldEnrichment == -Inf] <- -limits; ggplt }) |
232 | 235 |
} else { |
233 |
- ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_fill_gradientn(name='observed/expected', colors=grDevices::colorRampPalette(c("blue","white","red"))(20), values=c(seq(0,1,length.out=10), seq(1,maxfold,length.out=10)), rescaler=function(x,...) {x}, oob=identity, limits=c(0,maxfold)) }) |
|
236 |
+ # ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_fill_gradientn(name='observed/expected', colors=grDevices::colorRampPalette(c("blue","white","red"))(20), values=c(seq(0,1,length.out=10), seq(1,maxfold,length.out=10)), rescaler=function(x,...) {x}, oob=identity, limits=c(0,maxfold)) }) # broke in ggplot2 3.0.0 |
|
237 |
+ ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_fill_gradientn(name='observed/expected', colors=grDevices::colorRampPalette(c("blue","white","red"))(20), values=c(seq(0,1,length.out=10), seq(1,maxfold,length.out=10)), rescaler=function(x,...) {x}, limits=c(0,maxfold)) }) |
|
234 | 238 |
} |
235 | 239 |
} |
236 | 240 |
|
... | ... |
@@ -95,11 +95,12 @@ fixedWidthBins <- function(bamfile=NULL, assembly=NULL, chrom.lengths=NULL, chro |
95 | 95 |
} |
96 | 96 |
seqlevels(bins) <- chroms2use |
97 | 97 |
seqlengths(bins) <- chrom.lengths[seqlevels(bins)] |
98 |
+ skipped.chroms <- setdiff(chromosomes, as.character(unique(seqnames(bins)))) |
|
99 |
+ bins <- dropSeqlevels(bins, skipped.chroms, pruning.mode = 'coarse') |
|
98 | 100 |
bins.list[[as.character(binsize)]] <- bins |
99 | 101 |
|
100 |
- skipped.chroms <- setdiff(chromosomes, as.character(unique(seqnames(bins)))) |
|
101 | 102 |
if (length(skipped.chroms)>0) { |
102 |
- warning("The following chromosomes were skipped because they are smaller than binsize ", binsize, ": ", paste0(skipped.chroms, collapse=', ')) |
|
103 |
+ warning("The following chromosomes were dropped because they are smaller than binsize ", binsize, ": ", paste0(skipped.chroms, collapse=', ')) |
|
103 | 104 |
} |
104 | 105 |
stopTimedMessage(ptm) |
105 | 106 |
|
... | ... |
@@ -121,6 +122,7 @@ fixedWidthBins <- function(bamfile=NULL, assembly=NULL, chrom.lengths=NULL, chro |
121 | 122 |
#' @param chromosomes A subset of chromosomes for which the bins are generated. |
122 | 123 |
#' @return A \code{list()} of \code{\link{GRanges-class}} objects with variable-width bins. |
123 | 124 |
#' @author Aaron Taudt |
125 |
+#' @importFrom S4Vectors endoapply |
|
124 | 126 |
#' @export |
125 | 127 |
#' |
126 | 128 |
#'@examples |
... | ... |
@@ -194,7 +196,7 @@ variableWidthBins <- function(reads, binsizes, chromosomes=NULL) { |
194 | 196 |
} |
195 | 197 |
} |
196 | 198 |
if (length(skipped.chroms)>0) { |
197 |
- warning("The following chromosomes were skipped because they are smaller than binsize ", binsize, ": ", paste0(skipped.chroms, collapse=', ')) |
|
199 |
+ warning("The following chromosomes were dropped because they are smaller than binsize ", binsize, ": ", paste0(skipped.chroms, collapse=', ')) |
|
198 | 200 |
} |
199 | 201 |
subreads <- unlist(subreads, use.names=FALSE) |
200 | 202 |
## Adjust length of reads to get consecutive bins |
... | ... |
@@ -205,11 +207,11 @@ variableWidthBins <- function(reads, binsizes, chromosomes=NULL) { |
205 | 207 |
end(bins) <- end(bins) + 1 |
206 | 208 |
## We don't want incomplete bins at the end |
207 | 209 |
bins.split <- split(bins, seqnames(bins)) |
208 |
- bins.split <- endoapply(bins.split, function(x) { x[-length(x)] }) |
|
210 |
+ bins.split <- S4Vectors::endoapply(bins.split, function(x) { x[-length(x)] }) |
|
209 | 211 |
bins <- unlist(bins.split, use.names=FALSE) |
210 | 212 |
## Remove skipped chromosomes |
211 | 213 |
bins <- bins[!seqnames(bins) %in% skipped.chroms] |
212 |
- bins <- keepSeqlevels(bins, setdiff(seqlevels(bins), skipped.chroms)) |
|
214 |
+ bins <- dropSeqlevels(bins, skipped.chroms, pruning.mode = 'coarse') |
|
213 | 215 |
|
214 | 216 |
bins.list[[as.character(binsize)]] <- bins |
215 | 217 |
stopTimedMessage(ptm) |
... | ... |
@@ -87,6 +87,8 @@ genes <- GRanges(seqnames=paste0('chr',genes$chromosome_name), |
87 | 87 |
ranges=IRanges(start=genes$start, end=genes$end), |
88 | 88 |
strand=genes$strand, |
89 | 89 |
name=genes$external_gene_id, biotype=genes$gene_biotype) |
90 |
+# Rename chrMT to chrM |
|
91 |
+seqlevels(genes)[seqlevels(genes)=='chrMT'] <- 'chrM' |
|
90 | 92 |
print(genes) |
91 | 93 |
|
92 | 94 |
### Make the enrichment plots ### |
... | ... |
@@ -389,7 +389,10 @@ genes <- GRanges(seqnames=paste0('chr',genes$chromosome_name), |
389 | 389 |
ranges=IRanges(start=genes$start, end=genes$end), |
390 | 390 |
strand=genes$strand, |
391 | 391 |
name=genes$external_gene_id, biotype=genes$gene_biotype) |
392 |
+# Rename chrMT to chrM to avoid warnings |
|
392 | 393 |
seqlevels(genes)[seqlevels(genes)=='chrMT'] <- 'chrM' |
394 |
+# Select only chr12 to avoid warnings |
|
395 |
+genes <- keepSeqlevels(genes, 'chr12', pruning.mode = 'coarse') |
|
393 | 396 |
print(genes) |
394 | 397 |
@ |
395 | 398 |
|
... | ... |
@@ -447,6 +450,7 @@ expression.SHR <- GRanges(seqnames=paste0('chr',expr$chromosome_name), |
447 | 450 |
strand=expr$strand, name=expr$external_gene_id, |
448 | 451 |
biotype=expr$gene_biotype, |
449 | 452 |
expression=expr$expression_SHR) |
453 |
+# Rename chrMT to chrM to avoid warnings |
|
450 | 454 |
seqlevels(expression.SHR)[seqlevels(expression.SHR)=='chrMT'] <- 'chrM' |
451 | 455 |
# We apply an asinh transformation to reduce the effect of outliers |
452 | 456 |
expression.SHR$expression <- asinh(expression.SHR$expression) |
... | ... |
@@ -546,7 +550,10 @@ genes <- GRanges(seqnames=paste0('chr',genes$chromosome_name), |
546 | 550 |
ranges=IRanges(start=genes$start, end=genes$end), |
547 | 551 |
strand=genes$strand, |
548 | 552 |
name=genes$external_gene_id, biotype=genes$gene_biotype) |
553 |
+# Rename chrMT to chrM to avoid warnings |
|
549 | 554 |
seqlevels(genes)[seqlevels(genes)=='chrMT'] <- 'chrM' |
555 |
+# Select only chr12 to avoid warnings |
|
556 |
+genes <- keepSeqlevels(genes, 'chr12', pruning.mode = 'coarse') |
|
550 | 557 |
print(genes) |
551 | 558 |
@ |
552 | 559 |
|