Skip to content

Commit

Permalink
delete else_same_line_linter and merge it into brace_linter
Browse files Browse the repository at this point in the history
  • Loading branch information
AshesITR committed Apr 25, 2022
1 parent cdfbfd7 commit b7a3d8d
Show file tree
Hide file tree
Showing 13 changed files with 65 additions and 102 deletions.
1 change: 0 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,6 @@ Collate:
'declared_functions.R'
'deprecated.R'
'duplicate_argument_linter.R'
'else_same_line_linter.R'
'equals_na_linter.R'
'exclude.R'
'expect_comparison_linter.R'
Expand Down
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,6 @@ export(default_settings)
export(default_undesirable_functions)
export(default_undesirable_operators)
export(duplicate_argument_linter)
export(else_same_line_linter)
export(equals_na_linter)
export(expect_comparison_linter)
export(expect_identical_linter)
Expand Down
5 changes: 3 additions & 2 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,9 @@
* Consistent access to linters through a function call, even for linters without parameters (#245, @fangly, @AshesITR, and @MichaelChirico)
* Removed deprecated functions `absolute_paths_linter`, `camel_case_linter`, `multiple_dots_linter`, `snake_case_linter`, and `trailing_semicolons_linter`. They have been marked as deprecated since v1.0.1, which was released in 2017.
* Rename `semicolon_terminator_linter` to `semicolon_linter` for better consistency. `semicolon_terminator_linter` survives but is marked for deprecation. The new linter also has a new signature, taking arguments `allow_compound` and `allow_trailing` to replace the old single argument `semicolon=`, again for signature consistency with other linters.
* Combined several curly brace related linters into a new `brace_linter`:
* Combined several curly brace related linters into a new `brace_linter` (#1041, @AshesITR):
+ `closed_curly_linter()`
+ Require `else` to come on the same line as the preceding `}`, if present (#884, @michaelchirico)
* The `...` arguments for `lint()`, `lint_dir()`, and `lint_package()` have promoted to an earlier position to better match the [Tidyverse design principal](https://design.tidyverse.org/args-data-details.html) of data->descriptor->details. This change enables passing objects to `...` without needing to specify non-required arguments, e.g. `lint_dir("/path/to/dir", linter())` now works without the need to specify `relative_path`. This affects some code that uses positional arguments. (#935, @michaelchirico)
+ For `lint()`, `...` is now the 3rd argument, where earlier this was `cache=`
+ For `lint_dir()` and `lint_package()`, `...` is now the 2nd argument, where earlier this was `relative_path=`
Expand Down Expand Up @@ -130,7 +131,7 @@ function calls. (#850, #851, @renkun-ken)
* `nested_ifelse_linter()` Prevent nested calls to `ifelse()` like `ifelse(A, x, ifelse(B, y, z))`, and similar
* `condition_message_linter` Prevent condition messages from being constructed like `stop(paste(...))` (where just `stop(...)` is preferable)
* `redundant_ifelse_linter()` Prevent usage like `ifelse(A & B, TRUE, FALSE)` or `ifelse(C, 0, 1)` (the latter is `as.numeric(!C)`)
* `else_same_line_linter()` Require `else` to come on the same line as the preceding `}`, if present
* `brace_linter()` Require `else` to come on the same line as the preceding `}`, if present
* `unreachable_code_linter()` Prevent code after `return()` and `stop()` statements that will never be reached (extended for #1051 thanks to early user testing, thanks @bersbersbers!)
* `regex_subset_linter()` Require usage of `grep(ptn, x, value = TRUE)` over `x[grep(ptn, x)]` and similar
* `consecutive_stopifnot_linter()` Require consecutive calls to `stopifnot()` to be unified into one
Expand Down
15 changes: 15 additions & 0 deletions R/brace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@
#' Perform various style checks related to placement and spacing of curly braces:
#'
#' - Curly braces are on their own line unless they are followed by an `else`.
#' - Closing curly braces in `if` conditions are on the same line as the corresponding `else`.
#'
#' @param allow_single_line if `TRUE`, allow an open and closed curly pair on the same line.
#'
Expand Down Expand Up @@ -31,6 +32,7 @@ brace_linter <- function(allow_single_line = FALSE) {
)"
))

# TODO (AshesITR): if c_style_braces is TRUE, skip the not(ELSE) condition
xp_closed_curly <- glue::glue("//OP-RIGHT-BRACE[
{ xp_cond_closed } and (
(@line1 = preceding-sibling::*/@line2) or
Expand All @@ -48,6 +50,19 @@ brace_linter <- function(allow_single_line = FALSE) {
)
))

xp_else_closed_curly <- "preceding-sibling::IF/following-sibling::expr[2]/OP-RIGHT-BRACE"
# need to (?) repeat previous_curly_path since != will return true if there is
# no such node. ditto for approach with not(@line1 = ...).
# TODO (AshesITR): if c_style_braces is TRUE, this needs to be @line2 + 1
xp_else_same_line <- glue::glue("//ELSE[{xp_else_closed_curly} and @line1 != {xp_else_closed_curly}/@line2]")

lints <- c(lints, lapply(
xml2::xml_find_all(source_expression$xml_parsed_content, xp_else_same_line),
xml_nodes_to_lint,
source_file = source_expression,
lint_message = "`else` should come on the same line as the previous `}`."
))

lints
})
}
31 changes: 0 additions & 31 deletions R/else_same_line_linter.R

This file was deleted.

1 change: 0 additions & 1 deletion inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@ conjunct_test_linter,package_development best_practices readability
consecutive_stopifnot_linter,style readability consistency
cyclocomp_linter,style readability best_practices default configurable
duplicate_argument_linter,correctness common_mistakes configurable
else_same_line_linter,style readability
equals_na_linter,robustness correctness common_mistakes default
expect_comparison_linter,package_development best_practices
expect_identical_linter,package_development
Expand Down
3 changes: 2 additions & 1 deletion man/brace_linter.Rd

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

18 changes: 0 additions & 18 deletions man/else_same_line_linter.Rd

This file was deleted.

5 changes: 2 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: 0 additions & 1 deletion man/readability_linters.Rd

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

1 change: 0 additions & 1 deletion man/style_linters.Rd

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

43 changes: 43 additions & 0 deletions tests/testthat/test-brace_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,3 +80,46 @@ test_that("brace_linter lints closed braces correctly", {
# }} is allowed
expect_lint("{{ x }}", NULL, linter)
})

test_that("brace_linter lints else correctly", {
linter <- brace_linter()
expect_lint("if (TRUE) 1 else 2", NULL, linter)
expect_lint("if (TRUE) 1", NULL, linter)

lines_brace <- trim_some("
if (TRUE) {
1
} else {
2
}
")
expect_lint(lines_brace, NULL, linter)

# such usage is also not allowed by the style guide, but test anyway
lines_unbrace <- trim_some("
foo <- function(x) {
if (TRUE)
1
else
2
}
")
expect_lint(lines_unbrace, NULL, linter)

lines <- trim_some("
foo <- function(x) {
if (x) {
1
}
else {
2
}
}
")
expect_lint(
lines,
rex::rex("`else` should come on the same line as the previous `}`."),
linter
)
})

42 changes: 0 additions & 42 deletions tests/testthat/test-else_same_line_linter.R

This file was deleted.

0 comments on commit b7a3d8d

Please sign in to comment.