[R] Functional programming?
Gabor Grothendieck
ggrothendieck at gmail.com
Wed Mar 2 20:29:37 CET 2016
This manufactures the functions without using eval by using substitute
to substitute i-1 and a[i] into an expression for the body which is
then assigned to the body of the function:
hh <- vector("list", 5)
hh[[1]] <- f(a[1])
for(i in 2:5) {
hh[[i]] <- hh[[1]]
body(hh[[i]]) <- substitute(hh[[iprev]](x) * g(ai)(x), list(iprev
= i-1, ai = a[i]))
}
all.equal(h[[5]](.5), hh[[5]](.5)) # test
## [1] TRUE
This uses quote to define the body of h[[i]] as a call object and then
substitutes in the values of i-1 and a[i] assigning the result to the
body of h[[i]].
h <- vector("list", 5)
h[[1]] <- f(a[1])
for(i in 2:5) {
h[[i]] <- h[[1]]
body(hh[[i]]) <- do.call(substitute,
list(quote(hh[[iprev]](x) *
g(ai)(x)),
list(iprev = i-1, ai = a[i])))
}
On Wed, Mar 2, 2016 at 11:47 AM, Roger Koenker <rkoenker at illinois.edu> wrote:
> I have a (remarkably ugly!!) code snippet (below) that, given
> two simple functions, f and g, generates
> a list of new functions h_{k+1} = h_k * g, k= 1, …, K. Surely, there are vastly
> better ways to do this. I don’t particularly care about the returned list,
> I’d be happy to have the final h_K version of the function,
> but I keep losing my way and running into the dreaded:
>
> Error in h[[1]] : object of type 'closure' is not subsettable
> or
> Error: evaluation nested too deeply: infinite recursion / options(expressions=)?
>
> Mainly I’d like to get rid of the horrible, horrible paste/parse/eval evils. Admittedly
> the f,g look a bit strange, so you may have to suspend disbelief to imagine that there is
> something more sensible lurking beneath this minimal (toy) example.
>
> f <- function(u) function(x) u * x^2
> g <- function(u) function(x) u * log(x)
> set.seed(3)
> a <- runif(5)
> h <- list()
> hit <- list()
> h[[1]] <- f(a[1])
> hit[[1]] <- f(a[1])
> for(i in 2:5){
> ht <- paste("function(x) h[[", i-1, "]](x) * g(", a[i], ")(x)")
> h[[i]] <- eval(parse(text = ht))
> hit[[i]] <- function(x) {force(i); return(h[[i]] (x))}
> }
> x <- 1:99/10
> plot(x, h[[1]](x), type = "l")
> for(i in 2:5)
> lines(x, h[[i]](x), col = i)
>
> Thanks,
> Roger
>
> ______________________________________________
> R-help at r-project.org mailing list -- To UNSUBSCRIBE and more, see
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
--
Statistics & Software Consulting
GKX Group, GKX Associates Inc.
tel: 1-877-GKX-GROUP
email: ggrothendieck at gmail.com
More information about the R-help
mailing list