From 7178ee3687afdfe1583d0f9b717a8a3a16267e9c Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Mon, 4 Sep 2023 08:25:03 +0200 Subject: [PATCH 1/2] Add allow_trailing_comma parameter to commas_linter --- R/commas_linter.R | 21 +++++++++++++++++++-- 1 file changed, 19 insertions(+), 2 deletions(-) diff --git a/R/commas_linter.R b/R/commas_linter.R index d7ff5ac14..ea402971d 100644 --- a/R/commas_linter.R +++ b/R/commas_linter.R @@ -1,6 +1,9 @@ #' Commas linter #' #' Check that all commas are followed by spaces, but do not have spaces before them. +#' +#' @param allow_trailing_comma If `TRUE`, the linter allows a comma to be followed +#' directly by a closing bracket without a space. #' #' @examples #' # will produce lints @@ -18,6 +21,11 @@ #' text = "x[ ,, drop=TRUE]", #' linters = commas_linter() #' ) +#' +#' lint( +#' text = "x[1,]", +#' linters = commas_linter() +#' ) #' #' # okay #' lint( @@ -40,12 +48,17 @@ #' linters = commas_linter() #' ) #' +#' lint( +#' text = "x[1,]", +#' linters = commas_linter(allow_trailing_comma = TRUE) +#' ) +#' #' @evalRd rd_tags("commas_linter") #' @seealso #' - [linters] for a complete list of linters available in lintr. #' - #' @export -commas_linter <- function() { +commas_linter <- function(allow_trailing_comma = FALSE) { # conditions are in carefully-chosen order for performance -- # an expression like c(a,b,c,....) with many elements can have # a huge number of preceding-siblings and the performance of @@ -58,7 +71,11 @@ commas_linter <- function() { @line1 = preceding-sibling::*[1]/@line1 and not(preceding-sibling::*[1][self::OP-COMMA or self::EQ_SUB]) ]" - xpath_after <- "//OP-COMMA[@line1 = following-sibling::*[1]/@line1 and @col1 = following-sibling::*[1]/@col1 - 1]" + xpath_after <- paste0( + "//OP-COMMA[@line1 = following-sibling::*[1]/@line1 and @col1 = following-sibling::*[1]/@col1 - 1", + if(allow_trailing_comma) " and not(following-sibling::*[1]/self::OP-RIGHT-BRACKET)", + "]" + ) Linter(function(source_expression) { if (!is_lint_level(source_expression, "expression")) { From 643d2d7bf491855c210f7cf48e1b5c96cfb3365c Mon Sep 17 00:00:00 2001 From: Matthias Ollech Date: Mon, 4 Sep 2023 08:51:55 +0200 Subject: [PATCH 2/2] `commas_linter` tests use new parameter --- tests/testthat/test-commas_linter.R | 55 ++++++++++++++++++++++++++++- 1 file changed, 54 insertions(+), 1 deletion(-) diff --git a/tests/testthat/test-commas_linter.R b/tests/testthat/test-commas_linter.R index 0bb9e2abd..f01ec7048 100644 --- a/tests/testthat/test-commas_linter.R +++ b/tests/testthat/test-commas_linter.R @@ -1,4 +1,4 @@ -test_that("returns the correct linting", { +test_that("returns the correct linting (with default parameters)", { linter <- commas_linter() msg_after <- rex::rex("Commas should always have a space after.") msg_before <- rex::rex("Commas should never have a space before.") @@ -13,6 +13,8 @@ test_that("returns the correct linting", { expect_lint("fun(1\n,1)", msg_after, linter) expect_lint("fun(1,1)", msg_after, linter) expect_lint("\nfun(1,1)", msg_after, linter) + expect_lint("a(1,)", msg_after, linter) + expect_lint("a[1,]", msg_after, linter) expect_lint( "fun(1 ,1)", list( @@ -46,3 +48,54 @@ test_that("returns the correct linting", { linter ) }) + +test_that("returns the correct linting (with 'allow_trailing_comma' set)", { + linter <- commas_linter(allow_trailing_comma = TRUE) + msg_after <- rex::rex("Commas should always have a space after.") + msg_before <- rex::rex("Commas should never have a space before.") + + expect_lint("blah", NULL, linter) + expect_lint("fun(1, 1)", NULL, linter) + expect_lint("fun(1,\n 1)", NULL, linter) + expect_lint("fun(1,\n1)", NULL, linter) + expect_lint("fun(1\n,\n1)", NULL, linter) + expect_lint("fun(1\n ,\n1)", NULL, linter) + expect_lint("a[1,]", NULL, linter) + + expect_lint("fun(1\n,1)", msg_after, linter) + expect_lint("fun(1,1)", msg_after, linter) + expect_lint("\nfun(1,1)", msg_after, linter) + expect_lint("a(1,)", msg_after, linter) + expect_lint( + "fun(1 ,1)", + list( + msg_before, + msg_after + ), + linter + ) + + expect_lint("\"fun(1 ,1)\"", NULL, linter) + expect_lint("a[1, , 2]", NULL, linter) + expect_lint("a[1, , 2, , 3]", NULL, linter) + + expect_lint("switch(op, x = foo, y = bar)", NULL, linter) + expect_lint("switch(op, x = , y = bar)", NULL, linter) + expect_lint("switch(op, \"x\" = , y = bar)", NULL, linter) + expect_lint("switch(op, x = ,\ny = bar)", NULL, linter) + + expect_lint("switch(op, x = foo , y = bar)", msg_before, linter) + expect_lint("switch(op, x = foo , y = bar)", msg_before, linter) + expect_lint("switch(op , x = foo, y = bar)", msg_before, linter) + expect_lint("switch(op, x = foo, y = bar(a = 4 , b = 5))", msg_before, linter) + expect_lint("fun(op, x = foo , y = switch(bar, a = 4, b = 5))", msg_before, linter) + + expect_lint( + "fun(op ,bar)", + list( + list(message = msg_before, column_number = 7L, ranges = list(c(7L, 10L))), + list(message = msg_after, column_number = 12L, ranges = list(c(12L, 12L))) + ), + linter + ) +}) \ No newline at end of file