Skip to content

Commit a716e1a

Browse files
Give specific example of explicit types in implicit_integer_linter() message (#2406)
* give specific example of explicit types in lint message * delint --------- Co-authored-by: AshesITR <alexander.rosenstock@web.de>
1 parent a79b7cd commit a716e1a

File tree

2 files changed

+49
-42
lines changed

2 files changed

+49
-42
lines changed

R/implicit_integer_linter.R

+11-3
Original file line numberDiff line numberDiff line change
@@ -54,12 +54,20 @@ implicit_integer_linter <- function(allow_colon = FALSE) {
5454
Linter(linter_level = "file", function(source_expression) {
5555
xml <- source_expression$full_xml_parsed_content
5656

57-
numbers <- xml_find_all(xml, xpath)
57+
number_expr <- xml_find_all(xml, xpath)
58+
number <- xml_text(number_expr)
59+
lint_idx <- is_implicit_integer(number)
60+
number_expr <- number_expr[lint_idx]
61+
number <- number[lint_idx]
62+
is_negative <- !is.na(xml_find_first(number_expr, "parent::expr/preceding-sibling::OP-MINUS"))
63+
64+
lint_message <-
65+
sprintf("Use %1$dL or %1$d.0 to avoid implicit integers.", ((-1L) ^ is_negative) * as.integer(number))
5866

5967
xml_nodes_to_lints(
60-
numbers[is_implicit_integer(xml_text(numbers))],
68+
number_expr,
6169
source_expression = source_expression,
62-
lint_message = "Avoid implicit integers. Use e.g. 1L for integers or 1.0 for doubles.",
70+
lint_message = lint_message,
6371
type = "style",
6472
column_number_xpath = "number(./@col2 + 1)", # mark at end
6573
range_end_xpath = "number(./@col2 + 1)" # end after number for easy fixing (enter "L" or ".0")

tests/testthat/test-implicit_integer_linter.R

+38-39
Original file line numberDiff line numberDiff line change
@@ -4,59 +4,58 @@ local({
44
# Note: cases indicated by "*" are whole numbers, but don't lint because the user has
55
# effectively declared "this is a double" much as adding '.0' is otherwise accepted.
66
cases <- tibble::tribble(
7-
~num_value_str, ~should_lint,
8-
"Inf", FALSE,
9-
"NaN", FALSE,
10-
"TRUE", FALSE,
11-
"FALSE", FALSE,
12-
"NA", FALSE,
13-
"NA_character_", FALSE,
14-
"2.000", FALSE,
15-
"2.", FALSE,
16-
"2L", FALSE,
17-
"2.0", FALSE,
18-
"2.1", FALSE,
19-
"2", TRUE,
20-
"1e3", TRUE,
21-
"1e3L", FALSE,
22-
"1.0e3L", FALSE,
23-
"1.2e3", FALSE, # * ( = 1200)
24-
"1.2e-3", FALSE,
25-
"1e-3", FALSE,
26-
"1e-33", FALSE,
27-
"1.2e0", FALSE,
28-
"0x1p+0", FALSE, # * ( = 1)
29-
"0x1.ecp+6L", FALSE,
30-
"0x1.ecp+6", FALSE, # * ( = 123)
31-
"0x1.ec66666666666p+6", FALSE,
32-
"8i", FALSE,
33-
"8.0i", FALSE
7+
~num_value_str, ~lint_msg,
8+
"Inf", "",
9+
"NaN", "",
10+
"TRUE", "",
11+
"FALSE", "",
12+
"NA", "",
13+
"NA_character_", "",
14+
"2.000", "",
15+
"2.", "",
16+
"2L", "",
17+
"2.0", "",
18+
"2.1", "",
19+
"2", "2L or 2.0",
20+
"1e3", "1000L or 1000.0",
21+
"1e3L", "",
22+
"1.0e3L", "",
23+
"1.2e3", "", # * ( = 1200)
24+
"1.2e-3", "",
25+
"1e-3", "",
26+
"1e-33", "",
27+
"1.2e0", "",
28+
"0x1p+0", "", # * ( = 1)
29+
"0x1.ecp+6L", "",
30+
"0x1.ecp+6", "", # * ( = 123)
31+
"0x1.ec66666666666p+6", "",
32+
"8i", "",
33+
"8.0i", ""
3434
)
3535
# for convenience of coercing these to string (since tribble doesn't support auto-conversion)
3636
int_max <- .Machine[["integer.max"]] # largest number that R can represent as an integer
3737
cases_int_max <- tibble::tribble(
38-
~num_value_str, ~should_lint,
39-
-int_max - 1.0, FALSE,
40-
-int_max, TRUE,
41-
int_max, TRUE,
42-
int_max + 1.0, FALSE
38+
~num_value_str, ~lint_msg,
39+
-int_max - 1.0, "",
40+
-int_max, sprintf("%1$dL or %1$d.0", -int_max),
41+
int_max, sprintf("%1$dL or %1$d.0", int_max),
42+
int_max + 1.0, ""
4343
)
4444
cases_int_max$num_value_str <- as.character(cases_int_max$num_value_str)
4545
cases <- rbind(cases, cases_int_max)
46-
cases$.test_name <- sprintf("num_value_str=%s, should_lint=%s", cases$num_value_str, cases$should_lint)
4746

4847
linter <- implicit_integer_linter()
4948
patrick::with_parameters_test_that(
5049
"single numerical constants are properly identified ",
51-
expect_lint(num_value_str, if (should_lint) "Avoid implicit integers", linter),
50+
expect_lint(num_value_str, if (nzchar(lint_msg)) lint_msg, linter),
5251
.cases = cases
5352
)
5453
})
5554
# styler: on
5655

5756
test_that("linter returns the correct linting", {
5857
linter <- implicit_integer_linter()
59-
lint_msg <- rex::rex("Avoid implicit integers. Use e.g. 1L for integers or 1.0 for doubles.")
58+
lint_msg <- rex::rex("Use 1L or 1.0 to avoid implicit integers.")
6059

6160
expect_lint("x <<- 1L", NULL, linter)
6261
expect_lint("1.0/-Inf -> y", NULL, linter)
@@ -67,7 +66,7 @@ test_that("linter returns the correct linting", {
6766
)
6867
expect_lint(
6968
"z <- 1e5",
70-
list(message = lint_msg, line_number = 1L, column_number = 9L),
69+
list(message = rex::rex("100000L or 100000.0"), line_number = 1L, column_number = 9L),
7170
linter
7271
)
7372
expect_lint(
@@ -78,8 +77,8 @@ test_that("linter returns the correct linting", {
7877
expect_lint(
7978
"552^9",
8079
list(
81-
list(message = lint_msg, line_number = 1L, column_number = 4L),
82-
list(message = lint_msg, line_number = 1L, column_number = 6L)
80+
list(message = rex::rex("552L or 552.0"), line_number = 1L, column_number = 4L),
81+
list(message = rex::rex("9L or 9.0"), line_number = 1L, column_number = 6L)
8382
),
8483
linter
8584
)
@@ -90,7 +89,7 @@ patrick::with_parameters_test_that(
9089
"numbers in a:b input are optionally not linted",
9190
expect_lint(
9291
paste0(left, ":", right),
93-
if (n_lints > 0L) rep(list("Avoid implicit integers"), n_lints),
92+
if (n_lints > 0L) rep(list(rex::rex("Use 1L or 1.0")), n_lints),
9493
implicit_integer_linter(allow_colon = allow_colon)
9594
),
9695
.cases = tibble::tribble(

0 commit comments

Comments
 (0)