Skip to content

Commit ec5a625

Browse files
expect_type_linter (#924)
* expect_type_linter * dedup * tweak tests * refactor to readable xpath * customize lint message * glue in DESC * fix linter-as-call issue * fix tests * NEWS * remove @importFrom * catch yoda test version * skip patrick * re-document() * fix doc sorting * nolint false positive Co-authored-by: AshesITR <[email protected]>
1 parent 308be5b commit ec5a625

File tree

10 files changed

+163
-10
lines changed

10 files changed

+163
-10
lines changed

DESCRIPTION

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ Imports:
2222
codetools,
2323
cyclocomp,
2424
digest,
25+
glue,
2526
jsonlite,
2627
knitr,
2728
stats,
@@ -32,6 +33,7 @@ Suggests:
3233
covr,
3334
httr (>= 1.2.1),
3435
mockery,
36+
patrick,
3537
rmarkdown,
3638
rstudioapi (>= 0.2),
3739
testthat (>= 3.0.0),
@@ -63,6 +65,7 @@ Collate:
6365
'exclude.R'
6466
'expect_lint.R'
6567
'expect_null_linter.R'
68+
'expect_type_linter.R'
6669
'extract.R'
6770
'extraction_operator_linter.R'
6871
'function_left_parentheses.R'

NAMESPACE

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ export(equals_na_linter)
3232
export(expect_lint)
3333
export(expect_lint_free)
3434
export(expect_null_linter)
35+
export(expect_type_linter)
3536
export(extraction_operator_linter)
3637
export(function_left_parentheses_linter)
3738
export(get_source_expressions)

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -88,6 +88,7 @@ function calls. (#850, #851, @renkun-ken)
8888
* `lintr` now uses the 3rd edition of `testthat` (@MichaelChirico, #910)
8989
* `lintr` is adopting a new set of linters provided as part of Google's extension to the tidyverse style guide (#884, @michaelchirico)
9090
+ `expect_null_linter()` Require usage of `expect_null(x)` over `expect_equal(x, NULL)` and similar
91+
+ `expect_type_linter()` Require usage of `expect_type(x, t)` over `expect_equal(typeof(x), t)` and similar
9192
* `assignment_linter()` now lints right assignment (`->` and `->>`) and gains two arguments. `allow_cascading_assign` (`TRUE` by default) toggles whether to lint `<<-` and `->>`; `allow_right_assign` toggles whether to lint `->` and `->>` (#915, @michaelchirico)
9293

9394
# lintr 2.0.1

R/expect_type_linter.R

Lines changed: 62 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,62 @@
1+
#' Require usage of expect_type(x, type) over expect_equal(typeof(x), type)
2+
#'
3+
#' [testthat::expect_type()] exists specifically for testing the storage type
4+
#' of objects. [testthat::expect_equal()], [testthat::expect_identical()], and
5+
#' [testthat::expect_true()] can also be used for such tests,
6+
#' but it is better to use the tailored function instead.
7+
#'
8+
#' @evalRd rd_tags("expect_type_linter")
9+
#' @seealso [linters] for a complete list of linters available in lintr.
10+
#' @export
11+
expect_type_linter <- function() {
12+
Linter(function(source_file) {
13+
if (length(source_file$parsed_content) == 0L) {
14+
return(list())
15+
}
16+
17+
xml <- source_file$xml_parsed_content
18+
19+
base_type_tests <- xp_text_in_table(paste0("is.", base_types)) # nolint: object_usage_linter. TODO(#942): fix this.
20+
xpath <- glue::glue("//expr[
21+
(
22+
SYMBOL_FUNCTION_CALL[text() = 'expect_equal' or text() = 'expect_identical']
23+
and following-sibling::expr[
24+
expr[SYMBOL_FUNCTION_CALL[text() = 'typeof']]
25+
and (position() = 1 or preceding-sibling::expr[STR_CONST])
26+
]
27+
) or (
28+
SYMBOL_FUNCTION_CALL[text() = 'expect_true']
29+
and following-sibling::expr[1][expr[SYMBOL_FUNCTION_CALL[ {base_type_tests} ]]]
30+
)
31+
]")
32+
33+
bad_expr <- xml2::xml_find_all(xml, xpath)
34+
return(lapply(bad_expr, gen_expect_type_lint, source_file))
35+
})
36+
}
37+
38+
gen_expect_type_lint <- function(expr, source_file) {
39+
matched_function <- xml2::xml_text(xml2::xml_find_first(expr, "SYMBOL_FUNCTION_CALL"))
40+
if (matched_function %in% c("expect_equal", "expect_identical")) {
41+
lint_msg <- sprintf("expect_type(x, t) is better than %s(typeof(x), t)", matched_function)
42+
} else {
43+
lint_msg <- "expect_type(x, t) is better than expect_true(is.<t>(x))"
44+
}
45+
xml_nodes_to_lint(expr, source_file, lint_msg, type = "warning")
46+
}
47+
48+
49+
# NB: the full list of values that can arise from `typeof(x)` is available
50+
# in ?typeof (or, slightly more robustly, in the R source: src/main/util.c.
51+
# Not all of them are available in is.<type> form, e.g. 'any' or
52+
# 'special'. 'builtin' and 'closure' are special cases, corresponding to
53+
# is.primitive and is.function (essentially).
54+
base_types <- c(
55+
"raw", "logical", "integer", "double", "complex", "character", "list",
56+
"numeric", "function", "primitive", "environment", "pairlist", "promise",
57+
# Per ?is.language, it's the same as is.call || is.name || is.expression.
58+
# so by blocking it, we're forcing more precise tests of one of
59+
# those directly ("language", "symbol", and "expression", resp.)
60+
# NB: is.name and is.symbol are identical.
61+
"language", "call", "name", "symbol", "expression"
62+
)

inst/lintr/linters.csv

Lines changed: 9 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,44 +1,45 @@
11
linter,tags
22
absolute_path_linter,robustness best_practices configurable
33
assignment_linter,style consistency default
4+
assignment_spaces_linter,style readability
45
backport_linter,robustness configurable package_development
56
closed_curly_linter,style readability default configurable
67
commas_linter,style readability default
78
commented_code_linter,style readability best_practices default
89
cyclocomp_linter,style readability best_practices default configurable
10+
duplicate_argument_linter,correctness common_mistakes configurable
911
equals_na_linter,robustness correctness common_mistakes default
1012
expect_null_linter,package_development best_practices
13+
expect_type_linter,package_development best_practices
1114
extraction_operator_linter,style best_practices
1215
function_left_parentheses_linter,style readability default
1316
implicit_integer_linter,style consistency best_practices
1417
infix_spaces_linter,style readability default
1518
line_length_linter,style readability default configurable
19+
missing_argument_linter,correctness common_mistakes configurable
20+
missing_package_linter,robustness common_mistakes
21+
namespace_linter,correctness robustness configurable
1622
no_tab_linter,style consistency default
1723
nonportable_path_linter,robustness best_practices configurable
1824
object_length_linter,style readability default configurable
1925
object_name_linter,style consistency default configurable
2026
object_usage_linter,style readability correctness default
2127
open_curly_linter,style readability default configurable
2228
package_hooks_linter,style correctness package_development
29+
paren_body_linter,style readability default
2330
paren_brace_linter,style readability default
31+
pipe_call_linter,style readability
2432
pipe_continuation_linter,style readability default
2533
semicolon_terminator_linter,style readability default configurable
2634
seq_linter,robustness efficiency consistency best_practices default
2735
single_quotes_linter,style consistency readability default
2836
spaces_inside_linter,style readability default
2937
spaces_left_parentheses_linter,style readability default
38+
sprintf_linter,correctness common_mistakes
3039
T_and_F_symbol_linter,style readability robustness consistency best_practices default
3140
todo_comment_linter,style configurable
3241
trailing_blank_lines_linter,style default
3342
trailing_whitespace_linter,style default
3443
undesirable_function_linter,style efficiency configurable robustness best_practices
3544
undesirable_operator_linter,style efficiency configurable robustness best_practices
3645
unneeded_concatenation_linter,style readability efficiency
37-
assignment_spaces_linter,style readability
38-
duplicate_argument_linter,correctness common_mistakes configurable
39-
missing_argument_linter,correctness common_mistakes configurable
40-
missing_package_linter,robustness common_mistakes
41-
namespace_linter,correctness robustness configurable
42-
paren_body_linter,style readability default
43-
pipe_call_linter,style readability
44-
sprintf_linter,correctness common_mistakes

man/best_practices_linters.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/expect_type_linter.Rd

Lines changed: 20 additions & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/linters.Rd

Lines changed: 3 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/package_development_linters.Rd

Lines changed: 1 addition & 0 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Lines changed: 62 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,62 @@
1+
test_that("expect_type_linter skips allowed usages", {
2+
# expect_type doesn't have an inverted version
3+
expect_lint("expect_true(!is.numeric(x))", NULL, expect_type_linter())
4+
# NB: also applies to tinytest, but it's sufficient to test testthat
5+
expect_lint("testthat::expect_true(!is.numeric(x))", NULL, expect_type_linter())
6+
7+
# other is.<x> calls are not suitable for expect_type in particular
8+
expect_lint("expect_true(is.data.frame(x))", NULL, expect_type_linter())
9+
10+
# expect_type(x, ...) cannot be cleanly used here:
11+
expect_lint("expect_true(typeof(x) %in% c('builtin', 'closure'))", NULL, expect_type_linter())
12+
})
13+
14+
test_that("expect_type_linter blocks simple disallowed usages", {
15+
expect_lint(
16+
"expect_equal(typeof(x), 'double')",
17+
rex::rex("expect_type(x, t) is better than expect_equal(typeof(x), t)"),
18+
expect_type_linter()
19+
)
20+
21+
# expect_identical is treated the same as expect_equal
22+
expect_lint(
23+
"testthat::expect_identical(typeof(x), 'language')",
24+
rex::rex("expect_type(x, t) is better than expect_identical(typeof(x), t)"),
25+
expect_type_linter()
26+
)
27+
28+
# different equivalent usage
29+
expect_lint(
30+
"expect_true(is.complex(foo(x)))",
31+
rex::rex("expect_type(x, t) is better than expect_true(is.<t>(x))"),
32+
expect_type_linter()
33+
)
34+
35+
# yoda test with clear expect_type replacement
36+
expect_lint(
37+
"expect_equal('integer', typeof(x))",
38+
rex::rex("expect_type(x, t) is better than expect_equal(typeof(x), t)"),
39+
expect_type_linter()
40+
)
41+
})
42+
43+
44+
skip_if_not_installed("patrick")
45+
local({
46+
# test for lint errors appropriately raised for all is.<type> calls
47+
is_types <- c(
48+
"raw", "logical", "integer", "double", "complex", "character", "list",
49+
"numeric", "function", "primitive", "environment", "pairlist", "promise",
50+
"language", "call", "name", "symbol", "expression"
51+
)
52+
patrick::with_parameters_test_that(
53+
"expect_type_linter catches expect_true(is.<base type>)",
54+
expect_lint(
55+
sprintf("expect_true(is.%s(x))", is_type),
56+
rex::rex("expect_type(x, t) is better than expect_true(is.<t>(x))"),
57+
expect_type_linter()
58+
),
59+
.test_name = is_types,
60+
is_type = is_types
61+
)
62+
})

0 commit comments

Comments
 (0)