Skip to content

Commit 2438526

Browse files
Merge branch 'main' into sprintf-bug
2 parents dd88ff2 + 8ac582c commit 2438526

File tree

6 files changed

+46
-17
lines changed

6 files changed

+46
-17
lines changed

NAMESPACE

+3
Original file line numberDiff line numberDiff line change
@@ -161,10 +161,13 @@ importFrom(rex,rex)
161161
importFrom(stats,na.omit)
162162
importFrom(utils,capture.output)
163163
importFrom(utils,getParseData)
164+
importFrom(utils,getTxtProgressBar)
164165
importFrom(utils,globalVariables)
165166
importFrom(utils,head)
166167
importFrom(utils,relist)
168+
importFrom(utils,setTxtProgressBar)
167169
importFrom(utils,tail)
170+
importFrom(utils,txtProgressBar)
168171
importFrom(xml2,as_list)
169172
importFrom(xml2,xml_attr)
170173
importFrom(xml2,xml_find_all)

NEWS.md

+1
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@
1313
* New exclusion sentinel `# nolint next` to signify the next line should skip linting (#1791, @MichaelChirico). The usual rules apply for excluding specific linters, e.g. `# nolint next: assignment_linter.`. The exact string used to match a subsequent-line exclusion is controlled by the `exclude_next` config entry or R option `"lintr.exclude_next"`.
1414
* New `xp_call_name()` helper to facilitate writing custom linters (#2023, @MichaelChirico). This helper converts a matched XPath to the R function to which it corresponds. This is useful for including the "offending" function in the lint's message.
1515
* New `make_linter_from_xpath()` to facilitate making simple linters directly from a single XPath (#2064, @MichaelChirico). This is especially helpful for making on-the-fly/exploratory linters, but also extends to any case where the linter can be fully defined from a static lint message and single XPath.
16+
* Toggle lint progress indicators with argument `show_progress` to `lint_dir()` and `lint_package()` (#972, @MichaelChirico). The default is still to show progress in `interactive()` sessions. Progress is also now shown with a "proper" progress bar (`utils::txtProgressBar()`), which in particular solves the issue of progress `.` spilling well past the width of the screen in large directories.
1617
* `fixed_regex_linter()`
1718
+ Is pipe-aware, in particular removing false positives arong piping into {stringr} functions like `x |> str_replace(fixed("a"), "b")` (#1811, @MichaelChirico).
1819
+ Gains an option `allow_unescaped` (default `FALSE`) to toggle linting regexes not requiring any escapes or character classes (#1689, @MichaelChirico). Thus `fixed_regex_linter(allow_unescaped = TRUE)` would lint on `grepl("[$]", x)` but not on `grepl("a", x)` since the latter does not use any regex special characters.

R/lint.R

+26-14
Original file line numberDiff line numberDiff line change
@@ -106,6 +106,9 @@ lint <- function(filename, linters = NULL, ..., cache = FALSE, parse_settings =
106106
#' @param exclusions exclusions for [exclude()], relative to the package path.
107107
#' @param pattern pattern for files, by default it will take files with any of the extensions
108108
#' .R, .Rmd, .qmd, .Rnw, .Rhtml, .Rrst, .Rtex, .Rtxt allowing for lowercase r (.r, ...).
109+
#' @param show_progress Logical controlling whether to show linting progress with a simple text
110+
#' progress bar _via_ [utils::txtProgressBar()]. The default behavior is to show progress in
111+
#' [interactive()] sessions not running a testthat suite.
109112
#'
110113
#' @examples
111114
#' if (FALSE) {
@@ -126,7 +129,8 @@ lint_dir <- function(path = ".", ...,
126129
relative_path = TRUE,
127130
exclusions = list("renv", "packrat"),
128131
pattern = rex(".", one_of("Rr"), or("", "html", "md", "nw", "rst", "tex", "txt"), end),
129-
parse_settings = TRUE) {
132+
parse_settings = TRUE,
133+
show_progress = NULL) {
130134
if (has_positional_logical(list(...))) {
131135
stop(
132136
"'relative_path' is no longer available as a positional argument; ",
@@ -141,6 +145,8 @@ lint_dir <- function(path = ".", ...,
141145
exclusions <- c(exclusions, settings$exclusions)
142146
}
143147

148+
if (is.null(show_progress)) show_progress <- interactive() && !identical(Sys.getenv("TESTTHAT"), "true")
149+
144150
exclusions <- normalize_exclusions(
145151
exclusions,
146152
root = path,
@@ -159,15 +165,19 @@ lint_dir <- function(path = ".", ...,
159165
# Remove fully ignored files to avoid reading & parsing
160166
files <- drop_excluded(files, exclusions)
161167

168+
pb <- if (isTRUE(show_progress)) {
169+
txtProgressBar(max = length(files), style = 3L)
170+
}
171+
162172
lints <- flatten_lints(lapply(
163173
files,
164174
function(file) {
165-
maybe_report_progress()
175+
maybe_report_progress(pb)
166176
lint(file, ..., parse_settings = FALSE, exclusions = exclusions)
167177
}
168178
))
169179

170-
maybe_report_progress(done = TRUE)
180+
if (!is.null(pb)) close(pb)
171181

172182
lints <- reorder_lints(lints)
173183

@@ -211,7 +221,8 @@ drop_excluded <- function(files, exclusions) {
211221
lint_package <- function(path = ".", ...,
212222
relative_path = TRUE,
213223
exclusions = list("R/RcppExports.R"),
214-
parse_settings = TRUE) {
224+
parse_settings = TRUE,
225+
show_progress = NULL) {
215226
if (has_positional_logical(list(...))) {
216227
# nocov start: dead code path
217228
stop(
@@ -242,7 +253,13 @@ lint_package <- function(path = ".", ...,
242253
)
243254

244255
r_directories <- file.path(pkg_path, c("R", "tests", "inst", "vignettes", "data-raw", "demo", "exec"))
245-
lints <- lint_dir(r_directories, relative_path = FALSE, exclusions = exclusions, parse_settings = FALSE, ...)
256+
lints <- lint_dir(r_directories,
257+
relative_path = FALSE,
258+
exclusions = exclusions,
259+
parse_settings = FALSE,
260+
show_progress = show_progress,
261+
...
262+
)
246263

247264
if (isTRUE(relative_path)) {
248265
path <- normalizePath(pkg_path, mustWork = FALSE)
@@ -711,16 +728,11 @@ has_positional_logical <- function(dots) {
711728
!nzchar(names2(dots)[1L])
712729
}
713730

714-
maybe_report_progress <- function(done = FALSE) {
715-
if (interactive() && !identical(Sys.getenv("TESTTHAT"), "true")) {
716-
# nocov start
717-
if (done) {
718-
message()
719-
} else {
720-
message(".", appendLF = FALSE)
721-
}
722-
# nocov end
731+
maybe_report_progress <- function(pb) {
732+
if (is.null(pb)) {
733+
return(invisible())
723734
}
735+
setTxtProgressBar(pb, getTxtProgressBar(pb) + 1L)
724736
}
725737

726738
maybe_append_error_lint <- function(lints, error, lint_cache, filename) {

R/lintr-package.R

+2-1
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,8 @@
1212
#' @importFrom glue glue glue_collapse
1313
#' @importFrom rex rex regex re_matches re_substitutes character_class
1414
#' @importFrom stats na.omit
15-
#' @importFrom utils capture.output getParseData globalVariables head relist tail
15+
#' @importFrom utils capture.output getParseData getTxtProgressBar globalVariables head relist
16+
#' setTxtProgressBar tail txtProgressBar
1617
#' @importFrom xml2 as_list
1718
#' xml_attr xml_find_all xml_find_chr xml_find_lgl xml_find_num xml_find_first xml_name xml_text
1819
#' @rawNamespace

man/lint.Rd

+8-2
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

tests/testthat/test-dir_linters.R

+6
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,12 @@ test_that("lint all files in a directory", {
1010

1111
expect_s3_class(lints, "lints")
1212
expect_identical(sort(linted_files), sort(files))
13+
14+
expect_output(
15+
lint_dir(the_dir, parse_settings = FALSE, show_progress = TRUE),
16+
"======",
17+
fixed = TRUE
18+
)
1319
})
1420

1521
test_that("lint all relevant directories in a package", {

0 commit comments

Comments
 (0)