From a845f25cd56c438b6c21468474921fc2bb1b1bdf Mon Sep 17 00:00:00 2001 From: Tim Taylor Date: Mon, 4 Aug 2025 19:17:41 +0100 Subject: [PATCH 01/16] feat: argument to disable linting of `(` for auto-printing closes #2916 --- NEWS.md | 1 + R/implicit_assignment_linter.R | 19 ++++++++++++++++++- man/implicit_assignment_linter.Rd | 17 ++++++++++++++++- .../test-implicit_assignment_linter.R | 19 +++++++++++++++++++ 4 files changed, 54 insertions(+), 2 deletions(-) diff --git a/NEWS.md b/NEWS.md index 1a97d003fb..5d76e7b23d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -48,6 +48,7 @@ * `object_usage_linter()` lints missing packages that may cause false positives (#2872, @AshesITR) * New argument `include_s4_slots` for the `xml_find_function_calls()` entry in the `get_source_expressions()` to govern whether calls of the form `s4Obj@fun()` are included in the result (#2820, @MichaelChirico). * `sprintf_linter()` lints `sprintf()` and `gettextf()` calls when a constant string is passed to `fmt` (#2894, @Bisaloo). +* `implicit_assignment_linter()` gains argument `allow_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). ### New linters diff --git a/R/implicit_assignment_linter.R b/R/implicit_assignment_linter.R index c457328688..381fc29abc 100644 --- a/R/implicit_assignment_linter.R +++ b/R/implicit_assignment_linter.R @@ -9,6 +9,8 @@ #' @param allow_scoped Logical, default `FALSE`. If `TRUE`, "scoped assignments", #' where the object is assigned in the statement beginning a branch and used only #' within that branch, are skipped. +#' @param allow_print Logical, default `FALSE`. If `TRUE`, using `(` for auto-printing +#' at the top-level is not linted. #' #' @examples #' # will produce lints @@ -22,6 +24,12 @@ #' linters = implicit_assignment_linter() #' ) #' +#' lint( +#' text = "(x <- 1)", +#' linters = implicit_assignment_linter() +#' ) +#' +#' #' # okay #' lines <- "x <- 1L\nif (x) TRUE" #' writeLines(lines) @@ -53,6 +61,11 @@ #' linters = implicit_assignment_linter(allow_scoped = TRUE) #' ) #' +#' lint( +#' text = "(x <- 1)", +#' linters = implicit_assignment_linter(allow_print = TRUE) +#' ) +#' #' @evalRd rd_tags("implicit_assignment_linter") #' @seealso #' - [linters] for a complete list of linters available in lintr. @@ -61,7 +74,8 @@ #' @export implicit_assignment_linter <- function(except = c("bquote", "expression", "expr", "quo", "quos", "quote"), allow_lazy = FALSE, - allow_scoped = FALSE) { + allow_scoped = FALSE, + allow_print = FALSE) { stopifnot(is.null(except) || is.character(except)) if (length(except) > 0L) { @@ -116,6 +130,9 @@ implicit_assignment_linter <- function(except = c("bquote", "expression", "expr" bad_expr <- xml_find_all(xml, xpath) print_only <- !is.na(xml_find_first(bad_expr, "parent::expr[parent::exprlist and *[1][self::OP-LEFT-PAREN]]")) + if (allow_print) { + bad_expr <- bad_expr[!print_only] + } xml_nodes_to_lints( bad_expr, diff --git a/man/implicit_assignment_linter.Rd b/man/implicit_assignment_linter.Rd index 8eee7ea7d6..d77d419a68 100644 --- a/man/implicit_assignment_linter.Rd +++ b/man/implicit_assignment_linter.Rd @@ -7,7 +7,8 @@ implicit_assignment_linter( except = c("bquote", "expression", "expr", "quo", "quos", "quote"), allow_lazy = FALSE, - allow_scoped = FALSE + allow_scoped = FALSE, + allow_print = FALSE ) } \arguments{ @@ -19,6 +20,9 @@ trigger conditionally (e.g. in the RHS of \code{&&} or \code{||} expressions) ar \item{allow_scoped}{Logical, default \code{FALSE}. If \code{TRUE}, "scoped assignments", where the object is assigned in the statement beginning a branch and used only within that branch, are skipped.} + +\item{allow_print}{Logical, default \code{FALSE}. If \code{TRUE}, using \code{(} for auto-printing +at the top-level is not linted.} } \description{ Assigning inside function calls makes the code difficult to read, and should @@ -36,6 +40,12 @@ lint( linters = implicit_assignment_linter() ) +lint( + text = "(x <- 1)", + linters = implicit_assignment_linter() +) + + # okay lines <- "x <- 1L\nif (x) TRUE" writeLines(lines) @@ -67,6 +77,11 @@ lint( linters = implicit_assignment_linter(allow_scoped = TRUE) ) +lint( + text = "(x <- 1)", + linters = implicit_assignment_linter(allow_print = TRUE) +) + } \seealso{ \itemize{ diff --git a/tests/testthat/test-implicit_assignment_linter.R b/tests/testthat/test-implicit_assignment_linter.R index 5fe12c360f..b593417d13 100644 --- a/tests/testthat/test-implicit_assignment_linter.R +++ b/tests/testthat/test-implicit_assignment_linter.R @@ -476,3 +476,22 @@ test_that("call-less '(' mentions avoiding implicit printing", { linter ) }) + +test_that("allow_print allows `(` for auto printing", { + lint_message <- rex::rex("Avoid implicit assignments in function calls.") + linter <- implicit_assignment_linter(allow_print = TRUE) + expect_no_lint("(a <- foo())", linter) + + # Doesn't effect other cases + lint_message <- rex::rex("Avoid implicit assignments in function calls.") + expect_lint("if (x <- 1L) TRUE", lint_message, linter) + expect_lint("while (x <- 0L) FALSE", lint_message, linter) + expect_lint("for (x in 1:10 -> y) print(x)", lint_message, linter) + expect_lint("mean(x <- 1:4)", lint_message, linter) + + # default remains as is + print_msg <- rex::rex("Call print() explicitly instead of relying on implicit printing behavior via '('.") + expect_lint("(a <- foo())", print_msg, implicit_assignment_linter()) +}) + + From f136901c71b59e1faf093bb354169c7798e1852a Mon Sep 17 00:00:00 2001 From: Tim Taylor Date: Mon, 11 Aug 2025 14:50:21 +0100 Subject: [PATCH 02/16] lint: trailing newlines --- tests/testthat/test-implicit_assignment_linter.R | 2 -- 1 file changed, 2 deletions(-) diff --git a/tests/testthat/test-implicit_assignment_linter.R b/tests/testthat/test-implicit_assignment_linter.R index b593417d13..7e0b56c839 100644 --- a/tests/testthat/test-implicit_assignment_linter.R +++ b/tests/testthat/test-implicit_assignment_linter.R @@ -493,5 +493,3 @@ test_that("allow_print allows `(` for auto printing", { print_msg <- rex::rex("Call print() explicitly instead of relying on implicit printing behavior via '('.") expect_lint("(a <- foo())", print_msg, implicit_assignment_linter()) }) - - From 6ed91bbdaebc3a389ff01d4568d884269fc16bf6 Mon Sep 17 00:00:00 2001 From: Emmanuel Ferdman Date: Tue, 7 Oct 2025 07:38:33 +0300 Subject: [PATCH 03/16] Fix false positive for null coalescing without else clause (#2938) * Fix false positive for null coalescing without else clause Signed-off-by: Emmanuel Ferdman * cite in NEWS --------- Signed-off-by: Emmanuel Ferdman Co-authored-by: Michael Chirico --- NEWS.md | 2 +- R/coalesce_linter.R | 1 + tests/testthat/test-coalesce_linter.R | 3 +++ 3 files changed, 5 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index bacf8e02c6..14bf42dbb5 100644 --- a/NEWS.md +++ b/NEWS.md @@ -57,7 +57,7 @@ * `download_file_linter()` encourages the use of `mode = "wb"` (or `mode = "ab"`) when using `download.file()`, rather than `mode = "w"` or `mode = "a"`, as the latter can produce broken files in Windows (#2882, @Bisaloo). * `lint2df_linter()` encourages the use of the `list2DF()` function, or the `data.frame()` function when recycling is required, over the slower and less readable `do.call(cbind.data.frame, )` alternative (#2834, @Bisaloo). -* `coalesce_linter()` encourages the use of the infix operator `x %||% y`, which is equivalent to `if (is.null(x)) y else x` (#2246, @MichaelChirico). While this has long been used in many tidyverse packages (it was added to {ggplot2} in 2008), it became part of every R installation from R 4.4.0. +* `coalesce_linter()` encourages the use of the infix operator `x %||% y`, which is equivalent to `if (is.null(x)) y else x` (#2246, @MichaelChirico). While this has long been used in many tidyverse packages (it was added to {ggplot2} in 2008), it became part of every R installation from R 4.4.0. Thanks also to @emmanuel-ferdman for fixing a false positive before release. ### Lint accuracy fixes: removing false positives diff --git a/R/coalesce_linter.R b/R/coalesce_linter.R index befa1636b2..8c3f7274d7 100644 --- a/R/coalesce_linter.R +++ b/R/coalesce_linter.R @@ -60,6 +60,7 @@ coalesce_linter <- function() { parent::expr[ preceding-sibling::OP-EXCLAMATION and parent::expr/preceding-sibling::IF + and parent::expr/following-sibling::ELSE and ( expr[2] = parent::expr/following-sibling::expr[1] or expr[2] = parent::expr/following-sibling::{braced_expr_cond} diff --git a/tests/testthat/test-coalesce_linter.R b/tests/testthat/test-coalesce_linter.R index 434bdd7bd1..fcd25a189f 100644 --- a/tests/testthat/test-coalesce_linter.R +++ b/tests/testthat/test-coalesce_linter.R @@ -3,6 +3,9 @@ test_that("coalesce_linter skips allowed usage", { expect_no_lint("if (is.null(x)) y", linter) expect_no_lint("if (!is.null(x)) y", linter) + expect_no_lint("if (!is.null(x)) x", linter) + expect_no_lint("if (is.null(x)) x", linter) + expect_no_lint("c(if (!is.null(E)) E)", linter) expect_no_lint("if (is.null(x)) y else z", linter) expect_no_lint("if (!is.null(x)) x[1] else y", linter) expect_no_lint("if (is.null(x[1])) y else x[2]", linter) From aa5bf629193f9d0dd057080b6caef03f2df2f9e3 Mon Sep 17 00:00:00 2001 From: Hadley Wickham Date: Wed, 8 Oct 2025 11:36:58 -0500 Subject: [PATCH 04/16] Partial fix for upcoming testthat release (#2937) * Partial fix for upcoming testthat release `expect_success()` and `expect_failure()` now test that you have exactly one success/failure and zero failures/successes. I can't quite figure out why the tests are still failing here; maybe it's something to do with recycling? I'm happy to help but I unfortunately I don't know enough about the lintr internals to figure out what's going wrong here. We're planning to submit testthat to CRAN on Nov 10. * simple delint * extract to helper for cyclo complexity * avoid testthat::expect() again * fail() needs return() --------- Co-authored-by: Michael Chirico --- R/expect_lint.R | 93 ++++++++++++++++++++++++++----------------------- 1 file changed, 49 insertions(+), 44 deletions(-) diff --git a/R/expect_lint.R b/R/expect_lint.R index 3d9b54e746..7928907a2d 100644 --- a/R/expect_lint.R +++ b/R/expect_lint.R @@ -59,8 +59,10 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en", igno wrong_number_fmt <- "got %d lints instead of %d%s" if (is.null(checks)) { - msg <- sprintf(wrong_number_fmt, n_lints, length(checks), lint_str) - return(testthat::expect(n_lints %==% 0L, msg)) + if (n_lints != 0L) { + return(testthat::fail(sprintf(wrong_number_fmt, n_lints, 0L, lint_str))) + } + return(testthat::succeed()) } if (!is.list(checks) || !is.null(names(checks))) { # vector or named list @@ -69,8 +71,7 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en", igno checks[] <- lapply(checks, fix_names, "message") if (n_lints != length(checks)) { - msg <- sprintf(wrong_number_fmt, n_lints, length(checks), lint_str) - return(testthat::expect(FALSE, msg)) + return(testthat::fail(sprintf(wrong_number_fmt, n_lints, length(checks), lint_str))) } if (ignore_order) { @@ -85,42 +86,47 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en", igno checks <- checks[check_order] } - local({ - itr_env <- new.env(parent = emptyenv()) - itr_env$itr <- 0L - # valid fields are those from Lint(), plus 'linter' - lint_fields <- c(names(formals(Lint)), "linter") - Map( - function(lint, check) { - itr_env$itr <- itr_env$itr + 1L - lapply(names(check), function(field) { - if (!field %in% lint_fields) { - cli_abort(c( - x = "Check {.val {itr_env$itr}} has an invalid field: {.field {field}}.", - i = "Valid fields are: {.field {lint_fields}}." - )) - } - check <- check[[field]] - value <- lint[[field]] - msg <- sprintf( - "check #%d: %s %s did not match %s", - itr_env$itr, field, deparse(value), deparse(check) - ) - # deparse ensures that NULL, list(), etc are handled gracefully - ok <- if (field == "message") { - re_matches_logical(value, check) - } else { - isTRUE(all.equal(value, check)) - } - testthat::expect(ok, msg) - }) - }, - lints, - checks - ) - }) + expect_lint_impl_(lints, checks) + + testthat::succeed() +} - invisible(NULL) +#' NB: must _not_ succeed(), should only fail() or abort() +#' @noRd +expect_lint_impl_ <- function(lints, checks) { + itr <- 0L + # valid fields are those from Lint(), plus 'linter' + lint_fields <- c(names(formals(Lint)), "linter") + + for (i in seq_along(lints)) { + lint <- lints[[i]] + check <- checks[[i]] + + itr <- itr + 1L + + for (field in names(check)) { + if (!field %in% lint_fields) { + cli_abort(c( + x = "Check {.val {itr}} has an invalid field: {.field {field}}.", + i = "Valid fields are: {.field {lint_fields}}." + )) + } + check_field <- check[[field]] + value <- lint[[field]] + ok <- if (field == "message") { + re_matches_logical(value, check_field) + } else { + isTRUE(all.equal(value, check_field)) + } + if (!ok) { + return(testthat::fail(sprintf( + "check #%d: %s %s did not match %s", + # deparse ensures that NULL, list(), etc are handled gracefully + itr, field, deparse(value), deparse(check) + ))) + } + } + } } #' @rdname expect_lint @@ -162,12 +168,11 @@ expect_lint_free <- function(...) { if (has_lints) { lint_output <- format(lints) } - result <- testthat::expect( - !has_lints, - paste0("Not lint free\n", lint_output) - ) - invisible(result) + if (has_lints) { + return(testthat::fail(paste0("Not lint free\n", lint_output))) + } + testthat::succeed() } # Helper function to check if testthat is installed. From 825b1eeb86d384c8419506313049ef73242dab1c Mon Sep 17 00:00:00 2001 From: Etienne Bacher <52219252+etiennebacher@users.noreply.github.com> Date: Thu, 16 Oct 2025 00:30:00 +0200 Subject: [PATCH 05/16] clarify reasoning for repeat{} vs. while(TRUE){} --- R/repeat_linter.R | 3 ++- man/repeat_linter.Rd | 3 ++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/R/repeat_linter.R b/R/repeat_linter.R index 877ff0da7a..ebce9102e7 100644 --- a/R/repeat_linter.R +++ b/R/repeat_linter.R @@ -1,6 +1,7 @@ #' Repeat linter #' -#' Check that `while (TRUE)` is not used for infinite loops. +#' Check that `while (TRUE)` is not used for infinite loops. While this is valid +#' R code, using `repeat {}` is more explicit. #' #' @examples #' # will produce lints diff --git a/man/repeat_linter.Rd b/man/repeat_linter.Rd index 86db0ac3e7..08263204ad 100644 --- a/man/repeat_linter.Rd +++ b/man/repeat_linter.Rd @@ -7,7 +7,8 @@ repeat_linter() } \description{ -Check that \verb{while (TRUE)} is not used for infinite loops. +Check that \verb{while (TRUE)} is not used for infinite loops. While this is valid +R code, using \code{repeat {}} is more explicit. } \examples{ # will produce lints From 1af371ce9bf0c7549abd8bd2f656518a4bcd3577 Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Thu, 16 Oct 2025 18:47:08 +0200 Subject: [PATCH 06/16] Report a helpful error if linters_with_tags() specifies no tags. (#2942) --- R/with.R | 3 +++ tests/testthat/test-linter_tags.R | 1 + 2 files changed, 4 insertions(+) diff --git a/R/with.R b/R/with.R index e4087a42c2..56d2d6edd4 100644 --- a/R/with.R +++ b/R/with.R @@ -92,6 +92,9 @@ modify_defaults <- function(defaults, ...) { #' } #' @export linters_with_tags <- function(tags, ..., packages = "lintr", exclude_tags = "deprecated") { + if (missing(tags)) { + cli_abort("{.arg tags} was not specified. Available tags: {available_tags()}") + } if (!is.character(tags) && !is.null(tags)) { cli_abort("{.arg tags} must be a character vector, or {.code NULL}, not {.obj_type_friendly {tags}}.") } diff --git a/tests/testthat/test-linter_tags.R b/tests/testthat/test-linter_tags.R index faeb151025..b68c835ff7 100644 --- a/tests/testthat/test-linter_tags.R +++ b/tests/testthat/test-linter_tags.R @@ -41,6 +41,7 @@ test_that("default_linters and default tag match up", { test_that("warnings occur only for deprecated linters", { skip_if_not_installed("cyclocomp") # actually we expect a warning there + expect_error(linters_with_tags(), "`tags` was not specified. Available tags:") expect_silent(linters_with_tags(tags = NULL)) num_deprecated_linters <- nrow(available_linters(tags = "deprecated", exclude_tags = NULL)) outer_env <- new.env(parent = emptyenv()) From ec9f159011c9ba51c27fb8a7463170cdad37e5cc Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Thu, 16 Oct 2025 22:34:59 +0200 Subject: [PATCH 07/16] Don't lint T and F if followed by `[` (#2947) * Don't lint T and F if followed by `[`. * Address review comments. * subsume into same expr[] as $ and @ --------- Co-authored-by: Michael Chirico --- NEWS.md | 1 + R/T_and_F_symbol_linter.R | 2 +- tests/testthat/test-T_and_F_symbol_linter.R | 4 ++++ 3 files changed, 6 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 14bf42dbb5..a85ce40e52 100644 --- a/NEWS.md +++ b/NEWS.md @@ -74,6 +74,7 @@ files in Windows (#2882, @Bisaloo). * `assignment_linter()` with `operator = "="` does a better job of skipping implicit assignments, which are intended to be governed by `implicit_assignment_linter()` (#2765, @MichaelChirico). * `expect_true_false_linter()` is pipe-aware, so that `42 |> expect_identical(x, ignore_attr = TRUE)` no longer lints (#1520, @MichaelChirico). * `T_and_F_symbol_linter()` ignores `T` and `F` used as symbols in formulas (`y ~ T + F`), which can represent variables in data not controlled by the author (#2637, @MichaelChirico). +* `T_and_F_symbol_linter()` ignores `T` and `F` if followed by `[` or `[[` (#2944, @mcol). * `implicit_assignment_linter()` with `allow_scoped=TRUE` doesn't lint for `if (a <- 1) print(a)` (#2913, @MichaelChirico). ### Lint accuracy fixes: removing false negatives diff --git a/R/T_and_F_symbol_linter.R b/R/T_and_F_symbol_linter.R index f740e49de9..3497966b98 100644 --- a/R/T_and_F_symbol_linter.R +++ b/R/T_and_F_symbol_linter.R @@ -34,7 +34,7 @@ T_and_F_symbol_linter <- function() { # nolint: object_name. symbol_xpath <- "//SYMBOL[ (text() = 'T' or text() = 'F') - and not(parent::expr[OP-DOLLAR or OP-AT]) + and not(parent::expr[OP-DOLLAR or OP-AT or following-sibling::OP-LEFT-BRACKET or following-sibling::LBB]) and ( not(ancestor::expr[OP-TILDE]) or parent::expr/preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB] diff --git a/tests/testthat/test-T_and_F_symbol_linter.R b/tests/testthat/test-T_and_F_symbol_linter.R index de33bd5772..33f771b6bc 100644 --- a/tests/testthat/test-T_and_F_symbol_linter.R +++ b/tests/testthat/test-T_and_F_symbol_linter.R @@ -7,6 +7,8 @@ test_that("T_and_F_symbol_linter skips allowed usages", { expect_no_lint("y ~ T + F", linter) expect_no_lint("y ~ x + I(T^2)", linter) expect_no_lint("y ~ foo(T, F)", linter) + expect_no_lint("T[1]", linter) + expect_no_lint("T[[1]]", linter) }) test_that("T_and_F_symbol_linter blocks disallowed usages", { @@ -32,6 +34,8 @@ test_that("T_and_F_symbol_linter blocks disallowed usages", { expect_lint("DF$bool <- T", msg_true, linter) expect_lint("S4@bool <- T", msg_true, linter) expect_lint("sum(x, na.rm = T)", msg_true, linter) + expect_lint("x[T]", msg_true, linter) + expect_lint("x[, cols, drop = T]", msg_true, linter) expect_lint("y ~ foo(x, arg = T)", msg_true, linter) expect_lint( trim_some(" From a321e59933bc28add82104544d31ccd3d3fbe8bb Mon Sep 17 00:00:00 2001 From: Etienne Bacher <52219252+etiennebacher@users.noreply.github.com> Date: Fri, 17 Oct 2025 16:34:01 +0200 Subject: [PATCH 08/16] init (#2948) --- R/absolute_path_linter.R | 2 +- man/absolute_path_linter.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/absolute_path_linter.R b/R/absolute_path_linter.R index 38fffd40b5..e7324945d7 100644 --- a/R/absolute_path_linter.R +++ b/R/absolute_path_linter.R @@ -11,7 +11,7 @@ #' @examples #' # will produce lints #' lint( -#' text = 'R"--[/blah/file.txt]--"', +#' text = 'R"(/blah/file.txt)"', #' linters = absolute_path_linter() #' ) #' diff --git a/man/absolute_path_linter.Rd b/man/absolute_path_linter.Rd index 04fa1cf1a3..32a8ace12e 100644 --- a/man/absolute_path_linter.Rd +++ b/man/absolute_path_linter.Rd @@ -20,7 +20,7 @@ Check that no absolute paths are used (e.g. "/var", "C:\\System", "~/docs"). \examples{ # will produce lints lint( - text = 'R"--[/blah/file.txt]--"', + text = 'R"(/blah/file.txt)"', linters = absolute_path_linter() ) From dfe225554d79dca9271edaaf69bdcf17cb13c39e Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Fri, 17 Oct 2025 19:29:42 +0200 Subject: [PATCH 09/16] Use expect_no_lint() instead of expect_lint(., NULL). (#2950) Co-authored-by: Michael Chirico --- tests/testthat/test-namespace_linter.R | 34 +++++++------- tests/testthat/test-redundant_ifelse_linter.R | 46 +++++++++---------- tests/testthat/test-which_grepl_linter.R | 2 +- tests/testthat/test-whitespace_linter.R | 14 +++--- tests/testthat/test-yoda_test_linter.R | 12 ++--- 5 files changed, 53 insertions(+), 55 deletions(-) diff --git a/tests/testthat/test-namespace_linter.R b/tests/testthat/test-namespace_linter.R index 081e38b21b..847aad2152 100644 --- a/tests/testthat/test-namespace_linter.R +++ b/tests/testthat/test-namespace_linter.R @@ -1,34 +1,34 @@ test_that("namespace_linter skips allowed usages", { linter <- namespace_linter() - expect_lint("stats::sd", NULL, linter) - expect_lint("stats::sd(c(1,2,3))", NULL, linter) - expect_lint('"stats"::sd(c(1,2,3))', NULL, linter) - expect_lint('stats::"sd"(c(1,2,3))', NULL, linter) - expect_lint("stats::`sd`(c(1,2,3))", NULL, linter) + expect_no_lint("stats::sd", linter) + expect_no_lint("stats::sd(c(1,2,3))", linter) + expect_no_lint('"stats"::sd(c(1,2,3))', linter) + expect_no_lint('stats::"sd"(c(1,2,3))', linter) + expect_no_lint("stats::`sd`(c(1,2,3))", linter) - expect_lint("datasets::mtcars", NULL, linter) - expect_lint("stats:::print.formula", NULL, linter) - expect_lint('"stats":::print.formula', NULL, linter) + expect_no_lint("datasets::mtcars", linter) + expect_no_lint("stats:::print.formula", linter) + expect_no_lint('"stats":::print.formula', linter) }) test_that("namespace_linter respects check_exports and check_nonexports arguments", { - expect_lint("stats::ssd(c(1,2,3))", NULL, namespace_linter(check_exports = FALSE)) - expect_lint("stats:::ssd(c(1,2,3))", NULL, namespace_linter(check_nonexports = FALSE)) - expect_lint("stats:::ssd(c(1,2,3))", NULL, namespace_linter(check_exports = FALSE, check_nonexports = FALSE)) + expect_no_lint("stats::ssd(c(1,2,3))", namespace_linter(check_exports = FALSE)) + expect_no_lint("stats:::ssd(c(1,2,3))", namespace_linter(check_nonexports = FALSE)) + expect_no_lint("stats:::ssd(c(1,2,3))", namespace_linter(check_exports = FALSE, check_nonexports = FALSE)) }) test_that("namespace_linter can work with backticked symbols", { skip_if_not_installed("rlang") linter <- namespace_linter() - expect_lint("rlang::`%||%`", NULL, linter) - expect_lint("rlang::`%||%`()", NULL, linter) + expect_no_lint("rlang::`%||%`", linter) + expect_no_lint("rlang::`%||%`()", linter) - expect_lint("rlang::'%||%'", NULL, linter) - expect_lint("rlang::'%||%'()", NULL, linter) - expect_lint('rlang::"%||%"', NULL, linter) - expect_lint('rlang::"%||%"()', NULL, linter) + expect_no_lint("rlang::'%||%'", linter) + expect_no_lint("rlang::'%||%'()", linter) + expect_no_lint('rlang::"%||%"', linter) + expect_no_lint('rlang::"%||%"()', linter) expect_lint("rlang::`%>%`", "'%>%' is not exported from {rlang}.", linter) expect_lint("rlang::'%>%'()", "'%>%' is not exported from {rlang}.", linter) diff --git a/tests/testthat/test-redundant_ifelse_linter.R b/tests/testthat/test-redundant_ifelse_linter.R index bf7fbc0ae4..1c4bf78308 100644 --- a/tests/testthat/test-redundant_ifelse_linter.R +++ b/tests/testthat/test-redundant_ifelse_linter.R @@ -1,13 +1,13 @@ test_that("redundant_ifelse_linter skips allowed usages", { linter <- redundant_ifelse_linter() - expect_lint("ifelse(x > 5, 0, 2)", NULL, linter) - expect_lint("ifelse(x > 5, TRUE, NA)", NULL, linter) - expect_lint("ifelse(x > 5, FALSE, NA)", NULL, linter) - expect_lint("ifelse(x > 5, TRUE, TRUE)", NULL, linter) + expect_no_lint("ifelse(x > 5, 0, 2)", linter) + expect_no_lint("ifelse(x > 5, TRUE, NA)", linter) + expect_no_lint("ifelse(x > 5, FALSE, NA)", linter) + expect_no_lint("ifelse(x > 5, TRUE, TRUE)", linter) - expect_lint("ifelse(x > 5, 0L, 2L)", NULL, linter) - expect_lint("ifelse(x > 5, 0L, 10L)", NULL, linter) + expect_no_lint("ifelse(x > 5, 0L, 2L)", linter) + expect_no_lint("ifelse(x > 5, 0L, 10L)", linter) }) test_that("redundant_ifelse_linter blocks simple disallowed usages", { @@ -111,38 +111,38 @@ test_that("redundant_ifelse_linter blocks usages equivalent to as.numeric, optio test_that("allow10 works as intended", { linter <- redundant_ifelse_linter(allow10 = TRUE) - expect_lint("ifelse(x > 5, 1L, 0L)", NULL, linter) - expect_lint("ifelse(x > 5, 0L, 1L)", NULL, linter) + expect_no_lint("ifelse(x > 5, 1L, 0L)", linter) + expect_no_lint("ifelse(x > 5, 0L, 1L)", linter) - expect_lint("ifelse(x > 5, 1, 0)", NULL, linter) - expect_lint("ifelse(x > 5, 0, 1)", NULL, linter) + expect_no_lint("ifelse(x > 5, 1, 0)", linter) + expect_no_lint("ifelse(x > 5, 0, 1)", linter) - expect_lint("dplyr::if_else(x > 5, 1L, 0L)", NULL, linter) - expect_lint("data.table::fifelse(x > 5, 0L, 1L)", NULL, linter) + expect_no_lint("dplyr::if_else(x > 5, 1L, 0L)", linter) + expect_no_lint("data.table::fifelse(x > 5, 0L, 1L)", linter) - expect_lint("if_else(x > 5, 1, 0)", NULL, linter) - expect_lint("fifelse(x > 5, 0, 1)", NULL, linter) + expect_no_lint("if_else(x > 5, 1, 0)", linter) + expect_no_lint("fifelse(x > 5, 0, 1)", linter) }) test_that("ifelse(missing = ) gives correct lints", { linter <- redundant_ifelse_linter() expect_lint("if_else(x > 5, TRUE, FALSE, NA)", rex::rex("Just use the logical condition"), linter) - expect_lint("if_else(x > 5, TRUE, FALSE, TRUE)", NULL, linter) - expect_lint("if_else(x > 5, TRUE, FALSE, 5L)", NULL, linter) + expect_no_lint("if_else(x > 5, TRUE, FALSE, TRUE)", linter) + expect_no_lint("if_else(x > 5, TRUE, FALSE, 5L)", linter) expect_lint("if_else(x > 5, 1L, 0L, NA_integer_)", rex::rex("Prefer as.integer(x)"), linter) - expect_lint("if_else(x > 5, 1L, 0L, 2L)", NULL, linter) - expect_lint("if_else(x > 5, 1L, 0L, 5)", NULL, linter) + expect_no_lint("if_else(x > 5, 1L, 0L, 2L)", linter) + expect_no_lint("if_else(x > 5, 1L, 0L, 5)", linter) expect_lint("if_else(x > 5, 1, 0, NA_real_)", rex::rex("Prefer as.numeric(x)"), linter) - expect_lint("if_else(x > 5, 1, 0, 2)", NULL, linter) - expect_lint("if_else(x > 5, 1, 0, '5')", NULL, linter) + expect_no_lint("if_else(x > 5, 1, 0, 2)", linter) + expect_no_lint("if_else(x > 5, 1, 0, '5')", linter) # TRUE/FALSE must be found in yes/no, not missing= - expect_lint("if_else(x > 5, 'a', TRUE, FALSE)", NULL, linter) - expect_lint("if_else(x > 5, 'a', 0L, 1L)", NULL, linter) - expect_lint("if_else(x > 5, 'a', 1, 0)", NULL, linter) + expect_no_lint("if_else(x > 5, 'a', TRUE, FALSE)", linter) + expect_no_lint("if_else(x > 5, 'a', 0L, 1L)", linter) + expect_no_lint("if_else(x > 5, 'a', 1, 0)", linter) }) test_that("lints vectorize", { diff --git a/tests/testthat/test-which_grepl_linter.R b/tests/testthat/test-which_grepl_linter.R index 2c3a4e3baa..3f7b780a5f 100644 --- a/tests/testthat/test-which_grepl_linter.R +++ b/tests/testthat/test-which_grepl_linter.R @@ -1,6 +1,6 @@ test_that("which_grepl_linter skips allowed usages", { # this _could_ be combined as p1|p2, but often it's cleaner to read this way - expect_lint("which(grepl(p1, x) | grepl(p2, x))", NULL, which_grepl_linter()) + expect_no_lint("which(grepl(p1, x) | grepl(p2, x))", which_grepl_linter()) }) test_that("which_grepl_linter blocks simple disallowed usages", { diff --git a/tests/testthat/test-whitespace_linter.R b/tests/testthat/test-whitespace_linter.R index 0a6aca9d6e..bd48ac9e4c 100644 --- a/tests/testthat/test-whitespace_linter.R +++ b/tests/testthat/test-whitespace_linter.R @@ -1,24 +1,22 @@ test_that("whitespace_linter skips allowed usages", { linter <- whitespace_linter() - expect_lint("blah", NULL, linter) - expect_lint(" blah", NULL, linter) - expect_lint(" blah", NULL, linter) - expect_lint("#\tblah", NULL, linter) + expect_no_lint("blah", linter) + expect_no_lint(" blah", linter) + expect_no_lint(" blah", linter) + expect_no_lint("#\tblah", linter) }) test_that("whitespace_linter skips allowed tab usages inside strings", { linter <- whitespace_linter() - expect_lint( + expect_no_lint( 'lint_msg <- "dont flag tabs if\tthey are inside a string."', - NULL, linter ) - expect_lint( + expect_no_lint( 'lint_msg <- "dont flag tabs if\n\tthey are inside multiline strings."', - NULL, linter ) }) diff --git a/tests/testthat/test-yoda_test_linter.R b/tests/testthat/test-yoda_test_linter.R index 812440d9e5..09d1d9da54 100644 --- a/tests/testthat/test-yoda_test_linter.R +++ b/tests/testthat/test-yoda_test_linter.R @@ -1,12 +1,12 @@ test_that("yoda_test_linter skips allowed usages", { linter <- yoda_test_linter() - expect_lint("expect_equal(x, 2)", NULL, linter) + expect_no_lint("expect_equal(x, 2)", linter) # namespace qualification doesn't matter - expect_lint("testthat::expect_identical(x, 'a')", NULL, linter) + expect_no_lint("testthat::expect_identical(x, 'a')", linter) # two variables can't be distinguished which is expected/actual (without # playing quixotic games trying to parse that out from variable names) - expect_lint("expect_equal(x, y)", NULL, linter) + expect_no_lint("expect_equal(x, y)", linter) }) test_that("yoda_test_linter blocks simple disallowed usages", { @@ -24,8 +24,8 @@ test_that("yoda_test_linter ignores strings in $ expressions", { linter <- yoda_test_linter() # the "key" here shows up at the same level of the parse tree as plain "key" normally would - expect_lint('expect_equal(x$"key", 2)', NULL, linter) - expect_lint('expect_equal(x@"key", 2)', NULL, linter) + expect_no_lint('expect_equal(x$"key", 2)', linter) + expect_no_lint('expect_equal(x@"key", 2)', linter) }) # if we only inspect the first argument & ignore context, get false positives @@ -34,7 +34,7 @@ local({ linter <- yoda_test_linter() patrick::with_parameters_test_that( "yoda_test_linter ignores usage in pipelines", - expect_lint(sprintf("foo() %s expect_identical(2)", pipe), NULL, linter), + expect_no_lint(sprintf("foo() %s expect_identical(2)", pipe), linter), pipe = pipes, .test_name = names(pipes) ) From 3b0278d8d30dbe13f3d079ad29fcaa0f08434a9e Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Sat, 18 Oct 2025 00:27:51 +0200 Subject: [PATCH 10/16] Lint nrow, ncol, NROW and NCOL with logical expressions (#2952) * Lint nrow, ncol, NROW and NCOL with logical expressions. * Address review comments. * Fix indentation. * tidy up tests --------- Co-authored-by: Michael Chirico --- NEWS.md | 1 + R/length_test_linter.R | 32 +++++++++-- man/length_test_linter.Rd | 26 ++++++++- tests/testthat/test-length_test_linter.R | 67 +++++++++++++++--------- 4 files changed, 97 insertions(+), 29 deletions(-) diff --git a/NEWS.md b/NEWS.md index a85ce40e52..1e0c16530e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -50,6 +50,7 @@ * `sprintf_linter()` lints `sprintf()` and `gettextf()` calls when a constant string is passed to `fmt` (#2894, @Bisaloo). * `use_lintr()` adds the created `.lintr` file to the `.Rbuildignore` if run in a package (#2926, initial work by @MEO265, finalized by @Bisaloo). * `implicit_assignment_linter()` gains argument `allow_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). +* `length_test_linter()` is extended to check incorrect usage of `nrow()`, `ncol()`, `NROW()`, `NCOL()` (#2933, @mcol). ### New linters diff --git a/R/length_test_linter.R b/R/length_test_linter.R index 1a984ef666..62790c5eae 100644 --- a/R/length_test_linter.R +++ b/R/length_test_linter.R @@ -1,9 +1,11 @@ -#' Check for a common mistake where length is applied in the wrong place +#' Check for a common mistake where a size check like 'length' is applied in the wrong place #' #' Usage like `length(x == 0)` is a mistake. If you intended to check `x` is empty, #' use `length(x) == 0`. Other mistakes are possible, but running `length()` on the #' outcome of a logical comparison is never the best choice. #' +#' The linter also checks for similar usage with `nrow()`, `ncol()`, `NROW()`, and `NCOL()`. +#' #' @examples #' # will produce lints #' lint( @@ -11,11 +13,32 @@ #' linters = length_test_linter() #' ) #' +#' lint( +#' text = "nrow(x > 0) || ncol(x > 0)", +#' linters = length_test_linter() +#' ) +#' +#' lint( +#' text = "NROW(x == 1) && NCOL(y == 1)", +#' linters = length_test_linter() +#' ) +#' #' # okay #' lint( #' text = "length(x) > 0", #' linters = length_test_linter() #' ) +#' +#' lint( +#' text = "nrow(x) > 0 || ncol(x) > 0", +#' linters = length_test_linter() +#' ) +#' +#' lint( +#' text = "NROW(x) == 1 && NCOL(y) == 1", +#' linters = length_test_linter() +#' ) +#' #' @evalRd rd_tags("class_equals_linter") #' @seealso [linters] for a complete list of linters available in lintr. #' @export @@ -26,13 +49,14 @@ length_test_linter <- function() { ") Linter(linter_level = "expression", function(source_expression) { - xml_calls <- source_expression$xml_find_function_calls("length") + xml_calls <- source_expression$xml_find_function_calls(c("length", "nrow", "ncol", "NROW", "NCOL")) bad_expr <- xml_find_all(xml_calls, xpath) + matched_function <- xp_call_name(bad_expr) expr_parts <- vapply(lapply(bad_expr, xml_find_all, "expr[2]/*"), xml_text, character(3L)) lint_message <- sprintf( - "Checking the length of a logical vector is likely a mistake. Did you mean `length(%s) %s %s`?", - expr_parts[1L, ], expr_parts[2L, ], expr_parts[3L, ] + "Checking the %s of a logical vector is likely a mistake. Did you mean `%s(%s) %s %s`?", + matched_function, matched_function, expr_parts[1L, ], expr_parts[2L, ], expr_parts[3L, ] ) xml_nodes_to_lints( diff --git a/man/length_test_linter.Rd b/man/length_test_linter.Rd index 4071089051..963f50709f 100644 --- a/man/length_test_linter.Rd +++ b/man/length_test_linter.Rd @@ -2,7 +2,7 @@ % Please edit documentation in R/length_test_linter.R \name{length_test_linter} \alias{length_test_linter} -\title{Check for a common mistake where length is applied in the wrong place} +\title{Check for a common mistake where a size check like 'length' is applied in the wrong place} \usage{ length_test_linter() } @@ -11,6 +11,9 @@ Usage like \code{length(x == 0)} is a mistake. If you intended to check \code{x} use \code{length(x) == 0}. Other mistakes are possible, but running \code{length()} on the outcome of a logical comparison is never the best choice. } +\details{ +The linter also checks for similar usage with \code{nrow()}, \code{ncol()}, \code{NROW()}, and \code{NCOL()}. +} \examples{ # will produce lints lint( @@ -18,11 +21,32 @@ lint( linters = length_test_linter() ) +lint( + text = "nrow(x > 0) || ncol(x > 0)", + linters = length_test_linter() +) + +lint( + text = "NROW(x == 1) && NCOL(y == 1)", + linters = length_test_linter() +) + # okay lint( text = "length(x) > 0", linters = length_test_linter() ) + +lint( + text = "nrow(x) > 0 || ncol(x) > 0", + linters = length_test_linter() +) + +lint( + text = "NROW(x) == 1 && NCOL(y) == 1", + linters = length_test_linter() +) + } \seealso{ \link{linters} for a complete list of linters available in lintr. diff --git a/tests/testthat/test-length_test_linter.R b/tests/testthat/test-length_test_linter.R index b60557c12d..3d1a4b84b2 100644 --- a/tests/testthat/test-length_test_linter.R +++ b/tests/testthat/test-length_test_linter.R @@ -1,35 +1,54 @@ test_that("skips allowed usages", { linter <- length_test_linter() - expect_lint("length(x) > 0", NULL, linter) - expect_lint("length(DF[key == val, cols])", NULL, linter) + expect_no_lint("length(x) > 0", linter) + expect_no_lint("length(DF[key == val, cols])", linter) + expect_no_lint("nrow(x) > 0", linter) + expect_no_lint("nrow(DF[key == val, cols])", linter) + expect_no_lint("ncol(x) > 0", linter) + expect_no_lint("ncol(DF[key == val, cols])", linter) + expect_no_lint("NROW(x) > 0", linter) + expect_no_lint("NROW(DF[key == val, cols])", linter) + expect_no_lint("NCOL(x) > 0", linter) + expect_no_lint("NCOL(DF[key == val, cols])", linter) }) -test_that("blocks simple disallowed usages", { - linter <- length_test_linter() - lint_msg_stub <- rex::rex("Checking the length of a logical vector is likely a mistake. Did you mean ") - - expect_lint("length(x == 0)", rex::rex(lint_msg_stub, "`length(x) == 0`?"), linter) - expect_lint("length(x == y)", rex::rex(lint_msg_stub, "`length(x) == y`?"), linter) - expect_lint("length(x + y == 2)", rex::rex(lint_msg_stub, "`length(x+y) == 2`?"), linter) -}) - -local({ - ops <- c(lt = "<", lte = "<=", gt = ">", gte = ">=", eq = "==", neq = "!=") - linter <- length_test_linter() - lint_msg_stub <- rex::rex("Checking the length of a logical vector is likely a mistake. Did you mean ") - - patrick::with_parameters_test_that( - "all logical operators detected", +patrick::with_parameters_test_that( + "blocks simple disallowed usages", + { + linter <- length_test_linter() + lint_msg_stub <- sprintf("Checking the %s of a logical vector is likely a mistake. Did you mean ", fun) expect_lint( - paste("length(x", op, "y)"), - rex::rex("`length(x) ", op, " y`?"), + paste0(fun, "(x == 0)"), + rex::rex(lint_msg_stub, "`", fun, "(x) == 0`?"), linter - ), - op = ops, - .test_name = names(ops) + ) + expect_lint( + paste0(fun, "(x == y)"), + rex::rex(lint_msg_stub, "`", fun, "(x) == y`?"), + linter + ) + expect_lint( + paste0(fun, "(x + y == 2)"), + rex::rex(lint_msg_stub, "`", fun, "(x+y) == 2`?"), + linter + ) + }, + fun = c("length", "nrow", "ncol", "NROW", "NCOL") +) + +patrick::with_parameters_test_that( + "all logical operators detected", + expect_lint( + sprintf("%s(x %s y)", fun, op), + rex::rex("`", fun, "(x) ", op, " y`?"), + length_test_linter() + ), + .cases = expand.grid( + op = c("<", "<=", ">", ">=", "==", "!="), + fun = c("length", "nrow", "ncol", "NROW", "NCOL") ) -}) +) test_that("lints vectorize", { expect_lint( From 473486f2665a2f5c1234848106058f70d142184a Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Mon, 20 Oct 2025 08:59:12 +0200 Subject: [PATCH 11/16] Remove duplicated condition from paren_body_linter(). (#2954) --- R/paren_body_linter.R | 1 - 1 file changed, 1 deletion(-) diff --git a/R/paren_body_linter.R b/R/paren_body_linter.R index b8ec09e407..a758507b29 100644 --- a/R/paren_body_linter.R +++ b/R/paren_body_linter.R @@ -36,7 +36,6 @@ paren_body_linter <- make_linter_from_xpath( or preceding-sibling::OP-LAMBDA or preceding-sibling::IF or preceding-sibling::WHILE - or preceding-sibling::OP-LAMBDA ) ] /following-sibling::expr[1] From 748de8ee5af970b0c7040f0d91a8c5a9f9f9e6ac Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Mon, 20 Oct 2025 20:37:23 +0200 Subject: [PATCH 12/16] Make the message from cyclocomp_linter() more actionable (#2953) * Make the message from cyclocomp_linter() more actionable. * Revert output changes. --------- Co-authored-by: Michael Chirico --- R/cyclocomp_linter.R | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/R/cyclocomp_linter.R b/R/cyclocomp_linter.R index b06e4fbd63..2079b41e9c 100644 --- a/R/cyclocomp_linter.R +++ b/R/cyclocomp_linter.R @@ -45,8 +45,9 @@ cyclocomp_linter <- function(complexity_limit = 15L) { column_number = source_expression[["column"]][1L], type = "style", message = sprintf( - "Reduce the cyclomatic complexity of this expression from %d to at most %d.", - complexity, complexity_limit + "Reduce the cyclomatic complexity of this expression from %d to at most %d. %s", + complexity, complexity_limit, + "Consider replacing high-complexity sections like loops and branches with helper functions." ), ranges = list(rep(col1, 2L)), line = source_expression$lines[1L] From cdc91dde184c002da92c21fbc64ba42a3673c565 Mon Sep 17 00:00:00 2001 From: Marco Colombo Date: Wed, 22 Oct 2025 22:34:40 +0200 Subject: [PATCH 13/16] Note potential danger if argument can be NA in scalar_in_linter(). (#2958) --- R/scalar_in_linter.R | 8 ++++++-- man/scalar_in_linter.Rd | 5 ++++- 2 files changed, 10 insertions(+), 3 deletions(-) diff --git a/R/scalar_in_linter.R b/R/scalar_in_linter.R index 0f0828d78f..6c9d26d613 100644 --- a/R/scalar_in_linter.R +++ b/R/scalar_in_linter.R @@ -1,7 +1,10 @@ #' Block usage like x %in% "a" #' #' `vector %in% set` is appropriate for matching a vector to a set, but if -#' that set has size 1, `==` is more appropriate. +#' that set has size 1, `==` is more appropriate. However, if `vector` has +#' also size 1 and can be `NA`, the use of `==` should be accompanied by extra +#' protection for the missing case (for example, `isTRUE(NA == "arg")` or +#' `!is.na(x) && x == "arg"`). #' #' `scalar %in% vector` is OK, because the alternative (`any(vector == scalar)`) #' is more circuitous & potentially less clear. @@ -46,7 +49,8 @@ scalar_in_linter <- function(in_operators = NULL) { in_op <- xml_find_chr(bad_expr, "string(SPECIAL)") lint_msg <- paste0( "Use comparison operators (e.g. ==, !=, etc.) to match length-1 scalars instead of ", in_op, ". ", - "Note that comparison operators preserve NA where ", in_op, " does not." + "Note that if x can be NA, x == 'arg' is NA whereas x ", in_op, " 'arg' is FALSE, ", + "so consider extra protection for the missing case in your code." ) xml_nodes_to_lints( diff --git a/man/scalar_in_linter.Rd b/man/scalar_in_linter.Rd index 1773c699f8..6b8db47bea 100644 --- a/man/scalar_in_linter.Rd +++ b/man/scalar_in_linter.Rd @@ -12,7 +12,10 @@ e.g. \code{{data.table}}'s \verb{\%chin\%} operator.} } \description{ \code{vector \%in\% set} is appropriate for matching a vector to a set, but if -that set has size 1, \code{==} is more appropriate. +that set has size 1, \code{==} is more appropriate. However, if \code{vector} has +also size 1 and can be \code{NA}, the use of \code{==} should be accompanied by extra +protection for the missing case (for example, \code{isTRUE(NA == "arg")} or +\code{!is.na(x) && x == "arg"}). } \details{ \code{scalar \%in\% vector} is OK, because the alternative (\code{any(vector == scalar)}) From 6d5115524c8f5e12d7eb767b21aa0cd1f02f8ca8 Mon Sep 17 00:00:00 2001 From: "dependabot[bot]" <49699333+dependabot[bot]@users.noreply.github.com> Date: Tue, 28 Oct 2025 14:37:29 -0700 Subject: [PATCH 14/16] Bump actions/upload-artifact from 4 to 5 (#2959) Bumps [actions/upload-artifact](https://github.com/actions/upload-artifact) from 4 to 5. - [Release notes](https://github.com/actions/upload-artifact/releases) - [Commits](https://github.com/actions/upload-artifact/compare/v4...v5) --- updated-dependencies: - dependency-name: actions/upload-artifact dependency-version: '5' dependency-type: direct:production update-type: version-update:semver-major ... Signed-off-by: dependabot[bot] Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> --- .github/workflows/test-coverage.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.github/workflows/test-coverage.yaml b/.github/workflows/test-coverage.yaml index 4a4ba729f3..2831f43c23 100644 --- a/.github/workflows/test-coverage.yaml +++ b/.github/workflows/test-coverage.yaml @@ -57,7 +57,7 @@ jobs: - name: Upload test results if: failure() - uses: actions/upload-artifact@v4 + uses: actions/upload-artifact@v5 with: name: coverage-test-failures path: ${{ runner.temp }}/package From 521b4b7aef8143fb78802beb96cf6bd8ac86a252 Mon Sep 17 00:00:00 2001 From: Tim Taylor Date: Mon, 4 Aug 2025 19:17:41 +0100 Subject: [PATCH 15/16] feat: argument to disable linting of `(` for auto-printing closes #2916 --- NEWS.md | 1 + 1 file changed, 1 insertion(+) diff --git a/NEWS.md b/NEWS.md index 1e0c16530e..191cb1eb1b 100644 --- a/NEWS.md +++ b/NEWS.md @@ -51,6 +51,7 @@ * `use_lintr()` adds the created `.lintr` file to the `.Rbuildignore` if run in a package (#2926, initial work by @MEO265, finalized by @Bisaloo). * `implicit_assignment_linter()` gains argument `allow_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). * `length_test_linter()` is extended to check incorrect usage of `nrow()`, `ncol()`, `NROW()`, `NCOL()` (#2933, @mcol). +* `implicit_assignment_linter()` gains argument `allow_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). ### New linters From 60f203e164223d2a628d4aefc09ffd8c9b91b6b1 Mon Sep 17 00:00:00 2001 From: Tim Taylor Date: Wed, 29 Oct 2025 10:47:43 +0000 Subject: [PATCH 16/16] rename allow_print -> allow_paren_print --- NEWS.md | 2 +- R/implicit_assignment_linter.R | 8 ++++---- man/implicit_assignment_linter.Rd | 6 +++--- tests/testthat/test-implicit_assignment_linter.R | 4 ++-- 4 files changed, 10 insertions(+), 10 deletions(-) diff --git a/NEWS.md b/NEWS.md index 191cb1eb1b..db80dbcaae 100644 --- a/NEWS.md +++ b/NEWS.md @@ -51,7 +51,7 @@ * `use_lintr()` adds the created `.lintr` file to the `.Rbuildignore` if run in a package (#2926, initial work by @MEO265, finalized by @Bisaloo). * `implicit_assignment_linter()` gains argument `allow_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). * `length_test_linter()` is extended to check incorrect usage of `nrow()`, `ncol()`, `NROW()`, `NCOL()` (#2933, @mcol). -* `implicit_assignment_linter()` gains argument `allow_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). +* `implicit_assignment_linter()` gains argument `allow_paren_print` to disable lints for the use of `(` for auto-printing (#2919, @TimTaylor). ### New linters diff --git a/R/implicit_assignment_linter.R b/R/implicit_assignment_linter.R index 6092645115..4dcaff1323 100644 --- a/R/implicit_assignment_linter.R +++ b/R/implicit_assignment_linter.R @@ -9,7 +9,7 @@ #' @param allow_scoped Logical, default `FALSE`. If `TRUE`, "scoped assignments", #' where the object is assigned in the statement beginning a branch and used only #' within that branch, are skipped. -#' @param allow_print Logical, default `FALSE`. If `TRUE`, using `(` for auto-printing +#' @param allow_parent_print Logical, default `FALSE`. If `TRUE`, using `(` for auto-printing #' at the top-level is not linted. #' #' @examples @@ -63,7 +63,7 @@ #' #' lint( #' text = "(x <- 1)", -#' linters = implicit_assignment_linter(allow_print = TRUE) +#' linters = implicit_assignment_linter(allow_paren_print = TRUE) #' ) #' #' @evalRd rd_tags("implicit_assignment_linter") @@ -75,7 +75,7 @@ implicit_assignment_linter <- function(except = c("bquote", "expression", "expr", "quo", "quos", "quote"), allow_lazy = FALSE, allow_scoped = FALSE, - allow_print = FALSE) { + allow_paren_print = FALSE) { stopifnot(is.null(except) || is.character(except)) if (length(except) > 0L) { @@ -130,7 +130,7 @@ implicit_assignment_linter <- function(except = c("bquote", "expression", "expr" bad_expr <- xml_find_all(xml, xpath) print_only <- !is.na(xml_find_first(bad_expr, "parent::expr[parent::exprlist and *[1][self::OP-LEFT-PAREN]]")) - if (allow_print) { + if (allow_paren_print) { bad_expr <- bad_expr[!print_only] } diff --git a/man/implicit_assignment_linter.Rd b/man/implicit_assignment_linter.Rd index a9e3e99b1c..6d93a1dbea 100644 --- a/man/implicit_assignment_linter.Rd +++ b/man/implicit_assignment_linter.Rd @@ -8,7 +8,7 @@ implicit_assignment_linter( except = c("bquote", "expression", "expr", "quo", "quos", "quote"), allow_lazy = FALSE, allow_scoped = FALSE, - allow_print = FALSE + allow_paren_print = FALSE ) } \arguments{ @@ -21,7 +21,7 @@ trigger conditionally (e.g. in the RHS of \code{&&} or \code{||} expressions) ar where the object is assigned in the statement beginning a branch and used only within that branch, are skipped.} -\item{allow_print}{Logical, default \code{FALSE}. If \code{TRUE}, using \code{(} for auto-printing +\item{allow_parent_print}{Logical, default \code{FALSE}. If \code{TRUE}, using \code{(} for auto-printing at the top-level is not linted.} } \description{ @@ -79,7 +79,7 @@ lint( lint( text = "(x <- 1)", - linters = implicit_assignment_linter(allow_print = TRUE) + linters = implicit_assignment_linter(allow_paren_print = TRUE) ) } diff --git a/tests/testthat/test-implicit_assignment_linter.R b/tests/testthat/test-implicit_assignment_linter.R index 7e0b56c839..341d44ef4e 100644 --- a/tests/testthat/test-implicit_assignment_linter.R +++ b/tests/testthat/test-implicit_assignment_linter.R @@ -477,9 +477,9 @@ test_that("call-less '(' mentions avoiding implicit printing", { ) }) -test_that("allow_print allows `(` for auto printing", { +test_that("allow_paren_print allows `(` for auto printing", { lint_message <- rex::rex("Avoid implicit assignments in function calls.") - linter <- implicit_assignment_linter(allow_print = TRUE) + linter <- implicit_assignment_linter(allow_paren_print = TRUE) expect_no_lint("(a <- foo())", linter) # Doesn't effect other cases