Browse code

bugfix for export empty univariate peaks

ataudt authored on 27/05/2019 08:49:37
Showing 3 changed files

... ...
@@ -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.11.0
4
+Version: 1.11.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.
... ...
@@ -1,3 +1,11 @@
1
+CHANGES IN VERSION 1.11.1
2
+-------------------------
3
+
4
+BUGFIXES
5
+
6
+    o Bugfix for error when exporting empty peaks in univariateHMM.
7
+    
8
+    
1 9
 CHANGES IN VERSION 1.9.2
2 10
 ------------------------
3 11
 
... ...
@@ -193,30 +193,32 @@ exportUnivariatePeaks <- function(hmm.list, filename, header=TRUE, separate.file
193 193
             }
194 194
             cat(paste0("track name=\"",trackname.string,"\" description=\"",trackname.string,"\" visibility=1 itemRgb=Off priority=",priority,"\n"), file=filename.gz, append=TRUE)
195 195
         }
196
-        if (is.null(peaks$maxPostInPeak)) {
197
-            peaks$peakScores <- 0
198
-        } else {
199
-            peaks$peakScores <- suppressWarnings( -10*log10(1-peaks$maxPostInPeak) )
200
-            peaks$peakScores[is.nan(peaks$peakScores) | peaks$peakScores > 1000] <- 1000
201
-        }
202
-        df <- as.data.frame(peaks)
203
-        df$peakNumber <- paste0('peak_', 1:nrow(df))
204
-        df$strand <- sub('\\*', '.', df$strand)
205
-        df <- df[,c('chromosome','start','end','peakNumber','peakScores','strand')]
206
-        # Make score integer
207
-        df$peakScores <- round(df$peakScores)
208
-        numsegments <- nrow(df)
209
-        # Convert from 1-based closed to 0-based half open
210
-        df$start <- df$start - 1
211
-        # df$thickStart <- df$start
212
-        # df$thickEnd <- df$end
213
-        # # Colors
214
-        # RGB <- t(grDevices::col2rgb(getStateColors('modified')))
215
-        # df$itemRgb <- apply(RGB,1,paste,collapse=",")
216
-        if (nrow(df) == 0) {
217
-            warning('hmm ',imod,' does not contain any \'modified\' calls')
218
-        } else {
219
-            utils::write.table(format(df, scientific=FALSE, trim=TRUE), file=filename.gz, append=TRUE, row.names=FALSE, col.names=FALSE, quote=FALSE, sep='\t')
196
+        if (length(peaks) > 0) {
197
+            if (is.null(peaks$maxPostInPeak)) {
198
+                peaks$peakScores <- 0
199
+            } else {
200
+                peaks$peakScores <- suppressWarnings( -10*log10(1-peaks$maxPostInPeak) )
201
+                peaks$peakScores[is.nan(peaks$peakScores) | peaks$peakScores > 1000] <- 1000
202
+            }
203
+            df <- as.data.frame(peaks)
204
+            df$peakNumber <- paste0('peak_', 1:nrow(df))
205
+            df$strand <- sub('\\*', '.', df$strand)
206
+            df <- df[,c('chromosome','start','end','peakNumber','peakScores','strand')]
207
+            # Make score integer
208
+            df$peakScores <- round(df$peakScores)
209
+            numsegments <- nrow(df)
210
+            # Convert from 1-based closed to 0-based half open
211
+            df$start <- df$start - 1
212
+            # df$thickStart <- df$start
213
+            # df$thickEnd <- df$end
214
+            # # Colors
215
+            # RGB <- t(grDevices::col2rgb(getStateColors('modified')))
216
+            # df$itemRgb <- apply(RGB,1,paste,collapse=",")
217
+            if (nrow(df) == 0) {
218
+                warning('hmm ',imod,' does not contain any \'modified\' calls')
219
+            } else {
220
+                utils::write.table(format(df, scientific=FALSE, trim=TRUE), file=filename.gz, append=TRUE, row.names=FALSE, col.names=FALSE, quote=FALSE, sep='\t')
221
+            }
220 222
         }
221 223
         if (separate.files) {
222 224
             close(filename.gz)