Skip to content

Commit 4b59aac

Browse files
except_regex argument for todo_comment_linter() to skip valid TODO comments (#2439)
1 parent fdbb9bf commit 4b59aac

12 files changed

+96
-38
lines changed

.lintr

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,18 @@ linters: all_linters(
22
backport_linter("3.6.0", except = c("R_user_dir", "deparse1", "...names")),
33
line_length_linter(120L),
44
object_overwrite_linter(allow_names = c("line", "lines", "pipe", "symbols")),
5+
todo_comment_linter(
6+
except_regex = rex::rex(
7+
"TODO(",
8+
group(or(
9+
# GitHub issue number #1234, possibly from another repo org/repo#5678
10+
list(maybe(one_or_more(alnum, "-"), "/", one_or_more(alnum, ".", "-", "_")), "#", one_or_more(digit)),
11+
# GitHub user. TODO(#2450): remove this temporary immunity
12+
one_or_more(alnum, "-")
13+
)),
14+
")"
15+
)
16+
),
517
undesirable_function_linter(modify_defaults(
618
defaults = default_undesirable_functions,
719
library = NULL,

NEWS.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@
4343
* `format()` and `print()` methods for `lint` and `lints` classes get a new option `width` to control the printing width of lint messages (#1884, @MichaelChirico). The default is controlled by a new option `lintr.format_width`; if unset, no wrapping occurs (matching earlier behavior).
4444
* `implicit_assignment_linter()` gets a custom message for the case of using `(` to induce printing like `(x <- foo())`; use an explicit call to `print()` for clarity (#2257, @MichaelChirico).
4545
* New function node caching for big efficiency gains to most linters (e.g. overall `lint_package()` improvement of 14-27% and core linting improvement up to 30%; #2357, @AshesITR). Most linters are written around function usage, and XPath performance searching for many functions is poor. The new `xml_find_function_calls()` entry in the `get_source_expressions()` output caches all function call nodes instead. See the vignette on creating linters for more details on how to use it.
46+
* `todo_comment_linter()` has a new argument `except_regex` for setting _valid_ TODO comments, e.g. for forcing TODO comments to be linked to GitHub issues like `TODO(#154)` (#2047, @MichaelChirico).
4647
* `vector_logic_linter()` is extended to recognize incorrect usage of scalar operators `&&` and `||` inside subsetting expressions like `dplyr::filter(x, A && B)` (#2166, @MichaelChirico).
4748
* `any_is_na_linter()` is extended to catch the unusual usage `NA %in% x` (#2113, @MichaelChirico).
4849

R/brace_linter.R

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ brace_linter <- function(allow_single_line = FALSE) {
7474
)")
7575
))
7676

77-
# TODO (AshesITR): if c_style_braces is TRUE, invert the preceding-sibling condition
77+
# TODO(#1103): if c_style_braces is TRUE, invert the preceding-sibling condition
7878
xp_open_curly <- glue("//OP-LEFT-BRACE[
7979
{ xp_cond_open }
8080
and (
@@ -109,7 +109,7 @@ brace_linter <- function(allow_single_line = FALSE) {
109109
)"
110110
))
111111

112-
# TODO (AshesITR): if c_style_braces is TRUE, skip the not(ELSE) condition
112+
# TODO(#1103): if c_style_braces is TRUE, skip the not(ELSE) condition
113113
xp_closed_curly <- glue("//OP-RIGHT-BRACE[
114114
{ xp_cond_closed }
115115
and (
@@ -121,7 +121,7 @@ brace_linter <- function(allow_single_line = FALSE) {
121121
xp_else_closed_curly <- "preceding-sibling::IF/following-sibling::expr[2]/OP-RIGHT-BRACE"
122122
# need to (?) repeat previous_curly_path since != will return true if there is
123123
# no such node. ditto for approach with not(@line1 = ...).
124-
# TODO (AshesITR): if c_style_braces is TRUE, this needs to be @line2 + 1
124+
# TODO(#1103): if c_style_braces is TRUE, this needs to be @line2 + 1
125125
xp_else_same_line <- glue("//ELSE[{xp_else_closed_curly} and @line1 != {xp_else_closed_curly}/@line2]")
126126

127127
xp_function_brace <- "(//FUNCTION | //OP-LAMBDA)/parent::expr[@line1 != @line2 and not(expr[OP-LEFT-BRACE])]"

R/lint.R

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -24,8 +24,6 @@
2424
#' @param text Optional argument for supplying a string or lines directly, e.g. if the file is already in memory or
2525
#' linting is being done ad hoc.
2626
#'
27-
#' @aliases lint_file
28-
# TODO(next release after 3.0.0): remove the alias
2927
#' @return An object of class `c("lints", "list")`, each element of which is a `"list"` object.
3028
#'
3129
#' @examplesIf requireNamespace("withr", quietly = TRUE)

R/missing_argument_linter.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ missing_argument_linter <- function(except = c("alist", "quote", "switch"), allo
5858
named_idx <- xml_name(missing_args) == "EQ_SUB"
5959
arg_id <- character(length(missing_args))
6060
arg_id[named_idx] <- sQuote(xml_find_chr(missing_args[named_idx], "string(preceding-sibling::SYMBOL_SUB[1])"), "'")
61-
# TODO(r-lib/xml2#412-->CRAN): use xml_find_int() instead
61+
# TODO(#2452): use xml_find_int() instead
6262
arg_id[!named_idx] <- xml_find_num(missing_args[!named_idx], "count(preceding-sibling::OP-COMMA)") + 1.0
6363

6464
xml_nodes_to_lints(

R/object_usage_linter.R

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -87,8 +87,6 @@ object_usage_linter <- function(interpret_glue = TRUE, skip_with = TRUE) {
8787
skip_with = skip_with
8888
)
8989

90-
# TODO handle assignment functions properly
91-
# e.g. `not_existing<-`(a, b)
9290
res$name <- re_substitutes(res$name, rex("<-"), "")
9391

9492
lintable_symbols <- xml_find_all(fun_assignment, xpath_culprit_symbol)
@@ -211,7 +209,7 @@ parse_check_usage <- function(expression,
211209
# nocov start
212210
is_missing <- is.na(res$message)
213211
if (any(is_missing)) {
214-
# TODO (AshesITR): Remove this in the future, if no bugs arise from this safeguard
212+
# TODO(AshesITR): Remove this in the future, if no bugs arise from this safeguard
215213
warning(
216214
"Possible bug in lintr: Couldn't parse usage message ", sQuote(vals[is_missing][[1L]]), ". ",
217215
"Ignoring ", sum(is_missing), " usage warnings. Please report an issue at https://github.com/r-lib/lintr/issues.",

R/shared_constants.R

Lines changed: 1 addition & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -243,18 +243,7 @@ extract_glued_symbols <- function(expr, interpret_glue) {
243243
if (!isTRUE(interpret_glue)) {
244244
return(character())
245245
}
246-
# TODO support more glue functions
247-
# Package glue:
248-
# - glue_sql
249-
# - glue_safe
250-
# - glue_col
251-
# - glue_data
252-
# - glue_data_sql
253-
# - glue_data_safe
254-
# - glue_data_col
255-
#
256-
# Package stringr:
257-
# - str_interp
246+
# TODO(#2448): support more glue functions
258247
# NB: position() > 1 because position=1 is <expr><SYMBOL_FUNCTION_CALL>
259248
glue_call_xpath <- "
260249
descendant::SYMBOL_FUNCTION_CALL[text() = 'glue']

R/todo_comment_linter.R

Lines changed: 22 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -3,22 +3,24 @@
33
#' Check that the source contains no TODO comments (case-insensitive).
44
#'
55
#' @param todo Vector of case-insensitive strings that identify TODO comments.
6+
#' @param except_regex Vector of case-sensitive regular expressions that identify
7+
#' _valid_ TODO comments.
68
#'
79
#' @examples
810
#' # will produce lints
911
#' lint(
10-
#' text = "x + y # TODO",
11-
#' linters = todo_comment_linter()
12+
#' text = "x + y # TOODOO",
13+
#' linters = todo_comment_linter(todo = "toodoo")
1214
#' )
1315
#'
1416
#' lint(
15-
#' text = "pi <- 1.0 # FIXME",
16-
#' linters = todo_comment_linter()
17+
#' text = "pi <- 1.0 # FIIXMEE",
18+
#' linters = todo_comment_linter(todo = "fiixmee")
1719
#' )
1820
#'
1921
#' lint(
20-
#' text = "x <- TRUE # hack",
21-
#' linters = todo_comment_linter(todo = c("todo", "fixme", "hack"))
22+
#' text = "x <- TRUE # TOODOO(#1234): Fix this hack.",
23+
#' linters = todo_comment_linter()
2224
#' )
2325
#'
2426
#' # okay
@@ -37,20 +39,31 @@
3739
#' linters = todo_comment_linter()
3840
#' )
3941
#'
42+
#' lint(
43+
#' text = "x <- TRUE # TODO(#1234): Fix this hack.",
44+
#' linters = todo_comment_linter(except_regex = "TODO\\(#[0-9]+\\):")
45+
#' )
46+
#'
4047
#' @evalRd rd_tags("todo_comment_linter")
4148
#' @seealso [linters] for a complete list of linters available in lintr.
4249
#' @export
43-
todo_comment_linter <- function(todo = c("todo", "fixme")) {
50+
todo_comment_linter <- function(todo = c("todo", "fixme"), except_regex = NULL) {
4451
todo_comment_regex <- rex(one_or_more("#"), any_spaces, or(todo))
52+
valid_todo_regex <-
53+
if (!is.null(except_regex)) paste0("#+", rex::shortcuts$any_spaces, "(?:", paste(except_regex, collapse = "|"), ")")
4554

4655
Linter(linter_level = "expression", function(source_expression) {
4756
xml <- source_expression$xml_parsed_content
4857

4958
comment_expr <- xml_find_all(xml, "//COMMENT")
50-
are_todo <- re_matches(xml_text(comment_expr), todo_comment_regex, ignore.case = TRUE)
59+
comment_text <- xml_text(comment_expr)
60+
invalid_todo <- re_matches(comment_text, todo_comment_regex, ignore.case = TRUE)
61+
if (!is.null(valid_todo_regex)) {
62+
invalid_todo <- invalid_todo & !re_matches(comment_text, valid_todo_regex)
63+
}
5164

5265
xml_nodes_to_lints(
53-
comment_expr[are_todo],
66+
comment_expr[invalid_todo],
5467
source_expression = source_expression,
5568
lint_message = "Remove TODO comments.",
5669
type = "style"

R/xp_utils.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,7 @@ xp_find_location <- function(xml, xpath) {
118118
#' way to XPath 2.0-ish support by writing this simple function to remove comments.
119119
#'
120120
#' @noRd
121-
xpath_comment_re <- rex::rex(
121+
xpath_comment_re <- rex(
122122
"(:",
123123
zero_or_more(not(":)")),
124124
":)"

man/lint.Rd

Lines changed: 0 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/todo_comment_linter.Rd

Lines changed: 14 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.
Lines changed: 40 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
11
test_that("returns the correct linting", {
2-
linter <- todo_comment_linter(todo = c("todo", "fixme"))
2+
linter <- todo_comment_linter()
33
lint_msg <- rex::rex("Remove TODO comments.")
44

5-
expect_lint("a <- \"you#need#to#fixme\"", NULL, linter)
5+
expect_lint('a <- "you#need#to#fixme"', NULL, linter)
66
expect_lint("# something todo", NULL, linter)
77
expect_lint(
88
"cat(x) ### fixme",
@@ -15,11 +15,46 @@ test_that("returns the correct linting", {
1515
linter
1616
)
1717
expect_lint(
18-
"function() {\n# TODO\n function() {\n # fixme\n }\n}",
18+
trim_some("
19+
function() {
20+
# TODO
21+
function() {
22+
# fixme
23+
}
24+
}
25+
"),
1926
list(
20-
list(message = lint_msg, line_number = 2L, column_number = 1L),
21-
list(message = lint_msg, line_number = 4L, column_number = 3L)
27+
list(message = lint_msg, line_number = 2L, column_number = 3L),
28+
list(message = lint_msg, line_number = 4L, column_number = 5L)
2229
),
2330
linter
2431
)
2532
})
33+
34+
test_that("except_regex= excludes valid TODO", {
35+
linter <- todo_comment_linter(except_regex = "TODO\\(#[0-9]+\\):")
36+
lint_msg <- rex::rex("Remove TODO comments.")
37+
38+
expect_lint("foo() # TODO(#1234): Deprecate foo.", NULL, linter)
39+
# Non-excepted lints
40+
expect_lint(
41+
trim_some("
42+
foo() # TODO()
43+
bar() # TODO(#567): Deprecate bar.
44+
"),
45+
list(lint_msg, line_number = 1L),
46+
linter
47+
)
48+
# Only TODO() is excepted
49+
mixed_lines <- trim_some("
50+
foo() # TODO(#1234): Deprecate foo.
51+
bar() # fixme(#567): Deprecate bar.
52+
")
53+
54+
expect_lint(mixed_lines, list(lint_msg, line_number = 2L), linter)
55+
expect_lint(
56+
mixed_lines,
57+
NULL,
58+
todo_comment_linter(except_regex = c("TODO\\(#[0-9]+\\):", "fixme\\(#[0-9]+\\):"))
59+
)
60+
})

0 commit comments

Comments
 (0)