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(.)]`.
2
6
# '
3
7
# ' [sort()] is the dedicated option to sort a list or vector. It is more legible
4
8
# ' and around twice as fast as `.[order(.)]`, with the gap in performance
5
9
# ' growing with the vector size.
6
10
# '
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
+ # '
7
22
# ' @examples
8
23
# ' # will produce lints
9
24
# ' lint(
16
31
# ' linters = sort_linter()
17
32
# ' )
18
33
# '
34
+ # ' lint(
35
+ # ' text = "sort(x) == x",
36
+ # ' linters = sort_linter()
37
+ # ' )
38
+ # '
19
39
# ' # okay
20
40
# ' lint(
21
41
# ' text = "x[sample(order(x))]",
27
47
# ' linters = sort_linter()
28
48
# ' )
29
49
# '
50
+ # ' lint(
51
+ # ' text = "sort(x, decreasing = TRUE) == x",
52
+ # ' linters = sort_linter()
53
+ # ' )
54
+ # '
30
55
# ' # If you are sorting several objects based on the order of one of them, such
31
56
# ' # as:
32
57
# ' x <- sample(1:26)
44
69
# ' @seealso [linters] for a complete list of linters available in lintr.
45
70
# ' @export
46
71
sort_linter <- function () {
47
- xpath <- "
72
+ order_xpath <- "
48
73
//OP-LEFT-BRACKET
49
74
/following-sibling::expr[1][
50
75
expr[1][
@@ -57,6 +82,17 @@ sort_linter <- function() {
57
82
]
58
83
"
59
84
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
+
60
96
args_xpath <- " .//SYMBOL_SUB[text() = 'method' or
61
97
text() = 'decreasing' or
62
98
text() = 'na.last']"
@@ -70,45 +106,51 @@ sort_linter <- function() {
70
106
71
107
xml <- source_expression $ xml_parsed_content
72
108
73
- bad_expr <- xml_find_all(xml , xpath )
109
+ order_expr <- xml_find_all(xml , order_xpath )
74
110
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
+ ))
81
115
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 ))
87
117
88
118
# Reconstruct new argument call for each expression separately
89
- args <- vapply(bad_expr , function (e ) {
119
+ args <- vapply(order_expr , function (e ) {
90
120
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 ))
94
122
if (! " na.last" %in% arg_names ) {
95
123
arg_names <- c(arg_names , " na.last" )
96
124
arg_values <- c(arg_values , " TRUE" )
97
125
}
98
- toString( paste(arg_names , " =" , arg_values ) )
126
+ paste(arg_names , " =" , arg_values , collapse = " , " )
99
127
}, character (1L ))
100
128
101
- new_call <- sprintf(
102
- " sort(%1$s, %2$s)" ,
103
- var ,
104
- args
105
- )
129
+ new_call <- sprintf(" sort(%s, %s)" , var , args )
106
130
107
- xml_nodes_to_lints(
108
- bad_expr ,
131
+ order_lints <- xml_nodes_to_lints(
132
+ order_expr ,
109
133
source_expression = source_expression ,
110
134
lint_message = paste0(new_call , " is better than " , orig_call , " ." ),
111
135
type = " warning"
112
136
)
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 )
113
155
})
114
156
}
0 commit comments