R/methods-show.R

Defines functions show.urca

Documented in show.urca

##
## Setting methods for classes
##
show.urca <- function(object){
  title <- paste("#", object@test.name, "Unit Root / Cointegration Test #", sep=" ")
  row <- paste(rep("#", nchar(title)), collapse="")
  cat("\n")
  cat(row, "\n")
  cat(title, "\n")
  cat(row, "\n")
  cat("\n")
  cat("The value of the test statistic is:", round(object@teststat, 4), "\n")
  cat('\n')
}

setMethod("show", "ur.kpss", show.urca)
setMethod("show", "ca.jo", show.urca)
setMethod("show", "cajo.test", show.urca)
setMethod("show", "ca.po", show.urca)
setMethod("show", "ur.pp", show.urca)
setMethod("show", "ur.df", show.urca)
setMethod("show", "ur.sp", show.urca)
setMethod("show", "ur.za", show.urca)
setMethod("show", "ur.ers", show.urca)

setMethod("show", "sumurca", function(object){
  if(object@classname=="ur.za"){
    title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
    row <- paste(rep("#", nchar(title)), collapse="")
    cat("\n")
    cat(row, "\n")
    cat(title, "\n")
    cat(row, "\n")
    cat("\n")
    print(summary(object@testreg))
    cat('\n')
    cat('Teststatistic:', round(object@teststat, 4), '\n')
    cat('Critical values: 0.01=', object@cval[1], '0.05=', object@cval[2], '0.1=', object@cval[3], '\n')
    cat('\n')
    cat('Potential break point at position:', object@bpoint, '\n')
    cat('\n')
    invisible(object)
  }else if(object@classname=="ur.sp"){
    title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
    row <- paste(rep("#", nchar(title)), collapse="")
    cat("\n")
    cat(row, "\n")
    cat(title, "\n")
    cat(row, "\n")
    cat("\n")
    print(object@testreg)
    cat('\n')
    cat('Value of test-statistic is:', round(object@teststat, 4), '\n')
    cat('Critical value for a significance level of', object@signif, '\n')
    cat('is:', object@cval, '\n')
    cat('\n')
    invisible(object)
  }else if(object@classname=="ur.pp"){
    title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
    row <- paste(rep("#", nchar(title)), collapse="")
    cat("\n")
    cat(row, "\n")
    cat(title, "\n")
    cat(row, "\n")
    cat("\n")
    cat('Test regression', object@model, '\n')
    cat('\n')
    print(object@testreg)
    cat('\n')
    cat('Value of test-statistic, type:', object@type,' is:', round(object@teststat, 4), '\n')
    cat('\n')
    print(object@auxstat)
    cat('\n')
    if(identical(object@type, "Z-tau")){
      cat('Critical values for Z statistics: \n')
      print(object@cval)
      cat('\n')
    }
    invisible(object)
  }else if(object@classname=="ur.df"){
    title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
    row <- paste(rep("#", nchar(title)), collapse="")
    cat("\n")
    cat(row, "\n")
    cat(title, "\n")
    cat(row, "\n")
    cat("\n")
    cat('Test regression', object@model, '\n')
    cat('\n')
    print(object@testreg)
    cat('\n')
    cat('Value of test-statistic is:', round(object@teststat, 4), '\n')
    cat('\n')
    cat('Critical values for test statistics: \n')
    print(object@cval)
    cat('\n')
    invisible(object)
  }else if(object@classname=="ca.po"){
    title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
    row <- paste(rep("#", nchar(title)), collapse="")
    cat("\n")
    cat(row, "\n")
    cat(title, "\n")
    cat(row, "\n")
    cat("\n")
    cat("Test of type", object@type, "\ndetrending of series", object@model, "\n")
    cat("\n")
    print(object@testreg)
    cat('\n')
    cat('Value of test-statistic is:', round(object@teststat, 4), '\n')
    cat('\n')
    cat('Critical values of', object@type, "are:\n")
    print(object@cval)
    cat('\n')
    invisible(object)
    }else if(object@classname=="ur.kpss"){
      title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
      row <- paste(rep("#", nchar(title)), collapse="")
      cat("\n")
      cat(row, "\n")
      cat(title, "\n")
      cat(row, "\n")
      cat("\n")
      cat('Test is of type:', object@type, 'with', object@lag, 'lags. \n')
      cat('\n')
      cat('Value of test-statistic is:', round(object@teststat, 4), '\n')
      cat('\n')
      cat('Critical value for a significance level of: \n')
      print(object@cval)
      cat('\n')
      invisible(object)
    }else if(object@classname=="cajo.test"){
      title <- paste("#", object@test.name, "#", sep=" ")
      row <- paste(rep("#", nchar(title)), collapse="")
      cat("\n")
      cat(row, "\n")
      cat(title, "\n")
      cat(row, "\n")
      cat("\n")
      cat(object@type, "\n")
      cat("\n")
      cat("The VECM has been estimated subject to: \n")
      cat("beta=H*phi and/or alpha=A*psi\n")
      if(!is.null(object@H)){
        cat("\n")
        print(object@H)
        cat("\n")
      }
      if(!is.null(object@A)){
        cat("\n")
        print(object@A)
        cat("\n")
      }
      cat("Eigenvalues of restricted VAR (lambda):\n")
      print(round(object@lambda, 4))
      cat('\n')
      cat("The value of the likelihood ratio test statistic:\n")
      cat(round(object@teststat, 2), "distributed as chi square with", object@pval[2], "df.\n")
      cat("The p-value of the test statistic is:", round(object@pval[1], 2), "\n")
      cat("\n")
      cat("Eigenvectors, normalised to first column\n")
      cat("of the restricted VAR:\n")
      cat("\n")
      print(round(object@V, 4))
      cat("\n")
      cat("Weights W of the restricted VAR:\n")
      cat("\n")
      print(round(object@W, 4))
      cat("\n")
      invisible(object)
    }else if(object@classname=="ca.jo"){
      title <- paste("#", object@test.name, "#", sep=" ")
      row <- paste(rep("#", nchar(title)), collapse="")
      cat("\n")
      cat(row, "\n")
      cat(title, "\n")
      cat(row, "\n")
      cat("\n")
      cat("Test type:", object@type, ",", object@model, "\n")
      cat("\n")
      cat("Eigenvalues (lambda):\n")
      print(object@lambda)
      cat('\n')
      if(!(is.null(object@cval))){
        res1 <- as.matrix(round(object@teststat, 2))
        colnames(res1) <- "test"
        result <- cbind(res1, object@cval)
        cat("Values of teststatistic and critical values of test:\n")
        cat("\n")
        print(result)
        cat("\n")
      }else{
        cat("Values of test statistic\n")
        cat("\n")
        result <- as.matrix(object@teststat)
        rownames(result) <- c(paste("r <= ", (object@P-1):1, " |",sep=""), "r = 0  |")
        print(result)
        cat("\n")
        invisible(object)
      }
      cat("Eigenvectors, normalised to first column:\n")
      cat("(These are the cointegration relations)\n")
      cat("\n")
      print(object@V)
      cat("\n")
      cat("Weights W:\n")
      cat("(This is the loading matrix)\n")
      cat("\n")
      print(object@W)
      cat("\n")
      invisible(object)
    }else if(object@classname=="ur.ers"){
      title <- paste("#", object@test.name, "Unit Root Test #", sep=" ")
      row <- paste(rep("#", nchar(title)), collapse="")
      cat("\n")
      cat(row, "\n")
      cat(title, "\n")
      cat(row, "\n")
      cat("\n")
      cat("Test of type", object@type, "\ndetrending of series", object@model, "\n")
      cat("\n")
      if(!is.null(object@testreg)){
        print(object@testreg)
        cat('\n')
      }
      cat('Value of test-statistic is:', round(object@teststat, 4), '\n')
      cat('\n')
      cat('Critical values of', object@type, "are:\n")
      print(object@cval)
      cat('\n')
      invisible(object)
    }
})

Try the urca package in your browser

Any scripts or data that you put into this service are public.

urca documentation built on Sept. 9, 2022, 3:06 p.m.