diff --git a/R/run-examples.r b/R/run-examples.r index 51ee18864..592a5fe88 100644 --- a/R/run-examples.r +++ b/R/run-examples.r @@ -24,25 +24,27 @@ #' won't work. #' @keywords programming #' @export -run_examples <- function(pkg = ".", start = NULL, show = TRUE, test = FALSE, +run_examples <- function(pkg = ".", start = NULL, show, test = FALSE, run = TRUE, fresh = FALSE) { pkg <- as.package(pkg) - document(pkg) - if (!missing(show)) { warning("`show` is deprecated", call. = FALSE) } - files <- rd_files(pkg$path, start = start) - if (length(files) == 0) - return() - - rule("Running ", length(files), " example files in ", pkg$package) - if (fresh) { - to_run <- eval(substitute(function() devtools::run_examples(path), list(path = pkg$path))) - callr::r(to_run, show = TRUE) + to_run <- eval(substitute( + function() devtools::run_examples(path, start, test, run) + , list(path = pkg$path, start = start, test = test, run = run))) + callr::r(to_run, show = TRUE, spinner = FALSE) } else { + document(pkg) + + files <- rd_files(pkg$path, start = start) + if (length(files) == 0) + return() + + rule("Running ", length(files), " example files in ", pkg$package) + load_all(pkg$path, reset = TRUE, export_all = FALSE) on.exit(load_all(pkg$path, reset = TRUE)) diff --git a/man/run_examples.Rd b/man/run_examples.Rd index 7cf7f10a7..2d63b4eb9 100644 --- a/man/run_examples.Rd +++ b/man/run_examples.Rd @@ -4,8 +4,8 @@ \alias{run_examples} \title{Run all examples in a package.} \usage{ -run_examples(pkg = ".", start = NULL, show = TRUE, test = FALSE, - run = TRUE, fresh = FALSE) +run_examples(pkg = ".", start = NULL, show, test = FALSE, run = TRUE, + fresh = FALSE) } \arguments{ \item{pkg}{package description, can be path or package name. See