From b3ded9a7d1ba557cd61d70ba1bde08efb978161b Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Mon, 18 Sep 2023 21:48:07 -0700 Subject: [PATCH 1/9] Consistently lint OP-LAMBDA where FUNCTION is --- NEWS.md | 10 ++++++++++ R/brace_linter.R | 2 +- R/declared_functions.R | 2 +- R/function_left_parentheses_linter.R | 4 ++-- R/indentation_linter.R | 4 ++-- R/package_hooks_linter.R | 10 +++++----- R/paren_body_linter.R | 1 + R/unnecessary_lambda_linter.R | 2 +- R/unreachable_code_linter.R | 2 +- 9 files changed, 24 insertions(+), 13 deletions(-) diff --git a/NEWS.md b/NEWS.md index 005d22eed3..fac717adf4 100644 --- a/NEWS.md +++ b/NEWS.md @@ -35,6 +35,16 @@ + `undesirable_function_linter()` + `unreachable_code_linter()` + `yoda_test_linter()` +* Linters with logic around functon declarations consistently include the R4.0.0 shorthand `\()` (@MichaelChirico). + + `brace_linter()` + + `function_left_parentheses_linter()` + + `indentation_linter()` + + `object_length_linter()` + + `object_name_linter()` + + `package_hooks_linter()` + + `paren_body_linter()` + + `unnecessary_lambda_linter()` + + `unreachable_code_linter()` * `sprintf_linter()` is pipe-aware, so that `x %>% sprintf(fmt = "%s")` no longer lints (#1943, @MichaelChirico). * `line_length_linter()` helpfully includes the line length in the lint message (#2057, @MichaelChirico). * `conjunct_test_linter()` also lints usage like `dplyr::filter(x, A & B)` in favor of using `dplyr::filter(x, A, B)` (part of #884; #2110 and #2078, @salim-b and @MichaelChirico). Option `allow_filter` toggles when this applies. `allow_filter = "always"` drops such lints entirely, while `"not_dplyr"` only lints calls explicitly qualified as `dplyr::filter()`. The default, `"never"`, assumes all unqualified calls to `filter()` are `dplyr::filter()`. diff --git a/R/brace_linter.R b/R/brace_linter.R index 3cb00eee7a..787cd53244 100644 --- a/R/brace_linter.R +++ b/R/brace_linter.R @@ -124,7 +124,7 @@ brace_linter <- function(allow_single_line = FALSE) { # TODO (AshesITR): if c_style_braces is TRUE, this needs to be @line2 + 1 xp_else_same_line <- glue("//ELSE[{xp_else_closed_curly} and @line1 != {xp_else_closed_curly}/@line2]") - xp_function_brace <- "//FUNCTION/parent::expr[@line1 != @line2 and not(expr[OP-LEFT-BRACE])]" + xp_function_brace <- "(//FUNCTION | //OP-LAMBDA)/parent::expr[@line1 != @line2 and not(expr[OP-LEFT-BRACE])]" # if (x) { ... } else if (y) { ... } else { ... } is OK; fully exact pairing # of if/else would require this to be diff --git a/R/declared_functions.R b/R/declared_functions.R index 0096946b92..fa42981fb9 100644 --- a/R/declared_functions.R +++ b/R/declared_functions.R @@ -5,7 +5,7 @@ declared_s3_generics <- function(x) { # Assigns to a symbol "[./LEFT_ASSIGN|EQ_ASSIGN]", - "[./expr[FUNCTION]]", + "[./expr[FUNCTION or OP-LAMBDA]]", "[./expr/SYMBOL]", # Is a S3 Generic (contains call to UseMethod) diff --git a/R/function_left_parentheses_linter.R b/R/function_left_parentheses_linter.R index e19db0d8b2..9f9dfaca02 100644 --- a/R/function_left_parentheses_linter.R +++ b/R/function_left_parentheses_linter.R @@ -46,9 +46,9 @@ function_left_parentheses_linter <- function() { # nolint: object_length. # complicated call to an "extracted" function (see #1963). This mistake was made earlier # because it allows the xpath to be the same for both FUNCTION and SYMBOL_FUNCTION_CALL. # Further, write 4 separate XPaths because the 'range_end_xpath' differs for these two nodes. - bad_line_fun_xpath <- "//FUNCTION[@line1 != following-sibling::OP-LEFT-PAREN/@line1]" + bad_line_fun_xpath <- "(//FUNCTION | //OP-LAMBDA)[@line1 != following-sibling::OP-LEFT-PAREN/@line1]" bad_line_call_xpath <- "//SYMBOL_FUNCTION_CALL[@line1 != parent::expr/following-sibling::OP-LEFT-PAREN/@line1]" - bad_col_fun_xpath <- "//FUNCTION[ + bad_col_fun_xpath <- "(//FUNCTION | //OP-LAMBDA)[ @line1 = following-sibling::OP-LEFT-PAREN/@line1 and @col2 != following-sibling::OP-LEFT-PAREN/@col1 - 1 ]" diff --git a/R/indentation_linter.R b/R/indentation_linter.R index 425fca2bc8..800518b5e6 100644 --- a/R/indentation_linter.R +++ b/R/indentation_linter.R @@ -124,7 +124,7 @@ indentation_linter <- function(indent = 2L, hanging_indent_style = c("tidy", "al paren_tokens_right <- c("OP-RIGHT-BRACE", "OP-RIGHT-PAREN", "OP-RIGHT-BRACKET", "OP-RIGHT-BRACKET") infix_tokens <- setdiff(infix_metadata$xml_tag, c("OP-LEFT-BRACE", "OP-COMMA", paren_tokens_left)) no_paren_keywords <- c("ELSE", "REPEAT") - keyword_tokens <- c("FUNCTION", "IF", "FOR", "WHILE") + keyword_tokens <- c("FUNCTION", "OP-LAMBDA", "IF", "FOR", "WHILE") xp_last_on_line <- "@line1 != following-sibling::*[not(self::COMMENT)][1]/@line1" @@ -341,7 +341,7 @@ build_indentation_style_tidy <- function() { #> body #> } xp_is_double_indent <- " - parent::expr[FUNCTION and not(@line1 = SYMBOL_FORMALS/@line1)] + parent::expr[(FUNCTION or OP-LAMBDA) and not(@line1 = SYMBOL_FORMALS/@line1)] /OP-RIGHT-PAREN[@line1 = preceding-sibling::*[not(self::COMMENT)][1]/@line2] " diff --git a/R/package_hooks_linter.R b/R/package_hooks_linter.R index d541f944c8..40be40a302 100644 --- a/R/package_hooks_linter.R +++ b/R/package_hooks_linter.R @@ -54,7 +54,7 @@ package_hooks_linter <- function() { .onAttach = c(bad_msg_calls, "library.dynam") ) bad_msg_call_xpath_fmt <- " - //FUNCTION + (//FUNCTION | //OP-LAMBDA) /parent::expr[preceding-sibling::expr/SYMBOL[text() = '%s']] //SYMBOL_FUNCTION_CALL[%s] " @@ -81,7 +81,7 @@ package_hooks_linter <- function() { hook_xpath <- sprintf("string(./ancestor::expr/expr/SYMBOL[%s])", ns_calls) load_arg_name_xpath <- " - //FUNCTION + (//FUNCTION | //OP-LAMBDA) /parent::expr[ preceding-sibling::expr/SYMBOL[text() = '.onAttach' or text() = '.onLoad'] and ( @@ -95,7 +95,7 @@ package_hooks_linter <- function() { " library_require_xpath <- " - //FUNCTION + (//FUNCTION | //OP-LAMBDA) /parent::expr[preceding-sibling::expr/SYMBOL[text() = '.onAttach' or text() = '.onLoad']] //*[1][ (self::SYMBOL or self::SYMBOL_FUNCTION_CALL) @@ -104,13 +104,13 @@ package_hooks_linter <- function() { " bad_unload_call_xpath <- " - //FUNCTION + (//FUNCTION | //OP-LAMBDA) /parent::expr[preceding-sibling::expr/SYMBOL[text() = '.Last.lib' or text() = '.onDetach']] //SYMBOL_FUNCTION_CALL[text() = 'library.dynam.unload'] " unload_arg_name_xpath <- " - //FUNCTION + (//FUNCTION | //OP-LAMBDA) /parent::expr[ preceding-sibling::expr/SYMBOL[text() = '.onDetach' or text() = '.Last.lib'] and ( diff --git a/R/paren_body_linter.R b/R/paren_body_linter.R index 083f5fe1ce..eb44a80872 100644 --- a/R/paren_body_linter.R +++ b/R/paren_body_linter.R @@ -33,6 +33,7 @@ paren_body_linter <- make_linter_from_xpath( and @line1 = following-sibling::expr[1]/@line1 and ( preceding-sibling::FUNCTION + or preceding-sibling::OP-LAMBDA or preceding-sibling::IF or preceding-sibling::WHILE or preceding-sibling::OP-LAMBDA diff --git a/R/unnecessary_lambda_linter.R b/R/unnecessary_lambda_linter.R index 75a7fe857d..a445890333 100644 --- a/R/unnecessary_lambda_linter.R +++ b/R/unnecessary_lambda_linter.R @@ -64,7 +64,7 @@ unnecessary_lambda_linter <- function() { //SYMBOL_FUNCTION_CALL[ {apply_funs} ] /parent::expr /following-sibling::expr[ - FUNCTION + (FUNCTION or OP-LAMBDA) and count(SYMBOL_FORMALS) = 1 and {paren_path}/OP-LEFT-PAREN/following-sibling::expr[1][not(preceding-sibling::*[1][self::EQ_SUB])]/SYMBOL and SYMBOL_FORMALS = {paren_path}/OP-LEFT-PAREN/following-sibling::expr[1]/SYMBOL diff --git a/R/unreachable_code_linter.R b/R/unreachable_code_linter.R index ac2f2cb895..ba6850063f 100644 --- a/R/unreachable_code_linter.R +++ b/R/unreachable_code_linter.R @@ -57,7 +57,7 @@ unreachable_code_linter <- function() { # NB: use not(OP-DOLLAR) to prevent matching process$stop(), #1051 xpath_return_stop <- " - //FUNCTION + (//FUNCTION | //OP-LAMBDA) /following-sibling::expr /expr[expr[1][not(OP-DOLLAR or OP-AT) and SYMBOL_FUNCTION_CALL[text() = 'return' or text() = 'stop']]] /following-sibling::*[ From 5005cd1187db20d7a9b8efbb61e263868499d5fb Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Mon, 18 Sep 2023 21:49:39 -0700 Subject: [PATCH 2/9] PR # --- NEWS.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index fac717adf4..5b255762f5 100644 --- a/NEWS.md +++ b/NEWS.md @@ -35,7 +35,7 @@ + `undesirable_function_linter()` + `unreachable_code_linter()` + `yoda_test_linter()` -* Linters with logic around functon declarations consistently include the R4.0.0 shorthand `\()` (@MichaelChirico). +* Linters with logic around functon declarations consistently include the R4.0.0 shorthand `\()` (#2190, @MichaelChirico). + `brace_linter()` + `function_left_parentheses_linter()` + `indentation_linter()` From 61658b3b4696b83565197ed4d4712143ae5f612d Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 06:57:00 +0000 Subject: [PATCH 3/9] tests --- tests/testthat/test-brace_linter.R | 24 ++++++++++-- .../test-function_left_parentheses_linter.R | 11 ++++++ tests/testthat/test-indentation_linter.R | 37 +++++++++++++++++++ tests/testthat/test-object_length_linter.R | 8 ++++ tests/testthat/test-object_name_linter.R | 6 +++ tests/testthat/test-package_hooks_linter.R | 31 ++++++++++++++++ tests/testthat/test-paren_body_linter.R | 8 ++++ .../testthat/test-unnecessary_lambda_linter.R | 8 ++++ tests/testthat/test-unreachable_code_linter.R | 16 ++++++++ 9 files changed, 146 insertions(+), 3 deletions(-) diff --git a/tests/testthat/test-brace_linter.R b/tests/testthat/test-brace_linter.R index 3515e0d8ca..02af137ecb 100644 --- a/tests/testthat/test-brace_linter.R +++ b/tests/testthat/test-brace_linter.R @@ -2,10 +2,10 @@ test_that("brace_linter lints braces correctly", { open_curly_msg <- rex::rex( "Opening curly braces should never go on their own line" ) - closed_curly_msg <- rex::rex(paste( - "Closing curly-braces should always be on their own line,", + closed_curly_msg <- rex::rex( + "Closing curly-braces should always be on their own line, ", "unless they are followed by an else." - )) + ) linter <- brace_linter() expect_lint("blah", NULL, linter) @@ -553,3 +553,21 @@ test_that("code with pipes is handled correctly", { linter ) }) + +test_that("function shorthand is treated like 'full' function", { + skip_if_not_r_version("4.0.0") + linter <- brace_linter() + + expect_lint("a <- \\() { \n}", NULL, linter) + expect_lint( + trim_some(" + x <- \\() + {2} + "), + list( + rex::rex("Opening curly braces should never go on their own line"), + rex::rex("Closing curly-braces should always be on their own line") + ), + linter + ) +}) diff --git a/tests/testthat/test-function_left_parentheses_linter.R b/tests/testthat/test-function_left_parentheses_linter.R index fc9b8c1a14..09166e2718 100644 --- a/tests/testthat/test-function_left_parentheses_linter.R +++ b/tests/testthat/test-function_left_parentheses_linter.R @@ -167,6 +167,7 @@ test_that("it doesn't produce invalid lints", { test_that("newline in character string doesn't trigger false positive (#1963)", { linter <- function_left_parentheses_linter() + expect_lint('foo("\n")$bar()', NULL, linter) # also corrected the lint metadata for similar cases expect_lint( @@ -182,3 +183,13 @@ test_that("newline in character string doesn't trigger false positive (#1963)", linter ) }) + +test_that("shorthand functions are handled", { + skip_if_not_r_version("4.0.0") + linter <- function_left_parentheses_linter() + fun_lint_msg <- rex::rex("Remove spaces before the left parenthesis in a function definition.") + + expect_lint("blah <- \\(blah) { }", NULL, linter) + expect_lint("\\(){\\(){}}()()", NULL, linter) + expect_lint("test <- \\ (x) { }", fun_lint_msg, linter) +}) diff --git a/tests/testthat/test-indentation_linter.R b/tests/testthat/test-indentation_linter.R index 6d271a7574..3880c5d329 100644 --- a/tests/testthat/test-indentation_linter.R +++ b/tests/testthat/test-indentation_linter.R @@ -830,3 +830,40 @@ test_that("it doesn't error on invalid code", { # Part of #1427 expect_lint("function() {)", list(linter = "error", message = rex::rex("unexpected ')'")), indentation_linter()) }) + +test_that("function shorthand is handled", { + skip_if_not_r_version("4.0.0") + linter <- indentation_linter() + + expect_lint( + trim_some(" + lapply(1:10, \\(i) { + i %% 2 + }) + "), + NULL, + linter + ) + + expect_lint( + trim_some(" + lapply(1:10, \\(i) { + i %% 2 # indentation is only 1 character + }) + "), + "Indentation", + linter + ) + + expect_lint( + trim_some(" + \\( + a = 1L, + b = 2L) { + a + b + } + "), + NULL, + linter + ) +}) diff --git a/tests/testthat/test-object_length_linter.R b/tests/testthat/test-object_length_linter.R index 90b7494bd2..42668e1b06 100644 --- a/tests/testthat/test-object_length_linter.R +++ b/tests/testthat/test-object_length_linter.R @@ -64,3 +64,11 @@ test_that("object_length_linter won't fail if dependency has no exports", { 1L ) }) + +test_that("function shorthand is caught", { + expect_lint( + "abcdefghijklm <- \\() NULL", + "function names", + object_length_linter(length = 10L) + ) +}) diff --git a/tests/testthat/test-object_name_linter.R b/tests/testthat/test-object_name_linter.R index 57ec801452..4215ac1b8b 100644 --- a/tests/testthat/test-object_name_linter.R +++ b/tests/testthat/test-object_name_linter.R @@ -267,3 +267,9 @@ test_that("complex LHS of := doesn't cause false positive", { # but only parent::expr[ASSIGN] is needed for strings. expect_lint('dplyr::mutate(df, !!paste0(v, "_l") := df$a * 2)', NULL, object_name_linter()) }) + +test_that("function shorthand also lints", { + skip_if_not_r_version("4.0.0") + + expect_lint("aBc <- \\() NULL", "function name style", object_name_linter()) +}) diff --git a/tests/testthat/test-package_hooks_linter.R b/tests/testthat/test-package_hooks_linter.R index d982a6b866..752170df47 100644 --- a/tests/testthat/test-package_hooks_linter.R +++ b/tests/testthat/test-package_hooks_linter.R @@ -246,3 +246,34 @@ test_that("package_hooks_linter detects bad argument names in .onDetach()/.Last. package_hooks_linter() ) }) + +test_that("function shorthand is handled", { + skip_if_not_r_version("4.0.0") + linter <- package_hooks_linter() + + expect_lint( + ".onLoad <- \\(lib, pkg) packageStartupMessage('hi')", + rex::rex("Put packageStartupMessage() calls in .onAttach()"), + linter + ) + expect_lint( + ".onAttach <- \\(xxx, pkg) { }", + rex::rex(".onAttach() should take two arguments"), + linter + ) + expect_lint( + ".onAttach <- \\(lib, pkg) { require(foo) }", + rex::rex("Don't alter the search() path in .onAttach() by calling require()."), + linter + ) + expect_lint( + ".onDetach <- \\(lib) { library.dynam.unload() }", + rex::rex("Use library.dynam.unload() calls in .onUnload(), not .onDetach()."), + linter + ) + expect_lint( + ".onDetach <- \\(xxx) { }", + rex::rex(".onDetach() should take one argument starting with 'lib'."), + linter + ) +}) diff --git a/tests/testthat/test-paren_body_linter.R b/tests/testthat/test-paren_body_linter.R index 4d23bb511a..bb716696bc 100644 --- a/tests/testthat/test-paren_body_linter.R +++ b/tests/testthat/test-paren_body_linter.R @@ -84,3 +84,11 @@ test_that("multi-line versions are caught", { paren_body_linter() ) }) + +test_that("function shorthand is handled", { + skip_if_not_r_version("4.0.0") + linter <- paren_body_linter() + lint_msg <- rex::rex("There should be a space between a right parenthesis and a body expression.") + + expect_lint("\\()test", lint_msg, linter) +}) diff --git a/tests/testthat/test-unnecessary_lambda_linter.R b/tests/testthat/test-unnecessary_lambda_linter.R index dcbc18bd5c..dbb0be049e 100644 --- a/tests/testthat/test-unnecessary_lambda_linter.R +++ b/tests/testthat/test-unnecessary_lambda_linter.R @@ -120,3 +120,11 @@ test_that("cases with braces are caught", { linter ) }) + +test_that("function shorthand is handled", { + expect_lint( + "lapply(DF, \\(x) sum(x))", + rex::rex("Pass sum directly as a symbol to lapply()"), + unnecessary_lambda_linter() + ) +}) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index df8dae820d..a9a29baad2 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -375,6 +375,22 @@ test_that("unreachable_code_linter identifies unreachable code in mixed conditio ) }) +test_that("function shorthand is handled", { + expect_lint( + trim_some(" + foo <- \\(bar) { + return(bar) + x + 3 + } + "), + list( + line_number = 3L, + message = rex::rex("Code and comments coming after a top-level return() or stop()") + ), + unreachable_code_linter() + ) +}) + # nolint start: commented_code_linter. # TODO(michaelchirico): extend to work on switch() statements # test_that("unreachable_code_linter interacts with switch() as expected", { From dd11e9a47018c07fec93bcba0ca75de417c179a7 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 00:28:57 -0700 Subject: [PATCH 4/9] trailing ws --- tests/testthat/test-package_hooks_linter.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-package_hooks_linter.R b/tests/testthat/test-package_hooks_linter.R index 752170df47..0d1f69f153 100644 --- a/tests/testthat/test-package_hooks_linter.R +++ b/tests/testthat/test-package_hooks_linter.R @@ -255,7 +255,7 @@ test_that("function shorthand is handled", { ".onLoad <- \\(lib, pkg) packageStartupMessage('hi')", rex::rex("Put packageStartupMessage() calls in .onAttach()"), linter - ) + ) expect_lint( ".onAttach <- \\(xxx, pkg) { }", rex::rex(".onAttach() should take two arguments"), From 9267d992a611e4bdc7492dc864356c58122bf034 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 00:45:33 -0700 Subject: [PATCH 5/9] r version skip --- tests/testthat/test-unreachable_code_linter.R | 2 ++ 1 file changed, 2 insertions(+) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index a9a29baad2..cbc6e9f5d0 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -376,6 +376,8 @@ test_that("unreachable_code_linter identifies unreachable code in mixed conditio }) test_that("function shorthand is handled", { + skip_if_not_r_version("4.0.0") + expect_lint( trim_some(" foo <- \\(bar) { From d86d1bb2112418d76bda51092f5d12a7ff5f5ad5 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 00:46:03 -0700 Subject: [PATCH 6/9] skip on R<3 --- tests/testthat/test-unnecessary_lambda_linter.R | 2 ++ 1 file changed, 2 insertions(+) diff --git a/tests/testthat/test-unnecessary_lambda_linter.R b/tests/testthat/test-unnecessary_lambda_linter.R index dbb0be049e..030e1489ba 100644 --- a/tests/testthat/test-unnecessary_lambda_linter.R +++ b/tests/testthat/test-unnecessary_lambda_linter.R @@ -122,6 +122,8 @@ test_that("cases with braces are caught", { }) test_that("function shorthand is handled", { + skip_if_not_r_version("4.0.0") + expect_lint( "lapply(DF, \\(x) sum(x))", rex::rex("Pass sum directly as a symbol to lapply()"), From 1423aa614227ed51454d67f23023628f02a55671 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 00:46:24 -0700 Subject: [PATCH 7/9] another one --- tests/testthat/test-object_length_linter.R | 2 ++ 1 file changed, 2 insertions(+) diff --git a/tests/testthat/test-object_length_linter.R b/tests/testthat/test-object_length_linter.R index 42668e1b06..4575d3d5ad 100644 --- a/tests/testthat/test-object_length_linter.R +++ b/tests/testthat/test-object_length_linter.R @@ -66,6 +66,8 @@ test_that("object_length_linter won't fail if dependency has no exports", { }) test_that("function shorthand is caught", { + skip_if_not_r_version("4.0.0") + expect_lint( "abcdefghijklm <- \\() NULL", "function names", From 3afc911eb6e361ac88146a3aa166ab85e7b06df4 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 01:03:00 -0700 Subject: [PATCH 8/9] lambda from 4.1.0, not 4.0.0 --- tests/testthat/test-brace_linter.R | 2 +- tests/testthat/test-function_left_parentheses_linter.R | 2 +- tests/testthat/test-indentation_linter.R | 2 +- tests/testthat/test-object_length_linter.R | 2 +- tests/testthat/test-object_name_linter.R | 2 +- tests/testthat/test-package_hooks_linter.R | 2 +- tests/testthat/test-paren_body_linter.R | 2 +- tests/testthat/test-unnecessary_lambda_linter.R | 2 +- tests/testthat/test-unreachable_code_linter.R | 2 +- 9 files changed, 9 insertions(+), 9 deletions(-) diff --git a/tests/testthat/test-brace_linter.R b/tests/testthat/test-brace_linter.R index 02af137ecb..e3adc1a599 100644 --- a/tests/testthat/test-brace_linter.R +++ b/tests/testthat/test-brace_linter.R @@ -555,7 +555,7 @@ test_that("code with pipes is handled correctly", { }) test_that("function shorthand is treated like 'full' function", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") linter <- brace_linter() expect_lint("a <- \\() { \n}", NULL, linter) diff --git a/tests/testthat/test-function_left_parentheses_linter.R b/tests/testthat/test-function_left_parentheses_linter.R index 09166e2718..9c53df6627 100644 --- a/tests/testthat/test-function_left_parentheses_linter.R +++ b/tests/testthat/test-function_left_parentheses_linter.R @@ -185,7 +185,7 @@ test_that("newline in character string doesn't trigger false positive (#1963)", }) test_that("shorthand functions are handled", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") linter <- function_left_parentheses_linter() fun_lint_msg <- rex::rex("Remove spaces before the left parenthesis in a function definition.") diff --git a/tests/testthat/test-indentation_linter.R b/tests/testthat/test-indentation_linter.R index 3880c5d329..ed555223df 100644 --- a/tests/testthat/test-indentation_linter.R +++ b/tests/testthat/test-indentation_linter.R @@ -832,7 +832,7 @@ test_that("it doesn't error on invalid code", { }) test_that("function shorthand is handled", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") linter <- indentation_linter() expect_lint( diff --git a/tests/testthat/test-object_length_linter.R b/tests/testthat/test-object_length_linter.R index 4575d3d5ad..54e701b5c8 100644 --- a/tests/testthat/test-object_length_linter.R +++ b/tests/testthat/test-object_length_linter.R @@ -66,7 +66,7 @@ test_that("object_length_linter won't fail if dependency has no exports", { }) test_that("function shorthand is caught", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") expect_lint( "abcdefghijklm <- \\() NULL", diff --git a/tests/testthat/test-object_name_linter.R b/tests/testthat/test-object_name_linter.R index 4215ac1b8b..758c987b14 100644 --- a/tests/testthat/test-object_name_linter.R +++ b/tests/testthat/test-object_name_linter.R @@ -269,7 +269,7 @@ test_that("complex LHS of := doesn't cause false positive", { }) test_that("function shorthand also lints", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") expect_lint("aBc <- \\() NULL", "function name style", object_name_linter()) }) diff --git a/tests/testthat/test-package_hooks_linter.R b/tests/testthat/test-package_hooks_linter.R index 0d1f69f153..369ddbcbd6 100644 --- a/tests/testthat/test-package_hooks_linter.R +++ b/tests/testthat/test-package_hooks_linter.R @@ -248,7 +248,7 @@ test_that("package_hooks_linter detects bad argument names in .onDetach()/.Last. }) test_that("function shorthand is handled", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") linter <- package_hooks_linter() expect_lint( diff --git a/tests/testthat/test-paren_body_linter.R b/tests/testthat/test-paren_body_linter.R index bb716696bc..64e2522b3e 100644 --- a/tests/testthat/test-paren_body_linter.R +++ b/tests/testthat/test-paren_body_linter.R @@ -86,7 +86,7 @@ test_that("multi-line versions are caught", { }) test_that("function shorthand is handled", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") linter <- paren_body_linter() lint_msg <- rex::rex("There should be a space between a right parenthesis and a body expression.") diff --git a/tests/testthat/test-unnecessary_lambda_linter.R b/tests/testthat/test-unnecessary_lambda_linter.R index 030e1489ba..4fdf449052 100644 --- a/tests/testthat/test-unnecessary_lambda_linter.R +++ b/tests/testthat/test-unnecessary_lambda_linter.R @@ -122,7 +122,7 @@ test_that("cases with braces are caught", { }) test_that("function shorthand is handled", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") expect_lint( "lapply(DF, \\(x) sum(x))", diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index cbc6e9f5d0..523cdd56f4 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -376,7 +376,7 @@ test_that("unreachable_code_linter identifies unreachable code in mixed conditio }) test_that("function shorthand is handled", { - skip_if_not_r_version("4.0.0") + skip_if_not_r_version("4.1.0") expect_lint( trim_some(" From fdeed8344daed800cce62f7306c84b177e48ba76 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Tue, 19 Sep 2023 14:53:25 -0700 Subject: [PATCH 9/9] typo Co-authored-by: Indrajeet Patil --- NEWS.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 5b255762f5..af32bddf20 100644 --- a/NEWS.md +++ b/NEWS.md @@ -35,7 +35,7 @@ + `undesirable_function_linter()` + `unreachable_code_linter()` + `yoda_test_linter()` -* Linters with logic around functon declarations consistently include the R4.0.0 shorthand `\()` (#2190, @MichaelChirico). +* Linters with logic around function declarations consistently include the R 4.0.0 shorthand `\()` (#2190, @MichaelChirico). + `brace_linter()` + `function_left_parentheses_linter()` + `indentation_linter()`