Skip to content

Commit fceac40

Browse files
Use partial matching for linter names in exclusion directives (#1138)
* use partial matching for linter names in exclusion directives * document() * document() * add missing roxy * implicit integers: exclude.R * implicit integer: lint.R * implicit integer: function_left_parentheses.R * feedback Co-authored-by: Michael Chirico <chiricom@google.com>
1 parent f962bd0 commit fceac40

12 files changed

+106
-28
lines changed

NEWS.md

+1
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@
6868
* New syntax to exclude only selected linters from linting lines or passages. Use `# nolint: linter_name, linter2_name.`
6969
or `# nolint start: linter_name, linter2_name.` in source files or named lists of line numbers in `.lintr`.
7070
(#660, @AshesITR)
71+
+ Extended to allow for partial matching as long as the supplied prefix is unique (#872, @AshesITR)
7172
* Fixed `spaces_left_parentheses_linter` sporadically causing warnings (#654, #674, @AshesITR)
7273
* Fixed `line_length_linter` causing duplicate lints for lines containing multiple expressions (#681, #682, @AshesITR)
7374
* `line_length_linter` now places the source marker at the margin of the affected line to improve user experience during

R/T_and_F_symbol_linter.R

+1-1
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@
77
#' [linters] for a complete list of linters available in lintr. \cr
88
#' <https://style.tidyverse.org/syntax.html#logical-vectors>
99
#' @export
10-
T_and_F_symbol_linter <- function() { # nolint: object_name_linter.
10+
T_and_F_symbol_linter <- function() { # nolint: object_name.
1111
Linter(function(source_expression) {
1212
if (is.null(source_expression$xml_parsed_content)) return(list())
1313

R/exclude.R

+27-11
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
#'
33
#' @param lints that need to be filtered.
44
#' @param exclusions manually specified exclusions
5+
#' @param linter_names character vector of names of the active linters, used for parsing inline exclusions.
56
#' @param ... additional arguments passed to [parse_exclusions()]
67
#' @details
78
#' Exclusions can be specified in three different ways.
@@ -15,15 +16,15 @@
1516
#' 3. exclusions parameter, a named list of files with named lists of linters and lines to exclude them on, a named
1617
#' list of the files and lines to exclude, or just the filenames if you want to exclude the entire file, or the
1718
#' directory names if you want to exclude all files in a directory.
18-
exclude <- function(lints, exclusions = settings$exclusions, ...) {
19-
if (length(lints) <= 0) {
19+
exclude <- function(lints, exclusions = settings$exclusions, linter_names = NULL, ...) {
20+
if (length(lints) <= 0L) {
2021
return(lints)
2122
}
2223

2324
df <- as.data.frame(lints)
2425

2526
filenames <- unique(df$filename)
26-
source_exclusions <- lapply(filenames, parse_exclusions, ...)
27+
source_exclusions <- lapply(filenames, parse_exclusions, linter_names = linter_names, ...)
2728
names(source_exclusions) <- filenames
2829

2930

@@ -58,9 +59,9 @@ line_info <- function(line_numbers, type = c("start", "end")) {
5859
type <- match.arg(type)
5960
range_word <- paste0("range ", type, if (length(line_numbers) != 1L) "s")
6061
n <- length(line_numbers)
61-
if (n == 0) {
62+
if (n == 0L) {
6263
paste("0", range_word)
63-
} else if (n == 1) {
64+
} else if (n == 1L) {
6465
paste0("1 ", range_word, " (line ", line_numbers, ")")
6566
} else {
6667
paste0(n, " ", range_word, " (lines ", toString(line_numbers), ")")
@@ -77,14 +78,16 @@ line_info <- function(line_numbers, type = c("start", "end")) {
7778
#' `exclude` or `exclude_start` marker.
7879
#' @param exclude_linter_sep regular expression used to split a linter list into indivdual linter names for exclusion.
7980
#' @param lines a character vector of the content lines of `file`
81+
#' @param linter_names Names of active linters
8082
#'
8183
#' @return A possibly named list of excluded lines, possibly for specific linters.
8284
parse_exclusions <- function(file, exclude = settings$exclude,
8385
exclude_start = settings$exclude_start,
8486
exclude_end = settings$exclude_end,
8587
exclude_linter = settings$exclude_linter,
8688
exclude_linter_sep = settings$exclude_linter_sep,
87-
lines = NULL) {
89+
lines = NULL,
90+
linter_names = NULL) {
8891
if (is.null(lines)) {
8992
lines <- read_lines(file)
9093
}
@@ -102,7 +105,7 @@ parse_exclusions <- function(file, exclude = settings$exclude,
102105
starts <- which(!is.na(start_locations))
103106
ends <- which(!is.na(end_locations))
104107

105-
if (length(starts) > 0) {
108+
if (length(starts) > 0L) {
106109
if (length(starts) != length(ends)) {
107110
starts_msg <- line_info(starts, type = "start")
108111
ends_msg <- line_info(ends, type = "end")
@@ -114,7 +117,7 @@ parse_exclusions <- function(file, exclude = settings$exclude,
114117
linters_string <- substring(lines[starts[i]], start_locations[starts[i]])
115118
linters_string <- rex::re_matches(linters_string, exclude_linter)[, 1L]
116119

117-
exclusions <- add_exclusions(exclusions, excluded_lines, linters_string, exclude_linter_sep)
120+
exclusions <- add_exclusions(exclusions, excluded_lines, linters_string, exclude_linter_sep, linter_names)
118121
}
119122
}
120123

@@ -126,7 +129,7 @@ parse_exclusions <- function(file, exclude = settings$exclude,
126129
for (i in seq_along(nolints)) {
127130
linters_string <- substring(lines[nolints[i]], nolint_locations[nolints[i]])
128131
linters_string <- rex::re_matches(linters_string, exclude_linter)[, 1L]
129-
exclusions <- add_exclusions(exclusions, nolints[i], linters_string, exclude_linter_sep)
132+
exclusions <- add_exclusions(exclusions, nolints[i], linters_string, exclude_linter_sep, linter_names)
130133
}
131134

132135
exclusions[] <- lapply(exclusions, function(lines) sort(unique(lines)))
@@ -154,13 +157,26 @@ add_excluded_lines <- function(exclusions, excluded_lines, excluded_linters) {
154157
exclusions
155158
}
156159

157-
add_exclusions <- function(exclusions, lines, linters_string, exclude_linter_sep) {
160+
add_exclusions <- function(exclusions, lines, linters_string, exclude_linter_sep, linter_names) {
158161
# No match for linter list: Add to global excludes
159162
if (is.na(linters_string)) {
160163
exclusions <- add_excluded_lines(exclusions, lines, "")
161164
} else {
162165
# Matched a linter list: only add excluded lines for the listed linters.
163166
excluded_linters <- strsplit(linters_string, exclude_linter_sep)[[1L]]
167+
if (!is.null(linter_names)) {
168+
idxs <- pmatch(excluded_linters, linter_names, duplicates.ok = TRUE)
169+
matched <- !is.na(idxs)
170+
if (!all(matched)) {
171+
bad <- excluded_linters[!matched]
172+
warning(
173+
"Could not find linter", if (length(bad) > 1L) "s" else "", " named ",
174+
glue::glue_collapse(sQuote(bad), sep = ", ", last = " and "),
175+
" in the list of active linters. Make sure the linter is uniquely identified by the given name or prefix."
176+
)
177+
}
178+
excluded_linters[matched] <- linter_names[idxs[matched]]
179+
}
164180
exclusions <- add_excluded_lines(exclusions, lines, excluded_linters)
165181
}
166182
exclusions
@@ -192,7 +208,7 @@ add_exclusions <- function(exclusions, lines, linters_string, exclude_linter_sep
192208
normalize_exclusions <- function(x, normalize_path = TRUE,
193209
root = getwd(),
194210
pattern = NULL) {
195-
if (is.null(x) || length(x) <= 0) {
211+
if (is.null(x) || length(x) <= 0L) {
196212
return(list())
197213
}
198214

R/function_left_parentheses.R

+2-2
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@
77
#' [linters] for a complete list of linters available in lintr. \cr
88
#' <https://style.tidyverse.org/syntax.html#parentheses>
99
#' @export
10-
function_left_parentheses_linter <- function() { # nolint: object_length_linter.
10+
function_left_parentheses_linter <- function() { # nolint: object_length.
1111
Linter(function(source_expression) {
1212
lapply(
1313
ids_with_token(source_expression, "'('"),
@@ -20,7 +20,7 @@ function_left_parentheses_linter <- function() { # nolint: object_length_linter.
2020
source_expression$parsed_content$col1 < parsed$col1 &
2121
source_expression$parsed_content$terminal
2222

23-
last_type <- tail(source_expression$parsed_content$token[terminal_tokens_before], n = 1)
23+
last_type <- tail(source_expression$parsed_content$token[terminal_tokens_before], n = 1L)
2424

2525
is_function_call <- length(last_type) %!=% 0L &&
2626
(last_type %in% c("SYMBOL_FUNCTION_CALL", "FUNCTION", "'}'", "']'"))

R/lint.R

+4-4
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,7 @@ lint <- function(filename, linters = NULL, ..., cache = FALSE, parse_settings =
104104
if (!is.null(lints)) {
105105
# TODO: once cache= is fully deprecated as 3rd positional argument (see top of body), we can restore the cleaner:
106106
# > exclude(lints, lines = lines, ...)
107-
return(do.call(exclude, c(list(lints, lines = lines), dots)))
107+
return(do.call(exclude, c(list(lints, lines = lines, linter_names = names(linters)), dots)))
108108
}
109109
cache <- TRUE
110110
} else {
@@ -152,7 +152,7 @@ lint <- function(filename, linters = NULL, ..., cache = FALSE, parse_settings =
152152

153153
# TODO: once cache= is fully deprecated as 3rd positional argument (see top of body), we can restore the cleaner:
154154
# > exclude(lints, lines = lines, ...)
155-
res <- do.call(exclude, c(list(lints, lines = lines), dots))
155+
res <- do.call(exclude, c(list(lints, lines = lines, linter_names = names(linters)), dots))
156156

157157
# simplify filename if inline
158158
if (no_filename) {
@@ -461,7 +461,7 @@ pkg_name <- function(path = find_package()) {
461461
if (is.null(path)) {
462462
return(NULL)
463463
} else {
464-
read.dcf(file.path(path, "DESCRIPTION"), fields = "Package")[1]
464+
read.dcf(file.path(path, "DESCRIPTION"), fields = "Package")[1L]
465465
}
466466
}
467467

@@ -476,7 +476,7 @@ pkg_name <- function(path = find_package()) {
476476
#' @param linter deprecated. No longer used.
477477
#' @return an object of class 'lint'.
478478
#' @export
479-
Lint <- function(filename, line_number = 1L, column_number = 1L, # nolint: object_name_linter.
479+
Lint <- function(filename, line_number = 1L, column_number = 1L, # nolint: object_name.
480480
type = c("style", "warning", "error"),
481481
message = "", line = "", ranges = NULL, linter = "") {
482482
if (!missing(linter)) {

R/methods.R

+1-1
Original file line numberDiff line numberDiff line change
@@ -137,7 +137,7 @@ split.lints <- function(x, f = NULL, ...) {
137137
}
138138

139139
#' @export
140-
as.data.frame.lints <- function(x, row.names = NULL, optional = FALSE, ...) { # nolint: object_name_linter. (row.names)
140+
as.data.frame.lints <- function(x, row.names = NULL, optional = FALSE, ...) { # nolint: object_name. (row.names)
141141
data.frame(filename = vapply(x, `[[`, character(1), "filename"),
142142
line_number = vapply(x, `[[`, numeric(1), "line_number"),
143143
column_number = vapply(x, `[[`, numeric(1), "column_number"),

R/utils.R

+1-1
Original file line numberDiff line numberDiff line change
@@ -177,7 +177,7 @@ reset_lang <- function(old_lang) {
177177
#' Lints produced by the linter will be labelled with `name` by default.
178178
#' @return The same function with its class set to 'linter'.
179179
#' @export
180-
Linter <- function(fun, name = linter_auto_name()) { # nolint: object_name_linter.
180+
Linter <- function(fun, name = linter_auto_name()) { # nolint: object_name.
181181
if (!is.function(fun) || length(formals(args(fun))) != 1L) {
182182
stop("`fun` must be a function taking exactly one argument.", call. = FALSE)
183183
}

man/exclude.Rd

+3-1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/parse_exclusions.Rd

+4-1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
# nolint start: assign.
2+
a = 2
3+
# nolint end
4+
5+
# nolint start: s. warn (and lint) because of non-unique identifier
6+
x <- 42; y <- 2
7+
# nolint end
8+
9+
# nolint start: bogus_linter. warn because of nonexistent identifier
10+
11+
# nolint end
12+
13+
# nolint: hocus_pocus, bogus.

tests/testthat/test-exclusions.R

+30-6
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,13 @@ test_that("line_info works as expected", {
1313
)
1414
})
1515

16-
old_ops <- options(lintr.exclude = "#TeSt_NoLiNt",
17-
lintr.exclude_start = "#TeSt_NoLiNt_StArT",
18-
lintr.exclude_end = "#TeSt_NoLiNt_EnD")
19-
2016
test_that("it excludes properly", {
17+
withr::local_options(
18+
lintr.exclude = "#TeSt_NoLiNt",
19+
lintr.exclude_start = "#TeSt_NoLiNt_StArT",
20+
lintr.exclude_end = "#TeSt_NoLiNt_EnD"
21+
)
22+
2123
read_settings(NULL)
2224

2325
t1 <- lint("exclusions-test", parse_settings = FALSE)
@@ -42,13 +44,16 @@ test_that("it excludes properly", {
4244
})
4345

4446
test_that("it doesn't fail when encountering misspecified encodings", {
47+
withr::local_options(
48+
lintr.exclude = "#TeSt_NoLiNt",
49+
lintr.exclude_start = "#TeSt_NoLiNt_StArT",
50+
lintr.exclude_end = "#TeSt_NoLiNt_EnD"
51+
)
4552
read_settings(NULL)
4653

4754
expect_length(parse_exclusions("dummy_projects/project/cp1252.R"), 0L)
4855
})
4956

50-
options(old_ops)
51-
5257
test_that("it gives the expected error message when there is only one start but no end", {
5358
read_settings(NULL)
5459

@@ -68,3 +73,22 @@ test_that("it gives the expected error message when there is mismatch between mu
6873
fixed = TRUE
6974
)
7075
})
76+
77+
test_that("partial matching works for exclusions but warns if no linter found", {
78+
read_settings(NULL)
79+
80+
expect_warning(
81+
expect_warning(
82+
expect_warning(
83+
expect_lint(
84+
file = "dummy_projects/project/partially_matched_exclusions.R",
85+
checks = rex::rex("semicolons"),
86+
parse_settings = FALSE
87+
),
88+
rex::rex("Could not find linter named ", anything, "s")
89+
),
90+
rex::rex("Could not find linter named ", anything, "bogus_linter")
91+
),
92+
rex::rex("Could not find linters named ", anything, "hocus_pocus", anything, "bogus")
93+
)
94+
})

vignettes/using_lintr.Rmd

+19
Original file line numberDiff line numberDiff line change
@@ -265,6 +265,25 @@ lintr::lint(
265265
)
266266
```
267267

268+
You can also specify the linter names by a unique prefix instead of their full name:
269+
270+
**file5.R**
271+
```r
272+
X = 42L # nolint: object_name, line_len. this comment still overflows the default 80 chars line length.
273+
```
274+
275+
`> lint("file5.R")`
276+
```{r, echo = FALSE}
277+
lintr::lint(
278+
paste(
279+
"X = 42L",
280+
"# nolint: object_name, line_len. this comment still overflows the default 80 chars line length.\n"
281+
),
282+
parse_settings = FALSE
283+
)
284+
```
285+
286+
268287
### Excluding multiple lines of codes
269288

270289
If any or all linters should be disabled for a contiguous block of code, the `exclude_start` and `exclude_end` patterns

0 commit comments

Comments
 (0)