Mercurial > repos > lecorguille > camera_annotate
comparison lib.r @ 13:1c30ff90f3ae draft
planemo upload commit 301d42e88026afdac618f4ec56fc6cbe19e3e419
author | lecorguille |
---|---|
date | Fri, 07 Apr 2017 07:42:18 -0400 |
parents | 7da9252dd983 |
children | a2c49996603e |
comparison
equal
deleted
inserted
replaced
12:9c037181588e | 13:1c30ff90f3ae |
---|---|
1 # lib.r version="2.2.1" | 1 # lib.r |
2 | 2 |
3 #@author G. Le Corguille | |
3 #The function create a pdf from the different png generated by diffreport | 4 #The function create a pdf from the different png generated by diffreport |
4 diffreport_png2pdf <- function(filebase, new_file_path) { | 5 diffreport_png2pdf <- function(filebase) { |
5 | 6 dir.create("pdf") |
6 pdfEicOutput = paste(new_file_path,filebase,"-eic_visible_pdf",sep="") | 7 |
7 pdfBoxOutput = paste(new_file_path,filebase,"-box_visible_pdf",sep="") | 8 pdfEicOutput = paste0("pdf/",filebase,"-eic_pdf.pdf") |
8 | 9 pdfBoxOutput = paste0("pdf/",filebase,"-box_pdf.pdf") |
9 system(paste("gm convert ",filebase,"_eic/*.png ",filebase,"_eic.pdf",sep="")) | 10 |
10 system(paste("gm convert ",filebase,"_box/*.png ",filebase,"_box.pdf",sep="")) | 11 system(paste0("gm convert ",filebase,"_eic/*.png ",pdfEicOutput)) |
11 | 12 system(paste0("gm convert ",filebase,"_box/*.png ",pdfBoxOutput)) |
12 file.copy(paste(filebase,"_eic.pdf",sep=""), pdfEicOutput) | 13 |
13 file.copy(paste(filebase,"_box.pdf",sep=""), pdfBoxOutput) | 14 } |
15 | |
16 #@author G. Le Corguille | |
17 #This function convert if it is required the Retention Time in minutes | |
18 RTSecondToMinute <- function(variableMetadata, convertRTMinute) { | |
19 if (convertRTMinute){ | |
20 #converting the retention times (seconds) into minutes | |
21 print("converting the retention times into minutes in the variableMetadata") | |
22 variableMetadata[,"rt"]=variableMetadata[,"rt"]/60 | |
23 variableMetadata[,"rtmin"]=variableMetadata[,"rtmin"]/60 | |
24 variableMetadata[,"rtmax"]=variableMetadata[,"rtmax"]/60 | |
25 } | |
26 return (variableMetadata) | |
27 } | |
28 | |
29 #@author G. Le Corguille | |
30 #This function format ions identifiers | |
31 formatIonIdentifiers <- function(variableMetadata, numDigitsRT=0, numDigitsMZ=0) { | |
32 splitDeco = strsplit(as.character(variableMetadata$name),"_") | |
33 idsDeco = sapply(splitDeco, function(x) { deco=unlist(x)[2]; if (is.na(deco)) return ("") else return(paste0("_",deco)) }) | |
34 namecustom = make.unique(paste0("M",round(variableMetadata[,"mz"],numDigitsMZ),"T",round(variableMetadata[,"rt"],numDigitsRT),idsDeco)) | |
35 variableMetadata=cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))]) | |
36 return(variableMetadata) | |
14 } | 37 } |
15 | 38 |
16 #The function annotateDiffreport without the corr function which bugs | 39 #The function annotateDiffreport without the corr function which bugs |
17 annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv", dataMatrixOutput="dataMatrix.tsv",new_file_path=NULL) { | 40 annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv", dataMatrixOutput="dataMatrix.tsv") { |
18 # Resolve the bug with x11, with the function png | 41 # Resolve the bug with x11, with the function png |
19 options(bitmapType='cairo') | 42 options(bitmapType='cairo') |
20 | 43 |
21 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. | |
22 res=try(is.null(xset@filled)) | |
23 | |
24 # ------ annot ------- | |
25 listArguments[["calcCiS"]]=as.logical(listArguments[["calcCiS"]]) | |
26 listArguments[["calcIso"]]=as.logical(listArguments[["calcIso"]]) | |
27 listArguments[["calcCaS"]]=as.logical(listArguments[["calcCaS"]]) | |
28 | |
29 #graphMethod parameter bugs where this parameter is not defined in quick=true | |
30 if(listArguments[["quick"]]==TRUE) { | |
31 xa= annotate(object=xset,nSlaves=1,sigma=listArguments[["sigma"]],perfwhm=listArguments[["perfwhm"]],maxcharge=listArguments[["maxcharge"]],maxiso=listArguments[["maxiso"]],minfrac=listArguments[["minfrac"]],ppm=listArguments[["ppm"]],mzabs=listArguments[["mzabs"]],quick=listArguments[["quick"]],polarity=listArguments[["polarity"]],max_peaks=listArguments[["max_peaks"]],intval=listArguments[["intval"]]) | |
32 } | |
33 else { | |
34 xa= annotate(object=xset,nSlaves=1,sigma=listArguments[["sigma"]],perfwhm=listArguments[["perfwhm"]],graphMethod=listArguments[["graphMethod"]],cor_eic_th=listArguments[["cor_eic_th"]],pval=listArguments[["pval"]],calcCiS=listArguments[["calcCiS"]],calcIso=listArguments[["calcIso"]],calcCaS=listArguments[["calcCaS"]],multiplier=listArguments[["multiplier"]],maxcharge=listArguments[["maxcharge"]],maxiso=listArguments[["maxiso"]],minfrac=listArguments[["minfrac"]],ppm=listArguments[["ppm"]],mzabs=listArguments[["mzabs"]],quick=listArguments[["quick"]],polarity=listArguments[["polarity"]],max_peaks=listArguments[["max_peaks"]],intval=listArguments[["intval"]]) | |
35 | |
36 } | |
37 peakList=getPeaklist(xa,intval=listArguments[["intval"]]) | |
38 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); | |
39 | |
40 | |
41 # --- Multi condition : diffreport --- | |
42 diffrep=NULL | |
43 if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) { | |
44 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. | 44 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. |
45 res=try(is.null(xset@filled)) | 45 res=try(is.null(xset@filled)) |
46 classes=levels(sampclass(xset)) | 46 |
47 x=1:(length(classes)-1) | 47 # ------ annot ------- |
48 for (i in seq(along=x) ) { | 48 listArguments[["calcCiS"]]=as.logical(listArguments[["calcCiS"]]) |
49 y=1:(length(classes)) | 49 listArguments[["calcIso"]]=as.logical(listArguments[["calcIso"]]) |
50 for (n in seq(along=y)){ | 50 listArguments[["calcCaS"]]=as.logical(listArguments[["calcCaS"]]) |
51 if(i+n <= length(classes)){ | 51 |
52 filebase=paste(classes[i],class2=classes[i+n],sep="-vs-") | 52 # common parameters |
53 | 53 listArguments4annotate = list(object=xset, |
54 diffrep=diffreport(object=xset,class1=classes[i],class2=classes[i+n],filebase=filebase,eicmax=listArguments[["eicmax"]],eicwidth=listArguments[["eicwidth"]],sortpval=TRUE,value=listArguments[["value"]],h=listArguments[["h"]],w=listArguments[["w"]],mzdec=listArguments[["mzdec"]]) | 54 nSlaves=listArguments[["nSlaves"]],sigma=listArguments[["sigma"]],perfwhm=listArguments[["perfwhm"]], |
55 #combines results | 55 maxcharge=listArguments[["maxcharge"]],maxiso=listArguments[["maxiso"]],minfrac=listArguments[["minfrac"]], |
56 diffreportTSV=merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F) | 56 ppm=listArguments[["ppm"]],mzabs=listArguments[["mzabs"]],quick=listArguments[["quick"]], |
57 diffreportTSV=cbind(diffreportTSV[,!(colnames(diffreportTSV) %in% c(sampnames(xa@xcmsSet)))],diffreportTSV[,(colnames(diffreportTSV) %in% c(sampnames(xa@xcmsSet)))]) | 57 polarity=listArguments[["polarity"]],max_peaks=listArguments[["max_peaks"]],intval=listArguments[["intval"]]) |
58 | 58 |
59 if(listArguments[["sortpval"]]){ | 59 # quick == FALSE |
60 diffreportTSV=diffreportTSV[order(diffreportTSV$pvalue), ] | 60 if(listArguments[["quick"]]==FALSE) { |
61 } | 61 listArguments4annotate = append(listArguments4annotate, |
62 | 62 list(graphMethod=listArguments[["graphMethod"]],cor_eic_th=listArguments[["cor_eic_th"]],pval=listArguments[["pval"]], |
63 if (listArguments[["convert_param"]]){ | 63 calcCiS=listArguments[["calcCiS"]],calcIso=listArguments[["calcIso"]],calcCaS=listArguments[["calcCaS"]])) |
64 #converting the retention times (seconds) into minutes | 64 # no ruleset |
65 diffreportTSV$rt=diffreportTSV$rt/60;diffreportTSV$rtmin=diffreportTSV$rtmin/60; diffreportTSV$rtmax=diffreportTSV$rtmax/60; | 65 if (!is.null(listArguments[["multiplier"]])) { |
66 } | 66 listArguments4annotate = append(listArguments4annotate, |
67 write.table(diffreportTSV, sep="\t", quote=FALSE, row.names=FALSE, file=paste(new_file_path,filebase,"-tabular_visible_tabular",sep="")) | 67 list(multiplier=listArguments[["multiplier"]])) |
68 | 68 } |
69 if (listArguments[["eicmax"]] != 0) { | 69 # ruleset |
70 diffreport_png2pdf(filebase, new_file_path) | 70 else { |
71 } | 71 rulset=read.table(listArguments[["rules"]], h=T, sep=";") |
72 } | 72 if (ncol(rulset) < 4) rulset=read.table(listArguments[["rules"]], h=T, sep="\t") |
73 } | 73 if (ncol(rulset) < 4) rulset=read.table(listArguments[["rules"]], h=T, sep=",") |
74 } | 74 if (ncol(rulset) < 4) { |
75 } | 75 error_message="Your ruleset file seems not well formatted. The column separators accepted are ; , and tabulation" |
76 | 76 print(error_message) |
77 | 77 stop(error_message) |
78 | 78 } |
79 | 79 |
80 # --- variableMetadata --- | 80 listArguments4annotate = append(listArguments4annotate, |
81 variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] | 81 list(rules=rulset)) |
82 # if we have 2 conditions, we keep stat of diffrep | 82 } |
83 if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))==2) { | 83 } |
84 variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F) | 84 |
85 if(exists("listArguments[[\"sortpval\"]]")){ | 85 |
86 variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] | 86 # launch annotate |
87 } | 87 xa = do.call("annotate", listArguments4annotate) |
88 } | 88 peakList=getPeaklist(xa,intval=listArguments[["intval"]]) |
89 | 89 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); |
90 variableMetadataOri=variableMetadata | 90 |
91 if (listArguments[["convert_param"]]){ | 91 # --- dataMatrix --- |
92 #converting the retention times (seconds) into minutes | 92 dataMatrix = peakList[,(make.names(colnames(peakList)) %in% c("name", make.names(sampnames(xa@xcmsSet))))] |
93 print("converting the retention times into minutes in the variableMetadata") | 93 write.table(dataMatrix, sep="\t", quote=FALSE, row.names=FALSE, file=dataMatrixOutput) |
94 variableMetadata$rt=variableMetadata$rt/60;variableMetadata$rtmin=variableMetadata$rtmin/60; variableMetadata$rtmax=variableMetadata$rtmax/60; | 94 |
95 } | 95 |
96 #Transform metabolites name | 96 # --- Multi condition : diffreport --- |
97 variableMetadata$name= paste("M",round(variableMetadata$mz,digits=listArguments[["num_digits"]]),"T",round(variableMetadata$rt),sep="") | 97 diffrepOri=NULL |
98 write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) | 98 if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) { |
99 | 99 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. |
100 # --- dataMatrix --- | 100 res=try(is.null(xset@filled)) |
101 dataMatrix = peakList[,(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] | 101 classes=levels(sampclass(xset)) |
102 dataMatrix=cbind(peakList$name,dataMatrix); colnames(dataMatrix)[1] = c("name"); | 102 x=1:(length(classes)-1) |
103 | 103 for (i in seq(along=x) ) { |
104 if (listArguments[["convert_param"]]){ | 104 y=1:(length(classes)) |
105 #converting the retention times (seconds) into minutes | 105 for (n in seq(along=y)){ |
106 print("converting the retention times into minutes in the dataMatrix ids") | 106 if(i+n <= length(classes)){ |
107 peakList$rt=peakList$rt/60 | 107 filebase=paste(classes[i],class2=classes[i+n],sep="-vs-") |
108 } | 108 |
109 dataMatrix$name= paste("M",round(peakList$mz,digits=listArguments[["num_digits"]]),"T",round(peakList$rt),sep="") | 109 diffrep=diffreport(object=xset,class1=classes[i],class2=classes[i+n],filebase=filebase,eicmax=listArguments[["eicmax"]],eicwidth=listArguments[["eicwidth"]],sortpval=TRUE,value=listArguments[["value"]],h=listArguments[["h"]],w=listArguments[["w"]],mzdec=listArguments[["mzdec"]]) |
110 write.table(dataMatrix, sep="\t", quote=FALSE, row.names=FALSE, file=dataMatrixOutput) | 110 |
111 | 111 diffrepOri = diffrep |
112 return(list("xa"=xa,"diffrep"=diffrep,"variableMetadata"=variableMetadataOri)); | 112 |
113 | 113 # renamming of the column rtmed to rt to fit with camera peaklist function output |
114 } | 114 colnames(diffrep)[colnames(diffrep)=="rtmed"] <- "rt" |
115 | 115 colnames(diffrep)[colnames(diffrep)=="mzmed"] <- "mz" |
116 | 116 |
117 combinexsAnnos_function <- function(xaP, xaN, listOFlistArgumentsP,listOFlistArgumentsN, diffrepP=NULL,diffrepN=NULL,convert_param=FALSE,pos=TRUE,tol=2,ruleset=NULL,keep_meta=TRUE, variableMetadataOutput="variableMetadata.tsv"){ | 117 # combines results and reorder columns |
118 | 118 diffrep = merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F) |
119 #Load the two Rdata to extract the xset objects from positive and negative mode | 119 diffrep = cbind(diffrep[,!(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))],diffrep[,(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))]) |
120 cat("\tObject xset from positive mode\n") | 120 |
121 print(xaP) | 121 diffrep = RTSecondToMinute(diffrep, listArguments[["convertRTMinute"]]) |
122 cat("\n") | 122 diffrep = formatIonIdentifiers(diffrep, numDigitsRT=listArguments[["numDigitsRT"]], numDigitsMZ=listArguments[["numDigitsMZ"]]) |
123 | 123 |
124 cat("\tObject xset from negative mode\n") | 124 if(listArguments[["sortpval"]]){ |
125 print(xaN) | 125 diffrep=diffrep[order(diffrep$pvalue), ] |
126 cat("\n") | 126 } |
127 | 127 |
128 cat("\n") | 128 dir.create("tabular") |
129 cat("\tCombining...\n") | 129 write.table(diffrep, sep="\t", quote=FALSE, row.names=FALSE, file=paste("tabular/",filebase,"_tsv.tabular",sep="")) |
130 #Convert the string to numeric for creating matrix | 130 |
131 row=as.numeric(strsplit(ruleset,",")[[1]][1]) | 131 if (listArguments[["eicmax"]] != 0) { |
132 column=as.numeric(strsplit(ruleset,",")[[1]][2]) | 132 diffreport_png2pdf(filebase) |
133 ruleset=cbind(row,column) | 133 } |
134 #Test if the file comes from an older version tool | 134 } |
135 if ((!is.null(xaP)) & (!is.null(xaN))) { | 135 } |
136 #Launch the combinexsannos function from CAMERA | 136 } |
137 cAnnot=combinexsAnnos(xaP, xaN,pos=pos,tol=tol,ruleset=ruleset) | 137 } |
138 } else { | 138 |
139 stop("You must relauch the CAMERA.annotate step with the lastest version.") | 139 |
140 } | 140 # --- variableMetadata --- |
141 | 141 variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] |
142 | 142 variableMetadata = RTSecondToMinute(variableMetadata, listArguments[["convertRTMinute"]]) |
143 | 143 variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=listArguments[["numDigitsRT"]], numDigitsMZ=listArguments[["numDigitsMZ"]]) |
144 if(pos){ | 144 # if we have 2 conditions, we keep stat of diffrep |
145 xa=xaP | 145 if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))==2) { |
146 listOFlistArgumentsP=listOFlistArguments | 146 variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F) |
147 mode="neg. Mode" | 147 if(exists("listArguments[[\"sortpval\"]]")){ |
148 } else { | 148 variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] |
149 xa=xaN | 149 } |
150 listOFlistArgumentsN=listOFlistArguments | 150 } |
151 mode="pos. Mode" | 151 |
152 } | 152 variableMetadataOri=variableMetadata |
153 intval = "into"; for (steps in names(listOFlistArguments)) { if (!is.null(listOFlistArguments[[steps]]$intval)) intval = listOFlistArguments[[steps]]$intval } | 153 write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) |
154 peakList=getPeaklist(xa,intval=intval) | 154 |
155 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); | 155 return(list("xa"=xa,"diffrep"=diffrepOri,"variableMetadata"=variableMetadataOri)); |
156 variableMetadata=cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup",mode)]); | 156 |
157 variableMetadata=variableMetadata[,!(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))] | 157 } |
158 | 158 |
159 #Test if there are more than two classes (conditions) | 159 |
160 if ( nlevels(sampclass(xaP@xcmsSet))==2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) { | 160 combinexsAnnos_function <- function(xaP, xaN, listOFlistArgumentsP,listOFlistArgumentsN, diffrepP=NULL,diffrepN=NULL,pos=TRUE,tol=2,ruleset=NULL,keep_meta=TRUE, convertRTMinute=F, numDigitsMZ=0, numDigitsRT=0, variableMetadataOutput="variableMetadata.tsv"){ |
161 diffrepP = diffrepP[,c("name","fold","tstat","pvalue")]; colnames(diffrepP) = paste("P.",colnames(diffrepP),sep="") | 161 |
162 diffrepN = diffrepN[,c("name","fold","tstat","pvalue")]; colnames(diffrepN) = paste("N.",colnames(diffrepN),sep="") | 162 #Load the two Rdata to extract the xset objects from positive and negative mode |
163 | 163 cat("\tObject xset from positive mode\n") |
164 variableMetadata = merge(variableMetadata, diffrepP, by.x="name", by.y="P.name") | 164 print(xaP) |
165 variableMetadata = merge(variableMetadata, diffrepN, by.x="name", by.y="N.name") | 165 cat("\n") |
166 } | 166 |
167 | 167 cat("\tObject xset from negative mode\n") |
168 rownames(variableMetadata) = NULL | 168 print(xaN) |
169 #TODO: checker | 169 cat("\n") |
170 #colnames(variableMetadata)[1:2] = c("name","mz/rt"); | 170 |
171 | 171 cat("\n") |
172 #If the user want to convert the retention times (seconds) into minutes. | 172 cat("\tCombining...\n") |
173 if (listArguments[["convert_param"]]){ | 173 #Convert the string to numeric for creating matrix |
174 #converting the retention times (seconds) into minutes | 174 row=as.numeric(strsplit(ruleset,",")[[1]][1]) |
175 cat("\tConverting the retention times into minutes\n") | 175 column=as.numeric(strsplit(ruleset,",")[[1]][2]) |
176 variableMetadata$rtmed=cAnnot$rt/60; variableMetadata$rtmin=cAnnot$rtmin/60; variableMetadata$rtmax=cAnnot$rtmax/60; | 176 ruleset=cbind(row,column) |
177 } | 177 #Test if the file comes from an older version tool |
178 | 178 if ((!is.null(xaP)) & (!is.null(xaN))) { |
179 #If the user want to keep only the metabolites which match a difference | 179 #Launch the combinexsannos function from CAMERA |
180 if(keep_meta){ | 180 cAnnot=combinexsAnnos(xaP, xaN,pos=pos,tol=tol,ruleset=ruleset) |
181 variableMetadata=variableMetadata[variableMetadata[,c(mode)]!="",] | 181 } else { |
182 } | 182 stop("You must relauch the CAMERA.annotate step with the lastest version.") |
183 | 183 } |
184 #Write the output into a tsv file | 184 |
185 write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) | 185 if(pos){ |
186 return(variableMetadata); | 186 xa=xaP |
187 | 187 listOFlistArgumentsP=listOFlistArguments |
188 } | 188 mode="neg. Mode" |
189 } else { | |
190 xa=xaN | |
191 listOFlistArgumentsN=listOFlistArguments | |
192 mode="pos. Mode" | |
193 } | |
194 | |
195 peakList=getPeaklist(xa) | |
196 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); | |
197 variableMetadata=cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup",mode)]); | |
198 variableMetadata=variableMetadata[,!(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))] | |
199 | |
200 #Test if there are more than two classes (conditions) | |
201 if ( nlevels(sampclass(xaP@xcmsSet))==2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) { | |
202 diffrepP = diffrepP[,c("name","fold","tstat","pvalue")]; colnames(diffrepP) = paste("P.",colnames(diffrepP),sep="") | |
203 diffrepN = diffrepN[,c("name","fold","tstat","pvalue")]; colnames(diffrepN) = paste("N.",colnames(diffrepN),sep="") | |
204 | |
205 variableMetadata = merge(variableMetadata, diffrepP, by.x="name", by.y="P.name") | |
206 variableMetadata = merge(variableMetadata, diffrepN, by.x="name", by.y="N.name") | |
207 } | |
208 | |
209 rownames(variableMetadata) = NULL | |
210 #TODO: checker | |
211 #colnames(variableMetadata)[1:2] = c("name","mz/rt"); | |
212 | |
213 variableMetadata = RTSecondToMinute(variableMetadata, convertRTMinute) | |
214 variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=numDigitsRT, numDigitsMZ=numDigitsMZ) | |
215 | |
216 #If the user want to keep only the metabolites which match a difference | |
217 if(keep_meta){ | |
218 variableMetadata=variableMetadata[variableMetadata[,c(mode)]!="",] | |
219 } | |
220 | |
221 #Write the output into a tsv file | |
222 write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) | |
223 return(variableMetadata); | |
224 | |
225 } | |
226 | |
227 # This function get the raw file path from the arguments | |
228 getRawfilePathFromArguments <- function(singlefile, zipfile, listArguments) { | |
229 if (!is.null(listArguments[["zipfile"]])) zipfile = listArguments[["zipfile"]] | |
230 if (!is.null(listArguments[["zipfilePositive"]])) zipfile = listArguments[["zipfilePositive"]] | |
231 if (!is.null(listArguments[["zipfileNegative"]])) zipfile = listArguments[["zipfileNegative"]] | |
232 | |
233 if (!is.null(listArguments[["singlefile_galaxyPath"]])) { | |
234 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPath"]]; | |
235 singlefile_sampleNames = listArguments[["singlefile_sampleName"]] | |
236 } | |
237 if (!is.null(listArguments[["singlefile_galaxyPathPositive"]])) { | |
238 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathPositive"]]; | |
239 singlefile_sampleNames = listArguments[["singlefile_sampleNamePositive"]] | |
240 } | |
241 if (!is.null(listArguments[["singlefile_galaxyPathNegative"]])) { | |
242 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathNegative"]]; | |
243 singlefile_sampleNames = listArguments[["singlefile_sampleNameNegative"]] | |
244 } | |
245 if (exists("singlefile_galaxyPaths")){ | |
246 singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,",")) | |
247 singlefile_sampleNames = unlist(strsplit(singlefile_sampleNames,",")) | |
248 | |
249 singlefile=NULL | |
250 for (singlefile_galaxyPath_i in seq(1:length(singlefile_galaxyPaths))) { | |
251 singlefile_galaxyPath=singlefile_galaxyPaths[singlefile_galaxyPath_i] | |
252 singlefile_sampleName=singlefile_sampleNames[singlefile_galaxyPath_i] | |
253 singlefile[[singlefile_sampleName]] = singlefile_galaxyPath | |
254 } | |
255 } | |
256 for (argument in c("zipfile","zipfilePositive","zipfileNegative","singlefile_galaxyPath","singlefile_sampleName","singlefile_galaxyPathPositive","singlefile_sampleNamePositive","singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { | |
257 listArguments[[argument]]=NULL | |
258 } | |
259 return(list(zipfile=zipfile, singlefile=singlefile, listArguments=listArguments)) | |
260 } | |
261 | |
262 | |
263 # This function retrieve the raw file in the working directory | |
264 # - if zipfile: unzip the file with its directory tree | |
265 # - if singlefiles: set symlink with the good filename | |
266 retrieveRawfileInTheWorkingDirectory <- function(singlefile, zipfile) { | |
267 if(!is.null(singlefile) && (length("singlefile")>0)) { | |
268 for (singlefile_sampleName in names(singlefile)) { | |
269 singlefile_galaxyPath = singlefile[[singlefile_sampleName]] | |
270 if(!file.exists(singlefile_galaxyPath)){ | |
271 error_message=paste("Cannot access the sample:",singlefile_sampleName,"located:",singlefile_galaxyPath,". Please, contact your administrator ... if you have one!") | |
272 print(error_message); stop(error_message) | |
273 } | |
274 | |
275 file.symlink(singlefile_galaxyPath,singlefile_sampleName) | |
276 } | |
277 directory = "." | |
278 | |
279 } | |
280 if(!is.null(zipfile) && (zipfile!="")) { | |
281 if(!file.exists(zipfile)){ | |
282 error_message=paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!") | |
283 print(error_message) | |
284 stop(error_message) | |
285 } | |
286 | |
287 #list all file in the zip file | |
288 #zip_files=unzip(zipfile,list=T)[,"Name"] | |
289 | |
290 #unzip | |
291 suppressWarnings(unzip(zipfile, unzip="unzip")) | |
292 | |
293 #get the directory name | |
294 filesInZip=unzip(zipfile, list=T); | |
295 directories=unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1]))); | |
296 directories=directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] | |
297 directory = "." | |
298 if (length(directories) == 1) directory = directories | |
299 | |
300 cat("files_root_directory\t",directory,"\n") | |
301 | |
302 } | |
303 return (directory) | |
304 } |