Skip to content

Commit

Permalink
Merge pull request #128 from saurfang/spaces_left_parentheses_linter
Browse files Browse the repository at this point in the history
Make spaces_left_parentheses_linter more robust when determining `(` type
  • Loading branch information
jimhester committed Dec 29, 2015
2 parents bcf542b + 62eadcb commit 6381970
Show file tree
Hide file tree
Showing 8 changed files with 26 additions and 17 deletions.
2 changes: 1 addition & 1 deletion R/cache.R
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ find_new_line <- function(line_number, line, lines) {

width <- 1L

while(width <= length(lines)) {
while (width <= length(lines)) {
low <- line_number - width
if (low > 0L) {
if (lines[low] %==% line) {
Expand Down
6 changes: 3 additions & 3 deletions R/exclude.R
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
#' Exclude lines or files from linting
#'
#'
#' @param lints that need to be filetered.
#' @param exclusions manually specified exclusions
#' @param ... additional arguments passed to \code{\link{parse_exclusions}}
Expand All @@ -8,7 +8,7 @@
#' \enumerate{
#' \item{single line in the source file. default: \code{# nolint}}
#' \item{line range in the source file. default: \code{# nolint start}, \code{# nolint end}}
#' \item{exclusions parameter, a named list of the files and lines to exclude, or just the filenames
#' \item{exclusions parameter, a named list of the files and lines to exclude, or just the filenames
#' if you want to exclude the entire file.}
#' }
exclude <- function(lints, exclusions = settings$exclusions, ...) {
Expand Down Expand Up @@ -63,7 +63,7 @@ parse_exclusions <- function(file, exclude = settings$exclude,
stop(file, " has ", length(starts), " starts but only ", length(ends), " ends!")
}

for(i in seq_along(starts)) {
for (i in seq_along(starts)) {
exclusions <- c(exclusions, seq(starts[i], ends[i]))
}
}
Expand Down
2 changes: 1 addition & 1 deletion R/get_source_expressions.R
Original file line number Diff line number Diff line change
Expand Up @@ -249,7 +249,7 @@ fix_eq_assign <- function(pc) {

end <- true_locs[i]
j <- end + 1L
while(j <= length(expr_locs) && expr_locs[j] == FALSE) {
while (j <= length(expr_locs) && expr_locs[j] == FALSE) {
end <- j
j <- j + 1L
}
Expand Down
2 changes: 1 addition & 1 deletion R/methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ names.lints <- function(x, ...) {
split.lints <- function(x, f=NULL, ...) {
if (is.null(f)) f <- names(x)
splt <- split.default(x, f)
for(i in names(splt)) class(splt[[i]]) <- "lints"
for (i in names(splt)) class(splt[[i]]) <- "lints"
return(splt)
}

Expand Down
17 changes: 9 additions & 8 deletions R/spaces_left_parentheses_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,14 +7,15 @@ spaces_left_parentheses_linter <- function(source_file) {

parsed <- source_file$parsed_content[id, ]

family_ids <- family(source_file$parsed_content, parsed$id)

types <- source_file$parsed_content[
source_file$parsed_content$id %in% family_ids,
"token"]

is_function <- length(family_ids) %!=% 0L &&
any(types %in% c("SYMBOL_FUNCTION_CALL", "FUNCTION"))
terminal_tokens_before <-
source_file$parsed_content$token[
source_file$parsed_content$line1 == parsed$line1 &
source_file$parsed_content$col1 < parsed$col1 &
source_file$parsed_content$terminal]
last_type <- tail(terminal_tokens_before, n = 1)

is_function <- length(last_type) %!=% 0L &&
(last_type %in% c("SYMBOL_FUNCTION_CALL", "FUNCTION", "'}'", "')'", "']'"))

if (!is_function) {

Expand Down
2 changes: 1 addition & 1 deletion R/trailing_blank_lines_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ trailing_blank_lines_linter <- function(source_file) {

line_number <- length(source_file$file_lines)
lints <- list()
while(line_number > 0L && (is.na(blanks[[line_number]]) || isTRUE(blanks[[line_number]]))) {
while (line_number > 0L && (is.na(blanks[[line_number]]) || isTRUE(blanks[[line_number]]))) {
if (!is.na(blanks[[line_number]])) {
lints[[length(lints) + 1L]] <-
Lint(
Expand Down
4 changes: 2 additions & 2 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ named_list <- function(...) {
#' # you can also omit the argument name if you are just using different
#' # arguments.
#' with_defaults(line_length_linter(120))
#'
#'
#' # enforce camelCase rather than snake_case
#' with_defaults(camel_case_linter = NULL,
#' snake_case_linter)
Expand Down Expand Up @@ -110,7 +110,7 @@ settings <- list2env(default_settings, parent = emptyenv())
lintr.linter_file = ".lintr"
)
toset <- ! (names(op.lintr) %in% names(op))
if(any(toset)) options(op.lintr[toset])
if (any(toset)) options(op.lintr[toset])

invisible()
}
8 changes: 8 additions & 0 deletions tests/testthat/test-spaces_left_parentheses_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,10 @@ test_that("returns the correct linting", {

expect_lint("range(10)[(2 - 1):(10 - 1)]", NULL, spaces_left_parentheses_linter)

expect_lint("function(){function(){}}()()", NULL, spaces_left_parentheses_linter)

expect_lint("c(function(){})[1]()", NULL, spaces_left_parentheses_linter)

expect_lint("((1 + 1))",
rex("Place a space before left parenthesis, except in a function call."),
spaces_left_parentheses_linter)
Expand All @@ -55,6 +59,10 @@ test_that("returns the correct linting", {
rex("Place a space before left parenthesis, except in a function call."),
spaces_left_parentheses_linter)

expect_lint("test <- function(x) { if(`+`(1, 1)) 'hi' }",
rex("Place a space before left parenthesis, except in a function call."),
spaces_left_parentheses_linter)

expect_lint("\"test <- function(x) { if(1 + 1) 'hi' }\"",
NULL,
spaces_left_parentheses_linter)
Expand Down

0 comments on commit 6381970

Please sign in to comment.