Skip to content

Commit aef39b7

Browse files
committed
Polish vignette + docs
1 parent ceb276e commit aef39b7

File tree

6 files changed

+71
-75
lines changed

6 files changed

+71
-75
lines changed

R/expect-that.R

Lines changed: 23 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -2,25 +2,37 @@
22
#'
33
#' @description
44
#' These are the primitives that you can use to implement your own expectations.
5-
#' Every branch of code inside an expectation must call either `pass()` or
6-
#' `fail()`; learn more in `vignette("custom-expectation")`.
5+
#' Regardless of how it's called an expectation should either return `pass()`,
6+
#' `fail()`, or throw an error (if for example, the arguments are invalid).
77
#'
8-
#' @param message a string to display.
8+
#' Learn more about creating your own expectations in
9+
#' `vignette("custom-expectation")`.
10+
#'
11+
#' @param message Failure message to send to the user. It's best practice to
12+
#' describe both what is expected and what was actually received.
913
#' @param info Character vector continuing additional information. Included
1014
#' for backward compatibility only and new expectations should not use it.
1115
#' @param srcref Location of the failure. Should only needed to be explicitly
1216
#' supplied when you need to forward a srcref captured elsewhere.
17+
#' @param trace_env If `trace` is not specified, this is used to generate an
18+
#' informative traceack for failures. You should only need to set this if
19+
#' you're calling `fail()` from a helper function; see
20+
#' `vignette("custom-expectation")` for details.
1321
#' @param trace An optional backtrace created by [rlang::trace_back()].
1422
#' When supplied, the expectation is displayed with the backtrace.
15-
#' @param trace_env If `is.null(trace)`, this is used to automatically
16-
#' generate a traceback running from `test_code()`/`test_file()` to
17-
#' `trace_env`. You'll generally only need to set this if you're wrapping
18-
#' an expectation inside another function.
23+
#' Expert use only.
1924
#' @export
2025
#' @examples
21-
#' \dontrun{
22-
#' test_that("this test fails", fail())
23-
#' test_that("this test succeeds", succeed())
26+
#' expect_length <- function(object, n) {
27+
#' act <- quasi_label(rlang::enquo(object), arg = "object")
28+
#'
29+
#' act_n <- length(act$val)
30+
#' if (act_n != n) {
31+
#' msg <- sprintf("%s has length %i, not length %i.", act$lab, act_n, n)
32+
#' return(fail(msg))
33+
#' }
34+
#'
35+
#' pass(act$val)
2436
#' }
2537
fail <- function(
2638
message = "Failure has been forced",
@@ -53,7 +65,7 @@ pass <- function(value) {
5365
#' Mark a test as successful
5466
#'
5567
#' This is an older version of [pass()] that exists for backwards compatibility.
56-
#' You should now use `pass()` instead`
68+
#' You should now use `pass()` instead.
5769
#'
5870
#' @export
5971
#' @inheritParams fail

man/expect.Rd

Lines changed: 6 additions & 5 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/expectation.Rd

Lines changed: 2 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/fail.Rd

Lines changed: 23 additions & 11 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/succeed.Rd

Lines changed: 3 additions & 2 deletions
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

vignettes/custom-expectation.Rmd

Lines changed: 14 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -160,56 +160,25 @@ expect_s3_class(x3, "integer")
160160

161161
## Repeated code
162162

163-
As you write more expectations, you might discover repeated code that you want to extract out in to a helper. For example, testthat has `expect_true()`, `expect_false()`, and `expect_null()` which are special cases of `expect_equal()`.
163+
As you write more expectations, you might discover repeated code that you want to extract out in to a helper. Unfortunately creating helper functions is not straightforward in testthat because every `fail()` captures the calling environment in order to give maximally useful tracebacks. Because getting this right is not critical (you'll just get a slightly suboptimal traceback in the case of failure), we don't recommend bothering. However, we document it here because it's important to get it right in testthat itself.
164164

165-
```{r}
166-
expect_true <- function(object) {
167-
act <- quasi_label(enquo(object))
168-
expect_waldo_equal_("equal", act, TRUE, ignore_attr = TRUE)
169-
}
170-
expect_false <- function(object) {
171-
act <- quasi_label(enquo(object))
172-
expect_waldo_equal_("equal", act, FALSE, ignore_attr = TRUE)
173-
}
174-
expect_null <- function(object, label = NULL) {
175-
act <- quasi_label(enquo(object))
176-
expect_waldo_equal_("equal", act, NULL)
177-
}
178-
```
179-
180-
You might wonder why these functions don't call `expect_equal()` directly. Unfortunately creating helper functions is not straightforward in testthat because every `fail()` captures the calling environment in order to give maximally useful tracebacks. Getting this right is not critical (you'll just get a slightly suboptimal traceback in the case of failure) but it's good practice, particularly for testthat itself.
181-
182-
To do things 100% correctly, in your helper function you need to have a `trace_env` argument that defaults to `caller_env()`, and then you need to pass it to every instance of
165+
The key challenge is that `fail()` captures a `trace_env` which should be the execution environment of the expectation. This usually works, because the default value of `trace_env` is `caller_env()`. But when you introduce a helper, you'll need to explicitly pass it along:
183166

184167
```{r}
185-
expect_waldo_equal_ <- function(
186-
type,
187-
act,
188-
exp,
189-
info,
190-
...,
191-
trace_env = caller_env()
192-
) {
193-
comp <- waldo_compare(
194-
act$val,
195-
exp$val,
196-
...,
197-
x_arg = "actual",
198-
y_arg = "expected"
199-
)
200-
if (length(comp) != 0) {
201-
msg <- sprintf(
202-
"%s (%s) not %s to %s (%s).\n\n%s",
203-
act$lab,
204-
"`actual`",
205-
type,
206-
exp$lab,
207-
"`expected`",
208-
paste0(comp, collapse = "\n\n")
209-
)
210-
return(fail(msg, info = info, trace_env = trace_env))
168+
expect_length_ <- function(act, n, trace_env = caller_env()) {
169+
act_n <- length(act$val)
170+
if (act_n != n) {
171+
msg <- sprintf("%s has length %i, not length %i.", act$lab, act_n, n)
172+
return(fail(msg, trace_env = trace_env))
211173
}
174+
212175
pass(act$val)
213176
}
214177
178+
expect_length <- function(object, n) {
179+
act <- quasi_label(rlang::enquo(object), arg = "object")
180+
expect_length_(act, n)
181+
}
215182
```
183+
184+
Note that the helper probably shouldn't be user facing, and we give it a `_` suffix to make that clear. It's also typically easiest for a helper to take the labelled value produced by `quasi_label()` rather than having to do that repeatedly.

0 commit comments

Comments
 (0)