- There are still warnings and notes
- And still more stuff to re-factor
... | ... |
@@ -46,6 +46,7 @@ importFrom(readr, "cols", "cols_only", "col_character", "col_integer", |
46 | 46 |
"col_skip", "col_double", "col_factor", "read_tsv", "tokenizer_tsv") |
47 | 47 |
importFrom(Biostrings, "DNAString", "vmatchPattern", "reverseComplement") |
48 | 48 |
importFrom(utils, "read.delim") |
49 |
+importFrom(BSgenome, "vmatchPattern") |
|
49 | 50 |
|
50 | 51 |
## |
51 | 52 |
## Exporting |
... | ... |
@@ -54,6 +54,31 @@ |
54 | 54 |
} |
55 | 55 |
} |
56 | 56 |
|
57 |
+# Missing methods -------------------------------------------------------------- |
|
58 |
+ |
|
59 |
+# NOTE: Copied from minfi |
|
60 |
+# TODO: Perhaps move this to DelayedMatrixStats? |
|
61 |
+# TODO: DelayedArray::type() for all RealizationSink subclasses |
|
62 |
+setMethod("type", "HDF5RealizationSink", function(x) { |
|
63 |
+ x@type |
|
64 |
+}) |
|
65 |
+# NOTE: Copied from minfi |
|
66 |
+# TODO: Perhaps move this to DelayedMatrixStats? |
|
67 |
+setMethod("type", "arrayRealizationSink", function(x) { |
|
68 |
+ DelayedArray::type(x@result_envir$result) |
|
69 |
+}) |
|
70 |
+# NOTE: Copied from minfi |
|
71 |
+# TODO: Perhaps move this to DelayedMatrixStats? |
|
72 |
+setMethod("type", "RleRealizationSink", function(x) { |
|
73 |
+ x@type |
|
74 |
+}) |
|
75 |
+# NOTE: Copied from minfi |
|
76 |
+# TODO: Perhaps move this to DelayedMatrixStats? |
|
77 |
+# TODO: dimnames() for all RealizationSink subclasses |
|
78 |
+setMethod("dimnames", "arrayRealizationSink", function(x) { |
|
79 |
+ dimnames(x@result_envir$result) |
|
80 |
+}) |
|
81 |
+ |
|
57 | 82 |
# Helper functions for setting up ArrayGrid instances -------------------------- |
58 | 83 |
|
59 | 84 |
# NOTE: Copy of minfi:::colGrid() |
... | ... |
@@ -218,6 +218,9 @@ setMethod("findOverlaps", c("FWGRanges", "FWGRanges"), .findOverlaps_FWGRanges) |
218 | 218 |
.readBismarkAsFWGRanges <- function(file, rmZeroCov = FALSE, |
219 | 219 |
strandCollapse = FALSE, sort = TRUE, |
220 | 220 |
verbose = FALSE) { |
221 |
+ # Quieten R CMD check about 'no visible binding for global variable' ------- |
|
222 |
+ M <- U <- NULL |
|
223 |
+ |
|
221 | 224 |
# Read file to construct data.table of valid loci -------------------------- |
222 | 225 |
if (rmZeroCov) { |
223 | 226 |
dt <- .readBismarkAsDT( |
... | ... |
@@ -48,11 +48,16 @@ |
48 | 48 |
check = FALSE, |
49 | 49 |
verbose = FALSE, |
50 | 50 |
...) { |
51 |
+ # Quieten R CMD check about 'no visible binding for global variable' ------- |
|
52 |
+ M <- U <- NULL |
|
53 |
+ |
|
54 |
+ # Construct the column spec ------------------------------------------------ |
|
55 |
+ |
|
51 | 56 |
col_spec <- match.arg(col_spec) |
52 | 57 |
file_type <- .guessBismarkFileType(file) |
53 | 58 |
# TODO: Test for 'bismark_methylation_extractor' and 'bedGraph' formats, |
54 | 59 |
# and error out (they're not supported). |
55 |
- stopifnot(S4Vectors:::isTRUEorFALSE(check)) |
|
60 |
+ stopifnot(isTRUEorFALSE(check)) |
|
56 | 61 |
if (file_type == "cov") { |
57 | 62 |
col_names <- c("seqnames", "start", "end", "beta", "M", "U") |
58 | 63 |
if (col_spec == "BSseq") { |
... | ... |
@@ -112,6 +117,9 @@ |
112 | 117 |
trinucleotide_context = col_character()) |
113 | 118 |
} |
114 | 119 |
} |
120 |
+ |
|
121 |
+ # Read the file ------------------------------------------------------------ |
|
122 |
+ |
|
115 | 123 |
if (verbose) { |
116 | 124 |
message("[.readBismarkAsDT] Reading file '", file, "'") |
117 | 125 |
} |
... | ... |
@@ -124,6 +132,9 @@ |
124 | 132 |
quoted_na = FALSE, |
125 | 133 |
progress = verbose, |
126 | 134 |
...) |
135 |
+ |
|
136 |
+ # Construct the result ----------------------------------------------------- |
|
137 |
+ |
|
127 | 138 |
x <- setDT(x) |
128 | 139 |
if (check && all(c("M", "U") %in% colnames(x))) { |
129 | 140 |
if (verbose) { |
... | ... |
@@ -166,6 +177,10 @@ |
166 | 177 |
.constructCountsFromSingleFile <- function(b, files, strandCollapse, loci, |
167 | 178 |
grid, M_sink, Cov_sink, sink_lock, |
168 | 179 |
verbose, BPPARAM) { |
180 |
+ |
|
181 |
+ # Quieten R CMD check about 'no visible binding for global variable' ------- |
|
182 |
+ M <- U <- NULL |
|
183 |
+ |
|
169 | 184 |
# Read b-th file to construct data.table of valid loci and their counts ---- |
170 | 185 |
|
171 | 186 |
file <- files[b] |