Skip to content

Commit

Permalink
Handle numerical issues in SNMoE
Browse files Browse the repository at this point in the history
- SNMoE: Handle numerical issues when calculating the two conditional expectations 'E1ik' and 'E2ik' in StatSNMoE class;
- CITATION: Update citations;
- logsumexp.R: Correct a typo;
- IRLS.cpp: Correct a typo.
  • Loading branch information
Florian-Lecocq committed Sep 17, 2019
1 parent 07c449c commit e28b952
Show file tree
Hide file tree
Showing 12 changed files with 109 additions and 84 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,8 @@ exportClasses(StatNMoE)
exportClasses(StatSNMoE)
exportClasses(StatStMoE)
exportClasses(StatTMoE)
import(MASS)
import(methods)
import(pracma)
importFrom(Rcpp,sourceCpp)
useDynLib(meteorits, .registration = TRUE)
5 changes: 4 additions & 1 deletion R/ParamSNMoE.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
#' \eqn{(1, K)}).
#' @field lambda The skewness parameters for each experts (matrix of size
#' \eqn{(1, K)}).
#' @field delta delta is equal \eqn{\delta =
#' @field delta delta is equal to \eqn{\delta =
#' \frac{\lambda}{\sqrt{1+\lambda^2}}}{\delta = \lambda /
#' (1+\lambda^2)^(1/2)}.
#' @field df The degree of freedom of the SNMoE model representing the
Expand Down Expand Up @@ -123,6 +123,7 @@ ParamSNMoE <- setRefClass(
Z <- matrix(0, nrow = n, ncol = K)
Z[klas %*% ones(1, K) == ones(n, 1) %*% seq(K)] <- 1
tau <- Z

res <- IRLS(phiAlpha$XBeta, tau, ones(nrow(tau), 1), alpha)
alpha <<- res$W

Expand All @@ -147,6 +148,7 @@ ParamSNMoE <- setRefClass(
\\code{statSNMoE} of class \\link{StatSNMoE} (which contains the E-step)."

res_irls <- IRLS(phiAlpha$XBeta, statSNMoE$tik, ones(nrow(statSNMoE$tik), 1), alpha, verbose_IRLS)

statSNMoE$piik <- res_irls$piik
reg_irls <- res_irls$reg_irls

Expand All @@ -156,6 +158,7 @@ ParamSNMoE <- setRefClass(

# Update the regression coefficients
tauik_Xbeta <- (statSNMoE$tik[, k] %*% ones(1, p + 1)) * phiBeta$XBeta

beta[, k] <<- solve((t(tauik_Xbeta) %*% phiBeta$XBeta)) %*% (t(tauik_Xbeta) %*% (Y - delta[k] * statSNMoE$E1ik[, k]))

# Update the variances sigma2k
Expand Down
2 changes: 1 addition & 1 deletion R/ParamStMoE.R
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@
#' \eqn{(1, K)}).
#' @field lambda The skewness parameters for each experts (matrix of size
#' \eqn{(1, K)}).
#' @field delta delta is equal \eqn{\delta =
#' @field delta delta is equal to \eqn{\delta =
#' \frac{\lambda}{\sqrt{1+\lambda^2}}}{\delta = \lambda /
#' (1+\lambda^2)^(1/2)}.
#' @field nu The degree of freedom for the Student distribution for each
Expand Down
8 changes: 7 additions & 1 deletion R/StatSNMoE.R
Original file line number Diff line number Diff line change
Expand Up @@ -166,9 +166,13 @@ StatSNMoE <- setRefClass(

# E1ik = E[Ui|yi,xi,zik=1]
E1ik[, k] <<- mu_uk + sigma_uk * dnorm(paramSNMoE$lambda[k] * dik, 0, 1) / pnorm(paramSNMoE$lambda[k] * dik, 0, 1)
E1ik[is.nan(E1ik[, k]), k] <<- mu_uk[is.nan(E1ik[, k])] - sigma_uk * paramSNMoE$lambda[k] * dik[is.nan(E1ik[, k])]
E1ik[is.infinite(E1ik[, k]), k] <<- mu_uk[is.infinite(E1ik[, k])] - sigma_uk * paramSNMoE$lambda[k] * dik[is.infinite(E1ik[, k])]

# E2ik = E[Ui^2|y,zik=1]
E2ik[, k] <<- mu_uk ^ 2 + sigma_uk ^ 2 + sigma_uk * mu_uk * dnorm(paramSNMoE$lambda[k] * dik, 0, 1) / pnorm(paramSNMoE$lambda[k] * dik, 0, 1)
E2ik[is.nan(E2ik[, k]), k] <<- mu_uk[is.nan(E2ik[, k])] ^ 2 + sigma_uk ^ 2 - sigma_uk * mu_uk[is.nan(E2ik[, k])] * paramSNMoE$lambda[k] * dik[is.nan(E2ik[, k])]
E2ik[is.infinite(E2ik[, k]), k] <<- mu_uk[is.infinite(E2ik[, k])] ^ 2 + sigma_uk ^ 2 - sigma_uk * mu_uk[is.infinite(E2ik[, k])] * paramSNMoE$lambda[k] * dik[is.infinite(E2ik[, k])]

# weighted skew normal linear expert likelihood
piik_fik[, k] <- piik[, k] * (2 / sigmak) * dnorm(dik, 0, 1) * pnorm(paramSNMoE$lambda[k] * dik)
Expand All @@ -179,7 +183,9 @@ StatSNMoE <- setRefClass(
log_sum_piik_fik <<- matrix(log(rowSums(piik_fik)))

# E[Zik|y,x] and E[U^2|y,zik=1]
tik <<- piik_fik / (rowSums(piik_fik) %*% ones(1, paramSNMoE$K))
# tik <<- piik_fik / (rowSums(piik_fik) %*% ones(1, paramSNMoE$K))
log_Tauik <- log_piik_fik - logsumexp(log_piik_fik, 1) %*% ones(1, paramSNMoE$K)
tik <<- exp(log_Tauik)
}
)
)
2 changes: 1 addition & 1 deletion R/logsumexp.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ logsumexp <- function(A, margin) {
A <- xstar + log(apply(exp(M), 1, sum))
} else{
xstar <- apply(A, 2, max)
M <- M - matrix(1, nrow = row(M), ncol = 1) %*% xstar
M <- M - matrix(1, nrow = nrow(M), ncol = 1) %*% xstar
A <- xstar + log(apply(exp(M), 2, sum))
}
return(A)
Expand Down
24 changes: 13 additions & 11 deletions R/meteorits-package.R
Original file line number Diff line number Diff line change
Expand Up @@ -10,17 +10,17 @@
#' `meteorits` contains the following Mixture-of-Experts models:
#'
#' \itemize{
#' \item NMoE provides a flexible framework for heterogenous data with
#' Normal expert regressors network;
#' \item SNMoE provides a flexible modeling framework for heterogenous
#' data with possibly skewed distributions to generalize the standard Normal
#' mixture of expert model;
#' \item TMoE provides a flexible and robust modeling framework for
#' heterogenous data with possibly heavy-tailed distributions and corrupted by
#' atypical observations;
#' \item StMoE provides a flexible and robust modeling framework for
#' heterogenous data with possibly skewed, heavy-tailed distributions and
#' corrupted by atypical observations.
#' \item NMoE (Normal Mixtures-of-Experts) provides a flexible framework for
#' heterogenous data with Normal expert regressors network;
#' \item SNMoE (Skew-Normal Mixtures-of-Experts) provides a flexible
#' modeling framework for heterogenous data with possibly skewed
#' distributions to generalize the standard Normal mixture of expert model;
#' \item tMoE (t Mixtures-of-Experts) provides a flexible and robust
#' modeling framework for heterogenous data with possibly heavy-tailed
#' distributions and corrupted by atypical observations;
#' \item StMoE (Skew t Mixtures-of-Experts) provides a flexible and robust
#' modeling framework for heterogenous data with possibly skewed,
#' heavy-tailed distributions and corrupted by atypical observations.
#' }
#'
#' For the advantages/differences of each of them, the user is referred to our
Expand All @@ -46,6 +46,8 @@
#' Chamroukhi, F., A. Same, G. Govaert, and P. Aknin. 2009. \emph{Time Series Modeling by a Regression Approach Based on a Latent Process.} Neural Networks 22 (5-6): 593--602. \url{https://chamroukhi.com/papers/Chamroukhi_Neural_Networks_2009.pdf}.
#'
#' @import methods
#' @import pracma
#' @import MASS
## usethis namespace: start
#' @useDynLib meteorits, .registration = TRUE
## usethis namespace: end
Expand Down
122 changes: 67 additions & 55 deletions inst/CITATION
Original file line number Diff line number Diff line change
@@ -1,4 +1,7 @@
citHeader("To cite meteorits in publications use:")
citHeader("To cite the package meteorits in a publication please use the
following reference. To cite the corresponding paper for a specific package
from meteorits (e.g NMoE, SNMoE, tMoE, StMoE, etc), please choose the
reference(s) from the list provided below.")

note <- sprintf("R package version %s", meta$Version)

Expand All @@ -7,69 +10,76 @@ citEntry(
title = "meteorits: Mixtures-of-Experts Modeling for Complex and Non-Normal Distributions
('MEteorits')",
author = personList(person(given="F.", family="Chamroukhi"),
person(given="M.", family="Bartcus"),
person(given="F.", family="Lecocq")),
person(given="F.", family="Lecocq"),
person(given="M.", family="Bartcus")),
year = "2019",
note = note,
url = "https://github.com/fchamroukhi/MEteorits",
textVersion = paste0("Faicel Chamroukhi, Marius Bartcus and Florian Lecocq (2019).
textVersion = paste0("Faicel Chamroukhi, Florian Lecocq and Marius Bartcus (2019).
meteorits: Mixtures-of-Experts Modeling for Complex and Non-Normal Distributions
('MEteorits'). ", note, ". https://github.com/fchamroukhi/MEteorits")
)

citEntry(
entry = "Article",
entry = "Article",
author = personList(person(given="B-T.", family="Huynh"),
person(given="F.", family="Chamroukhi")),
journal = "Journal de la Societe Francaise de Statistique",
title = "Estimation and Feature Selection in Mixtures of Generalized Linear Experts Models.",
journal = "Journal de la Soci\\'{e}t\\'{e} Fran\\c{c}aise de Statistique",
title = "Estimation and Feature Selection in Mixtures of Generalized Linear Experts Models",
year = "2019",
url = "https://chamroukhi.com/papers/Chamroukhi_Huynh_jsfds-published.pdf",
textVersion = "B-T. Huynh and F. Chamroukhi (2019). \u201cEstimation and Feature Selection in Mixtures of Generalized Linear Experts Models.\u201d Journal de la Societe Francaise de Statistique. <URL: https://chamroukhi.com/papers/Chamroukhi_Huynh_jsfds-published.pdf."
url = "https://chamroukhi.com/papers/Chamroukhi_Huynh_jsfds-published.pdf",
textVersion = "Huynh B, Chamroukhi F (2019). \u201cEstimation and Feature Selection
in Mixtures of Generalized Linear Experts Models.\u201d Journal de la
Soci\u00e9t\u00e9 Fran\u00e7aise de Statistique.
<URL: https://chamroukhi.com/papers/Chamroukhi_Huynh_jsfds-published.pdf>."
)

citEntry(
entry = "Article",
title = "Regularized Maximum Likelihood Estimation and Feature Selection in Mixtures-of-Experts Models.",
entry = "Article",
title = "Regularized Maximum Likelihood Estimation and Feature Selection in Mixtures-of-Experts Models",
author = personList(person(given="F.", family="Chamroukhi"),
person(given="Bao T.", family="Huynh")),
journal = "Journal de la Soci\u00e9t\u00e9 Fran\u00e7aise de Statistique",
volume = "160(1)",
journal = "Journal de la Soci\\'{e}t\\'{e} Fran\\c{c}aise de Statistique",
volume = "160",
number = "1",
pages = "57--85",
year = "2019",
textVersion = "F. Chamroukhi and Bao T. Huynh (2019). \u201cRegularized Maximum Likelihood Estimation and Feature Selection in Mixtures-of-Experts Models.\u201d Journal de la Soci\u00e9t\u00e9 Fran\u00e7aise de Statistique, vol. 160(1), pp. 57--85"
textVersion = "Chamroukhi F, Huynh B (2019). \u201cRegularized Maximum
Likelihood Estimation and Feature Selection in Mixtures-of-Experts
Models.\u201d Journal de la Soci\u00e9t\u00e9 Fran\u00e7aise de Statistique,
*160(1)*, 57-85."
)

citEntry(
entry = "Article",
title = "Practical and theoretical aspects of mixture-of-experts modeling: An overview",
entry = "Article",
title = "Practical and theoretical aspects of mixture-of-experts modeling: An overview",
author = personList(person(given="Hien D.", family="Nguyen"),
person(given="F.", family="Chamroukhi")),
journal = "Wiley Interdisciplinary Reviews: Data Mining and Knowledge Discovery",
journal = "Wiley Interdisciplinary Reviews: Data Mining and Knowledge Discovery",
publisher = "Wiley Periodicals, Inc",
year = "2018",
year = "2018",
pages = "e1246--n/a",
doi = "10.1002/widm.1246",
url = "https://chamroukhi.com/papers/Nguyen-Chamroukhi-MoE-DMKD-2018",
textVersion = "Nguyen H and Chamroukhi F (2018). \u201cPractical and theoretical aspects
of mixture-of-experts modeling: An overview.\u201d Wiley Interdisciplinary Reviews:
Data Mining and Knowledge Discovery, pp. e1246-n/a.
doi: 10.1002/widm.1246 (URL:https://doi.org/10.1002/widm.1246),
url = "https://chamroukhi.com/papers/Nguyen-Chamroukhi-MoE-DMKD-2018",
textVersion = "Nguyen H, Chamroukhi F (2018). \u201cPractical and theoretical
aspects of mixture-of-experts modeling: An overview.\u201d Wiley
Interdisciplinary Reviews: Data Mining and Knowledge Discovery, e1246-n/a.
doi: 10.1002/widm.1246 (URL: http://doi.org/10.1002/widm.1246),
<URL: https://chamroukhi.com/papers/Nguyen-Chamroukhi-MoE-DMKD-2018>."
)

citEntry(
entry = "Article",
title = "Skew t mixture of experts",
author = personList(person(given="F.", family="Chamroukhi")),
journal = "Neurocomputing - Elsevier",
year = "2017",
volume = "266",
pages = "390--408",
url = "https://chamroukhi.com/papers/STMoE.pdf",
entry = "Article",
title = "Skew t mixture of experts",
author = personList(person(given="F.", family="Chamroukhi")),
journal = "Neurocomputing - Elsevier",
year = "2017",
volume = "266",
pages = "390--408",
url = "https://chamroukhi.com/papers/STMoE.pdf",
textVersion = "Chamroukhi F (2017). \u201cSkew t mixture of experts.\u201d
Neurocomputing - Elsevier,
266, pp. 390-408. <URL:https://chamroukhi.com/papers/STMoE.pdf>."
Neurocomputing - Elsevier, *266*, 390-408.
<URL: https://chamroukhi.com/papers/STMoE.pdf>."
)

citEntry(
Expand All @@ -81,60 +91,62 @@ citEntry(
volume = "79",
pages = "20--36",
url = "https://chamroukhi.com/papers/TMoE.pdf",
textVersion = "Chamroukhi F (2016). \u201cRobust mixture of experts modeling using the
t-distribution.\u201d Neural Networks - Elsevier, 79, pp. 20-36.
textVersion = "Chamroukhi F (2016). \u201cRobust mixture of experts modeling
using the t-distribution.\u201d Neural Networks - Elsevier, *79*, 20-36.
<URL: https://chamroukhi.com/papers/TMoE.pdf>."
)

citEntry(
entry = "InProceedings",
title = "Skew-Normal Mixture of Experts",
entry = "InProceedings",
title = "Skew-Normal Mixture of Experts",
author = personList(person(given="F.", family="Chamroukhi")),
booktitle = "The International Joint Conference on Neural Networks (IJCNN)",
year = "2016",
url = "https://chamroukhi.com/papers/Chamroukhi-SNMoE-IJCNN2016.pdf",
textVersion = "Chamroukhi F (2016). \u201cSkew-Normal Mixture of Experts.\u201d In
The International Joint Conference on Neural Networks (IJCNN).
<URL:https://chamroukhi.com/papers/Chamroukhi-SNMoE-IJCNN2016.pdf>."
booktitle = "The International Joint Conference on Neural Networks (IJCNN)",
year = "2016",
url = "https://chamroukhi.com/papers/Chamroukhi-SNMoE-IJCNN2016.pdf",
textVersion = "Chamroukhi F (2016). \u201cSkew-Normal Mixture of
Experts.\u201d In The International Joint Conference on Neural Networks (IJCNN).
<URL: https://chamroukhi.com/papers/Chamroukhi-SNMoE-IJCNN2016.pdf>."
)

citEntry(
entry = "PhdThesis",
title = "Statistical learning of latent data models for complex data analysis",
author = person(given="F.", family="Chamroukhi"),
school = "Universit\u00e9 de Toulon",
school = "Universit\\'{e} de Toulon",
year = "2015",
type = "Habilitation Thesis (HDR)",
url = "https://chamroukhi.com/Dossier/FChamroukhi-Habilitation.pdf",
textVersion = "Chamroukhi F (2015). Statistical learning of latent data models for
complex data analysis. Habilitation Thesis (HDR), Universit\u00e9 de Toulon.
textVersion = "Chamroukhi F (2015). Statistical learning of latent data models
for complex data analysis. PhD thesis, Universit\u00e9 de Toulon.
<URL: https://chamroukhi.com/Dossier/FChamroukhi-Habilitation.pdf>."
)

citEntry(
entry = "PhdThesis",
title = "Hidden process regression for curve modeling, classification and tracking",
author = person(given="F.", family="Chamroukhi"),
school = "Universit\'{e} de Technologie de Compi\`{e}gne",
school = "Universit\\'{e} de Technologie de Compi\\`{e}gne",
year = "2010",
type = "Ph.D. Thesis",
url = "https://chamroukhi.com/papers/FChamroukhi-Thesis.pdf",
textVersion = "Chamroukhi F (2010). \u201cHidden process regression for curve
modeling, classification and tracking\u201d. Ph.D. Thesis, Universit\u00e9 de
Technologie de Compi\u00e8gne.
<URL: https://chamroukhi.com/papers/FChamroukhi-Thesis.pdf>."
textVersion = "Chamroukhi F (2010). Hidden process regression for curve
modeling, classification and tracking. PhD thesis, Universit\u00e9 de Technologie
de Compi\u00e8gne. <URL: https://chamroukhi.com/papers/FChamroukhi-Thesis.pdf>."
)

citEntry(
entry = "Article",
title = "Time series modeling by a regression approach based on a latent process.",
title = "Time series modeling by a regression approach based on a latent process",
author = personList(person(given="F.", family="Chamroukhi"),
person(given="A.", family="Sam\u00e9"),
person(given="A.", family="Sam\\'{e}"),
person(given="G.", family="Govaert"),
person(given="P.", family="Aknin")),
journal = "Neural Networks Elsevier Science Ltd.",
year = "2009",
volume = "22(5-6)",
volume = "22",
number = "5-6",
pages = "593--602",
textVersion = "F. Chamroukhi and A. Sam\u00e9 and G. Govaert and P. Aknin (2009). \u201cTime series modeling by a regression approach based on a latent process.\u201d Neural Networks Elsevier Science Ltd., vol. 22(5-6), pp. 593--602."
textVersion = "Chamroukhi F, Sam\u00e9 A, Govaert G, Aknin P (2009). \u201cTime
series modeling by a regression approach based on a latent process.\u201d
Neural Networks Elsevier Science Ltd., *22(5-6)*, 593-602."
)
2 changes: 1 addition & 1 deletion man/ParamSNMoE-class.Rd

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

2 changes: 1 addition & 1 deletion man/ParamStMoE-class.Rd

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

22 changes: 11 additions & 11 deletions man/meteorits-package.Rd

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

Binary file modified meteorits_0.1.0.pdf
Binary file not shown.
2 changes: 1 addition & 1 deletion src/IRLS.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -250,7 +250,7 @@ List IRLS(arma::mat& X, arma::mat& Tau, arma::mat& Gamma, arma::mat& Winit, bool
}
} else {
Rcout << "\n";
Rcout << "IRLS : doesn't converged (increase the number of iterations > " + std::to_string(iter) + ")\n";
Rcout << "IRLS : did not converge (increase the number of iterations > " + std::to_string(max_iter) + ")\n";
}

double reg_irls = 0;
Expand Down

0 comments on commit e28b952

Please sign in to comment.