diff --git a/NEWS.md b/NEWS.md index c0d7a37ba..aa9e377a1 100644 --- a/NEWS.md +++ b/NEWS.md @@ -31,6 +31,7 @@ * Lints are now marked with the name of the `linter` that caused them instead of the name of their implementation function (#664, #673, @AshesITR). * Fixed `spaces_left_parentheses_linter` sporadically causing warnings (#654, #674, @AshesITR) +* Fixed `line_length_linter` causing duplicate lints for lines containing multiple expressions (#681, #682, @AshesITR) # lintr 2.0.1 diff --git a/R/line_length_linter.R b/R/line_length_linter.R index 174b490fc..752db356d 100644 --- a/R/line_length_linter.R +++ b/R/line_length_linter.R @@ -4,10 +4,16 @@ line_length_linter <- function(length) { function(source_file) { - lapply(names(source_file$lines)[vapply(source_file$lines, nchar, integer(1)) > length], + # Only go over complete file + if (is.null(source_file$file_lines)) return(list()) + + oversized_lines <- which(vapply(source_file$file_lines, nchar, integer(1)) > length) + + lapply(oversized_lines, function(line_number) { + col_start <- 1 - line <- source_file$lines[as.character(line_number)] + line <- source_file$file_lines[line_number] col_end <- unname(nchar(line)) Lint( diff --git a/tests/testthat/test-line_length_linter.R b/tests/testthat/test-line_length_linter.R index 04f1731d8..3fc6876df 100644 --- a/tests/testthat/test-line_length_linter.R +++ b/tests/testthat/test-line_length_linter.R @@ -1,4 +1,3 @@ -context("line_length_linter") test_that("returns the correct linting", { expect_lint("blah", @@ -30,4 +29,14 @@ test_that("returns the correct linting", { expect_lint("aaaaaaaaaaaaaaaaaaaab", rex("Lines should not be more than 20 characters"), line_length_linter(20)) + + # Don't duplicate lints + expect_length( + lint( + "x <- 2 # ------------\n", + linters = line_length_linter(20), + parse_settings = FALSE + ), + 1L + ) })