[Rd] Functions that write functions in R packages

Gabor Grothendieck ggrothendieck at gmail.com
Sat Feb 24 06:33:44 CET 2007


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 <h.wickham at gmail.com> 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 at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>



More information about the R-devel mailing list