[R] Specifying formula inside a function
Mark Seeto
markseeto at gmail.com
Thu Jun 10 07:09:31 CEST 2010
Bill and Erik, thank you very much for your help. In addition to
solving my problem, both solutions contain other good things I didn't
know about.
Regards,
Mark Seeto
On Thu, Jun 10, 2010 at 2:44 PM, Erik Iverson <eriki at ccbr.umn.edu> wrote:
> Hello,
>
>> How does one specify a formula to lm inside a function (with variable
>> names not known in advance) and have the formula appear explicitly in
>> the output?
>>
>> For example,
>>
>> f <- function(d) {
>> in.model <- sample(c(0,1), ncol(d)-1, replace=T)
>> current.model <- lm(paste(names(d)[1], "~",
>> paste(names(d[2:ncol(d)])[which(in.model == 1)], collapse= "+")),
>> data=d) #***
>> return(current.model)
>> }
>> x1 <- rnorm(50,0,1)
>> x2 <- rnorm(50,0,1)
>> x3 <- rnorm(50,0,1)
>> x4 <- rnorm(50,0,1)
>> y <- rnorm(50,0,1)
>> d <- data.frame(y, x1, x2, x3, x4)
>> f(d)
>>
>> Call:
>> lm(formula = paste(names(d)[1], "~",
>> paste(names(d[2:ncol(d)])[which(in.model == 1)], collapse = "+")),
>> data = d)
>>
>> Coefficients:
>> (Intercept) x3 x4
>> -0.1087 0.2830 0.1024
>>
>> How can I specify the formula in the line marked *** so that the
>> output will show "formula = y ~ x3 + x4" instead of "formula =
>> paste..."?
>>
>
> Well, there could very well be some tricks you can pull with ?substitute, or
> others, but I can't seem to figure it out. Instead of tricks, it might be
> easier/clearer to assign a class to your object, say 'test', and write a
> print method for that based on print.lm. There very well may be drawbacks
> to this that I am not realizing :).
>
> f <- function(d) {
> in.model <- sample(c(0,1), ncol(d)-1, replace=TRUE)
> current.model <- lm(paste(names(d)[1], "~",
> paste(names(d[2:ncol(d)])[which(in.model == 1)],
> collapse= "+")),
> data=d)
> class(current.model) <- c("test", "lm")
> current.model
> }
>
> # slight modification to print.lm
> print.test <- function (x, digits = max(3, getOption("digits") - 3), ...)
> {
> cat("\nCall:\n", deparse(x$terms), "\n\n", sep = "")
> if (length(coef(x))) {
> cat("Coefficients:\n")
> print.default(format(coef(x), digits = digits), print.gap = 2,
> quote = FALSE)
> }
> else cat("No coefficients\n")
> cat("\n")
> invisible(x)
> }
>
> # should give you what you want...
> f(d)
>
On Thu, Jun 10, 2010 at 2:43 PM, <Bill.Venables at csiro.au> wrote:
> Here is one way.
>
> f <- function(d) {
> y <- names(d)[1]
> xs <- names(d)[-1]
> nx <- length(xs)
> xs <- sort(sample(xs, sample(1:nx, 1)))
> form <- as.formula(paste(y, "~", paste(xs, collapse="+")))
> Call <- substitute(lm(FORM, data = d), list(FORM = form))
> eval(Call)
> }
> d <- within(data.frame(y = rnorm(50)), {
> x1 <- rnorm(50)
> x2 <- rnorm(50)
> x3 <- rnorm(50)
> x4 <- rnorm(50)
> })
>
> f(d)
>
More information about the R-help
mailing list