[R] limited formula length in tsls
John Fox
jfox at mcmaster.ca
Thu Aug 23 14:46:25 CEST 2001
Dear Brian,
At 07:53 AM 23/08/2001 +0100, Prof Brian D Ripley wrote:
>On Wed, 22 Aug 2001, John Fox wrote:
>. . .
> >
> > Clearly, the current situation is unsatisfactory, but it's unclear to me
> > what the best course of action is. A more elegant approach to treating the
> > model formula and instruments consistently would solve the problem, but
> > as.character should probably not truncate formulas.
>
>as.character is not the best tool for formulae. Use deparse:
>
> > deparse(mod)
>[1] "this ~ is + a + very + long + formula + with + a + very + large + "
>[2] " number + of + characters"
>
>say via
>
>paste(deparse(mod, 500), collapse="")
>
>which will cope with arbitrary long formulae.
>
>The cutoff limit is 500, and a trivial change to the internals of
>as.character (which I have just made for 1.3.1) increases the cutoff from
>60 to 500. Nevertheless. paste(deparse(mod, 500), collapse="") remains
>better.
Thank you for the suggestion. I've attached a modified tsls.formula, which
I'll include in the next version of the sem package. A few functions in my
car package do similar formula manipulation, and these too need to be
changed to avoid problems with long formulas.
Regards,
John
------------- snip ------------------
tsls.formula <- function(model, instruments, data, subset,
na.action, contrasts=NULL){
if (missing(na.action))
na.action <- options()$na.action
m <- match.call(expand.dots = FALSE)
if (is.matrix(eval(m$data, sys.frame(sys.parent()))))
m$data <- as.data.frame(data)
c1 <- unlist(strsplit(paste(deparse(model, width.cutoff=500),
collapse=""),'~'))
c2 <- unlist(strsplit(paste(deparse(instruments, width.cutoff=500),
collapse=""),'~'))
formula <- as.formula(paste(c1[1], '~', c1[2], '+', c2[2]))
m$formula <- formula
m$instruments <- m$model <- m$contrasts <- NULL
m[[1]] <- as.name("model.frame")
mf <- eval(m, sys.frame(sys.parent()))
na.act <- attr(mf, "na.action")
Z <- model.matrix(instruments, data = mf, contrasts)
response <- attr(attr(mf, "terms"), "response")
y <- mf[,response]
X <- model.matrix(model, data=mf, contrasts)
result <- tsls(y, X, Z, colnames(X))
result$response.name <- c1[1]
result$formula <- model
result$instruments <- instruments
if (!is.null(na.act))
result$na.action <- na.act
class(result) <- "tsls"
result
}
-----------------------------------------------------
John Fox
Department of Sociology
McMaster University
Hamilton, Ontario, Canada L8S 4M4
email: jfox at mcmaster.ca
phone: 905-525-9140x23604
web: www.socsci.mcmaster.ca/jfox
-----------------------------------------------------
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
r-help mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !) To: r-help-request at stat.math.ethz.ch
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._
More information about the R-help
mailing list