[R] environments: functions within functions
Iris Simmons
|kw@|mmo @end|ng |rom gm@||@com
Fri May 26 02:20:04 CEST 2023
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 using 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 using 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]]
More information about the R-help
mailing list