Skip to content

Commit 26eba6f

Browse files
Merge e1eca60 into 3d9e6d7
2 parents 3d9e6d7 + e1eca60 commit 26eba6f

File tree

4 files changed

+130
-27
lines changed

4 files changed

+130
-27
lines changed

NEWS.md

+1
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@
2323
+ `yoda_test_linter()`
2424
* `sprintf_linter()` is pipe-aware, so that `x %>% sprintf(fmt = "%s")` no longer lints (#1943, @MichaelChirico).
2525
* `line_length_linter()` helpfully includes the line length in the lint message (#2057, @MichaelChirico).
26+
* `sort_linter()` checks for code like `x == sort(x)` which is better served by using the function `is.unsorted()` (part of #884, @MichaelChirico).
2627
* `paste_linter()` gains detection for file paths that are better constructed with `file.path()`, e.g. `paste0(dir, "/", file)` would be better as `file.path(dir, file)` (part of #884, @MichaelChirico).
2728

2829
### New linters

R/sort_linter.R

+68-26
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,24 @@
1-
#' Require usage of `sort()` over `.[order(.)]`
1+
#' Check for common mistakes around sorting vectors
2+
#'
3+
#' This linter checks for some common mistakes when using [order()] or [sort()].
4+
#'
5+
#' First, it requires usage of `sort()` over `.[order(.)]`.
26
#'
37
#' [sort()] is the dedicated option to sort a list or vector. It is more legible
48
#' and around twice as fast as `.[order(.)]`, with the gap in performance
59
#' growing with the vector size.
610
#'
11+
#' Second, it requires usage of [is.unsorted()] over equivalents using `sort()`.
12+
#'
13+
#' The base function `is.unsorted()` exists to test the sortedness of a vector.
14+
#' Prefer it to inefficient and less-readable equivalents like
15+
#' `x != sort(x)`. The same goes for checking `x == sort(x)` -- use
16+
#' `!is.unsorted(x)` instead.
17+
#'
18+
#' Moreover, use of `x == sort(x)` can be risky because [sort()] drops missing
19+
#' elements by default, meaning `==` might end up trying to compare vectors
20+
#' of differing lengths.
21+
#'
722
#' @examples
823
#' # will produce lints
924
#' lint(
@@ -16,6 +31,11 @@
1631
#' linters = sort_linter()
1732
#' )
1833
#'
34+
#' lint(
35+
#' text = "sort(x) == x",
36+
#' linters = sort_linter()
37+
#' )
38+
#'
1939
#' # okay
2040
#' lint(
2141
#' text = "x[sample(order(x))]",
@@ -27,6 +47,11 @@
2747
#' linters = sort_linter()
2848
#' )
2949
#'
50+
#' lint(
51+
#' text = "sort(x, decreasing = TRUE) == x",
52+
#' linters = sort_linter()
53+
#' )
54+
#'
3055
#' # If you are sorting several objects based on the order of one of them, such
3156
#' # as:
3257
#' x <- sample(1:26)
@@ -44,7 +69,7 @@
4469
#' @seealso [linters] for a complete list of linters available in lintr.
4570
#' @export
4671
sort_linter <- function() {
47-
xpath <- "
72+
order_xpath <- "
4873
//OP-LEFT-BRACKET
4974
/following-sibling::expr[1][
5075
expr[1][
@@ -57,6 +82,17 @@ sort_linter <- function() {
5782
]
5883
"
5984

85+
sorted_xpath <- "
86+
//SYMBOL_FUNCTION_CALL[text() = 'sort']
87+
/parent::expr
88+
/parent::expr[not(SYMBOL_SUB)]
89+
/parent::expr[
90+
(EQ or NE)
91+
and expr/expr = expr
92+
]
93+
"
94+
95+
6096
args_xpath <- ".//SYMBOL_SUB[text() = 'method' or
6197
text() = 'decreasing' or
6298
text() = 'na.last']"
@@ -70,45 +106,51 @@ sort_linter <- function() {
70106

71107
xml <- source_expression$xml_parsed_content
72108

73-
bad_expr <- xml_find_all(xml, xpath)
109+
order_expr <- xml_find_all(xml, order_xpath)
74110

75-
var <- xml_text(
76-
xml_find_first(
77-
bad_expr,
78-
".//SYMBOL_FUNCTION_CALL[text() = 'order']/parent::expr[1]/following-sibling::expr[1]"
79-
)
80-
)
111+
var <- xml_text(xml_find_first(
112+
order_expr,
113+
".//SYMBOL_FUNCTION_CALL[text() = 'order']/parent::expr[1]/following-sibling::expr[1]"
114+
))
81115

82-
orig_call <- sprintf(
83-
"%1$s[%2$s]",
84-
var,
85-
get_r_string(bad_expr)
86-
)
116+
orig_call <- sprintf("%s[%s]", var, get_r_string(order_expr))
87117

88118
# Reconstruct new argument call for each expression separately
89-
args <- vapply(bad_expr, function(e) {
119+
args <- vapply(order_expr, function(e) {
90120
arg_names <- xml_text(xml_find_all(e, args_xpath))
91-
arg_values <- xml_text(
92-
xml_find_all(e, arg_values_xpath)
93-
)
121+
arg_values <- xml_text(xml_find_all(e, arg_values_xpath))
94122
if (!"na.last" %in% arg_names) {
95123
arg_names <- c(arg_names, "na.last")
96124
arg_values <- c(arg_values, "TRUE")
97125
}
98-
toString(paste(arg_names, "=", arg_values))
126+
paste(arg_names, "=", arg_values, collapse = ", ")
99127
}, character(1L))
100128

101-
new_call <- sprintf(
102-
"sort(%1$s, %2$s)",
103-
var,
104-
args
105-
)
129+
new_call <- sprintf("sort(%s, %s)", var, args)
106130

107-
xml_nodes_to_lints(
108-
bad_expr,
131+
order_lints <- xml_nodes_to_lints(
132+
order_expr,
109133
source_expression = source_expression,
110134
lint_message = paste0(new_call, " is better than ", orig_call, "."),
111135
type = "warning"
112136
)
137+
138+
sorted_expr <- xml_find_all(xml, sorted_xpath)
139+
140+
sorted_op <- xml_text(xml_find_first(sorted_expr, "*[2]"))
141+
lint_message <- ifelse(
142+
sorted_op == "==",
143+
"Use !is.unsorted(x) to test the sortedness of a vector.",
144+
"Use is.unsorted(x) to test the unsortedness of a vector."
145+
)
146+
147+
sorted_lints <- xml_nodes_to_lints(
148+
sorted_expr,
149+
source_expression = source_expression,
150+
lint_message = lint_message,
151+
type = "warning"
152+
)
153+
154+
c(order_lints, sorted_lints)
113155
})
114156
}

man/sort_linter.Rd

+27-1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-sort_linter.R

+34
Original file line numberDiff line numberDiff line change
@@ -79,3 +79,37 @@ test_that("sort_linter works with multiple lints in a single expression", {
7979
)
8080

8181
})
82+
83+
test_that("sort_linter skips usages calling sort arguments", {
84+
linter <- sort_linter()
85+
86+
# any arguments to sort --> not compatible
87+
expect_lint("sort(x, decreasing = TRUE) == x", NULL, linter)
88+
expect_lint("sort(x, na.last = TRUE) != x", NULL, linter)
89+
expect_lint("sort(x, method_arg = TRUE) == x", NULL, linter)
90+
})
91+
92+
test_that("sort_linter skips when inputs don't match", {
93+
linter <- sort_linter()
94+
95+
expect_lint("sort(x) == y", NULL, linter)
96+
expect_lint("sort(x) == foo(x)", NULL, linter)
97+
expect_lint("sort(foo(x)) == x", NULL, linter)
98+
})
99+
100+
test_that("sort_linter blocks simple disallowed usages", {
101+
linter <- sort_linter()
102+
unsorted_msg <- rex::rex("Use is.unsorted(x) to test the unsortedness of a vector.")
103+
sorted_msg <- rex::rex("Use !is.unsorted(x) to test the sortedness of a vector.")
104+
105+
expect_lint("sort(x) == x", sorted_msg, linter)
106+
107+
# argument order doesn't matter
108+
expect_lint("x == sort(x)", sorted_msg, linter)
109+
110+
# inverted version
111+
expect_lint("sort(x) != x", unsorted_msg, linter)
112+
113+
# expression matching
114+
expect_lint("sort(foo(x)) == foo(x)", sorted_msg, linter)
115+
})

0 commit comments

Comments
 (0)