Skip to content

Commit

Permalink
fix: Support multiline @examplesIf again
Browse files Browse the repository at this point in the history
  • Loading branch information
krlmlr committed Aug 2, 2024
1 parent b94b42f commit 04ad8f2
Show file tree
Hide file tree
Showing 3 changed files with 32 additions and 4 deletions.
10 changes: 6 additions & 4 deletions R/rd-examples.R
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,12 @@ roxy_tag_parse.roxy_tag_examplesIf <- function(x) {
)

x$raw <- paste(
paste0("\\dontshow{if (", condition, ") withAutoprint(\\{ # examplesIf}"),
lines[-1],
"\\dontshow{\\}) # examplesIf}",
sep = "\n"
c(
paste0("\\dontshow{if (", condition, ") withAutoprint(\\{ # examplesIf}"),
lines[-1],
"\\dontshow{\\}) # examplesIf}"
),
collapse = "\n"
)

tag_examples(x)
Expand Down
12 changes: 12 additions & 0 deletions tests/testthat/_snaps/rd-examples.md
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,18 @@
\dontshow{\}) # examplesIf}
}

# @examplesIf, multi-line

\examples{
\dontshow{if (foo::bar()) withAutoprint(\{ # examplesIf}
maybe-run-this-code
\dontshow{\}) # examplesIf}
\dontshow{if (foobar()) withAutoprint(\{ # examplesIf}
and-this
and-that
\dontshow{\}) # examplesIf}
}

# @examplesIf warns about unparseable condition

Code
Expand Down
14 changes: 14 additions & 0 deletions tests/testthat/test-rd-examples.R
Original file line number Diff line number Diff line change
Expand Up @@ -84,6 +84,20 @@ test_that("@examplesIf", {
expect_snapshot_output(out$get_section("examples"))
})

test_that("@examplesIf, multi-line", {
out <- roc_proc_text(rd_roclet(), "
#' @name a
#' @title a
#' @examplesIf foo::bar()
#' maybe-run-this-code
#' @examplesIf foobar()
#' and-this
#' and-that
NULL")[[1]]

expect_snapshot_output(out$get_section("examples"))
})

test_that("@examplesIf warns about unparseable condition", {
block <- "
#' @name a
Expand Down

0 comments on commit 04ad8f2

Please sign in to comment.