Skip to content

Commit

Permalink
Merge branch 'main' into which_grepl
Browse files Browse the repository at this point in the history
  • Loading branch information
MichaelChirico committed Nov 17, 2023
2 parents 82aefa0 + 9140487 commit 58f1d0c
Show file tree
Hide file tree
Showing 28 changed files with 447 additions and 27 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,7 @@ Collate:
'pipe_call_linter.R'
'pipe_consistency_linter.R'
'pipe_continuation_linter.R'
'print_linter.R'
'quotes_linter.R'
'redundant_equals_linter.R'
'redundant_ifelse_linter.R'
Expand Down
1 change: 1 addition & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ export(paste_linter)
export(pipe_call_linter)
export(pipe_consistency_linter)
export(pipe_continuation_linter)
export(print_linter)
export(quotes_linter)
export(redundant_equals_linter)
export(redundant_ifelse_linter)
Expand Down
5 changes: 5 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,9 @@
# lintr (development version)

## Bug fixes

* `object_name_linter()` no longer errors when user-supplied `regexes=` have capture groups (#2188, @MichaelChirico).

## New and improved features

* More helpful errors for invalid configs (#2253, @MichaelChirico).
Expand All @@ -11,6 +15,7 @@
* `comparison_negation_linter()` for discouraging negated comparisons when a direct negation is preferable, e.g. `!(x == y)` could be `x != y` (part of #884, @MichaelChirico).
* `terminal_close_linter()` for discouraging using `close()` to end functions (part of #884, @MichaelChirico). Such usages are not robust to errors, where `close()` will not be run as intended. Put `close()` in an `on.exit()` hook, or use {withr} to manage connections with proper cleanup.
* `which_grepl_linter()` for discouraging `which(grepl(ptn, x))` in favor of directly using `grep(ptn, x)` (part of #884, @MichaelChirico).
* `print_linter()` for discouraging usage of `print()` on string literals like `print("Reached here")` or `print(paste("Found", nrow(DF), "rows."))` (#1894, @MichaelChirico).

### Lint accuracy fixes: removing false positives

Expand Down
28 changes: 28 additions & 0 deletions R/comparison_negation_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,34 @@
#' `!(x == y)` is more readably expressed as `x != y`. The same is true of
#' other negations of simple comparisons like `!(x > y)` and `!(x <= y)`.
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "!x == 2",
#' linters = comparison_negation_linter()
#' )
#'
#' lint(
#' text = "!(x > 2)",
#' linters = comparison_negation_linter()
#' )
#'
#' # okay
#' lint(
#' text = "!(x == 2 & y > 2)",
#' linters = comparison_negation_linter()
#' )
#'
#' lint(
#' text = "!(x & y)",
#' linters = comparison_negation_linter()
#' )
#'
#' lint(
#' text = "x != 2",
#' linters = comparison_negation_linter()
#' )
#'
#' @evalRd rd_tags("comparison_negation_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
Expand Down
16 changes: 1 addition & 15 deletions R/get_source_expressions.R
Original file line number Diff line number Diff line change
Expand Up @@ -68,8 +68,7 @@ get_source_expressions <- function(filename, lines = NULL) {
}

# Only regard explicit attribute terminal_newline=FALSE as FALSE and all other cases (e.g. NULL or TRUE) as TRUE.
# We don't use isFALSE since it is introduced in R 3.5.0.
terminal_newline <- !identical(attr(source_expression$lines, "terminal_newline", exact = TRUE), FALSE)
terminal_newline <- !isFALSE(attr(source_expression$lines, "terminal_newline", exact = TRUE))

e <- NULL
source_expression$lines <- extract_r_source(
Expand Down Expand Up @@ -493,19 +492,6 @@ get_source_expression <- function(source_expression, error = identity) {
error = error
)

# TODO: Remove when minimum R version is bumped to > 3.5
#
# This needs to be done twice to avoid a bug fixed in R 3.4.4
# https://bugs.r-project.org/bugzilla/show_bug.cgi?id=16041
parsed_content <- tryCatch(
parse(
text = source_expression$content,
srcfile = source_expression,
keep.source = TRUE
),
error = error
)

if (inherits(parsed_content, c("error", "lint"))) {
assign("e", parsed_content, envir = parent.frame())
parse_error <- TRUE
Expand Down
8 changes: 1 addition & 7 deletions R/namespace.R
Original file line number Diff line number Diff line change
Expand Up @@ -85,13 +85,7 @@ is_s3_generic <- function(fun) {

.base_s3_generics <- unique(c(
names(.knownS3Generics),
if (getRversion() >= "3.5.0") {
.S3_methods_table[, 1L]
} else {
# R < 3.5.0 doesn't provide .S3_methods_table
# fallback: search baseenv() for generic methods
imported_s3_generics(data.frame(pkg = "base", fun = ls(baseenv()), stringsAsFactors = FALSE))$fun
},
.S3_methods_table[, 1L],
# Contains S3 generic groups, see ?base::groupGeneric and src/library/base/R/zzz.R
ls(.GenericArgsEnv)
))
13 changes: 13 additions & 0 deletions R/nonportable_path_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,19 @@
#'
#' Check that [file.path()] is used to construct safe and portable paths.
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "'abcdefg/hijklmnop/qrst/uv/wxyz'",
#' linters = nonportable_path_linter()
#' )
#'
#' # okay
#' lint(
#' text = "file.path('abcdefg', 'hijklmnop', 'qrst', 'uv', 'wxyz')",
#' linters = nonportable_path_linter()
#' )
#'
#' @inheritParams absolute_path_linter
#' @evalRd rd_tags("nonportable_path_linter")
#' @seealso
Expand Down
9 changes: 7 additions & 2 deletions R/object_name_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -152,8 +152,13 @@ object_name_linter <- function(styles = c("snake_case", "symbols"), regexes = ch
check_style <- function(nms, style, generics = character()) {
conforming <- re_matches(nms, style)

# mark empty names and NA names as conforming
conforming[!nzchar(nms) | is.na(conforming)] <- TRUE
# style has capture group(s)
if (is.data.frame(conforming)) {
# if any group is missing, all groups are missing, so just check the first column
conforming <- !is.na(conforming[[1L]])
}
# mark empty or NA names as conforming
conforming <- is.na(nms) | !nzchar(nms) | conforming

if (!all(conforming)) {
possible_s3 <- re_matches(
Expand Down
45 changes: 45 additions & 0 deletions R/print_linter.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
#' Block usage of print() for logging
#'
#' The default print method for character vectors is appropriate for interactively inspecting objects,
#' not for logging messages. Thus checked-in usage like `print(paste('Data has', nrow(DF), 'rows.'))`
#' is better served by using [cat()], e.g. `cat(sprintf('Data has %d rows.\n', nrow(DF)))` (noting that
#' using `cat()` entails supplying your own line returns, and that [glue::glue()] might be preferable
#' to [sprintf()] for constructing templated strings). Lastly, note that [message()] differs slightly
#' from `cat()` in that it prints to `stderr` by default, not `stdout`, but is still a good option
#' to consider for logging purposes.
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "print('a')",
#' linters = print_linter()
#' )
#'
#' lint(
#' text = "print(paste(x, 'y'))",
#' linters = print_linter()
#' )
#'
#' # okay
#' lint(
#' text = "print(x)",
#' linters = print_linter()
#' )
#'
#' @evalRd rd_tags("print_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
print_linter <- make_linter_from_xpath(
xpath = "
//SYMBOL_FUNCTION_CALL[text() = 'print']
/parent::expr
/parent::expr[expr[2][
STR_CONST
or expr/SYMBOL_FUNCTION_CALL[
text() = 'paste' or text() = 'paste0' or text() = 'sprintf'
]
]]
",
lint_message =
"Use cat() instead of print() logging messages. Use message() in cases calling for a signalled condition."
)
28 changes: 28 additions & 0 deletions R/sample_int_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,34 @@
#' [sample.int()] is preferable to `sample()` for the case of sampling numbers
#' between 1 and `n`. `sample` calls `sample.int()` "under the hood".
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "sample(1:10, 2)",
#' linters = sample_int_linter()
#' )
#'
#' lint(
#' text = "sample(seq(4), 2)",
#' linters = sample_int_linter()
#' )
#'
#' lint(
#' text = "sample(seq_len(8), 2)",
#' linters = sample_int_linter()
#' )
#'
#' # okay
#' lint(
#' text = "sample(seq(1, 5, by = 2), 2)",
#' linters = sample_int_linter()
#' )
#'
#' lint(
#' text = "sample(letters, 2)",
#' linters = sample_int_linter()
#' )
#'
#' @evalRd rd_tags("sample_int_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
Expand Down
18 changes: 18 additions & 0 deletions R/scalar_in_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,24 @@
#' `scalar %in% vector` is OK, because the alternative (`any(vector == scalar)`)
#' is more circuitous & potentially less clear.
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "x %in% 1L",
#' linters = scalar_in_linter()
#' )
#'
#' lint(
#' text = "x %chin% 'a'",
#' linters = scalar_in_linter()
#' )
#'
#' # okay
#' lint(
#' text = "x %in% 1:10",
#' linters = scalar_in_linter()
#' )
#'
#' @evalRd rd_tags("scalar_in_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
Expand Down
23 changes: 23 additions & 0 deletions R/stopifnot_all_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,29 @@
#' `stopifnot(A)` actually checks `all(A)` "under the hood" if `A` is a vector,
#' and produces a better error message than `stopifnot(all(A))` does.
#'
#' @examples
#' # will produce lints
#' lint(
#' text = "stopifnot(all(x > 0))",
#' linters = stopifnot_all_linter()
#' )
#'
#' lint(
#' text = "stopifnot(y > 3, all(x < 0))",
#' linters = stopifnot_all_linter()
#' )
#'
#' # okay
#' lint(
#' text = "stopifnot(is.null(x) || all(x > 0))",
#' linters = stopifnot_all_linter()
#' )
#'
#' lint(
#' text = "assert_that(all(x > 0))",
#' linters = stopifnot_all_linter()
#' )
#'
#' @evalRd rd_tags("stopifnot_all_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
Expand Down
31 changes: 31 additions & 0 deletions R/terminal_close_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,37 @@
#' Functions that end in `close(x)` are almost always better written by using
#' `on.exit(close(x))` close to where `x` is defined and/or opened.
#'
#' @examples
#' # will produce lints
#' code <- paste(
#' "f <- function(fl) {",
#' " conn <- file(fl, open = 'r')",
#' " readLines(conn)",
#' " close(conn)",
#' "}",
#' sep = "\n"
#' )
#' writeLines(code)
#' lint(
#' text = code,
#' linters = terminal_close_linter()
#' )
#'
#' # okay
#' code <- paste(
#' "f <- function(fl) {",
#' " conn <- file(fl, open = 'r')",
#' " on.exit(close(conn))",
#' " readLines(conn)",
#' "}",
#' sep = "\n"
#' )
#' writeLines(code)
#' lint(
#' text = code,
#' linters = terminal_close_linter()
#' )
#'
#' @evalRd rd_tags("terminal_close_linter")
#' @seealso [linters] for a complete list of linters available in lintr.
#' @export
Expand Down
1 change: 1 addition & 0 deletions inst/lintr/linters.csv
Original file line number Diff line number Diff line change
Expand Up @@ -70,6 +70,7 @@ paste_linter,best_practices consistency configurable
pipe_call_linter,style readability
pipe_consistency_linter,style readability configurable
pipe_continuation_linter,style readability default
print_linter,best_practices consistency
quotes_linter,style consistency readability default configurable
redundant_equals_linter,best_practices readability efficiency common_mistakes
redundant_ifelse_linter,best_practices efficiency consistency configurable
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.

29 changes: 29 additions & 0 deletions man/comparison_negation_linter.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/consistency_linters.Rd

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

Loading

0 comments on commit 58f1d0c

Please sign in to comment.