Browse code

merged with v14.1 from Bioc

ataudt authored on 30/04/2020 07:08:46
Showing 49 changed files

... ...
@@ -38,4 +38,4 @@ License: Artistic-2.0
38 38
 LazyLoad: yes
39 39
 VignetteBuilder: knitr
40 40
 biocViews: ImmunoOncology, Software, DifferentialPeakCalling, HiddenMarkovModel, ChIPSeq, HistoneModification, MultipleComparison, Sequencing, PeakDetection, ATACSeq
41
-RoxygenNote: 6.0.1
41
+RoxygenNote: 7.1.0
... ...
@@ -49,7 +49,7 @@ import(chromstaRData)
49 49
 import(doParallel)
50 50
 import(foreach)
51 51
 import(ggplot2)
52
-importFrom(BiocGenerics, "%in%")
52
+importFrom(BiocGenerics,"%in%")
53 53
 importFrom(GenomicAlignments,first)
54 54
 importFrom(GenomicAlignments,readGAlignmentPairs)
55 55
 importFrom(GenomicAlignments,readGAlignments)
... ...
@@ -1,3 +1,11 @@
1
+CHANGES IN VERSION 1.14.1
2
+-------------------------
3
+
4
+BUG FIXES
5
+
6
+    o Compatibility update: Replaced class() checks with is().
7
+
8
+
1 9
 CHANGES IN VERSION 1.13.1
2 10
 -------------------------
3 11
 
... ...
@@ -45,7 +45,7 @@ binReads <- function(file, experiment.table=NULL, ID=NULL, assembly, bamindex=fi
45 45
         if (is.character(file)) {
46 46
             file.clean <- sub('\\.gz$','', file)
47 47
             format <- rev(strsplit(file.clean, '\\.')[[1]])[1]
48
-        } else if (class(file)=='GRanges') {
48
+        } else if (is(file,'GRanges')) {
49 49
             format <- 'GRanges'
50 50
         } else {
51 51
             stop("Could not determine format automatically. Please specify it via the 'format' parameter.")
... ...
@@ -59,11 +59,11 @@ binReads <- function(file, experiment.table=NULL, ID=NULL, assembly, bamindex=fi
59 59
     if (format=='bed') {
60 60
         temp <- assembly # trigger error if not defined
61 61
     }
62
-    if (class(bins) == 'GRanges') {
62
+    if (is(bins,'GRanges')) {
63 63
         bins <- list(bins)
64 64
         names(bins) <- width(bins[[1]])[1]
65 65
     }
66
-    if (class(bins) == 'list') {
66
+    if (is(bins,'list')) {
67 67
         if (is.null(names(bins))) {
68 68
             names(bins) <- sapply(bins, function(x) { width(x)[1] })
69 69
         }
... ...
@@ -177,7 +177,7 @@ binReads <- function(file, experiment.table=NULL, ID=NULL, assembly, bamindex=fi
177 177
         if (is.character(variable.width.reference)) {
178 178
             variable.width.reference.clean <- sub('\\.gz$','', variable.width.reference)
179 179
             vformat <- rev(strsplit(variable.width.reference.clean, '\\.')[[1]])[1]
180
-        } else if (class(variable.width.reference)=='GRanges') {
180
+        } else if (is(variable.width.reference,'GRanges')) {
181 181
             vformat <- 'GRanges'
182 182
         }
183 183
         if (vformat == 'bam') {
... ...
@@ -55,7 +55,7 @@ callPeaksMultivariate <- function(hmms, use.states, max.states=NULL, per.chrom=T
55 55
 
56 56
     ## Intercept user input
57 57
     if (!is.null(use.states)) {
58
-        if (class(use.states)!='data.frame') stop("argument 'use.states' expects a data.frame generated by function 'state.brewer'")
58
+        if (!is(use.states,'data.frame')) stop("argument 'use.states' expects a data.frame generated by function 'state.brewer'")
59 59
     }
60 60
     if (!is.null(max.states)) {
61 61
         if (check.positive.integer(max.states)!=0) stop("argument 'max.states' expects a positive integer")
... ...
@@ -45,7 +45,7 @@
45 45
 callPeaksReplicates <- function(hmm.list, max.states=32, force.equal=FALSE, eps=0.01, max.iter=NULL, max.time=NULL, keep.posteriors=TRUE, num.threads=1, max.distance=0.2, per.chrom=TRUE) {
46 46
 
47 47
     ## Enable reanalysis of multivariate HMM
48
-    if (class(hmm.list)==class.multivariate.hmm) {
48
+    if (is(hmm.list,class.multivariate.hmm)) {
49 49
 
50 50
         multimodel <- hmm.list
51 51
         if (is.null(multimodel$replicateInfo)) {
... ...
@@ -51,7 +51,7 @@
51 51
 #'
52 52
 callPeaksUnivariate <- function(binned.data, control.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
-    if (class(binned.data) == 'character') { 
54
+    if (is(binned.data,'character')) { 
55 55
         messageU("Loading file(s) ", paste0(binned.data, collapse=', '), overline="_", underline=NULL)
56 56
         binned.datas <- loadHmmsFromFiles(binned.data)
57 57
         binned.data <- binned.datas[[1]]
... ...
@@ -66,7 +66,7 @@ callPeaksUnivariate <- function(binned.data, control.data=NULL, prefit.on.chr=NU
66 66
         }
67 67
     }
68 68
     if (!is.null(control.data)) {
69
-        if (class(control.data) == 'character') { 
69
+        if (is(control.data,'character')) { 
70 70
             message("Loading control file(s) ", paste0(control.data, collapse=', '))
71 71
             control.datas <- loadHmmsFromFiles(control.data)
72 72
             control.data <- control.datas[[1]]
... ...
@@ -168,7 +168,7 @@ callPeaksUnivariateAllChr <- function(binned.data, control.data=NULL, eps=0.01,
168 168
     war <- NULL
169 169
     if (is.null(eps.try)) eps.try <- eps
170 170
     ## Load binned.data and reuse values if present
171
-    if (class(binned.data) == 'character') { 
171
+    if (is(binned.data,'character')) { 
172 172
         binned.data <- loadHmmsFromFiles(binned.data)[[1]]
173 173
     }
174 174
 
... ...
@@ -182,7 +182,7 @@ callPeaksUnivariateAllChr <- function(binned.data, control.data=NULL, eps=0.01,
182 182
     info <- attr(binned.data, 'info')
183 183
 
184 184
     ### Assign initial parameters ###
185
-    if (class(binned.data) == class.univariate.hmm) {
185
+    if (is(binned.data,class.univariate.hmm)) {
186 186
         message("Using parameters from univariate HMM")
187 187
         hmm <- binned.data
188 188
         binned.data <- hmm$bins
... ...
@@ -194,7 +194,7 @@ callPeaksUnivariateAllChr <- function(binned.data, control.data=NULL, eps=0.01,
194 194
         size.initial <- hmm$distributions$size
195 195
         prob.initial <- hmm$distributions$prob
196 196
         continue.from.univariate.hmm <- TRUE
197
-    } else if (class(binned.data) == 'GRanges') {
197
+    } else if (is(binned.data,'GRanges')) {
198 198
         A.initial <- double(length=numstates*numstates)
199 199
         proba.initial <- double(length=numstates)
200 200
         size.initial <- double(length=numstates)
... ...
@@ -48,7 +48,7 @@ dec2bin = function(dec, colnames=NULL, ndigits=NULL) {
48 48
             binary.states[ ,ncol(binary.states)+1-i1] <- modulos[[i1]]
49 49
         }
50 50
     }
51
-    if (class(binary.states)!='matrix') {
51
+    if (!is(binary.states, 'matrix')) {
52 52
         binary.states <- matrix(binary.states, nrow=length(dec))
53 53
     }
54 54
 
... ...
@@ -78,8 +78,8 @@ plotFoldEnrichHeatmap <- function(hmm, annotations, what="combinations", combina
78 78
     hmm <- loadHmmsFromFiles(hmm, check.class=c(class.multivariate.hmm, class.combined.multivariate.hmm))[[1]]
79 79
     ## Variables
80 80
     bins <- hmm$bins
81
-    if (class(hmm) == class.combined.multivariate.hmm) {
82
-    } else if (class(hmm) == class.multivariate.hmm) {
81
+    if (is(hmm,class.combined.multivariate.hmm)) {
82
+    } else if (is(hmm,class.multivariate.hmm)) {
83 83
         # Rename 'combination' to 'combination.' for coherence with combinedMultiHMM
84 84
         names(mcols(bins))[grep('combination', names(mcols(bins)))] <- paste0('combination.', unique(hmm$info$condition))
85 85
     }
... ...
@@ -238,13 +238,13 @@ plotFoldEnrichHeatmap <- function(hmm, annotations, what="combinations", combina
238 238
         }
239 239
     }
240 240
 
241
-    if (class(hmm) == class.multivariate.hmm | what == 'transitions') {
241
+    if (is(hmm,class.multivariate.hmm) | what == 'transitions') {
242 242
         if (plot) {
243 243
             return(ggplts[[1]])
244 244
         } else {
245 245
             return(folds[[1]])
246 246
         }
247
-    } else if (class(hmm) == class.combined.multivariate.hmm) {
247
+    } else if (is(hmm,class.combined.multivariate.hmm)) {
248 248
         if (plot) {
249 249
             return(ggplts)
250 250
         } else {
... ...
@@ -273,7 +273,7 @@ plotEnrichCountHeatmap <- function(hmm, annotation, bp.around.annotation=10000,
273 273
     hmm <- loadHmmsFromFiles(hmm, check.class=c(class.multivariate.hmm, class.combined.multivariate.hmm))[[1]]
274 274
     ## Variables
275 275
     bins <- hmm$bins
276
-    if (class(hmm) == class.combined.multivariate.hmm) {
276
+    if (is(hmm,class.combined.multivariate.hmm)) {
277 277
         conditions <- sub('combination.', '', grep('combination', names(mcols(bins)), value=TRUE))
278 278
         comb.levels <- levels(mcols(bins)[,paste0('combination.', conditions[1])])
279 279
         ## Create new column combination with all conditions combined
... ...
@@ -283,7 +283,7 @@ plotEnrichCountHeatmap <- function(hmm, annotation, bp.around.annotation=10000,
283 283
         }
284 284
         combs$sep <- ', '
285 285
         bins$combination <- factor(do.call(paste, combs))
286
-    } else if (class(hmm) == class.multivariate.hmm) {
286
+    } else if (is(hmm,class.multivariate.hmm)) {
287 287
         comb.levels <- levels(bins$combination)
288 288
     }
289 289
     binsize <- width(bins)[1]
... ...
@@ -430,14 +430,14 @@ plotEnrichment <- function(hmm, annotation, bp.around.annotation=10000, region=c
430 430
     ## Variables
431 431
     hmm <- loadHmmsFromFiles(hmm, check.class=c(class.univariate.hmm, class.multivariate.hmm, class.combined.multivariate.hmm))[[1]]
432 432
     bins <- hmm$bins
433
-    if (class(hmm) == class.univariate.hmm) {
433
+    if (is(hmm,class.univariate.hmm)) {
434 434
         # bins$counts <- rpkm.vector(hmm$bins$counts, binsize=mean(width(hmm$bins)))
435 435
         mcols(bins)['combination.'] <- bins$state
436 436
         bins$state <- c('zero-inflation' = 0, 'unmodified' = 0, 'modified' = 1)[bins$state]
437 437
         hmm$info <- data.frame(file=NA, mark=1, condition=1, replicate=1, pairedEndReads=NA, controlFiles=NA, ID='1-1-rep1')
438
-    } else if (class(hmm) == class.combined.multivariate.hmm) {
438
+    } else if (is(hmm,class.combined.multivariate.hmm)) {
439 439
         # bins$counts <- rpkm.matrix(hmm$bins$counts, binsize=mean(width(hmm$bins)))
440
-    } else if (class(hmm) == class.multivariate.hmm) {
440
+    } else if (is(hmm,class.multivariate.hmm)) {
441 441
         # bins$counts <- rpkm.matrix(hmm$bins$counts, binsize=mean(width(hmm$bins)))
442 442
         # Rename 'combination' to 'combination.' for coherence with combinedMultiHMM
443 443
         names(mcols(bins))[grep('combination', names(mcols(bins)))] <- 'combination.'
... ...
@@ -566,11 +566,11 @@ plotEnrichment <- function(hmm, annotation, bp.around.annotation=10000, region=c
566 566
         ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_y_continuous(limits=c(minfold*(1-sign(minfold)*0.1),maxfold*(1+sign(maxfold)*0.1))) })
567 567
     }
568 568
     ggplts <- lapply(ggplts, function(ggplt) { ggplt + scale_color_manual(values=getDistinctColors(maxcol)) }) # Add color here like this because of weird bug
569
-    if (class(hmm) == class.univariate.hmm) {
569
+    if (is(hmm,class.univariate.hmm)) {
570 570
         return(ggplts[[1]])
571
-    } else if (class(hmm) == class.multivariate.hmm) {
571
+    } else if (is(hmm,class.multivariate.hmm)) {
572 572
         return(ggplts[[1]])
573
-    } else if (class(hmm) == class.combined.multivariate.hmm) {
573
+    } else if (is(hmm,class.combined.multivariate.hmm)) {
574 574
         return(ggplts)
575 575
     }
576 576
     
... ...
@@ -26,13 +26,13 @@ NULL
26 26
 exportPeaks <- function(model, filename, header=TRUE, separate.files=TRUE, trackname=NULL) {
27 27
   
28 28
     model <- loadHmmsFromFiles(model)[[1]]
29
-    if (class(model) == class.univariate.hmm) {
29
+    if (is(model,class.univariate.hmm)) {
30 30
         exportUnivariatePeaks(list(model), filename=paste0(filename, '_peaks'), header=header, separate.files=separate.files, trackname=trackname)
31 31
     }
32
-    if (class(model) == class.multivariate.hmm) {
32
+    if (is(model,class.multivariate.hmm)) {
33 33
         exportMultivariatePeaks(model, filename=paste0(filename, '_peaks'), header=header, separate.files=separate.files, trackname=trackname)
34 34
     }
35
-    if (class(model) == class.combined.multivariate.hmm) {
35
+    if (is(model,class.combined.multivariate.hmm)) {
36 36
         exportCombinedMultivariatePeaks(model, filename=paste0(filename, '_peaks'), header=header, separate.files=separate.files, trackname=trackname)
37 37
     }
38 38
   
... ...
@@ -44,16 +44,16 @@ exportPeaks <- function(model, filename, header=TRUE, separate.files=TRUE, track
44 44
 exportCounts <- function(model, filename, header=TRUE, separate.files=TRUE, trackname=NULL) {
45 45
   
46 46
     model <- loadHmmsFromFiles(model)[[1]]
47
-    if (class(model) == 'GRanges') {
47
+    if (is(model,'GRanges')) {
48 48
         exportBinnedData(list(model), filename=paste0(filename, '_counts'), header=header, separate.files=separate.files, trackname=trackname)
49 49
     }
50
-    if (class(model) == class.univariate.hmm) {
50
+    if (is(model,class.univariate.hmm)) {
51 51
         exportUnivariateCounts(list(model), filename=paste0(filename, '_counts'), header=header, separate.files=separate.files, trackname=trackname)
52 52
     }
53
-    if (class(model) == class.multivariate.hmm) {
53
+    if (is(model,class.multivariate.hmm)) {
54 54
         exportMultivariateCounts(model, filename=paste0(filename, '_counts'), header=header, separate.files=separate.files, trackname=trackname)
55 55
     }
56
-    if (class(model) == class.combined.multivariate.hmm) {
56
+    if (is(model,class.combined.multivariate.hmm)) {
57 57
         exportCombinedMultivariateCounts(model, filename=paste0(filename, '_counts'), header=header, separate.files=separate.files, trackname=trackname)
58 58
     }
59 59
   
... ...
@@ -67,10 +67,10 @@ exportCounts <- function(model, filename, header=TRUE, separate.files=TRUE, trac
67 67
 exportCombinations <- function(model, filename, header=TRUE, separate.files=TRUE, trackname=NULL, exclude.states='[]', include.states=NULL) {
68 68
   
69 69
     model <- loadHmmsFromFiles(model)[[1]]
70
-    if (class(model) == class.multivariate.hmm) {
70
+    if (is(model,class.multivariate.hmm)) {
71 71
         exportMultivariateCombinations(model, filename=paste0(filename, '_combinations'), header=header, trackname=trackname, exclude.states=exclude.states, include.states=include.states)
72 72
     }
73
-    if (class(model) == class.combined.multivariate.hmm) {
73
+    if (is(model,class.combined.multivariate.hmm)) {
74 74
         exportCombinedMultivariateCombinations(model, filename=paste0(filename, '_combinations'), header=header, separate.files=separate.files, trackname=trackname, exclude.states=exclude.states, include.states=include.states)
75 75
     }
76 76
   
... ...
@@ -52,8 +52,8 @@ plotExpression <- function(hmm, expression, combinations=NULL, return.marks=FALS
52 52
     hmm <- loadHmmsFromFiles(hmm, check.class=c(class.multivariate.hmm, class.combined.multivariate.hmm))[[1]]
53 53
     ## Variables
54 54
     bins <- hmm$bins
55
-    if (class(hmm) == class.combined.multivariate.hmm) {
56
-    } else if (class(hmm) == class.multivariate.hmm) {
55
+    if (is(hmm,class.combined.multivariate.hmm)) {
56
+    } else if (is(hmm,class.multivariate.hmm)) {
57 57
         # Rename 'combination' to 'combination.' for coherence with combinedMultiHMM
58 58
         names(mcols(bins))[grep('combination', names(mcols(bins)))] <- paste0('combination.', unique(hmm$info$condition))
59 59
     }
... ...
@@ -95,9 +95,9 @@ plotExpression <- function(hmm, expression, combinations=NULL, return.marks=FALS
95 95
         ggplts[[condition]] <- ggplt
96 96
     }
97 97
     
98
-    if (class(hmm) == class.multivariate.hmm) {
98
+    if (is(hmm,class.multivariate.hmm)) {
99 99
         return(ggplts[[1]])
100
-    } else if (class(hmm) == class.combined.multivariate.hmm) {
100
+    } else if (is(hmm,class.combined.multivariate.hmm)) {
101 101
         return(ggplts)
102 102
     }
103 103
 
... ...
@@ -30,7 +30,7 @@ genomicFrequencies <- function(multi.hmm, combinations=NULL, per.mark=FALSE) {
30 30
         return(list(frequency=t, domains=s))
31 31
     }
32 32
       
33
-    if (class(multi.hmm)==class.multivariate.hmm) {
33
+    if (is(multi.hmm,class.multivariate.hmm)) {
34 34
 
35 35
         if (is.null(combinations)) {
36 36
             comb.levels <- levels(bins$combination)
... ...
@@ -43,7 +43,7 @@ genomicFrequencies <- function(multi.hmm, combinations=NULL, per.mark=FALSE) {
43 43
         s <- s[names(s) %in% comb.levels]
44 44
         return(list(frequency=t, domains=s))
45 45
       
46
-    } else if (class(multi.hmm)==class.combined.multivariate.hmm) {
46
+    } else if (is(multi.hmm,class.combined.multivariate.hmm)) {
47 47
       
48 48
         if (is.null(combinations)) {
49 49
             comb.levels <- unique(as.vector(sapply(getCombinations(bins), levels)))
... ...
@@ -32,7 +32,7 @@ readBamFileAsGRanges <- function(bamfile, bamindex=bamfile, chromosomes=NULL, pa
32 32
 
33 33
     ## Input checks
34 34
     if (!is.null(blacklist)) {
35
-        if ( !(is.character(blacklist) | class(blacklist)=='GRanges') ) {
35
+        if ( !(is.character(blacklist) | is(blacklist,'GRanges')) ) {
36 36
             stop("'blacklist' has to be either a bed(.gz) file or a GRanges object")
37 37
         }
38 38
     }
... ...
@@ -141,7 +141,7 @@ readBamFileAsGRanges <- function(bamfile, bamindex=bamfile, chromosomes=NULL, pa
141 141
                 chromosome.format <- 'NCBI'
142 142
             }
143 143
             black <- readCustomBedFile(blacklist, skip=0, chromosome.format=chromosome.format)
144
-        } else if (class(blacklist)=='GRanges') {
144
+        } else if (is(blacklist,'GRanges')) {
145 145
             black <- blacklist
146 146
         } else {
147 147
             stop("'blacklist' has to be either a bed(.gz) file or a GRanges object")
... ...
@@ -206,7 +206,7 @@ readBedFileAsGRanges <- function(bedfile, assembly, chromosomes=NULL, remove.dup
206 206
 
207 207
     ## Input checks
208 208
     if (!is.null(blacklist)) {
209
-        if ( !(is.character(blacklist) | class(blacklist)=='GRanges') ) {
209
+        if ( !(is.character(blacklist) | is(blacklist,'GRanges')) ) {
210 210
             stop("'blacklist' has to be either a bed(.gz) file or a GRanges object")
211 211
         }
212 212
     }
... ...
@@ -311,7 +311,7 @@ readBedFileAsGRanges <- function(bedfile, assembly, chromosomes=NULL, remove.dup
311 311
                 chromosome.format <- 'NCBI'
312 312
             }
313 313
             black <- readCustomBedFile(blacklist, skip=0, chromosome.format=chromosome.format)
314
-        } else if (class(blacklist)=='GRanges') {
314
+        } else if (is(blacklist,'GRanges')) {
315 315
             black <- blacklist
316 316
         } else {
317 317
             stop("'blacklist' has to be either a bed(.gz) file or a GRanges object")
... ...
@@ -175,7 +175,7 @@ variableWidthBins <- function(reads, binsizes, chromosomes=NULL) {
175 175
     for (i1 in 1:length(binsizes)) {
176 176
         binsize <- binsizes[i1]
177 177
         ptm <- startTimedMessage("Making variable-width windows for bin size ", binsize, " ...")
178
-        if (class(binned.list)=='GRanges') {
178
+        if (is(binned.list,'GRanges')) {
179 179
             binned <- binned.list
180 180
         } else {
181 181
             binned <- binned.list[[i1]]
... ...
@@ -10,7 +10,7 @@ getMaxPostInPeaks <- function(states, posteriors) {
10 10
         r$values[r$values == FALSE] <- NA
11 11
         peakNumbers <- inverse.rle(r)
12 12
         df <- aggregate(posteriors[,icol], by=list(peakNumber=peakNumbers), FUN=max)
13
-        if (class(df$x) == 'list') {
13
+        if (is(df$x,'list')) {
14 14
             class(df$x) <- 'numeric'
15 15
         }
16 16
         r <- r.bin
... ...
@@ -477,7 +477,7 @@ plotGenomeBrowser <- function(model, chr, start, end, style='peaks', peakHeight=
477 477
     bins <- model$bins
478 478
     ranges2plot <- reduce(bins[bins@seqnames == chr & start(bins) >= start & start(bins) <= end, , drop=FALSE])
479 479
     bins <- subsetByOverlaps(bins, ranges2plot)
480
-    if (class(model)=='uniHMM') {
480
+    if (is(model,'uniHMM')) {
481 481
         peaklist <- list(model$peaks)
482 482
         bins$counts.rpkm <- matrix(bins$counts.rpkm, ncol=1)
483 483
         if (is.null(model$info)) {
... ...
@@ -61,7 +61,7 @@ removeCondition <- function(model, conditions) {
61 61
         removeconds <- paste0(paste0('-', conditions, '-'), collapse='|')
62 62
         keepconds <- grep(removeconds, colnames(counts), invert=TRUE, value=TRUE)
63 63
         counts <- counts[,keepconds]
64
-        if (class(counts) != "matrix") {
64
+        if (!is(counts,'matrix')) {
65 65
             counts <- matrix(counts, ncol=1, dimnames=list(NULL, keepconds))
66 66
         }
67 67
         model$bins$counts.rpkm <- counts
... ...
@@ -71,7 +71,7 @@ removeCondition <- function(model, conditions) {
71 71
         removeconds <- paste0(paste0('-', conditions, '-'), collapse='|')
72 72
         keepconds <- grep(removeconds, colnames(posteriors), invert=TRUE, value=TRUE)
73 73
         posteriors <- posteriors[,keepconds]
74
-        if (class(posteriors) != "matrix") {
74
+        if (!is(posteriors,'matrix')) {
75 75
             posteriors <- matrix(posteriors, ncol=1, dimnames=list(NULL, keepconds))
76 76
         }
77 77
         model$bins$posteriors <- posteriors
... ...
@@ -81,7 +81,7 @@ removeCondition <- function(model, conditions) {
81 81
         removeconds <- paste0(paste0('-', conditions, '-'), collapse='|')
82 82
         keepconds <- grep(removeconds, colnames(maxPostInPeak), invert=TRUE, value=TRUE)
83 83
         maxPostInPeak <- maxPostInPeak[,keepconds]
84
-        if (class(maxPostInPeak) != "matrix") {
84
+        if (!is(maxPostInPeak,'matrix')) {
85 85
             maxPostInPeak <- matrix(maxPostInPeak, ncol=1, dimnames=list(NULL, keepconds))
86 86
         }
87 87
         model$bins$maxPostInPeak <- maxPostInPeak
... ...
@@ -148,7 +148,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
148 148
         }
149 149
     }
150 150
     if (!is.null(binary.matrix)) {
151
-        if (class(binary.matrix) != 'matrix' | mode(binary.matrix) != 'logical') {
151
+        if (!is(binary.matrix,'matrix') | mode(binary.matrix) != 'logical') {
152 152
             stop("argument 'binary.matrix' expects a logical matrix")
153 153
         }
154 154
     }
... ...
@@ -197,11 +197,11 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
197 197
         statenames.sep <- apply(as.matrix(binstates[,mask]), 1, function(x) { tracknames.mask[x] })
198 198
         if (length(statenames.sep)==0) {
199 199
             stop("Something went wrong in constructing state names.")
200
-        } else if (class(statenames.sep)=='list') {
200
+        } else if (is(statenames.sep,'list')) {
201 201
             statenames <- sapply(statenames.sep, paste, collapse=sep)
202
-        } else if (class(statenames.sep)=='matrix') {
202
+        } else if (is(statenames.sep,'matrix')) {
203 203
             statenames <- apply(statenames.sep, 2, paste, collapse=sep)
204
-        } else if (class(statenames.sep)=='character') {
204
+        } else if (is(statenames.sep,'character')) {
205 205
             statenames <- statenames.sep
206 206
         }
207 207
     } else {
... ...
@@ -245,7 +245,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
245 245
                     mask <- rowSums(as.matrix(binstates[,names[track.index]]), na.rm = TRUE) < 2
246 246
                     binstates <- binstates[mask,]
247 247
                     
248
-                    if (class(binstates)!='matrix') {
248
+                    if (!is(binstates,'matrix')) {
249 249
                         binstates <- matrix(binstates, ncol=numtracks)
250 250
                         colnames(binstates) <- tracknames
251 251
                     }
... ...
@@ -267,7 +267,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
267 267
                 mask <- rep(TRUE, nrow(binstates))
268 268
             }
269 269
             binstates <- binstates[mask,]
270
-            if (class(binstates)!='matrix') {
270
+            if (!is(binstates,'matrix')) {
271 271
                 binstates <- matrix(binstates, ncol=length(binstates))
272 272
                 colnames(binstates) <- tracknames
273 273
             }
... ...
@@ -288,7 +288,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
288 288
         bindiffmatrix <- dec2bin(0:(2^length(intersect.tracks)-1)) # all possible binary combinations (rows) between tracks (cols)
289 289
         controlsum <- apply(bindiffmatrix, 1, sum)
290 290
         bindiffmatrix <- bindiffmatrix[controlsum >= min.diff,]
291
-        if (class(bindiffmatrix)!='matrix') { # R-behaviour differs with only one column
291
+        if (!is(bindiffmatrix,'matrix')) { # R-behaviour differs with only one column
292 292
             bindiffmatrix <- matrix(bindiffmatrix, nrow=1)
293 293
         }
294 294
         colnames(bindiffmatrix) <- intersect.tracks
... ...
@@ -338,7 +338,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
338 338
                     mask <- rep(TRUE, nrow(binstates.irow))
339 339
                 }
340 340
                 binstates.irow <- binstates.irow[mask,]
341
-                if (class(binstates.irow)!='matrix') {
341
+                if (!is(binstates.irow,'matrix')) {
342 342
                     binstates.irow <- matrix(binstates.irow, ncol=length(binstates.irow))
343 343
                     colnames(binstates.irow) <- tracknames.conditions
344 344
                 }
... ...
@@ -363,7 +363,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
363 363
         tracks2compare.split <- split(tracks2compare, conditions)
364 364
         intersect.tracks <- Reduce(intersect, lapply(tracks2compare.split, unique))
365 365
         bincommonmatrix <- dec2bin(0:(2^length(intersect.tracks)-1)) # all possible binary combinations (rows) between tracks (cols)
366
-        if (class(bincommonmatrix)!='matrix') { # R-behaviour differs with only one column
366
+        if (!is(bincommonmatrix,'matrix')) { # R-behaviour differs with only one column
367 367
             bincommonmatrix <- matrix(bincommonmatrix, nrow=1)
368 368
         }
369 369
         colnames(bincommonmatrix) <- intersect.tracks
... ...
@@ -411,7 +411,7 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
411 411
                     mask <- apply(as.matrix(binstates.irow[,track.index]), 1, function(x) { Reduce('&', x) })
412 412
                 }
413 413
                 binstates.irow <- binstates.irow[mask,]
414
-                if (class(binstates.irow)!='matrix') {
414
+                if (!is(binstates.irow,'matrix')) {
415 415
                     binstates.irow <- matrix(binstates.irow, ncol=length(binstates.irow))
416 416
                     colnames(binstates.irow) <- tracknames.conditions
417 417
                 }
... ...
@@ -435,11 +435,11 @@ state.brewer <- function(replicates=NULL, differential.states=FALSE, min.diff=1,
435 435
         statenames.sep <- apply(as.matrix(binstates[,mask]), 1, function(x) { tracknames.mask[x] })
436 436
         if (length(statenames.sep)==0) {
437 437
             stop("Something went wrong in constructing state names.")
438
-        } else if (class(statenames.sep)=='list') {
438
+        } else if (is(statenames.sep,'list')) {
439 439
             statenames <- sapply(statenames.sep, paste, collapse=sep)
440
-        } else if (class(statenames.sep)=='matrix') {
440
+        } else if (is(statenames.sep,'matrix')) {
441 441
             statenames <- apply(statenames.sep, 2, paste, collapse=sep)
442
-        } else if (class(statenames.sep)=='character') {
442
+        } else if (is(statenames.sep,'character')) {
443 443
             statenames <- statenames.sep
444 444
         }
445 445
     } else {
... ...
@@ -4,13 +4,31 @@
4 4
 \alias{Chromstar}
5 5
 \title{Wrapper function for the \pkg{\link{chromstaR}} package}
6 6
 \usage{
7
-Chromstar(inputfolder, experiment.table, outputfolder, configfile = NULL,
8
-  numCPU = 1, binsize = 1000, stepsize = binsize/2, assembly = NULL,
9
-  chromosomes = NULL, remove.duplicate.reads = TRUE, min.mapq = 10,
10
-  format = NULL, prefit.on.chr = NULL, eps.univariate = 0.1,
11
-  max.time = NULL, max.iter = 5000, read.cutoff.absolute = 500,
12
-  keep.posteriors = TRUE, mode = "differential", max.states = 128,
13
-  per.chrom = TRUE, eps.multivariate = 0.01, exclusive.table = NULL)
7
+Chromstar(
8
+  inputfolder,
9
+  experiment.table,
10
+  outputfolder,
11
+  configfile = NULL,
12
+  numCPU = 1,
13
+  binsize = 1000,
14
+  stepsize = binsize/2,
15
+  assembly = NULL,
16
+  chromosomes = NULL,
17
+  remove.duplicate.reads = TRUE,
18
+  min.mapq = 10,
19
+  format = NULL,
20
+  prefit.on.chr = NULL,
21
+  eps.univariate = 0.1,
22
+  max.time = NULL,
23
+  max.iter = 5000,
24
+  read.cutoff.absolute = 500,
25
+  keep.posteriors = TRUE,
26
+  mode = "differential",
27
+  max.states = 128,
28
+  per.chrom = TRUE,
29
+  eps.multivariate = 0.01,
30
+  exclusive.table = NULL
31
+)
14 32
 }
15 33
 \arguments{
16 34
 \item{inputfolder}{Folder with either BAM or BED-6 (see \code{\link{readBedFileAsGRanges}} files.}
... ...
@@ -27,7 +45,7 @@ Chromstar(inputfolder, experiment.table, outputfolder, configfile = NULL,
27 45
 
28 46
 \item{stepsize}{An integer specifying the step size for analysis.}
29 47
 
30
-\item{assembly}{A \code{data.frame} or tab-separated file with columns 'chromosome' and 'length'. Alternatively a character specifying the assembly, see \code{\link[GenomeInfoDb]{fetchExtendedChromInfoFromUCSC}} for available assemblies. Specifying an assembly is only necessary when importing BED files. BAM files are handled automatically.}
48
+\item{assembly}{A \code{data.frame} or tab-separated file with columns 'chromosome' and 'length'. Alternatively a character specifying the assembly, see \code{\link[GenomeInfoDb]{getChromInfoFromUCSC}} for available assemblies. Specifying an assembly is only necessary when importing BED files. BAM files are handled automatically.}
31 49
 
32 50
 \item{chromosomes}{If only a subset of the chromosomes should be imported, specify them here.}
33 51
 
... ...
@@ -5,12 +5,26 @@
5 5
 \alias{binning}
6 6
 \title{Convert aligned reads from various file formats into read counts in equidistant bins}
7 7
 \usage{
8
-binReads(file, experiment.table = NULL, ID = NULL, assembly,
9
-  bamindex = file, chromosomes = NULL, pairedEndReads = FALSE,
10
-  min.mapq = 10, remove.duplicate.reads = TRUE, max.fragment.width = 1000,
11
-  blacklist = NULL, binsizes = 1000, stepsizes = binsizes/2,
12
-  reads.per.bin = NULL, bins = NULL, variable.width.reference = NULL,
13
-  use.bamsignals = TRUE, format = NULL)
8
+binReads(
9
+  file,
10
+  experiment.table = NULL,
11
+  ID = NULL,
12
+  assembly,
13
+  bamindex = file,
14
+  chromosomes = NULL,
15
+  pairedEndReads = FALSE,
16
+  min.mapq = 10,
17
+  remove.duplicate.reads = TRUE,
18
+  max.fragment.width = 1000,
19
+  blacklist = NULL,
20
+  binsizes = 1000,
21
+  stepsizes = binsizes/2,
22
+  reads.per.bin = NULL,
23
+  bins = NULL,
24
+  variable.width.reference = NULL,
25
+  use.bamsignals = TRUE,
26
+  format = NULL
27
+)
14 28
 }
15 29
 \arguments{
16 30
 \item{file}{A file with aligned reads. Alternatively a \code{\link{GRanges-class}} with aligned reads.}
... ...
@@ -19,7 +33,7 @@ binReads(file, experiment.table = NULL, ID = NULL, assembly,
19 33
 
20 34
 \item{ID}{Optional ID to select a row from the \code{experiment.table}. Only necessary if the experiment table contains the same file in multiple positions in column 'file'.}
21 35
 
22
-\item{assembly}{Please see \code{\link[GenomeInfoDb]{fetchExtendedChromInfoFromUCSC}} for available assemblies. Only necessary when importing BED files. BAM files are handled automatically. Alternatively a data.frame with columns 'chromosome' and 'length'.}
36
+\item{assembly}{Please see \code{\link[GenomeInfoDb]{getChromInfoFromUCSC}} for available assemblies. Only necessary when importing BED files. BAM files are handled automatically. Alternatively a data.frame with columns 'chromosome' and 'length'.}
23 37
 
24 38
 \item{bamindex}{BAM index file. Can be specified without the .bai ending. If the index file does not exist it will be created and a warning is issued.}
25 39
 
... ...
@@ -4,10 +4,21 @@
4 4
 \alias{callPeaksMultivariate}
5 5
 \title{Fit a Hidden Markov Model to multiple ChIP-seq samples}
6 6
 \usage{
7
-callPeaksMultivariate(hmms, use.states, max.states = NULL, per.chrom = TRUE,
8
-  chromosomes = NULL, eps = 0.01, keep.posteriors = FALSE,
9
-  num.threads = 1, max.time = NULL, max.iter = NULL,
10
-  keep.densities = FALSE, verbosity = 1, temp.savedir = NULL)
7
+callPeaksMultivariate(
8
+  hmms,
9
+  use.states,
10
+  max.states = NULL,
11
+  per.chrom = TRUE,
12
+  chromosomes = NULL,
13
+  eps = 0.01,
14
+  keep.posteriors = FALSE,
15
+  num.threads = 1,
16
+  max.time = NULL,
17
+  max.iter = NULL,
18
+  keep.densities = FALSE,
19
+  verbosity = 1,
20
+  temp.savedir = NULL
21
+)
11 22
 }
12 23
 \arguments{
13 24
 \item{hmms}{A list of \code{\link{uniHMM}}s generated by \code{\link{callPeaksUnivariate}}, e.g. \code{list(hmm1,hmm2,...)} or a vector of files that contain such objects, e.g. \code{c("file1","file2",...)}.}
... ...
@@ -4,9 +4,18 @@
4 4
 \alias{callPeaksReplicates}
5 5
 \title{Fit a multivariate Hidden Markov Model to multiple ChIP-seq replicates}
6 6
 \usage{
7
-callPeaksReplicates(hmm.list, max.states = 32, force.equal = FALSE,
8
-  eps = 0.01, max.iter = NULL, max.time = NULL, keep.posteriors = TRUE,
9
-  num.threads = 1, max.distance = 0.2, per.chrom = TRUE)
7
+callPeaksReplicates(
8
+  hmm.list,
9
+  max.states = 32,
10
+  force.equal = FALSE,
11
+  eps = 0.01,
12
+  max.iter = NULL,
13
+  max.time = NULL,
14
+  keep.posteriors = TRUE,
15
+  num.threads = 1,
16
+  max.distance = 0.2,
17
+  per.chrom = TRUE
18
+)
10 19
 }
11 20
 \arguments{
12 21
 \item{hmm.list}{A list of \code{\link{uniHMM}}s generated by \code{\link{callPeaksUnivariate}}, e.g. \code{list(hmm1,hmm2,...)} or \code{c("file1","file2",...)}. Alternatively, this parameter also accepts a \code{\link{multiHMM}} and will check if the distance between replicates is greater than \code{max.distance}.}
... ...
@@ -4,13 +4,28 @@
4 4
 \alias{callPeaksUnivariate}
5 5
 \title{Fit a Hidden Markov Model to a ChIP-seq sample.}
6 6
 \usage{
7
-callPeaksUnivariate(binned.data, control.data = NULL, prefit.on.chr = NULL,
8
-  short = TRUE, eps = 0.1, init = "standard", max.time = NULL,
9
-  max.iter = 5000, num.trials = 1, eps.try = NULL, num.threads = 1,
10
-  read.cutoff = TRUE, read.cutoff.quantile = 1,
11
-  read.cutoff.absolute = 500, max.mean = Inf, post.cutoff = 0.5,
12
-  control = FALSE, keep.posteriors = FALSE, keep.densities = FALSE,
13
-  verbosity = 1)
7
+callPeaksUnivariate(
8
+  binned.data,
9
+  control.data = NULL,
10
+  prefit.on.chr = NULL,
11
+  short = TRUE,
12
+  eps = 0.1,
13
+  init = "standard",
14
+  max.time = NULL,
15
+  max.iter = 5000,
16
+  num.trials = 1,
17
+  eps.try = NULL,
18
+  num.threads = 1,
19
+  read.cutoff = TRUE,
20
+  read.cutoff.quantile = 1,
21
+  read.cutoff.absolute = 500,
22
+  max.mean = Inf,
23
+  post.cutoff = 0.5,
24
+  control = FALSE,
25
+  keep.posteriors = FALSE,
26
+  keep.densities = FALSE,
27
+  verbosity = 1
28
+)
14 29
 }
15 30
 \arguments{
16 31
 \item{binned.data}{A \code{\link{GRanges-class}} object with binned read counts or a file that contains such an object.}
... ...
@@ -4,12 +4,26 @@
4 4
 \alias{callPeaksUnivariateAllChr}
5 5
 \title{Fit a Hidden Markov Model to a ChIP-seq sample.}
6 6
 \usage{
7
-callPeaksUnivariateAllChr(binned.data, control.data = NULL, eps = 0.01,
8
-  init = "standard", max.time = NULL, max.iter = NULL, num.trials = 1,
9
-  eps.try = NULL, num.threads = 1, read.cutoff = TRUE,
10
-  read.cutoff.quantile = 1, read.cutoff.absolute = 500, max.mean = Inf,
11
-  post.cutoff = 0.5, control = FALSE, keep.posteriors = FALSE,
12
-  keep.densities = FALSE, verbosity = 1)
7
+callPeaksUnivariateAllChr(
8
+  binned.data,
9
+  control.data = NULL,
10
+  eps = 0.01,
11
+  init = "standard",
12
+  max.time = NULL,
13
+  max.iter = NULL,
14
+  num.trials = 1,
15
+  eps.try = NULL,
16
+  num.threads = 1,
17
+  read.cutoff = TRUE,
18
+  read.cutoff.quantile = 1,
19
+  read.cutoff.absolute = 500,
20
+  max.mean = Inf,
21
+  post.cutoff = 0.5,
22
+  control = FALSE,
23
+  keep.posteriors = FALSE,
24
+  keep.densities = FALSE,
25
+  verbosity = 1
26
+)
13 27
 }
14 28
 \arguments{
15 29
 \item{binned.data}{A \code{\link{GRanges-class}} object with binned read counts or a file that contains such an object.}
... ...
@@ -4,8 +4,14 @@
4 4
 \alias{collapseBins}
5 5
 \title{Collapse consecutive bins}
6 6
 \usage{
7
-collapseBins(data, column2collapseBy = NULL, columns2sumUp = NULL,
8
-  columns2average = NULL, columns2getMax = NULL, columns2drop = NULL)
7
+collapseBins(
8
+  data,
9
+  column2collapseBy = NULL,
10
+  columns2sumUp = NULL,
11
+  columns2average = NULL,
12
+  columns2getMax = NULL,
13
+  columns2drop = NULL
14
+)
9 15
 }
10 16
 \arguments{
11 17
 \item{data}{A data.frame containing the genomic coordinates in the first three columns.}
... ...
@@ -4,9 +4,16 @@
4 4
 \alias{enrichmentAtAnnotation}
5 5
 \title{Enrichment of (combinatorial) states for genomic annotations}
6 6
 \usage{
7
-enrichmentAtAnnotation(bins, info, annotation, bp.around.annotation = 10000,
8
-  region = c("start", "inside", "end"), what = "combinations",
9
-  num.intervals = 21, statistic = "fold")
7
+enrichmentAtAnnotation(
8
+  bins,
9
+  info,
10
+  annotation,
11
+  bp.around.annotation = 10000,
12
+  region = c("start", "inside", "end"),
13
+  what = "combinations",
14
+  num.intervals = 21,
15
+  statistic = "fold"
16
+)
10 17
 }
11 18
 \arguments{
12 19
 \item{bins}{The \code{$bins} entry from a \code{\link{multiHMM}} or \code{\link{combinedMultiHMM}} object.}
... ...
@@ -7,18 +7,39 @@
7 7
 \alias{plotEnrichment}
8 8
 \title{Enrichment analysis}
9 9
 \usage{
10
-plotFoldEnrichHeatmap(hmm, annotations, what = "combinations",
11
-  combinations = NULL, marks = NULL, plot = TRUE, logscale = TRUE)
12
-
13
-plotEnrichCountHeatmap(hmm, annotation, bp.around.annotation = 10000,
14
-  max.rows = 1000, combinations = NULL,
10
+plotFoldEnrichHeatmap(
11
+  hmm,
12
+  annotations,
13
+  what = "combinations",
14
+  combinations = NULL,
15
+  marks = NULL,
16
+  plot = TRUE,
17
+  logscale = TRUE
18
+)
19
+
20
+plotEnrichCountHeatmap(
21
+  hmm,
22
+  annotation,
23
+  bp.around.annotation = 10000,
24
+  max.rows = 1000,
25
+  combinations = NULL,
15 26
   colorByCombinations = sortByCombinations,
16
-  sortByCombinations = is.null(sortByColumns), sortByColumns = NULL)
17
-
18
-plotEnrichment(hmm, annotation, bp.around.annotation = 10000,
19
-  region = c("start", "inside", "end"), num.intervals = 20,
20
-  what = "combinations", combinations = NULL, marks = NULL,
21
-  statistic = "fold", logscale = TRUE)
27
+  sortByCombinations = is.null(sortByColumns),
28
+  sortByColumns = NULL
29
+)
30
+
31
+plotEnrichment(
32
+  hmm,
33
+  annotation,
34
+  bp.around.annotation = 10000,
35
+  region = c("start", "inside", "end"),
36
+  num.intervals = 20,
37
+  what = "combinations",
38
+  combinations = NULL,
39
+  marks = NULL,
40
+  statistic = "fold",
41
+  logscale = TRUE
42
+)
22 43
 }
23 44
 \arguments{
24 45
 \item{hmm}{A \code{\link{combinedMultiHMM}} or \code{\link{multiHMM}} object or a file that contains such an object.}
... ...
@@ -3,7 +3,9 @@
3 3
 \name{experiment.table}
4 4
 \alias{experiment.table}
5 5
 \title{Experiment data table}
6
-\format{A \code{data.frame} with columns 'file', 'mark', 'condition', 'replicate', 'pairedEndReads' and 'controlFiles'. Avoid the use of special characters like '-' or '+' as this will confuse the internal file management.}
6
+\format{
7
+A \code{data.frame} with columns 'file', 'mark', 'condition', 'replicate', 'pairedEndReads' and 'controlFiles'. Avoid the use of special characters like '-' or '+' as this will confuse the internal file management.
8
+}
7 9
 \description{
8 10
 A \code{data.frame} specifying the structure of the experiment.
9 11
 }
... ...
@@ -7,14 +7,31 @@
7 7
 \alias{exportCombinations}
8 8
 \title{Export genome browser uploadable files}
9 9
 \usage{
10
-exportPeaks(model, filename, header = TRUE, separate.files = TRUE,
11
-  trackname = NULL)
10
+exportPeaks(
11
+  model,
12
+  filename,
13
+  header = TRUE,
14
+  separate.files = TRUE,
15
+  trackname = NULL
16
+)
12 17
 
13
-exportCounts(model, filename, header = TRUE, separate.files = TRUE,
14
-  trackname = NULL)
18
+exportCounts(
19
+  model,
20
+  filename,
21
+  header = TRUE,
22
+  separate.files = TRUE,
23
+  trackname = NULL
24
+)
15 25
 
16
-exportCombinations(model, filename, header = TRUE, separate.files = TRUE,
17
-  trackname = NULL, exclude.states = "[]", include.states = NULL)
26
+exportCombinations(
27
+  model,
28
+  filename,
29
+  header = TRUE,
30
+  separate.files = TRUE,
31
+  trackname = NULL,
32
+  exclude.states = "[]",
33
+  include.states = NULL
34
+)
18 35
 }
19 36
 \arguments{
20 37
 \item{model}{A \code{\link{chromstaR-objects}}.}
... ...
@@ -4,9 +4,17 @@
4 4
 \alias{exportGRangesAsBedFile}
5 5
 \title{Export genome browser viewable files}
6 6
 \usage{
7
-exportGRangesAsBedFile(gr, trackname, filename, namecol = "combination",
8
-  scorecol = "score", colorcol = NULL, colors = NULL, header = TRUE,
9
-  append = FALSE)
7
+exportGRangesAsBedFile(
8
+  gr,
9
+  trackname,
10
+  filename,
11
+  namecol = "combination",
12
+  scorecol = "score",
13
+  colorcol = NULL,
14
+  colors = NULL,
15
+  header = TRUE,
16
+  append = FALSE
17
+)
10 18
 }
11 19
 \arguments{
12 20
 \item{gr}{A \code{\link{GRanges-class}} object.}
... ...
@@ -4,13 +4,19 @@
4 4
 \alias{fixedWidthBins}
5 5
 \title{Make fixed-width bins}
6 6
 \usage{
7
-fixedWidthBins(bamfile = NULL, assembly = NULL, chrom.lengths = NULL,
8
-  chromosome.format, binsizes = 1e+06, chromosomes = NULL)
7
+fixedWidthBins(
8
+  bamfile = NULL,
9
+  assembly = NULL,
10
+  chrom.lengths = NULL,
11
+  chromosome.format,
12
+  binsizes = 1e+06,
13
+  chromosomes = NULL
14
+)
9 15
 }
10 16
 \arguments{
11 17
 \item{bamfile}{A BAM file from which the header is read to determine the chromosome lengths. If a \code{bamfile} is specified, option \code{assembly} is ignored.}
12 18
 
13
-\item{assembly}{An assembly from which the chromosome lengths are determined. Please see \code{\link[GenomeInfoDb]{fetchExtendedChromInfoFromUCSC}} for available assemblies. This option is ignored if \code{bamfile} is specified. Alternatively a data.frame generated by \code{\link[GenomeInfoDb]{fetchExtendedChromInfoFromUCSC}}.}
19
+\item{assembly}{An assembly from which the chromosome lengths are determined. Please see \code{\link[GenomeInfoDb]{getChromInfoFromUCSC}} for available assemblies. This option is ignored if \code{bamfile} is specified. Alternatively a data.frame generated by \code{\link[GenomeInfoDb]{getChromInfoFromUCSC}}.}
14 20
 
15 21
 \item{chrom.lengths}{A named character vector with chromosome lengths. Names correspond to chromosomes.}
16 22
 
... ...
@@ -4,7 +4,9 @@
4 4
 \name{genes_rn4}
5 5
 \alias{genes_rn4}
6 6
 \title{Gene coordinates for rn4}
7
-\format{A data.frame.}
7
+\format{
8
+A data.frame.
9
+}
8 10
 \description{
9 11
 A data.frame containing gene coordinates and biotypes of the rn4 assembly.
10 12
 }
... ...
@@ -4,9 +4,14 @@
4 4
 \alias{getDistinctColors}
5 5
 \title{Get distinct colors}
6 6
 \usage{
7
-getDistinctColors(n, start.color = "blue4", exclude.colors = c("white",
8
-  "black", "gray", "grey", "\\\\<yellow\\\\>", "yellow1", "lemonchiffon"),
9
-  exclude.brightness.above = 1, exclude.rgb.above = 210)
7
+getDistinctColors(
8
+  n,
9
+  start.color = "blue4",
10
+  exclude.colors = c("white", "black", "gray", "grey", "\\\\<yellow\\\\>", "yellow1",
11
+    "lemonchiffon"),
12
+  exclude.brightness.above = 1,
13
+  exclude.rgb.above = 210
14
+)
10 15
 }
11 16
 \arguments{
12 17
 \item{n}{Number of colors to select. If \code{n} is a character vector, \code{length(n)} will be taken as the number of colors and the colors will be named by \code{n}.}
... ...
@@ -4,8 +4,11 @@
4 4
 \alias{heatmapTransitionProbs}
5 5
 \title{Heatmap of transition probabilities}
6 6
 \usage{
7
-heatmapTransitionProbs(model = NULL, reorder.states = TRUE,
8
-  transitionProbs = NULL)
7
+heatmapTransitionProbs(
8
+  model = NULL,
9
+  reorder.states = TRUE,
10
+  transitionProbs = NULL
11
+)
9 12
 }
10 13
 \arguments{
11 14
 \item{model}{A \code{\link{multiHMM}} object or file that contains such an object.}
... ...
@@ -4,8 +4,10 @@
4 4
 \alias{loadHmmsFromFiles}
5 5
 \title{Load \pkg{chromstaR} objects from file}
6 6
 \usage{
7
-loadHmmsFromFiles(files, check.class = c("GRanges", "uniHMM", "multiHMM",
8
-  "combinedMultiHMM"))
7
+loadHmmsFromFiles(
8
+  files,
9
+  check.class = c("GRanges", "uniHMM", "multiHMM", "combinedMultiHMM")
10
+)
9 11
 }
10 12
 \arguments{
11 13
 \item{files}{A list of \code{\link{chromstaR-objects}} or a vector of files that contain such objects.}
... ...
@@ -4,7 +4,9 @@
4 4
 \name{model.combined}
5 5
 \alias{model.combined}
6 6
 \title{Combined multivariate HMM for demonstration purposes}
7
-\format{A \code{\link{combinedMultiHMM}} object.}
7
+\format{
8
+A \code{\link{combinedMultiHMM}} object.
9
+}
8 10
 \description{
9 11
 A \code{\link{combinedMultiHMM}} object for demonstration purposes in examples of package \pkg{\link{chromstaR}}.
10 12
 }
... ...
@@ -4,7 +4,9 @@
4 4
 \name{model.multivariate}
5 5
 \alias{model.multivariate}
6 6
 \title{Multivariate HMM for demonstration purposes}
7
-\format{A \code{\link{multiHMM}} object.}
7
+\format{
8
+A \code{\link{multiHMM}} object.
9
+}
8 10
 \description{
9 11
 A \code{\link{multiHMM}} object for demonstration purposes in examples of package \pkg{\link{chromstaR}}.
10 12
 }
... ...
@@ -4,7 +4,9 @@
4 4
 \name{model.univariate}
5 5
 \alias{model.univariate}
6 6
 \title{Univariate HMM for demonstration purposes}
7
-\format{A \code{\link{uniHMM}} object.}
7
+\format{
8
+A \code{\link{uniHMM}} object.
9
+}
8 10
 \description{
9 11
 A \code{\link{uniHMM}} object for demonstration purposes in examples of package \pkg{\link{chromstaR}}.
10 12
 }
... ...
@@ -68,8 +68,16 @@ plotGenomeBrowser2 <- function(counts, peaklist=NULL, chr, start, end, countcol=
68 68
 }
69 69
 Plot a genome browser view}
70 70
 \usage{
71
-plotGenomeBrowser(model, chr, start, end, style = "peaks", peakHeight = 0.2,
72
-  peakColor = "blue", same.yaxis = TRUE)
71
+plotGenomeBrowser(
72
+  model,
73
+  chr,
74
+  start,
75
+  end,
76
+  style = "peaks",
77
+  peakHeight = 0.2,
78
+  peakColor = "blue",
79
+  same.yaxis = TRUE
80
+)
73 81
 }
74 82
 \arguments{
75 83
 \item{model}{A \code{\link{uniHMM}}, \code{\link{multiHMM}} or \code{\link{combinedMultiHMM}} object or file that contains such an object.}
... ...
@@ -4,8 +4,14 @@
4 4
 \alias{plotHistogram}
5 5
 \title{Histogram of binned read counts with fitted mixture distribution}
6 6
 \usage{
7
-plotHistogram(model, state = NULL, chromosomes = NULL, start = NULL,
8
-  end = NULL, linewidth = 1)
7
+plotHistogram(
8
+  model,
9
+  state = NULL,
10
+  chromosomes = NULL,
11
+  start = NULL,
12
+  end = NULL,
13
+  linewidth = 1
14
+)
9 15
 }
10 16
 \arguments{
11 17
 \item{model}{A \code{\link{uniHMM}} object or file that contains such an object.}
... ...
@@ -4,9 +4,17 @@
4 4
 \alias{readBamFileAsGRanges}
5 5
 \title{Import BAM file into GRanges}
6 6
 \usage{
7
-readBamFileAsGRanges(bamfile, bamindex = bamfile, chromosomes = NULL,
8
-  pairedEndReads = FALSE, remove.duplicate.reads = FALSE, min.mapq = 10,
9
-  max.fragment.width = 1000, blacklist = NULL, what = "mapq")
7
+readBamFileAsGRanges(
8
+  bamfile,
9
+  bamindex = bamfile,
10
+  chromosomes = NULL,
11
+  pairedEndReads = FALSE,
12
+  remove.duplicate.reads = FALSE,
13
+  min.mapq = 10,
14
+  max.fragment.width = 1000,
15
+  blacklist = NULL,
16
+  what = "mapq"
17
+)
10 18
 }
11 19
 \arguments{
12 20
 \item{bamfile}{A sorted BAM file.}
... ...
@@ -4,14 +4,20 @@
4 4
 \alias{readBedFileAsGRanges}
5 5
 \title{Import BED file into GRanges}
6 6
 \usage{
7
-readBedFileAsGRanges(bedfile, assembly, chromosomes = NULL,
8
-  remove.duplicate.reads = FALSE, min.mapq = 10,
9
-  max.fragment.width = 1000, blacklist = NULL)
7
+readBedFileAsGRanges(
8
+  bedfile,
9
+  assembly,
10
+  chromosomes = NULL,
11
+  remove.duplicate.reads = FALSE,
12
+  min.mapq = 10,
13
+  max.fragment.width = 1000,
14
+  blacklist = NULL
15
+)
10 16
 }
11 17
 \arguments{
12 18
 \item{bedfile}{A file with aligned reads in BED-6 format. The columns have to be c('chromosome','start','end','description','mapq','strand').}
13 19
 
14
-\item{assembly}{Please see \code{\link[GenomeInfoDb]{fetchExtendedChromInfoFromUCSC}} for available assemblies. Only necessary when importing BED files. BAM files are handled automatically. Alternatively a data.frame with columns 'chromosome' and 'length'.}
20
+\item{assembly}{Please see \code{\link[GenomeInfoDb]{getChromInfoFromUCSC}} for available assemblies. Only necessary when importing BED files. BAM files are handled automatically. Alternatively a data.frame with columns 'chromosome' and 'length'.}
15 21
 
16 22
 \item{chromosomes}{If only a subset of the chromosomes should be imported, specify them here.}
17 23
 
... ...
@@ -4,9 +4,14 @@
4 4
 \alias{readCustomBedFile}
5 5
 \title{Read bed-file into GRanges}
6 6
 \usage{
7
-readCustomBedFile(bedfile, col.names = c("chromosome", "start", "end", "name",
8
-  "score", "strand"), col.classes = NULL, skip = 0,
9
-  chromosome.format = "NCBI", sep = "")
7
+readCustomBedFile(
8
+  bedfile,
9
+  col.names = c("chromosome", "start", "end", "name", "score", "strand"),
10
+  col.classes = NULL,
11
+  skip = 0,
12
+  chromosome.format = "NCBI",
13
+  sep = ""
14
+)
10 15
 }
11 16
 \arguments{
12 17
 \item{bedfile}{Filename of the bed or bed.gz file.}
... ...
@@ -4,9 +4,16 @@
4 4
 \alias{scanBinsizes}
5 5
 \title{Find the best bin size for a given dataset}
6 6
 \usage{
7
-scanBinsizes(files.binned, outputfolder, chromosomes = "chr10", eps = 0.01,
8
-  max.iter = 100, max.time = 300, repetitions = 3,
9
-  plot.progress = FALSE)
7
+scanBinsizes(
8
+  files.binned,
9
+  outputfolder,
10
+  chromosomes = "chr10",
11
+  eps = 0.01,
12
+  max.iter = 100,
13
+  max.time = 300,
14
+  repetitions = 3,
15
+  plot.progress = FALSE
16
+)
10 17
 }
11 18
 \arguments{
12 19
 \item{files.binned}{A vector with files that contain \code{\link{binned.data}} in different bin sizes.}
... ...
@@ -4,8 +4,16 @@
4 4
 \alias{simulateMultivariate}
5 5
 \title{Simulate multivariate data}
6 6
 \usage{
7
-simulateMultivariate(bins, transition, emissions, weights, correlationMatrices,
8
-  combstates, IDs, fragLen = 50)
7
+simulateMultivariate(
8
+  bins,
9
+  transition,
10
+  emissions,
11
+  weights,
12
+  correlationMatrices,
13
+  combstates,
14
+  IDs,
15
+  fragLen = 50
16
+)
9 17
 }
10 18
 \arguments{
11 19
 \item{bins}{A \code{\link[GenomicRanges]{GRanges-class}} object for which reads will be simulated.}
... ...
@@ -4,10 +4,19 @@
4 4
 \alias{state.brewer}
5 5
 \title{Obtain combinatorial states from specification}
6 6
 \usage{
7
-state.brewer(replicates = NULL, differential.states = FALSE, min.diff = 1,
8
-  common.states = FALSE, conditions = NULL, tracks2compare = NULL,
9
-  sep = "+", statespec = NULL, diffstatespec = NULL,
10
-  exclusive.table = NULL, binary.matrix = NULL)
7
+state.brewer(
8
+  replicates = NULL,
9
+  differential.states = FALSE,
10
+  min.diff = 1,
11
+  common.states = FALSE,
12
+  conditions = NULL,
13
+  tracks2compare = NULL,
14
+  sep = "+",
15
+  statespec = NULL,
16
+  diffstatespec = NULL,
17
+  exclusive.table = NULL,
18
+  binary.matrix = NULL
19
+)
11 20
 }
12 21
 \arguments{
13 22
 \item{replicates}{A vector specifying the replicate structure. Similar entries will be treated as replicates.}
... ...
@@ -4,8 +4,14 @@
4 4
 \alias{stateBrewer}
5 5
 \title{Obtain combinatorial states from experiment table}
6 6
 \usage{
7
-stateBrewer(experiment.table, mode, differential.states = FALSE,
8
-  common.states = FALSE, exclusive.table = NULL, binary.matrix = NULL)
7
+stateBrewer(
8
+  experiment.table,
9
+  mode,
10
+  differential.states = FALSE,
11
+  common.states = FALSE,
12
+  exclusive.table = NULL,
13
+  binary.matrix = NULL
14
+)
9 15
 }
10 16
 \arguments{
11 17
 \item{experiment.table}{A \code{data.frame} specifying the experiment structure. See \code{\link{experiment.table}}.}
... ...
@@ -4,8 +4,12 @@
4 4
 \alias{transitionFrequencies}
5 5
 \title{Transition frequencies of combinatorial states}
6 6
 \usage{
7
-transitionFrequencies(multi.hmms = NULL, combined.hmm = NULL,
8
-  zero.states = "[]", combstates = NULL)
7
+transitionFrequencies(
8
+  multi.hmms = NULL,
9
+  combined.hmm = NULL,
10
+  zero.states = "[]",
11
+  combstates = NULL
12
+)
9 13
 }
10 14
 \arguments{
11 15
 \item{multi.hmms}{A named list with \code{\link{multiHMM}} objects or a vector with filenames that contain such objects.}
... ...
@@ -51,7 +51,7 @@ The zero-inflated negative binomial distribution with \code{size} \eqn{= n} and
51 51
    w + (1-w) * \Gamma(x+n)/(\Gamma(n) x!) p^n (1-p)^x}
52 52
  for \eqn{x = 0}, \eqn{n > 0}, \eqn{0 < p \le 1} and \eqn{0 \le w \le 1}.
53 53
 
54
-\deqn{
54
+ \deqn{
55 55
    p(x) = (1-w) \frac{\Gamma(x+n)}{\Gamma(n) x!} p^n (1-p)^x}{
56 56
    (1-w) * \Gamma(x+n)/(\Gamma(n) x!) p^n (1-p)^x}
57 57
  for \eqn{x = 1, 2, \ldots}, \eqn{n > 0}, \eqn{0 < p \le 1} and \eqn{0 \le w \le 1}.