3 #' Description de EMGrank
5 #' @param Pi Parametre de proportion
6 #' @param Rho Parametre initial de variance renormalisé
7 #' @param mini Nombre minimal d'itérations dans l'algorithme EM
8 #' @param maxi Nombre maximal d'itérations dans l'algorithme EM
9 #' @param X Régresseurs
11 #' @param eps Seuil pour accepter la convergence
12 #' @param rank Vecteur des rangs possibles
15 #' phi : parametre de moyenne renormalisé, calculé par l'EM
16 #' LLF : log vraisemblance associé à cet échantillon, pour les valeurs estimées des paramètres
19 EMGrank <- function(Pi, Rho, mini, maxi, X, Y, eps, rank, fast = TRUE)
24 return(.EMGrank_R(Pi, Rho, mini, maxi, X, Y, eps, rank))
28 n <- nrow(X) #nombre d'echantillons
29 p <- ncol(X) #nombre de covariables
30 m <- ncol(Y) #taille de Y (multivarié)
31 k <- length(Pi) #nombre de composantes dans le mélange
32 .Call("EMGrank", Pi, Rho, mini, maxi, X, Y, eps, as.integer(rank), phi = double(p * m * k),
33 LLF = double(1), n, p, m, k, PACKAGE = "valse")
36 # helper to always have matrices as arg (TODO: put this elsewhere? improve?) -->
37 # Yes, we should use by-columns storage everywhere... [later!]
38 matricize <- function(X)
41 return(t(as.matrix(X)))
45 # R version - slow but easy to read
46 .EMGrank_R <- function(Pi, Rho, mini, maxi, X, Y, eps, rank)
55 phi <- array(0, dim = c(p, m, k))
60 Phi <- array(0, dim = c(p, m, k))
63 deltaPhiBufferSize <- 20
67 while (ite <= mini || (ite <= maxi && sumDeltaPhi > eps))
69 # M step: update for Beta ( and then phi)
72 Z_indice <- seq_len(n)[Z == r] #indices where Z == r
73 if (length(Z_indice) == 0)
75 # U,S,V = SVD of (t(Xr)Xr)^{-1} * t(Xr) * Yr
76 s <- svd(MASS::ginv(crossprod(matricize(X[Z_indice, ]))) %*%
77 crossprod(matricize(X[Z_indice, ]), matricize(Y[Z_indice, ])))
79 # Set m-rank(r) singular values to zero, and recompose best rank(r) approximation
80 # of the initial product
81 if (rank[r] < length(S))
82 S[(rank[r] + 1):length(S)] <- 0
83 phi[, , r] <- s$u %*% diag(S) %*% t(s$v) %*% Rho[, , r]
86 # Step E and computation of the loglikelihood
94 dotProduct <- tcrossprod(Y[i, ] %*% Rho[, , r] - X[i, ] %*% phi[, , r])
95 logGamIR <- log(Pi[r]) + log(gdet(Rho[, , r])) - 0.5 * dotProduct
96 # Z[i] = index of max (gam[i,])
97 if (logGamIR > maxLogGamIR)
100 maxLogGamIR <- logGamIR
102 sumLLF1 <- sumLLF1 + exp(logGamIR)/(2 * pi)^(m/2)
104 sumLogLLF2 <- sumLogLLF2 + log(sumLLF1)
107 LLF <- -1/n * sumLogLLF2
109 # update distance parameter to check algorithm convergence (delta(phi, Phi))
110 deltaPhi <- c(deltaPhi, max((abs(phi - Phi))/(1 + abs(phi)))) #TODO: explain?
111 if (length(deltaPhi) > deltaPhiBufferSize)
112 deltaPhi <- deltaPhi[2:length(deltaPhi)]
113 sumDeltaPhi <- sum(abs(deltaPhi))
115 # update other local variables
119 return(list(phi = phi, LLF = LLF))