fix few things
[valse.git] / pkg / R / EMGLLF.R
CommitLineData
ffdf9447 1#' EMGLLF
4fed76cc
BA
2#'
3#' Description de EMGLLF
4#'
43d76c49 5#' @param phiInit an initialization for phi
6#' @param rhoInit an initialization for rho
7#' @param piInit an initialization for pi
8#' @param gamInit initialization for the a posteriori probabilities
9#' @param mini integer, minimum number of iterations in the EM algorithm, by default = 10
10#' @param maxi integer, maximum number of iterations in the EM algorithm, by default = 100
11#' @param gamma integer for the power in the penaly, by default = 1
12#' @param lambda regularization parameter in the Lasso estimation
13#' @param X matrix of covariates (of size n*p)
14#' @param Y matrix of responses (of size n*m)
15#' @param eps real, threshold to say the EM algorithm converges, by default = 1e-4
4fed76cc 16#'
c280fe59
BA
17#' @return A list ... phi,rho,pi,LLF,S,affec:
18#' phi : parametre de moyenne renormalisé, calculé par l'EM
19#' rho : parametre de variance renormalisé, calculé par l'EM
20#' pi : parametre des proportions renormalisé, calculé par l'EM
21#' LLF : log vraisemblance associée à cet échantillon, pour les valeurs estimées des paramètres
22#' S : ... affec : ...
4fed76cc 23#'
4fed76cc 24#' @export
ffdf9447
BA
25EMGLLF <- function(phiInit, rhoInit, piInit, gamInit, mini, maxi, gamma, lambda,
26 X, Y, eps, fast = TRUE)
1b698c16 27{
fb6e49cb 28 if (!fast)
29 {
30 # Function in R
ffdf9447
BA
31 return(.EMGLLF_R(phiInit, rhoInit, piInit, gamInit, mini, maxi, gamma, lambda,
32 X, Y, eps))
fb6e49cb 33 }
1b698c16 34
fb6e49cb 35 # Function in C
ffdf9447
BA
36 n <- nrow(X) #nombre d'echantillons
37 p <- ncol(X) #nombre de covariables
38 m <- ncol(Y) #taille de Y (multivarié)
39 k <- length(piInit) #nombre de composantes dans le mélange
40 .Call("EMGLLF", phiInit, rhoInit, piInit, gamInit, mini, maxi, gamma, lambda,
41 X, Y, eps, phi = double(p * m * k), rho = double(m * m * k), pi = double(k),
42 LLF = double(maxi), S = double(p * m * k), affec = integer(n), n, p, m, k,
43 PACKAGE = "valse")
4fed76cc 44}
aa480ac1
BA
45
46# R version - slow but easy to read
ffdf9447 47.EMGLLF_R <- function(phiInit, rhoInit, piInit, gamInit, mini, maxi, gamma, lambda,
c8baa022 48 X, Y, eps)
1b698c16 49{
c8baa022 50 # Matrix dimensions: NOTE: phiInit *must* be an array (even if p==1)
ffdf9447 51 n <- dim(Y)[1]
c8baa022
BA
52 p <- dim(phiInit)[1]
53 m <- dim(phiInit)[2]
54 k <- dim(phiInit)[3]
1b698c16 55
fb6e49cb 56 # Outputs
ffdf9447
BA
57 phi <- array(NA, dim = c(p, m, k))
58 phi[1:p, , ] <- phiInit
59 rho <- rhoInit
60 pi <- piInit
61 llh <- -Inf
62 S <- array(0, dim = c(p, m, k))
1b698c16 63
fb6e49cb 64 # Algorithm variables
ffdf9447
BA
65 gam <- gamInit
66 Gram2 <- array(0, dim = c(p, p, k))
67 ps2 <- array(0, dim = c(p, m, k))
68 X2 <- array(0, dim = c(n, p, k))
69 Y2 <- array(0, dim = c(n, m, k))
70 EPS <- 1e-15
1b698c16 71
fb6e49cb 72 for (ite in 1:maxi)
73 {
74 # Remember last pi,rho,phi values for exit condition in the end of loop
ffdf9447
BA
75 Phi <- phi
76 Rho <- rho
77 Pi <- pi
1b698c16 78
fb6e49cb 79 # Computations associated to X and Y
80 for (r in 1:k)
81 {
1b698c16
BA
82 for (mm in 1:m)
83 Y2[, mm, r] <- sqrt(gam[, r]) * Y[, mm]
84 for (i in 1:n)
85 X2[i, , r] <- sqrt(gam[i, r]) * X[i, ]
86 for (mm in 1:m)
87 ps2[, mm, r] <- crossprod(X2[, , r], Y2[, mm, r])
fb6e49cb 88 for (j in 1:p)
89 {
1b698c16
BA
90 for (s in 1:p)
91 Gram2[j, s, r] <- crossprod(X2[, j, r], X2[, s, r])
fb6e49cb 92 }
93 }
1b698c16
BA
94
95 ## M step
96
fb6e49cb 97 # For pi
ffdf9447
BA
98 b <- sapply(1:k, function(r) sum(abs(phi[, , r])))
99 gam2 <- colSums(gam)
100 a <- sum(gam %*% log(pi))
1b698c16 101
fb6e49cb 102 # While the proportions are nonpositive
ffdf9447
BA
103 kk <- 0
104 pi2AllPositive <- FALSE
fb6e49cb 105 while (!pi2AllPositive)
106 {
ffdf9447
BA
107 pi2 <- pi + 0.1^kk * ((1/n) * gam2 - pi)
108 pi2AllPositive <- all(pi2 >= 0)
109 kk <- kk + 1
fb6e49cb 110 }
1b698c16 111
fb6e49cb 112 # t(m) is the largest value in the grid O.1^k such that it is nonincreasing
1b698c16
BA
113 while (kk < 1000 && -a/n + lambda * sum(pi^gamma * b) <
114 -sum(gam2 * log(pi2))/n + lambda * sum(pi2^gamma * b))
115 {
ffdf9447
BA
116 pi2 <- pi + 0.1^kk * (1/n * gam2 - pi)
117 kk <- kk + 1
fb6e49cb 118 }
ffdf9447
BA
119 t <- 0.1^kk
120 pi <- (pi + t * (pi2 - pi))/sum(pi + t * (pi2 - pi))
1b698c16 121
ffdf9447 122 # For phi and rho
fb6e49cb 123 for (r in 1:k)
124 {
125 for (mm in 1:m)
126 {
ffdf9447 127 ps <- 0
1b698c16
BA
128 for (i in 1:n)
129 ps <- ps + Y2[i, mm, r] * sum(X2[i, , r] * phi[, mm, r])
ffdf9447
BA
130 nY2 <- sum(Y2[, mm, r]^2)
131 rho[mm, mm, r] <- (ps + sqrt(ps^2 + 4 * nY2 * gam2[r]))/(2 * nY2)
fb6e49cb 132 }
133 }
1b698c16 134
fb6e49cb 135 for (r in 1:k)
136 {
137 for (j in 1:p)
138 {
139 for (mm in 1:m)
140 {
1b698c16
BA
141 S[j, mm, r] <- -rho[mm, mm, r] * ps2[j, mm, r]
142 + sum(phi[-j, mm, r] * Gram2[j, -j, r])
143 if (abs(S[j, mm, r]) <= n * lambda * (pi[r]^gamma)) {
144 phi[j, mm, r] <- 0
145 } else if (S[j, mm, r] > n * lambda * (pi[r]^gamma)) {
146 phi[j, mm, r] <- (n * lambda * (pi[r]^gamma) - S[j, mm, r])/Gram2[j, j, r]
147 } else {
148 phi[j, mm, r] <- -(n * lambda * (pi[r]^gamma) + S[j, mm, r])/Gram2[j, j, r]
f7e157cd 149 }
fb6e49cb 150 }
151 }
152 }
1b698c16 153
c8baa022 154 ## E step
1b698c16 155
fb6e49cb 156 # Precompute det(rho[,,r]) for r in 1...k
ffdf9447 157 detRho <- sapply(1:k, function(r) det(rho[, , r]))
fb6e49cb 158 for (i in 1:n)
159 {
160 # Update gam[,]
1b698c16
BA
161 for (r in 1:k)
162 {
c8baa022 163 gam[i, r] <- pi[r] * exp(-0.5
1b698c16
BA
164 * sum((Y[i, ] %*% rho[, , r] - X[i, ] %*% phi[, , r])^2)) * detRho[r]
165 }
fb6e49cb 166 }
c8baa022
BA
167 norm_fact <- rowSums(gam)
168 gam <- gam / norm_fact
169 sumLogLLH <- sum(log(norm_fact) - log((2 * base::pi)^(m/2)))
ffdf9447
BA
170 sumPen <- sum(pi^gamma * b)
171 last_llh <- llh
172 llh <- -sumLogLLH/n + lambda * sumPen
173 dist <- ifelse(ite == 1, llh, (llh - last_llh)/(1 + abs(llh)))
174 Dist1 <- max((abs(phi - Phi))/(1 + abs(phi)))
175 Dist2 <- max((abs(rho - Rho))/(1 + abs(rho)))
176 Dist3 <- max((abs(pi - Pi))/(1 + abs(Pi)))
177 dist2 <- max(Dist1, Dist2, Dist3)
1b698c16 178
c8baa022 179 if (ite >= mini && (dist >= eps || dist2 >= sqrt(eps)))
fb6e49cb 180 break
181 }
1b698c16 182
ffdf9447 183 list(phi = phi, rho = rho, pi = pi, llh = llh, S = S)
aa480ac1 184}