Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Capture Arbitrary Conditions with `withCallingHandlers`

The Problem

I'm trying to write a function that will evaluate code and store the results, including any possible conditions signaled in the code. I've got this working perfectly fine, except for the situation when my function (let's call it evalcapt) is run within an error handling expression.

The problem is that withCallingHandlers will keep looking for matching condition handlers and if someone has defined such a handler outside of my function, my function loses control of execution. Here is simplified example of the problem:

evalcapt <- function(expr) {
  conds <- list()
  withCallingHandlers(
    val <- eval(expr),
    condition=function(e) {
      message("Caught condition of class ", deparse(class(e)))
      conds <<- c(conds, list(e))
  } )
  list(val=val, conditions=conds)
}

myCondition <- simpleCondition("this is a custom condition")
class(myCondition) <- c("custom", class(myCondition))
expr <- expression(signalCondition(myCondition), 25)

tryCatch(evalcapt(expr))          

Works as expected

Caught condition of class c("custom", "simpleCondition", "condition")
$val
[1] 25

$conditions
$conditions[[1]]
<custom: this is a custom condition>

but:

tryCatch(
  evalcapt(expr),               
  custom=function(e) stop("Hijacked `evalcapt`!")  
)

Doesn't work:

Caught condition of class c("custom", "simpleCondition", "condition")
Error in value[[3L]](cond) : Hijacked `evalcapt`!

A Solution I don't Know How To Implement

What I really need is a way of defining a restart right after the condition is signaled in the code which frankly is the way withCallingHandlers appears to work normally (when my handler is the last available handler), but I don't see the restart established when I browse in my handling function and use computeRestarts.

Things That Seem Like Solutions That Won't Work

Use tryCatch

tryCatch does not have the same problem as withCallingHandlers because it does not continue looking for handlers after it finds the first one. The big problem with is it also does not continue to evaluate the code after the condition. If you look at the example that worked above, but sub in tryCatch for withCallingHandlers, the value (25) does not get returned because execution is brought back to the tryCatch frame after the condition is handled.

So basically, I'm looking for a hybrid between tryCatch and withCallingHandlers, one that returns control to the condition signaler, but also stops looking for more handlers after the first one is found.

Break Up The Expression Into Sub-expression, then Use tryCatch

Okay, but how do you break up (and more complex functions with signaled conditions all over the place):

fun <- function(myCondition) {
  signalCondition(myCondition)
  25
}
expr <- expression(fun())

Misc

I looked for the source code associated with the .Internal(.signalCondition()) call to see if I can figure out if there is a behind the scenes restart being set, but I'm out of my depth there. It seems like:

    void R_ReturnOrRestart(SEXP val, SEXP env, Rboolean restart)
    {
        int mask;
        RCNTXT *c;

        mask = CTXT_BROWSER | CTXT_FUNCTION;

        for (c = R_GlobalContext; c; c = c->nextcontext) {
        if (c->callflag & mask && c->cloenv == env)
            findcontext(mask, env, val);
        else if (restart && IS_RESTART_BIT_SET(c->callflag))
            findcontext(CTXT_RESTART, c->cloenv, R_RestartToken);
        else if (c->callflag == CTXT_TOPLEVEL)
            error(_("No function to return from, jumping to top level"));
        }
    }

from src/main/errors.c is doing some of that restart invocation, and this is called by do_signalCondition, but I don't have a clue how I would go about messing with this.

like image 772
BrodieG Avatar asked Dec 13 '13 17:12

BrodieG


2 Answers

I think what you're looking for is to use withRestarts when your special condition is signaled, like from warning:

    withRestarts({
        .Internal(.signalCondition(cond, message, call))
        .Internal(.dfltWarn(message, call))
    }, muffleWarning = function() NULL)

so

evalcapt <- function(expr) {
  conds <- list()
  withCallingHandlers(
    val <- eval(expr),
    custom=function(e) {
      message("Caught condition of class ", deparse(class(e)))
      conds <<- c(conds, list(e))
      invokeRestart("muffleCustom")
  } )
  list(val=val, conditions=conds)
}

expr <- expression(withRestarts({
    signalCondition(myCondition)
}, muffleCustom=function() NULL), 25)

leads to

> tryCatch(evalcapt(expr))   
Caught condition of class c("custom", "simpleCondition", "condition")
$val
[1] 25

$conditions
$conditions[[1]]
<custom: this is a custom condition>


> tryCatch(
+   evalcapt(expr),               
+   custom=function(e) stop("Hijacked `evalcapt`!")  
+ )
Caught condition of class c("custom", "simpleCondition", "condition")
$val
[1] 25

$conditions
$conditions[[1]]
<custom: this is a custom condition>
like image 70
Martin Morgan Avatar answered Sep 27 '22 20:09

Martin Morgan


As far as I can tell there isn't and can't be a simple solution to this problem (I'm happy to be proven wrong). The source of the problem can be seen if we look at how tryCatch and withCallingHandlers register the handlers:

.Internal(.addCondHands(name, list(handler), parentenv, environment(), FALSE)) # tryCatch
.Internal(.addCondHands(classes, handlers, parentenv, NULL, TRUE)) # withCallingHandlers

The key point is the last argument, FALSE in tryCatch, TRUE in withCallingHandlers. This argument leads to the gp bit getting set by do_addCondHands > mkHandlerEntry in src/main/errors.c.

That same bit is then consulted by do_signalCondition (still in src/main/errors.c) when a condition is signaled:

// simplified code excerpt from `do_signalCondition

PROTECT(oldstack = R_HandlerStack);
while ((list = findConditionHandler(cond)) != R_NilValue) {
  SEXP entry = CAR(list);
  R_HandlerStack = CDR(list);
  if (IS_CALLING_ENTRY(entry)) {   // <<------------- Consult GP bit
    ... // Evaluate handler
  } else gotoExitingHandler(cond, ecall, entry);   // Evaluate handler and exit
}
R_HandlerStack = oldstack;
return R_NilValue;

Basically, if the GP bit is set, then we evaluate the handler, and keep iterating through the handler stack. If it isn't set, then we run gotExitingHandler which runs the handler but then returns control to the handling control structure rather than resuming the code where the condition was signaled.

Since the GP bit can only tell you to do one of two things, there is no straightforward way to modify the behavior of this call (i.e. you either iterate through all the handlers if using withCallingHandlers, or you stop at the first matching one registered by tryCatch).

I toyed with the idea of traceing signalConditions to add a restart there, but that seems too hackish.

like image 40
BrodieG Avatar answered Sep 27 '22 19:09

BrodieG