1
- # ' Force `&&` conditions in `expect_true()` and `expect_false()` to be written separately
1
+ # ' Force `&&` conditions to be written separately where appropriate
2
2
# '
3
3
# ' For readability of test outputs, testing only one thing per call to
4
4
# ' [testthat::expect_true()] is preferable, i.e.,
7
7
# '
8
8
# ' Similar reasoning applies to `&&` usage inside [stopifnot()] and `assertthat::assert_that()` calls.
9
9
# '
10
+ # ' Relatedly, `dplyr::filter(DF, A & B)` is the same as `dplyr::filter(DF, A, B)`, but the
11
+ # ' latter will be more readable / easier to format for long conditions. Note that this linter
12
+ # ' assumes usages of `filter()` are `dplyr::filter()`; if you're using another function named `filter()`,
13
+ # ' e.g. [stats::filter()], please namespace-qualify it to avoid false positives.
14
+ # '
10
15
# ' @param allow_named_stopifnot Logical, `TRUE` by default. If `FALSE`, "named" calls to `stopifnot()`,
11
16
# ' available since R 4.0.0 to provide helpful messages for test failures, are also linted.
12
17
# '
44
49
conjunct_test_linter <- function (allow_named_stopifnot = TRUE ) {
45
50
expect_true_assert_that_xpath <- "
46
51
//SYMBOL_FUNCTION_CALL[text() = 'expect_true' or text() = 'assert_that']
47
- /parent::expr
48
- /following-sibling::expr[1][AND2]
52
+ /parent::expr
53
+ /following-sibling::expr[1][AND2]
54
+ /parent::expr
49
55
"
50
56
named_stopifnot_condition <- if (allow_named_stopifnot ) " and not(preceding-sibling::*[1][self::EQ_SUB])" else " "
51
57
stopifnot_xpath <- glue("
52
58
//SYMBOL_FUNCTION_CALL[text() = 'stopifnot']
53
- /parent::expr
54
- /following-sibling::expr[1][AND2 {named_stopifnot_condition}]
59
+ /parent::expr
60
+ /following-sibling::expr[1][AND2 {named_stopifnot_condition}]
61
+ /parent::expr
55
62
" )
56
63
expect_false_xpath <- "
57
64
//SYMBOL_FUNCTION_CALL[text() = 'expect_false']
58
- /parent::expr
59
- /following-sibling::expr[1][OR2]
65
+ /parent::expr
66
+ /following-sibling::expr[1][OR2]
67
+ /parent::expr
60
68
"
61
- xpath <- paste0(
62
- c(expect_true_assert_that_xpath , stopifnot_xpath , expect_false_xpath ),
63
- " /parent::expr" ,
64
- collapse = " | "
69
+ test_xpath <- paste(
70
+ expect_true_assert_that_xpath ,
71
+ stopifnot_xpath ,
72
+ expect_false_xpath ,
73
+ sep = " | "
65
74
)
66
75
76
+ filter_xpath <- "
77
+ //SYMBOL_FUNCTION_CALL[text() = 'filter']
78
+ /parent::expr[not(SYMBOL_PACKAGE[text() != 'dplyr'])]
79
+ /parent::expr
80
+ /expr[AND]
81
+ "
82
+
67
83
Linter(function (source_expression ) {
68
84
# need the full file to also catch usages at the top level
69
85
if (! is_lint_level(source_expression , " file" )) {
@@ -72,24 +88,37 @@ conjunct_test_linter <- function(allow_named_stopifnot = TRUE) {
72
88
73
89
xml <- source_expression $ full_xml_parsed_content
74
90
75
- bad_expr <- xml_find_all(xml , xpath )
76
-
77
- if (length(bad_expr ) == 0L ) {
78
- return (list ())
79
- }
91
+ test_expr <- xml_find_all(xml , test_xpath )
80
92
81
- matched_fun <- xp_call_name(bad_expr )
82
- operator <- xml_find_chr(bad_expr , " string(expr/*[self::AND2 or self::OR2])" )
93
+ matched_fun <- xp_call_name(test_expr )
94
+ operator <- xml_find_chr(test_expr , " string(expr/*[self::AND2 or self::OR2])" )
83
95
replacement_fmt <- ifelse(
84
96
matched_fun %in% c(" expect_true" , " expect_false" ),
85
97
" write multiple expectations like %1$s(A) and %1$s(B)" ,
86
98
" write multiple conditions like %s(A, B)."
87
99
)
88
100
lint_message <- paste(
89
101
sprintf(" Instead of %s(A %s B)," , matched_fun , operator ),
90
- sprintf(replacement_fmt , matched_fun ),
102
+ # as.character() needed for 0-lint case where ifelse(logical(0)) returns logical(0)
103
+ sprintf(as.character(replacement_fmt ), matched_fun ),
91
104
" The latter will produce better error messages in the case of failure."
92
105
)
93
- xml_nodes_to_lints(bad_expr , source_expression , lint_message = lint_message , type = " warning" )
106
+ test_lints <- xml_nodes_to_lints(
107
+ test_expr ,
108
+ source_expression = source_expression ,
109
+ lint_message = lint_message ,
110
+ type = " warning"
111
+ )
112
+
113
+ filter_expr <- xml_find_all(xml , filter_xpath )
114
+
115
+ filter_lints <- xml_nodes_to_lints(
116
+ filter_expr ,
117
+ source_expression = source_expression ,
118
+ lint_message = " Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B)." ,
119
+ type = " warning"
120
+ )
121
+
122
+ c(test_lints , filter_lints )
94
123
})
95
124
}
0 commit comments