diff --git a/R/patch64.R b/R/patch64.R index 4e31df8..dc923da 100644 --- a/R/patch64.R +++ b/R/patch64.R @@ -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 diff --git a/tests/testthat/test-highlevel64.R b/tests/testthat/test-highlevel64.R index 047e358..4728730 100644 --- a/tests/testthat/test-highlevel64.R +++ b/tests/testthat/test-highlevel64.R @@ -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)) diff --git a/tests/testthat/test-integer64.R b/tests/testthat/test-integer64.R index 484a9b5..d10ad61 100644 --- a/tests/testthat/test-integer64.R +++ b/tests/testthat/test-integer64.R @@ -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(