Skip to content

Commit

Permalink
New function_brace_linter (#987)
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico authored Mar 27, 2022
1 parent 309db27 commit 4270c61
Show file tree
Hide file tree
Showing 12 changed files with 87 additions and 7 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ Collate:
'expect_type_linter.R'
'extract.R'
'extraction_operator_linter.R'
'function_brace_linter.R'
'function_left_parentheses.R'
'get_source_expressions.R'
'ids_with_token.R'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ export(expect_s4_class_linter)
export(expect_true_false_linter)
export(expect_type_linter)
export(extraction_operator_linter)
export(function_brace_linter)
export(function_left_parentheses_linter)
export(get_source_expressions)
export(ids_with_token)
Expand Down
28 changes: 28 additions & 0 deletions R/function_brace_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
#' Require multi-line functions to use braces
#'
#' This linter catches function definitions spanning multiple lines of code
#' that aren't wrapped in braces
#'
#' @evalRd rd_tags("function_brace_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
function_brace_linter <- function() {
Linter(function(source_file) {
if (length(source_file$xml_parsed_content) == 0L) {
return(list())
}

xml <- source_file$xml_parsed_content

bad_expr_xpath <- "//expr[FUNCTION and @line1 != @line2 and not(expr[OP-LEFT-BRACE])]"
bad_expr <- xml2::xml_find_all(xml, bad_expr_xpath)

return(lapply(
bad_expr,
xml_nodes_to_lint,
source_file = source_file,
lint_message = "Any function spanning multiple lines must use curly braces.",
type = "warning"
))
})
}
1 change: 1 addition & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ default_linters <- with_defaults(
commented_code_linter(),
cyclocomp_linter(),
equals_na_linter(),
function_brace_linter(),
function_left_parentheses_linter(),
if_else_match_braces_linter(),
infix_spaces_linter(),
Expand Down
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ expect_s4_class_linter,package_development best_practices
expect_true_false_linter,package_development best_practices readability
expect_type_linter,package_development best_practices
extraction_operator_linter,style best_practices
function_brace_linter,default style readability
function_left_parentheses_linter,style readability default
if_else_match_braces_linter,default style readability
implicit_integer_linter,style consistency best_practices
Expand Down
3 changes: 2 additions & 1 deletion man/default_linters.Rd

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

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

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

13 changes: 7 additions & 6 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.

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

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

4 changes: 4 additions & 0 deletions tests/testthat/default_linter_testcode.R
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,10 @@ someComplicatedFunctionWithALongCamelCaseName <- function(x)
# vector_logic
if (1 & 2) FALSE else TRUE

# function_brace
my_metric <- function(x)
sum(x) + prod(x)

# no_tab
# pipe_continuation
# seq_linter
Expand Down
22 changes: 22 additions & 0 deletions tests/testthat/test-function_brace_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
test_that("function_brace_linter skips allowed usages", {
expect_lint("function(x) 4", NULL, function_brace_linter())

lines <- trim_some("
function(x) {
x + 4
}
")
expect_lint(lines, NULL, function_brace_linter())
})

test_that("function_brace_linter blocks disallowed usage", {
lines <- trim_some("
function(x)
x+4
")
expect_lint(
lines,
rex::rex("Any function spanning multiple lines must use curly braces."),
function_brace_linter()
)
})

0 comments on commit 4270c61

Please sign in to comment.