From 19b4e8808eb209c72e37c4b000cf6fb89ca93706 Mon Sep 17 00:00:00 2001 From: dgkf <18220321+dgkf@users.noreply.github.com> Date: Sat, 23 Mar 2024 23:37:50 -0400 Subject: [PATCH] user more conventional roxygen2 approach --- DESCRIPTION | 2 +- NAMESPACE | 4 - R/roxygen2.R | 353 ++++++-------------- R/testthat.R | 15 +- R/utils.R | 53 +-- R/zzz.R | 2 - inst/pkg.example/DESCRIPTION | 6 +- inst/pkg.example/NAMESPACE | 2 + inst/pkg.example/R/fn.R | 40 +++ inst/pkg.example/man/fn_roxygen.Rd | 29 +- inst/pkg.example/man/fn_roxygen_multiple.Rd | 36 ++ inst/pkg.example/man/fn_roxygen_testthat.Rd | 38 ++- man/append_test.Rd | 31 -- man/append_test_rd.Rd | 32 -- man/escape_infotex.Rd | 25 -- man/format_tests.Rd | 44 --- man/roxy_test_helpers.Rd | 19 -- man/testex-private-imports.Rd | 26 -- man/{rd.Rd => testex-roclets.Rd} | 9 +- tests/testthat/test-roxygen2-expect.R | 16 +- tests/testthat/test-roxygen2-testthat.R | 16 +- 21 files changed, 259 insertions(+), 539 deletions(-) create mode 100644 inst/pkg.example/man/fn_roxygen_multiple.Rd delete mode 100644 man/append_test.Rd delete mode 100644 man/append_test_rd.Rd delete mode 100644 man/escape_infotex.Rd delete mode 100644 man/format_tests.Rd delete mode 100644 man/roxy_test_helpers.Rd delete mode 100644 man/testex-private-imports.Rd rename man/{rd.Rd => testex-roclets.Rd} (96%) diff --git a/DESCRIPTION b/DESCRIPTION index c92ef4c..c43ba2e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -22,4 +22,4 @@ Suggests: roxygen2 Encoding: UTF-8 Roxygen: list(markdown = TRUE) -RoxygenNote: 7.2.3 +RoxygenNote: 7.3.1 diff --git a/NAMESPACE b/NAMESPACE index 269b9b7..6fbf740 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -1,11 +1,7 @@ # Generated by roxygen2: do not edit by hand -S3method(roxygen2::roclet_output,roclet_rd) -S3method(roxygen2::roclet_process,roclet_rd) S3method(roxygen2::roxy_tag_parse,roxy_tag_expect) -S3method(roxygen2::roxy_tag_parse,roxy_tag_testthat) export(expect_no_error) -export(rd) export(s3_register) export(test_examples_as_testthat) export(testex) diff --git a/R/roxygen2.R b/R/roxygen2.R index 1df9707..69b95fb 100644 --- a/R/roxygen2.R +++ b/R/roxygen2.R @@ -25,6 +25,7 @@ #' #' @expect 3 #' #' @expect . == 3 #' #' +#' #' @examples #' #' 3 + 4 #' #' @expect identical(., 7) #' } @@ -48,268 +49,162 @@ #' #' @testthat expect_equal(3) #' #' @testthat expect_gt(0) #' #' +#' #' @examples #' #' 3 + 4 #' #' @testthat expect_equal(., 7) #' } #' } #' -#' @export -rd <- function() { - roxygen2::roclet("rd") -} - -#' @importFrom utils tail -#' @exportS3Method roxygen2::roclet_process roclet_rd -roclet_process.roclet_rd <- function(x, blocks, env, base_path) { - for (bi in seq_along(blocks)) { - blocks[[bi]] <- roclet_process_testex(blocks[[bi]]) - } - - .roxygen2()$roclet_process.roclet_rd(x, blocks, env, base_path) -} - -roclet_process_testex <- function(block) { - testex_tags <- c("expect", "testthat") - - idx_ex_tag <- roclet_which_example_tag(block$tags) - if (!length(idx_ex_tag)) return(block) - - # initial example, to which we'll merge in formatted tests code - ex_tag <- block$tags[[idx_ex_tag]] - ex <- ex_tag$val +#' @name testex-roclets +NULL - # aggregate expectations and srcref line ranges for consecutive test tags - expsloc <- rep_len(ex_tag$line, 2L) - exps <- list() - - i <- idx_ex_tag + 1 - while (i <= length(block$tags)) { - # read next tag, splitting content into example code and test code - tag <- block$tags[[i]] - if (!tag$tag %in% testex_tags) break - - # update expectation line range to include next tag - if (length(exps) == 0L) expsloc[[2L]] <- tag$line - 1L - exps <- append_test(tag, exps) - - # flush expects if back to example code (remainder) or last tag of test block - is_last <- !isTRUE(tag$tag == block$tags[[i + 1]]$tag) - if (roxy_test_has_remainder(tag) || is_last) { - rd <- format_tests(tag$tag, exps, file = block$file, lines = expsloc) - ex <- append_test_rd(ex, c(rd, sub("^\n", "", tag$remainder))) - expsloc <- rep_len(tag$line + !is_last * srcref_nlines(tag$test), 2L) - exps <- list() - } - - # strip original tag from block - block$tags[i] <- list(NULL) - i <- i + 1 - } - - # filter out any tags that were merged into the example block - block$tags[[idx_ex_tag]]$val <- ex - block$tags <- Filter(Negate(is.null), block$tags) - - block -} - -roclet_which_example_tag <- function(tags) { - tags <- vcapply(tags, `[[`, "tag") - which(tags == "examples") -} -#' @exportS3Method roxygen2::roclet_output roclet_rd -roclet_output.roclet_rd <- function(...) { - .roxygen2()$roclet_output.roclet_rd(...) -} #' @importFrom utils head tail #' @exportS3Method roxygen2::roxy_tag_parse roxy_tag_expect roxy_tag_parse.roxy_tag_expect <- function(x) { - x$test <- roxy_test_try_parse(x$raw) - if (inherits(x$test, "error")) { - warning( - "Error encountered while parsing expectation. This will likely ", - "cause an error when testing examples." - ) - } - - x$test <- roxy_test_update_srcref( - x$test, - file = x$file, - offset_lines = x$line - 1L - ) - - x$remainder <- roxy_test_raw_remainder(x) - - x -} - -#' @exportS3Method roxygen2::roxy_tag_parse roxy_tag_testthat -roxy_tag_parse.roxy_tag_testthat <- roxy_tag_parse.roxy_tag_expect - -roxy_test_try_parse <- function(x) { - # try to parse first expression - res <- tryCatch( - parse(text = x, n = 1, keep.source = TRUE), - error = function(e) e - ) - - # if parsing failed, use the error message to try to subset text before - # parsing error and try to parse first expression again - if (inherits(res, "error")) { - msg <- conditionMessage(res) - err_loc_re <- ":(\\d+):(\\d+):" - m <- regexec(err_loc_re, msg)[[1L]] - loc <- substring(msg, m[-1L], m[-1L] + attr(m, "match.length")[-1L] - 1L) - loc <- as.numeric(loc) - text <- head(strsplit(x, "\n")[[1L]], loc[[1L]]) - text[[length(text)]] <- substring(tail(text, 1L), 1L, loc[[2L]] - 1L) - - res <- tryCatch( - parse(text = text, n = 1, keep.source = TRUE), - error = function(e) e - ) - } - - res + x$raw <- x$val <- format_tag_expect_test(x) + as_example(x) } -roxy_test_has_remainder <- function(tag) { - nchar(trimws(tag$remainder)) > 0 +#' @importFrom utils head tail +#' @exportS3Method roxygen2::roxy_tag_parse roxy_tag_expect +roxy_tag_parse.roxy_tag_testthat <- function(x) { + x$raw <- x$val <- format_tag_testthat_test(x) + as_example(x) } -roxy_test_update_srcref <- function(x, file, offset_lines) { - # update parsed lines with actual lines - srcref <- attr(x, "srcref")[[1]] - if (file.exists(file)) - attr(srcref, "srcfile") <- srcfile(file) - srcref[1] <- srcref[1] + offset_lines - srcref[3] <- srcref[3] + offset_lines - srcref[4] <- file_line_nchar(file, srcref[3]) - attr(x, "srcref") <- srcref - x +#' Convert a Roxygen Tag to an Examples Tag +#' +#' Allows for converting testing tags into additional `@examples` tags, which +#' `roxygen2` will joint together into a single examples section. +#' +#' @param tag A `roxygen2` tag, whose class should be converted into an +#' examples tag. +#' @return The tag with an appropriate examples s3 class. +#' +#' @noRd +#' @keywords internal +as_example <- function(tag) { + class(tag) <- class(tag)[!startsWith(class(tag), "roxy_tag_")] + class(tag) <- c("roxy_tag_examples", class(tag)) + roxygen2::tag_examples(tag) } -#' Separate the remaining text following a parsed roxygen test +#' Format An `@expect` Tag #' -#' @param x A processed roxy testex tag, including a `$test` field -#' @return the string that follows the end of the test expression +#' @param tag A `roxygen2` `@expect` tag. +#' @return A formatted string of R documentation `\testonly{}` code. #' -#' @name roxy_test_helpers +#' @noRd #' @keywords internal -roxy_test_raw_remainder <- function(x) { - xlines <- strsplit(x$raw, "\n")[[1L]] +format_tag_expect_test <- function(tag) { # nolint + parsed_test <- parse(text = tag$raw, n = 1, keep.source = TRUE) + test <- populate_expect_dot(parsed_test) + n <- first_expr_end(parsed_test) - # find coding test lines, to determine trailing raw lines - test_lines <- as.character(attr(x$test, "srcref"), useSource = TRUE) - test_loc <- c(length(test_lines), nchar(tail(test_lines, 1L))) - - paste(collapse = "\n", c( - substring(xlines[[test_loc[[1L]]]], test_loc[[2L]] + 1L), - tail(xlines, -test_loc[[1L]]) - )) + paste0( + "\\testonly{", + "testex::testex(", + deparse_pretty(test), + ")}", + trimws(substring(tag$raw, n + 1L), "right") + ) } - - -#' Format test for an Rd \\testonly block +#' Populate An Implicit `@expect` Lambda Function #' -#' @param tag The roxygen tag that we are formatting -#' @param tests A \code{list} of test \code{code} objects to be formatted into a -#' \code{\\testonly} block. -#' @param ... Additional arguments used by methods +#' When an expect tag does not contain a `.` object, its result is considered +#' an an implicit test for an identical object. #' -#' @return A formatted block of code for an Rd section +#' @param expr A (possibly) implicity lambda function +#' @return A new expression, calling identical if needed. #' -#' @rdname format_tests -#' @family roclet_process_helpers +#' @noRd #' @keywords internal -format_tests <- function(tag, tests, ...) { - if (!length(tests)) return(character(0L)) - UseMethod("format_tests", structure(1L, class = tag)) +populate_expect_dot <- function(expr) { + if (is.expression(expr)) expr <- expr[[1]] + if (!"." %in% all.names(expr)) { + expr <- bquote(identical(., .(expr))) + } + expr } -#' @rdname format_tests -format_tests.default <- function(tag, tests, file, lines) { - character(0L) -} -#' @rdname format_tests -format_tests.expect <- function(tag, tests, file, lines) { - tests <- lapply(tests, `attributes<-`, NULL) - tests <- vcapply(tests, deparse_indent, indent = 2L) - example_src <- paste0(basename(file), ":", lines[[1]], ":", lines[[2]]) - c( - "\\testonly{", - "testex::testex(", - sprintf("%s,", escape_infotex(tests)), - sprintf(" example = \"%s\"", example_src), - ")}" +#' Format An `@testthat` Tag +#' +#' @param tag A `roxygen2` `@testthat` tag. +#' @return A formatted string of R documentation `\testonly{}` code. +#' +#' @noRd +#' @keywords internal +format_tag_testthat_test <- function(tag) { # nolint + parsed_test <- parse(text = tag$raw, n = 1, keep.source = TRUE) + test <- populate_testthat_dot(parsed_test) + + n <- first_expr_end(parsed_test) + test_str <- substring(tag$raw, 1L, n) + + nlines <- string_line_count(trimws(test_str, "right")) + lines <- tag$line + c(0L, nlines) + + src <- paste0(basename(tag$file), ":", lines[[1]], ":", lines[[2]]) + desc <- sprintf("example tests at `%s`", src) + + paste0( + "\\testonly{\n", + paste0("testex::testthat_block(test_that(", deparse(desc), ", {\n"), + paste0( + "testex::with_srcref(", + "\"", src, "\", ", deparse_pretty(test), + ")\n" + ), + "}))\n", + "}", + trimws(substring(tag$raw, n + 1L), "right") ) } -#' @param file The source file where the example test code originated -#' @param lines A \code{numeric} vector of length two indicating the start and -#' end lines of the example code block tested by the test code. +#' Populate An Implicit `@testthat` Lambda Function #' -#' @rdname format_tests -format_tests.testthat <- function(tag, tests, file, lines) { - srcs <- vcapply(tests, function(i) srcref_key(attr(i, "srcref"), nloc = 2L)) - tests <- vapply(tests, deparse_indent, character(1L), indent = 2L) - example_src <- paste0(basename(file), ":", lines[[1]], ":", lines[[2]]) - desc <- sprintf("example tests at `%s`", example_src) - - c( - "\\testonly{", - paste0("testex::testthat_block(test_that(", deparse(desc), ", {"), - paste0(" testex::with_srcref(\"", srcs, "\", ", trimws(escape_infotex(tests)), ")"), - "}),", - sprintf(" example = \"%s\"", example_src), - ")}" - ) +#' When a testthat tag does not contain a `.` object, its result is considered +#' an an implicit testthat expectation, which should be injected with a `.` +#' as a first argument. +#' +#' @param expr A (possibly) implicity lambda function +#' @return A new expression, injecting a `.` argument if needed. +#' +#' @noRd +#' @keywords internal +populate_testthat_dot <- function(expr) { + if (is.expression(expr)) expr <- expr[[1]] + if (!"." %in% all.names(expr)) { + expr <- as.call(append(as.list(expr), quote(.), after = 1L)) + } + expr } -#' Restructure and append tests to a test aggregating list -#' -#' @param tag The roxygen tag that we are formatting -#' @param tests A `list` of test `code` objects to be formatted into a -#' `\testonly` block. -#' @param test A new test `code` object to append to the list. If -#' necessary, the code will be modified to accommodate the testing style. +#' Find The Last Character of the First Expression #' -#' @return An appended `tests` `list` +#' @param x A parsed expression with srcref. +#' @return An integer representing the character position of the end of the +#' first call in a in a parsed expression. #' -#' @family roclet_process_helpers +#' @noRd #' @keywords internal -append_test <- function(tag, tests) { - UseMethod("append_test", structure(1L, class = tag$tag)) -} - -append_test.expect <- function(tag, tests) { - attrs <- attributes(tag$test) - test <- tag$test[[1L]] - if (!"." %in% all.names(test)) { - test <- bquote(identical(., .(test))) +first_expr_end <- function(x) { + if (!is.null(sr <- attr(x[[1]], "wholeSrcref"))) { + nchar(paste0(as.character(sr), collapse = "\n")) + } else if (!is.null(sr <- attr(x, "wholeSrcref"))) { + nchar(paste0(as.character(sr), collapse = "\n")) } - attributes(test) <- attrs - append(tests, list(test)) -} - -append_test.testthat <- function(tag, tests) { - attrs <- attributes(tag$test) - test <- tag$test[[1L]] - if (!"." %in% all.names(test)) - test <- as.call(append(as.list(test), quote(.), after = 1L)) - attributes(test) <- attrs - append(tests, list(test)) } @@ -317,37 +212,11 @@ append_test.testthat <- function(tag, tests) { #' Escape escaped Rd \\testonly strings #' #' @param x A \code{character} value -#' #' @return An escaped string, where any `\` is converted to `\\` #' +#' @noRd #' @family roclet_process_helpers #' @keywords internal escape_infotex <- function(x) { gsub("\\\\", "\\\\\\\\", x) } - - - -#' Append a test to the examples Rd section -#' -#' @note -#' Because of how newlines are formatted when rendering Rd contents, -#' `\testonly` blocks must starts on the last line of the code that they -#' test. Otherwise, an extra newline is printed when Rd is output as text. -#' -#' @param ex The existing character vector of example Rd section lines -#' @param test The additional test lines to add to the example -#' -#' @return The result of concatenating `test` into `ex` -#' -#' @family roclet_process_helpers -#' @keywords internal -append_test_rd <- function(ex, test) { - if (!length(test)) return(ex) - c( - ex[-length(ex)], - # \testonly on same line to prevent unintended linebreaks - paste0(ex[[length(ex)]], test[[1L]]), - test[-1L] - ) -} diff --git a/R/testthat.R b/R/testthat.R index 9d033ed..b11f616 100644 --- a/R/testthat.R +++ b/R/testthat.R @@ -180,18 +180,19 @@ expect_no_error <- function(object, ...) { #' } #' #' @export -test_examples_as_testthat <- function(package, path, ..., - test_dir = tempfile("testex"), clean = TRUE, overwrite = TRUE, - reporter = testthat::get_reporter()) { - +test_examples_as_testthat <- function( + package, path, ..., test_dir = tempfile("testex"), clean = TRUE, + overwrite = TRUE, reporter = testthat::get_reporter() +) { requireNamespace("testthat") testthat_envvar_val <- Sys.getenv("TESTTHAT") Sys.setenv(TESTTHAT = "true") on.exit(Sys.setenv(TESTTHAT = testthat_envvar_val)) - if (missing(path)) + if (missing(path)) { path <- find_package_root(testthat::test_path()) + } rds <- find_package_rds(package, path) test_dir_exists <- dir.exists(test_dir) @@ -207,7 +208,7 @@ test_examples_as_testthat <- function(package, path, ..., return() } - # find example sections and conver them to tests + # find example sections and convert them to tests rd_examples <- Filter(Negate(is.null), lapply(rds, rd_extract_examples)) test_files <- lapply(seq_along(rd_examples), function(i) { rd_filename <- names(rd_examples[i]) @@ -223,7 +224,7 @@ test_examples_as_testthat <- function(package, path, ..., ) # write out test code to file in test dir - path <- file.path(test_dir, paste0(tools::file_path_sans_ext(rd_filename), ".R")) + path <- file.path(test_dir, rd_filename) example_code <- vcapply(exprs, deparse_pretty) writeLines(paste(example_code, collapse = "\n\n"), path) diff --git a/R/utils.R b/R/utils.R index a8f8802..2706f0c 100644 --- a/R/utils.R +++ b/R/utils.R @@ -10,44 +10,6 @@ -#' Extract select unexported objects from a package namespace -#' -#' @param package A package name -#' @param names A \code{character} vector of object names to select -#' -#' @return A list of specified private namespace objects -#' -#' @name testex-private-imports -#' @keywords internal -#' -priv <- function(package, names) { - function() { - if (requireNamespace(package, quietly = TRUE)) { - ns <- as.list(getNamespace(package)) - if (any(!names %in% names(ns))) { - stop(sprintf("required objects not found in %s", package)) - } - ns[names] - } else { - message(sprintf("%s needed to use this functionality", package)) - } - } -} - - - -#' Private roxygen2 functions -#' -#' @name testex-private-imports -#' @keywords internal -#' -.roxygen2 <- priv("roxygen2", c( - "roclet_process.roclet_rd", - "roclet_output.roclet_rd" -)) - - - #' Temporarily attach a namespace #' #' This function is primarily for managing attaching of namespaces needed for @@ -68,10 +30,10 @@ with_attached <- function(ns, expr) { requireNamespace(ns) } - try({ + try(silent = TRUE, { attached <- attachNamespace(ns) on.exit(detach(attr(attached, "name"), character.only = TRUE)) - }, silent = TRUE) + }) expr <- substitute(expr) eval(expr) @@ -105,8 +67,15 @@ is_r_cmd_check <- function() { find_package_root <- function(path = ".", quiet = FALSE) { if (path == ".") path <- getwd() while (dirname(path) != path) { - if (file.exists(file.path(path, "DESCRIPTION"))) + if (file.exists(file.path(path, "DESCRIPTION"))) { + # package source directory return(path) + } else if (endsWith(basename(path), ".Rcheck")) { + # installed package, as during R CMD check + file <- basename(path) + package <- substring(file, 1, nchar(file) - nchar(".Rcheck")) + return(file.path(path, package)) + } path <- dirname(path) } @@ -220,7 +189,7 @@ deparse_pretty <- function(expr) { #' @keywords internal deparse_indent <- function(x, indent = 0L) { if (is.numeric(indent)) indent <- strrep(" ", indent) - paste0(indent, deparse(x), collapse = "\n") + paste0(indent, deparse(unclass(x)), collapse = "\n") } diff --git a/R/zzz.R b/R/zzz.R index 4d701d8..afb7cc4 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -1,6 +1,4 @@ .onLoad <- function(libname, pkgname) { - s3_register("roxygen2::roclet_output", "roclet_rd") - s3_register("roxygen2::roclet_process", "roclet_rd") s3_register("roxygen2::roxy_tag_parse", "roxy_tag_expect") s3_register("roxygen2::roxy_tag_parse", "roxy_tag_testthat") } diff --git a/inst/pkg.example/DESCRIPTION b/inst/pkg.example/DESCRIPTION index 792cc89..e84fe06 100644 --- a/inst/pkg.example/DESCRIPTION +++ b/inst/pkg.example/DESCRIPTION @@ -9,8 +9,8 @@ Suggests: testthat (>= 3.0.0), roxygen2 Encoding: UTF-8 -Roxygen: list(markdown = TRUE, roclets = c("namespace", "testex::rd")) -RoxygenNote: 7.2.3 +Roxygen: list(markdown = TRUE, packages = "testex") +RoxygenNote: 7.3.1 License: MIT + file LICENSE Config/testthat/edition: 3 -Config/testex/options: list(check = FALSE) +Config/testex/options: list(check = TRUE) diff --git a/inst/pkg.example/NAMESPACE b/inst/pkg.example/NAMESPACE index 2df0687..160956d 100644 --- a/inst/pkg.example/NAMESPACE +++ b/inst/pkg.example/NAMESPACE @@ -2,4 +2,6 @@ export(fn) export(fn_roxygen) +export(fn_roxygen_multiple1) +export(fn_roxygen_multiple2) export(fn_roxygen_testthat) diff --git a/inst/pkg.example/R/fn.R b/inst/pkg.example/R/fn.R index 78c145a..d7bd4a3 100644 --- a/inst/pkg.example/R/fn.R +++ b/inst/pkg.example/R/fn.R @@ -83,6 +83,7 @@ fn_roxygen <- function(x) { #' @testthat expect_equal("testing 1 2 3") #' @testthat expect_match("^testing") #' +#' @examples #' fn_roxygen_testthat("testing") #' @testthat expect_equal("testing 1 2 3") #' @testthat expect_match("^testing") @@ -91,3 +92,42 @@ fn_roxygen <- function(x) { fn_roxygen_testthat <- function(x) { paste(x, "1 2 3") } + + + + +#' Test Topic Covering Multiple Functions +#' +#' This example composes an examples section from multiple blocks. +#' +#' @param x A thing +#' @return The pasted thing +#' +#' @name fn_roxygen_multiple +NULL + +#' @describeIn fn_roxygen_multiple +#' Ensure multiple objects' examples are combined into a single topic +#' +#' @examples +#' fn_roxygen_multiple1("testing") +#' @expect grepl("\\d", .) +#' @expect startsWith(., "testing") +#' +#' @export +fn_roxygen_multiple1 <- function(x) { + paste(x, "1 2 3") +} + +#' @describeIn fn_roxygen_multiple +#' Ensure multiple objects' examples are combined into a single topic +#' +#' @examples +#' fn_roxygen_multiple2("testing") +#' @expect grepl("\\d", .) +#' @expect startsWith(., "testing") +#' +#' @export +fn_roxygen_multiple2 <- function(x) { + paste(x, "1 2 3") +} diff --git a/inst/pkg.example/man/fn_roxygen.Rd b/inst/pkg.example/man/fn_roxygen.Rd index 2c0540c..42a884a 100644 --- a/inst/pkg.example/man/fn_roxygen.Rd +++ b/inst/pkg.example/man/fn_roxygen.Rd @@ -21,30 +21,19 @@ using the \code{.}-syntax to test the last example result. value <- "testing" } -fn_roxygen(value)\testonly{ -testex::testex( - identical(., "testing 1 2 3"), - example = "fn.R:41:46" -)} - +fn_roxygen(value) +\testonly{testex::testex(identical(., "testing 1 2 3"))} \dontrun{ stop("this won't work") } -fn_roxygen("testing")\testonly{ -testex::testex( - grepl("\\\\d", .), - startsWith(., "testing"), - example = "fn.R:48:53" -)} - -fn_roxygen("testing")\testonly{ -testex::testex( - identical(., { - "testing 1 2 3" - }), - example = "fn.R:56:57" -)} +fn_roxygen("testing") +\testonly{testex::testex(grepl("\\\\d", .))} +\testonly{testex::testex(startsWith(., "testing"))} +fn_roxygen("testing") +\testonly{testex::testex(identical(., { + "testing 1 2 3" +}))} fn_roxygen("testing") # untested trailing example diff --git a/inst/pkg.example/man/fn_roxygen_multiple.Rd b/inst/pkg.example/man/fn_roxygen_multiple.Rd new file mode 100644 index 0000000..889953f --- /dev/null +++ b/inst/pkg.example/man/fn_roxygen_multiple.Rd @@ -0,0 +1,36 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/fn.R +\name{fn_roxygen_multiple} +\alias{fn_roxygen_multiple} +\alias{fn_roxygen_multiple1} +\alias{fn_roxygen_multiple2} +\title{Test Topic Covering Multiple Functions} +\usage{ +fn_roxygen_multiple1(x) + +fn_roxygen_multiple2(x) +} +\arguments{ +\item{x}{A thing} +} +\value{ +The pasted thing +} +\description{ +This example composes an examples section from multiple blocks. +} +\section{Functions}{ +\itemize{ +\item \code{fn_roxygen_multiple1()}: Ensure multiple objects' examples are combined into a single topic + +\item \code{fn_roxygen_multiple2()}: Ensure multiple objects' examples are combined into a single topic + +}} +\examples{ +fn_roxygen_multiple1("testing") +\testonly{testex::testex(grepl("\\\\d", .))} +\testonly{testex::testex(startsWith(., "testing"))} +fn_roxygen_multiple2("testing") +\testonly{testex::testex(grepl("\\\\d", .))} +\testonly{testex::testex(startsWith(., "testing"))} +} diff --git a/inst/pkg.example/man/fn_roxygen_testthat.Rd b/inst/pkg.example/man/fn_roxygen_testthat.Rd index 158df85..8a8b639 100644 --- a/inst/pkg.example/man/fn_roxygen_testthat.Rd +++ b/inst/pkg.example/man/fn_roxygen_testthat.Rd @@ -17,20 +17,26 @@ This example introduces \code{testthat}-style tests using in-line \verb{@testtha roxygen tags. } \examples{ -fn_roxygen_testthat("testing")\testonly{ -testex::testthat_block(test_that("example tests at `fn.R:81:82`", { - testex::with_srcref("fn.R:83:83", expect_equal(., "testing 1 2 3")) - testex::with_srcref("fn.R:84:84", expect_match(., "^testing")) -}), - example = "fn.R:81:82" -)} - -fn_roxygen_testthat("testing")\testonly{ -testex::testthat_block(test_that("example tests at `fn.R:85:86`", { - testex::with_srcref("fn.R:87:87", expect_equal(., "testing 1 2 3")) - testex::with_srcref("fn.R:88:88", expect_match(., "^testing")) -}), - example = "fn.R:85:86" -)} - +fn_roxygen_testthat("testing") +\testonly{ +testex::testthat_block(test_that("example tests at `fn.R:83:83`", { +testex::with_srcref("fn.R:83:83", expect_equal(., "testing 1 2 3")) +})) +} +\testonly{ +testex::testthat_block(test_that("example tests at `fn.R:84:84`", { +testex::with_srcref("fn.R:84:84", expect_match(., "^testing")) +})) +} +fn_roxygen_testthat("testing") +\testonly{ +testex::testthat_block(test_that("example tests at `fn.R:88:88`", { +testex::with_srcref("fn.R:88:88", expect_equal(., "testing 1 2 3")) +})) +} +\testonly{ +testex::testthat_block(test_that("example tests at `fn.R:89:89`", { +testex::with_srcref("fn.R:89:89", expect_match(., "^testing")) +})) +} } diff --git a/man/append_test.Rd b/man/append_test.Rd deleted file mode 100644 index 111337b..0000000 --- a/man/append_test.Rd +++ /dev/null @@ -1,31 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/roxygen2.R -\name{append_test} -\alias{append_test} -\title{Restructure and append tests to a test aggregating list} -\usage{ -append_test(tag, tests) -} -\arguments{ -\item{tag}{The roxygen tag that we are formatting} - -\item{tests}{A \code{list} of test \code{code} objects to be formatted into a -\verb{\testonly} block.} - -\item{test}{A new test \code{code} object to append to the list. If -necessary, the code will be modified to accommodate the testing style.} -} -\value{ -An appended \code{tests} \code{list} -} -\description{ -Restructure and append tests to a test aggregating list -} -\seealso{ -Other roclet_process_helpers: -\code{\link{append_test_rd}()}, -\code{\link{escape_infotex}()}, -\code{\link{format_tests}()} -} -\concept{roclet_process_helpers} -\keyword{internal} diff --git a/man/append_test_rd.Rd b/man/append_test_rd.Rd deleted file mode 100644 index b995fa5..0000000 --- a/man/append_test_rd.Rd +++ /dev/null @@ -1,32 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/roxygen2.R -\name{append_test_rd} -\alias{append_test_rd} -\title{Append a test to the examples Rd section} -\usage{ -append_test_rd(ex, test) -} -\arguments{ -\item{ex}{The existing character vector of example Rd section lines} - -\item{test}{The additional test lines to add to the example} -} -\value{ -The result of concatenating \code{test} into \code{ex} -} -\description{ -Append a test to the examples Rd section -} -\note{ -Because of how newlines are formatted when rendering Rd contents, -\verb{\testonly} blocks must starts on the last line of the code that they -test. Otherwise, an extra newline is printed when Rd is output as text. -} -\seealso{ -Other roclet_process_helpers: -\code{\link{append_test}()}, -\code{\link{escape_infotex}()}, -\code{\link{format_tests}()} -} -\concept{roclet_process_helpers} -\keyword{internal} diff --git a/man/escape_infotex.Rd b/man/escape_infotex.Rd deleted file mode 100644 index e59f17a..0000000 --- a/man/escape_infotex.Rd +++ /dev/null @@ -1,25 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/roxygen2.R -\name{escape_infotex} -\alias{escape_infotex} -\title{Escape escaped Rd \\testonly strings} -\usage{ -escape_infotex(x) -} -\arguments{ -\item{x}{A \code{character} value} -} -\value{ -An escaped string, where any \verb{\\} is converted to \verb{\\\\} -} -\description{ -Escape escaped Rd \\testonly strings -} -\seealso{ -Other roclet_process_helpers: -\code{\link{append_test_rd}()}, -\code{\link{append_test}()}, -\code{\link{format_tests}()} -} -\concept{roclet_process_helpers} -\keyword{internal} diff --git a/man/format_tests.Rd b/man/format_tests.Rd deleted file mode 100644 index afa23f0..0000000 --- a/man/format_tests.Rd +++ /dev/null @@ -1,44 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/roxygen2.R -\name{format_tests} -\alias{format_tests} -\alias{format_tests.default} -\alias{format_tests.expect} -\alias{format_tests.testthat} -\title{Format test for an Rd \\testonly block} -\usage{ -format_tests(tag, tests, ...) - -\method{format_tests}{default}(tag, tests, file, lines) - -\method{format_tests}{expect}(tag, tests, file, lines) - -\method{format_tests}{testthat}(tag, tests, file, lines) -} -\arguments{ -\item{tag}{The roxygen tag that we are formatting} - -\item{tests}{A \code{list} of test \code{code} objects to be formatted into a -\code{\\testonly} block.} - -\item{...}{Additional arguments used by methods} - -\item{file}{The source file where the example test code originated} - -\item{lines}{A \code{numeric} vector of length two indicating the start and -end lines of the example code block tested by the test code.} -} -\value{ -A formatted block of code for an Rd section -} -\description{ -Format test for an Rd \\testonly block -} -\seealso{ -Other roclet_process_helpers: -\code{\link{append_test_rd}()}, -\code{\link{append_test}()}, -\code{\link{escape_infotex}()} -} -\concept{roclet_process_helpers} -\keyword{internal} diff --git a/man/roxy_test_helpers.Rd b/man/roxy_test_helpers.Rd deleted file mode 100644 index 8632dbe..0000000 --- a/man/roxy_test_helpers.Rd +++ /dev/null @@ -1,19 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/roxygen2.R -\name{roxy_test_helpers} -\alias{roxy_test_helpers} -\alias{roxy_test_raw_remainder} -\title{Separate the remaining text following a parsed roxygen test} -\usage{ -roxy_test_raw_remainder(x) -} -\arguments{ -\item{x}{A processed roxy testex tag, including a \verb{$test} field} -} -\value{ -the string that follows the end of the test expression -} -\description{ -Separate the remaining text following a parsed roxygen test -} -\keyword{internal} diff --git a/man/testex-private-imports.Rd b/man/testex-private-imports.Rd deleted file mode 100644 index eb23c93..0000000 --- a/man/testex-private-imports.Rd +++ /dev/null @@ -1,26 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/utils.R -\name{testex-private-imports} -\alias{testex-private-imports} -\alias{priv} -\alias{.roxygen2} -\title{Extract select unexported objects from a package namespace} -\usage{ -priv(package, names) - -.roxygen2() -} -\arguments{ -\item{package}{A package name} - -\item{names}{A \code{character} vector of object names to select} -} -\value{ -A list of specified private namespace objects -} -\description{ -Extract select unexported objects from a package namespace - -Private roxygen2 functions -} -\keyword{internal} diff --git a/man/rd.Rd b/man/testex-roclets.Rd similarity index 96% rename from man/rd.Rd rename to man/testex-roclets.Rd index 96a8cd2..9016a5e 100644 --- a/man/rd.Rd +++ b/man/testex-roclets.Rd @@ -1,11 +1,8 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/roxygen2.R -\name{rd} -\alias{rd} +\name{testex-roclets} +\alias{testex-roclets} \title{testex replacement for roxygen2 rd roclet} -\usage{ -rd() -} \value{ A new \code{roxygen2} \code{"rd"} roclet. } @@ -34,6 +31,7 @@ output. #' @expect 3 #' @expect . == 3 #' +#' @examples #' 3 + 4 #' @expect identical(., 7) }\if{html}{\out{}} @@ -59,6 +57,7 @@ not do any further implicit modification of your expectation. #' @testthat expect_equal(3) #' @testthat expect_gt(0) #' +#' @examples #' 3 + 4 #' @testthat expect_equal(., 7) }\if{html}{\out{}} diff --git a/tests/testthat/test-roxygen2-expect.R b/tests/testthat/test-roxygen2-expect.R index 75def6c..cf6bb24 100644 --- a/tests/testthat/test-roxygen2-expect.R +++ b/tests/testthat/test-roxygen2-expect.R @@ -15,16 +15,12 @@ test_that("@expect tags produce \\testonly blocks", { " block <- roxygen2::parse_text(roxy_text)[[1]] + expect_tag <- block$tags[[5]] - expect_silent({ - block <- roclet_process_testex(block) - ex_idx <- which(vcapply(block$tags, `[[`, "tag") == "examples") - ex_tag <- block$tags[[ex_idx]] - ex_val <- ex_tag$val - }) + expect_equal(expect_tag$tag, "expect") + expect_s3_class(expect_tag, "roxy_tag_examples") - expect_true(any(grepl("\\\\testonly\\{", ex_tag$val))) - expect_true(any(grepl("testex::testex\\(", ex_tag$val))) - expect_true(any(grepl("identical\\(\\., 3\\)", ex_tag$val))) - expect_true(any(grepl("example = \".*:.:.\"", ex_tag$val))) + expect_true(any(grepl("\\\\testonly\\{", expect_tag$val))) + expect_true(any(grepl("testex::testex\\(", expect_tag$val))) + expect_true(any(grepl("identical\\(\\., 3\\)", expect_tag$val))) }) diff --git a/tests/testthat/test-roxygen2-testthat.R b/tests/testthat/test-roxygen2-testthat.R index b117cac..d8101bb 100644 --- a/tests/testthat/test-roxygen2-testthat.R +++ b/tests/testthat/test-roxygen2-testthat.R @@ -15,16 +15,12 @@ test_that("@expect tags produce \\testonly blocks", { " block <- roxygen2::parse_text(roxy_text)[[1]] + testthat_tag <- block$tags[[5]] - expect_silent({ - block <- roclet_process_testex(block) - ex_idx <- which(vcapply(block$tags, `[[`, "tag") == "examples") - ex_tag <- block$tags[[ex_idx]] - ex_val <- ex_tag$val - }) + expect_equal(testthat_tag$tag, "testthat") + expect_s3_class(testthat_tag, "roxy_tag_examples") - expect_true(any(grepl("\\\\testonly\\{", ex_tag$val))) - expect_true(any(grepl("testex::testthat_block\\(", ex_tag$val))) - expect_true(any(grepl("expect_equals\\(\\., 3\\)", ex_tag$val))) - expect_true(any(grepl("example = \".*:.:.\"", ex_tag$val))) + expect_true(any(grepl("\\\\testonly\\{", testthat_tag$val))) + expect_true(any(grepl("testex::testthat_block\\(", testthat_tag$val))) + expect_true(any(grepl("expect_equals\\(\\., 3\\)", testthat_tag$val))) })