diff --git a/DESCRIPTION b/DESCRIPTION index fecc8b63e..48c2b13b3 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -78,6 +78,7 @@ Collate: 'comment_linters.R' 'comments.R' 'comparison_negation_linter.R' + 'condition_call_linter.R' 'condition_message_linter.R' 'conjunct_test_linter.R' 'consecutive_assertion_linter.R' diff --git a/NAMESPACE b/NAMESPACE index 76ec11454..7f02530be 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -37,6 +37,7 @@ export(closed_curly_linter) export(commas_linter) export(commented_code_linter) export(comparison_negation_linter) +export(condition_call_linter) export(condition_message_linter) export(conjunct_test_linter) export(consecutive_assertion_linter) diff --git a/NEWS.md b/NEWS.md index 980a91c9f..a3615b629 100644 --- a/NEWS.md +++ b/NEWS.md @@ -34,6 +34,7 @@ ### New linters +* `condition_call_linter()` for ensuring consistent use of `call.` in `warning()` and `stop()`. The default `call. = FALSE` follows the tidyverse guidance of not displaying the call (#2226, @Bisaloo) * `sample_int_linter()` for encouraging `sample.int(n, ...)` over equivalents like `sample(1:n, ...)` (part of #884, @MichaelChirico). * `stopifnot_all_linter()` discourages tests with `all()` like `stopifnot(all(x > 0))`; `stopifnot()` runs `all()` itself, and uses a better error message (part of #884, @MichaelChirico). * `comparison_negation_linter()` for discouraging negated comparisons when a direct negation is preferable, e.g. `!(x == y)` could be `x != y` (part of #884, @MichaelChirico). diff --git a/R/condition_call_linter.R b/R/condition_call_linter.R new file mode 100644 index 000000000..1a618d8ba --- /dev/null +++ b/R/condition_call_linter.R @@ -0,0 +1,116 @@ +#' Recommend usage of `call. = FALSE` in conditions +#' +#' This linter, with the default `display_call = FALSE`, enforces the +#' recommendation of the tidyverse design guide regarding displaying error +#' calls. +#' +#' @param display_call Logical specifying expected behaviour regarding `call.` +#' argument in conditions. +#' - `NA` forces providing `call.=` but ignores its value (this can be used in +#' cases where you expect a mix of `call. = FALSE` and `call. = TRUE`) +#' - lints `call. = FALSE` +#' - forces `call. = FALSE` (lints `call. = TRUE` or missing `call.=` value) +#' +#' +#' @examples +#' # will produce lints +#' lint( +#' text = "stop('test')", +#' linters = condition_call_linter() +#' ) +#' +#' lint( +#' text = "stop('test', call. = TRUE)", +#' linters = condition_call_linter() +#' ) +#' +#' lint( +#' text = "stop('test', call. = FALSE)", +#' linters = condition_call_linter(display_call = TRUE) +#' ) +#' +#' lint( +#' text = "stop('this is a', 'test', call. = FALSE)", +#' linters = condition_call_linter(display_call = TRUE) +#' ) +#' +#' # okay +#' lint( +#' text = "stop('test', call. = FALSE)", +#' linters = condition_call_linter() +#' ) +#' +#' lint( +#' text = "stop('this is a', 'test', call. = FALSE)", +#' linters = condition_call_linter() +#' ) +#' +#' lint( +#' text = "stop('test', call. = TRUE)", +#' linters = condition_call_linter(display_call = TRUE) +#' ) +#' +#' @evalRd rd_tags("condition_call_linter") +#' @seealso +#' - [linters] for a complete list of linters available in lintr. +#' - > +#' @export +condition_call_linter <- function(display_call = FALSE) { + call_xpath <- glue::glue(" + following-sibling::SYMBOL_SUB[text() = 'call.'] + /following-sibling::expr[1] + /NUM_CONST[text() = '{!display_call}'] + ") + no_call_xpath <- " + parent::expr[ + count(SYMBOL_SUB[text() = 'call.']) = 0 + ] + " + + if (is.na(display_call)) { + frag <- no_call_xpath + } else if (display_call) { + frag <- call_xpath + } else { + # call. = TRUE can be expressed in two way: + # - either explicitly with call. = TRUE + # - or by implicitly relying on the default + frag <- xp_or(call_xpath, no_call_xpath) + } + + xpath <- glue::glue(" + //SYMBOL_FUNCTION_CALL[text() = 'stop' or text() = 'warning'] + /parent::expr[{frag}] + /parent::expr + ") + + Linter(linter_level = "expression", function(source_expression) { + + xml <- source_expression$xml_parsed_content + if (is.null(xml)) return(list()) + + bad_expr <- xml_find_all(xml, xpath) + + if (is.na(display_call)) { + msg <- glue::glue( + "Provide an explicit value for call. in {xp_call_name(bad_expr)}()." + ) + } else if (display_call) { + msg <- glue::glue( + "Use {xp_call_name(bad_expr)}(.) to display call in error message." + ) + } else { + msg <- glue::glue( + "Use {xp_call_name(bad_expr)}(., call. = FALSE)", + " to not display call in error message." + ) + } + + xml_nodes_to_lints( + bad_expr, + source_expression = source_expression, + lint_message = msg, + type = "warning" + ) + }) +} diff --git a/R/linter_tag_docs.R b/R/linter_tag_docs.R index 10facff84..b7777faf3 100644 --- a/R/linter_tag_docs.R +++ b/R/linter_tag_docs.R @@ -119,3 +119,13 @@ NULL #' @evalRd rd_linters("regex") #' @seealso [linters] for a complete list of linters available in lintr. NULL + +#' Tidyverse design linters +#' @name tidy_design_linters +#' @description +#' Linters based on guidelines described in the 'Tidy design principles' book. +#' @evalRd rd_linters("tidy_design") +#' @seealso +#' - [linters] for a complete list of linters available in lintr. +#' - +NULL diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 5a32733f9..effcbb1a3 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -11,6 +11,7 @@ closed_curly_linter,defunct commas_linter,style readability default configurable commented_code_linter,style readability best_practices default comparison_negation_linter,readability consistency +condition_call_linter,style tidy_design best_practices configurable condition_message_linter,best_practices consistency conjunct_test_linter,package_development best_practices readability configurable pkg_testthat consecutive_assertion_linter,style readability consistency diff --git a/man/best_practices_linters.Rd b/man/best_practices_linters.Rd index cd42b2fb6..9df79f943 100644 --- a/man/best_practices_linters.Rd +++ b/man/best_practices_linters.Rd @@ -18,6 +18,7 @@ The following linters are tagged with 'best_practices': \item{\code{\link{boolean_arithmetic_linter}}} \item{\code{\link{class_equals_linter}}} \item{\code{\link{commented_code_linter}}} +\item{\code{\link{condition_call_linter}}} \item{\code{\link{condition_message_linter}}} \item{\code{\link{conjunct_test_linter}}} \item{\code{\link{cyclocomp_linter}}} diff --git a/man/condition_call_linter.Rd b/man/condition_call_linter.Rd new file mode 100644 index 000000000..73302b7fe --- /dev/null +++ b/man/condition_call_linter.Rd @@ -0,0 +1,71 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/condition_call_linter.R +\name{condition_call_linter} +\alias{condition_call_linter} +\title{Recommend usage of \code{call. = FALSE} in conditions} +\usage{ +condition_call_linter(display_call = FALSE) +} +\arguments{ +\item{display_call}{Logical specifying expected behaviour regarding \code{call.} +argument in conditions. +\itemize{ +\item \code{NA} forces providing \verb{call.=} but ignores its value (this can be used in +cases where you expect a mix of \code{call. = FALSE} and \code{call. = TRUE}) +\item lints \code{call. = FALSE} +\item forces \code{call. = FALSE} (lints \code{call. = TRUE} or missing \verb{call.=} value) +}} +} +\description{ +This linter, with the default \code{display_call = FALSE}, enforces the +recommendation of the tidyverse design guide regarding displaying error +calls. +} +\examples{ +# will produce lints +lint( + text = "stop('test')", + linters = condition_call_linter() +) + +lint( + text = "stop('test', call. = TRUE)", + linters = condition_call_linter() +) + +lint( + text = "stop('test', call. = FALSE)", + linters = condition_call_linter(display_call = TRUE) +) + +lint( + text = "stop('this is a', 'test', call. = FALSE)", + linters = condition_call_linter(display_call = TRUE) +) + +# okay +lint( + text = "stop('test', call. = FALSE)", + linters = condition_call_linter() +) + +lint( + text = "stop('this is a', 'test', call. = FALSE)", + linters = condition_call_linter() +) + +lint( + text = "stop('test', call. = TRUE)", + linters = condition_call_linter(display_call = TRUE) +) + +} +\seealso{ +\itemize{ +\item \link{linters} for a complete list of linters available in lintr. +\item \url{https://design.tidyverse.org/err-call.html}> +} +} +\section{Tags}{ +\link[=best_practices_linters]{best_practices}, \link[=configurable_linters]{configurable}, \link[=style_linters]{style}, \link[=tidy_design_linters]{tidy_design} +} diff --git a/man/configurable_linters.Rd b/man/configurable_linters.Rd index b8dc83c49..4f22ee1a7 100644 --- a/man/configurable_linters.Rd +++ b/man/configurable_linters.Rd @@ -17,6 +17,7 @@ The following linters are tagged with 'configurable': \item{\code{\link{backport_linter}}} \item{\code{\link{brace_linter}}} \item{\code{\link{commas_linter}}} +\item{\code{\link{condition_call_linter}}} \item{\code{\link{conjunct_test_linter}}} \item{\code{\link{consecutive_mutate_linter}}} \item{\code{\link{cyclocomp_linter}}} diff --git a/man/linters.Rd b/man/linters.Rd index 8f5a6307f..e436c0f05 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -17,9 +17,9 @@ see also \code{\link[=available_tags]{available_tags()}}. \section{Tags}{ The following tags exist: \itemize{ -\item{\link[=best_practices_linters]{best_practices} (63 linters)} +\item{\link[=best_practices_linters]{best_practices} (64 linters)} \item{\link[=common_mistakes_linters]{common_mistakes} (10 linters)} -\item{\link[=configurable_linters]{configurable} (40 linters)} +\item{\link[=configurable_linters]{configurable} (41 linters)} \item{\link[=consistency_linters]{consistency} (32 linters)} \item{\link[=correctness_linters]{correctness} (7 linters)} \item{\link[=default_linters]{default} (26 linters)} @@ -31,7 +31,8 @@ The following tags exist: \item{\link[=readability_linters]{readability} (65 linters)} \item{\link[=regex_linters]{regex} (4 linters)} \item{\link[=robustness_linters]{robustness} (17 linters)} -\item{\link[=style_linters]{style} (40 linters)} +\item{\link[=style_linters]{style} (41 linters)} +\item{\link[=tidy_design_linters]{tidy_design} (1 linters)} } } \section{Linters}{ @@ -48,6 +49,7 @@ The following linters exist: \item{\code{\link{commas_linter}} (tags: configurable, default, readability, style)} \item{\code{\link{commented_code_linter}} (tags: best_practices, default, readability, style)} \item{\code{\link{comparison_negation_linter}} (tags: consistency, readability)} +\item{\code{\link{condition_call_linter}} (tags: best_practices, configurable, style, tidy_design)} \item{\code{\link{condition_message_linter}} (tags: best_practices, consistency)} \item{\code{\link{conjunct_test_linter}} (tags: best_practices, configurable, package_development, pkg_testthat, readability)} \item{\code{\link{consecutive_assertion_linter}} (tags: consistency, readability, style)} diff --git a/man/style_linters.Rd b/man/style_linters.Rd index 44de2fa03..9ef22feda 100644 --- a/man/style_linters.Rd +++ b/man/style_linters.Rd @@ -16,6 +16,7 @@ The following linters are tagged with 'style': \item{\code{\link{brace_linter}}} \item{\code{\link{commas_linter}}} \item{\code{\link{commented_code_linter}}} +\item{\code{\link{condition_call_linter}}} \item{\code{\link{consecutive_assertion_linter}}} \item{\code{\link{cyclocomp_linter}}} \item{\code{\link{extraction_operator_linter}}} diff --git a/man/tidy_design_linters.Rd b/man/tidy_design_linters.Rd new file mode 100644 index 000000000..b180248c7 --- /dev/null +++ b/man/tidy_design_linters.Rd @@ -0,0 +1,20 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/linter_tag_docs.R +\name{tidy_design_linters} +\alias{tidy_design_linters} +\title{Tidyverse design linters} +\description{ +Linters based on guidelines described in the 'Tidy design principles' book. +} +\seealso{ +\itemize{ +\item \link{linters} for a complete list of linters available in lintr. +\item \url{https://design.tidyverse.org/} +} +} +\section{Linters}{ +The following linters are tagged with 'tidy_design': +\itemize{ +\item{\code{\link{condition_call_linter}}} +} +} diff --git a/tests/testthat/test-condition_call_linter.R b/tests/testthat/test-condition_call_linter.R new file mode 100644 index 000000000..6ef37aa0c --- /dev/null +++ b/tests/testthat/test-condition_call_linter.R @@ -0,0 +1,39 @@ +test_that("condition_call_linter skips allowed usages", { + linter <- condition_call_linter() + + expect_lint("stop('test', call. = FALSE)", NULL, linter) + + # works even with multiple arguments + expect_lint("stop('this is a', 'test', call. = FALSE)", NULL, linter) + + linter <- condition_call_linter(display_call = TRUE) + + expect_lint("stop('test', call. = TRUE)", NULL, linter) + + linter <- condition_call_linter(display_call = NA) + + expect_lint("stop('test', call. = TRUE)", NULL, linter) + expect_lint("stop('test', call. = FALSE)", NULL, linter) +}) + +patrick::with_parameters_test_that( + "condition_call_linter blocks disallowed usages", + { + linter <- condition_call_linter() + lint_message <- rex::rex(call_name, anything, "to not display call") + + expect_lint(paste0(call_name, "('test')"), lint_message, linter) + expect_lint(paste0(call_name, "('test', call. = TRUE)"), lint_message, linter) + + linter <- condition_call_linter(display_call = TRUE) + lint_message <- rex::rex(call_name, anything, "to display call") + + expect_lint(paste0(call_name, "('test', call. = FALSE)"), lint_message, linter) + + linter <- condition_call_linter(display_call = NA) + lint_message <- rex::rex("explicit value", anything, call_name) + + expect_lint(paste0(call_name, "('test')"), lint_message, linter) + }, + call_name = c("stop", "warning") +)