diff --git a/NEWS.md b/NEWS.md index aedb8948e..ada219b7d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -6,6 +6,9 @@ ## Changes to defaults +* `object_usage_linter()` gains `skip_with` argument to skip code in `with()` expressions. + To be consistent with `R CMD check`, it defaults to `TRUE` (#941, #1458, @IndrajeetPatil). + * `unused_import_linter()` can detect datasets from imported packages and no longer warns when a package is imported only for its datasets (#1545, @IndrajeetPatil). @@ -62,7 +65,7 @@ ## Bug fixes -* `object_length_linter()` does not fail in case there are dependencies with no exports (e.g. data-only packages) (#1509, @IndrajeetPatil). +* `object_length_linter()` does not fail in case there are dependencies with no exports (e.g. data-only packages) (#1424, #1509, @IndrajeetPatil). * `get_source_expressions()` no longer fails on R files that match a knitr pattern (#743, #879, #1406, @AshesITR). * Parse error lints now appear with the linter name `"error"` instead of `NA` (#1405, @AshesITR). Also, linting no longer runs if the `source_expressions` contain invalid string data that would cause error messages diff --git a/R/object_usage_linter.R b/R/object_usage_linter.R index 718f50a24..170916627 100644 --- a/R/object_usage_linter.R +++ b/R/object_usage_linter.R @@ -5,11 +5,14 @@ #' #' @param interpret_glue If `TRUE`, interpret [glue::glue()] calls to avoid false positives caused by local variables #' which are only used in a glue expression. +#' @param skip_with A logical. If `TRUE` (default), code in `with()` expressions +#' will be skipped. This argument will be passed to `skipWith` argument of +#' `codetools::checkUsage()`. #' -#' @evalRd rd_tags("object_usage_linter") +#' @evalRd rd_linters("package_development") #' @seealso [linters] for a complete list of linters available in lintr. #' @export -object_usage_linter <- function(interpret_glue = TRUE) { +object_usage_linter <- function(interpret_glue = TRUE, skip_with = TRUE) { # NB: difference across R versions in how EQ_ASSIGN is represented in the AST # (under or ) # NB: the repeated expr[2][FUNCTION] XPath has no performance impact, so the different direct assignment XPaths are @@ -69,7 +72,8 @@ object_usage_linter <- function(interpret_glue = TRUE) { fun, known_used_symbols = known_used_symbols, declared_globals = declared_globals, - start_line = as.integer(xml2::xml_attr(fun_assignment, "line1")) + start_line = as.integer(xml2::xml_attr(fun_assignment, "line1")), + skip_with = skip_with ) # TODO handle assignment functions properly @@ -196,8 +200,11 @@ get_assignment_symbols <- function(xml) { )) } -parse_check_usage <- function(expression, known_used_symbols = character(), declared_globals = character(), - start_line = 1L) { +parse_check_usage <- function(expression, + known_used_symbols = character(), + declared_globals = character(), + start_line = 1L, + skip_with = TRUE) { vals <- list() report <- function(x) { @@ -211,7 +218,8 @@ parse_check_usage <- function(expression, known_used_symbols = character(), decl expression, report = report, suppressLocalUnused = known_used_symbols, - suppressUndefined = declared_globals + suppressUndefined = declared_globals, + skipWith = skip_with )) } ) diff --git a/man/expect_lint.Rd b/man/expect_lint.Rd index f9b4fbdb0..0d154b31f 100644 --- a/man/expect_lint.Rd +++ b/man/expect_lint.Rd @@ -41,13 +41,13 @@ expect_lint("a", NULL, trailing_blank_lines_linter) # one expected lint expect_lint("a\n", "superfluous", trailing_blank_lines_linter) -expect_lint("a\n", list(message="superfluous", line_number=2), trailing_blank_lines_linter) +expect_lint("a\n", list(message = "superfluous", line_number = 2), trailing_blank_lines_linter) # several expected lints expect_lint("a\n\n", list("superfluous", "superfluous"), trailing_blank_lines_linter) expect_lint( "a\n\n", - list(list(message="superfluous", line_number=2), list(message="superfluous", line_number=3)), + list(list(message = "superfluous", line_number = 2), list(message = "superfluous", line_number = 3)), trailing_blank_lines_linter() ) } diff --git a/man/get_r_string.Rd b/man/get_r_string.Rd index 18a62941e..33a0d01ab 100644 --- a/man/get_r_string.Rd +++ b/man/get_r_string.Rd @@ -15,7 +15,7 @@ and \code{xpath} is specified, it is extracted with \code{\link[xml2:xml_find_al } \description{ Convert \code{STR_CONST} \code{text()} values into R strings. This is useful to account for arbitrary -character literals valid since R 4.0, e.g. \verb{R"------[hello]------"}, which is parsed in +character literals valid since R 4.0, e.g. \code{R"------[hello]------"}, which is parsed in R as \code{"hello"}. It is quite cumbersome to write XPaths allowing for strings like this, so whenever your linter logic requires testing a \code{STR_CONST} node's value, use this function. diff --git a/man/linters_with_tags.Rd b/man/linters_with_tags.Rd index 63c18ba76..2036a3d5a 100644 --- a/man/linters_with_tags.Rd +++ b/man/linters_with_tags.Rd @@ -38,7 +38,9 @@ linters_with_tags(tags = "package_development") linters_with_tags(tags = NULL) # Get all linters tagged as "default" from lintr and mypkg -\dontrun{linters_with_tags("default", packages = c("lintr", "mypkg"))} +\dontrun{ +linters_with_tags("default", packages = c("lintr", "mypkg")) +} } \seealso{ \link{linters_with_defaults} for basing off lintr's set of default linters. diff --git a/man/modify_defaults.Rd b/man/modify_defaults.Rd index 138420112..5e2c8b1a5 100644 --- a/man/modify_defaults.Rd +++ b/man/modify_defaults.Rd @@ -26,8 +26,10 @@ Modify a list of defaults by name, allowing for replacement, deletion and additi # add cat (with a accompanying message), # add print (unnamed, i.e. with no accompanying message) # add return (as taken from all_undesirable_functions) -my_undesirable_functions <- modify_defaults(defaults = default_undesirable_functions, - sapply=NULL, "cat"="No cat allowed", "print", all_undesirable_functions[["return"]]) +my_undesirable_functions <- modify_defaults( + defaults = default_undesirable_functions, + sapply = NULL, "cat" = "No cat allowed", "print", all_undesirable_functions[["return"]] +) } \seealso{ \link{linters_with_tags}, \link{linters_with_defaults} for creating linter lists. diff --git a/man/object_usage_linter.Rd b/man/object_usage_linter.Rd index c21679c2e..6cffca422 100644 --- a/man/object_usage_linter.Rd +++ b/man/object_usage_linter.Rd @@ -4,11 +4,15 @@ \alias{object_usage_linter} \title{Object usage linter} \usage{ -object_usage_linter(interpret_glue = TRUE) +object_usage_linter(interpret_glue = TRUE, skip_with = TRUE) } \arguments{ \item{interpret_glue}{If \code{TRUE}, interpret \code{\link[glue:glue]{glue::glue()}} calls to avoid false positives caused by local variables which are only used in a glue expression.} + +\item{skip_with}{A logical. If \code{TRUE} (default), code in \code{with()} expressions +will be skipped. This argument will be passed to \code{skipWith} argument of +\code{codetools::checkUsage()}.} } \description{ Check that closures have the proper usage using \code{\link[codetools:checkUsage]{codetools::checkUsage()}}. @@ -17,6 +21,22 @@ Note that this runs \code{\link[base:eval]{base::eval()}} on the code, so \stron \seealso{ \link{linters} for a complete list of linters available in lintr. } -\section{Tags}{ -\link[=correctness_linters]{correctness}, \link[=default_linters]{default}, \link[=executing_linters]{executing}, \link[=readability_linters]{readability}, \link[=style_linters]{style} +\section{Linters}{ +The following linters are tagged with 'package_development': +\itemize{ +\item{\code{\link{backport_linter}}} +\item{\code{\link{conjunct_test_linter}}} +\item{\code{\link{expect_comparison_linter}}} +\item{\code{\link{expect_identical_linter}}} +\item{\code{\link{expect_length_linter}}} +\item{\code{\link{expect_named_linter}}} +\item{\code{\link{expect_not_linter}}} +\item{\code{\link{expect_null_linter}}} +\item{\code{\link{expect_s3_class_linter}}} +\item{\code{\link{expect_s4_class_linter}}} +\item{\code{\link{expect_true_false_linter}}} +\item{\code{\link{expect_type_linter}}} +\item{\code{\link{package_hooks_linter}}} +\item{\code{\link{yoda_test_linter}}} +} } diff --git a/tests/testthat/test-object_usage_linter.R b/tests/testthat/test-object_usage_linter.R index 672bc3662..c8ba70523 100644 --- a/tests/testthat/test-object_usage_linter.R +++ b/tests/testthat/test-object_usage_linter.R @@ -288,7 +288,7 @@ test_that("object_usage_linter finds lints spanning multiple lines", { } "), list(message = "unknown_symbol", line_number = 4L, column_number = 5L), - object_usage_linter() + object_usage_linter(skip_with = FALSE) ) # Even ugly names are found @@ -302,7 +302,7 @@ test_that("object_usage_linter finds lints spanning multiple lines", { } "), list(line_number = 4L, column_number = 5L), - object_usage_linter() + object_usage_linter(skip_with = FALSE) ) }) @@ -480,3 +480,16 @@ test_that("unknown infix operators give good lint metadata", { object_usage_linter() ) }) + +test_that("respects `skip_with` argument for `with()` expressions", { + f <- withr::local_tempfile( + lines = c( + "test_fun <- function(df) {", + " with(df, first_var + second_var)", + "}" + ) + ) + + expect_length(lint(f, object_usage_linter(skip_with = TRUE)), 0L) + expect_length(lint(f, object_usage_linter(skip_with = FALSE)), 2L) +})