Skip to content
Merged
Show file tree
Hide file tree
Changes from 22 commits
Commits
Show all changes
23 commits
Select commit Hold shift + click to select a range
f29437a
squashed commit for excluding entire directories
AshesITR Oct 21, 2020
3d9cd7f
fix lintr::lint_package("lintr") failure due to test file with delibe…
AshesITR Oct 27, 2020
dbe6e61
Merge branch 'master' into feature/ignore-dirs
AshesITR Oct 30, 2020
abc4076
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 1, 2020
a2f13a2
update NEWS and documentation
AshesITR Nov 1, 2020
6c02397
Merge remote-tracking branch 'upstream/master' into feature/ignore-dirs
AshesITR Nov 1, 2020
2a2f11e
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 2, 2020
77317c1
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 5, 2020
34c6580
move LANGUAGE = "en" to expect_lint()
AshesITR Nov 6, 2020
5ecacb9
add internal documentation for normalize_exclusions()
AshesITR Nov 6, 2020
6bc76a9
clarify purpose of delayed read_settings() calls in cache.R
AshesITR Nov 6, 2020
fa40340
steal tests from lintr#439
AshesITR Nov 6, 2020
b65e6fa
add test for lint_dir(relative_path = FALSE)
AshesITR Nov 6, 2020
361355b
fix typo
AshesITR Nov 6, 2020
3a6262b
fix R CMD check warnings (document(), wrong \link syntax, Suggest withr)
AshesITR Nov 6, 2020
444a1ca
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 12, 2020
b2a4125
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 12, 2020
3f3442e
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 18, 2020
4257484
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 23, 2020
c7af1ec
move tests/testthat/package to tests/testthat/dummy_packages
AshesITR Nov 23, 2020
9f536d7
document()
AshesITR Nov 23, 2020
4fae382
Merge branch 'master' into feature/ignore-dirs
AshesITR Nov 24, 2020
babe9f7
apply last changes, document(), test(), fix roxygen tag for normalize…
AshesITR Nov 25, 2020
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
8 changes: 7 additions & 1 deletion .lintr
Original file line number Diff line number Diff line change
@@ -1,2 +1,8 @@
linters: with_defaults(line_length_linter(120))
exclusions: list("inst/doc/creating_linters.R" = 1, "inst/example/bad.R", "tests/testthat/exclusions-test")
exclusions: list(
"inst/doc/creating_linters.R" = 1,
"inst/example/bad.R",
"tests/testthat/dummy_packages",
"tests/testthat/exclusions-test",
"tests/testthat/knitr_malformed/incomplete_r_block.Rmd"
)
3 changes: 2 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,8 @@ Imports:
xmlparsedata (>= 1.0.3)
Suggests:
rmarkdown,
mockery
mockery,
withr
License: MIT + file LICENSE
LazyData: true
Encoding: UTF-8
Expand Down
2 changes: 2 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,8 @@
* Fix handling zero-length variable name error (#566, #567, @renkun-ken)
* New `missing_argument_linter()` (#563, #565, @renkun-ken)
* New `sprintf_linter()` (#544, #578, @renkun-ken)
* exclusions are now always relative to the location of the `.lintr` file and they support excluding entire directories
by specifying a directory instead of a file (#158, #438, @AshesITR)

# lintr 2.0.1

Expand Down
15 changes: 9 additions & 6 deletions R/cache.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,9 +7,10 @@
#' @return 0 for success, 1 for failure, invisibly.
#' @export
clear_cache <- function(file = NULL, path = NULL) {
read_settings(file)

if (is.null(path)) {
# Only retrieve settings if `path` isn't specified.
# Otherwise, other settings may inadvertently be loaded, such as exclusions.
read_settings(file)
path <- settings$cache_directory
}

Expand All @@ -27,9 +28,10 @@ get_cache_file_path <- function(file, path) {
}

load_cache <- function(file, path = NULL) {
read_settings(file)

if (is.null(path)) {
# Only retrieve settings if `path` isn't specified.
# Otherwise, other settings may inadvertently be loaded, such as exclusions.
read_settings(file)
path <- settings$cache_directory
}

Expand All @@ -44,9 +46,10 @@ load_cache <- function(file, path = NULL) {
}

save_cache <- function(cache, file, path = NULL) {
read_settings(file)

if (is.null(path)) {
# Only retrieve settings if `path` isn't specified.
# Otherwise, other settings may inadvertently be loaded, such as exclusions.
read_settings(file)
path <- settings$cache_directory
}

Expand Down
60 changes: 57 additions & 3 deletions R/exclude.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,8 @@
#' \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
#' if you want to exclude the entire file.}
#' if you want to exclude the entire file, or the directory names if you want to exclude all files
#' in a directory.}
#' }
exclude <- function(lints, exclusions = settings$exclusions, ...) {
if (length(lints) <= 0) {
Expand Down Expand Up @@ -71,7 +72,26 @@ parse_exclusions <- function(file, exclude = settings$exclude,
sort(unique(c(exclusions, which(rex::re_matches(lines, exclude)))))
}

normalize_exclusions <- function(x, normalize_path=TRUE) {
#' Normalize lint exclusions
#'
#' @param x Exclusion specification
#' - A character vector of filenames or directories relative to \code{root}
#' - A named list of integers specifying lines to be excluded per file
#' @param normalize_path Should the names of the returned exclusion list be normalized paths?
#' If no, they will be relative to \code{root}.
#' @param root Base directory for relative filename resolution.
#' @param pattern If non-NULL, only exclude files in excluded directories if they match
#' \code{pattern}. Passed to \link[base]{list.files} if a directory is excluded.
#'
#' @value A named list of line numbers to exclude, or the sentinel \code{Inf} for completely
#' excluded files. The names of the list specify the filenames to be excluded.
#' If \code{normalize_path} is \code{TRUE}, they will be normalized relative to \code{root}.
#' Otherwise the paths are left as provided (relative to \code{root} or absolute).
#'
#' @keywords internal
normalize_exclusions <- function(x, normalize_path = TRUE,
root = getwd(),
pattern = NULL) {
if (is.null(x) || length(x) <= 0) {
return(list())
}
Expand Down Expand Up @@ -101,8 +121,42 @@ normalize_exclusions <- function(x, normalize_path=TRUE) {
}
}

paths <- names(x)
rel_path <- !is_absolute_path(paths)
paths[rel_path] <- file.path(root, paths[rel_path])

is_dir <- dir.exists(paths)
if (any(is_dir)) {
dirs <- names(x)[is_dir]
x <- x[!is_dir]
all_file_names <- unlist(lapply(
dirs,
function(dir) {
dir_path <- if (is_absolute_path(dir)) dir else file.path(root, dir)
files <- list.files(
path = dir_path,
pattern = pattern,
recursive = TRUE
)
file.path(dir, files) # non-normalized relative paths
}
))

# Only exclude file if there is no more specific exclusion already
all_file_names <- setdiff(all_file_names, names(x))

dir_exclusions <- as.list(rep_len(Inf, length(all_file_names)))
names(dir_exclusions) <- all_file_names
x <- c(x, dir_exclusions)
}

if (normalize_path) {
x <- x[file.exists(names(x))] # remove exclusions for non-existing files
paths <- names(x)
# specify relative paths w.r.t. root
rel_path <- !is_absolute_path(paths)
paths[rel_path] <- file.path(root, paths[rel_path])
names(x) <- paths
x <- x[file.exists(paths)] # remove exclusions for non-existing files
names(x) <- normalizePath(names(x)) # get full path for remaining files
}

Expand Down
9 changes: 8 additions & 1 deletion R/expect_lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,9 @@
#' is not recommended for new code.
#' @param ... arguments passed to \code{\link{lint}}, e.g. the linters or cache to use.
#' @param file if not \code{NULL}, read content from the specified file rather than from \code{content}.
#' @param language temporarily override Rs \code{LANGUAGE} envvar, controlling localisation of base
#' R error messages. This makes testing them reproducible on all systems irrespective of their
#' native R language setting.
#' @return \code{NULL}, invisibly.
#' @examples
#' # no expected lint
Expand All @@ -35,7 +38,11 @@
#' list(list(message="superfluous", line_number=2), list(message="superfluous", line_number=3)),
#' trailing_blank_lines_linter)
#' @export
expect_lint <- function(content, checks, ..., file = NULL) {
expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
oldlang <- Sys.getenv("LANGUAGE")
Sys.setenv(LANGUAGE = language)
on.exit(Sys.setenv(LANGUAGE = oldlang))

if (is.null(file)) {
file <- tempfile()
on.exit(unlink(file))
Expand Down
32 changes: 24 additions & 8 deletions R/lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -149,7 +149,7 @@ reorder_lints <- function(lints) {
#' lint_dir(
#' linters = list(semicolon_terminator_linter())
#' cache = TRUE,
#' exclusions = list("inst/doc/creating_linters.R" = 1, "inst/example/bad.R")
#' exclusions = list("inst/doc/creating_linters.R" = 1, "inst/example/bad.R", "renv")
#' )
#' }
#' @export
Expand All @@ -164,13 +164,23 @@ lint_dir <- function(path = ".", relative_path = TRUE, ..., exclusions = NULL,
if (isTRUE(parse_settings)) {
read_settings(path)
on.exit(clear_settings, add = TRUE)

exclusions <- c(exclusions, settings$exclusions)
}

files <- dir(path,
exclusions <- normalize_exclusions(
exclusions,
root = path,
pattern = pattern
)

# normalizePath ensures names(exclusions) and files have the same names for the same files.
# Otherwise on windows, files might incorrectly not be excluded in to_exclude
files <- normalizePath(dir(path,
pattern = pattern,
recursive = TRUE,
full.names = TRUE
)
))

# Remove fully ignored files to avoid reading & parsing
to_exclude <- vapply(
Expand Down Expand Up @@ -231,17 +241,23 @@ lint_dir <- function(path = ".", relative_path = TRUE, ..., exclusions = NULL,
#' lint_package(
#' linters = with_defaults(semicolon_linter = semicolon_terminator_linter())
#' cache = TRUE,
#' exclusions = list("inst/doc/creating_linters.R" = 1, "inst/example/bad.R")
#' exclusions = list("inst/doc/creating_linters.R" = 1, "inst/example/bad.R", "data")
#' )
#' }
#' @export
lint_package <- function(path = ".", relative_path = TRUE, ..., exclusions = list("R/RcppExports.R")) {
lint_package <- function(path = ".", relative_path = TRUE, ..., exclusions = list("R/RcppExports.R"), parse_settings = TRUE) {
path <- find_package(path)

read_settings(path)
on.exit(clear_settings, add = TRUE)
if (parse_settings) {
read_settings(path)
on.exit(clear_settings, add = TRUE)
}

exclusions <- normalize_exclusions(c(exclusions, settings$exclusions), FALSE)
exclusions <- normalize_exclusions(
c(exclusions, settings$exclusions),
root = path,
pattern = pattern
)

lints <- lint_dir(file.path(path, c("R", "tests", "inst", "vignettes", "data-raw")),
relative_path = FALSE, exclusions = exclusions, parse_settings = FALSE, ...)
Expand Down
7 changes: 6 additions & 1 deletion R/settings.R
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,12 @@ read_settings <- function(filename) {
for (setting in names(default_settings)) {
value <- get_setting(setting, config, default_settings)
if (setting == "exclusions") {
value <- normalize_exclusions(value)
if (!is.null(config_file)) {
root <- dirname(config_file)
} else {
root <- getwd()
}
value <- normalize_exclusions(value, root = root)
}

settings[[setting]] <- value
Expand Down
3 changes: 2 additions & 1 deletion man/exclude.Rd

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

6 changes: 5 additions & 1 deletion man/expect_lint.Rd

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

2 changes: 1 addition & 1 deletion man/lint_dir.Rd

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

7 changes: 5 additions & 2 deletions man/lint_package.Rd

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

25 changes: 25 additions & 0 deletions man/normalize_exclusions.Rd

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

9 changes: 9 additions & 0 deletions tests/testthat/dummy_packages/assignmentLinter/DESCRIPTION
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
Package: assignmentLinter
Type: Package
Title: What the package does (short line)
Version: 1.0
Date: 2019-12-17
Author: Who wrote it
Maintainer: Who to complain to <[email protected]>
Description: More about what it does (maybe more than one line)
License: What license is it under?
1 change: 1 addition & 0 deletions tests/testthat/dummy_packages/assignmentLinter/NAMESPACE
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
exportPattern("^[[:alpha:]]+")
2 changes: 2 additions & 0 deletions tests/testthat/dummy_packages/assignmentLinter/R/abc.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
abc = 123
ghi <- 456
2 changes: 2 additions & 0 deletions tests/testthat/dummy_packages/assignmentLinter/R/jkl.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
jkl = 456
mno = 789
Loading