The version I posted yesterday did indeed mess up when some arguments were unspecified. Here's a revision that seems to work in all the tests I can think of. I also added the SIMPLIFY and USE.NAMES args from mapply to it, and a sanity check to the args.
I did notice and work around one buglet in mapply: if you choose not to vectorize any arguments, you don't get a call to the original function, mapply returns "list()". For example, > mapply(function(x) x^2, MoreArgs = list(x=2)) list() whereas I would think 4 is a more logical answer. Vectorize <- function(FUN, vectorize.args = arg.names, SIMPLIFY = TRUE, USE.NAMES = TRUE) { arg.names <- as.list(formals(FUN)) arg.names[["..."]] <- NULL arg.names <- names(arg.names) vectorize.args <- as.character(vectorize.args) if (!length(vectorize.args)) return(FUN) if (!all(vectorize.args %in% arg.names)) stop("must specify formal argument names to vectorize") FUNV <- function() { # will set the formals below args <- lapply(as.list(match.call())[-1], eval, parent.frame()) dovec <- match(vectorize.args, names(args), nomatch = 0) do.call("mapply", c(FUN = FUN, args[dovec], MoreArgs = list(args[-dovec]), SIMPLIFY = SIMPLIFY, USE.NAMES = USE.NAMES)) } formals(FUNV) <- formals(FUN) FUNV } Duncan Murdoch On 10/31/2005 3:49 PM, Tony Plate wrote: > Duncan Murdoch wrote: >> On 10/31/2005 2:15 PM, Tony Plate wrote: >> >>> [snipped comments irrelevant to this post] >>> >>> So, here's a first pass at a general Vectorize() function: >>> >>> Vectorize <- function(FUN, vectorize.args) { >>> if (!all(is.element(vectorize.args, names(formals(FUN))))) >>> stop("some args to vectorize are not args of FUN") >>> FUNV <- eval(substitute(function(x, ...) mapply(FUN, x, >>> MoreArgs=list(...)), list(FUN=FUN))) >>> formals(FUNV) <- formals(FUNV)[c(rep(1, length(vectorize.args)), 2)] >>> names(formals(FUNV))[seq(along=vectorize.args)] <- vectorize.args >>> body(FUNV) <- body(FUNV)[c(1, 2, rep(3, length(vectorize.args)), 4)] >>> body(FUNV)[seq(3,len=length(vectorize.args))] <- >>> lapply(vectorize.args, as.name) >>> FUNV >>> } >> >> >> I'd think the formals of the result should be identical to the formals >> of the input. >> >> Regarding the environment of the result: it is used to determine the >> meaning of symbols that aren't defined within the function, e.g. things >> like "eval", "substitute", etc. So I'd say that you don't want anything >> special there, as long as you make sure that FUN is always evaluated in >> its original environment. >> >> Generally I don't like the look of that manipulation of the body of your >> result; it looks pretty fragile to me. But I haven't worked out exactly >> what you're doing, or whether it's possible to avoid it. >> >> Duncan Murdoch >> > > Thanks for explanation about the environment. > > I should have said, that manipulation of the body creates the call > mapply(FUN, A, alpha, MoreArgs=list(...)) > from the original (x is a dummy argument) > mapply(FUN, x, MoreArgs=list(...)) > > Are there better ways to create that call? The difficulty is that the > argument names in the call are derived from the actual arguments to > Vectorize(), and there is an arbitrary number of them. > > As for the formals of the result being identical to the formals of the > input, I couldn't see any easy way to do that and still support optional > arguments, e.g., if the input function formals were (a, b, t=1), then > the result function would look something like: > > function(a, b, t=1) mapply(FUN, a, b, t=t) > > and missing(t) would not work correctly within FUN (with even more > serious problems for optional arguments with no defaults). > > -- Tony Plate > > >> >>> ssd <- function(A,alpha,Y,t) sum((Y - A*exp(-alpha*t))2) >>> # SSD is a vectorized version of ssd >>> SSD <- function(Avec, alphavec, ...) mapply(ssd, Avec, alphavec, >>> MoreArgs=list(...)) >>> # Vectorize(ssd, c("A", "alpha")) should produce >>> # function(A, alpha, ...) mapply(ssd, A, alpha, MoreArgs=list(...)) >>> Y <- 1:5; t <- 3 >>> outer(1:3, 1:2, SSD, Y, t) >>> outer(1:3, 1:2, Vectorize(ssd, c("A", "alpha")), Y, t) >>> >>> > # transcript of running the above commands >>> > Vectorize(ssd, c("A", "alpha")) >>> function (A, alpha, ...) >>> mapply(function (A, alpha, Y, t) >>> sum((Y - A * exp(-alpha * t))^2), A, alpha, MoreArgs = list(...)) >>> <environment: 0x1361f40> >>> > Y <- 1:5; t <- 3 >>> > outer(1:3, 1:2, SSD, Y, t) >>> [,1] [,2] >>> [1,] 53.51878 54.92567 >>> [2,] 52.06235 54.85140 >>> [3,] 50.63071 54.77719 >>> > outer(1:3, 1:2, Vectorize(ssd, c("A", "alpha")), Y, t) >>> [,1] [,2] >>> [1,] 53.51878 54.92567 >>> [2,] 52.06235 54.85140 >>> [3,] 50.63071 54.77719 >>> > >>> >>> [There are a couple of minor design issues around syntax -- what is >>> the best way of specifying the arguments to vectorize? (e.g., what >>> about an interface that allowed Vectorize(ssd ~ A * alpha)?), and >>> should the function name rather than the definition appear in the >>> result of Vectorize()? But those are issues of secondary importance.] >>> >>> I have to confess I don't really understand how environments work with >>> functions, so I don't know if this Vectorize() function will work in >>> general. What is the appropriate environment for returned value of >>> Vectorize()? Is this approach to creating a Vectorize() function on >>> the right tack at all? Any other improvements or fixes? >>> >>> -- Tony Plate >>> >>> >>> Peter Dalgaard wrote: >>> >>>> Thomas Lumley <[EMAIL PROTECTED]> writes: >>>> >>>> >>>>> On Sun, 30 Oct 2005, Jonathan Rougier wrote: >>>>> >>>>> >>>>>> I'm not sure about this. Perhaps I am a dinosaur, but my feeling is >>>>>> that if people are writing functions in R that might be subject to >>>>>> simple operations like outer products, then they ought to be writing >>>>>> vectorised functions! >>>>> >>>>> >>>>> I would agree. How about an oapply() function that does multiway >>>>> (rather than just two-way) outer products. Basing the name on >>>>> "apply" would emphasize the similarity to other flexible, not >>>>> particularly optimized second-order functions. >>>> >>>> >>>> >>>> In fairness, it should probably be said that not all problems >>>> vectorize naturally. One example is >>>> >>>> ssd <- function(A,alpha) sum((Y - A*exp(-alpha*t))^2) >>>> >>>> However, it should be worth noting that with the mapply() function at >>>> hand, it is pretty easy to turn a non-vectorized function into a >>>> vectorized one. >>>> SSD <- function(A,alpha) mapply(ssd, A, alpha) >>>> >>>> (Anybody want to try their hand on writing a general Vectorize() >>>> function? I.e. one that allowed >>>> >>>> outer(Avec, alphavec, Vectorize(ssd)) >>>> >>>> to work.) >>> >>> >>> ______________________________________________ >>> 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 ______________________________________________ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel