0

Suppose that there is a finicky function f() that is costly to evaluate. It may be an optimisation algorithm that can throw a warning if it terminated without an error but failed some checks (e.g. max. iterations reached). I want to save the output of f() and the warnings if there were any because these warnings contain valuable information.

These solutions rely either on calling the function for the second time or on using withCallingHandlers. Frankly, there is so little documentation or examples online for withCallingHandlers, I cannot understand what this function does by looking at the definition.

The solution purrr::capture_output() relies on creating a temporary file and then, reading the lines from it. The problem is, I am trying to catch the warnings from millions of calls (small optimisation problems at the inner look of the function, and it is called millions, if not billions of times), so creating of a file() every time could be precarious (these functions are called in parallel).

Here is a MWE: there is a slow function (1 second) that may or may not throw a warning, and capturing the warning requires a second evaluation (the code below produces 2 warnings and 2 warning-free results = 2 + 2*2 = 6 seconds):

f <- function(i) {
  Sys.sleep(1)
  if (i < 3) warning(paste0("i is too small, took ", sample(3:10, 1),
                            " iterations, code ", sample(2:5, 1), "."))
  return(i)
}

set.seed(1)
f(1) # Warning
f(6) # No warning

saveWarnSlow <- function(i) {
  tryCatch(f(i), warning = function(w) list(output = f(i), warning = w))
}
system.time(out <- lapply(1:4, saveWarnSlow)) # Runs for 6 seconds
sapply(out, function(x) if (length(x) == 1) "OK" else as.character(x$warning))

# [1] "simpleWarning in f(i): i is too small, took 9 iterations, code 2.\n"
# [2] "simpleWarning in f(i): i is too small, took 9 iterations, code 4.\n"
# [3] "OK"                                                         
# [4] "OK"  

Maybe this is due to my poor knowledge on condition handling and recovery, but... how does on get rid of the repeated function evaluation to save the warning?

2 Answers2

2

I think you can't do it with tryCatch, but you can with withCallingHandlers. The idea is to save the warning message some place that is visible to the caller, then append the warning to the result.

f <- function(i) {
  Sys.sleep(1)
  if (i < 3) warning(paste0("i is too small, took ", sample(3:10, 1),
                            " iterations, code ", sample(2:5, 1), "."))
  return(i)
}

set.seed(1)

f(1) # Warning, but it won't be saved
#> Warning in f(1): i is too small, took 3 iterations, code 5.
#> [1] 1
f(6) # No warning
#> [1] 6

saveWarnSlow <- function(i) {
  thewarning <- ""
  
  wrapper <- function(value) {
    # Lazy evaluation means value hasn't been computed yet.
    thewarning <<- ""
    list(value = value, warning = thewarning)
  }
  
  withCallingHandlers(wrapper(f(i)),
    warning = 
      function(w) {
        thewarning <<- conditionMessage(w)
        invokeRestart("muffleWarning")
      })
}
system.time(out <- lapply(1:4, saveWarnSlow)) # Runs for 4 seconds
#>    user  system elapsed 
#>   0.013   0.000   4.024
out
#> [[1]]
#> [[1]]$value
#> [1] 1
#> 
#> [[1]]$warning
#> [1] "i is too small, took 9 iterations, code 2."
#> 
#> 
#> [[2]]
#> [[2]]$value
#> [1] 2
#> 
#> [[2]]$warning
#> [1] "i is too small, took 4 iterations, code 2."
#> 
#> 
#> [[3]]
#> [[3]]$value
#> [1] 3
#> 
#> [[3]]$warning
#> [1] ""
#> 
#> 
#> [[4]]
#> [[4]]$value
#> [1] 4
#> 
#> [[4]]$warning
#> [1] ""

Created on 2023-03-23 with reprex v2.0.2

user2554330
  • 37,248
  • 4
  • 43
  • 90
2

I'm not sure how to answer your question except by explaining in more detail the approach using withCallingHandlers and invokeRestart (already mentioned by you and @user2554330).

Without loss of generality, we can restrict attention to warnings signaled by warning(<condition>) rather than warning(<character>). The latter case is conceptually the same, but it involves a layer of C code (for pasting together message components) that isn't central to understanding condition handling.

w.list <- list()
f <- function() { 
    w <- simpleWarning("hello", sys.call())
    for (i in 1:3) warning(w)
    0
}
h <- function(w) { 
    w.list <<- c(w.list, list(w))
    invokeRestart("muffleWarning")
}
list(value = withCallingHandlers(f(), warning = h), warnings = w.list)
$value
[1] 0

$warnings
$warnings[[1]]
<simpleWarning in f(): hello>

$warnings[[2]]
<simpleWarning in f(): hello>

$warnings[[3]]
<simpleWarning in f(): hello>


withCallingHandlers is at first glance quite similar to tryCatch. Both push handlers onto a handler stack, evaluate an expression, and catch signaled conditions for which they find handlers. When a condition is caught by a handler, both clear that handler and those above it on the stack, then evaluate a call to the handler with the caught condition as an argument.

The main difference is the context to which control is transferred when a condition is caught.

When a condition is caught by a handler established by tryCatch(expr, ...), control is transferred to the context of the tryCatch call. Evaluation of expr halts, the handler is called with the caught condition as an argument, and tryCatch returns the value of this handler call. There is no way to resume evaluation of expr without re-evaluating it, because the context of its first evaluation is "lost".

When a condition is caught by a handler established by withCallingHandlers(expr, ...), control "remains" in the context in which the condition was signaled, inside of a call to signalCondition, message, warning, or stop (somewhere in the call stack associated with the evaluation of expr). In the case of warning, that context is right here, between these two .Internal calls:

> body(warning)
## ... TRUNCATED ...
        withRestarts({
            .Internal(.signalCondition(cond, message, call))
            .Internal(.dfltWarn(message, call))
        }, muffleWarning = function() NULL)
        invisible(message)
## ... TRUNCATED ...

The handler is called with the caught condition as an argument, but withCallingHandlers does not return the value of this handler call. Once the handler returns, any remaining handlers are tried in turn until none remain. Finally, evaluation of expr resumes and withCallingHandlers returns the value of expr. In the case of warning, evaluation of expr resumes with the second .Internal call above, which prints the warning message and call.

Thus, invokeRestart("muffleWarning") in this example serves two purposes:

  1. It halts the sequence of handler calls, so that any remaining handlers established by withCallingHandlers are ignored. (Well, here there are none.)
  2. It "skips over" the second .Internal call above, so that the warning message and call are not printed.

It does this by transferring control to the withRestarts call that established the muffleWarning handler. withRestarts returns the result of calling the muffleWarning handler with no arguments (that is, NULL), warning returns invisible(message), and evaluation of expr continues.

It would be nice if help("conditions") documented the muffleMessage and muffleWarning handlers a bit more clearly. Currently, you have to look at the body of message and warning to see that they exist and that they simply return NULL.

Mikael Jagan
  • 9,012
  • 2
  • 17
  • 48