Hi, I ran into a problem with S3 method dispatch and scoping while trying to use functions from the mixR package within my own functions. I know enough to find the problem (I think!), but not enough to fix it myself. The problem isn't really a package-specific problem, so I'm starting here, and will file an issue with the maintainer once I have a solution. Detailed explanation below, but briefly, the S3 methods in this package use match.call() and then eval() to select the correct internal method. This works fine from the command line, but if the method is called from within another function, the use of environment() within eval() means that the objects passed to the wrapper function are no longer visible within the eval() call. I have a two-part question: A. How do I get around this right now? B. What would the correct approach be for the package authors? library(mixR) # first example from ?mixfit ## fitting the normal mixture models set.seed(103) x <- rmixnormal(200, c(0.3, 0.7), c(2, 5), c(1, 1)) data <- bin(x, seq(-1, 8, 0.25)) fit1 <- mixfit(x, ncomp = 2) # raw data rm(x, data) ### # simple function funworks <- function(x) { print(x) } ### # almost identical simple function funfails <- function(thisx) { print(thisx) } ### funworks(fit1) funfails(fit1) ####### The explanation as I understand it... print called on this object gets passed to print.mixfitEM(), which is: function (x, digits = getOption("digits"), ...) { family <- x$family mc <- match.call() mc$digits <- digits fun.name <- paste0("print", family) mc[[1]] <- as.name(fun.name) eval(mc, environment()) } Working through the calls, when eval() is called from within funfails(), mc is printnormal(x = thisx, digits = 7) and the calling environment does not contain thisx. In funworks(), it's printnormal(x = x, digits = 7) and x is found. So, I can get around the problem by naming my argument x, as in funworks(), but that's unsatisfying. Is there something else I can do to get my functions to work? And what's the correct way to do what print.mixfitEM() is doing, so that it works regardless? I poked around for a while, but didn't find a clear (to me!) answer. Thanks, Sarah -- Sarah Goslee (she/her) http://www.numberwright.com
On 25/05/2023 10:18 a.m., Sarah Goslee wrote:> Hi, > > I ran into a problem with S3 method dispatch and scoping while trying > to use functions from the mixR package within my own functions. I know > enough to find the problem (I think!), but not enough to fix it > myself. The problem isn't really a package-specific problem, so I'm > starting here, and will file an issue with the maintainer once I have > a solution. > > Detailed explanation below, but briefly, the S3 methods in this > package use match.call() and then eval() to select the correct > internal method. This works fine from the command line, but if the > method is called from within another function, the use of > environment() within eval() means that the objects passed to the > wrapper function are no longer visible within the eval() call. > > I have a two-part question: > A. How do I get around this right now? > B. What would the correct approach be for the package authors?I'll try B first. The problem is that they want to look up fun.name in the environment that is visible from print.mixfitEM(), i.e. the mixR internal namespace environment, and they also want to evaluate that function the way it was evaluated when print.mixfitEM was called, i.e. in parent.frame(). R doesn't support that kind of thing in one step, so they should do it in two steps, e.g. rewriting print.mixfitEM something like this: function (x, digits = getOption("digits"), ...) { family <- x$family mc <- match.call() mc$digits <- digits fun.name <- paste0("print", family) e <- new.env(parent = parent.frame()) e[[fun.name]] <- get(fun.name) mc[[1]] <- as.name(fun.name) eval(mc, e) } This tries to get the function ("printnormal") from the local evaluation environment, but there's nothing there named "printnormal", so it goes to the parent environment, and gets it there. It puts it in a new environment whose parent is parent.frame() and everything works. For part A of your question, I can't think of any workaround other than using x as the name of the variable that is passed to print(). You could hide that fact by making a local function to do it, e.g. myprint <- function(x) print(x) and then calling myprint(fit1). Duncan Murdoch> > library(mixR) > > # first example from ?mixfit > ## fitting the normal mixture models > set.seed(103) > x <- rmixnormal(200, c(0.3, 0.7), c(2, 5), c(1, 1)) > data <- bin(x, seq(-1, 8, 0.25)) > fit1 <- mixfit(x, ncomp = 2) # raw data > rm(x, data) > ### > > # simple function > funworks <- function(x) { > print(x) > } > > ### > > # almost identical simple function > funfails <- function(thisx) { > print(thisx) > } > > ### > > funworks(fit1) > funfails(fit1) > > ####### > > The explanation as I understand it... > > print called on this object gets passed to print.mixfitEM(), which is: > > > function (x, digits = getOption("digits"), ...) > { > family <- x$family > mc <- match.call() > mc$digits <- digits > fun.name <- paste0("print", family) > mc[[1]] <- as.name(fun.name) > eval(mc, environment()) > } > > > Working through the calls, when eval() is called from within funfails(), mc is > printnormal(x = thisx, digits = 7) > and the calling environment does not contain thisx. > > In funworks(), it's > printnormal(x = x, digits = 7) > > and x is found. > > So, I can get around the problem by naming my argument x, as in > funworks(), but that's unsatisfying. Is there something else I can do > to get my functions to work? > > And what's the correct way to do what print.mixfitEM() is doing, so > that it works regardless? I poked around for a while, but didn't find > a clear (to me!) answer. > > Thanks, > Sarah >
? Thu, 25 May 2023 10:18:13 -0400 Sarah Goslee <sarah.goslee at gmail.com> ?????:> print called on this object gets passed to print.mixfitEM(), which is: > > > function (x, digits = getOption("digits"), ...) > { > family <- x$family > mc <- match.call() > mc$digits <- digits > fun.name <- paste0("print", family) > mc[[1]] <- as.name(fun.name) > eval(mc, environment()) > } > > > Working through the calls, when eval() is called from within > funfails(), mc is printnormal(x = thisx, digits = 7) > and the calling environment does not contain thisx.Your functions, both funworks and funfails, did nothing wrong. They are using R as intended, so there shouldn't be anything to fix. I think that mixR::mixfitEM is making a mistake in its use of non-standard evaluation. When working with match.call(), the typical pattern is to eval() the modified call in the parent.frame() (where the call had originated and where, presumably, all its referenced variables still live). mixR cannot use this pattern unaltered because they want to call an unexported function, e.g., mixR:::printnormal. The authors could construct a call to ::: and insert that into mc[[1]] instead of as.name(fun.name), so that the resulting call would be to mixR:::printnormal(remaining arguments) and would thus cleanly evaluate in the calling environment, but R CMD check could give them a NOTE for using ::: (even with their own package). One way to get around this would be to put the function itself in the first element of the call (i.e. mc[[1]] <- get(fun.name) instead of as.name(fun.name)), thus also making it possible to perform the call despite as.name(fun.name) cannot be resolved from parent.frame(). This could lead to scary-looking tracebacks. Another way would be to keep the environment of the call as it is, but evaluate the arguments from the matched call, something like: for (i in seq_along(mc)[-1]) mc[[i]] <- eval(mc[[i]], parent.frame()) This code is untested, but the idea is to remove any dependency of the matched call on the calling frame, thus making it possible to evaluate it without problems in the package environment. This will again lead to scary-looking tracebacks, potentially worse than the previous option (depending on whether deparse() is longer for mixR:::printnormal or its typical arguments), and will also wreak havoc on any additional use of non-standard evaluation by printnormal (hopefully there isn't any, but any arguments that should have stayed quoted will be evaluated instead). They already do something like this with the digits=... argument. I could also suggest a redesign of the package to make fuller use of the S3 dispatch system (i.e. prepend x$family to class(x), possibly with a package-specific prefix and make printnormal() and friends into S3 methods for print()) instead of trying to implement it oneself, but I understand that it may be not an available option. I was going to suggest patching around the bug using trace(), but it doesn't seem to work well with S3 method dispatch. No matter what I do, UseMethod() seems to pick up the original definition of mixR:::print.mixfitEM instead of the trace()-altered version: trace(mixR:::print.mixfitEM, quote({ mc$x <- x }), at = 7) mixR:::print.mixfitEM(fit1) # works as expected, but that doesn't matter print(fit1) # tracer not called -- Best regards, Ivan
Thank you to both Duncan and Ivan for the detailed answers. I'll point the mixR maintainer at this thread in the list archive, because your suggestions were so clear, and I can't explain them as thoroughly. I'll keep using x as the argument name for now. Much appreciated, Sarah On Thu, May 25, 2023 at 10:18?AM Sarah Goslee <sarah.goslee at gmail.com> wrote:> > Hi, > > I ran into a problem with S3 method dispatch and scoping while trying > to use functions from the mixR package within my own functions. I know > enough to find the problem (I think!), but not enough to fix it > myself. The problem isn't really a package-specific problem, so I'm > starting here, and will file an issue with the maintainer once I have > a solution. > > Detailed explanation below, but briefly, the S3 methods in this > package use match.call() and then eval() to select the correct > internal method. This works fine from the command line, but if the > method is called from within another function, the use of > environment() within eval() means that the objects passed to the > wrapper function are no longer visible within the eval() call. > > I have a two-part question: > A. How do I get around this right now? > B. What would the correct approach be for the package authors? > > library(mixR) > > # first example from ?mixfit > ## fitting the normal mixture models > set.seed(103) > x <- rmixnormal(200, c(0.3, 0.7), c(2, 5), c(1, 1)) > data <- bin(x, seq(-1, 8, 0.25)) > fit1 <- mixfit(x, ncomp = 2) # raw data > rm(x, data) > ### > > # simple function > funworks <- function(x) { > print(x) > } > > ### > > # almost identical simple function > funfails <- function(thisx) { > print(thisx) > } > > ### > > funworks(fit1) > funfails(fit1) > > ####### > > The explanation as I understand it... > > print called on this object gets passed to print.mixfitEM(), which is: > > > function (x, digits = getOption("digits"), ...) > { > family <- x$family > mc <- match.call() > mc$digits <- digits > fun.name <- paste0("print", family) > mc[[1]] <- as.name(fun.name) > eval(mc, environment()) > } > > > Working through the calls, when eval() is called from within funfails(), mc is > printnormal(x = thisx, digits = 7) > and the calling environment does not contain thisx. > > In funworks(), it's > printnormal(x = x, digits = 7) > > and x is found. > > So, I can get around the problem by naming my argument x, as in > funworks(), but that's unsatisfying. Is there something else I can do > to get my functions to work? > > And what's the correct way to do what print.mixfitEM() is doing, so > that it works regardless? I poked around for a while, but didn't find > a clear (to me!) answer. > > Thanks, > Sarah > > -- > Sarah Goslee (she/her) > http://www.numberwright.com-- Sarah Goslee (she/her) http://www.numberwright.com
Hi, I think there are two easy ways to fix this. The first is to use a `switch` to call the intended function, this should not be a problem since there are a small number of print functions in **mixR** ```R print.mixfitEM <- function (x, digits = getOption("digits"), ...) { switch(x$family, gamma = printgamma (x, digits), lnorm = printlnorm (x, digits), normal = printnormal (x, digits), weibull = printweibull(x, digits), stop(gettextf("invalid '%s' value", "x$family", domain = "R"))) invisible(x) } environment(print.mixfitEM) <- getNamespace("mixR") print.mixfitEM <- compiler::cmpfun(print.mixfitEM) ``` This is nice because 'x' is no longer evaluated twice (you could try this yourself with something like `mixR:::print.mixfitEM(writeLines("testing"))`, you'll see the output twice, once for `x$family` and a second for evaluating `match.call()` expression), it follows standard evaluation, and 'x' is returned invisibly at the end, like most other `print` methods. If you really wanted to continue using `eval`, you could instead do something like ```R print.mixfitEM <- function (x, digits = getOption("digits"), ...) { expr <- quote(printfunction(x, digits)) expr[[1L]] <- as.symbol(paste0("print", x$family)) eval(expr) invisible(x) } environment(print.mixfitEM) <- getNamespace("mixR") print.mixfitEM <- compiler::cmpfun(print.mixfitEM) ``` This also solves the same issues, but it's ugly and slower. At least for now, I would copy one of the functions above into the site-wide startup profile file or your user profile, along with ```R utils::assignInNamespace("print.mixfitEM", print.mixfitEM, "mixR") ``` This does have the unfortunate side effect of loading **mixR** every time an R session is launched, but you could also put it inside another function like: ```R fix.mixR.print.mixfitEM <- function () { print.mixfitEM <- function(x, digits = getOption("digits"), ...) { switch(x$family, gamma = printgamma (x, digits), lnorm = printlnorm (x, digits), normal = printnormal (x, digits), weibull = printweibull(x, digits), stop(gettextf("invalid '%s' value", "x$family", domain = "R"))) invisible(x) } environment(print.mixfitEM) <- getNamespace("mixR") print.mixfitEM <- compiler::cmpfun(print.mixfitEM) utils::assignInNamespace("print.mixfitEM", print.mixfitEM, "mixR") } ``` which you would then call in your scripts before using **mixR**. I hope this helps! On Thu, May 25, 2023 at 10:19?AM Sarah Goslee <sarah.goslee at gmail.com> wrote:> Hi, > > I ran into a problem with S3 method dispatch and scoping while trying > to use functions from the mixR package within my own functions. I know > enough to find the problem (I think!), but not enough to fix it > myself. The problem isn't really a package-specific problem, so I'm > starting here, and will file an issue with the maintainer once I have > a solution. > > Detailed explanation below, but briefly, the S3 methods in this > package use match.call() and then eval() to select the correct > internal method. This works fine from the command line, but if the > method is called from within another function, the use of > environment() within eval() means that the objects passed to the > wrapper function are no longer visible within the eval() call. > > I have a two-part question: > A. How do I get around this right now? > B. What would the correct approach be for the package authors? > > library(mixR) > > # first example from ?mixfit > ## fitting the normal mixture models > set.seed(103) > x <- rmixnormal(200, c(0.3, 0.7), c(2, 5), c(1, 1)) > data <- bin(x, seq(-1, 8, 0.25)) > fit1 <- mixfit(x, ncomp = 2) # raw data > rm(x, data) > ### > > # simple function > funworks <- function(x) { > print(x) > } > > ### > > # almost identical simple function > funfails <- function(thisx) { > print(thisx) > } > > ### > > funworks(fit1) > funfails(fit1) > > ####### > > The explanation as I understand it... > > print called on this object gets passed to print.mixfitEM(), which is: > > > function (x, digits = getOption("digits"), ...) > { > family <- x$family > mc <- match.call() > mc$digits <- digits > fun.name <- paste0("print", family) > mc[[1]] <- as.name(fun.name) > eval(mc, environment()) > } > > > Working through the calls, when eval() is called from within funfails(), > mc is > printnormal(x = thisx, digits = 7) > and the calling environment does not contain thisx. > > In funworks(), it's > printnormal(x = x, digits = 7) > > and x is found. > > So, I can get around the problem by naming my argument x, as in > funworks(), but that's unsatisfying. Is there something else I can do > to get my functions to work? > > And what's the correct way to do what print.mixfitEM() is doing, so > that it works regardless? I poked around for a while, but didn't find > a clear (to me!) answer. > > Thanks, > Sarah > > -- > Sarah Goslee (she/her) > http://www.numberwright.com > > ______________________________________________ > R-help at r-project.org mailing list -- To UNSUBSCRIBE and more, see > 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. >[[alternative HTML version deleted]]