Skip to content

Commit

Permalink
Add assertion
Browse files Browse the repository at this point in the history
  • Loading branch information
richfitz committed Aug 30, 2024
1 parent 1d48f71 commit d4f10cf
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 0 deletions.
10 changes: 10 additions & 0 deletions R/standalone-utils-assert.R
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,16 @@ assert_is <- function(x, what, name = deparse(substitute(x)), arg = name,
}


assert_list <- function(x, name = deparse(substitute(x)), arg = name,
call = parent.frame()) {
if (!is.list(x)) {
cli::cli_abort("Expected '{name}' to be a list",
arg = arg, call = call)
}
invisible(x)
}


assert_named <- function(x, unique = FALSE, name = deparse(substitute(x)),
arg = name, call = parent.frame()) {
nms <- names(x)
Expand Down
8 changes: 8 additions & 0 deletions tests/testthat/test-util-assert.R
Original file line number Diff line number Diff line change
Expand Up @@ -103,3 +103,11 @@ test_that("assert_scalar_logical", {
expect_no_error(assert_scalar_logical(TRUE))
expect_error(assert_scalar_logical(1), "to be logical")
})


test_that("assert_list", {
expect_silent(assert_list(list()))
expect_silent(assert_list(list(a = 1)))
x <- c(a = 1)
expect_error(assert_list(x), "Expected 'x' to be a list")
})

0 comments on commit d4f10cf

Please sign in to comment.