Skip to content

Commit a3c0535

Browse files
Merge 1347524 into 7d20334
2 parents 7d20334 + 1347524 commit a3c0535

12 files changed

+332
-5
lines changed

DESCRIPTION

+1
Original file line numberDiff line numberDiff line change
@@ -143,6 +143,7 @@ Collate:
143143
'nzchar_linter.R'
144144
'object_length_linter.R'
145145
'object_name_linter.R'
146+
'object_overwrite_linter.R'
146147
'object_usage_linter.R'
147148
'one_call_pipe_linter.R'
148149
'outer_negation_linter.R'

NAMESPACE

+1
Original file line numberDiff line numberDiff line change
@@ -105,6 +105,7 @@ export(numeric_leading_zero_linter)
105105
export(nzchar_linter)
106106
export(object_length_linter)
107107
export(object_name_linter)
108+
export(object_overwrite_linter)
108109
export(object_usage_linter)
109110
export(one_call_pipe_linter)
110111
export(open_curly_linter)

R/object_overwrite_linter.R

+114
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,114 @@
1+
#' Block assigning any variables whose name clashes with a `base` R function
2+
#'
3+
#' Re-using existing names creates a risk of subtle error best avoided.
4+
#' Avoiding this practice also encourages using better, more descriptive names.
5+
#'
6+
#' @param packages Character vector of packages to search for names that should
7+
#' be avoided. Defaults to the most common default packages: base, stats,
8+
#' utils, tools, methods, graphics, and grDevices.
9+
#' @param allow_names Character vector of object names to ignore, i.e., which
10+
#' are allowed to collide with exports from `packages`.
11+
#'
12+
#' @examples
13+
#' # will produce lints
14+
#' code <- "function(x) {\n data <- x\n data\n}"
15+
#' writeLines(code)
16+
#' lint(
17+
#' text = code,
18+
#' linters = object_overwrite_linter()
19+
#' )
20+
#'
21+
#' code <- "function(x) {\n lint <- 'fun'\n lint\n}"
22+
#' writeLines(code)
23+
#' lint(
24+
#' text = code,
25+
#' linters = object_overwrite_linter(packages = "lintr")
26+
#' )
27+
#'
28+
#' # okay
29+
#' code <- "function(x) {\n data('mtcars')\n}"
30+
#' writeLines(code)
31+
#' lint(
32+
#' text = code,
33+
#' linters = object_overwrite_linter()
34+
#' )
35+
#'
36+
#' code <- "function(x) {\n data <- x\n data\n}"
37+
#' writeLines(code)
38+
#' lint(
39+
#' text = code,
40+
#' linters = object_overwrite_linter(packages = "base")
41+
#' )
42+
#'
43+
#' # names in function signatures are ignored
44+
#' lint(
45+
#' text = "function(data) data <- subset(data, x > 0)",
46+
#' linters = object_overwrite_linter()
47+
#' )
48+
#'
49+
#' @evalRd rd_tags("object_overwrite_linter")
50+
#' @seealso
51+
#' - [linters] for a complete list of linters available in lintr.
52+
#' - <https://style.tidyverse.org/syntax.html#object-names>
53+
#' @export
54+
object_overwrite_linter <- function(
55+
packages = c("base", "stats", "utils", "tools", "methods", "graphics", "grDevices"),
56+
allow_names = character()) {
57+
for (package in packages) {
58+
if (!requireNamespace(package, quietly = TRUE)) {
59+
stop("Package '", package, "' is not available.")
60+
}
61+
}
62+
pkg_exports <- lapply(
63+
packages,
64+
# .__C__ etc.: drop 150+ "virtual" names since they are very unlikely to appear anyway
65+
function(pkg) setdiff(grep("^[.]__[A-Z]__", getNamespaceExports(pkg), value = TRUE, invert = TRUE), allow_names)
66+
)
67+
pkg_exports <- data.frame(
68+
package = rep(packages, lengths(pkg_exports)),
69+
name = unlist(pkg_exports),
70+
stringsAsFactors = FALSE
71+
)
72+
73+
# test that the symbol doesn't match an argument name in the function
74+
# NB: data.table := has parse token LEFT_ASSIGN as well
75+
xpath <- glue("
76+
//SYMBOL[
77+
not(text() = ancestor::expr/preceding-sibling::SYMBOL_FORMALS/text())
78+
and ({ xp_text_in_table(pkg_exports$name) })
79+
]/
80+
parent::expr[
81+
count(*) = 1
82+
and (
83+
following-sibling::LEFT_ASSIGN[text() != ':=']
84+
or following-sibling::EQ_ASSIGN
85+
or preceding-sibling::RIGHT_ASSIGN
86+
)
87+
and ancestor::*[
88+
(self::expr or self::expr_or_assign_or_help or self::equal_assign)
89+
and (preceding-sibling::FUNCTION or preceding-sibling::OP-LAMBDA)
90+
]
91+
]
92+
")
93+
94+
Linter(function(source_expression) {
95+
if (!is_lint_level(source_expression, "expression")) {
96+
return(list())
97+
}
98+
99+
xml <- source_expression$xml_parsed_content
100+
101+
bad_expr <- xml_find_all(xml, xpath)
102+
bad_symbol <- xml_text(xml_find_first(bad_expr, "SYMBOL"))
103+
source_pkg <- pkg_exports$package[match(bad_symbol, pkg_exports$name)]
104+
lint_message <-
105+
sprintf("'%s' is an exported object from package '%s'. Avoid re-using such symbols.", bad_symbol, source_pkg)
106+
107+
xml_nodes_to_lints(
108+
bad_expr,
109+
source_expression = source_expression,
110+
lint_message = lint_message,
111+
type = "warning"
112+
)
113+
})
114+
}

inst/lintr/linters.csv

+1
Original file line numberDiff line numberDiff line change
@@ -62,6 +62,7 @@ numeric_leading_zero_linter,style consistency readability
6262
nzchar_linter,efficiency best_practices consistency
6363
object_length_linter,style readability default configurable executing
6464
object_name_linter,style consistency default configurable executing
65+
object_overwrite_linter,best_practices robustness readability configurable executing
6566
object_usage_linter,style readability correctness default executing configurable
6667
one_call_pipe_linter,style readability
6768
open_curly_linter,defunct

man/best_practices_linters.Rd

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

man/configurable_linters.Rd

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

man/executing_linters.Rd

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

man/linters.Rd

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

man/object_overwrite_linter.Rd

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

man/readability_linters.Rd

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

man/robustness_linters.Rd

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

0 commit comments

Comments
 (0)