Skip to content

Commit

Permalink
Merge pull request #60 from palatej/develop
Browse files Browse the repository at this point in the history
Improvement of CanovaHansen tests
  • Loading branch information
palatej committed Aug 9, 2024
2 parents 4955a22 + 8a940e0 commit 1d60277
Show file tree
Hide file tree
Showing 13 changed files with 145 additions and 27 deletions.
3 changes: 2 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -247,6 +247,7 @@ export(sarima_model)
export(sarima_properties)
export(sarima_random)
export(seasonality_canovahansen)
export(seasonality_canovahansen_trigs)
export(seasonality_combined)
export(seasonality_f)
export(seasonality_friedman)
Expand All @@ -270,7 +271,7 @@ export(statisticaltest)
export(stock_td)
export(tc_variable)
export(td)
export(td_ch)
export(td_canovahansen)
export(td_f)
export(testofruns)
export(testofupdownruns)
Expand Down
6 changes: 6 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,12 @@ to [Semantic Versioning](https://semver.org/spec/v3.2.3.html).

## [Unreleased]

### Changed

* New JARS
* Improve Canova-Hansen tests for seasonality and trading days (new options, more output)
* Document (UC)ARIMA models

## [3.2.4] - 2024-07-12


Expand Down
2 changes: 1 addition & 1 deletion R/arima.R
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ sarima_random<-function(model, length, stde=1, tdegree=0, seed=-1){
#' @param rmod trend threshold.
#' @param epsphi seasonal tolerance (in degrees).
#'
#' @return
#' @return An UCARIMA model
#' @export
#'
#' @examples
Expand Down
56 changes: 48 additions & 8 deletions R/tests_seasonality.R
Original file line number Diff line number Diff line change
Expand Up @@ -133,19 +133,59 @@ seasonality_combined<-function(data, period, firstperiod=cycle(data)[1], mul=TRU
evolutive=.p2r_anova(p$evolutive_seasonality)))
}

#' Seasonal Canova-Hansen test
#' Canova-Hansen test using trigonometric variables
#'
#' @inheritParams seasonality_qs
#' @param p0 Initial periodicity (included).
#' @param p1 Final periodicity (included).
#' @param np Number of periodicities equally spaced in \eqn{[p_0,p_1]}.
#' @param periods Periodicities.
#' @param lag1 Lagged variable in the regression model.
#' @param kernel Kernel used to compute the robust covariance matrix.
#' @param order The truncation parameter used to compute the robust covariance matrix.
#' @param original `TRUE` for original algorithm, `FALSE` for solution proposed by T. Proietti (based on Ox code).
#'
#' @export
#'
#' @examples
seasonality_canovahansen<-function(data, p0, p1, np, original=FALSE){
jtest<-.jcall("jdplus/sa/base/r/SeasonalityTests", "[D", "canovaHansenTest",
as.numeric(data), as.numeric(p0), as.numeric(p1), as.integer(np), as.logical(original))
return(jtest)
#' s<-log(ABS$X0.2.20.10.M)
#' freqs<-seq(0.01, 0.5, 0.001)
#' plot(seasonality_canovahansen_trigs(s, 1/freqs, original = FALSE), type='l')
seasonality_canovahansen_trigs<-function(data, periods, lag1=TRUE,
kernel=c("Bartlett", "Square", "Welch", "Tukey", "Hamming", "Parzen"),
order=NA, original=FALSE){

kernel<-match.arg(kernel)
if (is.na(order)) order<--1

jtest<-.jcall("jdplus/sa/base/r/SeasonalityTests", "[D", "canovaHansenTrigs",
as.numeric(data), .jarray(periods),
as.logical(lag1), kernel, as.integer(order), as.logical(original))
return(jtest)
}

#' Canova-Hansen seasonality test
#'
#' @inheritParams seasonality_qs
#' @param trigs TRUE for trigonometric variables, FALSE for seasonal dummies.
#' @param lag1 Lagged variable in the regression model.
#' @param kernel Kernel used to compute the robust covariance matrix.
#' @param order The truncation parameter used to compute the robust covariance matrix.
#' @param start Position of the first observation of the series
#' @return list with the joint test and with details for the different seasonal variables
#' @export
#'
#' @examples
#' s<-log(ABS$X0.2.20.10.M)
#' seasonality_canovahansen(s, 12, trigs = FALSE)
#' seasonality_canovahansen(s, 12, trigs = TRUE)
seasonality_canovahansen<-function(data, period, trigs=TRUE, lag1=TRUE,
kernel=c("Bartlett", "Square", "Welch", "Tukey", "Hamming", "Parzen"),
order=NA, start=1){
kernel<-match.arg(kernel)
if (is.na(order)) order<--1

q<-.jcall("jdplus/sa/base/r/SeasonalityTests", "[D", "canovaHansen",
as.numeric(data), as.integer(period),
as.logical(trigs), as.logical(lag1),
kernel, as.integer(order), as.integer(start-1))
last<-length(q)
return(list(joint=q[last], details=q[-last]))
}
24 changes: 17 additions & 7 deletions R/tests_td.R
Original file line number Diff line number Diff line change
Expand Up @@ -54,17 +54,27 @@ td_f<-function(s, model=c("D1", "DY", "DYD1", "WN", "AIRLINE", "R011", "R100"),
return(.jd2r_test(jtest))
}

#' Canova-Hansen Trading Days test
#' Canova-Hansen test for stable trading days
#'
#' @inheritParams td_f
#' @param differencing differencing lags.
#' @param differencing Differencing lags.
#' @param kernel Kernel used to compute the robust covariance matrix.
#' @param order The truncation parameter used to compute the robust covariance matrix.
#'
#' @return
#' @return list with the joint test and with details for the different days (starting with Mondays).
#' @export
#'
#' @examples
td_ch<-function(s, differencing){
jts<-.r2jd_tsdata(s)
return(.jcall("jdplus/toolkit/base/r/modelling/TradingDaysTests", "[D", "chTest",
jts, .jarray(as.integer(differencing))))
#' s<-log(ABS$X0.2.20.10.M)
#' td_canovahansen(s, c(1,12))
td_canovahansen<-function(s, differencing, kernel=c("Bartlett", "Square", "Welch", "Tukey", "Hamming", "Parzen"),
order=NA){
kernel<-match.arg(kernel)
if (is.na(order)) order<--1
jts<-.r2jd_tsdata(s)
q<-.jcall("jdplus/toolkit/base/r/modelling/TradingDaysTests", "[D", "canovaHansen",
jts, .jarray(as.integer(differencing)), kernel, as.integer(order))

last<-length(q)
return(list(joint=q[last], details=q[-last]))
}
Binary file not shown.
Binary file not shown.
Binary file not shown.
Binary file not shown.
3 changes: 3 additions & 0 deletions man/sarima_decompose.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

31 changes: 24 additions & 7 deletions man/seasonality_canovahansen.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

30 changes: 30 additions & 0 deletions man/seasonality_canovahansen_trigs.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

17 changes: 14 additions & 3 deletions man/td_ch.Rd → man/td_canovahansen.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 1d60277

Please sign in to comment.