3 | 3 |
old mode 100644 |
4 | 4 |
new mode 100755 |
... | ... |
@@ -7,7 +7,7 @@ Author: Aaron Taudt, Maria Colome Tatche, Matthias Heinig, Minh Anh Nguyen |
7 | 7 |
Maintainer: Aaron Taudt <aaron.taudt@gmail.com> |
8 | 8 |
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. |
9 | 9 |
Depends: |
10 |
- R (>= 3.2.0), |
|
10 |
+ R (>= 3.3.0), |
|
11 | 11 |
GenomicRanges, |
12 | 12 |
ggplot2, |
13 | 13 |
chromstaRData |
26 | 26 |
old mode 100644 |
27 | 27 |
new mode 100755 |
... | ... |
@@ -49,7 +49,7 @@ |
49 | 49 |
#'## Check if the fit is ok |
50 | 50 |
#'plot(hmm, type='histogram') |
51 | 51 |
#' |
52 |
-callPeaksUnivariate <- function(binned.data, input.data=NULL, prefit.on.chr=NULL, short=TRUE, eps=0.01, init="standard", max.time=NULL, max.iter=5000, num.trials=1, eps.try=NULL, num.threads=1, read.cutoff=TRUE, read.cutoff.quantile=1, read.cutoff.absolute=500, max.mean=Inf, post.cutoff=0.5, control=FALSE, keep.posteriors=FALSE, keep.densities=FALSE, verbosity=1) { |
|
52 |
+callPeaksUnivariate <- function(binned.data, input.data=NULL, prefit.on.chr=NULL, short=TRUE, eps=0.1, init="standard", max.time=NULL, max.iter=5000, num.trials=1, eps.try=NULL, num.threads=1, read.cutoff=TRUE, read.cutoff.quantile=1, read.cutoff.absolute=500, max.mean=Inf, post.cutoff=0.5, control=FALSE, keep.posteriors=FALSE, keep.densities=FALSE, verbosity=1) { |
|
53 | 53 |
|
54 | 54 |
if (class(binned.data) == 'character') { |
55 | 55 |
message("Loading file ",binned.data) |
... | ... |
@@ -426,7 +426,7 @@ callPeaksUnivariateAllChr <- function(binned.data, input.data=NULL, eps=0.01, in |
426 | 426 |
red.df <- suppressMessages(collapseBins(df, column2collapseBy='state', columns2average=c('score'), columns2drop=c('width',grep('posterior', names(df), value=TRUE), 'counts'))) |
427 | 427 |
red.gr <- GRanges(seqnames=red.df[,1], ranges=IRanges(start=red.df[,2], end=red.df[,3]), strand=red.df[,4], state=red.df[,'state'], score=red.df[,'mean.score']) |
428 | 428 |
result$segments <- red.gr |
429 |
- seqlengths(result$segments) <- seqlengths(binned.data) |
|
429 |
+ seqlengths(result$segments) <- seqlengths(binned.data)[seqlevels(result$segments)] |
|
430 | 430 |
if (!keep.posteriors) { |
431 | 431 |
result$bins$posteriors <- NULL |
432 | 432 |
} |
433 | 433 |
old mode 100644 |
434 | 434 |
new mode 100755 |
... | ... |
@@ -67,7 +67,7 @@ changePostCutoff <- function(model, post.cutoff=0.5, separate.zeroinflation=TRUE |
67 | 67 |
red.df <- suppressMessages(collapseBins(df, column2collapseBy='state', columns2average=c('score'), columns2drop=c('width',grep('posteriors', names(df), value=TRUE), 'counts'))) |
68 | 68 |
red.gr <- GRanges(seqnames=red.df[,1], ranges=IRanges(start=red.df[,2], end=red.df[,3]), strand=red.df[,4], state=red.df[,'state'], score=red.df[,'mean.score']) |
69 | 69 |
model$segments <- red.gr |
70 |
- seqlengths(model$segments) <- seqlengths(model$bins) |
|
70 |
+ seqlengths(model$segments) <- seqlengths(model$bins)[seqlevels(model$segments)] |
|
71 | 71 |
stopTimedMessage(ptm) |
72 | 72 |
# ## Redo weights |
73 | 73 |
# model$weights <- table(model$bins$state) / length(model$bins) |
80 | 80 |
old mode 100644 |
81 | 81 |
new mode 100755 |
... | ... |
@@ -17,7 +17,7 @@ |
17 | 17 |
#' @param hmm.list A list of models generated by \code{\link{callPeaksUnivariate}}, e.g. 'list(model1,model2,...)'. |
18 | 18 |
#' @param binary If \code{TRUE}, a matrix of binary instead of decimal states will be returned. |
19 | 19 |
#' @return Output is a vector of integers representing the combinatorial state of each bin. |
20 |
-#' @seealso \code{link{dec2bin}}, \code{\link{bin2dec}} |
|
20 |
+#' @seealso \code{\link{dec2bin}}, \code{\link{bin2dec}} |
|
21 | 21 |
#' @examples |
22 | 22 |
#'# Get example BED files for 4 different marks in hypertensive rat (SHR) |
23 | 23 |
#'file.path <- system.file("extdata","euratrans", package='chromstaRData') |
24 | 24 |
old mode 100644 |
25 | 25 |
new mode 100755 |
... | ... |
@@ -4,7 +4,7 @@ |
4 | 4 |
#' |
5 | 5 |
#' @param hmms A \code{list()} with \code{\link{multiHMM}} objects. Alternatively a character vector with filenames that contain \code{\link{multiHMM}} objects. |
6 | 6 |
#' @param mode Mode of combination. See \code{\link{Chromstar}} for a description of the \code{mode} parameter. |
7 |
-#' @return A \code{link{combinedMultiHMM}} objects with combinatorial states for each condition. |
|
7 |
+#' @return A \code{\link{combinedMultiHMM}} objects with combinatorial states for each condition. |
|
8 | 8 |
#' @author Aaron Taudt |
9 | 9 |
#' @export |
10 | 10 |
#' @examples |
... | ... |
@@ -253,7 +253,7 @@ combineMultivariates <- function(hmms, mode) { |
253 | 253 |
segments.cond <- suppressMessages( collapseBins(df, column2collapseBy=cond, columns2drop=c('width', grep('posteriors', names(df), value=TRUE))) ) |
254 | 254 |
segments.cond <- as(segments.cond, 'GRanges') |
255 | 255 |
names(mcols(segments.cond)) <- 'combination' |
256 |
- seqlengths(segments.cond) <- seqlengths(bins) |
|
256 |
+ seqlengths(segments.cond) <- seqlengths(bins)[seqlevels(segments.cond)] |
|
257 | 257 |
segments.separate[[cond]] <- segments.cond |
258 | 258 |
} |
259 | 259 |
stopTimedMessage(ptm) |
266 | 266 |
old mode 100644 |
267 | 267 |
new mode 100755 |
... | ... |
@@ -3,7 +3,7 @@ |
3 | 3 |
#' Plotting functions for enrichment analysis of \code{\link{multiHMM}} objects with any annotation of interest, specified as a \code{\link[GenomicRanges]{GRanges}} object. |
4 | 4 |
#' |
5 | 5 |
#' @name enrichment_analysis |
6 |
-#' @return A \code{\link[ggplot2:ggplot]{ggplot}} object containing the plot. |
|
6 |
+#' @return A \code{\link[ggplot2:ggplot]{ggplot}} object containing the plot or a list() with \code{\link[ggplot2:ggplot]{ggplot}} objects if several plots are returned. |
|
7 | 7 |
#' @author Aaron Taudt |
8 | 8 |
#' @examples |
9 | 9 |
#'### Get an example multiHMM ### |
22 | 22 |
old mode 100644 |
23 | 23 |
new mode 100755 |
... | ... |
@@ -239,6 +239,7 @@ bed2GRanges <- function(bedfile, assembly, chromosomes=NULL, remove.duplicate.re |
239 | 239 |
} |
240 | 240 |
|
241 | 241 |
## Select only desired chromosomes |
242 |
+ ptm <- startTimedMessage("Subsetting chromosomes ...") |
|
242 | 243 |
data <- data[seqnames(data) %in% chroms2use] |
243 | 244 |
data <- keepSeqlevels(data, as.character(unique(seqnames(data)))) |
244 | 245 |
## Drop seqlevels where seqlength is NA |
... | ... |
@@ -248,6 +249,7 @@ bed2GRanges <- function(bedfile, assembly, chromosomes=NULL, remove.duplicate.re |
248 | 249 |
if (length(na.seqlevels) > 0) { |
249 | 250 |
warning("Dropped seqlevels because no length information was available: ", paste0(na.seqlevels, collapse=', ')) |
250 | 251 |
} |
252 |
+ stopTimedMessage(ptm) |
|
251 | 253 |
|
252 | 254 |
if (length(data) == 0) { |
253 | 255 |
stop(paste0('No reads imported!')) |
268 | 270 |
old mode 100644 |
269 | 271 |
new mode 100755 |
... | ... |
@@ -18,7 +18,7 @@ multivariateSegmentation <- function(bins, column2collapseBy='state') { |
18 | 18 |
names(red.df) <- sub('^mean.','', names(red.df)) |
19 | 19 |
segments <- as(red.df, 'GRanges') |
20 | 20 |
segments <- keepSeqlevels(segments, seqlevels(bins)) |
21 |
- seqlengths(segments) <- seqlengths(bins) |
|
21 |
+ seqlengths(segments) <- seqlengths(bins)[seqlevels(segments)] |
|
22 | 22 |
stopTimedMessage(ptm) |
23 | 23 |
|
24 | 24 |
return(segments) |
39 | 39 |
old mode 100644 |
40 | 40 |
new mode 100755 |
... | ... |
@@ -111,7 +111,7 @@ unis2pseudomulti <- function(uni.hmm.list) { |
111 | 111 |
red.df <- suppressMessages(collapseBins(df, column2collapseBy='state', columns2drop=c(ind.readcols, ind.widthcol))) |
112 | 112 |
red.gr <- GRanges(seqnames=red.df[,1], ranges=IRanges(start=red.df[,2], end=red.df[,3]), strand=red.df[,4], state=red.df[,'state'], combination=red.df[,'combination']) |
113 | 113 |
result$segments <- red.gr |
114 |
- seqlengths(result$segments) <- seqlengths(result$bins) |
|
114 |
+ seqlengths(result$segments) <- seqlengths(result$bins)[seqlevels(result$segments)] |
|
115 | 115 |
## Parameters |
116 | 116 |
result$mapping <- mapping |
117 | 117 |
# Weights |
140 | 140 |
old mode 100644 |
141 | 141 |
new mode 100755 |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
\title{Fit a Hidden Markov Model to a ChIP-seq sample.} |
6 | 6 |
\usage{ |
7 | 7 |
callPeaksUnivariate(binned.data, input.data = NULL, prefit.on.chr = NULL, |
8 |
- short = TRUE, eps = 0.01, init = "standard", max.time = NULL, |
|
8 |
+ short = TRUE, eps = 0.1, init = "standard", max.time = NULL, |
|
9 | 9 |
max.iter = 5000, num.trials = 1, eps.try = NULL, num.threads = 1, |
10 | 10 |
read.cutoff = TRUE, read.cutoff.quantile = 1, |
11 | 11 |
read.cutoff.absolute = 500, max.mean = Inf, post.cutoff = 0.5, |
62 | 62 |
old mode 100644 |
63 | 63 |
new mode 100755 |
... | ... |
@@ -12,7 +12,7 @@ combineMultivariates(hmms, mode) |
12 | 12 |
\item{mode}{Mode of combination. See \code{\link{Chromstar}} for a description of the \code{mode} parameter.} |
13 | 13 |
} |
14 | 14 |
\value{ |
15 |
-A \code{link{combinedMultiHMM}} objects with combinatorial states for each condition. |
|
15 |
+A \code{\link{combinedMultiHMM}} objects with combinatorial states for each condition. |
|
16 | 16 |
} |
17 | 17 |
\description{ |
18 | 18 |
Combine combinatorial states from several \code{\link{multiHMM}} objects. Combinatorial states can be combined for objects containing multiple marks (\code{mode='mark'}) or multiple conditions (\code{mode='condition'}). |
29 | 29 |
old mode 100644 |
30 | 30 |
new mode 100755 |
... | ... |
@@ -34,7 +34,7 @@ plotEnrichment(hmm, annotation, bp.around.annotation = 10000, |
34 | 34 |
\item{num.intervals}{Number of intervals for enrichment 'inside' of annotation.} |
35 | 35 |
} |
36 | 36 |
\value{ |
37 |
-A \code{\link[ggplot2:ggplot]{ggplot}} object containing the plot. |
|
37 |
+A \code{\link[ggplot2:ggplot]{ggplot}} object containing the plot or a list() with \code{\link[ggplot2:ggplot]{ggplot}} objects if several plots are returned. |
|
38 | 38 |
|
39 | 39 |
A \code{\link[ggplot2]{ggplot}} object (\code{plot=TRUE}) or a named array with fold enrichments (\code{plot=FALSE}). |
40 | 40 |
} |