git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/bsseq@71123 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -245,14 +245,15 @@ setMethod("combine", signature(x = "BSseq", y = "BSseq"), function(x, y, ...) { |
245 | 245 |
phenoData = phenoData, trans = trans, rmZeroCov = FALSE) |
246 | 246 |
}) |
247 | 247 |
|
248 |
-combineList <- function(...) { |
|
249 |
- x <- list(...) |
|
248 |
+combineList <- function(x, ...) { |
|
249 |
+ if(class(x) == "BSseq") |
|
250 |
+ x <- list(x, ...) |
|
250 | 251 |
stopifnot(all(sapply(x, class) == "BSseq")) |
251 |
- gr <- getBSseq(x[[1]], "granges") |
|
252 |
+ gr <- getBSseq(x[[1]], "gr") |
|
252 | 253 |
trans <- getBSseq(x[[1]], "trans") |
253 | 254 |
ok <- sapply(x[-1], function(xx) { |
254 |
- identical(gr, getBSseq(xx, "granges")) && |
|
255 |
- identical(transgr, getBSseq(xx, "trans")) |
|
255 |
+ identical(gr, getBSseq(xx, "gr")) && |
|
256 |
+ identical(trans, getBSseq(xx, "trans")) |
|
256 | 257 |
}) |
257 | 258 |
if(!all(ok)) |
258 | 259 |
stop("all elements of '...' in combineList needs to have the same granges and trans") |