X-Git-Url: https://git.auder.net/?a=blobdiff_plain;f=pkg%2FR%2FoptimParams.R;h=894aebd6dfa90dd49e474e0177baed7e9141bb17;hb=d9edcd6c1b17155153bb05a4f2274a2da6f2f543;hp=c42e6c54e022d454196c2ded156b3a4d1caa553d;hpb=44559add0e38058d9ce539c4b91246e4a088f67a;p=morpheus.git diff --git a/pkg/R/optimParams.R b/pkg/R/optimParams.R index c42e6c5..894aebd 100644 --- a/pkg/R/optimParams.R +++ b/pkg/R/optimParams.R @@ -31,7 +31,7 @@ #' o$f( o$linArgs(par0) ) #' o$f( o$linArgs(par1) ) #' @export -optimParams <- function(X, Y, K, link=c("logit","probit")) +optimParams <- function(X, Y, K, link=c("logit","probit"), M=NULL) { # Check arguments if (!is.matrix(X) || any(is.na(X))) @@ -42,9 +42,21 @@ optimParams <- function(X, Y, K, link=c("logit","probit")) if (!is.numeric(K) || K!=floor(K) || K < 2) stop("K: integer >= 2") + if (is.null(M)) + { + # Precompute empirical moments + Mtmp <- computeMoments(X, Y) + M1 <- as.double(Mtmp[[1]]) + M2 <- as.double(Mtmp[[2]]) + M3 <- as.double(Mtmp[[3]]) + M <- c(M1, M2, M3) + } + else + M <- c(M[[1]], M[[2]], M[[3]]) + # Build and return optimization algorithm object methods::new("OptimParams", "li"=link, "X"=X, - "Y"=as.integer(Y), "K"=as.integer(K)) + "Y"=as.integer(Y), "K"=as.integer(K), "Mhat"=as.double(M)) } #' Encapsulated optimization for p (proportions), β and b (regression parameters) @@ -82,18 +94,14 @@ setRefClass( "Check args and initialize K, d, W" callSuper(...) - if (!hasArg("X") || !hasArg("Y") || !hasArg("K") || !hasArg("li")) + if (!hasArg("X") || !hasArg("Y") || !hasArg("K") + || !hasArg("li") || !hasArg("Mhat")) + { stop("Missing arguments") - - # Precompute empirical moments - M <- computeMoments(X, Y) - M1 <- as.double(M[[1]]) - M2 <- as.double(M[[2]]) - M3 <- as.double(M[[3]]) - Mhat <<- c(M1, M2, M3) + } n <<- nrow(X) - d <<- length(M1) + d <<- ncol(X) W <<- diag(d+d^2+d^3) #initialize at W = Identity }, @@ -122,7 +130,7 @@ setRefClass( dd <- d + d^2 + d^3 M <- Moments(θ) Omega <- matrix( .C("Compute_Omega", - X=as.double(X), Y=as.double(Y), M=as.double(M), + X=as.double(X), Y=as.integer(Y), M=as.double(M), pn=as.integer(n), pd=as.integer(d), W=as.double(W), PACKAGE="morpheus")$W, nrow=dd, ncol=dd ) MASS::ginv(Omega) @@ -257,16 +265,18 @@ setRefClass( else if (!is.numeric(θ0$b) || length(θ0$b) != K || any(is.na(θ0$b))) stop("θ0$b: length K, no NA") # TODO: stopping condition? N iterations? Delta <= epsilon ? - for (loop in 1:10) + loopMax <- 2 + for (loop in 1:loopMax) { op_res = constrOptim( linArgs(θ0), .self$f, .self$grad_f, ui=cbind( rbind( rep(-1,K-1), diag(K-1) ), matrix(0, nrow=K, ncol=(d+1)*K) ), ci=c(-1,rep(0,K-1)) ) - W <<- computeW(expArgs(op_res$par)) - print(op_res$value) #debug - print(expArgs(op_res$par)) #debug + if (loop < loopMax) #avoid computing an extra W + W <<- computeW(expArgs(op_res$par)) + #print(op_res$value) #debug + #print(expArgs(op_res$par)) #debug } expArgs(op_res$par)