Skip to content

Commit

Permalink
assert_version_r()
Browse files Browse the repository at this point in the history
close #137
  • Loading branch information
wibeasley committed Jan 13, 2024
1 parent 52a372d commit 01699b0
Show file tree
Hide file tree
Showing 4 changed files with 127 additions and 0 deletions.
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

export(assert_non_na)
export(assert_non_na_and_unique)
export(assert_version_r)
export(clump_month_date)
export(clump_week_date)
export(column_class_headstart)
Expand Down
58 changes: 58 additions & 0 deletions R/assert-version.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
#' @name assert_version
#' @aliases assert_version_r
#' @title I that the local machine is using an acceptable version.
#'
#' @description Assert that the local machine is using a version that satisfies
#' the minimum version specified.
#'
#' @param minimum A [package_version] or [character] that specifies
#' the version of the software being examined
#' (ie, R, a package, or an ODBC driver).
#'
#' @return An error if the minimum version is not met.
#' If the local machine is using an acceptable version, an `invisible()` `TRUE`
#' is returned.
#'
#' @note These functions help us assert the the local machine has an acceptable
#' version of the software running.
#'
#' For [assert_version_r()], the current default value is "4.2.0" because
#' it introduced the
#' [placeholder](https://davidbudzynski.github.io/general/2022/04/23/r-native-placeholder.html)
#' for the native pipe. Future versions of OuhscMunge will likely increase
#' the default value to keep pace with important developments to R.
#'
#' @author Will Beasley
#'
#' @examples
#' assert_version_r("3.1.0")
#' assert_version_r()
#' # Fails: assert_version_r("99.1.0")

#' @export
assert_version_r <- function(minimum = base::package_version("4.2.1")) {
checkmate::assert_vector(minimum, len = 1, any.missing = FALSE)
v <-
if (inherits(minimum, "package_version")) {
as.character(minimum)
} else if (inherits(minimum, "character")) {
# Make sure it can be recognized as a version
as.character(base::package_version(minimum))
} else {
stop("The value passed to `minimum` must inherit either from 'character' or `package_version`.")
}

current <- as.character(utils::packageVersion("base"))

comparison <-
utils::compareVersion(
current,
v
)

if (comparison < 0 ) {
stop("Your R version is too old. Update it at <https://cloud.r-project.org>.")
} else {
TRUE
}
}
41 changes: 41 additions & 0 deletions man/assert_version.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

27 changes: 27 additions & 0 deletions tests/testthat/test-assert-version-r.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
library(testthat)

test_that("old minimum", {
r <- assert_version_r("3.1.0")
expect_true(r)

assert_version_r(package_version("3.1.0"))
expect_true(r)
})

test_that("default minimum", {
r <- assert_version_r()
expect_true(r)
})

test_that("minimum that throws an error", {
expected_error_message <- "Your R version is too old"
expect_error(
assert_version_r("99.1.0"),
expected_error_message
)

expect_error(
assert_version_r(package_version("99.1.0")),
expected_error_message
)
})

0 comments on commit 01699b0

Please sign in to comment.