How about something like this where we put the accessors in .GlobalEnv at object construction time in this example but you could alternately place them into package:ggplot or elsewhere on the search path:
library(proto) make.accessors <- function(p, e = p, ...) lapply(ls(p, ...), function(v) { if (is.function(get(v, p))) e[[v]] <- do.call("$.proto", list(p, v)) invisible(p) }) p <- proto(x = function(.) 1, y = function(.) 2) make.accessors(p, .GlobalEnv) x() print(x) y() print(y) rm(x, y) # or the constructor of objects like p could build it right it # at object construction time make.p <- function(..., e = .GlobalEnv) make.accessors(proto(...), e = e) q <- make.p(x = function(.) 1, y = function(.) 2) x() print(x) y() print(y) On 2/24/07, hadley wickham <[EMAIL PROTECTED]> wrote: > I'm trying to make wrappers to proto functions (eg. GeomPoint$new()) > so that user don't notice that they're using a proto function (ie. use > geom_point()) instead. I'm hoping I can wrap proto up sufficiently > that only developers need to worry that ggplot uses a completely > different oo system. > > Hadley > > On 2/23/07, Gabor Grothendieck <[EMAIL PROTECTED]> wrote: > > Not sure what the setup is here but if the objects are > > intended to be proto objects then the accessor functions > > could be placed in the object itself (or in an ancestor object) > > rather than in the global environment. For example, this inserts > > a function get.v(.) into proto object p for each variable v in p. > > > > library(proto) > > > > make.accessors <- function(p, ...) { > > lapply(ls(p, ...), f. <- function(v) { > > nm <- paste("get", v, sep = ".") > > p[[nm]] <- function(.) {} > > body(p[[nm]]) <- substitute(.$v, list(v = v)) > > environment(p[[nm]]) <- p > > }) > > invisible(p) > > } > > make.accessors(p) > > p$get.x() > > p$get.y() > > > > # or the constructor of objects like p could build it right it > > # at object construction time > > make.p <- function(...) make.accessors(proto(...)) > > q <- make.p(x = 1, y = 2) > > q$get.x() > > q$get.y() > > > > > > On 2/23/07, hadley wickham <[EMAIL PROTECTED]> wrote: > > > Dear all, > > > > > > Another question related to my ggplot package: I have made some > > > substantial changes to the backend of my package so that plot objects > > > can now describe themselves much better. A consequence of this is > > > that a number of convenience functions that previously I wrote by > > > hand, can now be written automatically. What is the best practice for > > > creating these functions for bundling in a package? I see three > > > possible solutions: > > > > > > * dump function specifications out to a .r file > > > * dynamically create at package build time so they are including in > > > the package rdata file > > > * dynamically create at package load time > > > > > > Can anyone offer any advice as to which is preferable? (or if there's > > > a better way I haven't thought of) > > > > > > My code currently looks like this (experimenting with two ways of > > > creating the functions) > > > > > > create_accessors <- function(objects, name, short=NULL) { > > > lapply(objects, function(x) { > > > assign(paste(name, x$objname, sep="_"), x$new, > > > pos=globalenv()) > > > if (!is.null(short)) { > > > eval( > > > substitute( > > > f <- function(plot, ...) plot + > > > add(...), > > > list( > > > add = as.name(paste(name, > > > x$objname, sep="_")), > > > f = as.name(paste(short, > > > x$objname, sep="")) > > > ) > > > ), envir = globalenv() > > > ) > > > > > > } > > > }) > > > } > > > > > > Thanks, > > > > > > Hadley > > > > > > ______________________________________________ > > > 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