... | ... |
@@ -122,6 +122,8 @@ combineList <- function(x, ..., BACKEND = NULL) { |
122 | 122 |
stopifnot(isTRUE(all(x_has_same_parameters))) |
123 | 123 |
# Check if all inputs have the same set of loci |
124 | 124 |
x_rowRanges <- lapply(x, rowRanges) |
125 |
+ # TODO: Check if all loci are identical()/all.equal(). This is must faster |
|
126 |
+ # that doing all these reduce()-ing intersect()-ing |
|
125 | 127 |
ans_rowRanges <- Reduce( |
126 | 128 |
f = function(x, y) { |
127 | 129 |
reduce(c(x, y), drop.empty.ranges = TRUE, min.gapwidth = 0L) |
... | ... |
@@ -215,5 +217,6 @@ combineList <- function(x, ..., BACKEND = NULL) { |
215 | 217 |
assays = ans_assays, |
216 | 218 |
rowRanges = ans_rowRanges, |
217 | 219 |
colData = ans_colData) |
220 |
+ # TODO: Avoid validity check. |
|
218 | 221 |
.BSseq(se, parameters = ans_parameters, trans = ans_trans) |
219 | 222 |
} |
... | ... |
@@ -360,6 +360,9 @@ |
360 | 360 |
|
361 | 361 |
# Exported functions ----------------------------------------------------------- |
362 | 362 |
|
363 |
+# TODO: If you have N cores available, are you better off using |
|
364 |
+# bpworkers() = N in the BPPARAM or nThread = N and use |
|
365 |
+# data.table::fread()? Or something in between? |
|
363 | 366 |
# TODO: Support passing a colData so that metadata is automatically added to |
364 | 367 |
# samples? |
365 | 368 |
# TODO: Document that `...` are used to pass filepath, chunkdim, level, etc. to |
... | ... |
@@ -567,8 +570,9 @@ read.bismark <- function(files, |
567 | 570 |
# TODO: Add function like minfi::read.metharray.sheet()? |
568 | 571 |
# TODO: Should BACKEND really be an argument of read.bismark(); see related |
569 | 572 |
# issue on minfi repo https://github.com/hansenlab/minfi/issues/140 |
570 |
-# TODO: May receive warning "In read_tokens_(data, tokenizer, col_specs, col_names, ... : length of NULL cannot be changed". This is fixed in devel version of |
|
571 |
-# readr (https://github.com/tidyverse/readr/issues/833) |
|
573 |
+# TODO: May receive warning "In read_tokens_(data, tokenizer, col_specs, |
|
574 |
+# col_names, ... : length of NULL cannot be changed". This is fixed in |
|
575 |
+# devel version of readr (https://github.com/tidyverse/readr/issues/833). |
|
572 | 576 |
# TODO: Think about naming scheme for functions. Try to have the function that |
573 | 577 |
# is bpapply()-ed have a similar name to its parent. |
574 | 578 |
# TODO: Document internal functions for my own sanity. Also, some may be useful |