diff --git a/.travis.yml b/.travis.yml index 60b1c51..62b8604 100644 --- a/.travis.yml +++ b/.travis.yml @@ -18,7 +18,7 @@ addons: - libmagick++-dev - libssh2-1-dev -# OS X (R release only) +# Matrix: 3x Linux, 1x OS X matrix: include: - r: oldrel @@ -28,6 +28,9 @@ matrix: r_github_packages: - krlmlr/pkgdown@develop - krlmlr/travis@develop + r_packages: + - covr + - roxygen2 - r: devel - os: osx osx_image: xcode7.2 @@ -37,7 +40,6 @@ matrix: #r_packages r_packages: - covr - - roxygen2 #notifications notifications: @@ -48,13 +50,18 @@ notifications: #after_success (deploy to gh-pages and run covr) after_success: - scripts/deploy-pages.sh - - R -e 'covr::codecov()'; fi + - R -e 'covr::codecov()' # Custom parts: #r_github_packages (also need to add to the matrix definition above) -#r_packages (need to copy packages included above) +#r_packages (need to copy packages included above, and add to the matrix definition) #env (need to copy settings from above) +# services + +#before_install + +# before_script diff --git a/DESCRIPTION b/DESCRIPTION index 8a2e982..1706ae1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: rprojroot Title: Finding Files in Project Subdirectories -Version: 1.0-6 +Version: 1.0-7 Authors@R: person(given = "Kirill", family = "Müller", role = c("aut", "cre"), email = "krlmlr+r@mailbox.org") Description: Robust, reliable and flexible paths to files below a @@ -9,6 +9,8 @@ Description: Robust, reliable and flexible paths to files below a regular file. Depends: R (>= 3.0.0) +Imports: + backports Suggests: testthat, knitr, diff --git a/NAMESPACE b/NAMESPACE index 876c516..1773a49 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -10,14 +10,20 @@ S3method(str,root_criteria) export(as.root_criterion) export(criteria) export(find_package_root_file) +export(find_remake_root_file) export(find_root) export(find_root_file) export(find_rstudio_root_file) +export(find_testthat_root_file) export(from_wd) +export(has_dirname) export(has_file) export(has_file_pattern) export(is.root_criterion) export(is_r_package) +export(is_remake_project) export(is_rstudio_project) +export(is_testthat) export(root_criterion) +import(backports) importFrom(utils,str) diff --git a/NEWS.md b/NEWS.md index f1759ae..9b8bb4a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,7 +1,16 @@ +## rprojroot 1.0-7 (2016-10-23) + +- New `is_testthat` and `find_testthat_root_file()` that looks for `tests/testthat` root (#14). +- Improve navbar on project page. +- Uses `backports` to simplify compatibility with R 3.0.0. +- New `is_remake_project` and `find_remake_root_file()` that looks for remate project (#17). + + ## rprojroot 1.0-6 (2016-10-22) - Travis tests three R versions, and OS X. + ## rprojroot 1.0-5 (2016-10-22) - Use Travis instead of wercker. diff --git a/R/criterion.R b/R/criterion.R index 95b382e..3af337b 100644 --- a/R/criterion.R +++ b/R/criterion.R @@ -10,6 +10,7 @@ #' if the directory specified by this parameter is the project root, #' and \code{FALSE} otherwise #' @param desc A textual description of the test criterion +#' @param subdir Subdirectories to start the search in, if found #' #' @return #' An S3 object of class \code{root_criterion} wit the following members: @@ -25,10 +26,20 @@ #' \dontrun{ #' is_r_package$make_fix_file(".") #' } -root_criterion <- function(testfun, desc) { +root_criterion <- function(testfun, desc, subdir = NULL) { if (!isTRUE(all.equal(names(formals(testfun)), "path"))) { stop("testfun must be a function with one argument 'path'") } + + full_desc <- paste0( + desc, + if (!is.null(subdir)) paste0( + " (also look in subdirectories: ", + paste0("'", subdir, "'", collapse = ", "), + ")" + ) + ) + criterion <- structure( list( #' @return @@ -36,7 +47,9 @@ root_criterion <- function(testfun, desc) { #' \item{\code{testfun}}{The \code{testfun} argument} testfun = testfun, #' \item{\code{desc}}{The \code{desc} argument} - desc = desc + desc = full_desc, + #' \item{\code{subdir}}{The \code{subdir} argument} + subdir = subdir ), class = "root_criterion" ) diff --git a/R/file.R b/R/file.R index 6125506..a1e44bb 100644 --- a/R/file.R +++ b/R/file.R @@ -11,8 +11,9 @@ #' @param criterion A criterion, will be coerced using #' \code{\link{as.root_criterion}} #' @param path The start directory -#' @param ... Additional arguments passed to \code{\link{file.path}} -#' @return The normalized path of the root as specified by the search criteria. +#' @param ... Further path components passed to \code{\link{file.path}} +#' @return The normalized path of the root as specified by the search criteria, +#' with the additional path components appended. #' Throws an error if no root is found #' #' @examples diff --git a/R/has-file.R b/R/has-file.R index 9a5cbd1..04f1bfe 100644 --- a/R/has-file.R +++ b/R/has-file.R @@ -66,15 +66,40 @@ has_file_pattern <- function(pattern, contents = NULL, n = -1L) { root_criterion(testfun, desc) } +#' @details +#' The \code{has_dirname} function constructs a criterion that checks if the +#' \code{\link[base]{dirname}} has a specific name. +#' +#' @rdname root_criterion +#' @param dirname A directory name, without subdirectories +#' @export +has_dirname <- function(dirname, subdir = NULL) { + force(dirname) + + testfun <- eval(bquote(function(path) { + dir.exists(file.path(dirname(path), .(dirname))) + })) + + desc <- paste0("Directory name is '", dirname, "'") + + root_criterion(testfun, desc, subdir = subdir) +} + #' @export is_rstudio_project <- has_file_pattern("[.]Rproj$", contents = "^Version: ", n = 1L) #' @export is_r_package <- has_file("DESCRIPTION", contents = "^Package: ") +#' @export +is_remake_project <- has_file("remake.yml") + #' @export from_wd <- root_criterion(function(path) TRUE, "From current working directory") +#' @export +is_testthat <- has_dirname("testthat", c("tests/testthat", "testthat")) + #' Prespecified criteria #' #' This is a collection of commonly used root criteria. @@ -84,6 +109,8 @@ criteria <- structure( list( is_rstudio_project = is_rstudio_project, is_r_package = is_r_package, + is_remake_project = is_remake_project, + is_testthat = is_testthat, from_wd = from_wd ), class = "root_criteria") @@ -108,6 +135,21 @@ str.root_criteria <- function(object, ...) { #' @export "is_r_package" +#' @details +#' \code{is_remake_project} looks for a \code{remake.yml} file. +#' +#' @rdname criteria +#' @export +"is_remake_project" + +#' @details +#' \code{is_testthat} looks for the \code{testthat} directory, works when +#' developing, testing, and checking a package. +#' +#' @rdname criteria +#' @export +"is_testthat" + #' @details #' \code{from_wd} uses the current working directory. #' @@ -124,10 +166,7 @@ list_files <- function(path, filename) { } is_dir <- function(x) { - if (getRversion() >= "3.2") - file.info(x, extra_cols = FALSE)$isdir - else - file.info(x)$isdir + dir.exists(x) } match_contents <- function(f, contents, n) { diff --git a/R/root.R b/R/root.R index c02c980..d52a332 100644 --- a/R/root.R +++ b/R/root.R @@ -26,8 +26,7 @@ find_root <- function(criterion, path = ".") { criterion <- as.root_criterion(criterion) - original_path <- path - path <- normalizePath(path, winslash = "/", mustWork = TRUE) + path <- start_path(path, criterion$subdir) for (i in seq_len(.MAX_DEPTH)) { if (criterion$testfun(path)) { @@ -47,6 +46,19 @@ find_root <- function(criterion, path = ".") { .MAX_DEPTH <- 100L +start_path <- function(path, subdirs) { + path <- normalizePath(path, winslash = "/", mustWork = TRUE) + + for (subdir in subdirs) { + subdir_path <- file.path(path, subdir) + if (dir.exists(subdir_path)) { + return(subdir_path) + } + } + + path +} + # Borrowed from devtools is_root <- function(path) { identical(normalizePath(path, winslash = "/"), diff --git a/R/rprojroot-package.R b/R/rprojroot-package.R index 6b14ed9..8f38d4f 100644 --- a/R/rprojroot-package.R +++ b/R/rprojroot-package.R @@ -5,7 +5,10 @@ #' #' @examples #' criteria +#' \dontrun{ #' is_r_package$find_file("NAMESPACE") #' root_fun <- is_r_package$make_fix_file() #' root_fun("NAMESPACE") +#' } +#' @import backports "_PACKAGE" diff --git a/R/shortcut.R b/R/shortcut.R index 08d5cba..8cdb366 100644 --- a/R/shortcut.R +++ b/R/shortcut.R @@ -5,3 +5,11 @@ find_rstudio_root_file <- is_rstudio_project$find_file #' @rdname find_root_file #' @export find_package_root_file <- is_r_package$find_file + +#' @rdname find_root_file +#' @export +find_remake_root_file <- is_remake_project$find_file + +#' @rdname find_root_file +#' @export +find_testthat_root_file <- is_testthat$find_file diff --git a/README.md b/README.md index 7445f36..55489fc 100644 --- a/README.md +++ b/README.md @@ -35,4 +35,4 @@ Install from GitHub: devtools::install_github("krlmlr/rprojroot") ``` -See the [vignette](http://krlmlr.github.io/rprojroot/vignettes/rprojroot.html) for more detail. +See the [documentation](http://krlmlr.github.io/rprojroot/articles/rprojroot.html) for more detail. diff --git a/_pkgdown.yml b/_pkgdown.yml index 1303a74..b042bb4 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -1,3 +1,12 @@ template: bootswatch: flatly # https://bootswatch.com/flatly/ +navbar: + type: default + left: + - text: Documentation + href: articles/rprojroot.html + - text: Reference + href: reference/index.html + - text: News + href: news/index.html diff --git a/man/criteria.Rd b/man/criteria.Rd index d6db9d3..a2e096c 100644 --- a/man/criteria.Rd +++ b/man/criteria.Rd @@ -5,9 +5,11 @@ \alias{criteria} \alias{from_wd} \alias{is_r_package} +\alias{is_remake_project} \alias{is_rstudio_project} +\alias{is_testthat} \title{Prespecified criteria} -\format{An object of class \code{root_criteria} of length 3.} +\format{An object of class \code{root_criteria} of length 5.} \usage{ criteria @@ -15,6 +17,10 @@ is_rstudio_project is_r_package +is_remake_project + +is_testthat + from_wd } \description{ @@ -25,6 +31,11 @@ This is a collection of commonly used root criteria. \code{is_r_package} looks for a \code{DESCRIPTION} file. +\code{is_remake_project} looks for a \code{remake.yml} file. + +\code{is_testthat} looks for the \code{testthat} directory, works when + developing, testing, and checking a package. + \code{from_wd} uses the current working directory. } \keyword{datasets} diff --git a/man/find_root_file.Rd b/man/find_root_file.Rd index 54ced59..9a1a706 100644 --- a/man/find_root_file.Rd +++ b/man/find_root_file.Rd @@ -2,8 +2,10 @@ % Please edit documentation in R/file.R, R/shortcut.R \name{find_root_file} \alias{find_package_root_file} +\alias{find_remake_root_file} \alias{find_root_file} \alias{find_rstudio_root_file} +\alias{find_testthat_root_file} \title{File paths relative to the root of a directory hierarchy} \usage{ find_root_file(..., criterion, path = ".") @@ -11,9 +13,13 @@ find_root_file(..., criterion, path = ".") find_rstudio_root_file(..., path = ".") find_package_root_file(..., path = ".") + +find_remake_root_file(..., path = ".") + +find_testthat_root_file(..., path = ".") } \arguments{ -\item{...}{Additional arguments passed to \code{\link{file.path}}} +\item{...}{Further path components passed to \code{\link{file.path}}} \item{criterion}{A criterion, will be coerced using \code{\link{as.root_criterion}}} @@ -21,7 +27,8 @@ find_package_root_file(..., path = ".") \item{path}{The start directory} } \value{ -The normalized path of the root as specified by the search criteria. +The normalized path of the root as specified by the search criteria, + with the additional path components appended. Throws an error if no root is found } \description{ diff --git a/man/root_criterion.Rd b/man/root_criterion.Rd index c26c37b..1320e93 100644 --- a/man/root_criterion.Rd +++ b/man/root_criterion.Rd @@ -4,13 +4,14 @@ \alias{as.root_criterion} \alias{as.root_criterion.character} \alias{as.root_criterion.root_criterion} +\alias{has_dirname} \alias{has_file} \alias{has_file_pattern} \alias{is.root_criterion} \alias{root_criterion} \title{Is a directory the project root?} \usage{ -root_criterion(testfun, desc) +root_criterion(testfun, desc, subdir = NULL) is.root_criterion(x) @@ -23,6 +24,8 @@ as.root_criterion(x) has_file(filepath, contents = NULL, n = -1L) has_file_pattern(pattern, contents = NULL, n = -1L) + +has_dirname(dirname, subdir = NULL) } \arguments{ \item{testfun}{A function with one parameter that returns \code{TRUE} @@ -31,6 +34,8 @@ and \code{FALSE} otherwise} \item{desc}{A textual description of the test criterion} +\item{subdir}{Subdirectories to start the search in, if found} + \item{x}{An object} \item{filepath}{File path (can contain directories)} @@ -42,6 +47,8 @@ and \code{FALSE} otherwise} input on the connection.} \item{pattern}{Regular expression to match the file name} + +\item{dirname}{A directory name, without subdirectories} } \value{ An S3 object of class \code{root_criterion} wit the following members: @@ -49,6 +56,7 @@ An S3 object of class \code{root_criterion} wit the following members: \describe{ \item{\code{testfun}}{The \code{testfun} argument} \item{\code{desc}}{The \code{desc} argument} + \item{\code{subdir}}{The \code{subdir} argument} \item{\code{find_file}}{A function with \code{...} argument that returns for a path relative to the root specified by this criterion. The optional \code{path} argument specifies the starting directory, @@ -81,6 +89,9 @@ root) with specific contents. The \code{has_file_pattern} function constructs a criterion that checks for the existence of a file that matches a pattern, with specific contents. + +The \code{has_dirname} function constructs a criterion that checks if the +\code{\link[base]{dirname}} has a specific name. } \examples{ root_criterion(function(path) file.exists(file.path(path, "somefile")), "Has somefile") diff --git a/man/rprojroot-package.Rd b/man/rprojroot-package.Rd index c6801f8..ce42a68 100644 --- a/man/rprojroot-package.Rd +++ b/man/rprojroot-package.Rd @@ -18,8 +18,10 @@ root criteria. } \examples{ criteria +\dontrun{ is_r_package$find_file("NAMESPACE") root_fun <- is_r_package$make_fix_file() root_fun("NAMESPACE") } +} diff --git a/readme/README.Rmd b/readme/README.Rmd index d162657..b51fcc4 100644 --- a/readme/README.Rmd +++ b/readme/README.Rmd @@ -46,4 +46,4 @@ Install from GitHub: devtools::install_github("krlmlr/rprojroot") ``` -See the [vignette](http://krlmlr.github.io/rprojroot/vignettes/rprojroot.html) for more detail. +See the [documentation](http://krlmlr.github.io/rprojroot/articles/rprojroot.html) for more detail. diff --git a/tests/testthat/package/DESCRIPTION b/tests/testthat/package/DESCRIPTION new file mode 100644 index 0000000..e69de29 diff --git a/tests/testthat/package/tests/testthat.R b/tests/testthat/package/tests/testthat.R new file mode 100644 index 0000000..e69de29 diff --git a/tests/testthat/package/tests/testthat/.gitignore b/tests/testthat/package/tests/testthat/.gitignore new file mode 100644 index 0000000..e69de29 diff --git a/tests/testthat/package/tests/testthat/test-something.R b/tests/testthat/package/tests/testthat/test-something.R new file mode 100644 index 0000000..e69de29 diff --git a/tests/testthat/test-criterion.R b/tests/testthat/test-criterion.R index 90be437..f1573b7 100644 --- a/tests/testthat/test-criterion.R +++ b/tests/testthat/test-criterion.R @@ -34,6 +34,8 @@ test_that("Formatting criteria", { }) test_that("Combining criteria", { + skip_on_cran() + comb_crit <- is_r_package | is_rstudio_project expect_true(is.root_criterion(comb_crit)) diff --git a/tests/testthat/test-root.R b/tests/testthat/test-root.R index df694e5..da39969 100644 --- a/tests/testthat/test-root.R +++ b/tests/testthat/test-root.R @@ -63,8 +63,42 @@ test_that("has_file_pattern", { ) }) +test_that("has_dirname", { + wd <- normalizePath(getwd(), winslash = "/") + hierarchy <- function(n = 0L) { + do.call(file.path, list(wd, "hierarchy", "a", "b", "c")[seq_len(n + 1L)]) + } + + stop_path <- hierarchy(1L) + path <- hierarchy(4L) + + with_mock( + `rprojroot:::is_root` = function(x) x == stop_path, + expect_equal(find_root(has_dirname("a"), path = path), hierarchy(2L)), + expect_equal(find_root(has_dirname("b"), path = path), hierarchy(3L)), + expect_equal(find_root_file("c", criterion = has_dirname("b"), path = path), + file.path(hierarchy(3L), "c")), + expect_equal(find_root(has_dirname("c"), path = path), hierarchy(4L)), + expect_error(find_root(has_dirname("d"), path = path), + "No root directory found.* is '.*'"), + expect_error(find_root(has_dirname("rprojroot.Rproj"), path = path), + "No root directory found.* is '.*'"), + TRUE + ) +}) + test_that("finds root", { skip_on_cran() # Checks that search for root actually terminates expect_error(find_root("/"), "No root directory found.* file '.*'") }) + +test_that("stops if depth reached", { + find_root_mocked <- find_root + mock_env <- new.env() + mock_env$dirname <- identity + environment(find_root_mocked) <- mock_env + + # Checks that search for root terminates for very deep hierarchies + expect_error(find_root_mocked(""), "Maximum search of [0-9]+ exceeded") +}) diff --git a/tests/testthat/test-testthat.R b/tests/testthat/test-testthat.R new file mode 100644 index 0000000..0553586 --- /dev/null +++ b/tests/testthat/test-testthat.R @@ -0,0 +1,14 @@ +context("testthat") + +test_that("is_testthat", { + expect_match(format(is_testthat), "^.*Directory name is 'testthat' .* subdirectories.*'tests/testthat'.*'testthat'.*$") + + testthat_path <- normalizePath("package/tests/testthat", winslash = "/") + expect_equal(is_testthat$find_file(path = "package"), testthat_path) + expect_equal(is_testthat$find_file(path = "package/tests"), testthat_path) + expect_equal(is_testthat$find_file(path = "package/tests/testthat"), testthat_path) +}) + +test_that("dogfood", { + expect_true(file.exists(is_testthat$find_file("hierarchy", "a", "b", "c", "d"))) +}) diff --git a/vignettes/rprojroot.Rmd b/vignettes/rprojroot.Rmd index 348a35f..28d725d 100644 --- a/vignettes/rprojroot.Rmd +++ b/vignettes/rprojroot.Rmd @@ -255,6 +255,33 @@ Take a look at the `thisfile()` function in the `kimisc` package for getting the path to the current script or `knitr` document. +## `testthat` files + +Tests run with [`testthat`](https://cran.r-project.org/package=testthat) +commonly use files that live below the `tests/testthat` directory. +Ideally, this should work in the following situation: + +- During package development (working directory: package root) +- When testing with `devtools::test()` (working directory: `tests/testthat`) +- When running `R CMD check` (working directory: a renamed recursive copy of `tests`) + +The `is_testthat` criterion allows robust lookup of test files. + +```{r} +is_testthat +``` + +The example code below lists all files in the +[hierarchy](https://github.com/krlmlr/rprojroot/tree/master/tests/testthat/hierarchy) +test directory. +It uses two project root lookups in total, +so that it also works when rendering the vignette (*sigh*): + +```{r} +dir(is_testthat$find_file("hierarchy", path = is_r_package$find_file())) +``` + + ## Summary The `rprojroot` package allows easy access to files below a project root