Mercurial > repos > lecorguille > anova
annotate abims_anova.r @ 8:a2b19a78306a draft default tip
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 493595bdd63ff88e7b93f22d8a092a70d4f39a05
author | lecorguille |
---|---|
date | Mon, 05 Mar 2018 09:24:51 -0500 |
parents | 8190dfb5a351 |
children |
rev | line source |
---|---|
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
1 #!/usr/local/public/bin/Rscript |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
2 # version="1.1" |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
3 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
4 # date: 06-06-2012 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
5 # update: 18-02-2014 |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
6 # **Authors** Gildas Le Corguille ABiMS - UPMC/CNRS - Station Biologique de Roscoff - gildas.lecorguille|at|sb-roscoff.fr |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
7 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
8 # abims_anova.r version 20140218 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
9 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
10 library(batch) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
11 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
12 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
13 # function avova |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
14 anova = function (file, sampleinfo, varinfo, mode="column", condition=1, interaction=F, method="BH", threshold=0.01, selection_method="intersection", sep=";", dec=".", outputdatapvalue="anova.data.output", outputdatasignif="anova.datasignif.output") { |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
15 |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
16 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
17 if (sep=="tabulation") sep="\t" |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
18 if (sep=="semicolon") sep=";" |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
19 if (sep=="comma") sep="," |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
20 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
21 anova_formula_operator = "+" |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
22 if (interaction) anova_formula_operator = "*" |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
23 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
24 # -- import -- |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
25 data=read.table(file, header = TRUE, row.names=1, sep = sep, quote="\"", dec = dec, fill = TRUE, comment.char="",na.strings = "NA", check.names=FALSE) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
26 |
8
a2b19a78306a
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 493595bdd63ff88e7b93f22d8a092a70d4f39a05
lecorguille
parents:
7
diff
changeset
|
27 if (mode == "row") {data=t(data)} else {data=as.matrix(data)} |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
28 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
29 sampleinfoTab=read.table(sampleinfo, header = TRUE, row.names=1, sep = sep, quote="\"") |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
30 rownames(sampleinfoTab) = make.names(rownames(sampleinfoTab)) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
31 |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
32 varinfoTab=read.table(varinfo, header = TRUE, sep = sep, quote="\"") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
33 if(sum(colnames(data)!=varinfoTab[,1])!=0){ # if ID not exactly identical |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
34 if(sum(colnames(data)[order(colnames(data))]!=varinfoTab[order(varinfoTab[,1]),1])==0){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
35 # reorder data matrix to match variable metadata order |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
36 data = data[,match(varinfoTab[,1],colnames(data))] |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
37 }else{ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
38 stop(paste0("\nVariables' ID do not match between your data matrix and your variable", |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
39 "metadata file. \nPlease check your data.")) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
40 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
41 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
42 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
43 # -- group -- |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
44 match_data_sampleinfoTab = match(rownames(data),rownames(sampleinfoTab)) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
45 if (sum(is.na(match_data_sampleinfoTab)) > 0) { |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
46 write("ERROR: There is a problem during to match sample names from the data matrix and from the sample info (presence of NA).", stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
47 write("You may need to use change the mode (column/row)", stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
48 write("10 first sample names in the data matrix:", stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
49 write(head(colnames(data)), stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
50 write("10 first sample names in the sample info:", stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
51 write(head(rownames(sampleinfoTab)), stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
52 quit("no",status=10) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
53 } |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
54 |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
55 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
56 # -- anova -- |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
57 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
58 # formula |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
59 grps=list() |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
60 anova_formula_s = "data ~ " |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
61 cat("\ncontrasts:\n") |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
62 for (i in 1:length(condition)) { |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
63 grps[[i]] = factor(sampleinfoTab[,condition[i]][match_data_sampleinfoTab]) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
64 anova_formula_s = paste(anova_formula_s, "grps[[",i,"]]",anova_formula_operator, sep="") |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
65 cat(condition[i],"\t",levels(grps[[i]]),"\n") |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
66 # write("Current groups: ", stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
67 # write(grp[[i]], stderr()) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
68 } |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
69 anova_formula_s = substr(anova_formula_s, 1, nchar(anova_formula_s)-1) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
70 anova_formula = as.formula(anova_formula_s) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
71 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
72 |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
73 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
74 # anova |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
75 manovaObjectList = manova(anova_formula) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
76 manovaList = summary.aov(manovaObjectList) |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
77 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
78 # condition renaming |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
79 manovaRownames = gsub(" ","",rownames(manovaList[[1]])) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
80 manovaNbrPvalue = length(manovaRownames)-1 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
81 manovaRownames = manovaRownames[-(manovaNbrPvalue+1)] |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
82 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
83 for (i in 1:length(condition)) { |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
84 manovaRownames = sub(paste("grps\\[\\[",i,"\\]\\]",sep=""),condition[i],manovaRownames) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
85 anova_formula_s = sub(paste("grps\\[\\[",i,"\\]\\]",sep=""),condition[i],anova_formula_s) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
86 } |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
87 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
88 # log |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
89 cat("\nanova_formula",anova_formula_s,"\n") |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
90 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
91 # p-value |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
92 aovPValue = sapply(manovaList,function(x){x[-(manovaNbrPvalue+1),5]}) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
93 if(length(condition) == 1) aovPValue = t(aovPValue) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
94 rownames(aovPValue) = paste("pvalue_",manovaRownames,sep="") |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
95 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
96 # p-value adjusted |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
97 if(length(condition) == 1) { |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
98 aovAdjPValue = t(p.adjust(aovPValue,method=method)) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
99 } else { |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
100 aovAdjPValue = t(apply(aovPValue,1,p.adjust, method=method)) |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
101 } |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
102 rownames(aovAdjPValue) = paste("pval.",method,".",manovaRownames,sep="") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
103 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
104 # selection |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
105 colSumThreshold = colSums(aovAdjPValue <= threshold) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
106 if (selection_method == "intersection") { |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
107 datafiltered = data[,colSumThreshold == nrow(aovAdjPValue ), drop=FALSE] |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
108 } else { |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
109 datafiltered = data[,colSumThreshold != 0, drop=FALSE] |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
110 } |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
111 selected.var = rep("no",ncol(data)) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
112 selected.var[colnames(data)%in%colnames(datafiltered)] = "yes" |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
113 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
114 #data=rbind(data, aovPValue, aovAdjPValue) |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
115 varinfoTab=cbind(varinfoTab, round(t(aovAdjPValue),10), selected.var) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
116 |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
117 # group means |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
118 for (i in 1:length(condition)) { |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
119 for(j in levels(grps[[i]])){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
120 subgp = rownames(sampleinfoTab[which(sampleinfoTab[,condition[i]]==j),]) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
121 modmean = colMeans(data[which(rownames(data)%in%subgp),],na.rm=TRUE) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
122 varinfoTab=cbind(varinfoTab, modmean) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
123 colnames(varinfoTab)[ncol(varinfoTab)] = paste0("Mean_",condition[i],".",j) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
124 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
125 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
126 colnames(varinfoTab) = make.unique(colnames(varinfoTab)) |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
127 |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
128 # pdf for significant variables |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
129 pdf(outputdatasignif) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
130 ### Venn diagram |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
131 if(nrow(aovAdjPValue)>5){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
132 pie(100,labels=NA,main=paste0("Venn diagram only available for maximum 5 terms\n", |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
133 "(your analysis concerns ",nrow(aovAdjPValue)," terms)\n\n", |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
134 "Number of significant variables relatively to\nyour chosen threshold and ", |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
135 "selection method: ",ncol(datafiltered)),cex.main=0.8) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
136 }else{ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
137 vennlist = list(NULL) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
138 names(vennlist) = rownames(aovAdjPValue)[1] |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
139 if(length(colnames(aovAdjPValue))==0){colnames(aovAdjPValue)=varinfoTab[,1]} |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
140 for(i in 1:nrow(aovAdjPValue)){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
141 vennlist[[rownames(aovAdjPValue)[i]]]=colnames(aovAdjPValue[i,which(aovAdjPValue[i,]<=threshold),drop=FALSE]) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
142 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
143 if(length(vennlist)==0){ pie(100,labels=NA,main="No significant ions was found.") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
144 }else{ library(venn) ; venn(vennlist, zcolor="style", cexil=2, cexsn=1.5) } |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
145 } |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
146 ### Boxplot |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
147 par(mfrow=c(2,2),mai=rep(0.5,4)) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
148 data <- as.data.frame(data) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
149 for(i in 1:nrow(aovAdjPValue)){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
150 factmain = gsub(paste0("pval.",method,"."),"",rownames(aovAdjPValue)[i]) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
151 factsignif = aovAdjPValue[i,which(aovAdjPValue[i,]<=threshold),drop=FALSE] |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
152 if((ncol(factsignif)!=0)&(factmain%in%colnames(sampleinfoTab))){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
153 for(j in 1:ncol(factsignif)){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
154 varsignif = gsub(" Response ","",colnames(factsignif)[j]) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
155 boxplot(as.formula(paste0("data$",varsignif," ~ sampleinfoTab$",factmain)), |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
156 main=paste0(factmain,"\n",varsignif), col="grey", mai=7) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
157 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
158 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
159 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
160 dev.off() |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
161 |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
162 # summary for significant variables |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
163 cat("\n\n- - - - - - - number of significant variables - - - - - - -\n\n") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
164 for(i in 1:nrow(aovAdjPValue)){ |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
165 cat(rownames(aovAdjPValue)[i],"-", |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
166 sum(aovAdjPValue[i,]<=threshold),"significant variable(s)\n") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
167 } |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
168 cat("\nIf some of your factors are missing here, this may be due to\neffects", |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
169 "not estimable; your design may not be balanced enough.\n") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
170 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
171 # -- output / return -- |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
172 write.table(varinfoTab, outputdatapvalue, sep=sep, quote=F, row.names=FALSE) |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
173 |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
174 # log |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
175 cat("\nthreshold:",threshold,"\n") |
7
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
176 cat("result:",ncol(datafiltered),"/",ncol(data),"\n\n") |
8190dfb5a351
planemo upload for repository https://github.com/workflow4metabolomics/anova commit 28838bb8dafd6d286157db77f181ed8a1b586664
lecorguille
parents:
0
diff
changeset
|
177 |
0
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
178 quit("no",status=0) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
179 } |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
180 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
181 # log |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
182 cat("ANOVA\n\n") |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
183 cat("Arguments\n") |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
184 args <- commandArgs(trailingOnly = TRUE) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
185 print(args) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
186 |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
187 listArguments = parseCommandArgs(evaluate=FALSE) |
924ff5a24122
planemo upload commit 0921bc80e825d98964cf7a72c57facdb593ae355-dirty
lecorguille
parents:
diff
changeset
|
188 do.call(anova, listArguments) |