comparison lib.r @ 39:db9bc2c27a0a draft

planemo upload commit d51a0d0a26833671b79711ee18d782e84f301e76
author workflow4metabolomics
date Fri, 26 Jul 2019 16:00:18 -0400
parents 636e36a64d31
children 3d943f088143
comparison
equal deleted inserted replaced
38:2184c0435edf 39:db9bc2c27a0a
1 # lib.r 1 # lib.r
2
3 #@author G. Le Corguille
4 # solve an issue with batch if arguments are logical TRUE/FALSE
5 parseCommandArgs <- function(...) {
6 args <- batch::parseCommandArgs(...)
7 for (key in names(args)) {
8 if (args[key] %in% c("TRUE","FALSE"))
9 args[key] = as.logical(args[key])
10 }
11 return(args)
12 }
13
14 #@author G. Le Corguille
15 # This function will
16 # - load the packages
17 # - display the sessionInfo
18 loadAndDisplayPackages <- function(pkgs) {
19 for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE)))
20
21 sessioninfo = sessionInfo()
22 cat(sessioninfo$R.version$version.string,"\n")
23 cat("Main packages:\n")
24 for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n")
25 cat("Other loaded packages:\n")
26 for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n")
27 }
2 28
3 # This function retrieve a xset like object 29 # This function retrieve a xset like object
4 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr 30 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr
5 getxcmsSetObject <- function(xobject) { 31 getxcmsSetObject <- function(xobject) {
6 # XCMS 1.x 32 # XCMS 1.x
67 variableMetadata=cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))]) 93 variableMetadata=cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))])
68 return(variableMetadata) 94 return(variableMetadata)
69 } 95 }
70 96
71 #The function annotateDiffreport without the corr function which bugs 97 #The function annotateDiffreport without the corr function which bugs
72 annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv") { 98 annotatediff <- function(xset=xset, args=args, variableMetadataOutput="variableMetadata.tsv") {
73 # Resolve the bug with x11, with the function png 99 # Resolve the bug with x11, with the function png
74 options(bitmapType='cairo') 100 options(bitmapType='cairo')
75 101
76 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. 102 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped.
77 res=try(is.null(xset@filled)) 103 res=try(is.null(xset@filled))
78 104
79 # ------ annot ------- 105 # ------ annot -------
80 listArguments[["calcCiS"]]=as.logical(listArguments[["calcCiS"]]) 106 args$calcCiS=as.logical(args$calcCiS)
81 listArguments[["calcIso"]]=as.logical(listArguments[["calcIso"]]) 107 args$calcIso=as.logical(args$calcIso)
82 listArguments[["calcCaS"]]=as.logical(listArguments[["calcCaS"]]) 108 args$calcCaS=as.logical(args$calcCaS)
83 109
84 # common parameters 110 # common parameters
85 listArguments4annotate = list(object=xset, 111 args4annotate = list(object=xset,
86 nSlaves=listArguments[["nSlaves"]],sigma=listArguments[["sigma"]],perfwhm=listArguments[["perfwhm"]], 112 nSlaves=args$nSlaves,sigma=args$sigma,perfwhm=args$perfwhm,
87 maxcharge=listArguments[["maxcharge"]],maxiso=listArguments[["maxiso"]],minfrac=listArguments[["minfrac"]], 113 maxcharge=args$maxcharge,maxiso=args$maxiso,minfrac=args$minfrac,
88 ppm=listArguments[["ppm"]],mzabs=listArguments[["mzabs"]],quick=listArguments[["quick"]], 114 ppm=args$ppm,mzabs=args$mzabs,quick=args$quick,
89 polarity=listArguments[["polarity"]],max_peaks=listArguments[["max_peaks"]],intval=listArguments[["intval"]]) 115 polarity=args$polarity,max_peaks=args$max_peaks,intval=args$intval)
90 116
91 # quick == FALSE 117 # quick == FALSE
92 if(listArguments[["quick"]]==FALSE) { 118 if(args$quick==FALSE) {
93 listArguments4annotate = append(listArguments4annotate, 119 args4annotate = append(args4annotate,
94 list(graphMethod=listArguments[["graphMethod"]],cor_eic_th=listArguments[["cor_eic_th"]],pval=listArguments[["pval"]], 120 list(graphMethod=args$graphMethod,cor_eic_th=args$cor_eic_th,pval=args$pval,
95 calcCiS=listArguments[["calcCiS"]],calcIso=listArguments[["calcIso"]],calcCaS=listArguments[["calcCaS"]])) 121 calcCiS=args$calcCiS,calcIso=args$calcIso,calcCaS=args$calcCaS))
96 # no ruleset 122 # no ruleset
97 if (!is.null(listArguments[["multiplier"]])) { 123 if (!is.null(args$multiplier)) {
98 listArguments4annotate = append(listArguments4annotate, 124 args4annotate = append(args4annotate,
99 list(multiplier=listArguments[["multiplier"]])) 125 list(multiplier=args$multiplier))
100 } 126 }
101 # ruleset 127 # ruleset
102 else { 128 else {
103 rulset=read.table(listArguments[["rules"]], h=T, sep=";") 129 rulset=read.table(args$rules, h=T, sep=";")
104 if (ncol(rulset) < 4) rulset=read.table(listArguments[["rules"]], h=T, sep="\t") 130 if (ncol(rulset) < 4) rulset=read.table(args$rules, h=T, sep="\t")
105 if (ncol(rulset) < 4) rulset=read.table(listArguments[["rules"]], h=T, sep=",") 131 if (ncol(rulset) < 4) rulset=read.table(args$rules, h=T, sep=",")
106 if (ncol(rulset) < 4) { 132 if (ncol(rulset) < 4) {
107 error_message="Your ruleset file seems not well formatted. The column separators accepted are ; , and tabulation" 133 error_message="Your ruleset file seems not well formatted. The column separators accepted are ; , and tabulation"
108 print(error_message) 134 print(error_message)
109 stop(error_message) 135 stop(error_message)
110 } 136 }
111 137
112 listArguments4annotate = append(listArguments4annotate, 138 args4annotate = append(args4annotate,
113 list(rules=rulset)) 139 list(rules=rulset))
114 } 140 }
115 } 141 }
116 142
117 143
118 # launch annotate 144 # launch annotate
119 xa = do.call("annotate", listArguments4annotate) 145 xa = do.call("annotate", args4annotate)
120 peakList=getPeaklist(xa,intval=listArguments[["intval"]]) 146 peakList=getPeaklist(xa,intval=args$intval)
121 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); 147 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name");
122 148
123 # --- Multi condition : diffreport --- 149 # --- Multi condition : diffreport ---
124 diffrepOri=NULL 150 diffrepOri=NULL
125 if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) { 151 if (!is.null(args$runDiffreport) & nlevels(sampclass(xset))>=2) {
126 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. 152 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped.
127 res=try(is.null(xset@filled)) 153 res=try(is.null(xset@filled))
128 classes=levels(sampclass(xset)) 154 classes=levels(sampclass(xset))
129 x=1:(length(classes)-1) 155 x=1:(length(classes)-1)
130 for (i in seq(along=x) ) { 156 for (i in seq(along=x) ) {
131 y=1:(length(classes)) 157 y=1:(length(classes))
132 for (n in seq(along=y)){ 158 for (n in seq(along=y)){
133 if(i+n <= length(classes)){ 159 if(i+n <= length(classes)){
134 filebase=paste(classes[i],class2=classes[i+n],sep="-vs-") 160 filebase=paste(classes[i],class2=classes[i+n],sep="-vs-")
135 161
136 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"]],missing=0) 162 diffrep=diffreport(
163 object=xset,class1=classes[i],class2=classes[i+n],
164 filebase=filebase,eicmax=args$eicmax,eicwidth=args$eicwidth,
165 sortpval=TRUE,value=args$value,h=args$h,w=args$w,mzdec=args$mzdec,missing=0)
137 166
138 diffrepOri = diffrep 167 diffrepOri = diffrep
139 168
140 # renamming of the column rtmed to rt to fit with camera peaklist function output 169 # renamming of the column rtmed to rt to fit with camera peaklist function output
141 colnames(diffrep)[colnames(diffrep)=="rtmed"] <- "rt" 170 colnames(diffrep)[colnames(diffrep)=="rtmed"] <- "rt"
143 172
144 # combines results and reorder columns 173 # combines results and reorder columns
145 diffrep = merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F) 174 diffrep = merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F)
146 diffrep = cbind(diffrep[,!(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))],diffrep[,(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))]) 175 diffrep = cbind(diffrep[,!(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))],diffrep[,(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))])
147 176
148 diffrep = RTSecondToMinute(diffrep, listArguments[["convertRTMinute"]]) 177 diffrep = RTSecondToMinute(diffrep, args$convertRTMinute)
149 diffrep = formatIonIdentifiers(diffrep, numDigitsRT=listArguments[["numDigitsRT"]], numDigitsMZ=listArguments[["numDigitsMZ"]]) 178 diffrep = formatIonIdentifiers(diffrep, numDigitsRT=args$numDigitsRT, numDigitsMZ=args$numDigitsMZ)
150 179
151 if(listArguments[["sortpval"]]){ 180 if(args$sortpval){
152 diffrep=diffrep[order(diffrep$pvalue), ] 181 diffrep=diffrep[order(diffrep$pvalue), ]
153 } 182 }
154 183
155 dir.create("tabular", showWarnings = FALSE) 184 dir.create("tabular", showWarnings = FALSE)
156 write.table(diffrep, sep="\t", quote=FALSE, row.names=FALSE, file=paste("tabular/",filebase,"_tsv.tabular",sep="")) 185 write.table(diffrep, sep="\t", quote=FALSE, row.names=FALSE, file=paste("tabular/",filebase,"_tsv.tabular",sep=""))
157 186
158 if (listArguments[["eicmax"]] != 0) { 187 if (args$eicmax != 0) {
159 if (listArguments[["png2"]] == "pdf") 188 if (args$png2 == "pdf")
160 diffreport_png2pdf(filebase) 189 diffreport_png2pdf(filebase)
161 } 190 }
162 } 191 }
163 } 192 }
164 } 193 }
165 if (listArguments[["png2"]] == "zip") 194 if (args$png2 == "zip")
166 diffreport_png2zip() 195 diffreport_png2zip()
167 if (listArguments[["tabular2"]] == "zip") 196 if (args$tabular2 == "zip")
168 diffreport_tabular2zip() 197 diffreport_tabular2zip()
169 } 198 }
170 199
171 # --- variableMetadata --- 200 # --- variableMetadata ---
172 variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] 201 variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))]
173 variableMetadata = RTSecondToMinute(variableMetadata, listArguments[["convertRTMinute"]]) 202 variableMetadata = RTSecondToMinute(variableMetadata, args$convertRTMinute)
174 variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=listArguments[["numDigitsRT"]], numDigitsMZ=listArguments[["numDigitsMZ"]]) 203 variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=args$numDigitsRT, numDigitsMZ=args$numDigitsMZ)
175 # if we have 2 conditions, we keep stat of diffrep 204 # if we have 2 conditions, we keep stat of diffrep
176 if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))==2) { 205 if (!is.null(args$runDiffreport) & nlevels(sampclass(xset))==2) {
177 variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F) 206 variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F)
178 if(exists("listArguments[[\"sortpval\"]]")){ 207 if(exists("args[[\"sortpval\"]]")){
179 variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] 208 variableMetadata=variableMetadata[order(variableMetadata$pvalue), ]
180 } 209 }
181 } 210 }
182 211
183 variableMetadataOri=variableMetadata 212 variableMetadataOri=variableMetadata
186 return(list("xa"=xa,"diffrep"=diffrepOri,"variableMetadata"=variableMetadataOri)); 215 return(list("xa"=xa,"diffrep"=diffrepOri,"variableMetadata"=variableMetadataOri));
187 216
188 } 217 }
189 218
190 219
191 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"){ 220 combinexsAnnos_function <- function(xaP, xaN, diffrepP=NULL,diffrepN=NULL,
221 pos=TRUE,tol=2,ruleset=NULL,keep_meta=TRUE, convertRTMinute=F, numDigitsMZ=0,
222 numDigitsRT=0, variableMetadataOutput="variableMetadata.tsv"){
192 223
193 #Load the two Rdata to extract the xset objects from positive and negative mode 224 #Load the two Rdata to extract the xset objects from positive and negative mode
194 cat("\tObject xset from positive mode\n") 225 cat("\tObject xset from positive mode\n")
195 print(xaP) 226 print(xaP)
196 cat("\n") 227 cat("\n")
213 stop("You must relauch the CAMERA.annotate step with the lastest version.") 244 stop("You must relauch the CAMERA.annotate step with the lastest version.")
214 } 245 }
215 246
216 if(pos){ 247 if(pos){
217 xa=xaP 248 xa=xaP
218 listOFlistArgumentsP=listOFlistArguments
219 mode="neg. Mode" 249 mode="neg. Mode"
220 } else { 250 } else {
221 xa=xaN 251 xa=xaN
222 listOFlistArgumentsN=listOFlistArguments
223 mode="pos. Mode" 252 mode="pos. Mode"
224 } 253 }
225 254
226 peakList=getPeaklist(xa) 255 peakList=getPeaklist(xa)
227 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); 256 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name");
254 return(variableMetadata); 283 return(variableMetadata);
255 284
256 } 285 }
257 286
258 # This function get the raw file path from the arguments 287 # This function get the raw file path from the arguments
259 getRawfilePathFromArguments <- function(singlefile, zipfile, listArguments) { 288 getRawfilePathFromArguments <- function(singlefile, zipfile, args) {
260 if (!is.null(listArguments[["zipfile"]])) zipfile = listArguments[["zipfile"]] 289 if (!is.null(args$zipfile)) zipfile = args$zipfile
261 if (!is.null(listArguments[["zipfilePositive"]])) zipfile = listArguments[["zipfilePositive"]] 290 if (!is.null(args$zipfilePositive)) zipfile = args$zipfilePositive
262 if (!is.null(listArguments[["zipfileNegative"]])) zipfile = listArguments[["zipfileNegative"]] 291 if (!is.null(args$zipfileNegative)) zipfile = args$zipfileNegative
263 292
264 if (!is.null(listArguments[["singlefile_galaxyPath"]])) { 293 if (!is.null(args$singlefile_galaxyPath)) {
265 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPath"]]; 294 singlefile_galaxyPaths = args$singlefile_galaxyPath;
266 singlefile_sampleNames = listArguments[["singlefile_sampleName"]] 295 singlefile_sampleNames = args$singlefile_sampleName
267 } 296 }
268 if (!is.null(listArguments[["singlefile_galaxyPathPositive"]])) { 297 if (!is.null(args$singlefile_galaxyPathPositive)) {
269 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathPositive"]]; 298 singlefile_galaxyPaths = args$singlefile_galaxyPathPositive;
270 singlefile_sampleNames = listArguments[["singlefile_sampleNamePositive"]] 299 singlefile_sampleNames = args$singlefile_sampleNamePositive
271 } 300 }
272 if (!is.null(listArguments[["singlefile_galaxyPathNegative"]])) { 301 if (!is.null(args$singlefile_galaxyPathNegative)) {
273 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathNegative"]]; 302 singlefile_galaxyPaths = args$singlefile_galaxyPathNegative;
274 singlefile_sampleNames = listArguments[["singlefile_sampleNameNegative"]] 303 singlefile_sampleNames = args$singlefile_sampleNameNegative
275 } 304 }
276 if (exists("singlefile_galaxyPaths")){ 305 if (exists("singlefile_galaxyPaths")){
277 singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,",")) 306 singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,","))
278 singlefile_sampleNames = unlist(strsplit(singlefile_sampleNames,",")) 307 singlefile_sampleNames = unlist(strsplit(singlefile_sampleNames,","))
279 308
282 singlefile_galaxyPath=singlefile_galaxyPaths[singlefile_galaxyPath_i] 311 singlefile_galaxyPath=singlefile_galaxyPaths[singlefile_galaxyPath_i]
283 singlefile_sampleName=singlefile_sampleNames[singlefile_galaxyPath_i] 312 singlefile_sampleName=singlefile_sampleNames[singlefile_galaxyPath_i]
284 singlefile[[singlefile_sampleName]] = singlefile_galaxyPath 313 singlefile[[singlefile_sampleName]] = singlefile_galaxyPath
285 } 314 }
286 } 315 }
287 for (argument in c("zipfile","zipfilePositive","zipfileNegative","singlefile_galaxyPath","singlefile_sampleName","singlefile_galaxyPathPositive","singlefile_sampleNamePositive","singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { 316 for (argument in c("zipfile", "zipfilePositive", "zipfileNegative",
288 listArguments[[argument]]=NULL 317 "singlefile_galaxyPath", "singlefile_sampleName",
289 } 318 "singlefile_galaxyPathPositive", "singlefile_sampleNamePositive",
290 return(list(zipfile=zipfile, singlefile=singlefile, listArguments=listArguments)) 319 "singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) {
320 args[[argument]]=NULL
321 }
322 return(list(zipfile=zipfile, singlefile=singlefile, args=args))
291 } 323 }
292 324
293 325
294 # This function retrieve the raw file in the working directory 326 # This function retrieve the raw file in the working directory
295 # - if zipfile: unzip the file with its directory tree 327 # - if zipfile: unzip the file with its directory tree