Skip to content

Commit

Permalink
Use nolint directives for undesirable_operator_linter() lints (#1748
Browse files Browse the repository at this point in the history
)
  • Loading branch information
IndrajeetPatil authored Oct 26, 2022
1 parent d0023d4 commit 15a9578
Show file tree
Hide file tree
Showing 7 changed files with 13 additions and 17 deletions.
1 change: 1 addition & 0 deletions .lintr_new
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ linters: linters_with_defaults(
redundant_ifelse_linter(),
sprintf_linter(),
strings_as_factors_linter(),
undesirable_operator_linter(),
unnecessary_lambda_linter(),
unneeded_concatenation_linter(allow_single_expression = FALSE),
yoda_test_linter()
Expand Down
2 changes: 1 addition & 1 deletion R/expect_lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ expect_lint <- function(content, checks, ..., file = NULL, language = "en") {
lint_fields <- unique(c(names(formals(Lint)), "linter"))
Map(
function(lint, check) {
itr <<- itr + 1L
itr <<- itr + 1L # nolint: undesirable_operator.
lapply(names(check), function(field) {
if (!field %in% lint_fields) {
stop(sprintf(
Expand Down
2 changes: 1 addition & 1 deletion R/get_source_expressions.R
Original file line number Diff line number Diff line change
Expand Up @@ -588,7 +588,7 @@ tab_offsets <- function(tab_columns) {
tab_columns - 1L,
function(tab_idx) {
offset <- 7L - (tab_idx + cum_offset) %% 8L # using a tab width of 8 characters
cum_offset <<- cum_offset + offset
cum_offset <<- cum_offset + offset # nolint: undesirable_operator.
offset
},
integer(1L),
Expand Down
13 changes: 4 additions & 9 deletions R/lint.R
Original file line number Diff line number Diff line change
Expand Up @@ -641,8 +641,7 @@ sarif_output <- function(lints, filename = "lintr_results.sarif") {

one_result <- append(one_result, c(ruleId = lint$linter))
one_result <- append(one_result, c(ruleIndex = rule_index))
one_result <-
append(one_result, list(message = list(text = lint$message)))
one_result <- append(one_result, list(message = list(text = lint$message)))
one_location <- list(physicalLocation = list(
artifactLocation = list(
uri = gsub("\\", "/", lint$filename, fixed = TRUE),
Expand All @@ -654,11 +653,8 @@ sarif_output <- function(lints, filename = "lintr_results.sarif") {
snippet = list(text = lint$line)
)
))
one_result <-
append(one_result, c(locations = list(list(one_location))))

sarif$runs[[1L]]$results <-
append(sarif$runs[[1L]]$results, list(one_result))
one_result <- append(one_result, c(locations = list(list(one_location))))
sarif$runs[[1L]]$results <- append(sarif$runs[[1L]]$results, list(one_result))
}

write(jsonlite::toJSON(sarif, pretty = TRUE, auto_unbox = TRUE), filename)
Expand All @@ -670,8 +666,7 @@ highlight_string <- function(message, column_number = NULL, ranges = NULL) {
line <- fill_with(" ", maximum)

lapply(ranges, function(range) {
substr(line, range[1L], range[2L]) <<-
fill_with("~", range[2L] - range[1L] + 1L)
substr(line, range[1L], range[2L]) <<- fill_with("~", range[2L] - range[1L] + 1L) # nolint: undesirable_operator.
})

substr(line, column_number, column_number + 1L) <- "^"
Expand Down
2 changes: 1 addition & 1 deletion R/object_usage_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -248,7 +248,7 @@ parse_check_usage <- function(expression,
vals <- list()

report <- function(x) {
vals[[length(vals) + 1L]] <<- x
vals[[length(vals) + 1L]] <<- x # nolint: undesirable_operator.
}

withr::with_options(
Expand Down
6 changes: 3 additions & 3 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -28,8 +28,8 @@ flatten_list <- function(x, class) {
itr <- 1L
assign_item <- function(x) {
if (inherits(x, class)) {
res[[itr]] <<- x
itr <<- itr + 1L
res[[itr]] <<- x # nolint: undesirable_operator.
itr <<- itr + 1L # nolint: undesirable_operator.
} else if (is.list(x)) {
lapply(x, assign_item)
}
Expand Down Expand Up @@ -174,7 +174,7 @@ read_lines <- function(file, encoding = settings$encoding, ...) {
readLines(file, warn = TRUE, ...),
warning = function(w) {
if (grepl("incomplete final line found on", w$message, fixed = TRUE)) {
terminal_newline <<- FALSE
terminal_newline <<- FALSE # nolint: undesirable_operator.
invokeRestart("muffleWarning")
}
}
Expand Down
4 changes: 2 additions & 2 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -295,7 +295,7 @@ settings <- NULL
}
}

default_settings <<- list(
default_settings <<- list( # nolint: undesirable_operator.
linters = default_linters,
encoding = "UTF-8",
exclude = rex::rex("#", any_spaces, "nolint"),
Expand Down Expand Up @@ -325,7 +325,7 @@ settings <- NULL
error_on_lint = logical_env("LINTR_ERROR_ON_LINT") %||% FALSE
)

settings <<- list2env(default_settings, parent = emptyenv())
settings <<- list2env(default_settings, parent = emptyenv()) # nolint: undesirable_operator.
invisible()
}
# nocov end

0 comments on commit 15a9578

Please sign in to comment.