From 79737d5e93037300eb78d89300af4bd44e4a781c Mon Sep 17 00:00:00 2001 From: Suraj Yerramilli Date: Sun, 22 May 2016 09:35:37 +0530 Subject: added the recursive arx method --- NAMESPACE | 1 + R/rarx.R | 30 ++++++++++++++++++++++++++++-- 2 files changed, 29 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 5350368..ce892cd 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -56,6 +56,7 @@ export(oe) export(optimOptions) export(outputData) export(outputNames) +export(rarx) export(read.idframe) export(read.table.idframe) export(residplot) diff --git a/R/rarx.R b/R/rarx.R index 8b477fa..b55e5ce 100644 --- a/R/rarx.R +++ b/R/rarx.R @@ -1,3 +1,4 @@ +#' @export rarx <- function(x,order=c(1,1,1),lambda=0.95){ y <- outputData(x); u <- inputData(x) N <- dim(y)[1] @@ -7,7 +8,32 @@ rarx <- function(x,order=c(1,1,1),lambda=0.95){ yout <- apply(y,2,padZeros,n=n) uout <- apply(u,2,padZeros,n=n) - fixedflag = is.null(fixed) uindex <- nk:nb1 - yindex <- 1:na + if(na!=0) yindex <- 1:na + + reg <- function(i) { + # regressor + temp <- numeric(0) + if(na!=0) temp <- c(temp,-yout[i-yindex,]) + phi <- c(temp,uout[i-uindex,]) + phi + } + + # R0 <- reg(n+1)%*%t(reg(n+1)) + # Plast <- solve(R0) + Plast <- 10^4*diag(na+nb) + theta <- matrix(0,N,na+nb) + theta[1,] <- Plast%*%reg(n+1)%*%y[1,,drop=FALSE] + yhat <- y + yhat[1,] <- t(reg(n+1))%*%t(theta[1,,drop=FALSE]) + + for(i in 2:N){ + temp <- reg(n+i) + yhat[i,] <- t(temp)%*%t(theta[i-1,,drop=FALSE]) + eps_i <- y[i,,drop=FALSE] - yhat[i,,drop=FALSE] + kappa_i <- Plast%*%temp/(lambda+t(temp)%*%Plast%*%temp)[1] + theta[i,] <- t(t(theta[i-1,,drop=F])+eps_i[1]*kappa_i) + Plast <- (diag(na+nb)-kappa_i%*%t(temp))%*%Plast/lambda + } + list(theta=theta,yhat=yhat,P=Plast) } \ No newline at end of file -- cgit