d8e2cf96432dbf5e75dede453c43a44ac097adf7
[morpheus.git] / pkg / R / optimParams.R
1 #' Wrapper function for OptimParams class
2 #'
3 #' @param K Number of populations.
4 #' @param link The link type, 'logit' or 'probit'.
5 #' @param X Data matrix of covariables
6 #' @param Y Output as a binary vector
7 #'
8 #' @return An object 'op' of class OptimParams, initialized so that \code{op$run(x0)}
9 #' outputs the list of optimized parameters
10 #' \itemize{
11 #' \item p: proportions, size K
12 #' \item β: regression matrix, size dxK
13 #' \item b: intercepts, size K
14 #' }
15 #' θ0 is a vector containing respectively the K-1 first elements of p, then β by
16 #' columns, and finally b: \code{θ0 = c(p[1:(K-1)],as.double(β),b)}.
17 #'
18 #' @seealso \code{multiRun} to estimate statistics based on β, and
19 #' \code{generateSampleIO} for I/O random generation.
20 #'
21 #' @examples
22 #' # Optimize parameters from estimated μ
23 #' io = generateSampleIO(10000, 1/2, matrix(c(1,-2,3,1),ncol=2), c(0,0), "logit")
24 #' μ = computeMu(io$X, io$Y, list(K=2))
25 #' o <- optimParams(io$X, io$Y, 2, "logit")
26 #' θ0 <- list(p=1/2, β=μ, b=c(0,0))
27 #' par0 <- o$run(θ0)
28 #' # Compare with another starting point
29 #' θ1 <- list(p=1/2, β=2*μ, b=c(0,0))
30 #' par1 <- o$run(θ1)
31 #' o$f( o$linArgs(par0) )
32 #' o$f( o$linArgs(par1) )
33 #' @export
34 optimParams <- function(X, Y, K, link=c("logit","probit"), M=NULL)
35 {
36 # Check arguments
37 if (!is.matrix(X) || any(is.na(X)))
38 stop("X: numeric matrix, no NAs")
39 if (!is.numeric(Y) || any(is.na(Y)) || any(Y!=0 & Y!=1))
40 stop("Y: binary vector with 0 and 1 only")
41 link <- match.arg(link)
42 if (!is.numeric(K) || K!=floor(K) || K < 2)
43 stop("K: integer >= 2")
44
45 if (is.null(M))
46 {
47 # Precompute empirical moments
48 Mtmp <- computeMoments(X, Y)
49 M1 <- as.double(Mtmp[[1]])
50 M2 <- as.double(Mtmp[[2]])
51 M3 <- as.double(Mtmp[[3]])
52 M <- c(M1, M2, M3)
53 }
54
55 # Build and return optimization algorithm object
56 methods::new("OptimParams", "li"=link, "X"=X,
57 "Y"=as.integer(Y), "K"=as.integer(K), "Mhat"=as.double(M))
58 }
59
60 #' Encapsulated optimization for p (proportions), β and b (regression parameters)
61 #'
62 #' Optimize the parameters of a mixture of logistic regressions model, possibly using
63 #' \code{mu <- computeMu(...)} as a partial starting point.
64 #'
65 #' @field li Link function, 'logit' or 'probit'
66 #' @field X Data matrix of covariables
67 #' @field Y Output as a binary vector
68 #' @field K Number of populations
69 #' @field d Number of dimensions
70 #' @field W Weights matrix (iteratively refined)
71 #'
72 setRefClass(
73 Class = "OptimParams",
74
75 fields = list(
76 # Inputs
77 li = "character", #link function
78 X = "matrix",
79 Y = "numeric",
80 Mhat = "numeric", #vector of empirical moments
81 # Dimensions
82 K = "integer",
83 n = "integer",
84 d = "integer",
85 # Weights matrix (generalized least square)
86 W = "matrix"
87 ),
88
89 methods = list(
90 initialize = function(...)
91 {
92 "Check args and initialize K, d, W"
93
94 callSuper(...)
95 if (!hasArg("X") || !hasArg("Y") || !hasArg("K")
96 || !hasArg("li") || !hasArg("Mhat"))
97 {
98 stop("Missing arguments")
99 }
100
101 n <<- nrow(X)
102 d <<- ncol(X)
103 W <<- diag(d+d^2+d^3) #initialize at W = Identity
104 },
105
106 expArgs = function(v)
107 {
108 "Expand individual arguments from vector v into a list"
109
110 list(
111 # p: dimension K-1, need to be completed
112 "p" = c(v[1:(K-1)], 1-sum(v[1:(K-1)])),
113 "β" = t(matrix(v[K:(K+d*K-1)], ncol=d)),
114 "b" = v[(K+d*K):(K+(d+1)*K-1)])
115 },
116
117 linArgs = function(L)
118 {
119 "Linearize vectors+matrices from list L into a vector"
120
121 # β linearized row by row, to match derivatives order
122 c(L$p[1:(K-1)], as.double(t(L$β)), L$b)
123 },
124
125 computeW = function(θ)
126 {
127 require(MASS)
128 dd <- d + d^2 + d^3
129 M <- Moments(θ)
130 Omega <- matrix( .C("Compute_Omega",
131 X=as.double(X), Y=as.integer(Y), M=as.double(M),
132 pn=as.integer(n), pd=as.integer(d),
133 W=as.double(W), PACKAGE="morpheus")$W, nrow=dd, ncol=dd )
134 MASS::ginv(Omega)
135 },
136
137 Moments = function(θ)
138 {
139 "Vector of moments, of size d+d^2+d^3"
140
141 p <- θ$p
142 β <- θ$β
143 λ <- sqrt(colSums(β^2))
144 b <- θ$b
145
146 # Tensorial products β^2 = β2 and β^3 = β3 must be computed from current β1
147 β2 <- apply(β, 2, function(col) col %o% col)
148 β3 <- apply(β, 2, function(col) col %o% col %o% col)
149
150 c(
151 β %*% (p * .G(li,1,λ,b)),
152 β2 %*% (p * .G(li,2,λ,b)),
153 β3 %*% (p * .G(li,3,λ,b)))
154 },
155
156 f = function(θ)
157 {
158 "Product t(hat_Mi - Mi) W (hat_Mi - Mi) with Mi(theta)"
159
160 L <- expArgs(θ)
161 A <- as.matrix(Mhat - Moments(L))
162 t(A) %*% W %*% A
163 },
164
165 grad_f = function(θ)
166 {
167 "Gradient of f, dimension (K-1) + d*K + K = (d+2)*K - 1"
168
169 L <- expArgs(θ)
170 -2 * t(grad_M(L)) %*% W %*% as.matrix(Mhat - Moments(L))
171 },
172
173 grad_M = function(θ)
174 {
175 "Gradient of the vector of moments, size (dim=)d+d^2+d^3 x K-1+K+d*K"
176
177 p <- θ$p
178 β <- θ$β
179 λ <- sqrt(colSums(β^2))
180 μ <- sweep(β, 2, λ, '/')
181 b <- θ$b
182
183 res <- matrix(nrow=nrow(W), ncol=0)
184
185 # Tensorial products β^2 = β2 and β^3 = β3 must be computed from current β1
186 β2 <- apply(β, 2, function(col) col %o% col)
187 β3 <- apply(β, 2, function(col) col %o% col %o% col)
188
189 # Some precomputations
190 G1 = .G(li,1,λ,b)
191 G2 = .G(li,2,λ,b)
192 G3 = .G(li,3,λ,b)
193 G4 = .G(li,4,λ,b)
194 G5 = .G(li,5,λ,b)
195
196 # Gradient on p: K-1 columns, dim rows
197 km1 = 1:(K-1)
198 res <- cbind(res, rbind(
199 sweep(as.matrix(β [,km1]), 2, G1[km1], '*') - G1[K] * β [,K],
200 sweep(as.matrix(β2[,km1]), 2, G2[km1], '*') - G2[K] * β2[,K],
201 sweep(as.matrix(β3[,km1]), 2, G3[km1], '*') - G3[K] * β3[,K] ))
202
203 for (i in 1:d)
204 {
205 # i determines the derivated matrix dβ[2,3]
206
207 dβ_left <- sweep(β, 2, p * G3 * β[i,], '*')
208 dβ_right <- matrix(0, nrow=d, ncol=K)
209 block <- i
210 dβ_right[block,] <- dβ_right[block,] + 1
211 dβ <- dβ_left + sweep(dβ_right, 2, p * G1, '*')
212
213 dβ2_left <- sweep(β2, 2, p * G4 * β[i,], '*')
214 dβ2_right <- do.call( rbind, lapply(1:d, function(j) {
215 sweep(dβ_right, 2, β[j,], '*')
216 }) )
217 block <- ((i-1)*d+1):(i*d)
218 dβ2_right[block,] <- dβ2_right[block,] + β
219 dβ2 <- dβ2_left + sweep(dβ2_right, 2, p * G2, '*')
220
221 dβ3_left <- sweep(β3, 2, p * G5 * β[i,], '*')
222 dβ3_right <- do.call( rbind, lapply(1:d, function(j) {
223 sweep(dβ2_right, 2, β[j,], '*')
224 }) )
225 block <- ((i-1)*d*d+1):(i*d*d)
226 dβ3_right[block,] <- dβ3_right[block,] + β2
227 dβ3 <- dβ3_left + sweep(dβ3_right, 2, p * G3, '*')
228
229 res <- cbind(res, rbind(dβ, dβ2, dβ3))
230 }
231
232 # Gradient on b
233 res <- cbind(res, rbind(
234 sweep(β, 2, p * G2, '*'),
235 sweep(β2, 2, p * G3, '*'),
236 sweep(β3, 2, p * G4, '*') ))
237
238 res
239 },
240
241 run = function(θ0)
242 {
243 "Run optimization from θ0 with solver..."
244
245 if (!is.list(θ0))
246 stop("θ0: list")
247 if (is.null(θ0$β))
248 stop("At least θ0$β must be provided")
249 if (!is.matrix(θ0$β) || any(is.na(θ0$β))
250 || nrow(θ0$β) != d || ncol(θ0$β) != K)
251 {
252 stop("θ0$β: matrix, no NA, nrow = d, ncol = K")
253 }
254 if (is.null(θ0$p))
255 θ0$p = rep(1/K, K-1)
256 else if (!is.numeric(θ0$p) || length(θ0$p) != K-1
257 || any(is.na(θ0$p)) || sum(θ0$p) > 1)
258 {
259 stop("θ0$p: length K-1, no NA, positive integers, sum to <= 1")
260 }
261 if (is.null(θ0$b))
262 θ0$b = rep(0, K)
263 else if (!is.numeric(θ0$b) || length(θ0$b) != K || any(is.na(θ0$b)))
264 stop("θ0$b: length K, no NA")
265 # TODO: stopping condition? N iterations? Delta <= epsilon ?
266 loopMax <- 2
267 for (loop in 1:loopMax)
268 {
269 op_res = constrOptim( linArgs(θ0), .self$f, .self$grad_f,
270 ui=cbind(
271 rbind( rep(-1,K-1), diag(K-1) ),
272 matrix(0, nrow=K, ncol=(d+1)*K) ),
273 ci=c(-1,rep(0,K-1)) )
274 if (loop < loopMax) #avoid computing an extra W
275 W <<- computeW(expArgs(op_res$par))
276 #print(op_res$value) #debug
277 #print(expArgs(op_res$par)) #debug
278 }
279
280 expArgs(op_res$par)
281 }
282 )
283 )
284
285 # Compute vectorial E[g^{(order)}(<β,x> + b)] with x~N(0,Id) (integral in R^d)
286 # = E[g^{(order)}(z)] with z~N(b,diag(λ))
287 # by numerically evaluating the integral.
288 #
289 # @param link Link, 'logit' or 'probit'
290 # @param order Order of derivative
291 # @param λ Norm of columns of β
292 # @param b Intercept
293 #
294 .G <- function(link, order, λ, b)
295 {
296 # NOTE: weird "integral divergent" error on inputs:
297 # link="probit"; order=2; λ=c(531.8099,586.8893,523.5816); b=c(-118.512674,-3.488020,2.109969)
298 # Switch to pracma package for that (but it seems slow...)
299 sapply( seq_along(λ), function(k) {
300 res <- NULL
301 tryCatch({
302 # Fast code, may fail:
303 res <- stats::integrate(
304 function(z) .deriv[[link]][[order]](λ[k]*z+b[k]) * exp(-z^2/2) / sqrt(2*pi),
305 lower=-Inf, upper=Inf )$value
306 }, error = function(e) {
307 # Robust slow code, no fails observed:
308 sink("/dev/null") #pracma package has some useless printed outputs...
309 res <- pracma::integral(
310 function(z) .deriv[[link]][[order]](λ[k]*z+b[k]) * exp(-z^2/2) / sqrt(2*pi),
311 xmin=-Inf, xmax=Inf, method="Kronrod")
312 sink()
313 })
314 res
315 })
316 }
317
318 # Derivatives list: g^(k)(x) for links 'logit' and 'probit'
319 #
320 .deriv <- list(
321 "probit"=list(
322 # 'probit' derivatives list;
323 # NOTE: exact values for the integral E[g^(k)(λz+b)] could be computed
324 function(x) exp(-x^2/2)/(sqrt(2*pi)), #g'
325 function(x) exp(-x^2/2)/(sqrt(2*pi)) * -x, #g''
326 function(x) exp(-x^2/2)/(sqrt(2*pi)) * ( x^2 - 1), #g^(3)
327 function(x) exp(-x^2/2)/(sqrt(2*pi)) * (-x^3 + 3*x), #g^(4)
328 function(x) exp(-x^2/2)/(sqrt(2*pi)) * ( x^4 - 6*x^2 + 3) #g^(5)
329 ),
330 "logit"=list(
331 # Sigmoid derivatives list, obtained with http://www.derivative-calculator.net/
332 # @seealso http://www.ece.uc.edu/~aminai/papers/minai_sigmoids_NN93.pdf
333 function(x) {e=exp(x); .zin(e /(e+1)^2)}, #g'
334 function(x) {e=exp(x); .zin(e*(-e + 1) /(e+1)^3)}, #g''
335 function(x) {e=exp(x); .zin(e*( e^2 - 4*e + 1) /(e+1)^4)}, #g^(3)
336 function(x) {e=exp(x); .zin(e*(-e^3 + 11*e^2 - 11*e + 1) /(e+1)^5)}, #g^(4)
337 function(x) {e=exp(x); .zin(e*( e^4 - 26*e^3 + 66*e^2 - 26*e + 1)/(e+1)^6)} #g^(5)
338 )
339 )
340
341 # Utility for integration: "[return] zero if [argument is] NaN" (Inf / Inf divs)
342 #
343 # @param x Ratio of polynoms of exponentials, as in .S[[i]]
344 #
345 .zin <- function(x)
346 {
347 x[is.nan(x)] <- 0.
348 x
349 }