Skip to content

Commit

Permalink
Merge pull request #20 from andrie/ridge-regression
Browse files Browse the repository at this point in the history
Added ridge regression
  • Loading branch information
andrie committed May 19, 2014
2 parents 5accfa4 + e32f332 commit 81d1ec0
Show file tree
Hide file tree
Showing 2 changed files with 84 additions and 0 deletions.
58 changes: 58 additions & 0 deletions R/rxRidgeReg.R
@@ -0,0 +1,58 @@
#' Fits ridge regression model.
#'
#' Fits ridge regression model using the correlation matrix. Supports estimation of multiple values of the regularisation coefficient (lambda).
#'
#' @param formula Model formula
#' @param data Data frame or XDF
#' @param lambda Regularisation coefficient. Can be a single value or a vector.
#' @param ... Passed to \code{\link[RevoScaleR]{rxCovCor}}
#' @references http://blog.revolutionanalytics.com/2014/03/extending-revoscaler-ridge-regression.html
#' @author Derek McRae Norton
#' @export
#'
rxRidgeReg <- function(formula, data, lambda, ...) {
myTerms <- all.vars(formula)
newForm <- as.formula(paste("~", paste(myTerms, collapse = "+")))
myCor <- rxCovCor(newForm, data = data, type = "Cor", ...)
n <- myCor$valid.obs
k <- nrow(myCor$CovCor) - 1
bridgeprime <- do.call(rbind, lapply(lambda,
function(l) qr.solve(myCor$CovCor[-1,-1] + l*diag(k),
myCor$CovCor[-1,1])))
bridge <- myCor$StdDevs[1] * sweep(bridgeprime, 2,
myCor$StdDevs[-1], "/")
bridge <- cbind(t(myCor$Means[1] -
tcrossprod(myCor$Means[-1], bridge)), bridge)
rownames(bridge) <- format(lambda)
obj <- bridge
class(obj) <- c("rxRidgeReg", "matrix")
obj
}


plot.rxRidgeReg <- function(dat, scale=FALSE){
if(colnames(dat)[1] == "") colnames(dat)[1] <- "Intercept"
if(scale) {
scaleValue <- apply(dat, 2, function(x){
max(max(x), abs(min(x)))
})
dat <- scale(dat, center=FALSE, scale=scaleValue)
ylab <- "Scaled coefficient"
} else {
ylab <- "Coefficient"
}

matplot(x=as.numeric(rownames(dat)), y=dat, type="l", bty="n",
ylab=ylab, xlab="lambda")

}

#' @examples
#' data(swiss)
#' frm <- formulaExpand(Fertility ~ ., data=swiss)
#' rxRidgeReg(frm, swiss, lambda=0)
#' model <- rxRidgeReg(frm, swiss, lambda=c(seq(from=0, to=1, by=0.05)))
#' plot(model)
#' plot(model, scale=TRUE)


26 changes: 26 additions & 0 deletions man/rxRidgeReg.Rd
@@ -0,0 +1,26 @@
\name{rxRidgeReg}
\alias{rxRidgeReg}
\title{Fits ridge regression model.}
\usage{
rxRidgeReg(formula, data, lambda, ...)
}
\arguments{
\item{formula}{Model formula}

\item{data}{Data frame or XDF}

\item{lambda}{Regularisation coefficient. Can be a
single value or a vector.}

\item{...}{Passed to \code{\link[RevoScaleR]{rxCovCor}}}
}
\description{
Fits ridge regression model using the correlation matrix. Supports estimation of multiple values of the regularisation coefficient (lambda).
}
\author{
Derek McRae Norton
}
\references{
http://blog.revolutionanalytics.com/2014/03/extending-revoscaler-ridge-regression.html
}

0 comments on commit 81d1ec0

Please sign in to comment.