Skip to content

Commit

Permalink
Merge branch 'master' into object-name-operator
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico committed Nov 29, 2020
2 parents bb5ce3f + 8fbc489 commit 93c076c
Show file tree
Hide file tree
Showing 12 changed files with 81 additions and 44 deletions.
2 changes: 1 addition & 1 deletion .lintr
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
linters: with_defaults( # The following TODOs are part of an effort to have {lintr} lint-free (#584)
line_length_linter = line_length_linter(160), # TODO reduce to 120 (#593)
line_length_linter = line_length_linter(120),
infix_spaces_linter = NULL, # TODO enable (#594)
commented_code_linter = NULL, # TODO enable (#595)
cyclocomp_linter = cyclocomp_linter(29), # TODO reduce to 15
Expand Down
5 changes: 4 additions & 1 deletion R/actions.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,10 @@ in_github_actions <- function() {
# Output logging commands for any lints found
github_actions_log_lints <- function(lints) {
for (x in lints) {
cat(sprintf("::warning file=%s,line=%s,col=%s::%s\n", x$filename, x$line_number, x$column_number, x$message), sep = "")
cat(
sprintf("::warning file=%s,line=%s,col=%s::%s\n", x$filename, x$line_number, x$column_number, x$message),
sep = ""
)
}
}

Expand Down
3 changes: 2 additions & 1 deletion R/closed_curly_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,8 @@ closed_curly_linter <- function(allow_single_line = FALSE) {
content_after <- unname(substr(line, parsed$col1 + 1L, nchar(line)))
content_before <- unname(substr(line, 1, parsed$col1 - 1L))

double_curly <- rex::re_matches(content_after, rex::rex(start, "}")) || rex::re_matches(content_before, rex::rex("}", end))
double_curly <- rex::re_matches(content_after, rex::rex(start, "}")) ||
rex::re_matches(content_before, rex::rex("}", end))

if (double_curly) {
return()
Expand Down
6 changes: 5 additions & 1 deletion R/expect_lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -91,7 +91,11 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
isTRUE(all.equal(value, check))
}
if (!is.logical(exp)) {
stop("Invalid regex result, did you mistakenly have a capture group in the regex? Be sure to escape parenthesis with `[]`", call. = FALSE)
stop(
"Invalid regex result, did you mistakenly have a capture group in the regex? ",
"Be sure to escape parenthesis with `[]`",
call. = FALSE
)
}
testthat::expect(exp, msg)
})
Expand Down
4 changes: 2 additions & 2 deletions R/get_source_expressions.R
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,7 @@ get_source_expressions <- function(filename) {
file_lines = source_file$lines,
content = source_file$lines,
full_parsed_content = parsed_content,
full_xml_parsed_content = if (!is.null(parsed_content)) tryCatch(xml2::read_xml(xmlparsedata::xml_parse_data(parsed_content)), error = function(e) NULL),
full_xml_parsed_content = safe_parse_to_xml(parsed_content),
terminal_newline = terminal_newline
)

Expand All @@ -194,7 +194,7 @@ get_single_source_expression <- function(loc,
column = parsed_content[loc, "col1"],
lines = expr_lines,
parsed_content = pc,
xml_parsed_content = tryCatch(xml2::read_xml(xmlparsedata::xml_parse_data(pc)), error = function(e) NULL),
xml_parsed_content = safe_parse_to_xml(pc),
content = content,
find_line = find_line_fun(content),
find_column = find_column_fun(content)
Expand Down
3 changes: 2 additions & 1 deletion R/lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -245,7 +245,8 @@ lint_dir <- function(path = ".", relative_path = TRUE, ..., exclusions = NULL,
#' )
#' }
#' @export
lint_package <- function(path = ".", relative_path = TRUE, ..., exclusions = list("R/RcppExports.R"), parse_settings = TRUE) {
lint_package <- function(path = ".", relative_path = TRUE, ...,
exclusions = list("R/RcppExports.R"), parse_settings = TRUE) {
path <- find_package(path)

if (parse_settings) {
Expand Down
5 changes: 4 additions & 1 deletion R/object_name_linters.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,10 @@ check_style <- function(nms, style, generics = character()) {
conforming[!nzchar(nms) | is.na(conforming)] <- TRUE

if (any(!conforming)) {
possible_s3 <- re_matches(nms[!conforming], rex(capture(name = "generic", something), ".", capture(name = "method", something)))
possible_s3 <- re_matches(
nms[!conforming],
rex(capture(name = "generic", something), ".", capture(name = "method", something))
)
if (any(!is.na(possible_s3))) {
has_generic <- possible_s3$generic %in% generics

Expand Down
3 changes: 2 additions & 1 deletion R/open_curly_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,8 @@ open_curly_linter <- function(allow_single_line = FALSE) {

only_comment <- rex::re_matches(content_after, rex::rex(any_spaces, "#", something, end))

double_curly <- rex::re_matches(content_after, rex::rex(start, "{")) || rex::re_matches(content_before, rex::rex("{", end))
double_curly <- rex::re_matches(content_after, rex::rex(start, "{")) ||
rex::re_matches(content_before, rex::rex("{", end))

if (double_curly) {
return()
Expand Down
5 changes: 5 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,11 @@ recursive_ls <- function(env) {
}
}

safe_parse_to_xml <- function(parsed_content) {
if (is.null(parsed_content)) return(NULL)
tryCatch(xml2::read_xml(xmlparsedata::xml_parse_data(parsed_content)), error = function(e) NULL)
}

get_content <- function(lines, info) {
lines[is.na(lines)] <- ""

Expand Down
13 changes: 13 additions & 0 deletions tests/testthat/test-actions.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
test_that("GitHub Actions functionality works", {
# imitate being on GHA whether or not we are
withr::with_envvar(c(GITHUB_ACTIONS = "true"), {
writeLines("x <- 1:nrow(y)", tmp <- tempfile())
on.exit(unlink(tmp))

old = options(lintr.rstudio_source_markers = FALSE)
on.exit(options(old), add = TRUE)

l <- lint(tmp)
expect_output(print(l), "::warning file", fixed = TRUE)
})
})
10 changes: 8 additions & 2 deletions tests/testthat/test-expect_lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -32,10 +32,14 @@ test_that("single check", {
expect_success(expect_lint("\t1", list(ranges = list(c(1L, 1L))), no_tab_linter))
expect_success(expect_lint("a=1", list(message = msg, line_number = 1L), linter))
expect_failure(expect_lint("a=1", list(2L, msg), linter))

expect_error(expect_lint("1:nrow(x)", "(group)", seq_linter), "Invalid regex result", fixed = TRUE)
})

test_that("multiple checks", {
expect_success(expect_lint(file = "exclusions-test", checks = as.list(rep(msg, 6L)), linters = linter, parse_settings = FALSE))
expect_success(
expect_lint(file = "exclusions-test", checks = as.list(rep(msg, 6L)), linters = linter, parse_settings = FALSE)
)

expect_success(expect_lint("a=1; b=2", list(msg, msg), linter))
expect_success(expect_lint("a=1; b=2", list(c(message = msg), c(message = msg)), linter))
Expand All @@ -46,6 +50,8 @@ test_that("multiple checks", {

expect_success(expect_lint("a=1; b=2", list(list(line_number = 1L), list(line_number = 2L)), linter))
expect_failure(expect_lint("a=1; b=2", list(list(line_number = 2L), list(line_number = 2L)), linter))
expect_success(expect_lint("\t1\n\t2", list("tabs", list(column_number = 1L, ranges = list(c(1L, 1L)))), no_tab_linter))
expect_success(
expect_lint("\t1\n\t2", list("tabs", list(column_number = 1L, ranges = list(c(1L, 1L)))), no_tab_linter)
)

})
66 changes: 33 additions & 33 deletions tests/testthat/test-object_name_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,40 +3,40 @@ context("object_name_linter")

test_that("styles are correctly identified", {
styles <- names(style_regexes)
# symbl UpC lowC snake SNAKE dot alllow ALLUP
expect_equivalent(lapply(styles, check_style, nms = "x" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = ".x" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X" ), list(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(lapply(styles, check_style, nms = "x." ), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X." ), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "x_" ), list(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X_" ), list(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "xy" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "xY" ), list(FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "Xy" ), list(FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "XY" ), list(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(lapply(styles, check_style, nms = "x1" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X1" ), list(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(lapply(styles, check_style, nms = "x_y"), list(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X_Y"), list(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X.Y"), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "x_2"), list(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X_2"), list(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "x.2"), list(FALSE, FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "X.2"), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
do_style_check <- function(nms) lapply(styles, check_style, nms = nms)
# symbl UpC lowC snake SNAKE dot alllow ALLUP
expect_equivalent(do_style_check("x" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(do_style_check(".x" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(do_style_check("X" ), list(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(do_style_check("x." ), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("X." ), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("x_" ), list(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("X_" ), list(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("xy" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(do_style_check("xY" ), list(FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("Xy" ), list(FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("XY" ), list(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(do_style_check("x1" ), list(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(do_style_check("X1" ), list(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(do_style_check("x_y"), list(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("X_Y"), list(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("X.Y"), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("x_2"), list(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("X_2"), list(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("x.2"), list(FALSE, FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE))
expect_equivalent(do_style_check("X.2"), list(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))


# symbl UpC lowC snake SNAKE dot alllow ALLUP
expect_equivalent(lapply(styles, check_style, nms = "IHave1Cat" ), c(FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "iHave1Cat" ), c(FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "i_have_1_cat" ), c(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "I_HAVE_1_CAT" ), c(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "i.have.1.cat" ), c(FALSE, FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "ihave1cat" ), c(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "IHAVE1CAT" ), c(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(lapply(styles, check_style, nms = "I.HAVE_ONECAT"), c(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "." ), c( TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(lapply(styles, check_style, nms = "%^%" ), c( TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
# symbl UpC lowC snake SNAKE dot alllow ALLUP
expect_equivalent(do_style_check("IHave1Cat" ), c(FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("iHave1Cat" ), c(FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("i_have_1_cat" ), c(FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("I_HAVE_1_CAT" ), c(FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("i.have.1.cat" ), c(FALSE, FALSE, FALSE, FALSE, FALSE, TRUE, FALSE, FALSE))
expect_equivalent(do_style_check("ihave1cat" ), c(FALSE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE, FALSE))
expect_equivalent(do_style_check("IHAVE1CAT" ), c(FALSE, TRUE, FALSE, FALSE, TRUE, FALSE, FALSE, TRUE))
expect_equivalent(do_style_check("I.HAVE_ONECAT"), c(FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("." ), c( TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
expect_equivalent(do_style_check("%^%" ), c( TRUE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE, FALSE))
})

test_that("linter ignores some objects", {
Expand Down

0 comments on commit 93c076c

Please sign in to comment.