Commit | Line | Data |
---|---|---|
1b698c16 | 1 | #' EMGrank |
4fed76cc BA |
2 | #' |
3 | #' Description de EMGrank | |
4 | #' | |
c280fe59 BA |
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 | |
10 | #' @param Y Réponse | |
11 | #' @param tau Seuil pour accepter la convergence | |
12 | #' @param rank Vecteur des rangs possibles | |
4fed76cc | 13 | #' |
c280fe59 BA |
14 | #' @return A list ... |
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 | |
4fed76cc | 17 | #' |
4fed76cc | 18 | #' @export |
ffdf9447 | 19 | EMGrank <- function(Pi, Rho, mini, maxi, X, Y, tau, rank, fast = TRUE) |
4fed76cc | 20 | { |
ffdf9447 BA |
21 | if (!fast) |
22 | { | |
23 | # Function in R | |
24 | return(.EMGrank_R(Pi, Rho, mini, maxi, X, Y, tau, rank)) | |
25 | } | |
1b698c16 | 26 | |
ffdf9447 BA |
27 | # Function in C |
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, tau, rank, phi = double(p * m * k), | |
33 | LLF = double(1), n, p, m, k, PACKAGE = "valse") | |
4fed76cc | 34 | } |
aa480ac1 | 35 | |
ffdf9447 BA |
36 | # helper to always have matrices as arg (TODO: put this elsewhere? improve?) --> |
37 | # Yes, we should use by-columns storage everywhere... [later!] | |
aa480ac1 BA |
38 | matricize <- function(X) |
39 | { | |
ffdf9447 BA |
40 | if (!is.matrix(X)) |
41 | return(t(as.matrix(X))) | |
42 | return(X) | |
aa480ac1 BA |
43 | } |
44 | ||
45 | # R version - slow but easy to read | |
ffdf9447 | 46 | .EMGrank_R <- function(Pi, Rho, mini, maxi, X, Y, tau, rank) |
aa480ac1 | 47 | { |
ffdf9447 | 48 | # matrix dimensions |
ea5860f1 BA |
49 | n <- nrow(X) |
50 | p <- ncol(X) | |
51 | m <- ncol(Y) | |
52 | k <- length(Pi) | |
1b698c16 | 53 | |
ffdf9447 BA |
54 | # init outputs |
55 | phi <- array(0, dim = c(p, m, k)) | |
56 | Z <- rep(1, n) | |
57 | LLF <- 0 | |
1b698c16 | 58 | |
ffdf9447 BA |
59 | # local variables |
60 | Phi <- array(0, dim = c(p, m, k)) | |
61 | deltaPhi <- c() | |
62 | sumDeltaPhi <- 0 | |
63 | deltaPhiBufferSize <- 20 | |
64 | ||
65 | # main loop | |
66 | ite <- 1 | |
67 | while (ite <= mini || (ite <= maxi && sumDeltaPhi > tau)) | |
68 | { | |
69 | # M step: update for Beta ( and then phi) | |
70 | for (r in 1:k) | |
71 | { | |
1b698c16 | 72 | Z_indice <- seq_len(n)[Z == r] #indices where Z == r |
ffdf9447 | 73 | if (length(Z_indice) == 0) |
aa480ac1 | 74 | next |
ffdf9447 | 75 | # U,S,V = SVD of (t(Xr)Xr)^{-1} * t(Xr) * Yr |
96b591b7 | 76 | s <- svd(MASS::ginv(crossprod(matricize(X[Z_indice, ]))) %*% |
77 | crossprod(matricize(X[Z_indice, ]), matricize(Y[Z_indice, ]))) | |
ffdf9447 BA |
78 | S <- s$d |
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] | |
aa480ac1 | 84 | } |
1b698c16 | 85 | |
ffdf9447 BA |
86 | # Step E and computation of the loglikelihood |
87 | sumLogLLF2 <- 0 | |
88 | for (i in seq_len(n)) | |
89 | { | |
90 | sumLLF1 <- 0 | |
91 | maxLogGamIR <- -Inf | |
92 | for (r in seq_len(k)) | |
93 | { | |
1b698c16 | 94 | dotProduct <- tcrossprod(Y[i, ] %*% Rho[, , r] - X[i, ] %*% phi[, , r]) |
ea5860f1 | 95 | logGamIR <- log(Pi[r]) + log(gdet(Rho[, , r])) - 0.5 * dotProduct |
ffdf9447 BA |
96 | # Z[i] = index of max (gam[i,]) |
97 | if (logGamIR > maxLogGamIR) | |
98 | { | |
99 | Z[i] <- r | |
100 | maxLogGamIR <- logGamIR | |
101 | } | |
102 | sumLLF1 <- sumLLF1 + exp(logGamIR)/(2 * pi)^(m/2) | |
103 | } | |
104 | sumLogLLF2 <- sumLogLLF2 + log(sumLLF1) | |
105 | } | |
1b698c16 | 106 | |
ffdf9447 | 107 | LLF <- -1/n * sumLogLLF2 |
1b698c16 | 108 | |
ffdf9447 | 109 | # update distance parameter to check algorithm convergence (delta(phi, Phi)) |
1b698c16 | 110 | deltaPhi <- c(deltaPhi, max((abs(phi - Phi))/(1 + abs(phi)))) #TODO: explain? |
ffdf9447 BA |
111 | if (length(deltaPhi) > deltaPhiBufferSize) |
112 | deltaPhi <- deltaPhi[2:length(deltaPhi)] | |
113 | sumDeltaPhi <- sum(abs(deltaPhi)) | |
1b698c16 | 114 | |
ffdf9447 BA |
115 | # update other local variables |
116 | Phi <- phi | |
117 | ite <- ite + 1 | |
aa480ac1 | 118 | } |
ffdf9447 | 119 | return(list(phi = phi, LLF = LLF)) |
aa480ac1 | 120 | } |