[R] Function that works within a package and not when copied in global environment. Why?

William Dunlap wdunlap at tibco.com
Thu Feb 2 18:32:21 CET 2017


When searching for the object referred to by a name, R looks first in
the current environment, then in the environment's parent environment,
then in that environment's parent environment, etc.  It stops looking
either when the name is found or when it hits .EmptyEnv, the ultimate
ancestor of all environments.

When a function,f,  is being evaluated, the current environment is a
child of environment(f), which is typically the environment in which
the function was created.  When a function is in a package, the
function's environment is generally the package's namespace. When a
function is made on the command line, its namespace is .GlobalEnv.
.GlobalEnv is not a descendant of any package namespace so when the
function is evaluated it will not look in any package namespace when
looking up names.

You can change the environment of a function with
   environment(f) <- someEnvironment
as in
    environment(revisedLmFunc) <- environment(lm)
or
    environment(revisedLmFunc) <- getNamespace(lm)
I do this when debugging functions in environments, but I don't
recommend it for general use (e.g., for code other people will be
using).

Here is some code that displays the ancestral environments of an
environment to help you look at various situations.

myFormatEnvironment <- function(envir) {
    if (is.null(n <- attr(envir, "name"))) {
        n <- format(envir)
    }
    n
}
ancestralEnvironments <- function (envir) {
    if (identical(envir, emptyenv())) {
        list(envir)
    }
    else {
        c(list(envir), ancestralEnvironments(parent.env(envir)))
    }
}

Here are some examples showing the ancestral environments of a (a)
function in a pacakge, (b) a function in .GlobalEnv, and (c) a
function created by a function in a package.

> vapply(ancestralEnvironments(environment(stats::lm)), myFormatEnvironment, "")
 [1] "<environment: namespace:stats>" "imports:stats"
 [3] "<environment: namespace:base>"  "<environment: R_GlobalEnv>"
 [5] "package:stats"                  "package:graphics"
 [7] "package:grDevices"              "package:utils"
 [9] "package:datasets"               "package:methods"
[11] "Autoloads"                      "<environment: base>"
[13] "<environment: R_EmptyEnv>"
> myFunc <- function(x) x
> vapply(ancestralEnvironments(environment(myFunc)), myFormatEnvironment, "")
 [1] "<environment: R_GlobalEnv>" "package:stats"
 [3] "package:graphics"           "package:grDevices"
 [5] "package:utils"              "package:datasets"
 [7] "package:methods"            "Autoloads"
 [9] "<environment: base>"        "<environment: R_EmptyEnv>"
> vapply(ancestralEnvironments(environment(approxfun(1:3,log(1:3)))), myFormatEnvironment, "")
 [1] "<environment: 0x0000000015d33f28>"
 [2] "<environment: namespace:stats>"
 [3] "imports:stats"
 [4] "<environment: namespace:base>"
 [5] "<environment: R_GlobalEnv>"
 [6] "package:stats"
 [7] "package:graphics"
 [8] "package:grDevices"
 [9] "package:utils"
[10] "package:datasets"
[11] "package:methods"
[12] "Autoloads"
[13] "<environment: base>"
[14] "<environment: R_EmptyEnv>"
Bill Dunlap
TIBCO Software
wdunlap tibco.com


On Thu, Feb 2, 2017 at 8:34 AM, Marc Girondot via R-help
<r-help at r-project.org> wrote:
> Thanks Bert for the explanation about identical.
>
> For the vectorize.args, note that vectorize.args is not a function but an
> variable that is unknown in the namespace nlWaldTest.
>
>> nlWaldTest::vectorize.args
> Erreur : 'vectorize.args' n'est pas un objet exporté depuis
> 'namespace:nlWaldTest'
>
>
> Furthermore, if the function is created from a copy of the original one:
>
> smartsub <- getFromNamespace(".smartsub", ns="nlWaldTest")
>
> or if it is created manually: by copy-paste of the code:
>
> smartsub2 <- function (pat, repl, x)
>  {
>      args <- lapply(as.list(match.call())[-1L], eval, parent.frame())
>      names <- if (is.null(names(args)))
>          character(length(args))
>      else names(args)
>      dovec <- names %in% vectorize.args
>      do.call("mapply", c(FUN = FUN, args[dovec], MoreArgs =
> list(args[!dovec]),
>                          SIMPLIFY = SIMPLIFY, USE.NAMES = USE.NAMES))
>  }
>
> Both are defined in the global env, but the first one works and not the
> second one.
>
> I am surprised and don't understand how it is possible.
>
> Sincerely
>
> Marc Girondot
>
>> 2. You need to review how namespaces work. From the "Writing R
>> extensions" manual:
>>
>> "The namespace controls the search strategy for variables used by
>> **functions in the package**. If not found locally, R searches the
>> package namespace first, then the imports, then the base namespace and
>> then the normal search path."
>>
>> So if vectorize.args() is among the package functions, it will be
>> found by package functions but not by those you write unless
>> specifically qualified by :: or ::: depending on whether it is
>> exported.
>>
>> Cheers,
>> Bert
>>
>>
>>
>> Bert Gunter
>>
>> "The trouble with having an open mind is that people keep coming along
>> and sticking things into it."
>> -- Opus (aka Berkeley Breathed in his "Bloom County" comic strip )
>>
>>
>> On Thu, Feb 2, 2017 at 6:30 AM, Marc Girondot via R-help
>> <r-help at r-project.org> wrote:
>>>
>>> Dear experts,
>>>
>>> In the package nlWaldTest, there is an hidden function : .smartsub
>>>
>>> I can use it, for example:
>>>
>>>> getFromNamespace(".smartsub", ns="nlWaldTest")(pat="x", repl="b" ,
>>>
>>> x="essai(b[1], b[2], x[1])")
>>> [1] "essai(b[1], b[2], b[1])"
>>>
>>> Now I try to create this function in my global environment:
>>> smartsub <- getFromNamespace(".smartsub", ns="nlWaldTest")
>>>
>>> It works also:
>>>>
>>>> smartsub(pat="x", repl="b" , x="essai(b[1], b[2], x[1])")
>>>
>>> [1] "essai(b[1], b[2], b[1])"
>>>
>>> But if I create the function manually:
>>>>
>>>> smartsub2 <- function (pat, repl, x)
>>>
>>>   {
>>>       args <- lapply(as.list(match.call())[-1L], eval, parent.frame())
>>>       names <- if (is.null(names(args)))
>>>           character(length(args))
>>>       else names(args)
>>>       dovec <- names %in% vectorize.args
>>>       do.call("mapply", c(FUN = FUN, args[dovec], MoreArgs =
>>> list(args[!dovec]),
>>>                           SIMPLIFY = SIMPLIFY, USE.NAMES = USE.NAMES))
>>>   }
>>>>
>>>> smartsub2(pat="x", repl="b" , x="essai(b[1], b[2], x[1])")
>>>
>>> Error in names %in% vectorize.args : objet 'vectorize.args' introuvable
>>>
>>> It fails because vectorize.args is unknown
>>>
>>> Indeed smartsub2 is different from smartsub.
>>>>
>>>> identical(smartsub, smartsub2)
>>>
>>> [1] FALSE
>>>
>>> 1/ Why are they different? They are just a copy of each other.
>>>
>>> 2/ Second question, vectorize.args is indeed not defined before to be
>>> used
>>> in the function. Why no error is produced in original function?
>>>
>>> Thanks a lot
>>>
>>> Marc
>>>
>>>
>>> --
>>>
>>> __________________________________________________________
>>> Marc Girondot, Pr
>>>
>>> Laboratoire Ecologie, Systématique et Evolution
>>> Equipe de Conservation des Populations et des Communautés
>>> CNRS, AgroParisTech et Université Paris-Sud 11 , UMR 8079
>>> Bâtiment 362
>>> 91405 Orsay Cedex, France
>>>
>>> Tel:  33 1 (0)1.69.15.72.30   Fax: 33 1 (0)1.69.15.73.53
>>> e-mail: marc.girondot at u-psud.fr
>>> Web: http://www.ese.u-psud.fr/epc/conservation/Marc.html
>>> Skype: girondot
>>>
>>> ______________________________________________
>>> 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.
>
>
> ______________________________________________
> 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.



More information about the R-help mailing list