diff --git a/R/conjunct_test_linter.R b/R/conjunct_test_linter.R index 95eee5150..8fd825b4a 100644 --- a/R/conjunct_test_linter.R +++ b/R/conjunct_test_linter.R @@ -82,7 +82,8 @@ conjunct_test_linter <- function(allow_named_stopifnot = TRUE, following-sibling::expr[1][AND2] /parent::expr " - named_stopifnot_condition <- if (allow_named_stopifnot) "and not(preceding-sibling::*[1][self::EQ_SUB])" else "" + named_stopifnot_condition <- + if (allow_named_stopifnot) "and not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB])" else "" stopifnot_xpath <- glue(" following-sibling::expr[1][AND2 {named_stopifnot_condition}] /parent::expr diff --git a/R/fixed_regex_linter.R b/R/fixed_regex_linter.R index 5ab8680d5..6655cda0c 100644 --- a/R/fixed_regex_linter.R +++ b/R/fixed_regex_linter.R @@ -120,7 +120,7 @@ fixed_regex_linter <- function(allow_unescaped = FALSE) { and not({ in_pipe_cond }) ) or ( STR_CONST - and preceding-sibling::*[2][self::SYMBOL_SUB/text() = 'pattern'] + and preceding-sibling::*[not(self::COMMENT)][2][self::SYMBOL_SUB/text() = 'pattern'] ) ] ") diff --git a/R/outer_negation_linter.R b/R/outer_negation_linter.R index 6a5ce6e18..584573fd6 100644 --- a/R/outer_negation_linter.R +++ b/R/outer_negation_linter.R @@ -44,7 +44,7 @@ outer_negation_linter <- function() { not(expr[ position() > 1 and not(OP-EXCLAMATION) - and not(preceding-sibling::*[1][self::EQ_SUB]) + and not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB]) ]) ] " diff --git a/R/shared_constants.R b/R/shared_constants.R index 20c054c11..dbad48dcb 100644 --- a/R/shared_constants.R +++ b/R/shared_constants.R @@ -220,7 +220,7 @@ object_name_xpath <- local({ ]" # either an argument supplied positionally, i.e., not like 'arg = val', or the call - not_kwarg_cond <- "not(preceding-sibling::*[1][self::EQ_SUB])" + not_kwarg_cond <- "not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB])" glue(xp_strip_comments(" //SYMBOL[ {sprintf(xp_assignment_target_fmt, 'ancestor', '')} ] diff --git a/R/unnecessary_concatenation_linter.R b/R/unnecessary_concatenation_linter.R index 271d2ece6..519662a91 100644 --- a/R/unnecessary_concatenation_linter.R +++ b/R/unnecessary_concatenation_linter.R @@ -66,7 +66,7 @@ unnecessary_concatenation_linter <- function(allow_single_expression = TRUE) { # pipes <- setdiff(magrittr_pipes, "%$%") to_pipe_xpath <- glue(" - ./preceding-sibling::*[1][ + ./preceding-sibling::*[not(self::COMMENT)][1][ self::PIPE or self::SPECIAL[{ xp_text_in_table(pipes) }] ] diff --git a/R/unnecessary_lambda_linter.R b/R/unnecessary_lambda_linter.R index f2f62232d..76dbf9c6b 100644 --- a/R/unnecessary_lambda_linter.R +++ b/R/unnecessary_lambda_linter.R @@ -125,10 +125,14 @@ unnecessary_lambda_linter <- function(allow_comparison = FALSE) { .//expr[ position() = 2 and preceding-sibling::expr/SYMBOL_FUNCTION_CALL - and not(preceding-sibling::*[1][self::EQ_SUB]) + and not(preceding-sibling::*[not(self::COMMENT)][1][self::EQ_SUB]) and not(parent::expr[ preceding-sibling::expr[not(SYMBOL_FUNCTION_CALL)] - or following-sibling::*[not(self::OP-RIGHT-PAREN or self::OP-RIGHT-BRACE)] + or following-sibling::*[not( + self::OP-RIGHT-PAREN + or self::OP-RIGHT-BRACE + or self::COMMENT + )] ]) ]/SYMBOL ] @@ -143,7 +147,12 @@ unnecessary_lambda_linter <- function(allow_comparison = FALSE) { purrr_fun_xpath <- glue(" following-sibling::expr[ OP-TILDE - and expr[OP-LEFT-PAREN/following-sibling::expr[1][not(preceding-sibling::*[2][self::SYMBOL_SUB])]/{purrr_symbol}] + and expr + /OP-LEFT-PAREN + /following-sibling::expr[1][ + not(preceding-sibling::*[not(self::COMMENT)][2][self::SYMBOL_SUB]) + ] + /{purrr_symbol} and not(expr/OP-LEFT-PAREN/following-sibling::expr[position() > 1]//{purrr_symbol}) ]") diff --git a/R/unnecessary_nesting_linter.R b/R/unnecessary_nesting_linter.R index 3490f9409..71e7b432e 100644 --- a/R/unnecessary_nesting_linter.R +++ b/R/unnecessary_nesting_linter.R @@ -234,7 +234,7 @@ unnecessary_nesting_linter <- function( # catch if (cond) { if (other_cond) { ... } } # count(*): only OP-LEFT-BRACE, one , and OP-RIGHT-BRACE. # Note that third node could be . - "following-sibling::expr[OP-LEFT-BRACE and count(*) = 3]/expr[IF and not(ELSE)]" + "following-sibling::expr[OP-LEFT-BRACE and count(*) - count(COMMENT) = 3]/expr[IF and not(ELSE)]" ), collapse = " | " ) diff --git a/tests/testthat/test-conjunct_test_linter.R b/tests/testthat/test-conjunct_test_linter.R index 047d2456d..d08e46d4f 100644 --- a/tests/testthat/test-conjunct_test_linter.R +++ b/tests/testthat/test-conjunct_test_linter.R @@ -1,21 +1,25 @@ test_that("conjunct_test_linter skips allowed usages of expect_true", { - expect_lint("expect_true(x)", NULL, conjunct_test_linter()) - expect_lint("testthat::expect_true(x, y, z)", NULL, conjunct_test_linter()) + linter <- conjunct_test_linter() + + expect_no_lint("expect_true(x)", linter) + expect_no_lint("testthat::expect_true(x, y, z)", linter) # more complicated expression - expect_lint("expect_true(x || (y && z))", NULL, conjunct_test_linter()) + expect_no_lint("expect_true(x || (y && z))", linter) # the same by operator precedence, though not obvious a priori - expect_lint("expect_true(x || y && z)", NULL, conjunct_test_linter()) - expect_lint("expect_true(x && y || z)", NULL, conjunct_test_linter()) + expect_no_lint("expect_true(x || y && z)", linter) + expect_no_lint("expect_true(x && y || z)", linter) }) test_that("conjunct_test_linter skips allowed usages of expect_true", { - expect_lint("expect_false(x)", NULL, conjunct_test_linter()) - expect_lint("testthat::expect_false(x, y, z)", NULL, conjunct_test_linter()) + linter <- conjunct_test_linter() + + expect_no_lint("expect_false(x)", linter) + expect_no_lint("testthat::expect_false(x, y, z)", linter) # more complicated expression # (NB: xx && yy || zz and xx || yy && zz both parse with || first) - expect_lint("expect_false(x && (y || z))", NULL, conjunct_test_linter()) + expect_no_lint("expect_false(x && (y || z))", linter) }) test_that("conjunct_test_linter blocks && conditions with expect_true()", { @@ -43,14 +47,14 @@ test_that("conjunct_test_linter blocks || conditions with expect_false()", { test_that("conjunct_test_linter skips allowed stopifnot() and assert_that() usages", { linter <- conjunct_test_linter() - expect_lint("stopifnot(x)", NULL, linter) - expect_lint("assert_that(x, y, z)", NULL, linter) + expect_no_lint("stopifnot(x)", linter) + expect_no_lint("assert_that(x, y, z)", linter) # more complicated expression - expect_lint("stopifnot(x || (y && z))", NULL, linter) + expect_no_lint("stopifnot(x || (y && z))", linter) # the same by operator precedence, though not obvious a priori - expect_lint("stopifnot(x || y && z)", NULL, linter) - expect_lint("assertthat::assert_that(x && y || z)", NULL, linter) + expect_no_lint("stopifnot(x || y && z)", linter) + expect_no_lint("assertthat::assert_that(x && y || z)", linter) }) test_that("conjunct_test_linter blocks simple disallowed usages of stopifnot() and assert_that()", { @@ -66,12 +70,23 @@ test_that("conjunct_test_linter blocks simple disallowed usages of stopifnot() a }) test_that("conjunct_test_linter's allow_named_stopifnot argument works", { + linter <- conjunct_test_linter() + # allowed by default - expect_lint( + expect_no_lint( "stopifnot('x must be a logical scalar' = length(x) == 1 && is.logical(x) && !is.na(x))", - NULL, - conjunct_test_linter() + linter ) + # including with intervening comment + expect_no_lint( + trim_some(" + stopifnot('x must be a logical scalar' = # comment + length(x) == 1 && is.logical(x) && !is.na(x) + ) + "), + linter + ) + expect_lint( "stopifnot('x is a logical scalar' = length(x) == 1 && is.logical(x) && !is.na(x))", rex::rex("Write multiple conditions like stopifnot(A, B)"), @@ -82,11 +97,11 @@ test_that("conjunct_test_linter's allow_named_stopifnot argument works", { test_that("conjunct_test_linter skips allowed usages", { linter <- conjunct_test_linter() - expect_lint("dplyr::filter(DF, A, B)", NULL, linter) - expect_lint("dplyr::filter(DF, !(A & B))", NULL, linter) + expect_no_lint("dplyr::filter(DF, A, B)", linter) + expect_no_lint("dplyr::filter(DF, !(A & B))", linter) # | is the "top-level" operator here - expect_lint("dplyr::filter(DF, A & B | C)", NULL, linter) - expect_lint("dplyr::filter(DF, A | B & C)", NULL, linter) + expect_no_lint("dplyr::filter(DF, A & B | C)", linter) + expect_no_lint("dplyr::filter(DF, A | B & C)", linter) }) test_that("conjunct_test_linter blocks simple disallowed usages", { @@ -105,22 +120,22 @@ test_that("conjunct_test_linter respects its allow_filter argument", { linter_dplyr <- conjunct_test_linter(allow_filter = "not_dplyr") lint_msg <- rex::rex("Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B)") - expect_lint("dplyr::filter(DF, A & B)", NULL, linter_always) - expect_lint("dplyr::filter(DF, A & B & C)", NULL, linter_always) - expect_lint("DF %>% dplyr::filter(A & B)", NULL, linter_always) + expect_no_lint("dplyr::filter(DF, A & B)", linter_always) + expect_no_lint("dplyr::filter(DF, A & B & C)", linter_always) + expect_no_lint("DF %>% dplyr::filter(A & B)", linter_always) expect_lint("dplyr::filter(DF, A & B)", lint_msg, linter_dplyr) expect_lint("dplyr::filter(DF, A & B & C)", lint_msg, linter_dplyr) expect_lint("DF %>% dplyr::filter(A & B)", lint_msg, linter_dplyr) - expect_lint("filter(DF, A & B)", NULL, linter_dplyr) - expect_lint("filter(DF, A & B & C)", NULL, linter_dplyr) - expect_lint("DF %>% filter(A & B)", NULL, linter_dplyr) + expect_no_lint("filter(DF, A & B)", linter_dplyr) + expect_no_lint("filter(DF, A & B & C)", linter_dplyr) + expect_no_lint("DF %>% filter(A & B)", linter_dplyr) }) test_that("filter() is assumed to be dplyr::filter() by default, unless o/w specified", { linter <- conjunct_test_linter() - expect_lint("stats::filter(A & B)", NULL, linter) - expect_lint("ns::filter(A & B)", NULL, linter) + expect_no_lint("stats::filter(A & B)", linter) + expect_no_lint("ns::filter(A & B)", linter) expect_lint( "DF %>% filter(A & B)", rex::rex("Use dplyr::filter(DF, A, B) instead of dplyr::filter(DF, A & B)"), diff --git a/tests/testthat/test-fixed_regex_linter.R b/tests/testthat/test-fixed_regex_linter.R index e0dcae72e..5ce25a2dd 100644 --- a/tests/testthat/test-fixed_regex_linter.R +++ b/tests/testthat/test-fixed_regex_linter.R @@ -352,13 +352,13 @@ test_that("'unescaped' regex can optionally be skipped", { }) local({ + linter <- fixed_regex_linter() + lint_msg <- "This regular expression is static" pipes <- pipes(exclude = c("%$%", "%T>%")) + patrick::with_parameters_test_that( "linter is pipe-aware", { - linter <- fixed_regex_linter() - lint_msg <- "This regular expression is static" - expect_lint(paste("x", pipe, "grepl(pattern = 'a')"), lint_msg, linter) expect_no_lint(paste("x", pipe, "grepl(pattern = '^a')"), linter) expect_no_lint(paste("x", pipe, "grepl(pattern = 'a', fixed = TRUE)"), linter) @@ -377,3 +377,14 @@ local({ .test_name = names(pipes) ) }) + +test_that("pipe-aware lint logic survives adversarial comments", { + expect_lint( + trim_some(" + x %>% grepl(pattern = # comment + 'a') + "), + "This regular expression is static", + fixed_regex_linter() + ) +}) diff --git a/tests/testthat/test-object_length_linter.R b/tests/testthat/test-object_length_linter.R index 240c86192..051c6bf2f 100644 --- a/tests/testthat/test-object_length_linter.R +++ b/tests/testthat/test-object_length_linter.R @@ -104,4 +104,14 @@ test_that("literals in assign() and setGeneric() are checked", { expect_lint("assign(x = 'badBadBadBadName', 2, env)", lint_msg, linter) expect_lint("assign(envir = 'good_env_name', 'badBadBadBadName', 2)", lint_msg, linter) expect_lint("assign(envir = 'good_env_name', x = 'badBadBadBadName', 2)", lint_msg, linter) + + # adversarial comments + expect_lint( + trim_some(" + assign(envir = # comment + 'good_env_name', 'badBadBadBadName', 2) + "), + lint_msg, + linter + ) }) diff --git a/tests/testthat/test-object_name_linter.R b/tests/testthat/test-object_name_linter.R index cdf6591c8..ad09b06c7 100644 --- a/tests/testthat/test-object_name_linter.R +++ b/tests/testthat/test-object_name_linter.R @@ -345,6 +345,16 @@ test_that("literals in assign() and setGeneric() are checked", { expect_lint("assign(x = 'badName', 2, env)", lint_msg, linter) expect_lint("assign(envir = 'good_env_name', 'badName', 2)", lint_msg, linter) expect_lint("assign(envir = 'good_env_name', x = 'badName', 2)", lint_msg, linter) + + # adversarial comments + expect_lint( + trim_some(" + assign(envir = # comment + 'good_env_name', 'badName', 2) + "), + lint_msg, + linter + ) }) test_that("generics assigned with '=' or <<- are registered", { diff --git a/tests/testthat/test-outer_negation_linter.R b/tests/testthat/test-outer_negation_linter.R index 0601aa4ee..aa18761f1 100644 --- a/tests/testthat/test-outer_negation_linter.R +++ b/tests/testthat/test-outer_negation_linter.R @@ -1,20 +1,20 @@ test_that("outer_negation_linter skips allowed usages", { linter <- outer_negation_linter() - expect_lint("x <- any(y)", NULL, linter) - expect_lint("y <- all(z)", NULL, linter) + expect_no_lint("x <- any(y)", linter) + expect_no_lint("y <- all(z)", linter) # extended usage of any is not covered - expect_lint("any(!a & b)", NULL, linter) - expect_lint("all(a | !b)", NULL, linter) - - expect_lint("any(a, b)", NULL, linter) - expect_lint("all(b, c)", NULL, linter) - expect_lint("any(!a, b)", NULL, linter) - expect_lint("all(a, !b)", NULL, linter) - expect_lint("any(a, !b, na.rm = TRUE)", NULL, linter) + expect_no_lint("any(!a & b)", linter) + expect_no_lint("all(a | !b)", linter) + + expect_no_lint("any(a, b)", linter) + expect_no_lint("all(b, c)", linter) + expect_no_lint("any(!a, b)", linter) + expect_no_lint("all(a, !b)", linter) + expect_no_lint("any(a, !b, na.rm = TRUE)", linter) # ditto when na.rm is passed quoted - expect_lint("any(a, !b, 'na.rm' = TRUE)", NULL, linter) + expect_no_lint("any(a, !b, 'na.rm' = TRUE)", linter) }) test_that("outer_negation_linter blocks simple disallowed usages", { @@ -31,15 +31,25 @@ test_that("outer_negation_linter blocks simple disallowed usages", { # catch when all inputs are negated expect_lint("any(!x, !y)", not_all_msg, linter) expect_lint("all(!x, !y, na.rm = TRUE)", not_any_msg, linter) + + # adversarial comment + expect_lint( + trim_some(" + any(!x, na.rm = # comment + TRUE) + "), + not_all_msg, + linter + ) }) test_that("outer_negation_linter doesn't trigger on empty calls", { linter <- outer_negation_linter() # minimal version of issue - expect_lint("any()", NULL, linter) + expect_no_lint("any()", linter) # closer to what was is practically relevant, as another regression test - expect_lint("x %>% any()", NULL, linter) + expect_no_lint("x %>% any()", linter) }) test_that("lints vectorize", { diff --git a/tests/testthat/test-sprintf_linter.R b/tests/testthat/test-sprintf_linter.R index 2f0e95886..25905febc 100644 --- a/tests/testthat/test-sprintf_linter.R +++ b/tests/testthat/test-sprintf_linter.R @@ -157,6 +157,26 @@ local({ ) }) +test_that("pipe logic survives adversarial comments", { + linter <- sprintf_linter() + + expect_no_lint( + trim_some(" + x |> # comment + sprintf(fmt = '%s') + "), + linter + ) + + expect_no_lint( + trim_some(' + "%s" %>% # comment + sprintf("%s%s") + '), + linter + ) +}) + test_that("lints vectorize", { skip_if_not_r_version("4.1.0") diff --git a/tests/testthat/test-unnecessary_concatenation_linter.R b/tests/testthat/test-unnecessary_concatenation_linter.R index 55abd21b0..1800f3490 100644 --- a/tests/testthat/test-unnecessary_concatenation_linter.R +++ b/tests/testthat/test-unnecessary_concatenation_linter.R @@ -1,13 +1,13 @@ test_that("unnecessary_concatenation_linter skips allowed usages", { linter <- unnecessary_concatenation_linter() - expect_lint("c(x)", NULL, linter) - expect_lint("c(1, 2)", NULL, linter) - expect_lint("c(x, recursive = TRUE)", NULL, linter) - expect_lint("c(1, recursive = FALSE)", NULL, linter) - expect_lint("lapply(1, c)", NULL, linter) - expect_lint("c(a = 1)", NULL, linter) - expect_lint("c('a' = 1)", NULL, linter) + expect_no_lint("c(x)", linter) + expect_no_lint("c(1, 2)", linter) + expect_no_lint("c(x, recursive = TRUE)", linter) + expect_no_lint("c(1, recursive = FALSE)", linter) + expect_no_lint("lapply(1, c)", linter) + expect_no_lint("c(a = 1)", linter) + expect_no_lint("c('a' = 1)", linter) }) test_that("unnecessary_concatenation_linter blocks disallowed usages", { @@ -54,7 +54,7 @@ local({ patrick::with_parameters_test_that( "Correctly handles concatenation within magrittr pipes", { - expect_lint(sprintf('"a" %s c("b")', pipe), NULL, linter) + expect_no_lint(sprintf('"a" %s c("b")', pipe), linter) expect_lint(sprintf('"a" %s c()', pipe), const_msg, linter) expect_lint(sprintf('"a" %s list("b", c())', pipe), no_arg_msg, linter) }, @@ -63,14 +63,24 @@ local({ ) }) +test_that("logic survives adversarial comments", { + expect_no_lint( + trim_some(' + "a" %T>% # comment + c("b") + '), + unnecessary_concatenation_linter() + ) +}) + test_that("symbolic expressions are allowed, except by request", { linter <- unnecessary_concatenation_linter() linter_strict <- unnecessary_concatenation_linter(allow_single_expression = FALSE) lint_msg <- rex::rex("Remove unnecessary c() of a constant expression.") - expect_lint("c(alpha / 2)", NULL, linter) - expect_lint("c(paste0('.', 1:2))", NULL, linter) - expect_lint("c(DF[cond > 1, col])", NULL, linter) + expect_no_lint("c(alpha / 2)", linter) + expect_no_lint("c(paste0('.', 1:2))", linter) + expect_no_lint("c(DF[cond > 1, col])", linter) # allow_single_expression = FALSE turns both into lints expect_lint("c(alpha / 2)", lint_msg, linter_strict) @@ -89,24 +99,24 @@ test_that("sequences with : are linted whenever a constant is involved", { # this is slightly different if a,b are factors, in which case : does # something like interaction - expect_lint("c(a:b)", NULL, linter) + expect_no_lint("c(a:b)", linter) expect_lint("c(a:b)", expr_msg, linter_strict) - expect_lint("c(a:foo(b))", NULL, linter) + expect_no_lint("c(a:foo(b))", linter) expect_lint("c(a:foo(b))", expr_msg, linter_strict) }) test_that("c(...) does not lint under !allow_single_expression", { - expect_lint("c(...)", NULL, unnecessary_concatenation_linter(allow_single_expression = FALSE)) + expect_no_lint("c(...)", unnecessary_concatenation_linter(allow_single_expression = FALSE)) }) test_that("invalid allow_single_expression argument produce informative error messages", { expect_error( - expect_lint("c()", NULL, unnecessary_concatenation_linter(allow_single_expression = 1.0)), + expect_no_lint("c()", unnecessary_concatenation_linter(allow_single_expression = 1.0)), rex::rex("is.logical(allow_single_expression) is not TRUE") ) expect_error( - expect_lint("c()", NULL, unnecessary_concatenation_linter(allow_single_expression = c(TRUE, FALSE))), + expect_no_lint("c()", unnecessary_concatenation_linter(allow_single_expression = c(TRUE, FALSE))), rex::rex("length(allow_single_expression) == 1L is not TRUE") ) }) diff --git a/tests/testthat/test-unnecessary_lambda_linter.R b/tests/testthat/test-unnecessary_lambda_linter.R index 44655b44b..f3228058b 100644 --- a/tests/testthat/test-unnecessary_lambda_linter.R +++ b/tests/testthat/test-unnecessary_lambda_linter.R @@ -161,6 +161,15 @@ test_that("unnecessary_lambda_linter doesn't apply to keyword args", { expect_no_lint("lapply(x, function(xi) data.frame(nm = xi))", linter) expect_no_lint("lapply(x, function(xi) return(data.frame(nm = xi)))", linter) + + # adversarially commented + expect_no_lint( + trim_some(" + lapply(x, function(xi) data.frame(nm = # comment + xi)) + "), + linter + ) }) test_that("purrr-style anonymous functions are also caught", { @@ -185,6 +194,15 @@ test_that("purrr-style anonymous functions are also caught", { rex::rex("Pass foo directly as a symbol to map_vec()"), linter ) + + # adversarial comment + expect_no_lint( + trim_some(" + map_dbl(x, ~foo(bar = # comment + .x)) + "), + linter + ) }) test_that("cases with braces are caught", { @@ -246,6 +264,16 @@ test_that("cases with braces are caught", { # false positives like #2231, #2247 are avoided with braces too expect_no_lint("lapply(x, function(xi) { foo(xi)$bar })", linter) expect_no_lint("lapply(x, function(xi) { foo(xi) - 1 })", linter) + + expect_lint( + trim_some(" + lapply(y, function(yi) { + print(yi) # comment + }) + "), + lint_msg, + linter + ) }) test_that("function shorthand is handled", { diff --git a/tests/testthat/test-unnecessary_nesting_linter.R b/tests/testthat/test-unnecessary_nesting_linter.R index c48383e64..64c09855a 100644 --- a/tests/testthat/test-unnecessary_nesting_linter.R +++ b/tests/testthat/test-unnecessary_nesting_linter.R @@ -496,6 +496,21 @@ test_that("unnecessary_nesting_linter skips allowed usages", { linter ) + # but comments are irrelevant (they should be moved to another anchor) + expect_lint( + trim_some(" + if (x && a) { + # comment1 + if (y || b) { + 1L + } + # comment2 + } + "), + "Combine this `if` statement with the one found at line 1", + linter + ) + expect_no_lint( trim_some(" if (x) { @@ -758,7 +773,7 @@ patrick::with_parameters_test_that( ) ) -test_that("allow_functions= works", { +test_that("allow_functions= works", { # nofuzz '})' break-up by comment linter_default <- unnecessary_nesting_linter() linter_foo <- unnecessary_nesting_linter(allow_functions = "foo") expect_lint("foo(x, {y}, z)", "Reduce the nesting of this statement", linter_default)