[Rd] Is it possible to retrieve the last error? (not error *message*)

Henrik Bengtsson henrik.bengtsson at gmail.com
Fri May 6 03:17:11 CEST 2016


Thanks.

As mentioned in that Stackoverflow thread, this requires re-evaluation
of the problematic code, which may or may not work (in addition to
taking time).

The closest I get to a solution, but which also requires being
proactive, is to use options(error=...) to record the condition
signaled by stop().  However, contrary to try()/tryCatch(), this is an
option that can be on all the time.  It can be automatically enabled
by setting it in for instance .Rprofile.

## This can be placed in .Rprofile
local({
  recordStop <- function(...) {
    ## Find the stop() frame
    frames <- sys.frames()
    args <- names(formals(base::stop))
    isStop <- lapply(frames, FUN=function(f) all(args %in% names(f)))
    idx <- which(unlist(isStop))[1]
    frame <- frames[[idx]]

    ## Was stop() called with a condition or a message?
    vars <- names(frame)
    if ("cond" %in% vars) {
      .Last.error <- frame$cond
    } else {
      msg <- eval(quote(.makeMessage(..., domain=domain)), envir=frame)
      call <- if (frame$call.) sys.calls()[[1]] else NULL
      .Last.error <- simpleError(msg, call=call)
    }

    assign(".Last.error", .Last.error, envir=.GlobalEnv)
  } ## recordStop()

  options(error=recordStop)
})


Then it can be used as:

## Requires options(error=recordStop)

## stop() at the prompt
stop("Hello")
## Error: Hello
print(.Last.error)
## <simpleError in stop("Hello"): Hello>
str(.Last.error)
# List of 3
#  $ message: chr "woops"
#  $ call   : NULL
#  $ value  : num 2
#  - attr(*, "class")= chr [1:4] "MyError" "simpleError" "error" "condition"


## stop() in a function
foo <- function() stop("woops")
ex <- tryCatch(foo(), error = function(ex) ex)
print(ex)
## <simpleError in foo(): woops>
foo()
## Error in foo() : woops
print(.Last.error)
## <simpleError in foo(): woops>
## Assert identical results
stopifnot(all.equal(.Last.error, ex))


## stop() in a nested call
bar <- function() foo()
ex <- tryCatch(bar(), error = function(ex) ex)
# <simpleError in foo(): woops>
bar()
# Error in foo() : woops
print(.Last.error)
# <simpleError in bar(): woops>
## Assert identical results
stopifnot(all.equal(.Last.error, ex))


## A custom error class
MyError <- function(..., value=0) {
  ex <- simpleError(...)
  ex$value <- value
  class(ex) <- c("MyError", class(ex))
  ex
}


## stop() from prompt
err <- MyError("woops", value=1L)
ex <- tryCatch(stop(err), error = function(ex) ex)
print(ex)
# <MyError: woops>
stop(err)
## Error: woops
print(.Last.error)
# <MyError: woops>
## Assert identical results
stopifnot(all.equal(.Last.error, ex))

## stop() in a function
yo <- function(value=1) stop(MyError("woops", value=value))
ex <- tryCatch(yo(), error = function(ex) ex)
print(ex)
# <MyError: woops>
yo()
# Error: woops
print(.Last.error)
# <MyError: woops>
## Assert identical results
stopifnot(all.equal(.Last.error, ex))

## stop() in a nested call
yeah <- function(value=2) yo(value=value)
ex <- tryCatch(yeah(), error = function(ex) ex)
print(ex)
# <MyError: woops>
yeah()
# Error: woops
print(.Last.error)
# <MyError: woops>
stopifnot(all.equal(.Last.error, ex))
str(.Last.error)
# List of 3
#  $ message: chr "woops"
#  $ call   : NULL
#  $ value  : num 2
#  - attr(*, "class")= chr [1:4] "MyError" "simpleError" "error" "condition"


/Henrik


On Wed, May 4, 2016 at 11:59 PM, Richard Cotton <richierocks at gmail.com> wrote:
> I wondered the same thing a few days ago.
>
> https://stackoverflow.com/questions/36966036/how-to-get-the-last-error
>
> The here's the solution from that discussion:
>
> get_last_error <- function()
> {
>   tr <- .traceback()
>   if(length(tr) == 0)
>   {
>     return(NULL)
>   }
>   tryCatch(eval(parse(text = tr[[1]])), error = identity)
> }
>
> Note that it uses .traceback() from R 3.3.0; you'll have to use
> baseenv()$.Traceback with earlier version of R.
>
> On 4 May 2016 at 22:41, Henrik Bengtsson <henrik.bengtsson at gmail.com> wrote:
>> Hi,
>>
>> at the R prompt, is it possible to retrieve the last error (as in
>> condition object of class "error")?
>>
>> I'm not asking for geterrmessage(), which only returns the error
>> message (as a character string).  I'm basically looking for a
>> .Last.error or .Last.condition, analogously to .Last.value for values,
>> which can be used when it is "too late" (not possible) to go back an
>> use try()/tryCatch().
>>
>> Thanks,
>>
>> Henrik
>>
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>
>
>
> --
> Regards,
> Richie
>
> Learning R
> 4dpiecharts.com



More information about the R-devel mailing list