[Rd] all.equal applied to function closures

Bill Dunlap w||||@mwdun|@p @end|ng |rom gm@||@com
Mon Nov 30 22:41:54 CET 2020


To make the comparison more complete, all.equal.environment could compare
the parents of the target and current environments.  That would have to be
recursive but could stop at the first 'top level environment' (the global,
empty, or a package-related environment generally) and use identical
there.  E.g.,

> f1 <- function(x) (function(){ expx <- exp(x) ; function(y) y + expx})()
> all.equal(f1(2), f1(3))
[1] "Environments: Component “expx”: Mean relative difference: 1.718282"

[2] "Environments: <parent.env> Component “x”: Mean relative difference:
0.5"

This is from the following, where I avoided putting the existing
non-recursive all.equal.environment into the body of this one.

all.equal.environment <-
function(target, current, ...)
{
    .all.equal.environment <- base::all.equal.environment # temporary hack
    stopifnot(is.environment(target), is.environment(current))
    if (identical(target, current)) {
        TRUE
    } else {
        msg <- NULL # TODO: check attributes
        # deal with emptyenv now since parent.env(emptyenv()) gives error
        # and topenv(emptyenv()) gives GlobalEnv
        eTarget <- identical(target, emptyenv()) ||
identical(target,topenv(target))
        eCurrent <- identical(current, emptyenv()) ||
identical(current,topenv(current))
        if (eTarget || eCurrent) {
            msg <- c(msg, paste("target is", format(target), "and current
is", format(current)))
        } else {
            thisComparison <- .all.equal.environment(target, current, ...)
            if (!isTRUE(thisComparison)) {
                msg <- c(msg, thisComparison)
            }
            parentComparison <- Recall(parent.env(target),
parent.env(current), ...)
            if (!isTRUE(parentComparison)) {
                msg <- c(msg, paste("<parent.env>", parentComparison))
            }
        }
        if (is.null(msg) || isTRUE(msg)) TRUE else msg
    }
}

On Mon, Nov 30, 2020 at 10:42 AM Duncan Murdoch <murdoch.duncan using gmail.com>
wrote:

> On 30/11/2020 1:05 p.m., Kevin Van Horn via R-devel wrote:
> > Consider the following code:
> >
> >      f <- function(x)function(y){x+y}
> >      all.equal(f(5), f(0))
> >
> > This returns TRUE, when it should return FALSE; I think it’s hard to
> make the case that f(5) and f(0) are “approximately equal” in any
> meaningful sense. Digging into the code for all.equal(), I see that
> all.equal(f(5), f(0)) results in a call to all.equal.language(f(5), f(0)),
> which only compares the function texts for equality.
> >
> > If it is decided to leave this behavior as-is, then at least it should
> be documented. Currently I cannot find any documentation for all.equal
> applied to functions.
>
> Clearly it should also compare the environments of the two functions,
> then it would see a difference:
>
>  > all.equal(environment(f(5)), environment(f(0)))
> [1] "Component “x”: Mean relative difference: 1"
>
> Changing the first few lines from
>
>      if (is.language(target) || is.function(target))
>          return(all.equal.language(target, current, ...))
>
> to
>
>      if (is.function(target)) {
>          msg <- all.equal.language(target, current, ...)
>          if (isTRUE(msg)) {
>              msg <- all.equal.environment(environment(target),
> environment(current), ...)
>              if (is.character(msg))
>                msg <- paste("Environments:", msg)
>          }
>          return(msg)
>      }
>      if (is.language(target))
>          return(all.equal.language(target, current, ...))
>
> would fix it.
>
> Duncan Murdoch
>
> ______________________________________________
> R-devel using r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>

	[[alternative HTML version deleted]]



More information about the R-devel mailing list