Skip to content

Commit b65c2e9

Browse files
Merge branch 'main' into exec
2 parents d5fda34 + 2d8a12d commit b65c2e9

34 files changed

+482
-142
lines changed

DESCRIPTION

+1-1
Original file line numberDiff line numberDiff line change
@@ -127,7 +127,6 @@ Collate:
127127
'namespace.R'
128128
'namespace_linter.R'
129129
'nested_ifelse_linter.R'
130-
'no_tab_linter.R'
131130
'nonportable_path_linter.R'
132131
'numeric_leading_zero_linter.R'
133132
'object_length_linter.R'
@@ -169,6 +168,7 @@ Collate:
169168
'unused_import_linter.R'
170169
'use_lintr.R'
171170
'vector_logic_linter.R'
171+
'whitespace_linter.R'
172172
'with.R'
173173
'with_id.R'
174174
'xml_nodes_to_lints.R'

NAMESPACE

+1
Original file line numberDiff line numberDiff line change
@@ -136,6 +136,7 @@ export(unreachable_code_linter)
136136
export(unused_import_linter)
137137
export(use_lintr)
138138
export(vector_logic_linter)
139+
export(whitespace_linter)
139140
export(with_defaults)
140141
export(with_id)
141142
export(xml_nodes_to_lints)

NEWS.md

+13-1
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,12 @@
11
# lintr (development version)
22

3-
## Deprecations
3+
## Deprecations & Breaking Changes
44

55
* `single_quotes_linter()` is deprecated in favor of the more generalizable `quotes_linter()` (#1729, @MichaelChirico).
66
* `unneeded_concatentation_linter()` is deprecated in favor of `unnecessary_concatenation_linter()` for naming consistency (#1707, @IndrajeetPatil).
77
* `consecutive_stopifnot_linter()` is deprecated in favor of the more general (see below) `consecutive_assertion_linter()` (#1604, @MichaelChirico).
8+
* `no_tab_linter()` is deprecated in favor of `whitespace_linter()` for naming consistency and future generalization (#1954, @MichaelChirico).
9+
* `available_linters()` prioritizes `tags` over `exclude_tags` in the case of overlap, i.e., tags listed in both arguments are included, not excluded. We don't expect many people to be affected by this, and the old behavior was not made explicit in the documentation, but make note of it here since it required changing a test in lintr's own suite where `linters_with_tags()` implicitly assumed this behavior.
810

911
## Bug fixes
1012

@@ -37,6 +39,9 @@
3739

3840
* `object_name_linter()` allows all S3 group Generics (see `?base::groupGeneric`) and S3 generics defined in a different file in the same package (#1808, #1841, @AshesITR)
3941

42+
* `object_usage_linter()` improves identification of the exact source of a lint for undefined variables in expressions with where the variable is used as a symbol in a usual way, for example in a formula or in an extraction with `$` (#1914, @MichaelChirico).
43+
44+
* `function_left_parentheses_linter()` produces a more specific lint (and no longer fails) when the opening parenthesis is on a different line than `function` or the call name (#1953, @MichaelChirico).
4045
## Changes to defaults
4146

4247
* Set the default for the `except` argument in `duplicate_argument_linter()` to `c("mutate", "transmute")`.
@@ -63,6 +68,7 @@
6368
+ `indentation_linter()`
6469
+ `quotes_linter()`
6570
+ `unnecessary_concatenation_linter()`
71+
+ `whitespace_linter()`
6672

6773
* `lint_package()` also looks for files in `exec/` (#1950, @jmaspons).
6874

@@ -111,6 +117,10 @@
111117

112118
* `missing_argument_linter()` allows missing arguments in `quote()` calls (#1889, @IndrajeetPatil).
113119

120+
* `get_source_expressions()` correctly extracts indented code chunks from R Markdown documents, which helps avoid spurious lints related to whitespace (#1945, @MichaelChirico). The convention taken is that, within each chunk, all code is anchored relative to the leftmost non-whitespace column.
121+
122+
* `available_linters()` gives priority to `tags` over `exclude_tags` in the case of overlap. In particular, this means that `available_linters(tags = "deprecated")` will work to return deprecated linters without needing to specify `exclude_tags` (#1959, @MichaelChirico).
123+
114124
### New linters
115125

116126
* `matrix_apply_linter()` recommends use of dedicated `rowSums()`, `colSums()`, `colMeans()`, `rowMeans()` over `apply(., MARGIN, sum)` or `apply(., MARGIN, mean)`. The recommended alternative is much more efficient and more readable (#1869, @Bisaloo).
@@ -152,6 +162,8 @@
152162

153163
* `consecutive_assertion_linter()` (f.k.a. `consecutive_stopifnot_linter()`) now lints for consecutive calls to `assertthat::assert_that()` (as long as the `msg=` argument is not used; #1604, @MichaelChirico).
154164

165+
* `whitespace_linter()` is simply `no_tab_linter()`, renamed. In the future, we plan to extend it to work for different whitespace preferences.
166+
155167
## Notes
156168

157169
* {lintr} now depends on R version 3.5.0, in line with the tidyverse policy for R version compatibility.

R/extract.R

+17-4
Original file line numberDiff line numberDiff line change
@@ -22,12 +22,14 @@ extract_r_source <- function(filename, lines, error = identity) {
2222

2323
output_env <- environment() # nolint: object_usage_linter. False positive-ish -- used below.
2424
Map(
25-
function(start, end) {
25+
function(start, end, indent) {
2626
line_seq <- seq(start + 1L, end - 1L)
27-
output_env$output[line_seq] <- lines[line_seq]
27+
chunk_code <- lines[line_seq]
28+
output_env$output[line_seq] <- if (indent > 0L) substr(chunk_code, indent + 1L, nchar(chunk_code)) else chunk_code
2829
},
2930
chunks[["starts"]],
30-
chunks[["ends"]]
31+
chunks[["ends"]],
32+
chunks[["indents"]]
3133
)
3234
# drop <<chunk>> references, too
3335
is.na(output) <- grep(pattern$ref.chunk, output)
@@ -73,7 +75,18 @@ get_chunk_positions <- function(pattern, lines) {
7375
# only keep those blocks that contain at least one line of code
7476
keep <- which(ends - starts > 1L)
7577

76-
list(starts = starts[keep], ends = ends[keep])
78+
starts <- starts[keep]
79+
ends <- ends[keep]
80+
81+
# Check indent on all lines in the chunk to allow for staggered indentation within a chunk;
82+
# set the initial column to the leftmost one within each chunk (including the start+end gates). See tests.
83+
# use 'ws_re' to make clear that we're matching knitr's definition of initial whitespace.
84+
ws_re <- sub("```.*", "", pattern$chunk.begin)
85+
indents <- mapply(
86+
function(start, end) min(vapply(gregexpr(ws_re, lines[start:end], perl = TRUE), attr, integer(1L), "match.length")),
87+
starts, ends
88+
)
89+
list(starts = starts, ends = ends, indents = indents)
7790
}
7891

7992
filter_chunk_start_positions <- function(starts, lines) {

R/function_left_parentheses_linter.R

+19-8
Original file line numberDiff line numberDiff line change
@@ -41,26 +41,37 @@
4141
#' - [spaces_left_parentheses_linter()]
4242
#' @export
4343
function_left_parentheses_linter <- function() { # nolint: object_length.
44-
xpath <- "
45-
//FUNCTION[@col2 != following-sibling::OP-LEFT-PAREN/@col1 - 1]
46-
|
47-
//SYMBOL_FUNCTION_CALL/parent::expr[@col2 != following-sibling::OP-LEFT-PAREN/@col1 - 1]
48-
"
44+
xpath_fmt <- "//FUNCTION[ {cond} ] | //SYMBOL_FUNCTION_CALL/parent::expr[ {cond} ]"
45+
bad_line_cond <- "@line1 != following-sibling::OP-LEFT-PAREN/@line1"
46+
bad_col_cond <- xp_and(
47+
"@line1 = following-sibling::OP-LEFT-PAREN/@line1",
48+
"@col2 != following-sibling::OP-LEFT-PAREN/@col1 - 1"
49+
)
50+
bad_line_xpath <- glue::glue(xpath_fmt, cond = bad_line_cond)
51+
bad_col_xpath <- glue::glue(xpath_fmt, cond = bad_col_cond)
4952

5053
Linter(function(source_expression) {
5154
if (!is_lint_level(source_expression, "expression")) {
5255
return(list())
5356
}
5457

5558
xml <- source_expression$xml_parsed_content
56-
bad_exprs <- xml2::xml_find_all(xml, xpath)
5759

58-
xml_nodes_to_lints(
59-
bad_exprs,
60+
bad_line_exprs <- xml2::xml_find_all(xml, bad_line_xpath)
61+
bad_line_lints <- xml_nodes_to_lints(
62+
bad_line_exprs,
63+
source_expression = source_expression,
64+
lint_message = "Left parenthesis should be on the same line as the function's symbol."
65+
)
66+
67+
bad_col_exprs <- xml2::xml_find_all(xml, bad_col_xpath)
68+
bad_col_lints <- xml_nodes_to_lints(
69+
bad_col_exprs,
6070
source_expression = source_expression,
6171
lint_message = "Remove spaces before the left parenthesis in a function call.",
6272
range_start_xpath = "number(./@col2 + 1)", # start after function / fun
6373
range_end_xpath = "number(./following-sibling::OP-LEFT-PAREN/@col1 - 1)" # end before (
6474
)
75+
c(bad_line_lints, bad_col_lints)
6576
})
6677
}

R/linter_tags.R

+13-5
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,8 @@
77
#' returned. If `tags` is `NULL`, all linters will be returned. See `available_tags("lintr")` to find out what
88
#' tags are already used by lintr.
99
#' @param exclude_tags Tags to exclude from the results. Linters with at least one matching tag will not be returned.
10-
#' If `except_tags` is `NULL`, no linters will be excluded.
10+
#' If `except_tags` is `NULL`, no linters will be excluded. Note that `tags` takes priority, meaning that any
11+
#' tag found in both `tags` and `exclude_tags` will be included, not excluded.
1112
#'
1213
#' @section Package Authors:
1314
#'
@@ -41,7 +42,9 @@
4142
#'
4243
#' lintr_linters2 <- available_linters(c("lintr", "does-not-exist"))
4344
#' identical(lintr_linters, lintr_linters2)
44-
#' @seealso [linters] for a complete list of linters available in lintr.
45+
#' @seealso
46+
#' - [linters] for a complete list of linters available in lintr.
47+
#' - [available_tags()] to retrieve the set of valid tags.
4548
#' @export
4649
available_linters <- function(packages = "lintr", tags = NULL, exclude_tags = "deprecated") {
4750
if (!is.character(packages)) {
@@ -54,6 +57,9 @@ available_linters <- function(packages = "lintr", tags = NULL, exclude_tags = "d
5457
stop("`exclude_tags` must be a character vector.")
5558
}
5659

60+
# any tags specified explicitly will not be excluded (#1959)
61+
exclude_tags <- setdiff(exclude_tags, tags)
62+
5763
# Handle multiple packages
5864
if (length(packages) > 1L) {
5965
return(do.call(rbind, lapply(packages, available_linters, tags = tags, exclude_tags = exclude_tags)))
@@ -160,7 +166,7 @@ rd_tags <- function(linter_name) {
160166
#'
161167
#' @noRd
162168
rd_linters <- function(tag_name) {
163-
linters <- available_linters(tags = tag_name, exclude_tags = NULL)
169+
linters <- available_linters(tags = tag_name)
164170
tagged <- platform_independent_sort(linters[["linter"]])
165171
if (length(tagged) == 0L) {
166172
stop("No linters found associated with tag ", tag_name)
@@ -181,9 +187,11 @@ rd_linters <- function(tag_name) {
181187
#' @noRd
182188
rd_taglist <- function() {
183189
linters <- available_linters(exclude_tags = NULL)
190+
# don't count tags on deprecated linters to the counts of other tags
191+
linters$tags <- lapply(linters$tags, function(x) if ("deprecated" %in% x) "deprecated" else x)
184192

185193
tag_table <- table(unlist(linters[["tags"]]))
186-
tags <- platform_independent_sort(unique(unlist(linters[["tags"]])))
194+
tags <- platform_independent_sort(names(tag_table))
187195
# re-order
188196
tag_table <- tag_table[tags]
189197

@@ -203,7 +211,7 @@ rd_taglist <- function() {
203211
#'
204212
#' @noRd
205213
rd_linterlist <- function() {
206-
linters <- available_linters(exclude_tags = NULL)
214+
linters <- available_linters()
207215
linter_names <- platform_independent_sort(linters[["linter"]])
208216

209217
c(

R/lintr-deprecated.R

+13
Original file line numberDiff line numberDiff line change
@@ -239,3 +239,16 @@ consecutive_stopifnot_linter <- function() {
239239
)
240240
consecutive_assertion_linter()
241241
}
242+
243+
#' No tabs linter
244+
#' @rdname lintr-deprecated
245+
#' @export
246+
no_tab_linter <- function() {
247+
lintr_deprecated(
248+
old = "no_tab_linter",
249+
new = "whitespace_linter",
250+
version = "3.1.0",
251+
type = "Linter"
252+
)
253+
whitespace_linter()
254+
}

R/object_usage_linter.R

+10-9
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,15 @@ object_usage_linter <- function(interpret_glue = TRUE, skip_with = TRUE) {
4646
sep = " | "
4747
)
4848

49+
# not all instances of linted symbols are potential sources for the observed violations -- see #1914
50+
symbol_exclude_cond <- "preceding-sibling::OP-DOLLAR or preceding-sibling::OP-AT or ancestor::expr[OP-TILDE]"
51+
xpath_culprit_symbol <- glue::glue("
52+
descendant::SYMBOL[not( {symbol_exclude_cond} )]
53+
| descendant::SYMBOL_FUNCTION_CALL[not( {symbol_exclude_cond} )]
54+
| descendant::SPECIAL
55+
| descendant::LEFT_ASSIGN[text() = ':=']
56+
")
57+
4958
Linter(function(source_expression) {
5059
if (!is_lint_level(source_expression, "file")) {
5160
return(list())
@@ -97,15 +106,7 @@ object_usage_linter <- function(interpret_glue = TRUE, skip_with = TRUE) {
97106
# e.g. `not_existing<-`(a, b)
98107
res$name <- rex::re_substitutes(res$name, rex::rex("<-"), "")
99108

100-
lintable_symbols <- xml2::xml_find_all(
101-
fun_assignment,
102-
"
103-
descendant::SYMBOL
104-
| descendant::SYMBOL_FUNCTION_CALL
105-
| descendant::SPECIAL
106-
| descendant::LEFT_ASSIGN[text() = ':=']
107-
"
108-
)
109+
lintable_symbols <- xml2::xml_find_all(fun_assignment, xpath_culprit_symbol)
109110

110111
lintable_symbol_names <- gsub("^`|`$", "", xml2::xml_text(lintable_symbols))
111112
lintable_symbol_lines <- as.integer(xml2::xml_attr(lintable_symbols, "line1"))

R/no_tab_linter.R renamed to R/whitespace_linter.R

+11-8
Original file line numberDiff line numberDiff line change
@@ -1,32 +1,35 @@
1-
#' No tab linter
1+
#' Whitespace linter
22
#'
3-
#' Check that only spaces are used for indentation, not tabs. Much ink has been
4-
#' spilled on this topic, and we encourage you to check out references for more
5-
#' information.
3+
#' Check that the correct character is used for indentation.
4+
#'
5+
#' Currently, only supports linting in the presence of tabs.
6+
#'
7+
#' Much ink has been spilled on this topic, and we encourage you to check
8+
#' out references for more information.
69
#'
710
#' @include make_linter_from_regex.R
811
#'
912
#' @examples
1013
#' # will produce lints
1114
#' lint(
1215
#' text = "\tx",
13-
#' linters = no_tab_linter()
16+
#' linters = whitespace_linter()
1417
#' )
1518
#'
1619
#' # okay
1720
#' lint(
1821
#' text = " x",
19-
#' linters = no_tab_linter()
22+
#' linters = whitespace_linter()
2023
#' )
2124
#'
22-
#' @evalRd rd_tags("no_tab_linter")
25+
#' @evalRd rd_tags("whitespace_linter")
2326
#' @seealso [linters] for a complete list of linters available in lintr.
2427
#'
2528
#' @references
2629
#' - https://www.jwz.org/doc/tabs-vs-spaces.html
2730
#' - https://blog.codinghorror.com/death-to-the-space-infidels/
2831
#' @export
29-
no_tab_linter <- make_linter_from_regex(
32+
whitespace_linter <- make_linter_from_regex(
3033
regex = rex(start, zero_or_more(regex("\\s")), one_or_more("\t")),
3134
lint_type = "style",
3235
lint_msg = "Use spaces to indent, not tabs."

R/zzz.R

+2-2
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,6 @@ default_linters <- modify_defaults(
2323
indentation_linter(),
2424
infix_spaces_linter(),
2525
line_length_linter(),
26-
no_tab_linter(),
2726
object_length_linter(),
2827
object_name_linter(),
2928
object_usage_linter(),
@@ -37,7 +36,8 @@ default_linters <- modify_defaults(
3736
T_and_F_symbol_linter(),
3837
trailing_blank_lines_linter(),
3938
trailing_whitespace_linter(),
40-
vector_logic_linter()
39+
vector_logic_linter(),
40+
whitespace_linter()
4141
)
4242

4343
#' Default undesirable functions and operators

inst/lintr/linters.csv

+2-1
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ missing_argument_linter,correctness common_mistakes configurable
4949
missing_package_linter,robustness common_mistakes
5050
namespace_linter,correctness robustness configurable executing
5151
nested_ifelse_linter,efficiency readability
52-
no_tab_linter,style consistency default
52+
no_tab_linter,style consistency deprecated
5353
nonportable_path_linter,robustness best_practices configurable
5454
numeric_leading_zero_linter,style consistency readability
5555
object_length_linter,style readability default configurable executing
@@ -93,4 +93,5 @@ unneeded_concatenation_linter,style readability efficiency configurable deprecat
9393
unreachable_code_linter,best_practices readability
9494
unused_import_linter,best_practices common_mistakes configurable executing
9595
vector_logic_linter,default efficiency best_practices
96+
whitespace_linter,style consistency default
9697
yoda_test_linter,package_development best_practices readability

man/available_linters.Rd

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

man/configurable_linters.Rd

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

0 commit comments

Comments
 (0)