diff --git a/DESCRIPTION b/DESCRIPTION index cdc3845c6..41f62c080 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -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' diff --git a/NAMESPACE b/NAMESPACE index 6d4724628..045ef8c43 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -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) diff --git a/NEWS.md b/NEWS.md index 117e23bd0..bd822eb18 100644 --- a/NEWS.md +++ b/NEWS.md @@ -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). @@ -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 diff --git a/R/comparison_negation_linter.R b/R/comparison_negation_linter.R index 7ac88e9c0..0c13422a2 100644 --- a/R/comparison_negation_linter.R +++ b/R/comparison_negation_linter.R @@ -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 diff --git a/R/get_source_expressions.R b/R/get_source_expressions.R index 5ebcf3c47..42cfb80e7 100644 --- a/R/get_source_expressions.R +++ b/R/get_source_expressions.R @@ -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( @@ -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 diff --git a/R/namespace.R b/R/namespace.R index 68379381f..a3fba3146 100644 --- a/R/namespace.R +++ b/R/namespace.R @@ -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) )) diff --git a/R/nonportable_path_linter.R b/R/nonportable_path_linter.R index ccd9c5632..aaf59b9ea 100644 --- a/R/nonportable_path_linter.R +++ b/R/nonportable_path_linter.R @@ -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 diff --git a/R/object_name_linter.R b/R/object_name_linter.R index 532947858..aaa79a9c3 100644 --- a/R/object_name_linter.R +++ b/R/object_name_linter.R @@ -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( diff --git a/R/print_linter.R b/R/print_linter.R new file mode 100644 index 000000000..72b90d66a --- /dev/null +++ b/R/print_linter.R @@ -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." +) diff --git a/R/sample_int_linter.R b/R/sample_int_linter.R index a9da00f6f..676077b55 100644 --- a/R/sample_int_linter.R +++ b/R/sample_int_linter.R @@ -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 diff --git a/R/scalar_in_linter.R b/R/scalar_in_linter.R index 89bd77f6f..078dad16b 100644 --- a/R/scalar_in_linter.R +++ b/R/scalar_in_linter.R @@ -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 diff --git a/R/stopifnot_all_linter.R b/R/stopifnot_all_linter.R index 307427061..f081cc0c0 100644 --- a/R/stopifnot_all_linter.R +++ b/R/stopifnot_all_linter.R @@ -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 diff --git a/R/terminal_close_linter.R b/R/terminal_close_linter.R index f860a3429..4b8a3ede3 100644 --- a/R/terminal_close_linter.R +++ b/R/terminal_close_linter.R @@ -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 diff --git a/inst/lintr/linters.csv b/inst/lintr/linters.csv index 1394150c3..910236d91 100644 --- a/inst/lintr/linters.csv +++ b/inst/lintr/linters.csv @@ -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 diff --git a/man/best_practices_linters.Rd b/man/best_practices_linters.Rd index 9baf4f3bc..4e8cc2ead 100644 --- a/man/best_practices_linters.Rd +++ b/man/best_practices_linters.Rd @@ -47,6 +47,7 @@ The following linters are tagged with 'best_practices': \item{\code{\link{nonportable_path_linter}}} \item{\code{\link{outer_negation_linter}}} \item{\code{\link{paste_linter}}} +\item{\code{\link{print_linter}}} \item{\code{\link{redundant_equals_linter}}} \item{\code{\link{redundant_ifelse_linter}}} \item{\code{\link{regex_subset_linter}}} diff --git a/man/comparison_negation_linter.Rd b/man/comparison_negation_linter.Rd index 10212fe0b..d1139f480 100644 --- a/man/comparison_negation_linter.Rd +++ b/man/comparison_negation_linter.Rd @@ -9,6 +9,35 @@ comparison_negation_linter() \description{ \code{!(x == y)} is more readably expressed as \code{x != y}. The same is true of other negations of simple comparisons like \code{!(x > y)} and \code{!(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() +) + } \seealso{ \link{linters} for a complete list of linters available in lintr. diff --git a/man/consistency_linters.Rd b/man/consistency_linters.Rd index 63bc6b98d..6eb6afb07 100644 --- a/man/consistency_linters.Rd +++ b/man/consistency_linters.Rd @@ -29,6 +29,7 @@ The following linters are tagged with 'consistency': \item{\code{\link{numeric_leading_zero_linter}}} \item{\code{\link{object_name_linter}}} \item{\code{\link{paste_linter}}} +\item{\code{\link{print_linter}}} \item{\code{\link{quotes_linter}}} \item{\code{\link{redundant_ifelse_linter}}} \item{\code{\link{scalar_in_linter}}} diff --git a/man/linters.Rd b/man/linters.Rd index 93d2c33f0..5cf54c87a 100644 --- a/man/linters.Rd +++ b/man/linters.Rd @@ -17,7 +17,7 @@ see also \code{\link[=available_tags]{available_tags()}}. \section{Tags}{ The following tags exist: \itemize{ -\item{\link[=best_practices_linters]{best_practices} (55 linters)} +\item{\link[=best_practices_linters]{best_practices} (56 linters)} \item{\link[=common_mistakes_linters]{common_mistakes} (8 linters)} \item{\link[=configurable_linters]{configurable} (34 linters)} \item{\link[=consistency_linters]{consistency} (24 linters)} @@ -103,6 +103,7 @@ The following linters exist: \item{\code{\link{pipe_call_linter}} (tags: readability, style)} \item{\code{\link{pipe_consistency_linter}} (tags: configurable, readability, style)} \item{\code{\link{pipe_continuation_linter}} (tags: default, readability, style)} +\item{\code{\link{print_linter}} (tags: best_practices, consistency)} \item{\code{\link{quotes_linter}} (tags: configurable, consistency, default, readability, style)} \item{\code{\link{redundant_equals_linter}} (tags: best_practices, common_mistakes, efficiency, readability)} \item{\code{\link{redundant_ifelse_linter}} (tags: best_practices, configurable, consistency, efficiency)} diff --git a/man/nonportable_path_linter.Rd b/man/nonportable_path_linter.Rd index 62b6024df..4b9d2cb53 100644 --- a/man/nonportable_path_linter.Rd +++ b/man/nonportable_path_linter.Rd @@ -16,6 +16,20 @@ If \code{TRUE}, only lint path strings, which } \description{ Check that \code{\link[=file.path]{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() +) + } \seealso{ \itemize{ diff --git a/man/print_linter.Rd b/man/print_linter.Rd new file mode 100644 index 000000000..eecf19001 --- /dev/null +++ b/man/print_linter.Rd @@ -0,0 +1,42 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/print_linter.R +\name{print_linter} +\alias{print_linter} +\title{Block usage of print() for logging} +\usage{ +print_linter() +} +\description{ +The default print method for character vectors is appropriate for interactively inspecting objects, +not for logging messages. Thus checked-in usage like \code{print(paste('Data has', nrow(DF), 'rows.'))} +is better served by using \code{\link[=cat]{cat()}}, e.g. \code{cat(sprintf('Data has \%d rows.\\n', nrow(DF)))} (noting that +using \code{cat()} entails supplying your own line returns, and that \code{\link[glue:glue]{glue::glue()}} might be preferable +to \code{\link[=sprintf]{sprintf()}} for constructing templated strings). Lastly, note that \code{\link[=message]{message()}} differs slightly +from \code{cat()} in that it prints to \code{stderr} by default, not \code{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() +) + +} +\seealso{ +\link{linters} for a complete list of linters available in lintr. +} +\section{Tags}{ +\link[=best_practices_linters]{best_practices}, \link[=consistency_linters]{consistency} +} diff --git a/man/sample_int_linter.Rd b/man/sample_int_linter.Rd index ed4c7a7fc..c2d46a64d 100644 --- a/man/sample_int_linter.Rd +++ b/man/sample_int_linter.Rd @@ -9,6 +9,35 @@ sample_int_linter() \description{ \code{\link[=sample.int]{sample.int()}} is preferable to \code{sample()} for the case of sampling numbers between 1 and \code{n}. \code{sample} calls \code{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() +) + } \seealso{ \link{linters} for a complete list of linters available in lintr. diff --git a/man/scalar_in_linter.Rd b/man/scalar_in_linter.Rd index a51ea443b..be94fd1a1 100644 --- a/man/scalar_in_linter.Rd +++ b/man/scalar_in_linter.Rd @@ -14,6 +14,25 @@ is matched as well. \details{ \code{scalar \%in\% vector} is OK, because the alternative (\code{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() +) + } \seealso{ \link{linters} for a complete list of linters available in lintr. diff --git a/man/stopifnot_all_linter.Rd b/man/stopifnot_all_linter.Rd index 17e9d8c49..9ee04d550 100644 --- a/man/stopifnot_all_linter.Rd +++ b/man/stopifnot_all_linter.Rd @@ -9,6 +9,30 @@ stopifnot_all_linter() \description{ \code{stopifnot(A)} actually checks \code{all(A)} "under the hood" if \code{A} is a vector, and produces a better error message than \code{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() +) + } \seealso{ \link{linters} for a complete list of linters available in lintr. diff --git a/man/terminal_close_linter.Rd b/man/terminal_close_linter.Rd index 207518708..3bb39c833 100644 --- a/man/terminal_close_linter.Rd +++ b/man/terminal_close_linter.Rd @@ -9,6 +9,38 @@ terminal_close_linter() \description{ Functions that end in \code{close(x)} are almost always better written by using \code{on.exit(close(x))} close to where \code{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() +) + } \seealso{ \link{linters} for a complete list of linters available in lintr. diff --git a/tests/testthat/test-lintr-package.R b/tests/testthat/test-lintr-package.R new file mode 100644 index 000000000..e7be3c484 --- /dev/null +++ b/tests/testthat/test-lintr-package.R @@ -0,0 +1,9 @@ +test_that("All linter help files have examples", { + help_db <- tools::Rd_db("lintr") + linter_db <- help_db[endsWith(names(help_db), "_linter.Rd")] + rd_has_examples <- function(rd) any(vapply(rd, attr, "Rd_tag", FUN.VALUE = character(1L)) == "\\examples") + linter_has_examples <- vapply(linter_db, rd_has_examples, logical(1L)) + for (ii in seq_along(linter_has_examples)) { + expect_true(linter_has_examples[ii], label = paste("Linter", names(linter_db)[ii], "has examples")) + } +}) diff --git a/tests/testthat/test-object_name_linter.R b/tests/testthat/test-object_name_linter.R index 4a5925198..7a0154561 100644 --- a/tests/testthat/test-object_name_linter.R +++ b/tests/testthat/test-object_name_linter.R @@ -273,3 +273,8 @@ test_that("function shorthand also lints", { expect_lint("aBc <- \\() NULL", "function name style", object_name_linter()) }) + +test_that("capture groups in style are fine", { + expect_lint("a <- 1\nab <- 2", NULL, object_name_linter(regexes = c(capture = "^(a)"))) + expect_lint("ab <- 1\nabc <- 2", NULL, object_name_linter(regexes = c(capture = "^(a)(b)"))) +}) diff --git a/tests/testthat/test-print_linter.R b/tests/testthat/test-print_linter.R new file mode 100644 index 000000000..b39f90869 --- /dev/null +++ b/tests/testthat/test-print_linter.R @@ -0,0 +1,35 @@ +test_that("print_linter skips allowed usages", { + linter <- print_linter() + + expect_lint("print(x)", NULL, linter) + expect_lint("print(foo(x))", NULL, linter) +}) + +test_that("print_linter blocks disallowed usages", { + linter <- print_linter() + lint_msg <- + rex::rex("Use cat() instead of print() logging messages. Use message() in cases calling for a signalled condition.") + + expect_lint('print("hi")', lint_msg, linter) + + # basic known-character functions + expect_lint('print(paste(x, "b", y))', lint_msg, linter) + expect_lint('print(paste0(x, "c", y))', lint_msg, linter) + expect_lint('print(sprintf("a %s", x))', lint_msg, linter) + + # vectorization, metadata + expect_lint( + trim_some("{ + print('a') + print(paste('x', y)) + print(z) + print(sprintf('%s', b)) + }"), + list( + list(lint_msg, line_number = 2L, column_number = 3L), + list(lint_msg, line_number = 3L, column_number = 3L), + list(lint_msg, line_number = 5L, column_number = 3L) + ), + linter + ) +}) diff --git a/tests/testthat/test-unreachable_code_linter.R b/tests/testthat/test-unreachable_code_linter.R index b1f434968..dfd57dffc 100644 --- a/tests/testthat/test-unreachable_code_linter.R +++ b/tests/testthat/test-unreachable_code_linter.R @@ -394,10 +394,10 @@ test_that("unreachable_code_linter ignores terminal nolint end comments", { trim_some(" foo <- function() { do_something - # nolint start: one_linter. + # TestNoLintStart: one_linter. a = 42 next - # nolint end + # TestNoLintEnd } "), NULL,