Skip to content

Commit d51a8b6

Browse files
committed
More expectation object tidying/refactoring
1 parent 84e5fe5 commit d51a8b6

File tree

4 files changed

+72
-82
lines changed

4 files changed

+72
-82
lines changed

R/expectation.R

+39-71
Original file line numberDiff line numberDiff line change
@@ -1,27 +1,24 @@
11
#' The building block of all `expect_` functions
22
#'
3-
#' Use this if you are writing your own expectation. See
3+
#' Call this function when writing your own expectations. See
44
#' `vignette("custom-expectation")` for details.
55
#'
6-
#' @param ok Was the expectation successful?
7-
#' @param failure_message What message should be shown if the expectation was
8-
#' not successful?
9-
#' @param info Additional information. Included for backward compatibility
10-
#' only and new expectations should not use it.
11-
#' @param srcref Only needed in very rare circumstances where you need to
12-
#' forward a srcref captured elsewhere.
6+
#' @param ok `TRUE` or `FALSE` indicating if the expectation was successful.
7+
#' @param failure_message Message to show if the expectation failed.
8+
#' @param info Character vector continuing additional information. Included
9+
#' for backward compatibility only and new expectations should not use it.
10+
#' @param srcref Location of the failure. Should only needed to be explicitly
11+
#' supplied when you need to forward a srcref captured elsewhere.
12+
#' @return An expectation object. Signals the expectation condition
13+
#' with a `continue_test` restart.
1314
#' @export
1415
expect <- function(ok, failure_message, info = NULL, srcref = NULL) {
1516
type <- if (ok) "success" else "failure"
1617
message <- paste(c(failure_message, info), collapse = "\n")
1718
exp <- expectation(type, message, srcref = srcref)
1819

1920
withRestarts(
20-
if (expectation_broken(exp)) {
21-
stop(exp)
22-
} else {
23-
signalCondition(exp)
24-
},
21+
if (ok) signalCondition(exp) else stop(exp),
2522
continue_test = function(e) NULL
2623
)
2724

@@ -31,7 +28,7 @@ expect <- function(ok, failure_message, info = NULL, srcref = NULL) {
3128
#' Construct an expectation object
3229
#'
3330
#' For advanced use only. If you are creating your own expectation, you should
34-
#' call `expect()` instead. See `vignette("custom-expectation")` for more
31+
#' call [expect()] instead. See `vignette("custom-expectation")` for more
3532
#' details.
3633
#'
3734
#' @param type Expectation type. Must be one of "success", "failure", "error",
@@ -63,39 +60,27 @@ expectation <- function(type, message, srcref = NULL) {
6360
#' @param x object to test for class membership
6461
is.expectation <- function(x) inherits(x, "expectation")
6562

66-
expectation_type <- function(exp) {
67-
stopifnot(is.expectation(exp))
68-
gsub("^expectation_", "", class(exp)[[1]])
69-
}
70-
71-
expectation_success <- function(exp) {
72-
expectation_type(exp) == "success"
73-
}
74-
75-
expectation_failure <- function(exp) {
76-
expectation_type(exp) == "failure"
77-
}
78-
79-
expectation_error <- function(exp) {
80-
expectation_type(exp) == "error"
63+
#' @export
64+
print.expectation <- function(x, ...) {
65+
cat(format(x), "\n")
8166
}
8267

83-
expectation_skip <- function(exp) {
84-
expectation_type(exp) == "skip"
68+
#' @export
69+
format.expectation_success <- function(x, ...) {
70+
"As expected"
8571
}
8672

87-
expectation_warning <- function(exp) {
88-
expectation_type(exp) == "warning"
73+
#' @export
74+
format.expectation_error <- function(x, ...) {
75+
paste(c(x$message, create_traceback(x$call)), collapse = "\n")
8976
}
9077

91-
expectation_broken <- function(exp) {
92-
expectation_failure(exp) || expectation_error(exp)
93-
}
94-
expectation_ok <- function(exp) {
95-
expectation_type(exp) %in% c("success", "warning")
78+
#' @export
79+
format.expectation <- function(x, ...) {
80+
x$message
9681
}
9782

98-
83+
# as.expectation ----------------------------------------------------------
9984

10085
as.expectation <- function(x, ...) UseMethod("as.expectation", x)
10186

@@ -109,9 +94,7 @@ as.expectation.default <- function(x, ..., srcref = NULL) {
10994

11095
#' @export
11196
as.expectation.expectation <- function(x, ..., srcref = NULL) {
112-
if (is.null(x$srcref)) {
113-
x$srcref <- srcref
114-
}
97+
x$srcref <- x$srcref %||% srcref
11598
x
11699
}
117100

@@ -120,51 +103,36 @@ as.expectation.error <- function(x, ..., srcref = NULL) {
120103
error <- x$message
121104

122105
msg <- gsub("Error.*?: ", "", as.character(error))
123-
124-
# Need to remove trailing newline from error message to be consistent
125-
# with other messages
106+
# Remove trailing newline to be consistent with other conditons
126107
msg <- gsub("\n$", "", msg)
127108

128109
expectation("error", msg, srcref)
129110
}
130111

131112
#' @export
132113
as.expectation.warning <- function(x, ..., srcref = NULL) {
133-
msg <- x$message
134-
135-
# msg <- gsub("Error.*?: ", "", as.character(error))
136-
# msg <- gsub("\n$", "", msg)
137-
138-
expectation("warning", msg, srcref)
114+
expectation("warning", x$message, srcref)
139115
}
140116

141117
#' @export
142118
as.expectation.skip <- function(x, ..., srcref = NULL) {
143-
error <- x$message
144-
msg <- gsub("Error.*?: ", "", as.character(error))
145-
146-
expectation("skip", msg, srcref)
147-
}
148-
149-
#' @export
150-
print.expectation <- function(x, ...) {
151-
cat(format(x), "\n")
119+
expectation("skip", x$message, srcref)
152120
}
153121

154-
#' @export
155-
format.expectation_success <- function(x, ...) {
156-
"As expected"
157-
}
122+
# expectation_type --------------------------------------------------------
158123

159-
#' @export
160-
format.expectation_error <- function(x, ...) {
161-
paste(c(x$message, create_traceback(x$call)), collapse = "\n")
124+
expectation_type <- function(exp) {
125+
stopifnot(is.expectation(exp))
126+
gsub("^expectation_", "", class(exp)[[1]])
162127
}
163128

164-
#' @export
165-
format.expectation <- function(x, ...) {
166-
x$message
167-
}
129+
expectation_success <- function(exp) expectation_type(exp) == "success"
130+
expectation_failure <- function(exp) expectation_type(exp) == "failure"
131+
expectation_error <- function(exp) expectation_type(exp) == "error"
132+
expectation_skip <- function(exp) expectation_type(exp) == "skip"
133+
expectation_warning <- function(exp) expectation_type(exp) == "warning"
134+
expectation_broken <- function(exp) expectation_failure(exp) || expectation_error(exp)
135+
expectation_ok <- function(exp) expectation_type(exp) %in% c("success", "warning")
168136

169137
single_letter_summary <- function(x) {
170138
switch(expectation_type(x),

man/expect.Rd

+11-8
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

man/expectation.Rd

+1-1
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

vignettes/custom-expectation.Rmd

+21-2
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ There are three main parts to writing an expectation, as illustrated by `expect_
2121
```{r}
2222
expect_length <- function(object, n) {
2323
# 1. Capture object and label
24-
act <- quasi_label(rlang::enquo(object))
24+
act <- quasi_label(rlang::enquo(object), arg = "object")
2525
2626
# 2. Call expect()
2727
act$n <- length(act$val)
@@ -37,7 +37,7 @@ expect_length <- function(object, n) {
3737

3838
## Quasi-labelling
3939

40-
The first step in any expectation is to capture the actual object, and generate a label for it to use if a failure occur. All testthat expectations supporting quasiquotation so that you can unquote variables. This makes it easier to generate good labels when the expectation is called from a function or within a for loop.
40+
The first step in any expectation is to capture the actual object, and generate a label for it to use if a failure occur. All testthat expectations support quasiquotation so that you can unquote variables. This makes it easier to generate good labels when the expectation is called from a function or within a for loop.
4141

4242
By convention, the first argument to every `expect_` function is called `object`, and you capture it's value (`val`) and label (`lab`) with `act <- quasi_label(enquo(object))`, where `act` is short for actual.
4343

@@ -68,6 +68,25 @@ mtcars %>%
6868
expect_length(11)
6969
```
7070

71+
## `suceed()` and `fail()`
72+
73+
For expectations with more complex logic governing when success or failure occurs, you can use `succeed()` and `fail()`. These are simple wrappers around `expect()` that allow you to write code that looks like this:
74+
75+
```{r}
76+
expect_length <- function(object, n) {
77+
act <- quasi_label(rlang::enquo(object), arg = "object")
78+
79+
act$n <- length(act$val)
80+
if (act$n == n) {
81+
succeed()
82+
invisible(act$val)
83+
}
84+
85+
message <- sprintf("%s has length %i, not length %i.", act$lab, act$n, n)
86+
fail(message)
87+
}
88+
```
89+
7190
## Testing your expectations
7291

7392
Use the expectations `expect_success()` and `expect_failure()` to test your expectation.

0 commit comments

Comments
 (0)