Skip to content

Commit

Permalink
reinstates 'miraiInterrupt' class
Browse files Browse the repository at this point in the history
  • Loading branch information
shikokuchuo committed Sep 12, 2023
1 parent e3b9b8b commit bec3824
Show file tree
Hide file tree
Showing 5 changed files with 40 additions and 7 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@

S3method(print,mirai)
S3method(print,miraiError)
S3method(print,miraiInterrupt)
S3method(print,resolvedExpr)
S3method(print,unresolvedExpr)
export("%>>%")
Expand All @@ -14,6 +15,7 @@ export(dispatcher)
export(is_error_value)
export(is_mirai)
export(is_mirai_error)
export(is_mirai_interrupt)
export(launch_local)
export(launch_remote)
export(mirai)
Expand Down
1 change: 0 additions & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@
* Improves shell quoting of daemon launch commands, making it easier to deploy manually via `launch_remote()`.
* Passing a filename to the 'tls' argument of `daemons()`, `launch_local()` or `launch_remote()` now works correctly as documented.
* Extends and clarifies documentation surrounding use of certificate authority signed TLS certificates.
* Retires the class `miraiInterrupt`: interrupts now generate a `miraiError` with an empty value.
* Certain error messages are more accurate and informative.
* Increases in performance and lower resource utilisation due to updates in nanonext 0.10.0.
* Requires nanonext >= 0.10.0 and R >= 3.5.
Expand Down
27 changes: 24 additions & 3 deletions R/mirai.R
Original file line number Diff line number Diff line change
Expand Up @@ -1299,8 +1299,13 @@ is_mirai <- function(x) inherits(x, "mirai")
#' the error message is returned as a character string of class 'miraiError'
#' and 'errorValue'.
#'
#' Is the object an 'errorValue', such as a mirai timeout, or a 'miraiError'.
#' This is a catch-all condition that includes all returned error values.
#' Is the object a 'miraiInterrupt'. When an ongoing mirai is sent a user
#' interrupt, the mirai will resolve to an empty character string classed as
#' 'miraiInterrupt' and 'errorValue'.
#'
#' Is the object an 'errorValue', such as a mirai timeout, a 'miraiError' or
#' a 'miraiInterrupt'. This is a catch-all condition that includes all
#' returned error values.
#'
#' @examples
#' if (interactive()) {
Expand All @@ -1309,11 +1314,13 @@ is_mirai <- function(x) inherits(x, "mirai")
#' m <- mirai(stop())
#' call_mirai(m)
#' is_mirai_error(m$data)
#' is_mirai_interrupt(m$data)
#' is_error_value(m$data)
#'
#' m2 <- mirai(Sys.sleep(1L), .timeout = 100)
#' call_mirai(m2)
#' is_mirai_error(m2$data)
#' is_mirai_interrupt(m2$data)
#' is_error_value(m2$data)
#'
#' }
Expand All @@ -1322,6 +1329,11 @@ is_mirai <- function(x) inherits(x, "mirai")
#'
is_mirai_error <- function(x) inherits(x, "miraiError")

#' @rdname is_mirai_error
#' @export
#'
is_mirai_interrupt <- function(x) inherits(x, "miraiInterrupt")

#' @rdname is_mirai_error
#' @export
#'
Expand All @@ -1345,6 +1357,15 @@ print.miraiError <- function(x, ...) {

}

#' @export
#'
print.miraiInterrupt <- function(x, ...) {

cat("'miraiInterrupt' chr \"\"\n", file = stdout())
invisible(x)

}

# internals --------------------------------------------------------------------

parse_dots <- function(...)
Expand Down Expand Up @@ -1457,7 +1478,7 @@ next_stream <- function(envir) {
stream
}

mk_interrupt_error <- function(e) `class<-`("", c("miraiError", "errorValue"))
mk_interrupt_error <- function(e) `class<-`("", c("miraiInterrupt", "errorValue"))

mk_mirai_error <- function(e) {
call <- deparse(.subset2(e, "call"), width.cutoff = 500L, backtick = TRUE, control = NULL, nlines = 1L)
Expand Down
14 changes: 12 additions & 2 deletions man/is_mirai_error.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 2 additions & 1 deletion tests/tests.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ nanotesterr(launch_local(1L), "requires daemons to be set")
nanotesto(daemons(1L, dispatcher = FALSE))
me <- mirai(mirai::mirai(), .timeout = 2000L)
nanotest(is_mirai_error(call_mirai(me)$data) || is_error_value(me$data))
nanotest(!is_mirai_interrupt(me$data))
nanotest(is_error_value(me[["data"]]))
nanotestp(me$data)
df <- data.frame(a = 1, b = 2)
Expand All @@ -35,7 +36,7 @@ nanotesterr(daemons(n = 0, url = "ws://localhost:0"), "1 or greater")
nanotesterr(daemons(raw(0L)), "must be numeric")
nanotesterr(daemon("URL"), "Invalid argument")
nanotesterr(dispatcher(client = "URL"), "at least one")
nanotest(is_mirai_error(r <- mirai:::mk_interrupt_error()))
nanotest(is_mirai_interrupt(r <- mirai:::mk_interrupt_error()))
nanotestp(r)
nanotestz(daemons(0L))
nanotestz(status()[["connections"]])
Expand Down

0 comments on commit bec3824

Please sign in to comment.