-
Notifications
You must be signed in to change notification settings - Fork 187
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Merge branch 'master' of github.com:r-lib/lintr into expect_true_fals…
…e_and_condition
- Loading branch information
Showing
9 changed files
with
184 additions
and
1 deletion.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,76 @@ | ||
#' Require usage of expect_identical(x, y) where appropriate | ||
#' | ||
#' At Google, [testthat::expect_identical()] should be the default/go-to function for | ||
#' comparing an output to an expected value. `expect_true(identical(x, y))` | ||
#' is an equivalent but unadvised method of the same test. Further, | ||
#' [testthat::expect_equal()] should only be used when `expect_identical()` | ||
#' is inappropriate, i.e., when `x` and `y` need only be *numerically | ||
#' equivalent* instead of fully identical (in which case, provide the | ||
#' `tolerance=` argument to `expect_equal()` explicitly). This also applies | ||
#' when it's inconvenient to check full equality (e.g., names can be ignored, | ||
#' in which case `ignore_attr = "names"` should be supplied to | ||
#' `expect_equal()` (or, for 2nd edition, `check.attributes = FALSE`). | ||
#' | ||
#' @section Exceptions: | ||
#' | ||
#' The linter allows `expect_equal()` in three circumstances: | ||
#' 1. A named argument is set (e.g. `ignore_attr` or `tolerance`) | ||
#' 2. Comparison is made to an explicit decimal, e.g. | ||
#' `expect_equal(x, 1.0)` (implicitly setting `tolerance`) | ||
#' 3. `...` is passed (wrapper functions whcih might set | ||
#' arguments such as `ignore_attr` or `tolerance`) | ||
#' | ||
#' @evalRd rd_tags("expect_identical_linter") | ||
#' @seealso [linters] for a complete list of linters available in lintr. | ||
#' @export | ||
expect_identical_linter <- function() { | ||
Linter(function(source_file) { | ||
if (length(source_file$parsed_content) == 0L) { | ||
return(list()) | ||
} | ||
|
||
xml <- source_file$xml_parsed_content | ||
|
||
# outline: | ||
# 1. conditions for expect_equal() | ||
# - skip when any named argument is set. most commonly this | ||
# is check.attributes (for 2e tests) or one of the ignore_* | ||
# arguments (for 3e tests). This will generate some false | ||
# negatives, but will be much easier to maintain. | ||
# - skip cases like expect_equal(x, 1.02) or the constant vector version | ||
# where a numeric constant indicates inexact testing is preferable | ||
# - skip calls using dots (`...`); see tests | ||
# 2. conditions for expect_true() | ||
xpath <- glue::glue("//expr[ | ||
( | ||
SYMBOL_FUNCTION_CALL[text() = 'expect_equal'] | ||
and not( | ||
following-sibling::SYMBOL_SUB | ||
or following-sibling::expr[ | ||
expr[SYMBOL_FUNCTION_CALL[text() = 'c']] | ||
and expr[NUM_CONST[contains(text(), '.')]] | ||
] | ||
or following-sibling::expr[NUM_CONST[contains(text(), '.')]] | ||
or following-sibling::expr[SYMBOL[text() = '...']] | ||
) | ||
) or ( | ||
SYMBOL_FUNCTION_CALL[text() = 'expect_true'] | ||
and following-sibling::expr[1][ | ||
expr[SYMBOL_FUNCTION_CALL[text() = 'identical']] | ||
] | ||
) | ||
]") | ||
|
||
bad_expr <- xml2::xml_find_all(xml, xpath) | ||
return(lapply( | ||
bad_expr, | ||
xml_nodes_to_lint, | ||
source_file = source_file, | ||
lint_message = paste( | ||
"Use expect_identical(x, y) by default; resort to expect_equal() only when needed,", | ||
"e.g. when setting ignore_attr= or tolerance=." | ||
), | ||
type = "warning" | ||
)) | ||
}) | ||
} |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.
Oops, something went wrong.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,62 @@ | ||
test_that("expect_identical_linter skips allowed usages", { | ||
# expect_type doesn't have an inverted version | ||
expect_lint("expect_true(identical(x, y) || identical(y, z))", NULL, expect_identical_linter()) | ||
# NB: also applies to tinytest, but it's sufficient to test testthat | ||
expect_lint("testthat::expect_true(identical(x, y) || identical(y, z))", NULL, expect_identical_linter()) | ||
|
||
# expect_equal calls with explicit tolerance= are OK | ||
expect_lint("expect_equal(x, y, tolerance = 1e-6)", NULL, expect_identical_linter()) | ||
|
||
# ditto for check.attributes = FALSE | ||
expect_lint("expect_equal(x, y, check.attributes = FALSE)", NULL, expect_identical_linter()) | ||
}) | ||
|
||
test_that("expect_identical_linter blocks simple disallowed usages", { | ||
expect_lint( | ||
"expect_equal(x, y)", | ||
rex::rex("Use expect_identical(x, y) by default; resort to expect_equal() only when needed"), | ||
expect_identical_linter() | ||
) | ||
|
||
# different usage to redirect to expect_identical | ||
expect_lint( | ||
"expect_true(identical(x, y))", | ||
rex::rex("Use expect_identical(x, y) by default; resort to expect_equal() only when needed"), | ||
expect_identical_linter() | ||
) | ||
}) | ||
|
||
test_that("expect_identical_linter skips cases likely testing numeric equality", { | ||
expect_lint("expect_equal(x, 1.034)", NULL, expect_identical_linter()) | ||
expect_lint("expect_equal(x, c(1.01, 1.02))", NULL, expect_identical_linter()) | ||
# whole numbers with explicit decimals are OK, even in mixed scenarios | ||
expect_lint("expect_equal(x, c(1.0, 2))", NULL, expect_identical_linter()) | ||
# plain numbers are still caught, however | ||
expect_lint( | ||
"expect_equal(x, 1L)", | ||
rex::rex("Use expect_identical(x, y) by default; resort to expect_equal() only when needed"), | ||
expect_identical_linter() | ||
) | ||
expect_lint( | ||
"expect_equal(x, 1)", | ||
rex::rex("Use expect_identical(x, y) by default; resort to expect_equal() only when needed"), | ||
expect_identical_linter() | ||
) | ||
# NB: TRUE is a NUM_CONST so we want test matching it, even though this test is | ||
# also a violation of expect_true_false_linter() | ||
expect_lint( | ||
"expect_equal(x, TRUE)", | ||
rex::rex("Use expect_identical(x, y) by default; resort to expect_equal() only when needed"), | ||
expect_identical_linter() | ||
) | ||
}) | ||
|
||
test_that("expect_identical_linter skips 3e cases needing expect_equal", { | ||
expect_lint("expect_equal(x, y, ignore_attr = 'names')", NULL, expect_identical_linter()) | ||
}) | ||
|
||
# this arose where a helper function was wrapping expect_equal() and | ||
# some of the "allowed" arguments were being passed --> false positive | ||
test_that("expect_identical_linter skips calls using ...", { | ||
expect_lint("expect_equal(x, y, ...)", NULL, expect_identical_linter()) | ||
}) |