Skip to content

Commit

Permalink
Merge branch 'main' into f1830-complex-conditional-linter
Browse files Browse the repository at this point in the history
  • Loading branch information
IndrajeetPatil authored Feb 3, 2025
2 parents 421c1db + dbfe81b commit c04e2f6
Show file tree
Hide file tree
Showing 43 changed files with 251 additions and 146 deletions.
39 changes: 39 additions & 0 deletions .github/CONTRIBUTING.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
# Contributing to `{lintr}`

This outlines how to propose a change to `{lintr}`. For a detailed discussion on contributing to this, r-lib, and other tidyverse packages, please see the [development contributing guide](https://rstd.io/tidy-contrib) and our [code review principles](https://code-review.tidyverse.org/).

## Fixing typos

You can fix typos, spelling mistakes, or grammatical errors in the documentation directly using the GitHub web interface, as long as the changes are made in the _source_ file. This generally means you'll need to edit [roxygen2 comments](https://roxygen2.r-lib.org/articles/roxygen2.html) in an `.R`, not a `.Rd` file. You can find the `.R` file that generates the `.Rd` by reading the comment in the first line.

## Bigger changes

If you want to make a bigger change, it's a good idea to first file an issue and make sure someone from the team agrees that it’s needed. If you’ve found a bug, please file an issue that illustrates the bug with a minimal [reprex](https://www.tidyverse.org/help/#reprex) (this will also help you write a unit test, if needed). See the tidyverse guide on [how to create a great issue](https://code-review.tidyverse.org/issues/) for more advice.

### Adding a new linter

If you wish to contribute a new linter, the [Creating new linters](https://lintr.r-lib.org/articles/creating_linters.html) article serves as a comprehensive guide.

### Pull request process

* Fork the package and clone onto your computer. If you haven't done this before, we recommend using `usethis::create_from_github("r-lib/lintr", fork = TRUE)`.

* Install all development dependencies with `devtools::install_dev_deps()`, and then make sure the package passes R CMD check by running `devtools::check()`. If R CMD check doesn't pass cleanly, it's a good idea to ask for help before continuing.

* Create a Git branch for your pull request (PR). We recommend using `usethis::pr_init("brief-description-of-change")`. At a minimum, please avoid submitting PRs from your fork's `main` branch` as this can make the review process more complicated.

* Make your changes, commit them to Git, and create a PR using `usethis::pr_push()`. Follow the prompts in your browser to complete the process. Use a concise title for your PR that summarizes the change, and include `Fixes #issue-number` in the PR _description_. Doing so will automatically close the linked issue when the PR is merged. For complicated changes, add a textual overview of what your PR does in the description. Consider breaking up large PRs into a chain of more digestible+focused smaller PRs.

* For user-facing changes, add a bullet appropriately in the top section of `NEWS.md` (i.e. below the first header). Follow the style described in <https://style.tidyverse.org/news.html>. Most importantly, your audience for NEWS items is a package user, i.e., _not_ a package developer.

### Code style

* New code should follow the tidyverse [style guide](https://style.tidyverse.org). You can use the [styler](https://CRAN.R-project.org/package=styler) package to apply these styles.

* We use [roxygen2](https://cran.r-project.org/package=roxygen2), with [Markdown syntax](https://cran.r-project.org/web/packages/roxygen2/vignettes/rd-formatting.html), for documentation.

* We use [testthat](https://cran.r-project.org/package=testthat) for unit tests. Contributions with test cases included are easier to accept.

## Code of Conduct

Please note that the lintr project is released with a [Contributor Code of Conduct](CODE_OF_CONDUCT.md). By contributing to this project you agree to abide by its terms.
2 changes: 1 addition & 1 deletion .github/workflows/pkgdown.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ jobs:

- name: Deploy to GitHub pages 🚀
if: github.event_name != 'pull_request'
uses: JamesIves/github-pages-deploy-action@v4.6.9
uses: JamesIves/github-pages-deploy-action@v4.7.2
with:
clean: false
branch: gh-pages
Expand Down
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ BugReports: https://github.com/r-lib/lintr/issues
Depends:
R (>= 4.0)
Imports:
backports (>= 1.1.7),
backports (>= 1.4.0),
cli (>= 3.4.0),
codetools,
digest,
Expand Down
6 changes: 3 additions & 3 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,15 @@

S3method("[",lints)
S3method(as.data.frame,lints)
S3method(data.table::as.data.table,lints)
S3method(format,lint)
S3method(format,lints)
S3method(names,lints)
S3method(print,lint)
S3method(print,lints)
S3method(split,lints)
S3method(summary,lints)
S3method(tibble::as_tibble,lints)
export(Lint)
export(Linter)
export(T_and_F_symbol_linter)
Expand Down Expand Up @@ -177,17 +179,15 @@ importFrom(rex,re_matches)
importFrom(rex,re_substitutes)
importFrom(rex,regex)
importFrom(rex,rex)
importFrom(stats,complete.cases)
importFrom(stats,na.omit)
importFrom(tools,R_user_dir)
importFrom(utils,capture.output)
importFrom(utils,getParseData)
importFrom(utils,getTxtProgressBar)
importFrom(utils,globalVariables)
importFrom(utils,head)
importFrom(utils,relist)
importFrom(utils,setTxtProgressBar)
importFrom(utils,tail)
importFrom(utils,txtProgressBar)
importFrom(xml2,as_list)
importFrom(xml2,xml_attr)
importFrom(xml2,xml_children)
Expand Down
5 changes: 3 additions & 2 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@
+ `source_file=` argument to `ids_with_token()` and `with_id()`.
+ Passing linters by name or as non-`"linter"`-classed functions.
+ `linter=` argument of `Lint()`.
+ Linters `closed_curly_linter()`, `open_curly_linter()`, `paren_brace_linter()`, and `semicolon_terminator_linter()`..
+ `with_defaults()`.
+ Linters `closed_curly_linter()`, `open_curly_linter()`, `paren_brace_linter()`, and `semicolon_terminator_linter()`.
+ Helper `with_defaults()`.
Expand Down Expand Up @@ -61,6 +60,7 @@
* `paste_linter()` is extended to recommend using `paste()` instead of `paste0()` for simply aggregating a character vector with `collapse=`, i.e., when `sep=` is irrelevant (#1108, @MichaelChirico).
* `expect_no_lint()` was added as new function to cover the typical use case of expecting no lint message, akin to the recent {testthat} functions like `expect_no_warning()` (#2580, @F-Noelle).
* `lint()` and friends emit a message if no lints are found (#2643, @IndrajeetPatil).
* `{lintr}` now has a hex sticker (https://github.com/rstudio/hex-stickers/pull/110). Thank you, @gregswinehart!

### New linters

Expand Down Expand Up @@ -91,9 +91,10 @@

## Notes

* All user-facing messages are now prepared using the `{cli}` package (#2418, @IndrajeetPatil). All messages have been reviewed and updated to be more informative and consistent.
* All user-facing messages (including progress bars) are now prepared using the `{cli}` package (#2418 and #2641, @IndrajeetPatil). All messages have been reviewed and updated to be more informative and consistent.
* File locations in lints and error messages contain clickable hyperlinks to improve code navigation (#2645, #2588, @olivroy).
* {lintr} now depends on R version 4.0.0. It already does so implicitly due to recursive upstream dependencies requiring this version; we've simply made that dependency explicit and up-front (#2569, @MichaelChirico).
* Some code with parameters accepting regular expressions is less strict about whether there are capture groups (#2678, @MichaelChirico). In particular, this affects `unreachable_code_linter(allow_comment_regex=)` and `expect_lint(checks=)`.

# lintr 3.1.2

Expand Down
8 changes: 1 addition & 7 deletions R/expect_lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -105,16 +105,10 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
)
# deparse ensures that NULL, list(), etc are handled gracefully
ok <- if (field == "message") {
re_matches(value, check)
re_matches_logical(value, check)
} else {
isTRUE(all.equal(value, check))
}
if (!is.logical(ok)) {
cli_abort(c(
x = "Invalid regex result. Did you mistakenly have a capture group in the regex?",
i = "You can match parentheses with a character class, i.e. inside `[]`."
))
}
testthat::expect(ok, msg)
})
},
Expand Down
3 changes: 3 additions & 0 deletions R/indentation_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -257,9 +257,12 @@ indentation_linter <- function(indent = 2L, hanging_indent_style = c("tidy", "al
}

# Only lint non-empty lines if the indentation level doesn't match.
# TODO: remove styler ignore directives once tidyverse/style/issues/197 is resolved
# styler: off
bad_lines <- which(indent_levels != expected_indent_levels &
nzchar(trimws(source_expression$file_lines)) &
!in_str_const)
# styler: on
if (length(bad_lines) > 0L) {
# Suppress consecutive lints with the same indentation difference, to not generate an excessive number of lints
is_consecutive_lint <- c(FALSE, diff(bad_lines) == 1L)
Expand Down
44 changes: 22 additions & 22 deletions R/lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,14 @@
#' @return An object of class `c("lints", "list")`, each element of which is a `"list"` object.
#'
#' @examples
#' # linting inline-code
#' lint("a = 123\n")
#' lint(text = "a = 123")
#'
#' # linting a file
#' f <- tempfile()
#' writeLines("a=1", f)
#' lint(f) # linting a file
#' lint("a = 123\n") # linting inline-code
#' lint(text = "a = 123") # linting inline-code
#' lint(f)
#' unlink(f)
#'
#' @export
Expand Down Expand Up @@ -182,20 +185,24 @@ lint_dir <- function(path = ".", ...,
return(lints)
}

pb <- if (isTRUE(show_progress)) {
txtProgressBar(max = length(files), style = 3L)
if (isTRUE(show_progress)) {
lints <- lapply(
# NB: This cli API is experimental (https://github.com/r-lib/cli/issues/709)
cli::cli_progress_along(files, name = "Running linters"),
function(idx) {
lint(files[idx], ..., parse_settings = FALSE, exclusions = exclusions)
}
)
} else {
lints <- lapply(
files,
function(file) { # nolint: unnecessary_lambda_linter.
lint(file, ..., parse_settings = FALSE, exclusions = exclusions)
}
)
}

lints <- flatten_lints(lapply(
files,
function(file) {
maybe_report_progress(pb)
lint(file, ..., parse_settings = FALSE, exclusions = exclusions)
}
))

if (!is.null(pb)) close(pb)

lints <- flatten_lints(lints)
lints <- reorder_lints(lints)

if (relative_path) {
Expand Down Expand Up @@ -688,13 +695,6 @@ has_positional_logical <- function(dots) {
!nzchar(names2(dots)[1L])
}

maybe_report_progress <- function(pb) {
if (is.null(pb)) {
return(invisible())
}
setTxtProgressBar(pb, getTxtProgressBar(pb) + 1L)
}

maybe_append_error_lint <- function(lints, error, lint_cache, filename) {
if (is_lint(error)) {
error$linter <- "error"
Expand Down
5 changes: 2 additions & 3 deletions R/lintr-package.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,9 @@
#' @importFrom cli cli_inform cli_abort cli_warn
#' @importFrom glue glue glue_collapse
#' @importFrom rex rex regex re_matches re_substitutes character_class
#' @importFrom stats na.omit
#' @importFrom stats complete.cases na.omit
#' @importFrom tools R_user_dir
#' @importFrom utils capture.output getParseData getTxtProgressBar globalVariables head relist
#' setTxtProgressBar tail txtProgressBar
#' @importFrom utils capture.output getParseData globalVariables head relist tail
#' @importFrom xml2 as_list
#' xml_attr xml_children xml_find_all xml_find_chr xml_find_lgl xml_find_num xml_find_first xml_name xml_text
## lintr namespace: end
Expand Down
2 changes: 2 additions & 0 deletions R/methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -173,6 +173,7 @@ as.data.frame.lints <- function(x, row.names = NULL, optional = FALSE, ...) { #
)
}

#' @exportS3Method tibble::as_tibble
as_tibble.lints <- function(x, ..., # nolint: object_name_linter.
.rows = NULL,
.name_repair = c("check_unique", "unique", "universal", "minimal"),
Expand All @@ -181,6 +182,7 @@ as_tibble.lints <- function(x, ..., # nolint: object_name_linter.
tibble::as_tibble(as.data.frame(x), ..., .rows = .rows, .name_repair = .name_repair, rownames = rownames)
}

#' @exportS3Method data.table::as.data.table
as.data.table.lints <- function(x, keep.rownames = FALSE, ...) { # nolint: object_name_linter.
stopifnot(requireNamespace("data.table", quietly = TRUE))
data.table::setDT(as.data.frame(x), keep.rownames = keep.rownames, ...)
Expand Down
5 changes: 3 additions & 2 deletions R/nested_pipe_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -51,8 +51,9 @@
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
nested_pipe_linter <- function(
allow_inline = TRUE,
allow_outer_calls = c("try", "tryCatch", "withCallingHandlers")) {
allow_inline = TRUE,
allow_outer_calls = c("try", "tryCatch", "withCallingHandlers")
) {
multiline_and <- if (allow_inline) "@line1 != @line2 and" else ""
xpath <- glue("
(//PIPE | //SPECIAL[{ xp_text_in_table(magrittr_pipes) }])
Expand Down
7 changes: 1 addition & 6 deletions R/object_name_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -146,13 +146,8 @@ object_name_linter <- function(styles = c("snake_case", "symbols"), regexes = ch
}

check_style <- function(nms, style, generics = character()) {
conforming <- re_matches(nms, style)
conforming <- re_matches_logical(nms, style)

# style has capture group(s)
if (is.data.frame(conforming)) {
# if any group is missing, all groups are missing, so just check the first column
conforming <- !is.na(conforming[[1L]])
}
# mark empty or NA names as conforming
conforming <- is.na(nms) | !nzchar(nms) | conforming

Expand Down
5 changes: 3 additions & 2 deletions R/object_overwrite_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,8 +52,9 @@
#' - <https://style.tidyverse.org/syntax.html#object-names>
#' @export
object_overwrite_linter <- function(
packages = c("base", "stats", "utils", "tools", "methods", "graphics", "grDevices"),
allow_names = character()) {
packages = c("base", "stats", "utils", "tools", "methods", "graphics", "grDevices"),
allow_names = character()
) {
for (package in packages) {
if (!requireNamespace(package, quietly = TRUE)) {
cli_abort("Package {.pkg {package}} is required, but not available.")
Expand Down
14 changes: 8 additions & 6 deletions R/return_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -72,11 +72,12 @@
#' - <https://style.tidyverse.org/functions.html?q=return#return>
#' @export
return_linter <- function(
return_style = c("implicit", "explicit"),
allow_implicit_else = TRUE,
return_functions = NULL,
except = NULL,
except_regex = NULL) {
return_style = c("implicit", "explicit"),
allow_implicit_else = TRUE,
return_functions = NULL,
except = NULL,
except_regex = NULL
) {
return_style <- match.arg(return_style)

check_except <- !allow_implicit_else || return_style == "explicit"
Expand Down Expand Up @@ -147,7 +148,8 @@ return_linter <- function(
xml <- source_expression$xml_parsed_content
if (defer_except) {
assigned_functions <- xml_text(xml_find_all(xml, function_name_xpath))
except <- union(except, assigned_functions[re_matches(assigned_functions, except_regex)])
except <-
union(except, assigned_functions[re_matches_logical(assigned_functions, except_regex)])
except_xpath <- glue(except_xpath_fmt, except = except)
body_xpath <- glue(body_xpath_fmt, except_xpath = except_xpath)
}
Expand Down
4 changes: 2 additions & 2 deletions R/todo_comment_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -57,9 +57,9 @@ todo_comment_linter <- function(todo = c("todo", "fixme"), except_regex = NULL)

comment_expr <- xml_find_all(xml, "//COMMENT")
comment_text <- xml_text(comment_expr)
invalid_todo <- re_matches(comment_text, todo_comment_regex, ignore.case = TRUE)
invalid_todo <- re_matches_logical(comment_text, todo_comment_regex, ignore.case = TRUE)
if (!is.null(valid_todo_regex)) {
invalid_todo <- invalid_todo & !re_matches(comment_text, valid_todo_regex)
invalid_todo <- invalid_todo & !re_matches_logical(comment_text, valid_todo_regex)
}

xml_nodes_to_lints(
Expand Down
21 changes: 11 additions & 10 deletions R/unnecessary_nesting_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -95,16 +95,17 @@
#' - [linters] for a complete list of linters available in lintr.
#' @export
unnecessary_nesting_linter <- function(
allow_assignment = TRUE,
allow_functions = c(
"switch",
"try", "tryCatch", "withCallingHandlers",
"quote", "expression", "bquote", "substitute",
"with_parameters_test_that",
"reactive", "observe", "observeEvent",
"renderCachedPlot", "renderDataTable", "renderImage", "renderPlot",
"renderPrint", "renderTable", "renderText", "renderUI"
)) {
allow_assignment = TRUE,
allow_functions = c(
"switch",
"try", "tryCatch", "withCallingHandlers",
"quote", "expression", "bquote", "substitute",
"with_parameters_test_that",
"reactive", "observe", "observeEvent",
"renderCachedPlot", "renderDataTable", "renderImage", "renderPlot",
"renderPrint", "renderTable", "renderText", "renderUI"
)
) {
exit_calls <- c("stop", "return", "abort", "quit", "q")
exit_call_expr <- glue("
expr[SYMBOL_FUNCTION_CALL[{xp_text_in_table(exit_calls)}]]
Expand Down
2 changes: 1 addition & 1 deletion R/unreachable_code_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ unreachable_code_linter <- function(allow_comment_regex = getOption("covr.exclud

drop_valid_comments <- function(expr, valid_comment_re) {
is_valid_comment <- xml2::xml_name(expr) == "COMMENT" &
re_matches(xml_text(expr), valid_comment_re)
re_matches_logical(xml_text(expr), valid_comment_re)
expr[!is_valid_comment]
}

Expand Down
14 changes: 12 additions & 2 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -187,15 +187,25 @@ read_lines <- function(file, encoding = settings$encoding, ...) {

# nocov start
# support for usethis::use_release_issue(). Make sure to use devtools::load_all() beforehand!
release_bullets <- function() {
}
release_bullets <- function() {}
# nocov end

# see issue #923, PR #2455 -- some locales ignore _ when running sort(), others don't.
# We want to consistently treat "_" < "n" = "N"; C locale does this, which 'radix' uses.
platform_independent_order <- function(x) order(tolower(x), method = "radix")
platform_independent_sort <- function(x) x[platform_independent_order(x)]

#' re_matches with type-stable logical output
#' TODO(r-lib/rex#94): Use re_matches() option directly & deprecate this.
#' @noRd
re_matches_logical <- function(x, regex, ...) {
res <- re_matches(x, regex, ...)
if (is.data.frame(res)) {
res <- complete.cases(res)
}
res
}

#' Extract text from `STR_CONST` nodes
#'
#' Convert `STR_CONST` `text()` values into R strings. This is useful to account for arbitrary
Expand Down
Loading

0 comments on commit c04e2f6

Please sign in to comment.