Skip to content

Commit

Permalink
Patch match.default for old R (workaround lack of mtfrm) (#108)
Browse files Browse the repository at this point in the history
* patch match.default for old R

* nocov
  • Loading branch information
MichaelChirico authored Oct 22, 2024
1 parent 1f1ff56 commit a64a059
Show file tree
Hide file tree
Showing 3 changed files with 5 additions and 5 deletions.
6 changes: 5 additions & 1 deletion R/patch64.R
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,11 @@ is.double.integer64 <- function(x)FALSE
match <- function(x, table, ...) UseMethod("match")
#' @rdname bit64S3
#' @export
match.default <- function(x, table, ...) base::match(x, table, ...)
match.default <- function(x, table, ...) {
# TODO(R>=4.2.0): Remove this workaround. Needed for #85.
if (!exists("mtfrm", baseenv()) && is.integer64(table)) base::match(as.character(x), as.character(table), ...) # nocov
else base::match(x, table, ...)
}

`%in%` <- function(x, table) UseMethod("%in%")
#' @rdname bit64S3
Expand Down
2 changes: 0 additions & 2 deletions tests/testthat/test-highlevel64.R
Original file line number Diff line number Diff line change
Expand Up @@ -4,8 +4,6 @@ test_that("match & %in% basics work", {
expect_identical(match(x, y), c(NA, 1:3))
expect_identical(match(y, x), c(2:4, NA))

# TODO(#85): restore these tests on old R.
skip_if_not_r_version("4.0.0")
expect_identical(match(2:5, y), c(NA, 1:3))
expect_identical(match(as.numeric(2:5), y), c(NA, 1:3))
expect_identical(match(y, 2:5), c(2:4, NA))
Expand Down
2 changes: 0 additions & 2 deletions tests/testthat/test-integer64.R
Original file line number Diff line number Diff line change
Expand Up @@ -284,8 +284,6 @@ test_that("all.equal.integer64 reflects changes for vector scale= from all.equal
),
"Mean scaled difference: 1"
)
# TODO(#100): restore this if possible.
skip_if_not_r_version("4.1.3")
# same test as for base R, multiplied by 1e9
one_e9 = as.integer64(1000000000L)
expect_true(all.equal(
Expand Down

0 comments on commit a64a059

Please sign in to comment.