[Rd] suppress *specific* warnings?

luke-tierney at uiowa.edu luke-tierney at uiowa.edu
Mon Oct 22 18:57:49 CEST 2012


On Sun, 21 Oct 2012, Martin Morgan wrote:

> On 10/21/2012 12:28 PM, Ben Bolker wrote:
>>
>>    Not desperately important, but nice to have and possibly of use to
>> others, is the ability to suppress specific warnings rather than
>> suppressing warnings indiscriminately.  I often know of a specific
>> warning that I want to ignore (because I know that's it's a false
>> positive/ignorable), but the current design of suppressWarnings() forces
>> me to ignore *any* warnings coming from the expression.
>>
>>    I started to write a new version that would check and, if supplied
>> with a regular expression, would only block matching warnings and
>> otherwise would produce the warnings as usual, but I don't quite know
>> enough about what I'm doing: see ??? in expression below.
>>
>>    Can anyone help, or suggest pointers to relevant
>> examples/documentation (I've looked at demo(error.catching), which isn't
>> helping me ... ?)
>> 
>> suppressWarnings2 <- function(expr,regex=NULL) {
>>      opts <- options(warn = -1)
>>      on.exit(options(opts))
>
> I'm not really sure what the options(warn=-1) is doing there, maybe its for 
> efficiency to avoid generating a warning message (as distinct from signalling

The sources in srs/library/base/conditions.R have

suppressWarnings <- function(expr) {
     ops <- options(warn = -1) ## FIXME: temporary hack until R_tryEval
     on.exit(options(ops))     ## calls are removed from methods code
     withCallingHandlers(expr,
                         warning=function(w)
                             invokeRestart("muffleWarning"))
}

I uspect we have still not entirely eliminated R_tryEval in this context
but I'm not sure. Will check when I get a chance.

> a warning). I think you're after something like
>
>  suppressWarnings2 <-
>      function(expr, regex=character())
>  {
>      withCallingHandlers(expr, warning=function(w) {
>          if (length(regex) == 1 && length(grep(regex, conditionMessage(w)))) 
> {
>              invokeRestart("muffleWarning")
>          }
>      })
>  }

A problem with using expression matching is of course that this fails
with internationalized messages. Ideally warnings should be signaled as
warning conditions of a particular class, and that class can be used
to discriminate. Unfortunately very few warnings are designed this way.

Best,

luke

>
> If the  restart isn't invoked, then the next handler is called and the 
> warning is handled as normal. So with
>
>  f <- function() {
>      warning("oops")
>      2
>  }
>
> there is
>
>> suppressWarnings2(f())
> [1] 2
> Warning message:
> In f() : oops
>> suppressWarnings2(f(), "oops")
> [1] 2
>
> For your own code I think a better strategy is to create a sub-class of 
> warnings that can be handled differently
>
>  mywarn <-
>      function(..., call.=TRUE, immediate.=FALSE, domain=NULL)
>  {
>      msg <- .makeMessage(..., domain=domain, appendLF=FALSE)
>      call <- NULL
>      if (call.)
>          call <- sys.call(1L)
>      class <- c("silencable", "simpleWarning",  "warning", "condition")
>      cond <- structure(list(message=msg, call=call), class=class)
>      warning(cond)
>  }
>
>  suppressWarnings3 <-
>          function(expr)
>  {
>      withCallingHandlers(expr, silencable=function(w) {
>          invokeRestart("muffleWarning")
>      })
>  }
>
> then with
>
>  g <- function() {
>      mywarn("oops")
>      3
>  }
>
>> suppressWarnings3(f())
> [1] 2
> Warning message:
> In f() : oops
>> g()
> [1] 3
> Warning message:
> In g() : oops
>> suppressWarnings3(g())
> [1] 3
>
>>      withCallingHandlers(expr, warning = function(w) {
>>          ## browser()
>>          if (is.null(regex) || grepl(w[["message"]],regex)) {
>>              invokeRestart("muffleWarning")
>>          } else {
>>              ## ? what do I here to get the warning issued?
>>              ## browser()
>>              ## computeRestarts() shows "browser",
>>              ##    "muffleWarning", and "abort" ...
>>              options(opts)
>>              warning(w$message)
>>              ## how can I get back from here to the calling point
>>              ##   *without* muffling warnings ... ?
>>          }
>>      })
>> }
>> 
>> suppressWarnings2(sqrt(-1))
>> suppressWarnings2(sqrt(-1),"abc")
>>
>>    It seems to me I'd like to have a restart option that just returns to
>> the point where the warning was caught, *without* muffling warnings ...
>> ?  But I don't quite understand how to set one up ...
>>
>>    Ben Bolker
>> 
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>> 
>
>
>

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



More information about the R-devel mailing list