>>>>> Suharto Anggono Suharto Anggono
>>>>> on Wed, 27 Feb 2019 22:46:04 +0000 writes:
> My points:
> - The 'withCallingHandlers' construct that is used in current
'stopifnot' code has no effect. Without it, the warning message is the
same. The overridden warning is not raised. The original warning stays.
> - Overriding call in error and warning to 'cl.i' doesn't
always give better outcome. The original call may be "narrower" than
'cl.i'.
I see. Thank you for stating the summary.
> I have found these examples.
> identity(is.na(log()))
> identity(is.na(log("a")))
> Error message from the first contains full call. Error message from the
second doesn't.
> So, how about being "natural", not using
'withCallingHandlers' and 'tryCatch' in 'stopifnot'?
If we can achieve good (or better) messages as before, I
entirely agree.
Originally, one "design principle" for stopifnot() had been to
create a relatively simple "self explaining" (for code readers)
function with that functionality.
The all.equal() special treatment has really added an extra
level of usefulness, and the somewhat recent ensuring of careful
sequential eval() is also important.
Somewhere there I found I'd need the sophisticated error
catching [tryCatch() ..], but if turns that it is unneeded, I
think we'd all be more than happy.
> Another thing: currently,
> stopifnot(exprs=TRUE)
> fails.
good catch - indeed!
I've started to carefully test and try the interesting nice
patch you've provided below.
Thank you very much for your careful and constructive
suggestions! I'll get back after some testing {and fulfilling
quite a few other jobs/duties I've got these days ...}
Martin
> A patch:
> --- stop.R 2019-02-27 16:15:45.324167577 +0000
> +++ stop_new.R 2019-02-27 16:22:15.936203541 +0000
> @@ -1,7 +1,7 @@
> # File src/library/base/R/stop.R
> # Part of the R package, https://www.R-project.org
> #
> -# Copyright (C) 1995-2018 The R Core Team
> +# Copyright (C) 1995-2019 The R Core Team
> #
> # This program is free software; you can redistribute it and/or modify
> # it under the terms of the GNU General Public License as published by
> @@ -33,25 +33,27 @@
> stopifnot <- function(..., exprs, local = TRUE)
> {
> + n <- ...length()
> missE <- missing(exprs)
> - cl <-
> if(missE) { ## use '...' instead of exprs
> - match.call(expand.dots=FALSE)$...
> } else {
> - if(...length())
> + if(n)
> stop("Must use 'exprs' or unnamed expressions, but not
both")
> envir <- if (isTRUE(local)) parent.frame()
> else if(isFALSE(local)) .GlobalEnv
> else if (is.environment(local)) local
> else stop("'local' must be TRUE, FALSE or an
environment")
> exprs <- substitute(exprs) # protect from evaluation
> - E1 <- exprs[[1]]
> + E1 <- if(is.call(exprs)) exprs[[1]]
> + cl <-
> if(identical(quote(`{`), E1)) # { ... }
> - do.call(expression, as.list(exprs[-1]))
> + exprs[-1]
> else if(identical(quote(expression), E1))
> eval(exprs, envir=envir)
> else
> as.expression(exprs) # or fail ..
> + if(!is.null(names(cl))) names(cl) <- NULL
> + return(eval(as.call(c(sys.call()[[1]], as.list(cl))),
envir=envir))
> }
> Dparse <- function(call, cutoff = 60L) {
> ch <- deparse(call, width.cutoff = cutoff)
> @@ -62,14 +64,10 @@
> abbrev <- function(ae, n = 3L)
> paste(c(head(ae, n), if(length(ae) > n) "...."),
collapse="\n ")
> ##
> - for (i in seq_along(cl)) {
> - cl.i <- cl[[i]]
> - ## r <- eval(cl.i, ..) # with correct warn/err messages:
> - r <- withCallingHandlers(
> - tryCatch(if(missE) ...elt(i) else eval(cl.i, envir=envir),
> - error = function(e) { e$call <- cl.i; stop(e) }),
> - warning = function(w) { w$call <- cl.i; w })
> + for (i in seq_len(n)) {
> + r <- ...elt(i)
> if (!(is.logical(r) && !anyNA(r) && all(r))) {
> + cl.i <- match.call(expand.dots=FALSE)$...[[i]]
> msg <- ## special case for decently written 'all.equal(*)':
> if(is.call(cl.i) && identical(cl.i[[1]], quote(all.equal))
&&
> (is.null(ni <- names(cl.i)) || length(cl.i) == 3L ||
> @@ -84,7 +82,11 @@
> "%s are not all TRUE"),
> Dparse(cl.i))
> - stop(simpleError(msg, call = sys.call(-1)))
> + p <- sys.parent()
> + if(p && identical(sys.function(p), stopifnot) &&
> + !eval(expression(missE), p)) # originally stopifnot(exprs=*)
> + p <- sys.parent(2)
> + stop(simpleError(msg, call = if(p) sys.call(p)))
> }
> }
> invisible()
> --------------------------------------------
> On Wed, 27/2/19, Martin Maechler <maechler at stat.math.ethz.ch>
wrote:
> Subject: Re: [Rd] stopifnot
> To: "Suharto Anggono Suharto Anggono" <suharto_anggono at
yahoo.com>
> Cc: r-devel at r-project.org
> Date: Wednesday, 27 February, 2019, 5:36 PM
>>>>> Suharto Anggono Suharto Anggono via R-devel
>>>>>> ? ? on Sun, 24 Feb 2019 14:22:48 +0000 writes:
> ? ? >> From
https://github.com/HenrikBengtsson/Wishlist-for-R/issues/70 :
> ? ? > ... and follow up note from 2018-03-15: Ouch... in R-devel,
stopifnot() has become yet 4-5 times slower;
> ? ? > ...
> ? ? > which is due to a complete rewrite using tryCatch() and
withCallingHandlers().
> ? ? >> From
https://stat.ethz.ch/pipermail/r-devel/2017-May/074256.html , it seems that
'tryCatch' was used to avoid the following example from giving error
message with 'eval' call and 'withCallingHandlers' was meant to
handle similar case for warning.
> ? ? > tst <- function(y) { stopifnot(is.numeric(y)); y+ 1 }
> ? ? > try(tst())
> ? ? > However,
> ? ? > withCallingHandlers(<something>,
> ? ? > warning = function(w) { w$call <- cl.i; w })
> ? ? > actally has no effect. In current code of function
'stopifnot', 'eval' is used only in handling stopifnot(exprs=) .
The warning message from
> ? ? > stopifnot(exprs={warning()})
> ? ? > has 'eval' call:
> ? ? > In eval(cl.i, envir = envir) :
> ? ? > This may work.
> ? ? > withCallingHandlers(<something>,
> ? ? > warning = function(w) {
> ? ? > w$call <- cl.i; warning(w);
invokeRestart("muffleWarning") })
> ? ? > Current documentation says:
> ? ? > Since R version 3.5.0, expressions are evaluated sequentially,
and hence evaluation stops as soon as there is a "non-TRUE",
asnindicated by the above conceptual equivalence statement. Further, when such
an expression signals an error or warning, its conditionCall() no longer
contains the full stopifnot call, but just the erroneous expression.
> ? ? > I assume that "no longer contains ..." is supposed
to be the effect of the use of 'withCallingHandlers' and
'tryCatch' in 'stopifnot'.
> ? ? > Actually, "contains the full stopifnot call" is not
always the case in R before version 3.5.0. Normally, the call is the
"innermost context".
> Thank you Suharto, for thinking about these issues and being
> constructive, trying to improve the current state.
> Unfortunately, I do not quite understand what you are trying to
> say here.
> The main somewhat recent changes to stopifnot() have been (in
> inverse time ordering)
> 1) Do what the documentation always promised, namely eval() the
> ? expressions one by one, and stop evaluation as soon as one of
> ? them is not all(.) TRUE.
> ? For that reason, the previously used idiom? 'list(...)'
> ? is a no go, as "of course", it evaluates all the
expressions in '...'
> 2) Try to ensure that warning() and stop()/error messages are
> ? shown the same {as closely as feasible}? to how they are
> ? shown outside of stopifnot(.)
> ? ? ? ? ? ? ==> partly the topic of this e-mail.
> 3) [2.5 years ago:] stopifnot() became smart about all.equal(.)
expressions,
> ? showing the all.equal() string if it was not TRUE:
> ? In older R versions (<= 3.3.x ?), we had
> ? ? ? > stopifnot(all.equal(pi, 3.1415))
> ? ? Error: all.equal(pi, 3.1415) is not TRUE
> ? where as in R (>= 3.4.0 at least):
> ? ? ? > stopifnot(all.equal(pi, 3.1415))
> ? ? ? Error: pi and 3.1415 are not equal:
> ? ? Mean relative difference: 2.949255e-05
> One example of what I meant with the above documentation ("no
> longer contains")? is the following:
> In R 3.5.x,
> ? > lf <- list(fm = y ~ f(x), osf = ~ sin(x))
> ? > stopifnot(identical(deparse(lf), deparse(lf,
control="all")))
> ? Warning message:
> ? In deparse(lf, control = "all") : deparse may be incomplete
> ? >
> If I change the calling handler to use the
> invokeRestart("muffleWarning") which I understand you are
> proposing, then the message becomes
> ? Warning message:
> ? In identical(deparse(lf, control = "all"), deparse(lf)) :
> ? ? deparse may be incomplete
> which is less useful as I can no longer see directly which of
> the deparse() produced the warning.
> ? ? > Example:
> ? ? > stopifnot((1:2) + (1:3) > 0)
> ? ? > Warning message:
> ? ? > In (1:2) + (1:3) :
> ? ? >?? longer object length is not a multiple of shorter object
length
> Which is the good answer
> (whereas also showing "> 0" in the warning is slightly
off).
> Again, if I'd use the? ..muffleWarning.. code instead, the above
> would change to the worse
> ? ? Warning message:
> ? ? In (1:2) + (1:3) > 0 :
> ? ? ? longer object length is not a multiple of shorter object length
> which "wrongly includes the '> 0'.
> So I guess I really don't understand what you are proposing, or
> would like to change? ...
> ? ? > Example that gives error:
> ? ? > stopifnot(is.na(log("a")))
> ? ? > R 3.5.0:
> ? ? > R 3.3.2:
> That's a good one: we want the error message *not to* mention
> is.na(.) but just 'log': i.e.,
> We'd like? [ R versions <= 3.4.4 ] :
>> stopifnot(is.na(log("a")))
> Error in log("a") : non-numeric argument to mathematical
function
> as opposed to [ R version >= 3.5.0 ] :
>> stopifnot(is.na(log("a")))
> Error in is.na(log("a")) : non-numeric argument to
mathematical function
> -----------------------------------------
> Again, I'm sure I partly failed to understand what you said in
> your e-mail and apologize for that.
> Of course, I'm happy and glad to discuss improvements to
> stopifnot() which improve speed (while retaining important
> current functionality)? or also just improve current
> functionality
> -- e.g. get the "better" error message in the
stopifnot(is.na(log("a")))
> ? example.
> High regards,
> Martin Maechler