Skip to content

Commit 5cb223a

Browse files
Create list2df_linter() (#2834)
* Create cbind_dataframe_linter() Fix #2596 * Rename linter to list2df_linter() * Ensure symmetry in examples * Remove unnecessary "if available" in msg * Refactor linter without make_linter_from_xpath() * Detect functions passed as string * Fix lints * Re-document * refine wording+docs * Add test for anonymous function * Use stricter xpath to avoid get_r_string() on false positives * Add extra !is.na() safety to avoid NA in unanticipated complex xpaths * Add anonymous function expr to vectorized test * Revert to xml_find_function_calls() approach * Land on parent::expr * Use xml_parent() instead of xml_find_all() * Add NEWS bullet * Add column_number to tests to ensure lints lands where expected Co-authored-by: Michael Chirico <chiricom@google.com> --------- Co-authored-by: Michael Chirico <michaelchirico4@gmail.com> Co-authored-by: Michael Chirico <chiricom@google.com>
1 parent 8913141 commit 5cb223a

10 files changed

+180
-26
lines changed

DESCRIPTION

+1
Original file line numberDiff line numberDiff line change
@@ -132,6 +132,7 @@ Collate:
132132
'linter_tags.R'
133133
'lintr-deprecated.R'
134134
'lintr-package.R'
135+
'list2df_linter.R'
135136
'list_comparison_linter.R'
136137
'literal_coercion_linter.R'
137138
'make_linter_from_regex.R'

NAMESPACE

+1
Original file line numberDiff line numberDiff line change
@@ -90,6 +90,7 @@ export(lint_dir)
9090
export(lint_package)
9191
export(linters_with_defaults)
9292
export(linters_with_tags)
93+
export(list2df_linter)
9394
export(list_comparison_linter)
9495
export(literal_coercion_linter)
9596
export(make_linter_from_function_xpath)

NEWS.md

+25-24
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@
3333

3434
### New linters
3535

36+
* `lint2df_linter()` encourages the use of the `list2DF()` function, or the `data.frame()` function when recycling is required, over the slower and less readable `do.call(cbind.data.frame, )` alternative (#2834, @Bisaloo).
3637
* `coalesce_linter()` encourages the use of the infix operator `x %||% y`, which is equivalent to `if (is.null(x)) y else x` (#2246, @MichaelChirico). While this has long been used in many tidyverse packages (it was added to {ggplot2} in 2008), it became part of every R installation from R 4.4.0.
3738

3839
### Lint accuracy fixes: removing false positives
@@ -304,7 +305,7 @@
304305

305306
## Bug fixes
306307

307-
* `linters_with_tags()` now includes the previously missing spaces around "and" when listing missing linters advertised by `available_linters()`.
308+
* `linters_with_tags()` now includes the previously missing spaces around "and" when listing missing linters advertised by `available_linters()`.
308309
This error message may appear e.g. when you update lintr to a version with new linters but don't restart your R session (#1946, @Bisaloo)
309310

310311
* `fixed_regex_linter()` is more robust to errors stemming from unrecognized escapes (#1545, #1845, @IndrajeetPatil).
@@ -358,7 +359,7 @@
358359
the style guide on handling this case awaits clarification: https://github.com/tidyverse/style/issues/191.
359360
(#1346, @MichaelChirico)
360361

361-
* `undesirable_function_linter()` and `undesirable_operator_linter()` now produce an error
362+
* `undesirable_function_linter()` and `undesirable_operator_linter()` now produce an error
362363
if empty vector of undesirable functions or operators is provided (#1867, @IndrajeetPatil).
363364

364365
* New linters which are also included as defaults (see "New linters" for more details):
@@ -412,7 +413,7 @@
412413

413414
* `all_linters()` function provides an easy way to access all available linters (#1843, @IndrajeetPatil)
414415

415-
* `missing_argument_linter()` allows missing arguments in `quote()` calls (#1889, @IndrajeetPatil).
416+
* `missing_argument_linter()` allows missing arguments in `quote()` calls (#1889, @IndrajeetPatil).
416417

417418
* `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.
418419

@@ -453,7 +454,7 @@
453454

454455
* `indentation_linter()` for checking that the indentation conforms to 2-space Tidyverse-style (@AshesITR and @dgkf, #1411, #1792, #1898).
455456

456-
* `unnecessary_nested_if_linter()` for checking unnecessary nested `if` statements where a single
457+
* `unnecessary_nested_if_linter()` for checking unnecessary nested `if` statements where a single
457458
`if` statement with appropriate conditional expression would suffice (@IndrajeetPatil and @AshesITR, #1778).
458459

459460
* `implicit_assignment_linter()` for checking implicit assignments in function calls (@IndrajeetPatil and @AshesITR, #1777).
@@ -474,17 +475,17 @@
474475
`marginformat` from {tufte} or `theorem` from {bookdown}, note that those engines must be registered
475476
in {knitr} prior to running `lint()` in order for {lintr} to behave as expected, i.e., they should be
476477
shown as part of `knitr::knit_engines$get()`.
477-
478+
478479
For {tufte} and {bookdown} in particular, one only needs to load the package namespace to accomplish
479480
this (i.e., minimally `loadNamespace("tufte")` or `loadNamespace("bookdown")`, respectively, will
480481
register those packages' custom engines; since `library()` also runs `loadNamespace()`, running
481482
`library()` will also work). Note further that {tufte} only added this code to their `.onLoad()` recently
482483
after our request to do so (see https://github.com/rstudio/tufte/issues/117). Therefore, ensure you're using a
483484
more recent version to get the behavior described here for {tufte}.
484-
485+
485486
More generally, there is no requirement that `loadNamespace()` will register a package's custom {knitr}
486487
engines, so you may need to work with other package authors to figure out a solution for other engines.
487-
488+
488489
Thanks to Yihui and other developers for their helpful discussions around this issue (#797, @IndrajeetPatil).
489490

490491
* The output of `lint()` and `Lint()` gain S3 class `"list"` to assist with S3 dispatch (#1494, @MichaelChirico)
@@ -509,23 +510,23 @@ works when passed to the `styles` parameter (#1924, @hedsnz).
509510

510511
## Changes to defaults
511512

512-
* `brace_linter()` allows opening curly braces on a new line when there is
513+
* `brace_linter()` allows opening curly braces on a new line when there is
513514
a comment ending the preceding line (#1433 and #1434, @IndrajeetPatil).
514515

515-
* `seq_linter()` produces lint for `seq(...)`, since it also cannot properly
516+
* `seq_linter()` produces lint for `seq(...)`, since it also cannot properly
516517
handle empty edge cases (#1468, @IndrajeetPatil).
517518

518-
* `seq_linter()` additionally lints on `1:n()` (from {dplyr})
519+
* `seq_linter()` additionally lints on `1:n()` (from {dplyr})
519520
and `1:.N` (from {data.table}) (#1396, @IndrajeetPatil).
520521

521-
* `literal_coercion_linter()` lints {rlang}'s atomic vector constructors
522-
(i.e., `int()`, `chr()`, `lgl()`, and `dbl()`) if the argument is a scalar
522+
* `literal_coercion_linter()` lints {rlang}'s atomic vector constructors
523+
(i.e., `int()`, `chr()`, `lgl()`, and `dbl()`) if the argument is a scalar
523524
(#1437, @IndrajeetPatil).
524525

525-
* `redundant_ifelse_linter()`'s lint message correctly suggests negation when
526+
* `redundant_ifelse_linter()`'s lint message correctly suggests negation when
526527
the `yes` condition is `0` (#1432, @IndrajeetPatil).
527528

528-
* `seq_linter()` provides more specific replacement code in lint message
529+
* `seq_linter()` provides more specific replacement code in lint message
529530
(#1475, @IndrajeetPatil).
530531

531532
## New and improved features
@@ -537,8 +538,8 @@ works when passed to the `styles` parameter (#1924, @hedsnz).
537538
* New `function_argument_linter()` to enforce that arguments with defaults appear last in function declarations,
538539
see the [Tidyverse design guide](https://design.tidyverse.org/required-no-defaults.html) (#450, @AshesITR).
539540

540-
* New `allow_trailing` argument added to `assignment_linter()` to check when assignment operators are at the
541-
end of a line, and the value is on the following line (#1491, @ashbaldry)
541+
* New `allow_trailing` argument added to `assignment_linter()` to check when assignment operators are at the
542+
end of a line, and the value is on the following line (#1491, @ashbaldry)
542543

543544
* New `sarif_output()` function to output lints to SARIF output (#1424, @shaopeng-gh)
544545

@@ -549,15 +550,15 @@ works when passed to the `styles` parameter (#1924, @hedsnz).
549550

550551
* `object_length_linter()` does not fail in case there are dependencies with no exports (e.g. data-only packages) (#1424, #1509, @IndrajeetPatil).
551552
* `get_source_expressions()` no longer fails on R files that match a knitr pattern (#743, #879, #1406, @AshesITR).
552-
* Parse error lints now appear with the linter name `"error"` instead of `NA` (#1405, @AshesITR).
553+
* Parse error lints now appear with the linter name `"error"` instead of `NA` (#1405, @AshesITR).
553554
Also, linting no longer runs if the `source_expressions` contain invalid string data that would cause error messages
554-
in other linters.
555+
in other linters.
555556
in other linters.
556557
* Prevent `lint()` from hanging on Rmd files with some syntax errors (#1443, @MichaelChirico).
557-
* `get_source_expressions()` no longer omits trailing non-code lines from knitr files (#1400, #1415, @AshesITR).
558+
* `get_source_expressions()` no longer omits trailing non-code lines from knitr files (#1400, #1415, @AshesITR).
558559
This fixes the location information for `trailing_blank_lines_linter()` in RMarkdown documents without terminal
559560
newlines.
560-
* The `vignette("lintr")` incorrectly cited `exclude` as the key for setting file exclusions in `.lintr` when it is
561+
* The `vignette("lintr")` incorrectly cited `exclude` as the key for setting file exclusions in `.lintr` when it is
561562
actually `exclusions`. (#1401, @AshesITR)
562563
* Fixed file exclusion detection in `lint_dir()` so it no longer errors if there are multiple exclusions or no global
563564
exclusions configured for a single file (#1413, #1442, @AshesITR).
@@ -567,9 +568,9 @@ works when passed to the `styles` parameter (#1924, @hedsnz).
567568
* The minimum needed version for soft dependency `{withr}` has been bumped to `2.5.0`
568569
(#1404, @IndrajeetPatil).
569570
* Changed the deprecation warning for `with_defaults()` to also mention `modify_defaults()` (#1438, @AshesITR).
570-
* Quarto files (`.qmd`) were supported out of the box. The documentation and the
571+
* Quarto files (`.qmd`) were supported out of the box. The documentation and the
571572
testing infrastructure are updated to reflect this (#1486, @IndrajeetPatil).
572-
573+
573574
# lintr 3.0.0
574575

575576
## Breaking changes
@@ -681,7 +682,7 @@ works when passed to the `styles` parameter (#1924, @hedsnz).
681682
(#914, @MichaelChirico).
682683
+ Add an exception for `/` usage in `box::use()` declarations (#1087, @klmr).
683684
* `line_length_linter()`: place the source marker at the margin of the affected line to improve user experience
684-
during de-linting -- just press <kbd>Return</kbd> (#735, @AshesITR).*
685+
during de-linting -- just press <kbd>Return</kbd> (#735, @AshesITR).*
685686
* `no_tab_linter()`: use more reliable matching (e.g., excluding matches found in comments; #441, @russHyde).
686687
* `object_length_linter()`: correctly detect generics and only count the implementation class towards the length.
687688
This prevents false positive lints in the case of long generic names, e.g.
@@ -751,7 +752,7 @@ works when passed to the `styles` parameter (#1924, @hedsnz).
751752
@AshesITR).
752753
* `duplicate_argument_linter()` similarly checks that there are no duplicate arguments supplied to function calls (#850,
753754
@renkun-ken).
754-
* `missing_argument_linter()` to check for empty (missing) arguments in function calls (#563, #1152, @renkun-ken and
755+
* `missing_argument_linter()` to check for empty (missing) arguments in function calls (#563, #1152, @renkun-ken and
755756
@AshesITR).
756757
* `missing_package_linter()` to check if packages in calls to `library()` and friends
757758
are missing (#536, #1037, @renkun-ken and @MichaelChirico).

R/list2df_linter.R

+61
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,61 @@
1+
#' Recommend direct usage of `data.frame()` to create a data.frame from a list
2+
#'
3+
#' [list2DF()] is the preferred way to turn a list of columns into a data.frame.
4+
#' Note that it doesn't support recycling; if that's required, use [data.frame()].
5+
#'
6+
#' @examples
7+
#' # will produce lints
8+
#' lint(
9+
#' text = "do.call(cbind.data.frame, x)",
10+
#' linters = list2df_linter()
11+
#' )
12+
#'
13+
#' lint(
14+
#' text = "do.call('cbind.data.frame', x)",
15+
#' linters = list2df_linter()
16+
#' )
17+
#'
18+
#' lint(
19+
#' text = "do.call(cbind.data.frame, list(a = 1, b = 1:10))",
20+
#' linters = list2df_linter()
21+
#' )
22+
#'
23+
#' # okay
24+
#' lint(
25+
#' text = "list2df(x)",
26+
#' linters = list2df_linter()
27+
#' )
28+
#'
29+
#' lint(
30+
#' text = "data.frame(list(a = 1, b = 1:10))",
31+
#' linters = list2df_linter()
32+
#' )
33+
#'
34+
#' @evalRd rd_tags("list2df_linter")
35+
#' @seealso [linters] for a complete list of linters available in lintr.
36+
#' @export
37+
list2df_linter <- function() {
38+
39+
Linter(linter_level = "expression", function(source_expression) {
40+
xml_calls <- source_expression$xml_find_function_calls("do.call")
41+
42+
xml_calls_nolambda <- xml_find_all(
43+
xml_calls,
44+
"./following-sibling::expr[1][SYMBOL or STR_CONST]"
45+
)
46+
47+
bad_expr <- xml_calls_nolambda[
48+
get_r_string(xml_calls_nolambda) == "cbind.data.frame"
49+
]
50+
51+
xml_nodes_to_lints(
52+
xml2::xml_parent(bad_expr),
53+
source_expression = source_expression,
54+
lint_message = paste(
55+
"Use `list2DF(lst)` instead of `do.call(cbind.data.frame, lst)`.",
56+
"If recycling is required, use `data.frame(lst)`."
57+
),
58+
type = "warning"
59+
)
60+
})
61+
}

inst/lintr/linters.csv

+1
Original file line numberDiff line numberDiff line change
@@ -52,6 +52,7 @@ length_test_linter,common_mistakes efficiency
5252
lengths_linter,efficiency readability best_practices
5353
library_call_linter,style best_practices readability configurable
5454
line_length_linter,style readability default configurable
55+
list2df_linter,readability efficiency
5556
list_comparison_linter,best_practices common_mistakes
5657
literal_coercion_linter,best_practices consistency efficiency
5758
matrix_apply_linter,readability efficiency

man/efficiency_linters.Rd

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

man/linters.Rd

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

man/list2df_linter.Rd

+47
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.

tests/testthat/test-list2df_linter.R

+39
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,39 @@
1+
test_that("list2df_linter skips allowed usages", {
2+
linter <- list2df_linter()
3+
4+
expect_no_lint("cbind.data.frame(x, x)", linter)
5+
expect_no_lint("do.call(mean, x)", linter)
6+
expect_no_lint("do.call('c', x)", linter)
7+
8+
# Other cbind methods
9+
expect_no_lint("do.call(cbind, x)", linter)
10+
11+
# Anonymous function
12+
expect_no_lint("do.call(function(x) x, l)", linter)
13+
})
14+
15+
test_that("list2df_linter blocks simple disallowed usages", {
16+
linter <- list2df_linter()
17+
lint_message <- rex::rex("use `data.frame(lst)`")
18+
19+
expect_lint("do.call(cbind.data.frame, x)", lint_message, linter)
20+
expect_lint("do.call('cbind.data.frame', x)", lint_message, linter)
21+
})
22+
23+
test_that("lints vectorize", {
24+
lint_message <- rex::rex("use `data.frame(lst)`")
25+
26+
expect_lint(
27+
trim_some("{
28+
cbind(a, b)
29+
do.call(cbind.data.frame, x)
30+
do.call(function(x) x, l)
31+
do.call('cbind.data.frame', y)
32+
}"),
33+
list(
34+
list(lint_message, line_number = 3L, column_number = 3L),
35+
list(lint_message, line_number = 5L, column_number = 3L)
36+
),
37+
list2df_linter()
38+
)
39+
})

0 commit comments

Comments
 (0)