[Rd] Qs: The list of arguments, wrapping functions...

Wacek Kusnierczyk Waclaw.Marcin.Kusnierczyk at idi.ntnu.no
Tue May 19 23:42:06 CEST 2009


Kynn Jones wrote:
> Hi.  I'm pretty new to R, but I've been programming in other languages for
> some time.  I have a couple of questions regarding programming with function
> objects.
> 1. Is there a way for a function to refer generically to all its actual
> arguments as a list?  I'm thinking of something like the @_ array in Perl or
> the arguments variable in JavaScript.  (By "actual" I mean the ones that
> were actually passed, as opposed to its formal arguments, as returned by
> formals()).
>   

a quick shot from a naive r user:

    f = function(a=1, b, ...)
        as.list(match.call()[-1])

    f(2)
    f(b=2)
    f(1,2,3)


> 2. I have a package in which most of the functions have the form:
>
> the.function <- function(some, list, of, params) {
>     return( some.other.function(the.list.of.params.to.this.function));
> }
>
> Is there a way that I can use a loop to define all these functions?
>   

what do you mean, precisely?

> In general, I'm looking for all the information I can find on the subject of
> dynamic function definition (i.e. using code to automate the definition of
> functions at runtime).  I'm most interested in introspection facilities and
> dynamic code generation.  E.g. is it possible to write a module that
> "redefines itself" when sourced?  Or can a function redefine itself when
> first run?  Or how can a function find out about how it was called?
>   

another quick shot from a naive r user:

    f = function()
       assign(
           as.character(match.call()[[1]]),
           function() evil(),
           envir=parent.frame())
      
    f
    f()
    f

you can then use stuff like formals, body, match.call, parent.frame,
etc. to have your function reimplement itself based on how and where it
is called.

> FWIW, Some of the things I'd like to do are in the spirit of a decorator in
> Python, which is a function that take a function f an argument and return
> another function g that is somehow based on f.  For example, this makes it
> very easy to write functions as wrappers to other simpler functions.
>   

recall that decorators, when applied using the @syntax, do not just
return a new function, but rather redefine the one to which they are
applied.  so in r it would not be enough to write a function that takes
a function and returns another one;  it'd have to establish the input
function's name and the environment it resides in, and then replace that
entry in that environment with the new function.

yet another quick shot from the same naive r user:

    # the decorator operator
    '%@%' = function(decorator, definition) {
       definition = substitute(definition)
       name = definition[[2]][[2]]
       definition = definition[[2]][[3]]
       assign(
           as.character(name),
           decorator(eval(definition, envir=parent.frame())),
           envir=parent.frame()) }

    # a decorator
    twice = function(f)
       function(...)
           do.call(f, as.list(f(...)))

    # a function
    inv = function(a, b)
       c(b, a)

    inv(1,2)
    # 2 1
    twice(inv)(1,2)
    # 1 2

    # a decorated function
    twice %@% {
       square = function(x) x^2 }

    square(2)
    # 16

    # another decorator
    verbose = function(f)
       function(...) {
          cat('computing...\n')
          f(...) }

    # another decorated function
    verbose %@% {
       square = function(x) x^2 }

    square(2)
    # computing...
    # 4

there is certainly a lot of space for improvements, and there are
possibly bugs in the code above, but i hope it helps a little.

vQ



More information about the R-devel mailing list