warnings and tryCatch() (Was: RE: [R] catching the warnings)

Luke Tierney luke at stat.uiowa.edu
Fri Jun 4 03:06:39 CEST 2004


The bits you need for collecting warnings are described on the
`warning' help page, though rather tersely.  The implementation of
suppressWarnings provides an example:
                                           
> suppressWarnings
function (expr)
{
    withCallingHandlers(expr, 
                        warning = function(w) invokeRestart("muffleWarning"))
}

This does two things:

    It uses withCallingHandlers to have the handler called from
    within the warning call rather than after a jump back to the context
    where the handler is established, as happens with tryCatch.

    Within the handler it invokes the 'muffleWarnings' restart to avoid
    continuing with the default handling of the warning (which would put
    it on the list that eventually gets printed).

If you want to write a function that computes a value and collects all
warning you could do it like this:

    withWarnings <- function(expr) {
	myWarnings <- NULL
	wHandler <- function(w) {
	    myWarnings <<- c(myWarnings, list(w))
	    invokeRestart("muffleWarning")
	}
	val <- withCallingHandlers(expr, warning = wHandler)
	list(value = val, warnings = myWarnings)
    }

This gives

    > withWarnings({warning("A");warning("B");1})
    $value
    [1] 1

    $warnings
    $warnings[[1]]
    <simpleWarning in withCallingHandlers(expr, warning = wHandler): A>

    $warnings[[2]]
    <simpleWarning in withCallingHandlers(expr, warning = wHandler): B>


On Fri, 4 Jun 2004, Henrik Bengtsson wrote:

> Seeing this question I was thinking of using tryCatch() to "catch" warnings.
> Here is an example:
> 
> doWarn <- function() {
>   a <<- 1
>   warning("Wow!")
>   a <<- 2
> }
> 
> lastError <- lastWarning <- NULL
> tryCatch({ 
>   x <- 2 
>   doWarn()
>   x <- 3
>   stop("Oops.")
>   x <- 4
> }, warning = function(warn) { 
>   lastWarning <<- warn
> }, error = function(err) { 
>   lastError <<- err
> })
> stopifnot(a==1)
> stopifnot(x==2)
> stopifnot(inherits(lastWarning, "simpleWarning"))
> stopifnot(is.null(lastError))
> 
> However, as the example shows, as soon as a warning is caught, tryCatch()
> returns without evaluating the rest of the expressions. My question: is
> there a simple way to continue the evaluation of expressions following the
> expression that generated the condition? For instance, can I continue at "a
> <<- 2" inside doWarn() by "doing something" within the warning handler? 

You can by using a calling handler rather than an exiting
one. tryCatch establishes exiting handlrs that are called after a jump
from the point where the condition is signaled to the point where the
handler is established, i.e. the tryCatch context.

> I have noticed withCallingHandlers():
> 
> lastError <- lastWarning <- NULL
> withCallingHandlers({ 
>   x <- 2 
>   doWarn()
>   x <- 3
>   stop("Oops.")
>   x <- 4
> }, warning = function(warn) { 
>   lastWarning <<- warn
> }, error = function(err) { 
>   lastError <<- err
> })
> stopifnot(a==2)
> stopifnot(x==3)
> stopifnot(inherits(lastWarning, "simpleWarning"))
> stopifnot(inherits(lastError, "simpleError"))
> 
> Is the latter intended for what I am asking for? It will solve it for
> warnings, but it will not allow to restart/continue after an error. Also, in
> this case the error message is shown.

If the calling handler returns then other available handlers, if any,
are tried and finally the default mechanism of the signaling function
is used.  For warnings the default handling involves storing the
message and then continuing; for errors signaled with stop or the
internal error function it usually involves printing a message and
jumping to top level.

Hope that helps.

luke

> Cheer
> 
> Henrik Bengtsson
> 
> 
> -----Original Message-----
> From: r-help-bounces at stat.math.ethz.ch
> [mailto:r-help-bounces at stat.math.ethz.ch] On Behalf Of Roger D. Peng
> Sent: Thursday, June 03, 2004 2:43 PM
> To: Marc Mamin
> Cc: r-help at stat.math.ethz.ch
> Subject: Re: [R] catching the warnings
> 
> 
> The warnings are stored in a variable `last.warning' in the workspace. 
>   warnings() simply prints this variable.
> 
> -roger
> 
> Marc Mamin wrote:
> > Hello,
> > 
> > I'd like to catch the warnings in a variable in order to evaluate 
> > them, but...
> > 
> > 
> > 
> >>tt<-warnings()
> > 
> > Warning messages:
> > 1: XML Parsing Error: test.xml:2: xmlParseStartTag: invalid element 
> > name
> > 2: XML Parsing Error: test.xml:3: Extra content at the end of the document
> > 
> >>tt
> > 
> > NULL
> > 
> > is there a way to achieve this (R1.8.1)?
> > 
> > thanks,
> > 
> > Marc
> > 
> > ______________________________________________
> > R-help at stat.math.ethz.ch mailing list 
> > https://www.stat.math.ethz.ch/mailman/listinfo/r-help
> > PLEASE do read the posting guide! 
> > http://www.R-project.org/posting-guide.html
> >
> 
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide!
> http://www.R-project.org/posting-guide.html
> 
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide! http://www.R-project.org/posting-guide.html
> 

-- 
Luke Tierney
University of Iowa                  Phone:             319-335-3386
Department of Statistics and        Fax:               319-335-3017
   Actuarial Science
241 Schaeffer Hall                  email:      luke at stat.uiowa.edu
Iowa City, IA 52242                 WWW:  http://www.stat.uiowa.edu




More information about the R-help mailing list