Skip to content

Commit

Permalink
First draft for in_linter()
Browse files Browse the repository at this point in the history
  • Loading branch information
Bisaloo committed Jun 22, 2024
1 parent 1c7f4a0 commit 1d2e4b1
Show file tree
Hide file tree
Showing 10 changed files with 137 additions and 3 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -112,6 +112,7 @@ Collate:
'ifelse_censor_linter.R'
'implicit_assignment_linter.R'
'implicit_integer_linter.R'
'in_linter.R'
'indentation_linter.R'
'infix_spaces_linter.R'
'inner_combine_linter.R'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,7 @@ export(if_switch_linter)
export(ifelse_censor_linter)
export(implicit_assignment_linter)
export(implicit_integer_linter)
export(in_linter)
export(indentation_linter)
export(infix_spaces_linter)
export(inner_combine_linter)
Expand Down
35 changes: 35 additions & 0 deletions R/in_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
#' Chained equality check linter
#'
#' Report the use of chained equality checks where `%in%` would be more
#' appropriate
#'
#' @examples
#' # lints
#' lint(
#' text = "x == 'a' | x == 'b'",
#' linters = in_linter()
#' )
#'
#' # This only makes sense in the case x if of length 1
#' lint(
#' text = "x == 'a' || x == 'b'",
#' linters = in_linter()
#' )
#'
#' # okay
#' lint(
#' text = "x %in% c('a', 'b')",
#' linters = in_linter()
#' )
#'
#' @evalRd rd_tags("in_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
in_linter <- make_linter_from_xpath(
xpath = "(//OR|//OR2)[
preceding-sibling::expr[EQ]
and following-sibling::expr[EQ]
and preceding-sibling::expr/expr/SYMBOL/text() = following-sibling::expr/expr/SYMBOL/text()
]",
lint_message = "Use %in% to test equality of a variable against multiple values."
)
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,7 @@ if_switch_linter,best_practices readability consistency efficiency configurable
ifelse_censor_linter,best_practices efficiency
implicit_assignment_linter,style best_practices readability configurable
implicit_integer_linter,style consistency best_practices configurable
in_linter,readability efficiency best_practices
indentation_linter,style readability default configurable
infix_spaces_linter,style readability default configurable
inner_combine_linter,efficiency consistency readability
Expand Down
1 change: 1 addition & 0 deletions man/best_practices_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/efficiency_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

38 changes: 38 additions & 0 deletions man/in_linter.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

7 changes: 4 additions & 3 deletions man/linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/readability_linters.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

54 changes: 54 additions & 0 deletions tests/testthat/test-in_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
test_that("in_linter catches unnecessary OR chains", {
linter <- in_linter()
lint_msg <- rex::rex("%in%")

expect_lint(
"x == 'a' | x == 'b'",
lint_msg,
linter
)

# Works with short-circuit operator
expect_lint(
"x == 'a' || x == 'b'",
lint_msg,
linter
)

# Works with yoda tests
expect_lint(
"'a' == x || 'b' == x",
lint_msg,
linter
)

# Works with 'semi-yoda' tests
expect_lint(
"x == 'a' || 'b' == x",
lint_msg,
linter
)

# Works with longer chains
expect_lint(
"x == 'a' | x == 'b' | x == 'c'",
lint_msg,
linter
)
})

test_that("common in_linter negative cases", {
linter <- in_linter()

expect_lint(
"x == 'a' | y == 'b'",
NULL,
linter
)

expect_lint(
"x == 'a' || y == 'b'",
NULL,
linter
)
})

0 comments on commit 1d2e4b1

Please sign in to comment.