Skip to content

Commit 0910ccd

Browse files
committed
add more tests, refactor to file-level because of a systematic problem with expression level
1 parent 0ff0394 commit 0910ccd

File tree

2 files changed

+54
-10
lines changed

2 files changed

+54
-10
lines changed

R/indentation_linter.R

Lines changed: 16 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -82,8 +82,8 @@ indentation_linter <- function(indent = 2L, use_hybrid_indent = TRUE) {
8282
paste(
8383
c(
8484
glue::glue("self::{paren_tokens_left}/following-sibling::{paren_tokens_right}/preceding-sibling::*[1]/@line2"),
85-
glue::glue("self::*[{xp_and(paste0('not(self::', paren_tokens_left, ')'))}]/following-sibling::SYMBOL_FUNCTION_CALL/
86-
parent::expr/following-sibling::expr[1]/@line2"),
85+
glue::glue("self::*[{xp_and(paste0('not(self::', paren_tokens_left, ')'))}]
86+
/following-sibling::SYMBOL_FUNCTION_CALL/parent::expr/following-sibling::expr[1]/@line2"),
8787
glue::glue("self::*[
8888
{xp_and(paste0('not(self::', paren_tokens_left, ')'))} and
8989
not(following-sibling::SYMBOL_FUNCTION_CALL)
@@ -113,19 +113,25 @@ indentation_linter <- function(indent = 2L, use_hybrid_indent = TRUE) {
113113
xp_multiline_string <- "//STR_CONST[@line1 < @line2]"
114114

115115
Linter(function(source_expression) {
116-
if (!is_lint_level(source_expression, "expression")) {
116+
# must run on file level because a line can contain multiple expressions, losing indentation information, e.g.
117+
#
118+
#> fun(
119+
# a) # comment
120+
#
121+
# will have "# comment" as a separate expression
122+
if (!is_lint_level(source_expression, "file")) {
117123
return(list())
118124
}
119125

120-
xml <- source_expression$xml_parsed_content
126+
xml <- source_expression$full_xml_parsed_content
121127
# Indentation increases by 1 for:
122128
# - { } blocks that span multiple lines
123129
# - ( ), [ ], or [[ ]] calls that span multiple lines
124130
# + if a token follows (, a hanging indent is required until )
125131
# + if there is no token following ( on the same line, a block indent is required until )
126132
# - binary operators where the second arguments starts on a new line
127133

128-
indent_levels <- rex::re_matches(source_expression$lines, rex::rex(start, any_spaces), locations = TRUE)[, "end"]
134+
indent_levels <- rex::re_matches(source_expression$file_lines, rex::rex(start, any_spaces), locations = TRUE)[, "end"]
129135
expected_indent_levels <- integer(length(indent_levels))
130136
is_hanging <- logical(length(indent_levels))
131137

@@ -135,7 +141,7 @@ indentation_linter <- function(indent = 2L, use_hybrid_indent = TRUE) {
135141
change_begin <- as.integer(xml2::xml_attr(change, "line1")) + 1L
136142
change_end <- xml2::xml_find_num(change, xp_block_ends)
137143
if (change_begin <= change_end) {
138-
to_indent <- seq(from = change_begin, to = change_end) - source_expression$line + 1L
144+
to_indent <- seq(from = change_begin, to = change_end)
139145
if (change_starts_hanging) {
140146
expected_indent_levels[to_indent] <- as.integer(xml2::xml_attr(change, "col2"))
141147
is_hanging[to_indent] <- TRUE
@@ -152,12 +158,12 @@ indentation_linter <- function(indent = 2L, use_hybrid_indent = TRUE) {
152158
is_in_str <- seq(
153159
from = as.integer(xml2::xml_attr(string, "line1")) + 1L,
154160
to = as.integer(xml2::xml_attr(string, "line2"))
155-
) - source_expression$line + 1L
161+
)
156162
in_str_const[is_in_str] <- TRUE
157163
}
158164

159165
# Only lint non-empty lines if the indentation level doesn't match.
160-
bad_lines <- which(indent_levels != expected_indent_levels & nzchar(source_expression$lines) & !in_str_const)
166+
bad_lines <- which(indent_levels != expected_indent_levels & nzchar(trimws(source_expression$file_lines)) & !in_str_const)
161167
if (length(bad_lines)) {
162168
# Suppress consecutive lints with the same indentation difference, to not generate an excessive number of lints
163169
is_consecutive_lint <- c(FALSE, diff(bad_lines) == 1L)
@@ -172,7 +178,7 @@ indentation_linter <- function(indent = 2L, use_hybrid_indent = TRUE) {
172178
expected_indent_levels[bad_lines],
173179
indent_levels[bad_lines]
174180
)
175-
lint_lines <- unname(as.integer(names(source_expression$lines)[bad_lines]))
181+
lint_lines <- unname(as.integer(names(source_expression$file_lines)[bad_lines]))
176182
lint_ranges <- cbind(
177183
pmin(expected_indent_levels[bad_lines] + 1L, indent_levels[bad_lines]),
178184
pmax(expected_indent_levels[bad_lines], indent_levels[bad_lines])
@@ -184,7 +190,7 @@ indentation_linter <- function(indent = 2L, use_hybrid_indent = TRUE) {
184190
column_number = indent_levels[bad_lines],
185191
type = "style",
186192
message = lint_messages,
187-
line = unname(source_expression$lines[bad_lines]),
193+
line = unname(source_expression$file_lines[bad_lines]),
188194
ranges = apply(lint_ranges, 1L, list, simplify = FALSE)
189195
)
190196
} else {

tests/testthat/test-indentation_linter.R

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,21 @@ test_that("indentation linter flags unindented expressions", {
3232
linter
3333
)
3434

35+
# no double-block indents even if the indentation-starting tokens are immediately next to each other
36+
expect_lint(
37+
trim_some("
38+
local({
39+
# no lint
40+
})
41+
42+
local({
43+
# must lint
44+
})
45+
"),
46+
list(line_number = 6L, message = "Indentation"),
47+
linter
48+
)
49+
3550
expect_lint(
3651
trim_some("
3752
lapply(1:10, function(i) {
@@ -305,6 +320,29 @@ test_that("indentation works with control flow statements", {
305320
)
306321
})
307322

323+
test_that("indentation lint messages are dynamic", {
324+
linter <- indentation_linter()
325+
326+
expect_lint(
327+
trim_some("
328+
local({
329+
# should be 2
330+
})
331+
"),
332+
rex::rex("Indentation should be 2 spaces but is 4 spaces."),
333+
linter
334+
)
335+
336+
expect_lint(
337+
trim_some("
338+
fun(
339+
3) # should be 4
340+
"),
341+
rex::rex("Hanging indent should be 4 spaces but is 2 spaces."),
342+
linter
343+
)
344+
})
345+
308346
test_that("indentation within string constants is ignored", {
309347
expect_lint(
310348
trim_some("

0 commit comments

Comments
 (0)