fix EMGRank.R, and add some lines in the roxygen code for some functions
[valse.git] / pkg / R / constructionModelesLassoRank.R
index 339ba60..5da26e3 100644 (file)
@@ -1,84 +1,95 @@
 #' constructionModelesLassoRank
 #'
-#' TODO: description
+#' Construct a collection of models with the Lasso-Rank procedure.
+#' 
+#' @param S output of selectVariables.R
+#' @param k number of components
+#' @param mini integer, minimum number of iterations in the EM algorithm, by default = 10
+#' @param maxi integer, maximum number of iterations in the EM algorithm, by default = 100
+#' @param X matrix of covariates (of size n*p)
+#' @param Y matrix of responses (of size n*m)
+#' @param eps real, threshold to say the EM algorithm converges, by default = 1e-4
+#' @param rank.min integer, minimum rank in the low rank procedure, by default = 1
+#' @param rank.max integer, maximum rank in the low rank procedure, by default = 5
+#' @param ncores Number of cores, by default = 3
+#' @param fast TRUE to use compiled C code, FALSE for R code only
+#' @param verbose TRUE to show some execution traces
+#' 
+#' @return a list with several models, defined by phi, rho, pi, llh
 #'
-#' @param ...
-#'
-#' @return ...
-#'
-#' export
-constructionModelesLassoRank = function(pi, rho, mini, maxi, X, Y, tau, A1, rangmin,
-       rangmax, ncores, fast=TRUE, verbose=FALSE)
+#' @export
+constructionModelesLassoRank = function(S, k, mini, maxi, X, Y, eps, rank.min,
+                                        rank.max, ncores, fast=TRUE, verbose=FALSE)
 {
   n = dim(X)[1]
   p = dim(X)[2]
-  m = dim(rho)[2]
-  k = dim(rho)[3]
-  L = dim(A1)[2]
-
-       # On cherche les rangs possiblement intéressants
-  deltaRank = rangmax - rangmin + 1
+  m = dim(Y)[2]
+  L = length(S)
+  
+  # Possible interesting ranks
+  deltaRank = rank.max - rank.min + 1
   Size = deltaRank^k
-  Rank = matrix(0, nrow=Size, ncol=k)
+  RankLambda = matrix(0, nrow=Size*L, ncol=k+1)
   for (r in 1:k)
-       {
-               # On veut le tableau de toutes les combinaisons de rangs possibles
-               # Dans la première colonne : on répète (rangmax-rangmin)^(k-1) chaque chiffre :
-               #   ça remplit la colonne
-               # Dans la deuxieme : on répète (rangmax-rangmin)^(k-2) chaque chiffre,
-               #   et on fait ça (rangmax-rangmin)^2 fois
-               # ...
-               # Dans la dernière, on répète chaque chiffre une fois,
-               #   et on fait ça (rangmin-rangmax)^(k-1) fois.
-    Rank[,r] = rangmin + rep(0:(deltaRank-1), deltaRank^(r-1), each=deltaRank^(k-r))
+  {
+    # On veut le tableau de toutes les combinaisons de rangs possibles, et des lambdas
+    # Dans la première colonne : on répète (rank.max-rank.min)^(k-1) chaque chiffre :
+    #   ça remplit la colonne
+    # Dans la deuxieme : on répète (rank.max-rank.min)^(k-2) chaque chiffre,
+    #   et on fait ça (rank.max-rank.min)^2 fois
+    # ...
+    # Dans la dernière, on répète chaque chiffre une fois,
+    #   et on fait ça (rank.min-rank.max)^(k-1) fois.
+    RankLambda[,r] = rep(rank.min + rep(0:(deltaRank-1), deltaRank^(r-1), each=deltaRank^(k-r)), each = L)
   }
-
+  RankLambda[,k+1] = rep(1:L, times = Size)
+  
   if (ncores > 1)
-       {
+  {
     cl = parallel::makeCluster(ncores, outfile='')
     parallel::clusterExport( cl, envir=environment(),
-                       varlist=c("A1","Size","Pi","Rho","mini","maxi","X","Y","tau",
-                       "Rank","m","phi","ncores","verbose") )
-       }
-
-       computeAtLambda <- function(lambdaIndex)
-       {
-               if (ncores > 1)
-                       require("valse") #workers start with an empty environment
-
-    # on ne garde que les colonnes actives
-    # 'active' sera l'ensemble des variables informatives
-    active = A1[,lambdaIndex]
-    active = active[-(active==0)]
-               phi = array(0, dim=c(p,m,k,Size))
-               llh = matrix(0, Size, 2) #log-likelihood
-    if (length(active) > 0)
-               {
-      for (j in 1:Size)
-                       {
-        res = EMGrank(Pi[,lambdaIndex], Rho[,,,lambdaIndex], mini, maxi,
-                                       X[,active], Y, tau, Rank[j,], fast)
-        llh = rbind(llh,
-                                       c( res$LLF, sum(Rank[j,] * (length(active)- Rank[j,] + m)) ) )
-        phi[active,,,] = rbind(phi[active,,,], res$phi)
+                             varlist=c("A1","Size","Pi","Rho","mini","maxi","X","Y","eps",
+                                       "Rank","m","phi","ncores","verbose") )
+  }
+  
+  computeAtLambda <- function(index)
+  {
+    lambdaIndex = RankLambda[index,k+1]
+    rankIndex = RankLambda[index,1:k]
+    if (ncores > 1)
+      require("valse") #workers start with an empty environment
+    
+    # 'relevant' will be the set of relevant columns
+    selected = S[[lambdaIndex]]$selected
+    relevant = c()
+    for (j in 1:p){
+      if (length(selected[[j]])>0){
+        relevant = c(relevant,j)
       }
     }
-               list("llh"=llh, "phi"=phi)
-       }
-
-       #Pour chaque lambda de la grille, on calcule les coefficients
+    if (max(rankIndex)<length(relevant)){
+      phi = array(0, dim=c(p,m,k))
+      if (length(relevant) > 0)
+      {
+        res = EMGrank(S[[lambdaIndex]]$Pi, S[[lambdaIndex]]$Rho, mini, maxi,
+                      X[,relevant], Y, eps, rankIndex, fast)
+        llh = c( res$LLF, sum(rankIndex * (length(relevant)- rankIndex + m)) ) 
+        phi[relevant,,] = res$phi
+      }
+      list("llh"=llh, "phi"=phi, "pi" = S[[lambdaIndex]]$Pi, "rho" = S[[lambdaIndex]]$Rho)
+      
+    }
+  }
+  
+  #For each lambda in the grid we compute the estimators
   out =
-               if (ncores > 1)
-                       parLapply(cl, seq_along(glambda), computeAtLambda)
-               else
-                       lapply(seq_along(glambda), computeAtLambda)
-
-       if (ncores > 1)
+    if (ncores > 1)
+      parLapply(cl, seq_len(length(S)*Size), computeAtLambda)
+  else
+    lapply(seq_len(length(S)*Size), computeAtLambda)
+  
+  if (ncores > 1)
     parallel::stopCluster(cl)
-
-       # TODO: this is a bit ugly. Better use bigmemory and fill llh/phi in-place
-       # (but this also adds a dependency...)
-       llh <- do.call( rbind, lapply(out, function(model) model$llh) )
-       phi <- do.call( rbind, lapply(out, function(model) model$phi) )
-       list("llh"=llh, "phi"=phi)
+  
+  out
 }