Skip to content

Commit

Permalink
Cleaned reconc file and added check on S. Now if S is not 0s and 1s o…
Browse files Browse the repository at this point in the history
…nly we return an error, issue #8.
  • Loading branch information
dazzimonti committed Nov 27, 2023
1 parent ed158a8 commit 94d818e
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 22 deletions.
25 changes: 3 additions & 22 deletions R/reconc.R
Original file line number Diff line number Diff line change
Expand Up @@ -297,28 +297,7 @@ reconc_BUIS <- function(S,
return(out)
}

###############################################################################
.check_cov <- function(cov_matrix) {
# Check if the matrix is square
if (!is.matrix(cov_matrix) || nrow(cov_matrix) != ncol(cov_matrix)) {
stop("base_forecasts.Sigma not square")
}
# Check if the matrix is positive semi-definite
eigen_values <- eigen(cov_matrix, symmetric = TRUE)$values
if (any(eigen_values <= 0)) {
stop("base_forecasts.Sigma not positive semi-definite")
}
# Check if the matrix is symmetric
if (!isSymmetric(cov_matrix)) {
stop("base_forecasts.Sigma not symmetric")
}
# Check if the diagonal elements are non-negative
if (any(diag(cov_matrix) < 0)) {
stop("base_forecasts.Sigma, diagonal elements are non-positive")
}
# If all checks pass, return TRUE
return(TRUE)
}


#' @title Analytical reconciliation of Gaussian base forecasts
#'
Expand Down Expand Up @@ -379,6 +358,8 @@ reconc_BUIS <- function(S,
#' @export
reconc_gaussian <- function(S, base_forecasts.mu,
base_forecasts.Sigma) {
# Check if S contains only 0s and 1s.
.check_S(S)
hier = .get_A_from_S(S)
A = hier$A
k = nrow(A) #number of upper TS
Expand Down
34 changes: 34 additions & 0 deletions R/utils.R
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
.DISTR_SET2 = c("continuous", "discrete")
.check_input <- function(S, base_forecasts, in_type, distr) {

.check_S(S)

if (!(nrow(S) == length(base_forecasts))) {
stop("Input error: nrow(S) != length(base_forecasts)")
}
Expand Down Expand Up @@ -61,6 +63,38 @@
# TODO if distr is a list, check that entries are coherent
}


# Checks if a matrix is a covariance matrix (i.e. symmetric p.d.)
.check_cov <- function(cov_matrix) {
# Check if the matrix is square
if (!is.matrix(cov_matrix) || nrow(cov_matrix) != ncol(cov_matrix)) {
stop("base_forecasts.Sigma not square")
}
# Check if the matrix is positive semi-definite
eigen_values <- eigen(cov_matrix, symmetric = TRUE)$values
if (any(eigen_values <= 0)) {
stop("base_forecasts.Sigma not positive semi-definite")
}
# Check if the matrix is symmetric
if (!isSymmetric(cov_matrix)) {
stop("base_forecasts.Sigma not symmetric")
}
# Check if the diagonal elements are non-negative
if (any(diag(cov_matrix) < 0)) {
stop("base_forecasts.Sigma, diagonal elements are non-positive")
}
# If all checks pass, return TRUE
return(TRUE)
}


# Function to check values allowed in S.
.check_S <- function(S) {
if(!identical(sort(unique(as.vector(S))), c(0,1)) ){
stop("Input error: S must be a matrix containing only 0s and 1s.")
}
}

# Individual check on the parameter distr
.check_distr <- function(in_type, distr, i=NULL) {

Expand Down

0 comments on commit 94d818e

Please sign in to comment.