[R] keep information on the number of warnings

William Dunlap wdunlap at tibco.com
Mon Aug 4 19:04:26 CEST 2014


Look at withCallngHandlers for another way to capture warnings.  It
will let you attach warnings from an iteration of your function to the
output of the function so you can later track down the root cause of
the warning.

E.g., the attached captureWarningsAndMessagesWithContext attaches
warnings, messages, and errors to the output, along with a traceback
for each.

captureWarningsAndMessagesWithContext <-
function(expr) {

   warnings <- list()
   messages <- list()
   fmt <- function(cond, sysCalls) {
      c(Message = conditionMessage(cond),
        Call = deparse(conditionCall(cond))[1],
        rev(vapply(sysCalls, function(sc)deparse(sc)[1], "")))
   }
   retval <- list(result=withCallingHandlers(try(expr, silent=TRUE),
                                  warning=function(w){
                                      warnings[[length(warnings)+1]]
<<- fmt(w, sys.calls())
                                      invokeRestart("muffleWarning")
                                  },
                                  message=function(m){
                                      messages[[length(messages)+1]]
<<- fmt(m, sys.calls())
                                      invokeRestart("muffleMessage")
                                  }
                                 )
                  )
   # retval$result will have class "try-error" if there was an error,
   # which the caller can check for.
   retval$messages <- messages
   retval$warnings <- warnings
   retval
}

E.g.,

z <- lapply(list(log, lm, function(x)1/x),
function(fun)captureWarningsAndMessagesWithContext(fun(-1)))

Bill Dunlap
TIBCO Software
wdunlap tibco.com


On Mon, Aug 4, 2014 at 9:24 AM, Luis Borda de Agua
<lbagua.cloud at gmail.com> wrote:
> Dear David
>
> Thank you very much for your reply. I’ve only seen it now.
> I tried length(warnings) and I got a strange result.
>
> When I used
>
> lw <- length(warnings)
> print(lw)
>
> I obtained lw=36
>
> however,  the number of warnings was 38 according to message to screen:
>
> "There were 38 warnings (use warnings() to see them)"
>
> (I’m listing the warning messages below.)
>
> Why should these numbers be different?
>
> Thank you in advance,
>
> Luís
>
>> warnings()
> Warning messages:
> 1: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 2: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 3: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 4: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 5: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 6: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 7: In stode(y, time, func, parms = parms, ...) :
>   error during factorisation of matrix (dgefa);         singular matrix
> 8: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 9: In stode(y, time, func, parms = parms, ...) :
>   error during factorisation of matrix (dgefa);         singular matrix
> 10: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 11: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 12: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 13: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 14: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 15: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 16: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 17: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 18: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 19: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 20: In stode(y, time, func, parms = parms, ...) :
>   error during factorisation of matrix (dgefa);         singular matrix
> 21: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 22: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 23: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 24: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 25: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 26: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 27: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 28: In stode(y, time, func, parms = parms, ...) :
>   error during factorisation of matrix (dgefa);         singular matrix
> 29: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 30: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 31: In stode(y, time, func, parms = parms, ...) :
>   error during factorisation of matrix (dgefa);         singular matrix
> 32: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 33: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 34: In stode(y, time, func, parms = parms, ...) :
>   error during factorisation of matrix (dgefa);         singular matrix
> 35: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 36: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 37: In stode(y, time, func, parms = parms, ...) : steady-state not reached
> 38: In stode(y, time, func, parms = parms, ...) : steady-state not reached
>
>
>
>
>
> _______________________________
> Luís Borda de Água
> Centro de Biologia Ambiental
> Faculdade de Ciências
> Universidade de Lisboa
> Edifício C2, 6º Piso, Sala 2.6.04/07
> Campo Grande
> 1749-016 Lisboa, Portugal
> Tel: +351 21 750 00 00 (ext: 22607)
> Fax: +351 21 750 00 28
>
>
>
>
>
>
>
>
>
>
>         [[alternative HTML version deleted]]
>
>
> ______________________________________________
> R-help at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
>



More information about the R-help mailing list