This document presents the implementation of name space support provided in R 1.7. Some minor changes in the current development verison have also been incorporated. A pdf version of this document is also available.
Name spaces provide a means for packages to control the way global
variables in their function definitions are resolved and to control
which local definitions are to be available outside the package.
Packages with name spaces export variables with certain values. A
package with a name space can import variables exported by other
packages with name spaces. Functions defined within a name space are
defined in an environment consisting of the internal name space frame,
which is enclosed in a (set of) imported frames. [The
implementation fuses all explicit imports into a single frame. This
means that a non-function in a more recent import will mask a function
in an earlier import. I think I consider this a feature, not a bug.]
All name spaces import the base
name space. The base
name
space is a special name space that is enclosed by the global
environment. For example, a function defined in a name space bar
that imports foo
will be defined in an environment that looks like
this:
--------------- | bar internals | --------------- | foo exports | --------------- | base exports | --------------- | .GlobalEnv | --------------- | package:pkg1 | --------------- ... --------------- | package:base | ---------------The variables in
base
appear twice: once as a statically
determined import (static in the sense that its position in the
environment is fixed) and once at the end of the dynamic global
environment (where the search index of base varies as packages are
attached and detached). [In his comments on the first draft of
this proposal, John Chambers suggested that it might be cleaner to not
include .GlobalEnv
, so that all globals must be found in explicit
imports or in base. I agree with this in principle. Unfortunately
the need to accommodate UseMethod
dispatch means, I think, that
this is not possible for now. Some additional discussion of the
interactions of name spaces with UseMethod
dispatch is given in
Section [->].]
Name spaces are sealed once they are created. Sealing means that imports and exports cannot be changed and that internal variable bindings cannot be changed. Sealing is important if a compiler is to be able to clearly identify what a global variable refers to in order, for example, to handle a reference to certain functions in base in a special way. Sealing also allows a simpler implementation strategy for this name space mechanism.
There are currently two different ways to create a package with a name
space. The primary approach is to use a NAMESPACE
file with
directives describing the name space. An alternative is based on
including name space directives in the package code. Eventually we
will settle on one of these approaches and eliminate the other. But
for the moment both are supported.
NAMESPACE
file in its root
directory. This file specifies the imports and exports of the name
space. These examples should make the syntax used in NAMESPACE
files clear.
Suppose we want to create a package foo
with internal definitions
for a variable x
and a function f
. The code file is
<foo/R/foo.R>= [D->] x <- 1 f <- function(y) c(x,y)
If we want to export only f
, then the NAMESPACE
file is just
<foo/NAMESPACE>= [D->] export(f)
A second package bar
has a code file that looks like
<bar/R/bar.R>= c <- function(...) sum(...) g <- function(y) f(c(y, 7)) h <- function(y) y+9
The definition of c
masks the function in base. f
is not
defined in bar
but is imported from foo
. Only g
and h
are exported. Thus the NAMESPACE
file looks like
<bar/NAMESPACE>= import(foo) export(g, h)
Finally, a third package baz
has an empty code file baz.R
<baz/R/baz.R>= # empty file
The purpose of baz
is to import some of the exports of foo
and
bar
and re-export them, using renaming in one case: bar
's
export g
is imported under the internal name hh
, and the
internal variable hh
is exported under the name
gg
. [Renaming seems like a useful option, but it may turn
out to create to many complications and need to be dropped.]
<baz/NAMESPACE>= import(foo) importFrom(bar, hh = g) export(f, gg = hh)
A user accesses a package with a name space like any other package by
calling library
to load it and attach it to the search path. This
recursively loads any packages required to satisfy import
specifications, but these implicitly loaded packages will not be
attached to the search path. So for the baz
package,
<R session>= [D->] > library(baz) > search() [1] ".GlobalEnv" "package:baz" "package:methods" "package:ctest" [5] "package:mva" "package:modreg" "package:nls" "package:ts" [9] "Autoloads" "package:base" > loadedNamespaces() [1] "bar" "base" "baz" "foo"
Loading baz
with library
causes it to be loaded and its
exports attached. In addition, foo
and bar
are loaded but not
attached. Only the exports of baz
are available in the attached
frame. Their printed representations show the name spaces in which
they were defined.
<R session>+= [<-D->] > ls("package:baz") [1] "f" "gg" > f function (y) c(x, y) <environment: namespace:foo> > gg function (y) f(c(y, 7)) <environment: namespace:bar>
Calling gg
produces a result consistent with the definitions of
c
in the two settings: in bar
the function c
is defined to
be equivalent to sum
, but in foo
the variable c
refers to
the standard function c
in base.
<R session>+= [<-D->] > gg(6) [1] 1 13
A name space file can also register a method for S3 method dispatch.
If foo
includes the definition
<foo/R/foo.R>+= [<-D] print.foo <- function(x, ...) cat("<a foo>\n")
and the NAMESPACE
file includes
<foo/NAMESPACE>+= [<-D->] S3method(print,foo)
then the print.foo
function is registered as the print
method
for class foo
. It is not necessary to export the method. The
need for this is discussed in
Section [->].
Finally, a shared library can be registered for loading by adding a directive of the form
<foo/NAMESPACE>+= [<-D] useDynLib(foo)
to the NAMESPACE
file. The name space loading mechanism will load
this library with library.dynam
when the name space is loaded.
This eliminates the need for most load hook functions.
Loading and attaching are separate processes for packages with name
spaces: if package foo
is loaded to satisfy the import request
from bar
then foo
is not attached to the global search path.
As a result, instead of the single hook function .First.lib
two
hook functions are needed, .onLoad
and .onAttach
. Most
packages will need at most .onLoad
. These variables should not be
exported.
foo
is to
add the line
Namespace: footo the
DESCRIPTION
file. The name specified must match the
package name. [R CMD check
will check for this in R 1.8.]
Then calls to the functions .Import
, .ImportFrom
, .Export
,
and .S3method
can be placed directly in the package
code. [Perhaps a .UseDynLib
function should also be
provided.] The code files for three packages foo1
, bar1
, and
baz1
analogous to the three example packages of the previous
section would be
<foo1/R/foo1.R>= x <- 1 f <- function(y) c(x,y) print.foo <- function(x, ...) cat("<a foo>\n") .S3method(print,foo) .Export(f) .onLoad <- function(lib, pkg) library.dynam("foo", pkg, lib)
<bar1/R/bar1.R>= .Import(foo1) c <- function(...) sum(...) g <- function(y) f(c(y, 7)) h <- function(y) y+9 .Export(g, h)
<baz1/R/baz1.R>= .Import(foo1) .ImportFrom(bar1, hh = g) .Export(f, gg = hh)
This approach may allow us to use .Import
in base, thus allowing
some functionality to be moved out of base into packages and allowing
those packages to use private functions in their
definitions. [For implementation reasons all variabls in base
are exported.]
One issue that has not been resolved is how to track documentation of functions that have been imported and then re-exported.
NAMESPACE
file has
to be added to the package. For a package that does not use other
packages the NAMESPACE
file will only contain export directives.
The directive can be constructed using ls
. For example, for
ctest
a reasonable directive can be built with
<R session>+= [<-D->] > as.call(c(as.name("export"), ls("package:ctest"))) export("ansari.test", "ansari.test.default", "ansari.test.formula", "bartlett.test", "bartlett.test.default", "bartlett.test.formula", ... "wilcox.test.default", "wilcox.test.formula")
This leaves out only one of the internal variables: .First.lib
,
which should be replaced by .onLoad
or a useDynLib
directive.
To support adding name spaces to existing packages with many public
variables it is useful to have an export directive that allows
variables to be exported as patterns. The exportPattern
directive can be used as
exportPattern("^trellis\\.")for example. The arguments are patterns that are processed by calling
ls
on the internal name space environment with all=TRUE
; this
means imports are not picked up by the pattern. This is just one of
many possible approaches. Using this approach, a package that wants
to export all variables except those beginning with a dot could use
<NAMESPACE file to export varialbles not beginning with a period>= exportPattern("^[^\\.]")
as its NAMESPACE
file, together with a useDynLib
directive or
a definition for .onLoad
.
A package that needs other packages that have name spaces should
remove calls to require
from the sources and replace them with
import
directives in the NAMESPACE
file.
It may also be necessary to make some changes to the content of a
.First.lib
function, in addition to renaming it as .onLoad
,
when converting to using a name space. Many existing .First.lib
functions do something like
pkgEnv <- pos.to.env(match(paste("package:",pkgname,sep=""), search())) assign("foo", bar, envir = pkgEnv)to obtain the package environment. This can be replaced by
pkgEnv <- topenv()The function
topenv
returns the environment to be used for top
level definitions---either the first name space internal environment
found searching from the environment where topenv
is called, or
.GlobalEnv
.
One other issue that may need to be addressed is the registration of
methods for UseMethod
dispatch. Some tools for locating these
would be useful.
For now, packages that use name spaces must not be installed with
--save
. Section [->] discusses this issue,
which should not be too hard to resolve.
UseMethod
dispatch---the name-pasting that goes on in
dispatch makes this impossible. So class names are globally scoped.
The issue is making sure that methods are reasonably scoped, in
particular that methods that are defined can be found.
When a generic function uses UseMethod
to dispatch to an
appropriate method the environment searched for methods is the
environment in which the generic is called. This means that methods
are found if they are defined in the local environment of the call or
in the global search path. Without name spaces, essentially all
methods are going to be accessible from .GlobalEnv
(i.e. they are
in base, in loaded packages, or in the top level .GlobalEnv
frame
itself).
Suppose a package/name space p1
defines and exports a print method
print.C
for a class C
. Suppose a package/name space p2
imports p1
and exports a function f
that returns an object of
class C
and the user executes
library(p2) print(f())The
library
call loads and attaches the package/name space p2
.
It also loads p1
as a dependency, but p1
is not
attached. Hence the print.C
method of p1
is not visible at
the call site of print
. The only way around this I can see is an
explicit method registration mechanism.
A very simple method registration mechanism has been developed to
overcome this problem. After searching the call environment, the top
frame of the definition environment for the generic is examined for
the existence of a variable containing a methods table. If this
exists and is an environment, then it is searched for a method
definition. For internal functions the defining environment is taken
to be .BaseNamespaceEnv
. For example,
<R session>+= [<-D] > .S3method(print, C, function(x) cat("<C>\n")) > .S3method(as.character, C, function(x) "<--C-->") > x<-structure(list(1), class="C") > x <C> > as.character(x) [1] "<--C-->"
This approach associates methods with their generics and insures that methods are visible whenever their generics are. The reason for searching the calling environment first is to minimize changes from the current behavior.
This registration mechanism is only intended to be used within a name
space, and packages with name spaces currently do not work with
--save
. Figuring out how to support registration and saving is I
think going to be very similar to figuring out how to integrate
methods
and name spaces. Some discussion is given in Section
[->].
saveload
code for R 1.4 includes support for name spaces:
If an internal name space environment is to be saved, then instead of
saving the entire environment a marker is saved along with a character
vector describing the name space. For now that character vector
contains just the name and the version, and the version is currently
ignored, but it could eventually be expanded. When a work space with
such a reference is loaded into an R process, then the character
vector is passed to getNamespace
, which calls loadNamespace
to
load the name space and then return the loaded name space's internal
environment.
One thing that has not been addressed yet is how to handle
installation with --save
. I don't think there are conceptual
difficulties, it just has to be done. For now, R 1.7 signals an error
if --save
is used and the package has a NAMESPACE
file.
namespace(foo) { ... }
Other languages, such as Ada, Modula 3, mzScheme, and ML separate out the declaration of modules from the implementation source code. Whether they go so far as to require that source and module declarations be in separate files varies, but some do.
Both approaches have merits. Interweaving name space declarations
with code makes it easier to see how a particular definition fits into
the public interface of the module. Declaring a Java method as
public
, for example, makes clear that it is part of the public
interface. On the other hand, separating out the module structure
makes it easier to see the public interface at a glance and to think
about plugging in different implementations of the same interface.
The main reasons I chose the approach of using a NAMESPACE
file
are:
Having a name space that spans several packages could be useful to allow bits of a larger implementation to easily be replaced by new implementations. This can be achieved with the existing mechanism by organizing code into several implementation packages and then defining one interface package that imports the implementations and re-exports them.
One scenario where it might be useful for a single package to provide two name spaces is when the package can be used directly by end users or as a building block for extension by programmers. One set of features could then be exported for the end user and a different set for extension purposes.
A perhaps related issue is whether we should allow nested name spaces or packages in some form.
Should there be a formal syntax for accessing internal variables?
Exported variables can be accessed with foo::f
. Internal variable
can be accessed with something like
get("x", env = getNamespace("foo"))or, using the convenience function
getFromNamespace
,
getFromNamespace("x", "foo")but should it also be possible to do some sort of special syntax access the internal value of
x
in foo
? In the absence of
renaming, foo::x
could be made to work; whether it
should is not clear.
base
. However, this determination will have
to be made on the basis of the name space structure in place at
compile time. If the name space structure at load time is different,
in particular if the name space structure at load time shadows certain
base
variables that were not shadowed at compile time, then
assumptions made at compile time may be invalid.
To deal with this we would need to keep enough information about name spaces in a saved work space to be able to determine whether assumptions the compiler makes remain valid. What happens if they do not is another issue---the compiled version could be discarded or an error could be signaled. One option would be for the sealing process to do a semantic analysis that determines exactly which variables the name space uses from each imported name space and to save this information as a signature of the imports. At load time the name space structure could then be checked for consistency with this signature. Version information could also help.
methods
Packagemethods
to know how complicated this is going to be.
The defining functions in methods
(setClass
, setMethod
,
and friends) take a where
argument. The current default is
.GlobalEnv
. With name spaces the default will need to be the top
definition environment for the environment of the call,
topenv(parent.frame())
.
Generic functions are stored in ordinary variables, so in principle
nothing additional should be needed. Classes are not directly stored
as ordinary variables. They seem to use a name mangling mechanism,
with setClass("track",...)
producing a variable ".__C__track"
containing some form of class object. To support classes in name
spaces we would just need a mechanism of exporting and importing that
is aware of this name mangling, say directives of the form
exportClass(track) exportClass(trace = track) importClassFrom(foo, trace) importClassFrom(foo, mytrack = trace)
Within a single run of R little more should be needed.
A call to setMethod
of the form
setMethod("plotData", signature(x="track", y="missing"),...)will resolve
plotData
as a reference to the function by that name
visible at the call site by name space rules, and track
will refer
to the class by that name visible at the call site by name space
rules. Where things get tricky is figuring out how to deal with saved
work spaces. If user code executes a setMethod
and then
save.image
, then some mechanism is needed to make sure the method
is installed in the right place when the saved work space is loaded.
The mechanism needed is clear: some form of hook on the load process.
A special hook for methods
is one approach, but as something
similar is needed for registered UseMethod
methods, which might
prove useful, perhaps a general mechanism for triggering actions on
load is worth considering. The tricky issue is finding the right
place.
There are two distinct scenarios. One is saved work spaces created by
--save
installations of packages. Here the original setMethod
is known to have occurred in a particular name space context with a
known set of classes and generics visible by name space rules. These
same classes and generics should be visible at load time, so just
saving the raw setMethod
call and executing it at load time should
be pretty close to sufficient. Things are different if the
setMethod
is evaluated at top level. Here the visible classes and
generics are determined by the dynamic search path consisting of the
packages that happen to be loaded. If a top level call
setMethod("gen", signature(x = "foo"), ...)is evaluated and at evaluation time
gen
is found in package A
and foo
in package B
, then it is not entirely clear what
should happen if the work space is saved after this definition and
then restored. Should the method be installed against whatever
context happens to be found when the restore occurs? Or should an
attempt be made to get the "right" packages loaded?
If the packages have name spaces a reasonable case can be made that
the right packages should be loaded if possible. This can be done by
saving the method definition in a way that records the source name
space of the generic as well as the source name space of the class
that were used when the original setMethod
call was evaluated.
With this information, the appropriate name spaces could be loaded
with loadNamespace
(i.e. loaded but not attached). In a sense
this requires that objects carry what might be called fully qualified
class identifiers.
A similar issue arises if class foo
is defined in a name space
A
and an object of class foo
is created at top level and
saved. Should the class information attached to the object allow the
name space A
to be loaded when the object is loaded? The new
save/load code should allow us to do this if we decide it is the right
way to go. Loading A
is likely to provide many important methods,
such as print
methods. But methods for foo
defined in a
different name space B
cannot easily loaded automatically. One
approach that would cover this case is to maintain a library-level
directory of all methods.
pi
or inlining a call to log
.
We could consider a name space implementation in which bindings are
imported and exported rather than values. If the bindings are
read-only then you get the current behavior. If they are writable,
then assigning to an imported binding (the <<-
kind of assignment)
should change the value of the corresponding variable in the exporting
name space and in all other importing name spaces. Importing bindings
requires a more complex implementation, in particular some fairly
heavy changes in envir.c
, but it is in principle possible.
Whether having writable exports is desirable or not is debatable.
Exporting values rather than bindings and sealing all bindings leads
to a conceptually simpler model and eliminates the possibility of
certain kinds of mischief. If we choose to go that route one option
that might minimize changes needed in envir.c
would be to use
special promises.
library
it is convenient to be able to use
a short name like nls
to specify the library. Any version issues
can be resolved by specifying the lib.loc
argument. With name
spaces there is a need for implicit loading of imports. Manual
intervention is at the very least inconvenient if not impossible. It
would therefore be nice to be able to specify an import directive that
makes sure the right package and perhaps the right version within a
package is loaded.
One option might be to allow packages to register full names that make
a conflict less likely. The NAMESPACE
file for nls
for
example might contain a directive like
namespace.fullname(r-project.org/r-core/nls)A package depending on
nls
might then import it as
import(nls=r-project.org/r-core/nls)or something along those lines. This would require some form of support in how packages are registered at installation and how package search works.
A hierarchical package structure might be another way to address these issues.
Packages already have a version mechanism; perhaps import directives should allow a minimal version to be specified in some form.
core
, models
, etc. A given site could then perhaps define
its own base as
<site base name space>= importAndExport(core) importAndExport(models) importAndExport(ctest)
or something along these lines. If we did this then the default name
space included in all name spaces should probably be core
, not
base
.
One advantage of this approach would be to make base
easier
maintain by allowing some large chunks of code that is repeated in
several places to be split out into utility functions that can be
re-used internally but need not be exported.
Several things may still need to be made aware of name spaces. The
utilities in the tools
package seem mostly compatible with name
spaes at this point but may need another look once integration of name
spaces and S4 dispatch begins.
The fix
function may be somewhat less useful now since with name
spaces you cannot mask functions in packages using name spaces (or
base if defined in a name space) with definitions in .GlobalEnv
.
As an interim measure, Brian Ripley has developed a fixInNamespace
function that may be useful.
One option to consider to avoid having some packages with and some without name spaces is to implicitly define a name space for a package when it is loaded. On the other hand, pure data packages are probably better served by the current approach.
Many more advanced module systems, such as the Scheme48 and MzScheme ones and the ML one allow incomplete or parameterized modules. This sort of thing seems to be used in two different ways. In strongly typed languages like ML the parameters are often types and allow for generic modules. In languages like MzScheme with single inheritance object systems the parameters would often be classes and the parameterized modules would provide a way to specify mixin functionality that can then easily be added to any class, thus providing similar benefits to multiple inheritance. At this point I'm not convinced the benefits for R would outweigh the complexity, but this is the time to think through the issues.
The implementation consists of R code in namespace.R
and C
code in the base distribution.
<namespace.R>= <public name space functions> <internal name space functions>
getNamespace
.
<public name space functions>= (<-U) [D->] getNamespace <- function(name) { ns <- .Internal(getRegisteredNamespace(as.name(name))) if (! is.null(ns)) ns else loadNamespace(name) }
DefinesgetNamespace
(links are to index).
A listing of the registered name spaces is returned by
loadedNamespaces
.
<public name space functions>+= (<-U) [<-D->] loadedNamespaces <- function() ls(env = .Internal(getNamespaceRegistry()), all = TRUE)
DefinesloadedNamespaces
(links are to index).
--------------- | internals | --------------- | imports | --------------- | base exports | --------------- | .GlobalEnv | ---------------The structure is intended to be private; all access to name space internals is through a set of accessor functions.
The .__NAMESPACE__.
variable contains an environment to store
onformation about the name space. The spec
field is used by
internal C code; if its name is changed here then the C code must be
changed as well. The spec
is a character vector. Its first
element is the name space name. The second element is the name space
version; the version is ignored for now. Additional elements may be
added later. The internal serialization code writes out the entire
spec
vector as an identifier for the name space to load when
unserializing. The internal unserialize code passes that character
vector to getNamespace
, which currently ignores the version
component.
makeNamespace
. For
bootstrapping reasons the spec
field needs to be installed using
assign
, not setNamespaceInfo
.
<makeNamespace
definition>= (U->)
makeNamespace <- function(name, version = NULL, lib = NULL) {
impenv <- new.env(parent = .BaseNamespaceEnv, hash = TRUE)
env <- new.env(parent = impenv, hash = TRUE)
name <- as.character(as.name(name))
version <- as.character(version)
info <- new.env(hash = TRUE, parent = NULL)
assign(".__NAMESPACE__.", info, env = env)
assign("spec", c(name=name,version=version), env = info)
setNamespaceInfo(env, "exports", new.env(hash = TRUE, parent = NULL))
setNamespaceInfo(env, "imports", list("base"=TRUE))
setNamespaceInfo(env, "path", file.path(lib, name))
setNamespaceInfo(env, "dynlibs", NULL)
setNamespaceInfo(env, "S3methods", NULL)
.Internal(registerNamespace(name, env))
env
}
DefinesmakeNamespace
(links are to index).
Predicates for recognizing name space objects and identifying the base name space are provided by
<internal name space functions>= (<-U) [D->] isNamespace <- function(ns) .Internal(isNamespaceEnv(ns)) isBaseNamespace <- function(ns) identical(ns, .BaseNamespaceEnv)
DefinesisNamespace
(links are to index).
The functions getNamespaceInfo
and setNamespaceInfo
are used
for accessing and assigning values in the auxiliary information
environment.
<internal name space functions>+= (<-U) [<-D->] getNamespaceInfo <- function(ns, which) { ns <- asNamespace(ns, base.OK = FALSE) info <- get(".__NAMESPACE__.", env = ns, inherits = FALSE) get(which, env = info, inherits = FALSE) } setNamespaceInfo <- function(ns, which, val) { ns <- asNamespace(ns, base.OK = FALSE) info <- get(".__NAMESPACE__.", env = ns, inherits = FALSE) assign(which, val, env = info) }
DefinesgetNamespaceInfo
,setNamespaceInfo
(links are to index).
<public name space functions>+= (<-U) [<-D->] getNamespaceName <- function(ns) { ns <- asNamespace(ns) if (isBaseNamespace(ns)) "base" else getNamespaceInfo(ns, "spec")["name"] } getNamespaceVersion <- function(ns) { ns <- asNamespace(ns) if (isBaseNamespace(ns)) c(version = paste(R.version$major, R.version$minor, sep=".")) else getNamespaceInfo(ns, "spec")["version"] }
DefinesgetNamespaceName
,getNamespaceVersion
(links are to index).
<getInternalExportName
definition>= (U-> U->)
getInternalExportName <- function(name, ns) {
exports <- getNamespaceInfo(ns, "exports")
if (! exists(name, env = exports, inherits = FALSE))
stop(paste(name, "is not an exported object"))
get(name, env = exports, inherits = FALSE)
}
DefinesgetInternalExportName
(links are to index).
The currently registered exports are returned by getNamespaceExports
.
<public name space functions>+= (<-U) [<-D->] getNamespaceExports <- function(ns) { ns <- asNamespace(ns) if (isBaseNamespace(ns)) ls(NULL, all = TRUE) else ls(getNamespaceInfo(ns, "exports"), all = TRUE) }
DefinesgetNamespaceExports
(links are to index).
addExports
registers new export specifications.
<addExports
definition>= (U->)
addExports <- function(ns, new) {
exports <- getNamespaceInfo(ns, "exports")
expnames <- names(new)
intnames <- new
for (i in seq(along = new)) {
if (exists(expnames[i], env = exports, inherits = FALSE))
warning("replacing previous export:", expnames[i])
assign(expnames[i], intnames[i], env = exports)
}
}
DefinesaddExports
(links are to index).
<public name space functions>+= (<-U) [<-D->] getNamespaceImports <- function(ns) { ns <- asNamespace(ns) if (isBaseNamespace(ns)) NULL else getNamespaceInfo(ns, "imports") }
DefinesgetNamespaceImports
(links are to index).
addImports
registers new import specifications.
<addImports
definition>= (U->)
addImports <- function(ns, from, what) {
imp <- structure(list(what), names = getNamespaceName(from))
imports <- getNamespaceImports(ns)
setNamespaceInfo(ns, "imports", c(imports, imp))
}
DefinesaddImports
(links are to index).
The function getNamespaceUsers
provides a possible fairly
inefficient function for determining all loaded name spaces that
import a given name space.
<public name space functions>+= (<-U) [<-D->] getNamespaceUsers <- function(ns) { nsname <- getNamespaceName(asNamespace(ns)) users <- character(0) for (n in loadedNamespaces()) { inames <- names(getNamespaceImports(n)) if (match(nsname, inames, 0)) users <- c(n, users) } users }
sealNamespace
function seals a name space by locking its
internal enveronment and its imports frame.
<sealNamespace
definition>= (U->) sealNamespace <- function(ns) { <namespaceIsSealed
definition> ns <- asNamespace(ns, base.OK = FALSE) if (namespaceIsSealed(ns)) stop("already sealed") lockEnvironment(ns, TRUE) lockEnvironment(parent.env(ns), TRUE) }
DefinessealNamespace
(links are to index).
The predicate namespaceIsSealed
just checks whether the internal
environment is locked.
<namespaceIsSealed
definition>= (<-U U-> U->)
namespaceIsSealed <- function(ns)
environmentIsLocked(ns)
DefinesnamespaceIsSealed
(links are to index).
<addNamespaceS3method
definition>= (U->)
addNamespaceS3method <- function(ns, generic, class, method) {
regs <- getNamespaceInfo(ns, "S3methods")
regs <- c(regs, list(list(generic, class, method)))
setNamespaceInfo(ns, "S3methods", regs)
}
DefinesaddNamespaceS3method
(links are to index).
<addNamespaceDynLibs
definition>= (U->)
addNamespaceDynLibs <- function(ns, newlibs) {
dynlibs <- getNamespaceInfo(ns, "dynlibs")
setNamespaceInfo(ns, "dynlibs", c(dynlibs, newlibs))
}
DefinesaddNamespaceDynlibs
(links are to index).
asNamespace
is used to allow most higher level
functions to be called with either a name space object or a character
string naming a registered name space.
<internal name space functions>+= (<-U) [<-D->] asNamespace <- function(ns, base.OK = TRUE) { if (is.character(ns) || is.name(ns)) ns <- getNamespace(ns) if (! isNamespace(ns)) stop("not a name space") else if (! base.OK && isBaseNamespace(ns)) stop("operation not allowed on base name space") else ns }
DefinesasNamespace
(links are to index).
namespaceImport
function accepts any number of name spaces as
arguments but defers the actual work to namespaceImportFrom
.
<internal name space functions>+= (<-U) [<-D->] namespaceImport <- function(self, ...) { for (ns in list(...)) namespaceImportFrom(self, asNamespace(ns)) }
DefinesnamespaceImport
(links are to index).
The namespaceImportFrom
function imports the values of the
specified variables into the import frame and it records the import
request. The record maintained in the name space could be used to
restore a saved name space. This definition allows importing into
base and into non-namespace environments.
<internal name space functions>+= (<-U) [<-D->] namespaceImportFrom <- function(self, ns, vars) { <addImports
definition> <namespaceIsSealed
definition> <makeImportExportNames
definition> if (is.character(self)) self <- getNamespace(self) ns <- asNamespace(ns) if (missing(vars)) impvars <- getNamespaceExports(ns) else impvars <- vars impvars <- makeImportExportNames(impvars) impnames <- names(impvars) if (any(duplicated(impnames))) { stop("duplicate import names ", paste(impnames[duplicated(impnames)], collapse=", ")) } if (isNamespace(self) && isBaseNamespace(self)) { impenv <- self msg <- "replacing local value with import:" register <- FALSE } else if (isNamespace(self)) { if (namespaceIsSealed(self)) stop("cannot import into a sealed namespace") impenv <- parent.env(self) msg <- "replacing previous import:" register <- TRUE } else if (is.environment(self)) { impenv <- self msg <- "replacing local value with import:" register <- FALSE } else stop("invalid import target") for (n in impnames) if (exists(n, env = impenv, inherits = FALSE)) warning(paste(msg, n)) importIntoEnv(impenv, impnames, ns, impvars) if (register) { if (missing(vars)) addImports(self, ns, TRUE) else addImports(self, ns, impvars) } }
DefinesnamespaceImportFrom
(links are to index).
The function importIntoEnv
is responsible for transferring
bindings from one environment to another. The internal version,
insures that promises are not forced and that active bindings are
transferred properly.
<internal name space functions>+= (<-U) [<-D->]
importIntoEnv <- function(impenv, impnames, expenv, expnames) {
<getInternalExportName
definition>
expnames <- unlist(lapply(expnames, getInternalExportName, expenv))
.Internal(importIntoEnv(impenv, impnames, expenv, expnames))
}
DefinesimportIntoEnv
(links are to index).
The variables to be imported are specified as a character vector. If entries in the vector are named then the values are imported under the specified name. Thus
namespaceImportFrom(bar, foo, y="x")means the value of the variable
x
exported by foo
will be
imported into bar
under the name y
. The function
makeImportExportNames
takes a possibly named character vector and
adds names for all elements. This function is also used to allow
renaming of exports.
<makeImportExportNames
definition>= (<-U U->)
makeImportExportNames <- function(spec) {
old <- as.character(spec)
new <- names(spec)
if (is.null(new)) new <- old
else new[new==""] <- old[new==""]
names(old) <- new
old
}
DefinesmakeImportExportNames
(links are to index).
namespaceExport
function accepts a character vector of names
to export. If the elements of the argument are named, then the names
are used as the export names.
<internal name space functions>+= (<-U) [<-D->] namespaceExport <- function(ns, vars) { <namespaceIsSealed
definition> if (namespaceIsSealed(ns)) stop("cannot add to exports of a sealed namespace") ns <- asNamespace(ns, base.OK = FALSE) if (length(vars) > 0) { <addExports
definition> <makeImportExportNames
definition> new <- makeImportExportNames(vars) if (any(duplicated(new))) stop("duplicate export names ", paste(new[duplicated(new)], collapse=", ")) undef <- new[! sapply(new, exists, env = ns)] if (length(undef) != 0) { undef <- do.call("paste", as.list(c(undef, sep=", "))) stop(paste("undefined exports:", undef)) } addExports(ns, new) } }
DefinesnamespaceExport
(links are to index).
getExportedValue
. The name provided to getExportedValue
is
first translated to its internal name, and then the value of the
internal name is looked up in the internal frame and returned.
<public name space functions>+= (<-U) [<-D->]
getExportedValue <- function(ns, name) {
<getInternalExportName
definition>
ns <- asNamespace(ns)
if (isBaseNamespace(ns)) get(name, env = ns)
else get(getInternalExportName(name, ns), env = ns)
}
DefinesgetExportedValue
(links are to index).
The ::
operator provides a shorthand for getExportedValue
:
<public name space functions>+= (<-U) [<-D->] "::" <- function(pkg,name){ pkg <- as.character(substitute(pkg)) name <- as.character(substitute(name)) getExportedValue(pkg, name) }
Defines::
(links are to index).
attachNamespace
attaches a NULL
list and then
transfers the values of the exported variables of a name space into
the resulting environment. The attached frame is locked. The
.onAttach
hook function, if present in the internal environment,
is run after the variables have been installed. It is not likely that
this mechanism will get much use; the onLoad
hook in
loadNamespace
is much more useful.
<public name space functions>+= (<-U) [<-D->]
attachNamespace <- function(ns, pos = 2) {
<runHook
definition>
ns <- asNamespace(ns, base.OK = FALSE)
nsname <- getNamespaceName(ns)
nspath <- getNamespaceInfo(ns, "path")
attname <- paste("package", nsname, sep=":")
if (attname %in% search())
stop("name space is already attached")
env <- attach(NULL, pos = pos, name = attname)
on.exit(detach(pos = pos))
attr(env, "path") <- nspath
exports <- getNamespaceExports(ns)
importIntoEnv(env, exports, ns, exports)
runHook(".onAttach", ns, dirname(nspath), nsname)
lockEnvironment(env, TRUE)
on.exit()
invisible(env)
}
DefinesattachNamespace
(links are to index).
<runHook
definition>= (<-U U-> U->)
runHook <- function(hookname, env, ...) {
if (exists(hookname, envir = env, inherits = FALSE)) {
fun <- get(hookname, envir = env, inherits = FALSE)
if (! is.null(try({ fun(...); NULL})))
stop(paste(hookname, "failed"))
}
}
DefinesrunHook
(links are to index).
NAMESPACE
file of a package is
encoded in the function namespaceFilePath
. Changing this
convention means just changing this function.
<namespaceFilePath
definition>= (U-> U->)
namespaceFilePath <- function(package, package.lib)
file.path(package.lib, package, "NAMESPACE")
DefinesnamespaceFilePath
(links are to index).
The test of whether a package has a name space is handled by
packageHasNamespace
<internal name space functions>+= (<-U) [<-D->]
packageHasNamespace <- function(package, package.lib) {
<namespaceFilePath
definition>
file.exists(namespaceFilePath(package, package.lib)) ||
! is.na(read.dcf(file.path(package.lib, package, "DESCRIPTION"),
fields="Namespace"))
}
DefinespackageHasNamespace
(links are to index).
The function parseNamespaceFile
is responsible for reading in a
NAMESPACE
file using parse
and collecting the directives into
a structure.
<internal name space functions>+= (<-U) [<-D->] parseNamespaceFile <- function(package, package.lib, mustExist = TRUE) { <namespaceFilePath
definition> <sQuote
definition> nsFile <- namespaceFilePath(package, package.lib) if (file.exists(nsFile)) directives <- parse(nsFile) else if (mustExist) stop(paste("package", sQuote(package), "has no NAMESPACE file")) else directives <- NULL exports <- character(0) exportPatterns <- character(0) imports <- list() dynlibs <- character(0) S3methods <- list() for (e in directives) switch(as.character(e[[1]]), export = { exp <- e[-1] exp <- structure(as.character(exp), names=names(exp)) exports <- c(exports, exp) }, exportPattern = { pat <- as.character(e[-1]) exportPatterns <- c(pat, exportPatterns) }, import = imports <- c(imports,as.list(as.character(e[-1]))), importFrom = { imp <- e[-1] ivars <- imp[-1] inames <- names(ivars) imp <- list(as.character(imp[1]), structure(as.character(ivars), names=inames)) imports <- c(imports, list(imp)) }, useDynLib = { dyl <- e[-1] dynlibs <- c(dynlibs, as.character(dyl)) }, S3method = { spec <- e[-1] if (length(spec) != 2 && length(spec) != 3) stop(paste("bad S3method directive:", deparse(e))) S3methods <- c(S3methods, list(as.character(e[-1]))) }, stop(paste("unknown namespace directive:", deparse(e)))) list(imports=imports, exports=exports, exportPatterns = exportPatterns, dynlibs=dynlibs, S3methods = S3methods) }
DefinesparseNamespaceFile
(links are to index).
<sQuote
definition>= (<-U U->)
sQuote <- function(s) paste("'", s, "'", sep = "")
DefinessQuote
(links are to index).
library
. An on.exit
action is installed to unregister the name space if the load fails; no
attempt is made to roll back any successfully loaded imports in this
case. A crude dynamic variable is used to check for circular
dependencies. Currently cacheMetaData
is called if it looks like
methods have been defined, but this is not likely to work yet and a
warning is issued.
<public name space functions>+= (<-U) [<-D->] loadNamespace <- function (package, lib.loc = NULL, keep.source = getOption("keep.source.pkgs")) { # eventually allow version as second component; ignore for now. package <- as.character(package)[[1]] # check for cycles <dynGet
definition> loading <- dynGet("__NameSpacesLoading__", NULL) if (match(package, loading, 0)) stop("cyclic name space dependencies are not supported") "__NameSpacesLoading__" <- c(package, loading) ns <- .Internal(getRegisteredNamespace(as.name(package))) if (! is.null(ns)) ns else { <runHook
definition> <sQuote
definition> <makeNamespace
definition> <sealNamespace
definition> <addNamespaceDynLibs
definition> # **** FIXME: test for methods hadMethods <- "package:methods" %in% search() # find package and check it has a name space pkgpath <- .find.package(package, lib.loc, quiet = TRUE) if (length(pkgpath) == 0) stop(paste("There is no package called", sQuote(package))) package.lib <- dirname(pkgpath) if (! packageHasNamespace(package, package.lib)) stop(paste("package", sQuote(package), "does not have a name space")) # create namespace; arrange to unregister on error nsInfo <- parseNamespaceFile(package, package.lib, mustExist = FALSE) version = read.dcf(file.path(package.lib, package, "DESCRIPTION"), fields="Version") ns <- makeNamespace(package, version = version, lib = package.lib) on.exit(.Internal(unregisterNamespace(package))) # process imports for (i in nsInfo$imports) { if (is.character(i)) namespaceImport(ns, loadNamespace(i, c(lib.loc, .libPaths()), keep.source)) else namespaceImportFrom(ns, loadNamespace(i[[1]], c(lib.loc, .libPaths()), keep.source), i[[2]]) } # load the code env <- asNamespace(ns) codeFile <- file.path(package.lib, package, "R", package) if (file.exists(codeFile)) sys.source(codeFile, env, keep.source = keep.source) else warning(paste("Package ", sQuote(package), "contains no R code")) # save the package name in the environment assign(".packageName", package, envir = env) # register any S3 methods for (spec in nsInfo$S3methods) { generic <- spec[1] class <- spec[2] if (length(spec) == 3) mname <- spec[3] else mname <- paste(generic, class, sep=".") registerS3method(spec[1], spec[2], mname, env = env) } # load any dynamic libraries for (lib in nsInfo$dynlibs) library.dynam(lib, package, package.lib) addNamespaceDynLibs(env, nsInfo$dynlibs) # run the load hook runHook(".onLoad", env, package.lib, package) # process exports, seal, and clear on.exit action exports <- nsInfo$exports for (p in nsInfo$exportPatterns) exports <- c(ls(env, pat = p, all = TRUE), exports) namespaceExport(ns, exports) sealNamespace(ns) # **** FIXME: process methods but warn of possible problems if (! exists(".noGenerics", envir = env, inherits = FALSE) && length(objects(env, pattern="^\\.__M", all=TRUE)) != 0 && hadMethods && ! identical(package, "package:methods")) { warning("method code may not work in a name space") cacheMetaData(env, TRUE) } on.exit() ns } }
DefinesloadNamespace
(links are to index).
<dynGet
definition>= (<-U)
dynGet <- function(name, notFound = stop(paste(name, "not found"))) {
n <- sys.nframe()
while (n > 1) {
n <- n - 1
env <- sys.frame(n)
if (exists(name, env = env, inherits = FALSE))
return(get(name, env = env, inherits = FALSE))
}
notFound
}
DefinesdynGet
(links are to index).
library
library function just adds a small bit of
code to check whether the package to be loaded is a name space
package. If it is, it is loaded using loadNamespace
; otherwise
the code falls through the standard library
code.
<modification to library
function in base package>=
# if the name space mechanism is available and the package
# has a name space, then the name space loading mechanism
# takes over.
if (exists("packageHasNamespace") &&
packageHasNamespace(package, which.lib.loc)) {
tt <- try({
ns <- loadNamespace(package, c(which.lib.loc, lib.loc))
env <- attachNamespace(ns)
})
if (inherits(tt, "try-error"))
if (logical.return)
return(FALSE)
else stop("package/namespace load failed")
else {
on.exit(do.call("detach", list(name = pkgname)))
nogenerics <- checkNoGenerics(env)
if(warn.conflicts &&
!exists(".conflicts.OK", envir = env, inherits = FALSE))
checkConflicts(package, pkgname, pkgpath, nogenerics)
on.exit()
if (logical.return)
return(TRUE)
else
return(invisible(.packages()))
}
}
topenv
locates the nearest ``top level'' environment
to its argument.
<public name space functions>+= (<-U) [<-D->] topenv <- function(envir = parent.frame()) { while (! is.null(envir)) { if (! is.null(attr(envir, "name")) || identical(envir, .GlobalEnv) || .Internal(isNamespaceEnv(envir))) return(envir) else envir <- parent.env(envir) } return(.GlobalEnv) }
Definestopenv
(links are to index).
<public name space functions>+= (<-U) [<-D->]
unloadNamespace <- function(ns) {
<runHook
definition>
ns <- asNamespace(ns, base.OK = FALSE)
nsname <- getNamespaceName(ns)
pos <- match(paste("package", nsname, sep=":"), search())
if (! is.na(pos)) detach(pos = pos)
users <- getNamespaceUsers(ns)
if (length(users) != 0)
stop(paste("name space still used by:", paste(users, collapse = ", ")))
nspath <- getNamespaceInfo(ns, "path")
try(runHook(".onUnload", ns, nspath))
.Internal(unregisterNamespace(nsname))
}
.__S3MethodsTable__.
variable. (This is just a crude hack for now---something a bit more
sophisticated would be useful.) The function registerS3method
registers a method. This definition uses a promise if the method is
specified by name in order to work well with data base storage.
<internal name space functions>+= (<-U) [<-D]
registerS3method <- function(genname, class, method, envir = parent.frame()) {
<addNamespaceS3method
definition>
genfun <- get(genname, envir = envir)
if (typeof(genfun) == "closure")
defenv <- environment(genfun)
else defenv <- .BaseNamespaceEnv
if (! exists(".__S3MethodsTable__.", envir = defenv, inherits = FALSE))
assign(".__S3MethodsTable__.", new.env(hash = TRUE, parent = NULL),
envir = defenv)
table <- get(".__S3MethodsTable__.", envir = defenv, inherits = FALSE)
if (is.character(method)) {
wrap <- function(method, home) {
method <- method # force evaluation
home <- home # force evaluation
delay(get(method, env = home), env = environment())
}
assign(paste(genname, class, sep = "."), wrap(method, envir),
envir = table)
}
else if (is.function(method))
assign(paste(genname, class, sep = "."), method, envir = table)
else stop("bad method")
if (isNamespace(envir) && ! identical(envir, .BaseNamespaceEnv))
addNamespaceS3method(envir, genname, class, method)
}
DefinesregisterS3method
(links are to index).
<public name space functions>+= (<-U) [<-D] .Import <- function(...) { envir <- parent.frame() names <- as.character(substitute(list(...)))[-1] for (n in names) namespaceImportFrom(envir, n) } .ImportFrom <- function(name, ...) { envir <- parent.frame() name <- as.character(substitute(name)) names <- as.character(substitute(list(...)))[-1] namespaceImportFrom(envir, name, names) } .Export <- function(...) { ns <- topenv(parent.frame()) if (identical(ns, .BaseNamespaceEnv)) warning("all objects in base name space are currently exported.") else if (! isNamespace(ns)) stop("can only export from a name space") else { names <- as.character(substitute(list(...)))[-1] namespaceExport(ns, names) } } .S3method <- function(generic, class, method) { generic <- as.character(substitute(generic)) class <- as.character(substitute(class)) if (missing(method)) method <- paste(generic, class, sep=".") registerS3method(generic, class, method, envir = parent.frame()) invisible(NULL) }
Defines.Export
,.Import
,.ImportFrom
,.S3method
(links are to index).
addExports
definition>: D1, U2
addImports
definition>: D1, U2
addNamespaceDynLibs
definition>: D1, U2
addNamespaceS3method
definition>: D1, U2
dynGet
definition>: U1, D2
getInternalExportName
definition>: D1, U2, U3
makeImportExportNames
definition>: U1, D2, U3
makeNamespace
definition>: D1, U2
namespaceFilePath
definition>: D1, U2, U3
namespaceIsSealed
definition>: U1, D2, U3, U4
runHook
definition>: U1, D2, U3, U4
sealNamespace
definition>: D1, U2
sQuote
definition>: U1, D2, U3
library
function in base package>: D1