Skip to content

Commit 86ef6b4

Browse files
include line length in lint message (#2066)
* include line length in lint message * slight refactor, test multiple lints * rm vestigial * adjust incidental test * NEWS grammar * trailing ws * explicit integer
1 parent 2813b6d commit 86ef6b4

File tree

4 files changed

+35
-16
lines changed

4 files changed

+35
-16
lines changed

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@
2323
+ `unreachable_code_linter()`
2424
+ `yoda_test_linter()`
2525
* `sprintf_linter()` is pipe-aware, so that `x %>% sprintf(fmt = "%s")` no longer lints (#1943, @MichaelChirico).
26+
* `line_length_linter()` helpfully includes the line length in the lint message (#2057, @MichaelChirico).
2627

2728
### New linters
2829

R/line_length_linter.R

Lines changed: 17 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,8 @@
2323
#' - <https://style.tidyverse.org/syntax.html#long-lines>
2424
#' @export
2525
line_length_linter <- function(length = 80L) {
26+
general_msg <- paste("Lines should not be more than", length, "characters.")
27+
2628
Linter(function(source_expression) {
2729
# Only go over complete file
2830
if (!is_lint_level(source_expression, "file")) {
@@ -32,18 +34,20 @@ line_length_linter <- function(length = 80L) {
3234
line_lengths <- nchar(source_expression$file_lines)
3335
long_lines <- which(line_lengths > length)
3436

35-
lint_message <- sprintf("Lines should not be more than %d characters.", length)
36-
37-
lapply(long_lines, function(long_line) {
38-
Lint(
39-
filename = source_expression$filename,
40-
line_number = long_line,
41-
column_number = length + 1L,
42-
type = "style",
43-
message = lint_message,
44-
line = source_expression$file_lines[long_line],
45-
ranges = list(c(1L, line_lengths[long_line]))
46-
)
47-
})
37+
mapply(
38+
function(long_line, line_length) {
39+
Lint(
40+
filename = source_expression$filename,
41+
line_number = long_line,
42+
column_number = length + 1L,
43+
type = "style",
44+
message = paste(general_msg, "This line is", line_length, "characters."),
45+
line = source_expression$file_lines[long_line],
46+
ranges = list(c(1L, line_length))
47+
)
48+
},
49+
long_lines, line_lengths[long_lines],
50+
SIMPLIFY = FALSE
51+
)
4852
})
4953
}

tests/testthat/test-line_length_linter.R

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ test_that("line_length_linter skips allowed usages", {
77

88
test_that("line_length_linter blocks disallowed usages", {
99
linter <- line_length_linter(80L)
10-
lint_msg <- rex::rex("Lines should not be more than 80 characters")
10+
lint_msg <- rex::rex("Lines should not be more than 80 characters. This line is 81 characters.")
1111

1212
expect_lint(
1313
strrep("x", 81L),
@@ -34,7 +34,7 @@ test_that("line_length_linter blocks disallowed usages", {
3434
)
3535

3636
linter <- line_length_linter(20L)
37-
lint_msg <- rex::rex("Lines should not be more than 20 characters")
37+
lint_msg <- rex::rex("Lines should not be more than 20 characters. This line is 22 characters.")
3838
expect_lint(strrep("a", 20L), NULL, linter)
3939
expect_lint(
4040
strrep("a", 22L),
@@ -55,3 +55,14 @@ test_that("line_length_linter blocks disallowed usages", {
5555
1L
5656
)
5757
})
58+
59+
test_that("Multiple lints give custom messages", {
60+
expect_lint(
61+
trim_some("{
62+
abcdefg
63+
hijklmnop
64+
}"),
65+
list("9 characters", "11 characters"),
66+
line_length_linter(5L)
67+
)
68+
})

tests/testthat/test-with.R

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,10 @@ test_that("all default linters are tagged default", {
5050
skip_if_not_r_version("4.1.0") # Desired all.equal behavior only available in >= 4.1
5151
expect_identical(
5252
all.equal(linters_with_tags("default"), linters_with_defaults(line_length_linter(120L))),
53-
'Component "line_length_linter": Component "length": Mean relative difference: 0.5'
53+
c(
54+
'Component "line_length_linter": Component "general_msg": 1 string mismatch',
55+
'Component "line_length_linter": Component "length": Mean relative difference: 0.5'
56+
)
5457
)
5558
})
5659

0 commit comments

Comments
 (0)