Browse code

Resync with latest internal changes to S4Vectors and IRanges

Hervé Pagès authored on 09/06/2020 01:36:15
Showing 6 changed files

... ...
@@ -1,5 +1,5 @@
1 1
 Package: bsseq
2
-Version: 1.25.3
2
+Version: 1.25.4
3 3
 Encoding: UTF-8
4 4
 Title: Analyze, manage and store bisulfite sequencing data
5 5
 Description: A collection of tools for analyzing and visualizing bisulfite
... ...
@@ -11,10 +11,10 @@ Depends:
11 11
     R (>= 3.5),
12 12
     methods,
13 13
     BiocGenerics,
14
-    GenomicRanges (>= 1.33.6),
15
-    SummarizedExperiment (>= 1.17.4)
14
+    GenomicRanges (>= 1.41.5),
15
+    SummarizedExperiment (>= 1.19.5)
16 16
 Imports:
17
-    IRanges (>= 2.23.5),
17
+    IRanges (>= 2.23.9),
18 18
     GenomeInfoDb,
19 19
     scales,
20 20
     stats,
... ...
@@ -23,7 +23,7 @@ Imports:
23 23
     locfit,
24 24
     gtools,
25 25
     data.table (>= 1.11.8),
26
-    S4Vectors (>= 0.25.14),
26
+    S4Vectors (>= 0.27.12),
27 27
     R.utils (>= 2.0.0),
28 28
     DelayedMatrixStats (>= 1.5.2),
29 29
     permute,
... ...
@@ -92,7 +92,7 @@ BSseq <- function(M = NULL, Cov = NULL, coef = NULL, se.coef = NULL,
92 92
     if (is.null(sampleNames)) {
93 93
         if (is.null(pData)) {
94 94
             # BSseq object will have no colnames.
95
-            pData <- S4Vectors:::new_DataFrame(nrows = ncol(M))
95
+            pData <- make_zero_col_DFrame(ncol(M))
96 96
         } else {
97 97
             # BSseq object will have 'sampleNames' as colnames.
98 98
             pData <- DataFrame(row.names = sampleNames)
... ...
@@ -251,8 +251,8 @@ blockApplyWithRealization <- function(x, FUN, ..., sink = NULL, x_grid = NULL,
251 251
     FUN <- match.fun(FUN)
252 252
 
253 253
     # Check conformable dots_grids and sinks_grids
254
-    x_grid <- DelayedArray:::.normarg_grid(x_grid, x)
255
-    sink_grid <- DelayedArray:::.normarg_grid(sink_grid, sink)
254
+    x_grid <- DelayedArray:::normarg_grid(x_grid, x)
255
+    sink_grid <- DelayedArray:::normarg_grid(sink_grid, sink)
256 256
     if (!identical(dim(x_grid), dim(sink_grid))) {
257 257
         stop("non-conformable 'x_grid' and 'sink_grid'")
258 258
     }
... ...
@@ -22,12 +22,12 @@
22 22
 
23 23
 # Internal methods -------------------------------------------------------------
24 24
 
25
-# NOTE: Combine the new "vertical slots" with those of the parent class. Make
26
-#       sure to put the new vertical slots **first**. See R/bindROWS.R file in
27
-#       the S4Vectors package for what slots should or should not be considered
28
-#       "vertical".
25
+# NOTE: Combine the new "parallel slots" with those of the parent class. Make
26
+#       sure to put the new parallel slots **first**. See R/Vector-class.R file
27
+#       in the S4Vectors package for what slots should or should not be
28
+#       considered "parallel".
29 29
 setMethod(
30
-    "vertical_slot_names",
30
+    "parallel_slot_names",
31 31
     "FWGRanges",
32 32
     function(x) {
33 33
         c(GenomicRanges:::extraColumnSlotNames(x), "seqnames", "ranges",
... ...
@@ -146,7 +146,7 @@ setMethod("update", "FWGRanges", function(object, ...) {
146 146
         s_space <- as.integer(strand(subject)) - 3L
147 147
     }
148 148
 
149
-    # IRanges:::NCList_find_overlaps_in_groups() ---------------------------
149
+    # IRanges:::find_overlaps_in_groups_NCList() ---------------------------
150 150
     q <- query@ranges
151 151
     s <- subject@ranges
152 152
     circle.length <- circle_length
... ...
@@ -186,7 +186,7 @@ setMethod("update", "FWGRanges", function(object, ...) {
186 186
         x = s,
187 187
         x_groups = s_groups,
188 188
         circle.length = s_circle_len)
189
-    .Call2("NCList_find_overlaps_in_groups",
189
+    .Call2("C_find_overlaps_in_groups_NCList",
190 190
            start(q), end(q), q_space, q_groups,
191 191
            start(s), end(s), s_space, s_groups,
192 192
            nclists, nclist_is_q,
... ...
@@ -281,7 +281,7 @@ setMethod("findOverlaps", c("FWGRanges", "FWGRanges"), .findOverlaps_FWGRanges)
281 281
     seqinfo <- Seqinfo(seqnames = levels(seqnames))
282 282
     ranges <- .FWIRanges(start = dt[["start"]], width = 1L)
283 283
     dt[, start := NULL]
284
-    mcols <- S4Vectors:::make_zero_col_DataFrame(length(ranges))
284
+    mcols <- make_zero_col_DFrame(length(ranges))
285 285
     if (is.null(dt[["strand"]])) {
286 286
         strand <- strand(Rle("*", length(seqnames)))
287 287
     } else {
... ...
@@ -35,7 +35,7 @@ setValidity2("FWIRanges", .valid.FWIRanges)
35 35
 
36 36
 # Internal methods -------------------------------------------------------------
37 37
 
38
-setMethod("vertical_slot_names", "FWIRanges",
38
+setMethod("parallel_slot_names", "FWIRanges",
39 39
           function(x) c("start", "NAMES", callNextMethod())
40 40
 )
41 41
 
... ...
@@ -53,10 +53,6 @@ setMethod("end", "FWIRanges", function(x) {
53 53
 
54 54
 setMethod("names", "FWIRanges", function(x) x@NAMES)
55 55
 
56
-setMethod("vertical_slot_names", "FWIRanges",
57
-          function(x) c("start", "NAMES", callNextMethod())
58
-)
59
-
60 56
 # TODO: Room for optmisation (e.g., write in C to reduce memory allocations).
61 57
 .set_FWIRanges_start <- function(x, value, check = TRUE) {
62 58
     if (!isTRUEorFALSE(check)) stop("'check' must be TRUE or FALSE")
... ...
@@ -180,7 +180,7 @@
180 180
     seqinfo <- Seqinfo(seqnames = levels(seqnames))
181 181
     ranges <- .FWIRanges(start = dt[["start"]], width = 1L)
182 182
     dt[, start := NULL]
183
-    mcols <- S4Vectors:::make_zero_col_DataFrame(length(ranges))
183
+    mcols <- make_zero_col_DFrame(length(ranges))
184 184
     if (is.null(dt[["strand"]])) {
185 185
         strand <- strand(Rle("*", length(seqnames)))
186 186
     } else {