Mercurial > repos > yguitton > metams_rungc
annotate lib_metams.r @ 0:2066efbafd7c draft
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
author | yguitton |
---|---|
date | Wed, 13 Jul 2016 06:46:45 -0400 |
parents | |
children | c75532b75ba1 |
rev | line source |
---|---|
0
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
1 # lib_metams.r version 0.99.6 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
2 # R function for metaMS runGC under W4M |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
3 # author Yann GUITTON CNRS IRISA/LINA Idealg project 2014-2015 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
4 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
5 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
6 ##ADDITIONS FROM Y. Guitton |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
7 getBPC <- function(file,rtcor=NULL, ...) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
8 object <- xcmsRaw(file) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
9 sel <- profRange(object, ...) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
10 cbind(if (is.null(rtcor)) object@scantime[sel$scanidx] else rtcor ,xcms:::colMax(object@env$profile[sel$massidx,sel$scanidx,drop=FALSE])) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
11 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
12 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
13 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
14 getBPC2s <- function (files, pdfname="BPCs.pdf", rt = c("raw","corrected"), scanrange=NULL) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
15 require(xcms) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
16 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
17 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
18 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
19 #create sampleMetadata, get sampleMetadata and class |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
20 sampleMetadata<-xcms:::phenoDataFromPaths(files) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
21 class<-class<-as.vector(levels(sampleMetadata[,"class"])) #create phenoData like table |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
22 classnames<-vector("list",length(class)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
23 for (i in 1:length(class)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
24 classnames[[i]]<-which( sampleMetadata[,1]==class[i]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
25 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
26 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
27 N <- dim(sampleMetadata)[1] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
28 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
29 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
30 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
31 TIC <- vector("list",N) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
32 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
33 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
34 for (j in 1:N) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
35 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
36 cat(files[j],"\n") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
37 TIC[[j]] <- getBPC(files[j]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
38 #good for raw |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
39 # seems strange for corrected |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
40 #errors if scanrange used in xcmsSetgeneration |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
41 if (!is.null(xcmsSet) && rt == "corrected") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
42 rtcor <- xcmsSet@rt$corrected[[j]] else |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
43 rtcor <- NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
44 TIC[[j]] <- getBPC(files[j],rtcor=rtcor) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
45 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
46 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
47 pdf(pdfname,w=16,h=10) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
48 cols <- rainbow(N) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
49 lty = 1:N |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
50 pch = 1:N |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
51 #search for max x and max y in BPCs |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
52 xlim = range(sapply(TIC, function(x) range(x[,1]))) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
53 ylim = range(sapply(TIC, function(x) range(x[,2]))) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
54 ylim = c(-ylim[2], ylim[2]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
55 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
56 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
57 ##plot start |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
58 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
59 if (length(class)>2){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
60 for (k in 1:(length(class)-1)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
61 for (l in (k+1):length(class)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
62 print(paste(class[k],"vs",class[l],sep=" ")) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
63 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Base Peak Chromatograms \n","BPCs_",class[k]," vs ",class[l], sep=""), xlab = "Retention Time (min)", ylab = "BPC") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
64 colvect<-NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
65 for (j in 1:length(classnames[[k]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
66 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
67 tic <- TIC[[classnames[[k]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
68 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
69 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
70 colvect<-append(colvect,cols[classnames[[k]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
71 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
72 for (j in 1:length(classnames[[l]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
73 # i=class2names[j] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
74 tic <- TIC[[classnames[[l]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
75 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
76 colvect<-append(colvect,cols[classnames[[l]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
77 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
78 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col = colvect, lty = lty, pch = pch) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
79 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
80 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
81 }#end if length >2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
82 if (length(class)==2){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
83 k=1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
84 l=2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
85 colvect<-NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
86 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Base Peak Chromatograms \n","BPCs_",class[k],"vs",class[l], sep=""), xlab = "Retention Time (min)", ylab = "BPC") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
87 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
88 for (j in 1:length(classnames[[k]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
89 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
90 tic <- TIC[[classnames[[k]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
91 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
92 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
93 colvect<-append(colvect,cols[classnames[[k]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
94 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
95 for (j in 1:length(classnames[[l]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
96 # i=class2names[j] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
97 tic <- TIC[[classnames[[l]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
98 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
99 colvect<-append(colvect,cols[classnames[[l]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
100 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
101 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col = colvect, lty = lty, pch = pch) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
102 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
103 }#end length ==2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
104 if (length(class)==1){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
105 k=1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
106 ylim = range(sapply(TIC, function(x) range(x[,2]))) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
107 colvect<-NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
108 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Base Peak Chromatograms \n","BPCs_",class[k], sep=""), xlab = "Retention Time (min)", ylab = "BPC") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
109 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
110 for (j in 1:length(classnames[[k]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
111 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
112 tic <- TIC[[classnames[[k]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
113 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
114 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
115 colvect<-append(colvect,cols[classnames[[k]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
116 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
117 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
118 legend("topright",paste(basename(files[c(classnames[[k]])])), col = colvect, lty = lty, pch = pch) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
119 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
120 }#end length ==1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
121 dev.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
122 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
123 # invisible(TIC) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
124 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
125 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
126 getTIC <- function(file,rtcor=NULL) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
127 object <- xcmsRaw(file) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
128 cbind(if (is.null(rtcor)) object@scantime else rtcor, rawEIC(object,mzrange=range(object@env$mz))$intensity) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
129 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
130 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
131 ## |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
132 ## overlay TIC from all files in current folder or from xcmsSet, create pdf |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
133 ## |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
134 getTIC2s <- function(files, pdfname="TICs.pdf", rt=c("raw","corrected")) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
135 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
136 #create sampleMetadata, get sampleMetadata and class |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
137 sampleMetadata<-xcms:::phenoDataFromPaths(files) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
138 class<-class<-as.vector(levels(sampleMetadata[,"class"])) #create phenoData like table |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
139 classnames<-vector("list",length(class)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
140 for (i in 1:length(class)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
141 classnames[[i]]<-which( sampleMetadata[,1]==class[i]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
142 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
143 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
144 N <- dim(sampleMetadata)[1] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
145 TIC <- vector("list",N) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
146 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
147 for (i in 1:N) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
148 cat(files[i],"\n") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
149 if (!is.null(xcmsSet) && rt == "corrected") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
150 rtcor <- xcmsSet@rt$corrected[[i]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
151 else |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
152 rtcor <- NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
153 TIC[[i]] <- getTIC(files[i],rtcor=rtcor) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
154 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
155 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
156 pdf(pdfname,w=16,h=10) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
157 cols <- rainbow(N) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
158 lty = 1:N |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
159 pch = 1:N |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
160 #search for max x and max y in TICs |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
161 xlim = range(sapply(TIC, function(x) range(x[,1]))) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
162 ylim = range(sapply(TIC, function(x) range(x[,2]))) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
163 ylim = c(-ylim[2], ylim[2]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
164 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
165 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
166 ##plot start |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
167 if (length(class)>2){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
168 for (k in 1:(length(class)-1)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
169 for (l in (k+1):length(class)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
170 print(paste(class[k],"vs",class[l],sep=" ")) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
171 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Total Ion Chromatograms \n","TICs_",class[k]," vs ",class[l], sep=""), xlab = "Retention Time (min)", ylab = "TIC") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
172 colvect<-NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
173 for (j in 1:length(classnames[[k]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
174 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
175 tic <- TIC[[classnames[[k]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
176 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
177 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
178 colvect<-append(colvect,cols[classnames[[k]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
179 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
180 for (j in 1:length(classnames[[l]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
181 # i=class2names[j] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
182 tic <- TIC[[classnames[[l]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
183 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
184 colvect<-append(colvect,cols[classnames[[l]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
185 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
186 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col = colvect, lty = lty, pch = pch) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
187 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
188 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
189 }#end if length >2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
190 if (length(class)==2){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
191 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
192 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
193 k=1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
194 l=2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
195 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
196 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Total Ion Chromatograms \n","TICs_",class[k],"vs",class[l], sep=""), xlab = "Retention Time (min)", ylab = "TIC") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
197 colvect<-NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
198 for (j in 1:length(classnames[[k]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
199 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
200 tic <- TIC[[classnames[[k]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
201 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
202 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
203 colvect<-append(colvect,cols[classnames[[k]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
204 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
205 for (j in 1:length(classnames[[l]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
206 # i=class2names[j] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
207 tic <- TIC[[classnames[[l]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
208 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
209 colvect<-append(colvect,cols[classnames[[l]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
210 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
211 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col = colvect, lty = lty, pch = pch) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
212 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
213 }#end length ==2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
214 if (length(class)==1){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
215 k=1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
216 ylim = range(sapply(TIC, function(x) range(x[,2]))) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
217 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
218 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Total Ion Chromatograms \n","TICs_",class[k], sep=""), xlab = "Retention Time (min)", ylab = "TIC") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
219 colvect<-NULL |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
220 for (j in 1:length(classnames[[k]])) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
221 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
222 tic <- TIC[[classnames[[k]][j]]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
223 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
224 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
225 colvect<-append(colvect,cols[classnames[[k]][j]]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
226 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
227 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
228 legend("topright",paste(basename(files[c(classnames[[k]])])), col = colvect, lty = lty, pch = pch) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
229 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
230 }#end length ==1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
231 dev.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
232 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
233 # invisible(TIC) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
234 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
235 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
236 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
237 ##addition for quality control of peak picking |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
238 #metaMS EIC and pspectra plotting option |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
239 #version 20150512 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
240 #only for Galaxy |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
241 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
242 plotUnknowns<-function(resGC, unkn=""){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
243 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
244 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
245 ##Annotation table each value is a pcgrp associated to the unknown |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
246 ##NOTE pcgrp index are different between xcmsSet and resGC due to filtering steps in metaMS |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
247 ##R. Wehrens give me some clues on that and we found a correction |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
248 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
249 mat<-matrix(ncol=length(resGC$xset), nrow=dim(resGC$PeakTable)[1]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
250 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
251 for (j in 1: length(resGC$xset)){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
252 test<-resGC$annotation[[j]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
253 print(paste("j=",j)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
254 for (i in 1:dim(test)[1]){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
255 if (as.numeric(row.names(test)[i])>dim(mat)[1]){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
256 next |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
257 } else { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
258 mat[as.numeric(row.names(test)[i]),j]<-test[i,1] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
259 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
260 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
261 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
262 colnames(mat)<-colnames(resGC$PeakTable[,c((which(colnames(resGC$PeakTable)=="rt"|colnames(resGC$PeakTable)=="RI")[length(which(colnames(resGC$PeakTable)=="rt"|colnames(resGC$PeakTable)=="RI"))]+1):dim(resGC$PeakTable)[2])]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
263 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
264 #debug |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
265 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
266 # print(dim(mat)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
267 # print(mat[1:3,]) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
268 # write.table(mat, file="myannotationtable.tsv", sep="\t", row.names=FALSE) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
269 #correction of annotation matrix due to pcgrp removal by quality check in runGCresult |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
270 #matrix of correspondance between an@pspectra and filtered pspectra from runGC |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
271 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
272 allPCGRPs <- |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
273 lapply(1:length(resGC$xset), |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
274 function(i) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
275 an <- resGC$xset[[i]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
276 huhn <- an@pspectra[which(sapply(an@pspectra, length) >= |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
277 metaSetting(resGC$settings, |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
278 "DBconstruction.minfeat"))] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
279 matCORR<-cbind(1:length(huhn), match(huhn, an@pspectra)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
280 }) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
281 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
282 if (unkn[1]==""){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
283 #plot EIC and spectra for all unknown for comparative purpose |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
284 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
285 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
286 par (mar=c(5, 4, 4, 2) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
287 for (l in 1:dim(resGC$PeakTable)[1]){ #l=2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
288 #recordPlot |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
289 perpage=3 #if change change layout also! |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
290 num.plots <- ceiling(dim(mat)[2]/perpage) #three pcgroup per page |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
291 my.plots <- vector(num.plots, mode='list') |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
292 dev.new(width=21/2.54, height=29.7/2.54, file=paste("Unknown_",l,".pdf", sep="")) #A4 pdf |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
293 # par(mfrow=c(perpage,2)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
294 layout(matrix(c(1,1,2,3,4,4,5,6,7,7,8,9), 6, 2, byrow = TRUE), widths=rep(c(1,1),perpage), heights=rep(c(1,5),perpage)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
295 # layout.show(6) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
296 oma.saved <- par("oma") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
297 par(oma = rep.int(0, 4)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
298 par(oma = oma.saved) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
299 o.par <- par(mar = rep.int(0, 4)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
300 on.exit(par(o.par)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
301 stop=0 #initialize |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
302 for (i in 1:num.plots) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
303 start=stop+1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
304 stop=start+perpage-1 # |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
305 for (c in start:stop){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
306 if (c <=dim(mat)[2]){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
307 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
308 #get sample name |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
309 sampname<-basename(resGC$xset[[c]]@xcmsSet@filepaths) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
310 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
311 #remove .cdf, .mzXML filepattern |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
312 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]", |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
313 "[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
314 filepattern <- paste(paste("\\.", filepattern, "$", sep = ""), |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
315 collapse = "|") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
316 sampname<-gsub(filepattern, "",sampname) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
317 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
318 title1<-paste("unknown", l,"from",sampname, sep=" ") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
319 an<-resGC$xset[[c]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
320 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
321 par (mar=c(0, 0, 0, 0) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
322 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
323 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
324 text(0.5, 0.5, title1, cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
325 if (!is.na(mat[l,c])){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
326 pcgrp=allPCGRPs[[c]][which(allPCGRPs[[c]][,1]==mat[l,c]),2] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
327 if (pcgrp!=mat[l,c]) print ("pcgrp changed") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
328 par (mar=c(3, 2.5, 3, 1.5) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
329 plotEICs(an, pspec=pcgrp, maxlabel=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
330 plotPsSpectrum(an, pspec=pcgrp, maxlabel=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
331 } else { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
332 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
333 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
334 text(0.5, 0.5, "NOT FOUND", cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
335 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
336 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
337 text(0.5, 0.5, "NOT FOUND", cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
338 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
339 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
340 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
341 # my.plots[[i]] <- recordPlot() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
342 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
343 graphics.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
344 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
345 # pdf(file=paste("Unknown_",l,".pdf", sep=""), onefile=TRUE) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
346 # for (my.plot in my.plots) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
347 # replayPlot(my.plot) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
348 # } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
349 # my.plots |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
350 # graphics.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
351 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
352 }#end for l |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
353 }#end if unkn="" |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
354 else{ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
355 par (mar=c(5, 4, 4, 2) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
356 l=unkn |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
357 if (length(l)==1){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
358 #recordPlot |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
359 perpage=3 #if change change layout also! |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
360 num.plots <- ceiling(dim(mat)[2]/perpage) #three pcgroup per page |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
361 my.plots <- vector(num.plots, mode='list') |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
362 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
363 dev.new(width=21/2.54, height=29.7/2.54, file=paste("Unknown_",l,".pdf", sep="")) #A4 pdf |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
364 # par(mfrow=c(perpage,2)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
365 layout(matrix(c(1,1,2,3,4,4,5,6,7,7,8,9), 6, 2, byrow = TRUE), widths=rep(c(1,1),perpage), heights=rep(c(1,5),perpage)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
366 # layout.show(6) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
367 oma.saved <- par("oma") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
368 par(oma = rep.int(0, 4)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
369 par(oma = oma.saved) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
370 o.par <- par(mar = rep.int(0, 4)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
371 on.exit(par(o.par)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
372 stop=0 #initialize |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
373 for (i in 1:num.plots) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
374 start=stop+1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
375 stop=start+perpage-1 # |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
376 for (c in start:stop){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
377 if (c <=dim(mat)[2]){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
378 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
379 #get sample name |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
380 sampname<-basename(resGC$xset[[c]]@xcmsSet@filepaths) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
381 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
382 #remove .cdf, .mzXML filepattern |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
383 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]", "[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
384 filepattern <- paste(paste("\\.", filepattern, "$", sep = ""), collapse = "|") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
385 sampname<-gsub(filepattern, "",sampname) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
386 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
387 title1<-paste("unknown", l,"from",sampname, sep=" ") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
388 an<-resGC$xset[[c]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
389 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
390 par (mar=c(0, 0, 0, 0) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
391 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
392 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
393 text(0.5, 0.5, title1, cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
394 if (!is.na(mat[l,c])){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
395 pcgrp=allPCGRPs[[c]][which(allPCGRPs[[c]][,1]==mat[l,c]),2] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
396 if (pcgrp!=mat[l,c]) print ("pcgrp changed") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
397 par (mar=c(3, 2.5, 3, 1.5) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
398 plotEICs(an, pspec=pcgrp, maxlabel=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
399 plotPsSpectrum(an, pspec=pcgrp, maxlabel=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
400 } else { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
401 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
402 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
403 text(0.5, 0.5, "NOT FOUND", cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
404 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
405 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
406 text(0.5, 0.5, "NOT FOUND", cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
407 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
408 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
409 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
410 # my.plots[[i]] <- recordPlot() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
411 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
412 graphics.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
413 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
414 # pdf(file=paste("Unknown_",l,".pdf", sep=""), onefile=TRUE) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
415 # for (my.plot in my.plots) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
416 # replayPlot(my.plot) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
417 # } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
418 # my.plots |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
419 # graphics.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
420 } else { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
421 par (mar=c(5, 4, 4, 2) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
422 for (l in 1:length(unkn)){ #l=2 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
423 #recordPlot |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
424 perpage=3 #if change change layout also! |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
425 num.plots <- ceiling(dim(mat)[2]/perpage) #three pcgroup per page |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
426 my.plots <- vector(num.plots, mode='list') |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
427 dev.new(width=21/2.54, height=29.7/2.54, file=paste("Unknown_",unkn[l],".pdf", sep="")) #A4 pdf |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
428 # par(mfrow=c(perpage,2)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
429 layout(matrix(c(1,1,2,3,4,4,5,6,7,7,8,9), 6, 2, byrow = TRUE), widths=rep(c(1,1),perpage), heights=rep(c(1,5),perpage)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
430 # layout.show(6) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
431 oma.saved <- par("oma") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
432 par(oma = rep.int(0, 4)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
433 par(oma = oma.saved) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
434 o.par <- par(mar = rep.int(0, 4)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
435 on.exit(par(o.par)) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
436 stop=0 #initialize |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
437 for (i in 1:num.plots) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
438 start=stop+1 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
439 stop=start+perpage-1 # |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
440 for (c in start:stop){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
441 if (c <=dim(mat)[2]){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
442 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
443 #get sample name |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
444 sampname<-basename(resGC$xset[[c]]@xcmsSet@filepaths) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
445 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
446 #remove .cdf, .mzXML filepattern |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
447 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]", "[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
448 filepattern <- paste(paste("\\.", filepattern, "$", sep = ""), collapse = "|") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
449 sampname<-gsub(filepattern, "",sampname) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
450 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
451 title1<-paste("unknown",unkn[l],"from",sampname, sep=" ") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
452 an<-resGC$xset[[c]] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
453 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
454 par (mar=c(0, 0, 0, 0) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
455 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
456 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
457 text(0.5, 0.5, title1, cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
458 if (!is.na(mat[unkn[l],c])){ |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
459 pcgrp=allPCGRPs[[c]][which(allPCGRPs[[c]][,1]==mat[unkn[l],c]),2] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
460 if (pcgrp!=mat[unkn[l],c]) print ("pcgrp changed") |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
461 par (mar=c(3, 2.5, 3, 1.5) + 0.1) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
462 plotEICs(an, pspec=pcgrp, maxlabel=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
463 plotPsSpectrum(an, pspec=pcgrp, maxlabel=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
464 } else { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
465 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
466 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
467 text(0.5, 0.5, "NOT FOUND", cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
468 plot.new() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
469 box() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
470 text(0.5, 0.5, "NOT FOUND", cex=2) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
471 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
472 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
473 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
474 # my.plots[[i]] <- recordPlot() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
475 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
476 graphics.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
477 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
478 # pdf(file=paste("Unknown_",unkn[l],".pdf", sep=""), onefile=TRUE) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
479 # for (my.plot in my.plots) { |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
480 # replayPlot(my.plot) |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
481 # } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
482 # my.plots |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
483 # graphics.off() |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
484 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
485 }#end for unkn[l] |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
486 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
487 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
488 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
489 } |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
490 } #end function |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
491 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
492 |
2066efbafd7c
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 6384fcf4496a64affe0b8a173c3f7ea09a275ffb
yguitton
parents:
diff
changeset
|
493 |