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