Browse code

Remove deprecated arguments

Kasper wants these removed without deprecation/defunct cycle

Peter Hickey authored on 10/07/2018 04:39:30
Showing 2 changed files

... ...
@@ -115,8 +115,6 @@ makeClusters <- function(hasGRanges, maxGap = 10^8) {
115 115
 # Exported functions -----------------------------------------------------------
116 116
 
117 117
 # TODO: BSmooth() should warn if BSseq object contains mix of strands.
118
-# TODO: Make 'mc.cores', 'mc.preschedule', and 'verbose' defunct one release
119
-#       cycle with them deprecated.
120 118
 # TODO: Consider having BSmooth() create a 'smoothed' assay in addition to or
121 119
 #       instead of the 'coef' and 'se.coef' assays.
122 120
 BSmooth <- function(BSseq,
... ...
@@ -127,10 +125,7 @@ BSmooth <- function(BSseq,
127 125
                     verbose = TRUE,
128 126
                     BPPARAM = bpparam(),
129 127
                     BACKEND = getRealizationBackend(),
130
-                    ...,
131
-                    parallelBy = c("sample", "chromosome"),
132
-                    mc.preschedule = FALSE,
133
-                    mc.cores = 1) {
128
+                    ...) {
134 129
     # Argument checks-----------------------------------------------------------
135 130
 
136 131
     # Check validity of 'BSseq' argument
... ...
@@ -143,40 +138,6 @@ BSmooth <- function(BSseq,
143 138
     if (is.unsorted(BSseq)) {
144 139
         stop("'BSseq' must be sorted before smoothing. Use 'sort(BSseq)'.")
145 140
     }
146
-    # Check for deprecated arguments and issue warning(s) if found.
147
-    if (!missing(parallelBy)) {
148
-        warning(
149
-            "'parallelBy' is deprecated and ignored.\n",
150
-            "See help(\"BSmooth\") for details.",
151
-            call. = FALSE,
152
-            immediate. = TRUE)
153
-    }
154
-    if (!missing(mc.preschedule)) {
155
-        warning(
156
-            "'mc.preschedule' is deprecated and ignored.\n",
157
-            "See help(\"BSmooth\") for details.",
158
-            call. = FALSE,
159
-            immediate. = TRUE)
160
-    }
161
-    if (!missing(mc.cores)) {
162
-        # TODO: What if user has provided a BPPARAM?
163
-        warning(
164
-            "'mc.cores' is deprecated.\n",
165
-            "Replaced with 'BPPARAM = MulticoreParam(workers = mc.cores)'",
166
-            ".\nSee help(\"BSmooth\").",
167
-            call. = FALSE,
168
-            immediate. = TRUE)
169
-        BPPARAM <- MulticoreParam(workers = mc.cores)
170
-    }
171
-    if (!missing(verbose)) {
172
-        warning(
173
-            "'verbose' is deprecated.\n",
174
-            "Replaced by setting 'bpprogressbar(BPPARAM) <- TRUE'.\n",
175
-            "See help(\"BSmooth\") for details.",
176
-            call. = FALSE,
177
-            immediate. = TRUE)
178
-        if (verbose) bpprogressbar(BPPARAM) <- TRUE
179
-    }
180 141
     # Register 'BACKEND' and return to current value on exit
181 142
     current_BACKEND <- getRealizationBackend()
182 143
     on.exit(setRealizationBackend(current_BACKEND), add = TRUE)
... ...
@@ -25,7 +25,7 @@
25 25
     guessed_file_types
26 26
 }
27 27
 
28
-# NOTE: In brief  benchmarking, readr::read_csv() is ~1.3-1.6x faster than
28
+# NOTE: In brief benchmarking, readr::read_csv() is ~1.3-1.6x faster than
29 29
 #       utils::read.delim() when reading a gzipped file, albeit it with ~1.6-2x
30 30
 #       more total memory allocated. Therefore, there may be times users prefer
31 31
 #       to trade off faster speed for lower memory usage.
... ...
@@ -383,7 +383,7 @@
383 383
 #       bpworkers() = N in the BPPARAM or nThread = N and use
384 384
 #       data.table::fread()? Or something in between?
385 385
 # TODO: Support passing a colData so that metadata is automatically added to
386
-#       samples?
386
+#       samples? Yes, do this.
387 387
 # TODO: Document that `...` are used to pass filepath, chunkdim, level, etc. to
388 388
 #       HDF5RealizationSink().
389 389
 # TODO: (long term) Formalise `...` by something analogous to the
... ...
@@ -403,32 +403,10 @@ read.bismark <- function(files,
403 403
                          verbose = TRUE,
404 404
                          BPPARAM = bpparam(),
405 405
                          BACKEND = getRealizationBackend(),
406
-                         is_zcat_available = TRUE,
407 406
                          nThread = 1L,
408
-                         ...,
409
-                         fileType = c("cov", "oldBedGraph", "cytosineReport"),
410
-                         mc.cores = 1) {
407
+                         ...) {
411 408
     # Argument checks ----------------------------------------------------------
412 409
 
413
-    # Check for deprecated arguments and issue warning(s) if found.
414
-    if (!missing(fileType)) {
415
-        warning(
416
-            "'filetype' is deprecated.\n",
417
-            "Replaced with automatic detection of file types.\n",
418
-            "See help(\"read.bismark\") for details.",
419
-            call. = FALSE,
420
-            immediate. = TRUE)
421
-    }
422
-    if (!missing(mc.cores)) {
423
-        # TODO: What if user has provided a BPPARAM?
424
-        warning(
425
-            "'mc.cores' is deprecated.\n",
426
-            "Replaced with 'BPPARAM = MulticoreParam(workers = mc.cores)'",
427
-            ".\nSee help(\"BSmooth\").",
428
-            call. = FALSE,
429
-            immediate. = TRUE)
430
-        BPPARAM <- MulticoreParam(workers = mc.cores)
431
-    }
432 410
     # Check 'files' is valid.
433 411
     # TODO: Allow duplicate files? Useful in testing/debugging but generally a
434 412
     #       bad idea.