[R] RE: [S] VIF Variance Inflation Factor

Bill.Venables@cmis.csiro.au Bill.Venables at cmis.csiro.au
Tue Oct 22 03:54:35 CEST 2002


Kenneth Cabrera asks:

>  -----Original Message-----
> From: 	Kenneth Cabrera [mailto:krcabrer at epm.net.co] 
> Sent:	Tuesday, October 22, 2002 10:05 AM
> Cc:	s-news at lists.biostat.wustl.edu
> Subject:	[S] VIF Variance Inflation Factor
> 
> Hi Dear S+ Users:
> 
> How can I obtain the VIF of a lm object?
	[WNV]  this comes up every now and then and I suppose it has been
answered dozens of times, but here is a simple version of a generic function
that people might find useful (and may consider adding methods to)

vif <- function(object, ...)
UseMethod("vif")

vif.default <- function(object, ...)
stop("No default method for vif.  Sorry.")

vif.lm <- function(object, ...) {	
  V <- summary(object)$cov.unscaled
  Vi <- crossprod(model.matrix(object))
	nam <- names(coef(object))
  if(k <- match("(Intercept)", nam, nomatch = F)) {
		v1 <- diag(V)[-k]
		v2 <- (diag(Vi)[-k] - Vi[k, -k]^2/Vi[k,k])
		nam <- nam[-k]
	} else {
		v1 <- diag(V)
		v2 <- diag(Vi)
		warning("No intercept term detected.  Results may
surprise.")
	}
	structure(v1*v2, names = nam)
}

	[WNV]  use in the obvious way.  (Works in both S universes.)

	> fm <- lm(Gas ~ Insul/Temp, whiteside)
	> vif(fm)
	  Insul InsulBeforeTemp InsulAfterTemp 
	 4.3299        2.932245       2.397654
	> fm <- lm(Gas ~ Insul + Temp, whiteside)
	> vif(fm)
	    Insul     Temp 
	 1.027048 1.027048
	> fm <- lm(Gas ~ Temp, whiteside)
	> vif(fm)
	 Temp 
	    1
	>


> Thank you for your help!
> 
> Kenneth Cabrera
> 
> --------------------------------------------------------------------
> This message was distributed by s-news at lists.biostat.wustl.edu.  To
> unsubscribe send e-mail to s-news-request at lists.biostat.wustl.edu with
> the BODY of the message:  unsubscribe s-news

-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
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