[Rd] Aliasing a function

hadley wickham h.wickham at gmail.com
Tue Feb 26 18:16:48 CET 2008


Thanks Tony (and others), for getting me started.  I eventually ended up with:

TopLevel$build_accessor <- function(., extra_args = c()) {
  layer <- if (.$class() %in% c("geom","stat", "position")) c(
    list(mapping=NULL,data=NULL),
    compact(list(
      geom = if (exists("default_geom", .)) .$default_geom()$objname,
      stat = if (exists("default_stat", .)) .$default_stat()$objname,
      position = if (exists("default_pos", .)) .$default_pos()$objname
    ))
  )
  params <- .$params()
  params <- params[names(params) != "..."]
  args <- c(layer, params)

  body <- ps(
    .$myName(), "$", "new(",
    if (length(args) > 0) ps(names(args),"=", names(args), collase =", "),
    if (length(extra_args) > 0) ps(names(extra_args),"=", extra_args,
collase =", "),
    "...",
    ")"
  )
  f <- function() {}
  formals(f) <- as.pairlist(c(args, alist(... =)))
  body(f) <- parse(text = body)
  environment(f) <- globalenv()
  f
}

-- obviously there are far more ggplot details in there than I had
first anticipated.

Hadley

On Mon, Feb 25, 2008 at 12:24 AM, Tony Plate <tplate at acm.org> wrote:
> Maybe something like this? (though it seems like it might be more
>  straightforward to do this sort of thing by text-processing a source
>  file then source'ing it in R).
>
>   > f <- function(a, b, c) c(a=a,b=b,c=c)
>   > attr(f, "source") <- NULL
>   > f
>  function (a, b, c)
>
> c(a = a, b = b, c = c)
>   > g1 <- f
>   > ff <- formals(f)
>   > argtrans <- c(a="d", b="e", c="f")
>   > names(ff) <- argtrans
>   > g2 <- as.function(c(ff, as.call(c(list(as.name("f")),
>  lapply(argtrans, as.name)))))
>   > g2
>  function (d, e, f)
>  f(a = d, b = e, c = f)
>   > f(1,2,3)
>  a b c
>  1 2 3
>   > g1(a=1,b=2,c=3)
>  a b c
>  1 2 3
>   > g2(d=1,e=2,f=3)
>  a b c
>  1 2 3
>   >
>
>  -- Tony Plate
>
>
>
>
>  hadley wickham wrote:
>  > On Sat, Feb 23, 2008 at 5:52 PM, Gabor Grothendieck
>  > <ggrothendieck at gmail.com> wrote:
>  >
>  >> I assume he wants to be able to change the
>  >>  formals although its confusing since the example
>  >>  uses the same formals in both cases.
>  >>
>  >
>  > Yes, that was an important point that I forgot to mention!  Thanks for
>  > the pointer to formals but it doesn't work in this case:
>  >
>  > function (a = 1, b = 2, c = 3)
>  > g(...)
>  >
>  >> f(c=5)
>  >>
>  > Error in f(c = 5) : '...' used in an incorrect context
>  >
>  > Hadley
>  >
>  >
>  >
>
>



-- 
http://had.co.nz/



More information about the R-devel mailing list