Skip to content

Instantly share code, notes, and snippets.

@crowding
Created January 20, 2013 08:37
Show Gist options
  • Save crowding/4577311 to your computer and use it in GitHub Desktop.
Save crowding/4577311 to your computer and use it in GitHub Desktop.
enumerate all expressions w. some oberands and operators
##
{
## let's go ahead and generate the possibilities.
x <- 2
y <- pi
z <- exp(1)
`%^%` <- `^`
`%/%` <- `/`
splitrows <- function(s) split(s, seq_len(dim(s)[[1]]))
sym <- c("x", "y", "z")
op <- c("%/%","%^%", "%*%")
library(gtools)
syms <- permutations(length(sym), length(sym), sym)
ops <- permutations(length(op), length(sym)-1, op, repeats.allowed=TRUE)
orders <- permutations(length(sym)-1, length(sym)-1)
cases <- Reduce(merge,
list(data.frame(sym=I(splitrows(syms))),
data.frame(op=I(splitrows(ops))),
data.frame(order=I(splitrows(orders)))))
results <- do.call(rbind, apply(
cases, 1,
function(case) {
with(lapply(case, unlist), {
expr <- sym #or lapply(sym, as.name)
for ( i in seq_along(op)) {
expr[c(order[i], order[i]+1)] <-
paste("(", expr[[order[i]]], op[i], expr[[order[i]+1]], ")")
#alternately
#paste("`",op[i],"`(", expr[[order[i]]], ", ", expr[[order[i]+1]], ")", sep="")
#alternately
#list(call(op[i], expr[[order[i]]], op[i], expr[[order[i]+1]])
}
expr <- expr[[order[i]]]
value <- eval(parse(text=expr))
reparse <- deparse(parse(text=expr)[[1]])
value2 <- eval(parse(text=reparse))
same <- value == value2
data.frame(expr, value, reparse, value2, same)
})
}))
}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment