Browse code

fixed seqlengths assign bug, ubuntu reinstall

chakalakka authored on 07/06/2016 09:48:47
Showing 121 changed files

1 1
old mode 100644
2 2
new mode 100755
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
14 14
old mode 100644
15 15
new mode 100755
16 16
old mode 100644
17 17
new mode 100755
18 18
old mode 100644
19 19
new mode 100755
20 20
old mode 100644
21 21
new mode 100755
22 22
old mode 100644
23 23
new mode 100755
24 24
old mode 100644
25 25
new mode 100755
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)
74 74
old mode 100644
75 75
new mode 100755
76 76
old mode 100644
77 77
new mode 100755
78 78
old mode 100644
79 79
new mode 100755
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)
260 260
old mode 100644
261 261
new mode 100755
262 262
old mode 100644
263 263
new mode 100755
264 264
old mode 100644
265 265
new mode 100755
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 ###
10 10
old mode 100644
11 11
new mode 100755
12 12
old mode 100644
13 13
new mode 100755
14 14
old mode 100644
15 15
new mode 100755
16 16
old mode 100644
17 17
new mode 100755
18 18
old mode 100644
19 19
new mode 100755
20 20
old mode 100644
21 21
new mode 100755
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!'))
254 256
old mode 100644
255 257
new mode 100755
256 258
old mode 100644
257 259
new mode 100755
258 260
old mode 100644
259 261
new mode 100755
260 262
old mode 100644
261 263
new mode 100755
262 264
old mode 100644
263 265
new mode 100755
264 266
old mode 100644
265 267
new mode 100755
266 268
old mode 100644
267 269
new mode 100755
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)
25 25
old mode 100644
26 26
new mode 100755
27 27
old mode 100644
28 28
new mode 100755
29 29
old mode 100644
30 30
new mode 100755
31 31
old mode 100644
32 32
new mode 100755
33 33
old mode 100644
34 34
new mode 100755
35 35
old mode 100644
36 36
new mode 100755
37 37
old mode 100644
38 38
new mode 100755
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
118 118
old mode 100644
119 119
new mode 100755
120 120
old mode 100644
121 121
new mode 100755
122 122
old mode 100644
123 123
new mode 100755
124 124
old mode 100644
125 125
new mode 100755
126 126
old mode 100644
127 127
new mode 100755
128 128
old mode 100644
129 129
new mode 100755
130 130
old mode 100644
131 131
new mode 100755
132 132
old mode 100644
133 133
new mode 100755
134 134
old mode 100644
135 135
new mode 100755
136 136
old mode 100644
137 137
new mode 100755
138 138
old mode 100644
139 139
new mode 100755
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,
12 12
old mode 100644
13 13
new mode 100755
14 14
old mode 100644
15 15
new mode 100755
16 16
old mode 100644
17 17
new mode 100755
18 18
old mode 100644
19 19
new mode 100755
20 20
old mode 100644
21 21
new mode 100755
22 22
old mode 100644
23 23
new mode 100755
... ...
@@ -56,6 +56,6 @@ table(states)
56 56
 Aaron Taudt
57 57
 }
58 58
 \seealso{
59
-\code{link{dec2bin}}, \code{\link{bin2dec}}
59
+\code{\link{dec2bin}}, \code{\link{bin2dec}}
60 60
 }
61 61
 
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'}).
19 19
old mode 100644
20 20
new mode 100755
21 21
old mode 100644
22 22
new mode 100755
23 23
old mode 100644
24 24
new mode 100755
25 25
old mode 100644
26 26
new mode 100755
27 27
old mode 100644
28 28
new mode 100755
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
 }
41 41
old mode 100644
42 42
new mode 100755
43 43
old mode 100644
44 44
new mode 100755
45 45
old mode 100644
46 46
new mode 100755
47 47
old mode 100644
48 48
new mode 100755
49 49
old mode 100644
50 50
new mode 100755
51 51
old mode 100644
52 52
new mode 100755
53 53
old mode 100644
54 54
new mode 100755
55 55
old mode 100644
56 56
new mode 100755
57 57
old mode 100644
58 58
new mode 100755
59 59
old mode 100644
60 60
new mode 100755
61 61
old mode 100644
62 62
new mode 100755
63 63
old mode 100644
64 64
new mode 100755
65 65
old mode 100644
66 66
new mode 100755
67 67
old mode 100644
68 68
new mode 100755
69 69
old mode 100644
70 70
new mode 100755
71 71
old mode 100644
72 72
new mode 100755
73 73
old mode 100644
74 74
new mode 100755
75 75
old mode 100644
76 76
new mode 100755
77 77
old mode 100644
78 78
new mode 100755
79 79
old mode 100644
80 80
new mode 100755
81 81
old mode 100644
82 82
new mode 100755
83 83
old mode 100644
84 84
new mode 100755
85 85
old mode 100644
86 86
new mode 100755
87 87
old mode 100644
88 88
new mode 100755
89 89
old mode 100644
90 90
new mode 100755
91 91
old mode 100644
92 92
new mode 100755
93 93
old mode 100644
94 94
new mode 100755
95 95
old mode 100644
96 96
new mode 100755
97 97
old mode 100644
98 98
new mode 100755
99 99
old mode 100644
100 100
new mode 100755
101 101
old mode 100644
102 102
new mode 100755
103 103
old mode 100644
104 104
new mode 100755
105 105
old mode 100644
106 106
new mode 100755
107 107
old mode 100644
108 108
new mode 100755
109 109
old mode 100644
110 110
new mode 100755
111 111
old mode 100644
112 112
new mode 100755
113 113
old mode 100644
114 114
new mode 100755
115 115
old mode 100644
116 116
new mode 100755
117 117
old mode 100644
118 118
new mode 100755
119 119
old mode 100644
120 120
new mode 100755
121 121
old mode 100644
122 122
new mode 100755
123 123
old mode 100644
124 124
new mode 100755
125 125
old mode 100644
126 126
new mode 100755
127 127
old mode 100644
128 128
new mode 100755
129 129
old mode 100644
130 130
new mode 100755
131 131
old mode 100644
132 132
new mode 100755
133 133
old mode 100644
134 134
new mode 100755
135 135
old mode 100644
136 136
new mode 100755
137 137
old mode 100644
138 138
new mode 100755
139 139
old mode 100644
140 140
new mode 100755
141 141
old mode 100644
142 142
new mode 100755
143 143
old mode 100644
144 144
new mode 100755
145 145
old mode 100644
146 146
new mode 100755
147 147
old mode 100644
148 148
new mode 100755