On 30/06/2021 7:37 a.m., Taras Zakharko wrote:
Thats not how I read the code? Consider this snippet from registerS3method:

genfun <- get(genname, envir = envir)
         if (.isMethodsDispatchOn() && methods::is(genfun, "genericFunction"))
             genfun <- methods::finalDefaultMethod(genfun@default)
         if (typeof(genfun) == "closure")
             environment(genfun)
         else .BaseNamespaceEnv

This is the environment where the method cache (.__S3MethodsTable__.) will be 
updated. The problem hoverer, the with the default setting of 
_R_S3_METHOD_LOOKUP_USE_TOPENV_AS_DEFENV_ this is *not* the environment where R 
will look for the method cache. Manually injecting the entry into the method 
cache of the top environment instead works like a charm.

The envir argument is just for looking up the generic function.

Yes, I think you're right: the method is registered in the environment of the generic. I think by default it is searched for in the topenv() of that environment.

In most cases those are the same thing, but in your code they aren't the same: the topenv is the global environment.

So I think I'd agree this is a bug. I'd say the bug is in registerS3method, which should pay attention to the _R_S3_METHOD_LOOKUP_USE_TOPENV_AS_DEFENV_ setting when it computes defenv.

Here's a workaround that copies methods to the appropriate place:

fixS3registrations <- function(genericname, envir = parent.frame()) {
  generic <- get(genericname, envir=envir)
  genenv <- environment(generic)
  top <- topenv(genenv)

  if (!identical(genenv, top)) {
    toptable <- top[[".__S3MethodsTable__."]]
    if (is.null(toptable)) {
      toptable <- new.env(hash = TRUE, parent = baseenv())
      top[[".__S3MethodsTable__."]] <- toptable
    }
    table <- genenv[[".__S3MethodsTable__."]]
    if (!is.null(table)) {
      methodnames <- ls(table, pattern = paste0(genericname, "[.][^.]*$"))
      for (m in methodnames)
        toptable[[m]] <- table[[m]]
    }
  }
}

env <- local({
  # define the generic function and the method
  myfun <- function(x) UseMethod("myfun")
  myfun.myclass <- function(x) print("called myfun.myclass")

     # register the method
     .S3method("myfun", "myclass", myfun.myclass)
     fixS3registrations("myfun")

     environment()
  })

env$myfun(structure(0, class = "myclass"))
#> [1] "called myfun.myclass"


Duncan Murdoch


Best,

Taras



On 30 Jun 2021, at 13:29, Duncan Murdoch <murdoch.dun...@gmail.com> wrote:

On 30/06/2021 7:23 a.m., Taras Zakharko wrote:
I had another glance at the code and now I’m convinced that this is the bug in 
registerS3method(). Default R behavior (in objects.c) appears to be to look for 
method definitions in the top environment, not the defining environment, but 
registerS3method() registers the method in the defining environment. I think 
registerS3method() should be changed to something like:

It registers wherever you ask it to.  The default is the defining environment.

.S3method is the one that always uses the defining environment, since it has no 
way to override the default.

Duncan Murdoch

- if (typeof(genfun) == "closure”)
-            environment(genfun)
------------
+ if (typeof(genfun) == "closure”)
+ if(isFALSE(Sys.getenv("_R_S3_METHOD_LOOKUP_USE_TOPENV_AS_DEFENV_”))  
environment(genfun) else topenv(environment(genfun))
in order to match the behavior of do_usemethod()
Best,
Taras
On 30 Jun 2021, at 12:51, Taras Zakharko <taras.zakha...@uzh.ch> wrote:

@Duncan: .S3method() calls registerS3method() with appropriate environmental 
argument under the good, so that’s not the problem.

Anyway, I’ve been doing some debugging and I think I have found the issue. The 
following snippet in src/objects.c 
(https://github.com/wch/r-source/blob/ecc633b37d77fdd1cb27dda74d7f6b3684f0c01c/src/main/objects.c#L525)
 sets the global lookup_use_topenv_as_defenv variable:


if(lookup_use_topenv_as_defenv == -1) {
        lookup = getenv("_R_S3_METHOD_LOOKUP_USE_TOPENV_AS_DEFENV_");
        lookup_use_topenv_as_defenv =
            ((lookup != NULL) && StringFalse(lookup)) ? 0 : 1;
}

Isn’t that supposed to be

        lookup_use_topenv_as_defenv =  ((lookup != NULL) && 
StringFalse(lookup)) ? 1 : 0;

instead?

The way the code works right now, methods will be looked up in top environment 
exactly if _R_S3_METHOD_LOOKUP_USE_TOPENV_AS_DEFENV_ is not set. This seems 
incompatible with what registerS3method() does (setting the 
.__S3MethodsTable__. on the defining environment instead of the topenv). When I 
change 0 and 1 around, everything works as expected.

In the meantime, I can work around it by manually injecting __S3MethodsTable__ 
into .GlobalEnv (which is my topenv here).

I can open a bug report, but I would like to wait for some more comments.

Best,

Taras

On 30 Jun 2021, at 12:39, Joshua Ulrich <josh.m.ulr...@gmail.com> wrote:

On Wed, Jun 30, 2021 at 5:17 AM Duncan Murdoch <murdoch.dun...@gmail.com> wrote:

On 30/06/2021 5:22 a.m., Taras Zakharko wrote:
Dear all,

I have a generic function and a bunch of methods defined in a separate 
environment. Here is a reduced example:

   env <- local({
     # define the generic function and the method
     myfun <- function(x) UseMethod("myfun")
     myfun.myclass <- function(x) print("called myfun.myclass”)

     # register the method
     .S3method("myfun", "myclass", myfun.myclass)

     environment()
  })

Since the method has been registered, I hoped that invocation like this would 
work:

   env$myfun(structure(0, class = "myclass”))

However, this results in a “no applicable method" error.

It is my understanding that registerS3method (called by .S3method) will install 
the method string in the .__S3MethodsTable__. table of the environment where 
the generic function is defined, and this table is subsequently used by 
usemethod() inside R, so I am puzzled that the dispatch does not work. I 
checked and the  .__S3MethodsTable__. of env is indeed setup correctly. I also 
tried manually adding the method string to the global .__S3MethodsTable__. 
inside .BaseNamespaceEnv to no effect.

In fact, the only way to make it work is to define either myfun or  
myfun.myclas in the global environment, which is something I would like to 
avoid.

Thank you in advance for any pointers!


registerS3method has an additional parameter "envir" which I believe
would end up set to env in your code.  So this works:

eval(expression(myfun(structure(0, class = "myclass"))), envir = env)
[1] "called myfun.myclass"

You could probably also call registerS3method with envir specified
appropriately and get your original expression to work.

That doesn't seem to work on 4.1.0 for me. The code below worked for
me in Oct-2020, though I'm not sure what version of R I was using at
the time. I was slow to upgrade to 4.0, so it was probably the latest
3.x version.

env <- new.env()
local({
  # define the generic function and the method
  myfun <- function(x) { UseMethod("myfun", x) }

  # register the method
  registerS3method("myfun", "myclass",
      function(x) { print("called myfun.myclass") },
      envir = env)
}, envir = env)
attach(env)
myfun(structure(0, class = "myclass"))


Duncan Murdoch

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel



--
Joshua Ulrich  |  about.me/joshuaulrich
FOSS Trading  |  www.fosstrading.com

______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel


______________________________________________
R-devel@r-project.org mailing list
https://stat.ethz.ch/mailman/listinfo/r-devel

Reply via email to