diff --git a/.lintr b/.lintr index bf7f63a38..e182f51a1 100644 --- a/.lintr +++ b/.lintr @@ -31,7 +31,7 @@ linters: linters_with_defaults( sort_linter(), sprintf_linter(), strings_as_factors_linter(), - undesirable_function_linter(c(Sys.setenv = NA_character_, mapply = NA_character_)), + undesirable_function_linter(c(Sys.setenv = NA_character_, mapply = NA_character_, structure = NA_character_)), unnecessary_nested_if_linter(), unnecessary_lambda_linter(), unnecessary_concatenation_linter(allow_single_expression = FALSE), diff --git a/NEWS.md b/NEWS.md index a8bd1468a..d75bf5f2d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -52,7 +52,7 @@ * `unreachable_code_linter()` checks for code inside `if (FALSE)` and other conditional loops with deterministically false conditions (#1428, @ME0265). * `implicit_assignment_linter()` gains an argument `allow_lazy` (default `FALSE`) that allows optionally skipping lazy assignments like `A && (B <- foo(A))` (#2016, @MichaelChirico). * `unused_import_linter()` gains an argument `interpret_glue` (default `TRUE`) paralleling that in `object_usage_linter()` to toggle whether `glue::glue()` expressions should be inspected for exported object usage (#2042, @MichaelChirico). -* `default_undesirable_functions` is updated to also include `Sys.unsetenv()` (#2192, @IndrajeetPatil). +* `default_undesirable_functions` is updated to also include `Sys.unsetenv()` and `structure()` (#2192 and #2228, @IndrajeetPatil and @MichaelChirico). * Linters with logic around the magrittr pipe `%>%` consistently apply it to the other pipes `%!>%`, `%T>%`, `%<>%` (and possibly `%$%`) where appropriate (#2008, @MichaelChirico). + `brace_linter()` + `pipe_call_linter()` diff --git a/R/zzz.R b/R/zzz.R index f7ed629e1..b9d6f4b7c 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -171,7 +171,9 @@ all_undesirable_functions <- modify_defaults( untrace = paste( "remove this likely leftover from debugging.", "It is only useful for interactive debugging with trace()" - ) + ), + structure = + "Use class<-, names<-, and attr<- to set attributes" ) #' @rdname default_undesirable_functions @@ -194,12 +196,14 @@ default_undesirable_functions <- all_undesirable_functions[names(all_undesirable "setwd", "sink", "source", + "structure", "Sys.setenv", "Sys.setlocale", "Sys.unsetenv", "trace", "undebug", - "untrace" + "untrace", + NULL )] #' @rdname default_undesirable_functions @@ -232,7 +236,8 @@ all_undesirable_operators <- modify_defaults( default_undesirable_operators <- all_undesirable_operators[names(all_undesirable_operators) %in% c( ":::", "<<-", - "->>" + "->>", + NULL )] #' Default lintr settings diff --git a/tests/testthat/test-checkstyle_output.R b/tests/testthat/test-checkstyle_output.R index 2b16504cd..d962ea96f 100644 --- a/tests/testthat/test-checkstyle_output.R +++ b/tests/testthat/test-checkstyle_output.R @@ -1,33 +1,31 @@ test_that("return lint report as checkstyle xml", { - lints <- structure( - list( - Lint( - filename = "test_file", - line_number = 1L, - column_number = 2L, - type = "error", - line = "a line", - message = "foo" - ), - Lint( - filename = "test_file", - line_number = 2L, - column_number = 1L, - type = "style", - line = "another line", - message = "bar" - ), - Lint( - filename = "test_file2", - line_number = 1L, - column_number = 1L, - type = "warning", - line = "yet another line", - message = "baz" - ) + lints <- list( + Lint( + filename = "test_file", + line_number = 1L, + column_number = 2L, + type = "error", + line = "a line", + message = "foo" ), - class = "lints" + Lint( + filename = "test_file", + line_number = 2L, + column_number = 1L, + type = "style", + line = "another line", + message = "bar" + ), + Lint( + filename = "test_file2", + line_number = 1L, + column_number = 1L, + type = "warning", + line = "yet another line", + message = "baz" + ) ) + class(lints) <- "lints" tmp <- withr::local_tempfile() checkstyle_output(lints, tmp) diff --git a/tests/testthat/test-error.R b/tests/testthat/test-error.R index e8412ad18..3001c8d66 100644 --- a/tests/testthat/test-error.R +++ b/tests/testthat/test-error.R @@ -3,12 +3,15 @@ test_that("returns the correct linting", { expect_lint('"\\R"', msg_escape_char) expect_lint('"\\A"', msg_escape_char) expect_lint('"\\z"', msg_escape_char) + placeholder_linter <- function(...) NULL + class(placeholder_linter) <- "linter" + attr(placeholder_linter, "name") <- "null" expect_lint( "a <- 1 function() { b", rex::rex("unexpected end of input"), - structure(function(...) NULL, class = "linter", name = "null") + placeholder_linter ) linter <- equals_na_linter() diff --git a/tests/testthat/test-methods.R b/tests/testthat/test-methods.R index e77a99e73..f9def5807 100644 --- a/tests/testthat/test-methods.R +++ b/tests/testthat/test-methods.R @@ -50,7 +50,8 @@ test_that("as.data.frame.lints", { ) # Convert lints to data.frame - lints <- structure(list(l1, l2), class = "lints") + lints <- list(l1, l2) + class(lints) <- "lints" df <- as.data.frame(lints) expect_s3_class(df, "data.frame") diff --git a/tests/testthat/test-rstudio_markers.R b/tests/testthat/test-rstudio_markers.R index ca21a35fe..203e87a41 100644 --- a/tests/testthat/test-rstudio_markers.R +++ b/tests/testthat/test-rstudio_markers.R @@ -4,19 +4,15 @@ test_that("it returns markers which match lints", { mockery::stub(rstudio_source_markers, "rstudioapi::callFun", function(...) list(...)) mockery::stub(rstudio_source_markers, "rstudioapi::executeCommand", function(...) NULL) - lint1 <- structure( - list( - Lint( - filename = "test_file", - line_number = 1L, - column_number = 2L, - type = "error", - line = "a line", - message = "hi" - ) - ), - class = "lints" - ) + lint1 <- list(Lint( + filename = "test_file", + line_number = 1L, + column_number = 2L, + type = "error", + line = "a line", + message = "hi" + )) + class(lint1) <- "lints" lint1[[1L]]$linter <- "linter_name" marker1 <- rstudio_source_markers(lint1) @@ -27,26 +23,24 @@ test_that("it returns markers which match lints", { expect_identical(marker1$markers[[1L]]$column, lint1[[1L]]$column_number) expect_identical(marker1$markers[[1L]]$message, paste0("[", lint1[[1L]]$linter, "] ", lint1[[1L]]$message)) - lint2 <- structure( - list( - Lint( - filename = "test_file", - line_number = 1L, - column_number = 2L, - type = "error", - line = "a line", - message = "hi" - ), - Lint( - filename = "test_file2", - line_number = 10L, - column_number = 1L, - type = "warning", - message = "test a message" - ) + lint2 <- list( + Lint( + filename = "test_file", + line_number = 1L, + column_number = 2L, + type = "error", + line = "a line", + message = "hi" ), - class = "lints" + Lint( + filename = "test_file2", + line_number = 10L, + column_number = 1L, + type = "warning", + message = "test a message" + ) ) + class(lint2) <- "lints" lint2[[1L]]$linter <- "linter_name" lint2[[2L]]$linter <- "linter_name" marker2 <- rstudio_source_markers(lint2) @@ -64,20 +58,16 @@ test_that("it prepends the package path if it exists", { mockery::stub(rstudio_source_markers, "rstudioapi::callFun", function(...) list(...)) mockery::stub(rstudio_source_markers, "rstudioapi::executeCommand", function(...) NULL) - lint3 <- structure( - list( - Lint( - filename = "test_file", - line_number = 1L, - column_number = 2L, - type = "error", - line = "a line", - message = "hi" - ) - ), - class = "lints", - path = "test" - ) + lint3 <- list(Lint( + filename = "test_file", + line_number = 1L, + column_number = 2L, + type = "error", + line = "a line", + message = "hi" + )) + class(lint3) <- "lints" + attr(lint3, "path") <- "test" lint3[[1L]]$linter <- "linter_name" marker3 <- rstudio_source_markers(lint3) expect_identical(marker3$name, "lintr") @@ -95,10 +85,7 @@ test_that("it returns an empty list of markers if there are no lints", { mockery::stub(rstudio_source_markers, "rstudioapi::callFun", function(...) list(...)) mockery::stub(rstudio_source_markers, "rstudioapi::executeCommand", function(...) NULL) - lint4 <- structure( - list(), - class = "lints" - ) + lint4 <- `class<-`(list(), "lints") marker4 <- rstudio_source_markers(lint4) expect_identical(marker4$name, "lintr") expect_identical(marker4$markers, list())