From 5d0f7349cf11754f1d13817e8e53f64e365c2582 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Tue, 5 Dec 2023 19:37:20 +0100 Subject: [PATCH 01/17] feat: `use_lintr`adds .lintr to .Rbuildignore --- R/use_lintr.R | 20 ++++++++++++++++++-- man/use_lintr.Rd | 2 +- 2 files changed, 19 insertions(+), 3 deletions(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index 235946c6b..835115383 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -1,6 +1,6 @@ #' Use lintr in your project #' -#' Create a minimal lintr config file as a starting point for customization +#' Create a minimal lintr config file as a starting point for customization and add it to the .Rbuildignore #' #' @param path Path to project root, where a `.lintr` file should be created. #' If the `.lintr` file already exists, an error will be thrown. @@ -25,7 +25,7 @@ #' lintr::lint_dir() #' } use_lintr <- function(path = ".", type = c("tidyverse", "full")) { - config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = FALSE) + config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = FALSE, winslash = "/") if (file.exists(config_file)) { stop("Found an existing configuration file at '", config_file, "'.") } @@ -43,5 +43,21 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ) ) write.dcf(the_config, config_file, width = Inf) + + # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" + pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") + if(startsWith(config_file, prefix = pkg_path)) { + # Skip a extra character for the leading `/` + rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) + ignore_path <- file.path(pkg_path, ".Rbuildignore") + if (!file.exists(ignore_path)) file.create(ignore_path) + # Follow the same procedure as base R to see if the file is already ignored + ignore <- trimws(readLines(ignore_path, warn = FALSE)) + ignore <- ignore[nzchar(ignore)] + if(!any(vapply(ignore, \(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { + cat(file = ignore_path, paste0("^", rel_path, "$"), "\n", append = TRUE) + } + } + invisible(config_file) } diff --git a/man/use_lintr.Rd b/man/use_lintr.Rd index 701e1042c..a1497bc91 100644 --- a/man/use_lintr.Rd +++ b/man/use_lintr.Rd @@ -21,7 +21,7 @@ These are suitable for following \href{https://style.tidyverse.org/}{the tidyver Path to the generated configuration, invisibly. } \description{ -Create a minimal lintr config file as a starting point for customization +Create a minimal lintr config file as a starting point for customization and add it to the .Rbuildignore } \examples{ if (FALSE) { From fdb2307780f9310bc0b3bd085fab97a1e86b3307 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Wed, 6 Dec 2023 19:20:12 +0100 Subject: [PATCH 02/17] mnt: Fix linted code --- R/use_lintr.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index 835115383..f8eb3ea39 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -46,7 +46,7 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") - if(startsWith(config_file, prefix = pkg_path)) { + if (startsWith(config_file, prefix = pkg_path)) { # Skip a extra character for the leading `/` rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) ignore_path <- file.path(pkg_path, ".Rbuildignore") @@ -54,7 +54,7 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { # Follow the same procedure as base R to see if the file is already ignored ignore <- trimws(readLines(ignore_path, warn = FALSE)) ignore <- ignore[nzchar(ignore)] - if(!any(vapply(ignore, \(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { + if (!any(vapply(ignore, function(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { cat(file = ignore_path, paste0("^", rel_path, "$"), "\n", append = TRUE) } } From ee7c47c6f537af50112d3964fee21ccf7dc2f319 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Wed, 6 Dec 2023 19:22:36 +0100 Subject: [PATCH 03/17] mnt: Use rex for regex escaping --- R/use_lintr.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index f8eb3ea39..b5612dee2 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -55,7 +55,7 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ignore <- trimws(readLines(ignore_path, warn = FALSE)) ignore <- ignore[nzchar(ignore)] if (!any(vapply(ignore, function(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { - cat(file = ignore_path, paste0("^", rel_path, "$"), "\n", append = TRUE) + cat(file = ignore_path, rex::rex(start, rel_path, end), sep = "\n", append = TRUE) } } From 7f538d0aed77632c9c0eaadda689cd3f063963c8 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Thu, 7 Dec 2023 18:03:49 +0100 Subject: [PATCH 04/17] feat: Only add to .Rbuildignore if package --- .lintr | 50 -------------------------------------------------- R/use_lintr.R | 3 ++- 2 files changed, 2 insertions(+), 51 deletions(-) delete mode 100644 .lintr diff --git a/.lintr b/.lintr deleted file mode 100644 index 05ce17036..000000000 --- a/.lintr +++ /dev/null @@ -1,50 +0,0 @@ -linters: linters_with_defaults( - any_duplicated_linter(), - any_is_na_linter(), - backport_linter("oldrel-4", except = c("R_user_dir", "str2lang", "str2expression", "deparse1", "...names")), - consecutive_assertion_linter(), - expect_comparison_linter(), - expect_identical_linter(), - expect_length_linter(), - expect_named_linter(), - expect_not_linter(), - expect_null_linter(), - expect_s3_class_linter(), - expect_s4_class_linter(), - expect_true_false_linter(), - expect_type_linter(), - fixed_regex_linter(), - for_loop_index_linter(), - if_not_else_linter(), - implicit_assignment_linter(), - implicit_integer_linter(), - keyword_quote_linter(), - lengths_linter(), - line_length_linter(120L), - missing_argument_linter(), - nested_ifelse_linter(), - numeric_leading_zero_linter(), - outer_negation_linter(), - paste_linter(), - redundant_equals_linter(), - redundant_ifelse_linter(), - sort_linter(), - sprintf_linter(), - strings_as_factors_linter(), - undesirable_function_linter(c(Sys.setenv = NA_character_, mapply = NA_character_, structure = NA_character_)), - unnecessary_nested_if_linter(), - unnecessary_lambda_linter(), - unnecessary_concatenation_linter(allow_single_expression = FALSE), - yoda_test_linter() - ) -exclusions: list( - "inst/doc/creating_linters.R" = 1, - "inst/example/bad.R", - "tests/testthat/default_linter_testcode.R", - "tests/testthat/dummy_packages", - "tests/testthat/dummy_projects", - "tests/testthat/exclusions-test", - "tests/testthat/knitr_extended_formats", - "tests/testthat/knitr_formats", - "tests/testthat/knitr_malformed" - ) diff --git a/R/use_lintr.R b/R/use_lintr.R index b5612dee2..8b5f3cefe 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -46,7 +46,7 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") - if (startsWith(config_file, prefix = pkg_path)) { + if (file.exists("DESCRIPTION") && startsWith(config_file, prefix = pkg_path)) { # Skip a extra character for the leading `/` rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) ignore_path <- file.path(pkg_path, ".Rbuildignore") @@ -56,6 +56,7 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ignore <- ignore[nzchar(ignore)] if (!any(vapply(ignore, function(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { cat(file = ignore_path, rex::rex(start, rel_path, end), sep = "\n", append = TRUE) + message("Adding ", rel_path, " to .Rbuildignore") } } From fb9e003b7a7500e1cc579346516138b9a1d077e4 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Thu, 7 Dec 2023 18:07:26 +0100 Subject: [PATCH 05/17] feat: Handle .Rbuildignore w/o final new line --- R/use_lintr.R | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index 8b5f3cefe..c90507f98 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -52,7 +52,10 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ignore_path <- file.path(pkg_path, ".Rbuildignore") if (!file.exists(ignore_path)) file.create(ignore_path) # Follow the same procedure as base R to see if the file is already ignored - ignore <- trimws(readLines(ignore_path, warn = FALSE)) + tryCatch({ + ignore <- trimws(readLines(ignore_path, warn = FALSE)) + }, warning = function(e) cat(file = ignore_path, "\n", append = TRUE) + ) ignore <- ignore[nzchar(ignore)] if (!any(vapply(ignore, function(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { cat(file = ignore_path, rex::rex(start, rel_path, end), sep = "\n", append = TRUE) From 8f9bb6f29a13f839d9607ce791e303803f274336 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Thu, 7 Dec 2023 18:14:13 +0100 Subject: [PATCH 06/17] doc: Add to NEWS --- NEWS.md | 1 + 1 file changed, 1 insertion(+) diff --git a/NEWS.md b/NEWS.md index 7573a1288..7a2201d7d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -29,6 +29,7 @@ * `return_linter()` also has an argument `return_style` (`"implicit"` by default) which checks that all functions confirm to the specified return style of `"implicit"` or `"explicit"` (part of #884, @MichaelChirico, @AshesITR and @MEO265). * `unnecessary_lambda_linter` is extended to encourage vectorized comparisons where possible, e.g. `sapply(x, sum) > 0` instead of `sapply(x, function(x) sum(x) > 0)` (part of #884, @MichaelChirico). Toggle this behavior with argument `allow_comparison`. * `Linter()` has a new argument `linter_level` (default `NA`). This is used by `lint()` to more efficiently check for expression levels than the idiom `if (!is_lint_level(...)) { return(list()) }` (#2351, @AshesITR). +* `use_lintr()` adds the created `.lintr` file to the `.Rbuildignore` if run in a package. (#1805, @MEO265) ### New linters From 81c77612fd154af9799df064e0bfb7ff295b8795 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Thu, 7 Dec 2023 18:17:05 +0100 Subject: [PATCH 07/17] fix: Accidentally deleted .lintr while testing --- .lintr | 50 ++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 50 insertions(+) create mode 100644 .lintr diff --git a/.lintr b/.lintr new file mode 100644 index 000000000..05ce17036 --- /dev/null +++ b/.lintr @@ -0,0 +1,50 @@ +linters: linters_with_defaults( + any_duplicated_linter(), + any_is_na_linter(), + backport_linter("oldrel-4", except = c("R_user_dir", "str2lang", "str2expression", "deparse1", "...names")), + consecutive_assertion_linter(), + expect_comparison_linter(), + expect_identical_linter(), + expect_length_linter(), + expect_named_linter(), + expect_not_linter(), + expect_null_linter(), + expect_s3_class_linter(), + expect_s4_class_linter(), + expect_true_false_linter(), + expect_type_linter(), + fixed_regex_linter(), + for_loop_index_linter(), + if_not_else_linter(), + implicit_assignment_linter(), + implicit_integer_linter(), + keyword_quote_linter(), + lengths_linter(), + line_length_linter(120L), + missing_argument_linter(), + nested_ifelse_linter(), + numeric_leading_zero_linter(), + outer_negation_linter(), + paste_linter(), + redundant_equals_linter(), + redundant_ifelse_linter(), + sort_linter(), + sprintf_linter(), + strings_as_factors_linter(), + undesirable_function_linter(c(Sys.setenv = NA_character_, mapply = NA_character_, structure = NA_character_)), + unnecessary_nested_if_linter(), + unnecessary_lambda_linter(), + unnecessary_concatenation_linter(allow_single_expression = FALSE), + yoda_test_linter() + ) +exclusions: list( + "inst/doc/creating_linters.R" = 1, + "inst/example/bad.R", + "tests/testthat/default_linter_testcode.R", + "tests/testthat/dummy_packages", + "tests/testthat/dummy_projects", + "tests/testthat/exclusions-test", + "tests/testthat/knitr_extended_formats", + "tests/testthat/knitr_formats", + "tests/testthat/knitr_malformed" + ) From 09a888a228b15e1ec71b54b8126386126d4749c0 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 07:31:18 +0100 Subject: [PATCH 08/17] fix: Handle DESCRIPTION correctly --- R/use_lintr.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index c90507f98..16ebb4ecd 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -46,7 +46,7 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") - if (file.exists("DESCRIPTION") && startsWith(config_file, prefix = pkg_path)) { + if (file.exists(file.path(path, "DESCRIPTION")) && startsWith(config_file, prefix = pkg_path)) { # Skip a extra character for the leading `/` rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) ignore_path <- file.path(pkg_path, ".Rbuildignore") From 25ada69923ecc0460a791c55f8bfed47dd56dad2 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 07:32:25 +0100 Subject: [PATCH 09/17] test: Add new tests --- tests/testthat/test-use_lintr.R | 53 +++++++++++++++++++++++++++++++++ 1 file changed, 53 insertions(+) diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index 68e089322..275f77ee8 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -35,3 +35,56 @@ test_that("use_lintr with type = full also works", { lints <- lint_dir(tmp) expect_length(lints, 0L) }) + +test_that("No .Rbuildignore is created of packages", { + tmp <- withr::local_tempdir() + + lintr_file <- use_lintr(path = tmp, type = "full") + expect_false(file.exists(file.path(tmp, ".Rbuildignore"))) +}) + +test_that("No .Rbuildignore is filled outside of packages", { + tmp <- withr::local_tempdir() + ignore <- file.path(tmp, ".Rbuildignore") + file.create(ignore) + + lintr_file <- use_lintr(path = tmp, type = "full") + expect_identical(readLines(ignore), character()) +}) + +test_that("No .Rbuildignore is filled if matching regex exists", { + tmp <- withr::local_tempdir() + file.create(file.path(tmp, "DESCRIPTION")) + ignore <- file.path(tmp, ".Rbuildignore") + file.create(ignore) + cat(file = ignore, ".*", sep = "\n") + + lintr_file <- use_lintr(path = tmp, type = "full") + expect_identical(readLines(ignore), ".*") +}) + +test_that("use_lintr creates the correct regex", { + tmp <- withr::local_tempdir() + file.create(file.path(tmp, "DESCRIPTION")) + ignore <- file.path(tmp, ".Rbuildignore") + file.create(ignore) + cat(file = ignore, "fu", "bar", sep = "\n") + + expect_message({ + lintr_file <- use_lintr(path = tmp, type = "full") + }, regexp = "Adding .* to .Rbuildignore") + expect_identical(readLines(ignore), c("fu", "bar", "^\\.lintr$")) +}) + +test_that("use_lintr handles missing final new line", { + tmp <- withr::local_tempdir() + file.create(file.path(tmp, "DESCRIPTION")) + ignore <- file.path(tmp, ".Rbuildignore") + file.create(ignore) + cat(file = ignore, "fu\nbar") + + expect_message({ + lintr_file <- use_lintr(path = tmp, type = "full") + }, regexp = "Adding .* to .Rbuildignore") + expect_identical(readLines(ignore), c("fu", "bar", "^\\.lintr$")) +}) From 06f031a148395bb6a0edc919581b22710bca8918 Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 07:37:25 +0100 Subject: [PATCH 10/17] fix: Handle missing final new line --- R/use_lintr.R | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index 16ebb4ecd..80bddf4bf 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -52,10 +52,12 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ignore_path <- file.path(pkg_path, ".Rbuildignore") if (!file.exists(ignore_path)) file.create(ignore_path) # Follow the same procedure as base R to see if the file is already ignored - tryCatch({ - ignore <- trimws(readLines(ignore_path, warn = FALSE)) - }, warning = function(e) cat(file = ignore_path, "\n", append = TRUE) - ) + ignore <- tryCatch({ + trimws(readLines(ignore_path)) + }, warning = function(e) { + cat(file = ignore_path, "\n", append = TRUE) + trimws(readLines(ignore_path)) + }) ignore <- ignore[nzchar(ignore)] if (!any(vapply(ignore, function(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { cat(file = ignore_path, rex::rex(start, rel_path, end), sep = "\n", append = TRUE) From 6cb1b49558d30166280cef7b0b1f6f89bac86c1f Mon Sep 17 00:00:00 2001 From: MEO265 <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 08:26:25 +0100 Subject: [PATCH 11/17] test: More robust tests --- tests/testthat/test-use_lintr.R | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index 275f77ee8..9a5b5a99c 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -68,12 +68,12 @@ test_that("use_lintr creates the correct regex", { file.create(file.path(tmp, "DESCRIPTION")) ignore <- file.path(tmp, ".Rbuildignore") file.create(ignore) - cat(file = ignore, "fu", "bar", sep = "\n") + cat(file = ignore, "^fu$", "^bar$", sep = "\n") expect_message({ lintr_file <- use_lintr(path = tmp, type = "full") }, regexp = "Adding .* to .Rbuildignore") - expect_identical(readLines(ignore), c("fu", "bar", "^\\.lintr$")) + expect_identical(readLines(ignore), c("^fu$", "^bar$", "^\\.lintr$")) }) test_that("use_lintr handles missing final new line", { @@ -81,10 +81,10 @@ test_that("use_lintr handles missing final new line", { file.create(file.path(tmp, "DESCRIPTION")) ignore <- file.path(tmp, ".Rbuildignore") file.create(ignore) - cat(file = ignore, "fu\nbar") + cat(file = ignore, "^fu$\n^bar$") expect_message({ lintr_file <- use_lintr(path = tmp, type = "full") }, regexp = "Adding .* to .Rbuildignore") - expect_identical(readLines(ignore), c("fu", "bar", "^\\.lintr$")) + expect_identical(readLines(ignore), c("^fu$", "^bar$", "^\\.lintr$")) }) From 24624b96b1fd5c76061aa53905f9cf0ebace018b Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 10:36:27 +0100 Subject: [PATCH 12/17] debug: Test sub-functions in test --- tests/testthat/test-use_lintr.R | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index 9a5b5a99c..d9f173dfa 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -88,3 +88,12 @@ test_that("use_lintr handles missing final new line", { }, regexp = "Adding .* to .Rbuildignore") expect_identical(readLines(ignore), c("^fu$", "^bar$", "^\\.lintr$")) }) + +test_that("use_lintr handles missing final new line", { + path <- withr::local_tempdir() + file.create(file.path(path, "DESCRIPTION")) + config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = FALSE, winslash = "/") + pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") + expect_true(startsWith(config_file, prefix = pkg_path)) + expect_true(file.exists(file.path(path, "DESCRIPTION"))) +}) From 302782edcc7d5b9e9f6522a6eb4b561782d0b2f9 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 10:51:55 +0100 Subject: [PATCH 13/17] debug: Test sub-functions in test II --- tests/testthat/test-use_lintr.R | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index d9f173dfa..a7e00d133 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -92,8 +92,10 @@ test_that("use_lintr handles missing final new line", { test_that("use_lintr handles missing final new line", { path <- withr::local_tempdir() file.create(file.path(path, "DESCRIPTION")) - config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = FALSE, winslash = "/") - pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") + config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") + pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") + warning(config_file, call. = FALSE + warning(pkg_path, call. = FALSE) expect_true(startsWith(config_file, prefix = pkg_path)) expect_true(file.exists(file.path(path, "DESCRIPTION"))) }) From bd566908a75c198cb735c1d9adb4957e251e4843 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 10:54:55 +0100 Subject: [PATCH 14/17] debug: Test sub-functions in test III --- tests/testthat/test-use_lintr.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index a7e00d133..36e6f6342 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -94,7 +94,7 @@ test_that("use_lintr handles missing final new line", { file.create(file.path(path, "DESCRIPTION")) config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") - warning(config_file, call. = FALSE + warning(config_file, call. = FALSE) warning(pkg_path, call. = FALSE) expect_true(startsWith(config_file, prefix = pkg_path)) expect_true(file.exists(file.path(path, "DESCRIPTION"))) From 1226e0c6df67570a6528b857ccc5f2aaa225aa8c Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 11:30:41 +0100 Subject: [PATCH 15/17] debug: Test sub-functions in test IV It runs locally on Windows, which surprises me --- tests/testthat/test-use_lintr.R | 1 + 1 file changed, 1 insertion(+) diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index 36e6f6342..8f75a7d16 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -92,6 +92,7 @@ test_that("use_lintr handles missing final new line", { test_that("use_lintr handles missing final new line", { path <- withr::local_tempdir() file.create(file.path(path, "DESCRIPTION")) + file.create(file.path(path, lintr_option("linter_file"))) config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") warning(config_file, call. = FALSE) From 88acd40e7bf938e59219c4176737f59e58a44266 Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 11:44:51 +0100 Subject: [PATCH 16/17] debug: Test sub-functions in test V Some OS can only normalize a path if the associated file or folder exists --- R/use_lintr.R | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index 03f85e615..088a894dc 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -44,8 +44,10 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ) write.dcf(the_config, config_file, width = Inf) + # Some OS can only normalize a path if the associated file or folder exists, so the path needs to be re-normalized + config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") + pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" - pkg_path <- normalizePath(path, mustWork = FALSE, winslash = "/") if (file.exists(file.path(path, "DESCRIPTION")) && startsWith(config_file, prefix = pkg_path)) { # Skip a extra character for the leading `/` rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) From 9e9611bf9cf81b90b596173a5778ce888f28ed8e Mon Sep 17 00:00:00 2001 From: Matthias Ollech <99362508+MEO265@users.noreply.github.com> Date: Fri, 8 Dec 2023 12:03:11 +0100 Subject: [PATCH 17/17] fix: Re-normalize path after creating files --- R/use_lintr.R | 46 +++++++++++++++++++-------------- tests/testthat/test-use_lintr.R | 12 --------- 2 files changed, 27 insertions(+), 31 deletions(-) diff --git a/R/use_lintr.R b/R/use_lintr.R index 088a894dc..d98eafa31 100644 --- a/R/use_lintr.R +++ b/R/use_lintr.R @@ -44,26 +44,34 @@ use_lintr <- function(path = ".", type = c("tidyverse", "full")) { ) write.dcf(the_config, config_file, width = Inf) - # Some OS can only normalize a path if the associated file or folder exists, so the path needs to be re-normalized - config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") - pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") - # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" - if (file.exists(file.path(path, "DESCRIPTION")) && startsWith(config_file, prefix = pkg_path)) { - # Skip a extra character for the leading `/` - rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) - ignore_path <- file.path(pkg_path, ".Rbuildignore") - if (!file.exists(ignore_path)) file.create(ignore_path) - # Follow the same procedure as base R to see if the file is already ignored - ignore <- tryCatch({ - trimws(readLines(ignore_path)) - }, warning = function(e) { - cat(file = ignore_path, "\n", append = TRUE) - trimws(readLines(ignore_path)) + if (file.exists(file.path(path, "DESCRIPTION"))) { + # Some OS can only normalize a path if the associated file or folder exists, so the path needs to be re-normalized + tryCatch({ + pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") + config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") + }, error = function(e) { + stop("No entry could be added to the .Rbuildignore.", call. = FALSE) }) - ignore <- ignore[nzchar(ignore)] - if (!any(vapply(ignore, function(x) grepl(rel_path, pattern = x, perl = TRUE, ignore.case = TRUE), logical(1L)))) { - cat(file = ignore_path, rex::rex(start, rel_path, end), sep = "\n", append = TRUE) - message("Adding ", rel_path, " to .Rbuildignore") + # Check if config_file is in package i.e. lintr_option("linter_file") != "../.lintr" + if (startsWith(config_file, prefix = pkg_path)) { + # Skip a extra character for the leading `/` + rel_path <- substring(config_file, first = nchar(pkg_path) + 2L, last = nchar(config_file)) + ignore_path <- file.path(pkg_path, ".Rbuildignore") + if (!file.exists(ignore_path)) file.create(ignore_path) + # Follow the same procedure as base R to see if the file is already ignored + ignore <- tryCatch({ + trimws(readLines(ignore_path)) + }, warning = function(e) { + cat(file = ignore_path, "\n", append = TRUE) + trimws(readLines(ignore_path)) + }) + ignore <- ignore[nzchar(ignore)] + already_ignored <- + any(vapply(ignore, FUN = grepl, x = rel_path, perl = TRUE, ignore.case = TRUE, FUN.VALUE = logical(1L))) + if (!already_ignored) { + cat(file = ignore_path, rex::rex(start, rel_path, end), sep = "\n", append = TRUE) + message("Adding ", rel_path, " to .Rbuildignore") + } } } diff --git a/tests/testthat/test-use_lintr.R b/tests/testthat/test-use_lintr.R index 8f75a7d16..9a5b5a99c 100644 --- a/tests/testthat/test-use_lintr.R +++ b/tests/testthat/test-use_lintr.R @@ -88,15 +88,3 @@ test_that("use_lintr handles missing final new line", { }, regexp = "Adding .* to .Rbuildignore") expect_identical(readLines(ignore), c("^fu$", "^bar$", "^\\.lintr$")) }) - -test_that("use_lintr handles missing final new line", { - path <- withr::local_tempdir() - file.create(file.path(path, "DESCRIPTION")) - file.create(file.path(path, lintr_option("linter_file"))) - config_file <- normalizePath(file.path(path, lintr_option("linter_file")), mustWork = TRUE, winslash = "/") - pkg_path <- normalizePath(path, mustWork = TRUE, winslash = "/") - warning(config_file, call. = FALSE) - warning(pkg_path, call. = FALSE) - expect_true(startsWith(config_file, prefix = pkg_path)) - expect_true(file.exists(file.path(path, "DESCRIPTION"))) -})