Skip to content

Commit

Permalink
Add potential sequence() lints to seq_linter() (#2618)
Browse files Browse the repository at this point in the history
* Draft sequence_linter linter

* Fold sequence_linter() into seq_linter()

* Add tests

* Add NEWS bullet

* Switch to xml_find_function_calls

* Change element order in xpath

* Support lapply(x, seq)

* Simplify xpath

* Do not lint seq() calls with extra arguments

* Edit false positive example

* Add more info about new lints in NEWS

* update

* Update NEWS.md

* add Hugo to DESCRIPTION (and clean it up)

* change DESCRIPTION --> change Rd

---------

Co-authored-by: Michael Chirico <[email protected]>
Co-authored-by: Michael Chirico <[email protected]>
  • Loading branch information
3 people authored Mar 4, 2025
1 parent 500a38c commit cf9758a
Show file tree
Hide file tree
Showing 6 changed files with 84 additions and 8 deletions.
13 changes: 8 additions & 5 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,17 @@ Version: 3.2.0.9000
Authors@R: c(
person("Jim", "Hester", , role = "aut"),
person("Florent", "Angly", role = "aut",
comment = "fangly"),
comment = c(GitHub = "fangly")),
person("Russ", "Hyde", role = "aut"),
person("Michael", "Chirico", email = "[email protected]", role = c("aut", "cre")),
person("Michael", "Chirico", email = "[email protected]", role = c("aut", "cre"),
comment = c(ORCID = "0000-0003-0787-087X")),
person("Kun", "Ren", role = "aut"),
person("Alexander", "Rosenstock", role = "aut",
comment = "AshesITR"),
person("Indrajeet", "Patil", , "[email protected]", role = "aut",
comment = c(ORCID = "0000-0003-1995-6531", Twitter = "@patilindrajeets"))
comment = c(GitHub = "AshesITR")),
person("Indrajeet", "Patil", email = "[email protected]", role = "aut",
comment = c(ORCID = "0000-0003-1995-6531", Twitter = "@patilindrajeets")),
person("Hugo", "Gruson", role = "aut",
comment = c(ORCID = "0000-0002-4094-1476"))
)
Description: Checks adherence to a given style, syntax errors and possible
semantic issues. Supports on the fly checking of R code edited with
Expand Down
4 changes: 3 additions & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,9 @@
## New and improved features

* `brace_linter()`' has a new argument `function_bodies` (default `"multi_line"`) which controls when to require function bodies to be wrapped in curly braces, with the options `"always"`, `"multi_line"` (only require curly braces when a function body spans multiple lines), `"not_inline"` (only require curly braces when a function body starts on a new line) and `"never"` (#1807, #2240, @salim-b).
* `seq_linter()` recommends using `seq_along(x)` instead of `seq_len(length(x))` (#2577, @MichaelChirico).
* `seq_linter()`:
+ recommends using `seq_along(x)` instead of `seq_len(length(x))` (#2577, @MichaelChirico).
+ recommends using `sequence()` instead of `unlist(lapply(ints, seq))` (#2618, @Bisaloo)
* `undesirable_operator_linter()` lints operators in prefix form, e.g. `` `%%`(x, 2)`` (#1910, @MichaelChirico). Disable this by setting `call_is_undesirable=FALSE`.
* `indentation_linter()` handles `for` un-braced for loops correctly (#2564, @MichaelChirico).
* Setting `exclusions` supports globs like `knitr*` to exclude files/directories with a pattern (#1554, @MichaelChirico).
Expand Down
32 changes: 31 additions & 1 deletion R/seq_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,11 @@
#' linters = seq_linter()
#' )
#'
#' lint(
#' text = "unlist(lapply(x, seq_len))",
#' linters = seq_linter()
#' )
#'
#' # okay
#' lint(
#' text = "seq_along(x)",
Expand All @@ -53,6 +58,11 @@
#' linters = seq_linter()
#' )
#'
#' lint(
#' text = "sequence(x)",
#' linters = seq_linter()
#' )
#'
#' @evalRd rd_tags("seq_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
Expand Down Expand Up @@ -80,6 +90,17 @@ seq_linter <- function() {
parent::expr[expr/expr/SYMBOL_FUNCTION_CALL[text() = 'length']]
"

map_funcs <- c("sapply", "lapply", "map")
seq_funcs <- xp_text_in_table(c("seq_len", "seq"))
# count(expr) = 3 because we only want seq() calls without extra arguments
sequence_xpath <- glue("
parent::expr[
count(expr) = 3
and expr/SYMBOL[ {seq_funcs} ]
and preceding-sibling::expr/SYMBOL_FUNCTION_CALL[text() = 'unlist']
]
")

## The actual order of the nodes is document order
## In practice we need to handle length(x):1
get_fun <- function(expr, n) {
Expand Down Expand Up @@ -138,6 +159,15 @@ seq_linter <- function() {
type = "warning"
)

c(seq_lints, seq_len_lints)
xml_map_calls <- source_expression$xml_find_function_calls(map_funcs)
potential_sequence_calls <- xml_find_all(xml_map_calls, sequence_xpath)
sequence_lints <- xml_nodes_to_lints(
potential_sequence_calls,
source_expression,
"Use sequence() to generate a concatenated sequence of seq_len().",
type = "warning"
)

c(seq_lints, seq_len_lints, sequence_lints)
})
}
3 changes: 2 additions & 1 deletion man/lintr-package.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

10 changes: 10 additions & 0 deletions man/seq_linter.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

30 changes: 30 additions & 0 deletions tests/testthat/test-seq_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -123,6 +123,24 @@ test_that("reverse seq is ok", {
)
})

test_that("finds potential sequence() replacements", {
linter <- seq_linter()
lint_msg <- rex::rex("Use sequence()")

expect_lint("unlist(lapply(x, seq_len))", lint_msg, linter)

expect_lint("unlist(lapply(x, seq))", lint_msg, linter)

# Even for prefixed purrr:: calls
expect_lint("unlist(purrr::map(x, seq_len))", lint_msg, linter)
})

test_that("sequence() is not recommended for complex seq() calls", {
linter <- seq_linter()

expect_no_lint("unlist(lapply(x, seq, from = 2))", linter)
})

test_that("Message vectorization works for multiple lints", {
linter <- seq_linter()

Expand Down Expand Up @@ -173,6 +191,18 @@ test_that("Message vectorization works for multiple lints", {
),
linter
)

expect_lint(
trim_some("{
1:NROW(x)
unlist(lapply(y, seq_len))
}"),
list(
list(rex::rex("seq_len(NROW(...))", anything, "1:NROW(...)"), line_number = 2L),
list(rex::rex("sequence()"), line_number = 3L)
),
linter
)
})

test_that("Message recommends rev() correctly", {
Expand Down

0 comments on commit cf9758a

Please sign in to comment.