Skip to content

Commit

Permalink
Merge pull request #129 from saurfang/commas_linter
Browse files Browse the repository at this point in the history
Get correct line_number in commas_linter
  • Loading branch information
jimhester committed Dec 29, 2015
2 parents 980e5cd + 08e3507 commit bcf542b
Show file tree
Hide file tree
Showing 3 changed files with 15 additions and 10 deletions.
11 changes: 6 additions & 5 deletions R/commas_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,8 @@ commas_linter <- function(source_file) {

res <- re_matches(source_file$lines, re, global = TRUE, locations = TRUE)

lapply(seq_along(res), function(line_number) {
lapply(seq_along(res), function(id) {
line_number <- names(source_file$lines)[id]

mapply(
FUN = function(start, end) {
Expand All @@ -17,7 +18,7 @@ commas_linter <- function(source_file) {

lints <- list()

line <- unname(source_file$lines[[line_number]])
line <- unname(source_file$lines[[id]])

comma_loc <- start + re_matches(substr(line, start, end), rex(","), locations = TRUE)$start - 1L

Expand Down Expand Up @@ -62,7 +63,7 @@ commas_linter <- function(source_file) {
Lint(
filename = source_file$filename,
line_number = line_number,
column_number = comma_loc,
column_number = comma_loc + 1,
type = "style",
message = "Commas should always have a space after.",
line = line,
Expand All @@ -74,8 +75,8 @@ commas_linter <- function(source_file) {

lints
},
start = res[[line_number]]$start,
end = res[[line_number]]$end,
start = res[[id]]$start,
end = res[[id]]$end,
SIMPLIFY = FALSE
)
})
Expand Down
10 changes: 5 additions & 5 deletions R/get_source_expressions.R
Original file line number Diff line number Diff line change
Expand Up @@ -282,16 +282,16 @@ fix_eq_assign <- function(pc) {
pc[next_loc, "parent"] <- id[i]
}
res <- rbind(pc, data.frame(line1, col1, line2, col2, id, parent, token, terminal, text, row.names=id))
res[order(res$line1, res$col1, res$line2, res$col2, res$id),]
res[order(res$line1, res$col1, res$line2, res$col2, res$id), ]
}

prev_with_parent <- function(pc, loc) {

id <- pc$id[loc]
parent_id <- pc$parent[loc]

with_parent <- pc[pc$parent == parent_id,]
with_parent <- with_parent[order(with_parent$line1, with_parent$col1, with_parent$line2, with_parent$col2),]
with_parent <- pc[pc$parent == parent_id, ]
with_parent <- with_parent[order(with_parent$line1, with_parent$col1, with_parent$line2, with_parent$col2), ]

loc <- which(with_parent$id == id)

Expand All @@ -303,8 +303,8 @@ next_with_parent <- function(pc, loc) {
id <- pc$id[loc]
parent_id <- pc$parent[loc]

with_parent <- pc[pc$parent == parent_id,]
with_parent <- with_parent[order(with_parent$line1, with_parent$col1, with_parent$line2, with_parent$col2),]
with_parent <- pc[pc$parent == parent_id, ]
with_parent <- with_parent[order(with_parent$line1, with_parent$col1, with_parent$line2, with_parent$col2), ]

loc <- which(with_parent$id == id)

Expand Down
4 changes: 4 additions & 0 deletions tests/testthat/test-commas_linter.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,10 @@ test_that("returns the correct linting", {
rex("Commas should always have a space after."),
commas_linter)

expect_lint("\nfun(1,1)",
rex("Commas should always have a space after."),
commas_linter)

expect_lint("fun(1 ,1)",
list(
rex("Commas should never have a space before."),
Expand Down

0 comments on commit bcf542b

Please sign in to comment.