From 7a56cc1804edcc2bb3ca3e4a8589faf55eb03547 Mon Sep 17 00:00:00 2001 From: Benjamin Auder Date: Fri, 14 Apr 2017 17:30:04 +0200 Subject: [PATCH] add automatic code formatter following https://google.github.io/styleguide/Rguide.xml --- hooks/pre-commit | 46 ++++++++++++++ hooks/pre-push | 5 ++ initialize.sh | 25 +++++--- pkg/R/constructionModelesLassoRank.R | 94 ++++++++++++++-------------- 4 files changed, 116 insertions(+), 54 deletions(-) create mode 100755 hooks/pre-commit create mode 100755 hooks/pre-push diff --git a/hooks/pre-commit b/hooks/pre-commit new file mode 100755 index 0000000..f9649b3 --- /dev/null +++ b/hooks/pre-commit @@ -0,0 +1,46 @@ +#!/bin/sh +# +# Hook used to indent all source files before commiting +# + +# indent / format file by type +indent() { + # getting against as the current commit + if git rev-parse --verify HEAD >/dev/null 2>&1 + then + local against=HEAD + else + # Initial commit: diff against an empty tree object + local against=4b825dc642cb6eb9a060e54bf8d69288fbee4904 + fi + + # loop on modified files + git diff --cached --name-only $against |while read file; + do + local ext=$(expr "$file" : ".*\(\..*\)") + case $ext in + .R|.r) + __indent_R; + ;; + esac + done +} + +# Indent the file with `indent' if this is a R file +__indent_R() { + if test ! -x "$INDENT" + then + return; + fi + if test ! -f $file + then + return; + fi + + echo "Indenting " $file + echo "library(formatR);formatR::tidy_source('$file',comment=TRUE,blank=TRUE, + arrow=TRUE,brace.newline=TRUE,indent=2,width.cutoff=80,file='$file')" | R --slave + git add "$file" +} + +indent diff --git a/hooks/pre-push b/hooks/pre-push new file mode 100755 index 0000000..7f26c8f --- /dev/null +++ b/hooks/pre-push @@ -0,0 +1,5 @@ +#!/bin/sh + +./.git-fat/git-fat pull +./.git-fat/git-fat push +git submodule update --merge diff --git a/initialize.sh b/initialize.sh index 59c9d17..48f0ba1 100755 --- a/initialize.sh +++ b/initialize.sh @@ -3,21 +3,32 @@ #initialize submodules, set-up .git/config and .gitattributes, and pre-push hook git submodule init && git submodule update --merge +#filter for git-fat +printf \ +'*.pdf filter=fat +*.tar.xz filter=fat +*.png filter=fat +*.jpg filter=fat +*.ps filter=fat\n' > .gitattributes + #filter for Jupyter python .nbstripout/nbstripout.py --install --attributes .gitattributes -#filter for git-fat [TODO: idempotent...] -printf '*.pdf filter=fat\n*.tar.xz filter=fat\n*.png filter=fat\n*.jpg filter=fat\n*.ps filter=fat\n' >> .gitattributes +#pre-commit and pre-push hooks: indentation, git fat push, submodules update +cp hooks/* .git/hooks/ -#pre-push hook: git fat push, submodules update -printf '#!/bin/sh\n./.git-fat/git-fat pull\n./.git-fat/git-fat push\ngit submodule update --merge\n' > .git/hooks/pre-push -chmod 755 .git/hooks/pre-push +#install formatR +echo 'if (! "formatR" %in% rownames(installed.packages())) + install.packages("formatR",repos="https://cloud.r-project.org")' | R --slave #.gitfat file with remote on gitfat@auder.net printf '[rsync]\nremote = gitfat@auder.net:~/files/valse\n' > .gitfat #manual git-fat init: with relative path to binary -#1] remove filter if exists http://stackoverflow.com/questions/12179437/replace-3-lines-with-another-line-sed-syntax +#1] remove filter if exists http://stackoverflow.com/a/12179641/4640434 sed -i '1N;$!N;s/\[filter "fat"\]\n.*\n.*//;P;D' .git/config #2] place new filter -printf '[filter "fat"]\n\tclean = ./.git-fat/git-fat filter-clean\n\tsmudge = ./.git-fat/git-fat filter-smudge\n' >> .git/config +printf \ +'[filter "fat"] + clean = ./.git-fat/git-fat filter-clean + smudge = ./.git-fat/git-fat filter-smudge\n' >> .git/config diff --git a/pkg/R/constructionModelesLassoRank.R b/pkg/R/constructionModelesLassoRank.R index 5da26e3..fe75d2c 100644 --- a/pkg/R/constructionModelesLassoRank.R +++ b/pkg/R/constructionModelesLassoRank.R @@ -18,77 +18,77 @@ #' @return a list with several models, defined by phi, rho, pi, llh #' #' @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(Y)[2] - L = length(S) +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(Y)[2] + L <- length(S) # Possible interesting ranks - deltaRank = rank.max - rank.min + 1 - Size = deltaRank^k - RankLambda = matrix(0, nrow=Size*L, ncol=k+1) + deltaRank <- rank.max - rank.min + 1 + Size <- deltaRank^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, 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) + # 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) + 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","eps", - "Rank","m","phi","ncores","verbose") ) + cl <- parallel::makeCluster(ncores, outfile = "") + parallel::clusterExport(cl, envir = environment(), 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 + 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) + selected <- S[[lambdaIndex]]$selected + relevant <- c() + for (j in 1:p) + { + if (length(selected[[j]]) > 0) + { + relevant <- c(relevant, j) } } - if (max(rankIndex) 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 + 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) + 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_len(length(S)*Size), computeAtLambda) - else - lapply(seq_len(length(S)*Size), computeAtLambda) + # For each lambda in the grid we compute the estimators + out <- if (ncores > 1) + parLapply(cl, seq_len(length(S) * Size), computeAtLambda) else lapply(seq_len(length(S) * Size), computeAtLambda) - if (ncores > 1) + if (ncores > 1) parallel::stopCluster(cl) out -- 2.44.0