Skip to content

Commit

Permalink
Tests for trailing_blank_lines_linter() with chunks (#1614)
Browse files Browse the repository at this point in the history
* Tests for `trailing_blank_lines_linter()` with chunks

Closes #741

* Use `library(withr)`

* formatting

* restructure

* Don't set `content` to `NULL`

* make it DAMP

* restructure to bring message closer to expectations

* use namespace

* use loadNamespace() for test-required packages

* Update test-trailing_blank_lines_linter.R

* Apply cleanup to the rest of the file

* same clean up in another test file

* Use `trim_some()`

Co-authored-by: Michael Chirico <chiricom@google.com>
  • Loading branch information
IndrajeetPatil and MichaelChirico authored Oct 7, 2022
1 parent 8bec6df commit a6254c2
Show file tree
Hide file tree
Showing 4 changed files with 125 additions and 49 deletions.
2 changes: 2 additions & 0 deletions R/trailing_blank_lines_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ trailing_blank_lines_linter <- function() {
}
line_number <- line_number - 1L
}

if (identical(source_expression$terminal_newline, FALSE)) { # could use isFALSE, but needs backports
last_line <- tail(source_expression$file_lines, 1L)

Expand All @@ -39,6 +40,7 @@ trailing_blank_lines_linter <- function() {
line = last_line
)
}

lints
})
}
2 changes: 2 additions & 0 deletions tests/testthat.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,6 @@
library(testthat)
library(lintr)
loadNamespace("rex")
loadNamespace("withr")

test_check("lintr")
36 changes: 18 additions & 18 deletions tests/testthat/test-knitr_formats.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,77 +20,77 @@ test_that("it handles dir", {

test_that("it handles markdown", {
expect_lint(
file = "knitr_formats/test.Rmd",
file = test_path("knitr_formats", "test.Rmd"),
checks = list(
list(regexes[["assign"]], line_number = 9L),
list(regexes[["local_var"]], line_number = 22L),
list(regexes[["assign"]], line_number = 22L),
list(regexes[["trailing"]], line_number = 24L)
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})

test_that("it handles quarto", {
expect_lint(
file = "knitr_formats/test.qmd",
file = test_path("knitr_formats", "test.qmd"),
checks = list(
list(regexes[["assign"]], line_number = 9L),
list(regexes[["local_var"]], line_number = 22L),
list(regexes[["assign"]], line_number = 22L),
list(regexes[["trailing"]], line_number = 24L)
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})

test_that("it handles Sweave", {
expect_lint(
file = "knitr_formats/test.Rnw",
file = test_path("knitr_formats", "test.Rnw"),
checks = list(
list(regexes[["assign"]], line_number = 12L),
list(regexes[["local_var"]], line_number = 24L),
list(regexes[["assign"]], line_number = 24L),
list(regexes[["trailing"]], line_number = 26L)
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})

test_that("it handles reStructuredText", {
expect_lint(
file = "knitr_formats/test.Rrst",
file = test_path("knitr_formats", "test.Rrst"),
checks = list(
list(regexes[["assign"]], line_number = 10L),
list(regexes[["local_var"]], line_number = 23L),
list(regexes[["assign"]], line_number = 23L),
list(regexes[["trailing"]], line_number = 25L)
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})

test_that("it handles HTML", {
expect_lint(
file = "knitr_formats/test.Rhtml",
file = test_path("knitr_formats", "test.Rhtml"),
checks = list(
list(regexes[["assign"]], line_number = 15L),
list(regexes[["local_var"]], line_number = 27L),
list(regexes[["assign"]], line_number = 27L),
list(regexes[["trailing"]], line_number = 29L)
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})

test_that("it handles tex", {
expect_lint(
file = "knitr_formats/test.Rtex",
file = test_path("knitr_formats", "test.Rtex"),
checks = list(
list(regexes[["assign"]], line_number = 11L),
list(regexes[["local_var"]], line_number = 23L),
Expand All @@ -102,21 +102,21 @@ test_that("it handles tex", {
# "%" as well.
# cf. get_source_expressions("tests/testthat/knitr_formats/test.Rtex")$lines[[25]]
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})

test_that("it handles asciidoc", {
expect_lint(
file = "knitr_formats/test.Rtxt",
file = test_path("knitr_formats", "test.Rtxt"),
checks = list(
list(regexes[["assign"]], line_number = 9L),
list(regexes[["local_var"]], line_number = 22L),
list(regexes[["assign"]], line_number = 22L),
list(regexes[["trailing"]], line_number = 24L)
),
default_linters,
linters = default_linters,
parse_settings = FALSE
)
})
Expand All @@ -141,16 +141,16 @@ test_that("it does _not_ error with inline \\Sexpr", {

test_that("it does lint .Rmd or .qmd file with malformed input", {
expect_lint(
file = "knitr_malformed/incomplete_r_block.Rmd",
file = test_path("knitr_malformed", "incomplete_r_block.Rmd"),
checks = "Missing chunk end",
default_linters,
linters = default_linters,
parse_settings = FALSE
)

expect_lint(
file = "knitr_malformed/incomplete_r_block.qmd",
file = test_path("knitr_malformed", "incomplete_r_block.qmd"),
checks = "Missing chunk end",
default_linters,
linters = default_linters,
parse_settings = FALSE
)

Expand Down
134 changes: 103 additions & 31 deletions tests/testthat/test-trailing_blank_lines_linter.R
Original file line number Diff line number Diff line change
@@ -1,35 +1,43 @@
test_that("returns the correct linting", {
test_that("trailing_blank_lines_linter doesn't block allowed usages", {
linter <- trailing_blank_lines_linter()
msg <- rex::rex("Trailing blank lines are superfluous.")
msg2 <- rex::rex("Missing terminal newline.")

expect_lint("blah", NULL, linter)
expect_lint("blah <- 1 ", NULL, linter)
expect_lint("blah <- 1\nblah", NULL, linter)
expect_lint("blah <- 1\nblah\n \n blah", NULL, linter)

tmp <- withr::local_tempfile(lines = "lm(y ~ x)")
expect_lint(file = tmp, checks = NULL, linters = linter)
})

test_that("trailing_blank_lines_linter detects disallowed usages", {
linter <- trailing_blank_lines_linter()
msg <- rex::rex("Trailing blank lines are superfluous.")

expect_lint("blah <- 1\n", msg, linter)
expect_lint("blah <- 1\n ", msg, linter)

expect_lint("blah <- 1\n \n ", list(msg, msg), linter)
expect_lint("blah <- 1\n\n", list(msg, msg), linter)
expect_lint("blah <- 1\n\t\n", list(msg, msg), linter)

# Construct a test file without terminal newline
# cf. test-get_source_expressions.R
tmp <- withr::local_tempfile()
tmp2 <- withr::local_tempfile()
cat("lm(y ~ x)\n", file = tmp)
cat("lm(y ~ x)", file = tmp2)
expect_lint(
file = tmp2,
checks = list(
message = rex::rex("Missing terminal newline."),
line_number = 1L,
column_number = 10L
),
linters = linter
)
})

expect_lint(content = NULL, file = tmp, NULL, linter)
expect_lint(content = NULL, file = tmp2, list(
message = msg2,
line_number = 1L,
column_number = 10L
), linter)
test_that("trailing_blank_lines_linter detects missing terminal newlines in Rmd/qmd docs", {
linter <- trailing_blank_lines_linter()

# Construct an Rmd file without terminal newline
tmp3 <- withr::local_tempfile(fileext = ".Rmd")
cat(
trim_some(
Expand All @@ -46,12 +54,16 @@ test_that("returns the correct linting", {
),
file = tmp3
)
expect_lint(content = NULL, file = tmp3, list(
message = msg2,
line_number = 10L,
# We can't get 4 here because the line is NA-masked in get_source_expressions(), so no line length info exists.
column_number = 1L
), linter)
expect_lint(
file = tmp3,
checks = list(
message = rex::rex("Missing terminal newline."),
line_number = 10L,
# We can't get 4 here because the line is NA-masked in get_source_expressions(), so no line length info exists.
column_number = 1L
),
linters = linter
)

# Construct an Rmd file without R code (#1415)
tmp4 <- withr::local_tempfile(fileext = ".Rmd")
Expand All @@ -65,12 +77,16 @@ test_that("returns the correct linting", {
),
file = tmp4
)
expect_lint(content = NULL, file = tmp4, list(
message = msg2,
line_number = 5L,
# We can't get 4 here because the line is NA-masked in get_source_expressions(), so no line length info exists.
column_number = 1L
), linter)
expect_lint(
file = tmp4,
checks = list(
message = rex::rex("Missing terminal newline."),
line_number = 5L,
# We can't get 4 here because the line is NA-masked in get_source_expressions(), so no line length info exists.
column_number = 1L
),
linters = linter
)

# Construct a qmd file without terminal newline
tmp5 <- withr::local_tempfile(fileext = ".qmd")
Expand All @@ -89,10 +105,66 @@ test_that("returns the correct linting", {
),
file = tmp5
)
expect_lint(content = NULL, file = tmp5, list(
message = msg2,
line_number = 10L,
# We can't get 4 here because the line is NA-masked in get_source_expressions(), so no line length info exists.
column_number = 1L
), linter)
expect_lint(
file = tmp5,
checks = list(
message = rex::rex("Missing terminal newline."),
line_number = 10L,
# We can't get 4 here because the line is NA-masked in get_source_expressions(), so no line length info exists.
column_number = 1L
),
linters = linter
)
})

test_that("blank lines in knitr chunks produce lints", {
linter <- trailing_blank_lines_linter()

tmp6 <- withr::local_tempfile(
fileext = ".Rmd",
lines = trim_some(
'---
title: "Some file"
---
```{r}
abc = 123
```
\n'
)
)

expect_lint(
file = tmp6,
checks = list(message = rex::rex("Trailing blank lines are superfluous."), line_number = 7L, column_number = 1L),
linters = linter
)

tmp7 <- withr::local_tempfile(
fileext = ".qmd",
lines = trim_some(
'---
title: "Some file"
---
```{r}
abc = 123
```
\n'
)
)

expect_lint(
file = tmp7,
checks = list(
list(message = rex::rex("Trailing blank lines are superfluous."), line_number = 7L, column_number = 1L),
list(message = rex::rex("Trailing blank lines are superfluous."), line_number = 8L, column_number = 1L),
list(message = rex::rex("Trailing blank lines are superfluous."), line_number = 9L, column_number = 1L)
),
linters = linter
)
})

0 comments on commit a6254c2

Please sign in to comment.