Skip to content

Commit eece3c1

Browse files
MichaelChiricojimhester
authored andcommitted
treat tabs as spaces in print.lint
1 parent b937655 commit eece3c1

File tree

2 files changed

+11
-1
lines changed

2 files changed

+11
-1
lines changed

R/methods.R

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ print.lint <- function(x, ...) {
1414
as.character(x$column_number), ": ", sep = ""),
1515
color(x$type, ": ", sep = ""),
1616
crayon::bold(x$message), "\n",
17-
x$line, "\n",
17+
# swap tabs for spaces for #528 (sorry Richard Hendricks)
18+
chartr("\t", " ", x$line), "\n",
1819
highlight_string(x$message, x$column_number, x$ranges),
1920
"\n"
2021
)

tests/testthat/test-methods.R

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -86,3 +86,12 @@ test_that("summary.lints() works (lints found)", {
8686
expect_equal(has_lint_summary$error, 0)
8787
})
8888

89+
test_that("print.lint works", {
90+
# don't treat \t as width-1, #528
91+
l <- Lint(
92+
filename = "tmp", line_number = 1L, column_number = 3L,
93+
type = "warning", message = "this is a lint",
94+
line = c(`1` = "\t\t1:length(x)"), ranges = list(c(3L, 3L)), linter = "lnt"
95+
)
96+
expect_output(print(l), " 1:length(x)", fixed = TRUE)
97+
})

0 commit comments

Comments
 (0)