Skip to content

Commit c9c47cc

Browse files
Merge branch 'main' into sb-eq
2 parents 2d4157c + 01ccab3 commit c9c47cc

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

47 files changed

+702
-201
lines changed

.github/workflows/R-CMD-check.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ jobs:
3737
# Use older ubuntu to maximise backward compatibility
3838
- {os: ubuntu-latest, r: 'devel', http-user-agent: 'release'}
3939
- {os: ubuntu-latest, r: 'devel', http-user-agent: 'release', locale: 'en_US'}
40-
- {os: ubuntu-latest, r: 'devel', http-user-agent: 'release', locale: 'zh_CN'}
40+
- {os: ubuntu-latest, r: 'release', http-user-agent: 'release', locale: 'zh_CN'}
4141
- {os: ubuntu-latest, r: 'release'}
4242
- {os: ubuntu-latest, r: 'oldrel-1'}
4343
- {os: ubuntu-latest, r: 'oldrel-2'}

DESCRIPTION

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,7 @@ Collate:
7878
'comment_linters.R'
7979
'comments.R'
8080
'comparison_negation_linter.R'
81+
'condition_call_linter.R'
8182
'condition_message_linter.R'
8283
'conjunct_test_linter.R'
8384
'consecutive_assertion_linter.R'

NAMESPACE

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -37,6 +37,7 @@ export(closed_curly_linter)
3737
export(commas_linter)
3838
export(commented_code_linter)
3939
export(comparison_negation_linter)
40+
export(condition_call_linter)
4041
export(condition_message_linter)
4142
export(conjunct_test_linter)
4243
export(consecutive_assertion_linter)

NEWS.md

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@
1515
## Bug fixes
1616

1717
* `object_name_linter()` no longer errors when user-supplied `regexes=` have capture groups (#2188, @MichaelChirico).
18+
* `.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`.
1819

1920
## Changes to default linters
2021

@@ -31,9 +32,12 @@
3132
* `backport_linter()` is slightly faster by moving expensive computations outside the linting function (#2339, #2348, @AshesITR and @MichaelChirico).
3233
* `Linter()` has a new argument `linter_level` (default `NA`). This is used by `lint()` to more efficiently check for expression levels than the idiom `if (!is_lint_level(...)) { return(list()) }` (#2351, @AshesITR).
3334
* `string_boundary_linter()` recognizes regular expression calls like `grepl("^abc$", x)` that can be replaced by using `==` instead (#1613, @MichaelChirico).
35+
* `unreachable_code_linter()` has an argument `allow_comment_regex` for customizing which "terminal" comments to exclude (#2327, @MichaelChirico). `# nolint end` comments are always excluded, as are {covr} exclusions (e.g. `# nocov end`) by default.
36+
* `format()` and `print()` methods for `lint` and `lints` classes get a new option `width` to control the printing width of lint messages (#1884, @MichaelChirico). The default is controlled by a new option `lintr.format_width`; if unset, no wrapping occurs (matching earlier behavior).
3437

3538
### New linters
3639

40+
* `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)
3741
* `sample_int_linter()` for encouraging `sample.int(n, ...)` over equivalents like `sample(1:n, ...)` (part of #884, @MichaelChirico).
3842
* `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).
3943
* `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).
@@ -58,6 +62,7 @@
5862
* `unnecessary_lambda_linter()`
5963
+ ignores extractions with explicit returns like `lapply(l, function(x) foo(x)$bar)` (#2258, @MichaelChirico).
6064
+ ignores calls on the RHS of operators like `lapply(l, function(x) "a" %in% names(x))` (#2310, @MichaelChirico).
65+
* `vector_logic_linter()` recognizes some cases where bitwise `&`/`|` are used correctly (#1453, @MichaelChirico).
6166

6267
# lintr 3.1.1
6368

R/addins.R

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
# nocov start
22
addin_lint <- function() {
33
if (!requireNamespace("rstudioapi", quietly = TRUE)) {
4-
stop("'rstudioapi' is required for add-ins.")
4+
stop("'rstudioapi' is required for add-ins.", call. = FALSE)
55
}
66
filename <- rstudioapi::getSourceEditorContext()
77
if (filename$path == "") {
@@ -27,7 +27,7 @@ addin_lint <- function() {
2727

2828
addin_lint_package <- function() {
2929
if (!requireNamespace("rstudioapi", quietly = TRUE)) {
30-
stop("'rstudioapi' is required for add-ins.")
30+
stop("'rstudioapi' is required for add-ins.", call. = FALSE)
3131
}
3232
project <- rstudioapi::getActiveProject()
3333
project_path <- if (is.null(project)) getwd() else project

R/backport_linter.R

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ normalize_r_version <- function(r_version) {
9494
version_names <- c("devel", "release", paste0("oldrel-", seq_len(length(minor_versions) - 2L)))
9595
if (!r_version %in% version_names) {
9696
# This can only trip if e.g. oldrel-99 is requested
97-
stop("`r_version` must be a version number or one of ", toString(sQuote(version_names)))
97+
stop("`r_version` must be a version number or one of ", toString(sQuote(version_names)), call. = FALSE)
9898
}
9999
requested_version <- minor_versions[match(r_version, table = version_names)]
100100
available_patches <- all_versions[startsWith(all_versions, requested_version)]
@@ -106,10 +106,13 @@ normalize_r_version <- function(r_version) {
106106
} else if (is.character(r_version)) {
107107
r_version <- R_system_version(r_version, strict = TRUE)
108108
} else if (!inherits(r_version, "R_system_version")) {
109-
stop("`r_version` must be a R version number, returned by R_system_version(), or a string.")
109+
stop("`r_version` must be a R version number, returned by R_system_version(), or a string.", call. = FALSE)
110110
}
111111
if (r_version < "3.0.0") {
112-
warning("It is not recommended to depend on an R version older than 3.0.0. Resetting 'r_version' to 3.0.0.")
112+
warning(
113+
"It is not recommended to depend on an R version older than 3.0.0. Resetting 'r_version' to 3.0.0.",
114+
call. = FALSE
115+
)
113116
r_version <- R_system_version("3.0.0")
114117
}
115118
r_version

R/cache.R

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,8 @@ load_cache <- function(file, path = NULL) {
5555
error = function(e) {
5656
warning(
5757
"Could not load cache file '", file, "':\n",
58-
conditionMessage(e)
58+
conditionMessage(e),
59+
call. = FALSE
5960
)
6061
}
6162
)

R/comments.R

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -84,10 +84,10 @@ wercker_build_info <- function() {
8484
# nocov start
8585
github_comment <- function(text, info = NULL, token = settings$comment_token) {
8686
if (!requireNamespace("httr", quietly = TRUE)) {
87-
stop("Package 'httr' is required to post comments with github_comment().")
87+
stop("Package 'httr' is required to post comments with github_comment().", call. = FALSE)
8888
}
8989
if (!requireNamespace("jsonlite", quietly = TRUE)) {
90-
stop("Package 'jsonlite' is required to post comments with github_comment().")
90+
stop("Package 'jsonlite' is required to post comments with github_comment().", call. = FALSE)
9191
}
9292

9393
if (is.null(info)) {
@@ -99,7 +99,7 @@ github_comment <- function(text, info = NULL, token = settings$comment_token) {
9999
} else if (!is.null(info$commit)) {
100100
api_subdir <- file.path("commits", info$commit)
101101
} else {
102-
stop("Expected a pull or a commit, but received ci_build_info() = ", format(info))
102+
stop("Expected a pull or a commit, but received ci_build_info() = ", format(info), call. = FALSE)
103103
}
104104
response <- httr::POST(
105105
"https://api.github.com",

R/condition_call_linter.R

Lines changed: 116 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,116 @@
1+
#' Recommend usage of `call. = FALSE` in conditions
2+
#'
3+
#' This linter, with the default `display_call = FALSE`, enforces the
4+
#' recommendation of the tidyverse design guide regarding displaying error
5+
#' calls.
6+
#'
7+
#' @param display_call Logical specifying expected behaviour regarding `call.`
8+
#' argument in conditions.
9+
#' - `NA` forces providing `call.=` but ignores its value (this can be used in
10+
#' cases where you expect a mix of `call. = FALSE` and `call. = TRUE`)
11+
#' - lints `call. = FALSE`
12+
#' - forces `call. = FALSE` (lints `call. = TRUE` or missing `call.=` value)
13+
#'
14+
#'
15+
#' @examples
16+
#' # will produce lints
17+
#' lint(
18+
#' text = "stop('test')",
19+
#' linters = condition_call_linter()
20+
#' )
21+
#'
22+
#' lint(
23+
#' text = "stop('test', call. = TRUE)",
24+
#' linters = condition_call_linter()
25+
#' )
26+
#'
27+
#' lint(
28+
#' text = "stop('test', call. = FALSE)",
29+
#' linters = condition_call_linter(display_call = TRUE)
30+
#' )
31+
#'
32+
#' lint(
33+
#' text = "stop('this is a', 'test', call. = FALSE)",
34+
#' linters = condition_call_linter(display_call = TRUE)
35+
#' )
36+
#'
37+
#' # okay
38+
#' lint(
39+
#' text = "stop('test', call. = FALSE)",
40+
#' linters = condition_call_linter()
41+
#' )
42+
#'
43+
#' lint(
44+
#' text = "stop('this is a', 'test', call. = FALSE)",
45+
#' linters = condition_call_linter()
46+
#' )
47+
#'
48+
#' lint(
49+
#' text = "stop('test', call. = TRUE)",
50+
#' linters = condition_call_linter(display_call = TRUE)
51+
#' )
52+
#'
53+
#' @evalRd rd_tags("condition_call_linter")
54+
#' @seealso
55+
#' - [linters] for a complete list of linters available in lintr.
56+
#' - <https://design.tidyverse.org/err-call.html>>
57+
#' @export
58+
condition_call_linter <- function(display_call = FALSE) {
59+
call_xpath <- glue::glue("
60+
following-sibling::SYMBOL_SUB[text() = 'call.']
61+
/following-sibling::expr[1]
62+
/NUM_CONST[text() = '{!display_call}']
63+
")
64+
no_call_xpath <- "
65+
parent::expr[
66+
count(SYMBOL_SUB[text() = 'call.']) = 0
67+
]
68+
"
69+
70+
if (is.na(display_call)) {
71+
frag <- no_call_xpath
72+
} else if (display_call) {
73+
frag <- call_xpath
74+
} else {
75+
# call. = TRUE can be expressed in two way:
76+
# - either explicitly with call. = TRUE
77+
# - or by implicitly relying on the default
78+
frag <- xp_or(call_xpath, no_call_xpath)
79+
}
80+
81+
xpath <- glue::glue("
82+
//SYMBOL_FUNCTION_CALL[text() = 'stop' or text() = 'warning']
83+
/parent::expr[{frag}]
84+
/parent::expr
85+
")
86+
87+
Linter(linter_level = "expression", function(source_expression) {
88+
89+
xml <- source_expression$xml_parsed_content
90+
if (is.null(xml)) return(list())
91+
92+
bad_expr <- xml_find_all(xml, xpath)
93+
94+
if (is.na(display_call)) {
95+
msg <- glue::glue(
96+
"Provide an explicit value for call. in {xp_call_name(bad_expr)}()."
97+
)
98+
} else if (display_call) {
99+
msg <- glue::glue(
100+
"Use {xp_call_name(bad_expr)}(.) to display call in error message."
101+
)
102+
} else {
103+
msg <- glue::glue(
104+
"Use {xp_call_name(bad_expr)}(., call. = FALSE)",
105+
" to not display call in error message."
106+
)
107+
}
108+
109+
xml_nodes_to_lints(
110+
bad_expr,
111+
source_expression = source_expression,
112+
lint_message = msg,
113+
type = "warning"
114+
)
115+
})
116+
}

R/exclude.R

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -129,7 +129,7 @@ parse_exclusions <- function(file,
129129
if (length(starts) != length(ends)) {
130130
starts_msg <- line_info(starts, type = "start")
131131
ends_msg <- line_info(ends, type = "end")
132-
stop(file, " has ", starts_msg, " but only ", ends_msg, " for exclusion from linting!")
132+
stop(file, " has ", starts_msg, " but only ", ends_msg, " for exclusion from linting!", call. = FALSE)
133133
}
134134

135135
for (i in seq_along(starts)) {
@@ -204,7 +204,8 @@ add_exclusions <- function(exclusions, lines, linters_string, exclude_linter_sep
204204
warning(
205205
"Could not find linter", if (length(bad) > 1L) "s" else "", " named ",
206206
glue_collapse(sQuote(bad), sep = ", ", last = " and "),
207-
" in the list of active linters. Make sure the linter is uniquely identified by the given name or prefix."
207+
" in the list of active linters. Make sure the linter is uniquely identified by the given name or prefix.",
208+
call. = FALSE
208209
)
209210
}
210211
excluded_linters[matched] <- linter_names[idxs[matched]]

R/expect_lint.R

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,8 @@
4242
expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
4343
if (!requireNamespace("testthat", quietly = TRUE)) {
4444
stop( # nocov start
45-
"'expect_lint' is designed to work within the 'testthat' testing framework, but 'testthat' is not installed."
45+
"'expect_lint' is designed to work within the 'testthat' testing framework, but 'testthat' is not installed.",
46+
call. = FALSE
4647
) # nocov end
4748
}
4849
old_lang <- set_lang(language)
@@ -90,7 +91,7 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
9091
stop(sprintf(
9192
"check #%d had an invalid field: \"%s\"\nValid fields are: %s\n",
9293
itr, field, toString(lint_fields)
93-
))
94+
), call. = FALSE)
9495
}
9596
check <- check[[field]]
9697
value <- lint[[field]]

R/extract.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ get_knitr_pattern <- function(filename, lines) {
5151
("knitr" %:::% "detect_pattern")(lines, tolower(("knitr" %:::% "file_ext")(filename))),
5252
warning = function(cond) {
5353
if (!grepl("invalid UTF-8", conditionMessage(cond), fixed = TRUE)) {
54-
warning(cond)
54+
warning(cond, call. = FALSE)
5555
}
5656
invokeRestart("muffleWarning")
5757
}

R/lint.R

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -233,12 +233,15 @@ lint_package <- function(path = ".", ...,
233233
parse_settings = TRUE,
234234
show_progress = NULL) {
235235
if (length(path) > 1L) {
236-
stop("Only linting one package at a time is supported.")
236+
stop("Only linting one package at a time is supported.", call. = FALSE)
237237
}
238238
pkg_path <- find_package(path)
239239

240240
if (is.null(pkg_path)) {
241-
warning(sprintf("Didn't find any R package searching upwards from '%s'.", normalizePath(path)))
241+
warning(
242+
sprintf("Didn't find any R package searching upwards from '%s'.", normalizePath(path)),
243+
call. = FALSE
244+
)
242245
return(NULL)
243246
}
244247

@@ -331,7 +334,7 @@ validate_linter_object <- function(linter, name) {
331334
stop(gettextf(
332335
"Expected '%s' to be a function of class 'linter', not a %s of class '%s'",
333336
name, typeof(linter), class(linter)[[1L]]
334-
))
337+
), call. = FALSE)
335338
}
336339
if (is_linter_factory(linter)) {
337340
what <- "Passing linters as variables"
@@ -394,17 +397,17 @@ Lint <- function(filename, line_number = 1L, column_number = 1L, # nolint: objec
394397
}
395398

396399
if (length(line) != 1L || !is.character(line)) {
397-
stop("`line` must be a string.")
400+
stop("`line` must be a string.", call. = FALSE)
398401
}
399402
max_col <- max(nchar(line) + 1L, 1L, na.rm = TRUE)
400403
if (!is_number(column_number) || column_number < 0L || column_number > max_col) {
401404
stop(sprintf(
402405
"`column_number` must be an integer between 0 and nchar(line) + 1 (%d). It was %s.",
403406
max_col, column_number
404-
))
407+
), call. = FALSE)
405408
}
406409
if (!is_number(line_number) || line_number < 1L) {
407-
stop(sprintf("`line_number` must be a positive integer. It was %s.", line_number))
410+
stop(sprintf("`line_number` must be a positive integer. It was %s.", line_number), call. = FALSE)
408411
}
409412
check_ranges(ranges, max_col)
410413

@@ -439,23 +442,23 @@ check_ranges <- function(ranges, max_col) {
439442
return()
440443
}
441444
if (!is.list(ranges)) {
442-
stop("`ranges` must be NULL or a list.")
445+
stop("`ranges` must be NULL or a list.", call. = FALSE)
443446
}
444447

445448
for (range in ranges) {
446449
if (!is_number(range, 2L)) {
447-
stop("`ranges` must only contain length 2 integer vectors without NAs.")
450+
stop("`ranges` must only contain length 2 integer vectors without NAs.", call. = FALSE)
448451
} else if (!is_valid_range(range, max_col)) {
449452
stop(sprintf(
450453
"All entries in `ranges` must satisfy 0 <= range[1L] <= range[2L] <= nchar(line) + 1 (%d).", max_col
451-
))
454+
), call. = FALSE)
452455
}
453456
}
454457
}
455458

456459
rstudio_source_markers <- function(lints) {
457460
if (!requireNamespace("rstudioapi", quietly = TRUE)) {
458-
stop("'rstudioapi' is required for rstudio_source_markers().") # nocov
461+
stop("'rstudioapi' is required for rstudio_source_markers().", call. = FALSE) # nocov
459462
}
460463

461464
# package path will be NULL unless it is a relative path
@@ -548,7 +551,7 @@ checkstyle_output <- function(lints, filename = "lintr_results.xml") {
548551
#' @export
549552
sarif_output <- function(lints, filename = "lintr_results.sarif") {
550553
if (!requireNamespace("jsonlite", quietly = TRUE)) {
551-
stop("'jsonlite' is required to produce SARIF reports, please install to continue.") # nocov
554+
stop("'jsonlite' is required to produce SARIF reports, please install to continue.", call. = FALSE) # nocov
552555
}
553556

554557
# package path will be `NULL` unless it is a relative path

R/linter_tag_docs.R

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -119,3 +119,13 @@ NULL
119119
#' @evalRd rd_linters("regex")
120120
#' @seealso [linters] for a complete list of linters available in lintr.
121121
NULL
122+
123+
#' Tidyverse design linters
124+
#' @name tidy_design_linters
125+
#' @description
126+
#' Linters based on guidelines described in the 'Tidy design principles' book.
127+
#' @evalRd rd_linters("tidy_design")
128+
#' @seealso
129+
#' - [linters] for a complete list of linters available in lintr.
130+
#' - <https://design.tidyverse.org/>
131+
NULL

0 commit comments

Comments
 (0)