Skip to content

Commit 7a4fcee

Browse files
use normalizePath() in find_package() (#1765)
* use normalizePath() in find_package() fixes #1759 * allow undesirable_operator ::: in test-settings.R * d'oh * remove unnecessary testthat.R * add back testthat.R without comments Co-authored-by: Indrajeet Patil <[email protected]>
1 parent f486464 commit 7a4fcee

File tree

7 files changed

+31
-3
lines changed

7 files changed

+31
-3
lines changed

NEWS.md

+2
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@
1313

1414
* `namespace_linter()` correctly recognizes backticked operators to be exported from respectives namespaces (like `` rlang::`%||%` ``) (#1752, @IndrajeetPatil)
1515

16+
* `lint_package()` correctly finds a package from within a subdir if the `path` points to anywhere within the package (#1759, @AshesITR)
17+
1618
## Changes to defaults
1719

1820
* Set the default for the `except` argument in `duplicate_argument_linter()` to `c("mutate", "transmute")`.

R/settings_utils.R

+1
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ has_description <- function(path) {
44
}
55

66
find_package <- function(path) {
7+
path <- normalizePath(path)
78
depth <- 2L
89
while (!has_description(path)) {
910
path <- dirname(path)

tests/testthat/dummy_packages/assignmentLinter/DESCRIPTION

+3
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,6 @@ Author: Who wrote it
77
Maintainer: Who to complain to <[email protected]>
88
Description: More about what it does (maybe more than one line)
99
License: What license is it under?
10+
Suggests:
11+
testthat (>= 3.0.0)
12+
Config/testthat/edition: 3
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
library(testthat)
2+
library(assignmentLinter)
3+
4+
test_check("assignmentLinter")
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
test_that("test abc", {
2+
expect_equal(2 * 2, 4)
3+
})

tests/testthat/test-lint_package.R

+13-1
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,11 @@ test_that(
9191
)
9292
lints_from_a_subdir <- withr::with_dir(
9393
file.path(pkg_path, "R"),
94-
lint_package("..", linters = list(assignment_linter()))
94+
lint_package(".", linters = list(assignment_linter()))
95+
)
96+
lints_from_a_subsubdir <- withr::with_dir(
97+
file.path(pkg_path, "tests", "testthat"),
98+
lint_package(".", linters = list(assignment_linter()))
9599
)
96100

97101
expect_identical(
@@ -114,6 +118,14 @@ test_that(
114118
"(.lintr config present)"
115119
)
116120
)
121+
expect_identical(
122+
as.data.frame(lints_from_outside),
123+
as.data.frame(lints_from_a_subsubdir),
124+
info = paste(
125+
"lint_package() finds the same lints from a sub-subdir as from outside a pkg",
126+
"(.lintr config present)"
127+
)
128+
)
117129
}
118130
)
119131

tests/testthat/test-settings.R

+5-2
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
# nolint start: undesirable_operator.
2+
# This test file tests multiple internal lintr functions, so we need to allow lintr:::*
13
test_that("it uses default settings if none provided", {
24
lintr:::read_settings(NULL)
35

@@ -98,8 +100,8 @@ test_that("it has a smart default for encodings", {
98100
lintr:::read_settings(NULL)
99101
expect_identical(settings$encoding, "UTF-8")
100102

101-
proj_file <- test_path("dummy_projects", "project", "metropolis-hastings-rho.R")
102-
pkg_file <- test_path("dummy_packages", "cp1252", "R", "metropolis-hastings-rho.R")
103+
proj_file <- test_path("dummy_projects", "project", "cp1252.R")
104+
pkg_file <- test_path("dummy_packages", "cp1252", "R", "cp1252.R")
103105

104106
expect_identical(
105107
normalizePath(find_rproj_at(find_rproj_or_package(proj_file)), winslash = "/"),
@@ -119,3 +121,4 @@ test_that("it has a smart default for encodings", {
119121
lintr:::read_settings(pkg_file)
120122
expect_identical(settings$encoding, "ISO8859-1")
121123
})
124+
# nolint end

0 commit comments

Comments
 (0)