Skip to content

Commit

Permalink
Clean-up: be consistent in action-reason structure to lint messages (#…
Browse files Browse the repository at this point in the history
…2385)

* Batch of message consistency checks

* Update R/class_equals_linter.R

Co-authored-by: Indrajeet Patil <[email protected]>

* Update R/is_numeric_linter.R

Co-authored-by: Indrajeet Patil <[email protected]>

* finish first pass

* progress fixing tests

* a near-complete pass

* done tests?

* fix expect_lint exxample

* delint

* NEWS

* correct spelling mistakes

* Update R/class_equals_linter.R

Co-authored-by: AshesITR <[email protected]>

* Update NEWS.md

Co-authored-by: AshesITR <[email protected]>

* simplify replacement/duplicate ifelse()

* grammar

* calls with ()

* condense

* fixes

* condense, set patrick dependency

* consistency in file name

* checks= is required here

* fix lint message

* condense

* review changes

* revert

* commas feedback

* implicit integers feedback

* one more revert

* drop "the equivalent"

* restore after fix already in main

---------

Co-authored-by: Indrajeet Patil <[email protected]>
Co-authored-by: AshesITR <[email protected]>
  • Loading branch information
3 people authored Dec 6, 2023
1 parent f262dd1 commit e84ab51
Show file tree
Hide file tree
Showing 73 changed files with 333 additions and 387 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ Suggests:
cli,
httr (>= 1.2.1),
jsonlite,
patrick,
patrick (>= 0.2.0),
rlang,
rmarkdown,
rstudioapi (>= 0.2),
Expand Down
3 changes: 2 additions & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,11 +11,12 @@
+ Linters `closed_curly_linter()`, `open_curly_linter()`, `paren_brace_linter()`, and `semicolon_terminator_linter()`.
+ Helper `with_defaults()`.
* `all_linters()` has signature `all_linters(..., packages)` rather than `all_linters(packages, ...)` (#2332, @MichaelChirico). This forces `packages=` to be supplied by name and will break users who rely on supplying `packages=` positionally, of which we found none searching GitHub.
* Adjusted various lint messages for consistency in readability (#1330, @MichaelChirico). In general, we favor lint messages to be phrased like "Action, reason" to but the "what" piece of the message front-and-center. This may be a breaking change for code that tests the specific phrasing of lints.

## Bug fixes

* `object_name_linter()` no longer errors when user-supplied `regexes=` have capture groups (#2188, @MichaelChirico).
* `.lintr` config validation correctly accepts regular exressions which only compile under `perl = TRUE` (#2375, @MichaelChirico). These have always been valid (since `rex::re_matches()`, which powers the lint exclusion logic, also uses this setting), but the new up-front validation in v3.1.1 incorrectly used `perl = FALSE`.
* `.lintr` config validation correctly accepts regular expressions which only compile under `perl = TRUE` (#2375, @MichaelChirico). These have always been valid (since `rex::re_matches()`, which powers the lint exclusion logic, also uses this setting), but the new up-front validation in v3.1.1 incorrectly used `perl = FALSE`.

## Changes to default linters

Expand Down
2 changes: 1 addition & 1 deletion R/assignment_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ assignment_linter <- function(allow_cascading_assign = TRUE,
operator <- xml_text(bad_expr)
lint_message_fmt <- rep("Use <-, not %s, for assignment.", length(operator))
lint_message_fmt[operator %in% c("<<-", "->>")] <-
"%s can have hard-to-predict behavior; prefer assigning to a specific environment instead (with assign() or <-)."
"Replace %s by assigning to a specific environment (with assign() or <-) to avoid hard-to-predict behavior."
lint_message_fmt[operator == "%<>%"] <-
"Avoid the assignment pipe %s; prefer using <- and %%>%% separately."

Expand Down
5 changes: 1 addition & 4 deletions R/backport_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -58,10 +58,7 @@ backport_linter <- function(r_version = getRversion(), except = character()) {
needs_backport <- !is.na(bad_versions)

lint_message <- sprintf(
paste(
"%s (R %s) is not available for dependency R >= %s.",
"Use the `except` argument of `backport_linter()` to configure available backports."
),
"%s (R %s) is not available for dependency R >= %s.",
all_names[needs_backport],
bad_versions[needs_backport],
r_version
Expand Down
2 changes: 1 addition & 1 deletion R/brace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -194,7 +194,7 @@ brace_linter <- function(allow_single_line = FALSE) {
xml_nodes_to_lints(
xml_find_all(xml, xp_function_brace),
source_expression = source_expression,
lint_message = "Any function spanning multiple lines should use curly braces."
lint_message = "Use curly braces for any function spanning multiple lines."
)
)

Expand Down
2 changes: 1 addition & 1 deletion R/class_equals_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,7 @@ class_equals_linter <- function() {

operator <- xml_find_chr(bad_expr, "string(*[2])")
lint_message <- sprintf(
"Instead of comparing class(x) with %s, use inherits(x, 'class-name') or is.<class> or is(x, 'class')",
"Use inherits(x, 'class-name'), is.<class> or is(x, 'class') instead of comparing class(x) with %s.",
operator
)
xml_nodes_to_lints(
Expand Down
4 changes: 2 additions & 2 deletions R/commas_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,15 +84,15 @@ commas_linter <- function(allow_trailing = FALSE) {
before_lints <- xml_nodes_to_lints(
xml_find_all(xml, xpath_before),
source_expression = source_expression,
lint_message = "Commas should never have a space before.",
lint_message = "Remove spaces before a comma.",
range_start_xpath = "number(./preceding-sibling::*[1]/@col2 + 1)", # start after preceding expression
range_end_xpath = "number(./@col1 - 1)" # end before comma
)

after_lints <- xml_nodes_to_lints(
xml_find_all(xml, xpath_after),
source_expression = source_expression,
lint_message = "Commas should always have a space after.",
lint_message = "Put a space after a comma.",
range_start_xpath = "number(./@col2 + 1)", # start and end after comma
range_end_xpath = "number(./@col2 + 1)"
)
Expand Down
4 changes: 2 additions & 2 deletions R/comment_linters.R
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,7 @@ commented_code_linter <- function() {
lint_list <- xml_nodes_to_lints(
all_comment_nodes[is_parsable],
source_expression = source_expression,
lint_message = "Commented code should be removed."
lint_message = "Remove commented code."
)

# Location info needs updating
Expand Down Expand Up @@ -175,7 +175,7 @@ todo_comment_linter <- function(todo = c("todo", "fixme")) {
line_number = token[["line1"]],
column_number = token[["col1"]],
type = "style",
message = "TODO comments should be removed.",
message = "Remove TODO comments.",
line = source_expression[["lines"]][[as.character(token[["line1"]])]],
ranges = list(c(token[["col1"]], token[["col2"]]))
)
Expand Down
41 changes: 12 additions & 29 deletions R/condition_call_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -58,58 +58,41 @@
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}']
/following-sibling::expr[1]
/NUM_CONST[text() = '{!display_call}']
")
no_call_xpath <- "
parent::expr[
count(SYMBOL_SUB[text() = 'call.']) = 0
]
"
no_call_xpath <- "parent::expr[not(SYMBOL_SUB[text() = 'call.'])]"

if (is.na(display_call)) {
frag <- no_call_xpath
call_cond <- no_call_xpath
msg_fmt <- "Provide an explicit value for `call.` in %s()."
} else if (display_call) {
frag <- call_xpath
call_cond <- call_xpath
msg_fmt <- "Use %s(.) to display the call in an error message."
} 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)
call_cond <- xp_or(call_xpath, no_call_xpath)
msg_fmt <- "Use %s(., call. = FALSE) not to display the call in an error message."
}

xpath <- glue::glue("
//SYMBOL_FUNCTION_CALL[text() = 'stop' or text() = 'warning']
/parent::expr[{frag}]
/parent::expr
/parent::expr[{call_cond}]
/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,
lint_message = sprintf(msg_fmt, xp_call_name(bad_expr)),
type = "warning"
)
})
Expand Down
6 changes: 3 additions & 3 deletions R/conjunct_test_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -127,13 +127,13 @@ conjunct_test_linter <- function(allow_named_stopifnot = TRUE,
operator <- xml_find_chr(test_expr, "string(expr/*[self::AND2 or self::OR2])")
replacement_fmt <- ifelse(
matched_fun %in% c("expect_true", "expect_false"),
"write multiple expectations like %1$s(A) and %1$s(B)",
"write multiple conditions like %s(A, B)."
"Write multiple expectations like %1$s(A) and %1$s(B)",
"Write multiple conditions like %s(A, B)"
)
lint_message <- paste(
sprintf("Instead of %s(A %s B),", matched_fun, operator),
# as.character() needed for 0-lint case where ifelse(logical(0)) returns logical(0)
sprintf(as.character(replacement_fmt), matched_fun),
sprintf("instead of %s(A %s B).", matched_fun, operator),
"The latter will produce better error messages in the case of failure."
)
lints <- xml_nodes_to_lints(
Expand Down
4 changes: 2 additions & 2 deletions R/cyclocomp_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ cyclocomp_linter <- function(complexity_limit = 15L) {
column_number = source_expression[["column"]][1L],
type = "style",
message = sprintf(
"Functions should have cyclomatic complexity of less than %d, this has %d.",
complexity_limit, complexity
"Reduce the cyclomatic complexity of this function from %d to at most %d.",
complexity, complexity_limit
),
ranges = list(rep(col1, 2L)),
line = source_expression$lines[1L]
Expand Down
2 changes: 1 addition & 1 deletion R/duplicate_argument_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ duplicate_argument_linter <- function(except = c("mutate", "transmute")) {
xml_nodes_to_lints(
unlist(all_arg_nodes, recursive = FALSE)[unlist(is_duplicated)],
source_expression = source_expression,
lint_message = "Duplicate arguments in function call.",
lint_message = "Avoid duplicate arguments in function calls.",
type = "warning"
)
})
Expand Down
10 changes: 5 additions & 5 deletions R/expect_lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,16 +25,16 @@
#' 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", "trailing blank", trailing_blank_lines_linter())
#' expect_lint("a\n", list(message = "trailing blank", 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("trailing blank", "trailing blank"), trailing_blank_lines_linter())
#' expect_lint(
#' "a\n\n",
#' list(
#' list(message = "superfluous", line_number = 2),
#' list(message = "superfluous", line_number = 3)
#' list(message = "trailing blank", line_number = 2),
#' list(message = "trailing blank", line_number = 3)
#' ),
#' trailing_blank_lines_linter()
#' )
Expand Down
20 changes: 11 additions & 9 deletions R/fixed_regex_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -145,25 +145,27 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) {

patterns <- xml_find_all(xml, xpath)
pattern_strings <- get_r_string(patterns)

is_static <- is_not_regex(pattern_strings, allow_unescaped)
patterns <- patterns[is_static]
pattern_strings <- pattern_strings[is_static]

fixed_equivalent <- encodeString(get_fixed_string(pattern_strings[is_static]), quote = '"', justify = "none")
call_name <- xml_find_chr(patterns[is_static], "string(preceding-sibling::expr[last()]/SYMBOL_FUNCTION_CALL)")
fixed_equivalent <- encodeString(get_fixed_string(pattern_strings), quote = '"', justify = "none")
call_name <- xml_find_chr(patterns, "string(preceding-sibling::expr[last()]/SYMBOL_FUNCTION_CALL)")

is_stringr <- startsWith(call_name, "str_")
replacement <- ifelse(
replacement_suggestion <- ifelse(
is_stringr,
sprintf("stringr::fixed(%s)", fixed_equivalent),
fixed_equivalent
sprintf("stringr::fixed(%s) as the pattern", fixed_equivalent),
sprintf("%s with fixed = TRUE", fixed_equivalent)
)
msg <- paste(
"This regular expression is static, i.e., its matches can be expressed as a fixed substring expression, which",
"is faster to compute. Here, you can use",
replacement, ifelse(is_stringr, "as the pattern.", "with fixed = TRUE.")
"Use", replacement_suggestion, "here. This regular expression is static, i.e.,",
"its matches can be expressed as a fixed substring expression, which is faster to compute."
)

xml_nodes_to_lints(
patterns[is_static],
patterns,
source_expression = source_expression,
lint_message = msg,
type = "warning"
Expand Down
5 changes: 1 addition & 4 deletions R/if_not_else_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -91,10 +91,7 @@ if_not_else_linter <- function(exceptions = c("is.null", "is.na", "missing")) {
if_lints <- xml_nodes_to_lints(
if_expr,
source_expression = source_expression,
lint_message = paste(
"In a simple if/else statement,",
"prefer `if (A) x else y` to the less-readable `if (!A) y else x`."
),
lint_message = "Prefer `if (A) x else y` to the less-readable `if (!A) y else x` in a simple if/else statement.",
type = "warning"
)

Expand Down
2 changes: 1 addition & 1 deletion R/implicit_integer_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@ implicit_integer_linter <- function(allow_colon = FALSE) {
xml_nodes_to_lints(
numbers[is_implicit_integer(xml_text(numbers))],
source_expression = source_expression,
lint_message = "Integers should not be implicit. Use the form 1L for integers or 1.0 for doubles.",
lint_message = "Avoid implicit integers. Use e.g. 1L for integers or 1.0 for doubles.",
type = "style",
column_number_xpath = "number(./@col2 + 1)", # mark at end
range_end_xpath = "number(./@col2 + 1)" # end after number for easy fixing (enter "L" or ".0")
Expand Down
4 changes: 2 additions & 2 deletions R/is_numeric_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ is_numeric_linter <- function() {
or_expr,
source_expression = source_expression,
lint_message = paste(
"is.numeric(x) is the same as is.numeric(x) || is.integer(x).",
"Use `is.numeric(x)` instead of the equivalent `is.numeric(x) || is.integer(x)`.",
"Use is.double(x) to test for objects stored as 64-bit floating point."
),
type = "warning"
Expand All @@ -97,7 +97,7 @@ is_numeric_linter <- function() {
class_expr,
source_expression = source_expression,
lint_message = paste(
'is.numeric(x) is the same as class(x) %in% c("integer", "numeric").',
'Use is.numeric(x) instead of class(x) %in% c("integer", "numeric").',
"Use is.double(x) to test for objects stored as 64-bit floating point."
),
type = "warning"
Expand Down
2 changes: 1 addition & 1 deletion R/namespace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ build_ns_get_int_lints <- function(packages, symbols, symbol_nodes, namespaces,
symbol_nodes[exported],
source_expression = source_expression,
lint_message =
sprintf("'%1$s' is exported from {%2$s}. Use %2$s::%1$s instead.", symbols[exported], packages[exported]),
sprintf("Don't use `:::` to access %s, which is exported from %s.", symbols[exported], packages[exported]),
type = "warning"
)

Expand Down
4 changes: 2 additions & 2 deletions R/nzchar_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,7 @@ nzchar_linter <- function() {
comparison_expr,
source_expression = source_expression,
lint_message = paste(
'Instead of comparing strings to "", use nzchar().',
'Use nzchar() instead of comparing strings to "".',
"Note that if x is a factor, you'll have use ",
'as.character() to replicate an implicit conversion that happens in x == "".',
keepna_note
Expand All @@ -114,7 +114,7 @@ nzchar_linter <- function() {
nchar_expr,
source_expression = source_expression,
lint_message = paste(
"Instead of comparing nchar(x) to 0, use nzchar().",
"Use nzchar() instead of comparing nchar(x) to 0.",
keepna_note
),
type = "warning"
Expand Down
2 changes: 1 addition & 1 deletion R/one_call_pipe_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ one_call_pipe_linter <- function() {
xml_nodes_to_lints(
bad_expr,
source_expression = source_expression,
lint_message = paste0("Expressions with only a single call shouldn't use pipe ", pipe, "."),
lint_message = paste0("Avoid pipe ", pipe, " for expressions with only a single call."),
type = "warning"
)
})
Expand Down
2 changes: 1 addition & 1 deletion R/paren_body_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,6 @@ paren_body_linter <- make_linter_from_xpath(
]
/following-sibling::expr
",
lint_message = "There should be a space between a right parenthesis and a body expression.",
lint_message = "Put a space between a right parenthesis and a body expression.",
type = "style"
)
3 changes: 1 addition & 2 deletions R/pipe_consistency_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,8 +53,7 @@ pipe_consistency_linter <- function(pipe = c("auto", "%>%", "|>")) {
xml = c(match_magrittr, match_native),
source_expression = source_expression,
lint_message = glue(
"Found {n_magrittr} instances of %>% and {n_native} instances of |>. ",
"Stick to one pipe operator."
"Stick to one pipe operator; found {n_magrittr} instances of %>% and {n_native} instances of |>."
),
type = "style"
)
Expand Down
2 changes: 1 addition & 1 deletion R/pipe_continuation_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ pipe_continuation_linter <- function() {
pipe_exprs,
source_expression = source_expression,
lint_message = sprintf(
"`%s` should always have a space before it and a new line after it, unless the full pipeline fits on one line.",
"Put a space before `%s` and a new line after it, unless the full pipeline fits on one line.",
pipe_text
),
type = "style"
Expand Down
5 changes: 2 additions & 3 deletions R/pipe_return_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,7 @@ pipe_return_linter <- make_linter_from_xpath(
/following-sibling::expr[expr/SYMBOL_FUNCTION_CALL[text() = 'return']]
",
lint_message = paste(
"Using return() as the final step of a magrittr pipeline",
"is an anti-pattern. Instead, assign the output of the pipeline to",
"a well-named object and return that."
"Avoid return() as the final step of a magrittr pipeline. ",
"Instead, assign the output of the pipeline to a well-named object and return that."
)
)
2 changes: 1 addition & 1 deletion R/return_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
#' This linter checks functions' [return()] expressions.
#'
#' @param return_style Character string naming the return style. `"implicit"`,
#' the default, enforeces the Tidyverse guide recommendation to leave terminal
#' the default, enforces the Tidyverse guide recommendation to leave terminal
#' returns implicit. `"explicit"` style requires that `return()` always be
#' explicitly supplied.
#' @param allow_implicit_else Logical, default `TRUE`. If `FALSE`, functions with a terminal
Expand Down
4 changes: 2 additions & 2 deletions R/semicolon_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -60,8 +60,8 @@
#' - <https://style.tidyverse.org/syntax.html#semicolons>
#' @export
semicolon_linter <- function(allow_compound = FALSE, allow_trailing = FALSE) {
msg_trailing <- "Trailing semicolons are not needed."
msg_compound <- "Compound semicolons are discouraged. Replace them by a newline."
msg_trailing <- "Remove trailing semicolons."
msg_compound <- "Replace compound semicolons by a newline."

if (allow_compound && allow_trailing) {
stop(
Expand Down
Loading

0 comments on commit e84ab51

Please sign in to comment.