# HG changeset patch # User lecorguille # Date 1491565358 14400 # Node ID 198b035d4848c128ae9cb40e0c1033b561028096 # Parent c23aa0cbc550430b753582b37416aceaccae3691 planemo upload commit 301d42e88026afdac618f4ec56fc6cbe19e3e419 diff -r c23aa0cbc550 -r 198b035d4848 CAMERA.r --- a/CAMERA.r Wed Feb 01 12:24:21 2017 -0500 +++ b/CAMERA.r Fri Apr 07 07:42:38 2017 -0400 @@ -11,12 +11,12 @@ #pkgs=c("xcms","batch") pkgs=c("parallel","BiocGenerics", "Biobase", "Rcpp", "mzR", "xcms","snow","igraph","CAMERA","multtest","batch") for(p in pkgs) { - suppressPackageStartupMessages(suppressWarnings(library(p, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) - cat(p,"\t",as.character(packageVersion(p)),"\n",sep="") + suppressPackageStartupMessages(suppressWarnings(library(p, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) + cat(p,"\t",as.character(packageVersion(p)),"\n",sep="") } source_local <- function(fname){ argv <- commandArgs(trailingOnly = FALSE); base_dir <- dirname(substring(argv[grep("--file=", argv)], 8)); source(paste(base_dir, fname, sep="/")) } -cat("\n\n"); +cat("\n\n"); @@ -34,25 +34,25 @@ #image is an .RData file necessary to use xset variable given by previous tools if (!is.null(listArguments[["image"]])){ - load(listArguments[["image"]]); listArguments[["image"]]=NULL + load(listArguments[["image"]]); listArguments[["image"]]=NULL } if (listArguments[["xfunction"]] %in% c("combinexsAnnos")) { - load(listArguments[["image_pos"]]) - xaP=xa - listOFlistArgumentsP=listOFlistArguments - if (exists("xsAnnotate_object")) xaP=xsAnnotate_object - - diffrepP=NULL - if (exists("diffrep")) diffrepP=diffrep + load(listArguments[["image_pos"]]) + xaP=xa + listOFlistArgumentsP=listOFlistArguments + if (exists("xsAnnotate_object")) xaP=xsAnnotate_object + + diffrepP=NULL + if (exists("diffrep")) diffrepP=diffrep - load(listArguments[["image_neg"]]) - xaN=xa - listOFlistArgumentsN=listOFlistArguments - if (exists("xsAnnotate_object")) xaN=xsAnnotate_object + load(listArguments[["image_neg"]]) + xaN=xa + listOFlistArgumentsN=listOFlistArguments + if (exists("xsAnnotate_object")) xaN=xsAnnotate_object - diffrepN=NULL - if (exists("diffrep")) diffrepN=diffrep + diffrepN=NULL + if (exists("diffrep")) diffrepN=diffrep } @@ -73,67 +73,42 @@ xsetRdataOutput = paste(thefunction,"RData",sep=".") if (!is.null(listArguments[["xsetRdataOutput"]])){ - xsetRdataOutput = listArguments[["xsetRdataOutput"]]; listArguments[["xsetRdataOutput"]]=NULL + xsetRdataOutput = listArguments[["xsetRdataOutput"]]; listArguments[["xsetRdataOutput"]]=NULL } rplotspdf = "Rplots.pdf" if (!is.null(listArguments[["rplotspdf"]])){ - rplotspdf = listArguments[["rplotspdf"]]; listArguments[["rplotspdf"]]=NULL + rplotspdf = listArguments[["rplotspdf"]]; listArguments[["rplotspdf"]]=NULL } dataMatrixOutput = "dataMatrix.tsv" if (!is.null(listArguments[["dataMatrixOutput"]])){ - dataMatrixOutput = listArguments[["dataMatrixOutput"]]; listArguments[["dataMatrixOutput"]]=NULL + dataMatrixOutput = listArguments[["dataMatrixOutput"]]; listArguments[["dataMatrixOutput"]]=NULL } variableMetadataOutput = "variableMetadata.tsv" if (!is.null(listArguments[["variableMetadataOutput"]])){ - variableMetadataOutput = listArguments[["variableMetadataOutput"]]; listArguments[["variableMetadataOutput"]]=NULL -} - -if (!is.null(listArguments[["new_file_path"]])){ - new_file_path = listArguments[["new_file_path"]]; listArguments[["new_file_path"]]=NULL + variableMetadataOutput = listArguments[["variableMetadataOutput"]]; listArguments[["variableMetadataOutput"]]=NULL } #Import the different functions source_local("lib.r") -#necessary to unzip .zip file uploaded to Galaxy -#thanks to .zip file it's possible to upload many file as the same time conserving the tree hierarchy of directories - - -if (!is.null(listArguments[["zipfile"]])){ - zipfile= listArguments[["zipfile"]]; listArguments[["zipfile"]]=NULL -} - # We unzip automatically the chromatograms from the zip files. if (thefunction %in% c("annotatediff")) { - if(exists("zipfile") && (zipfile!="")) { - if(!file.exists(zipfile)){ - error_message=paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!") - print(error_message) - stop(error_message) - } - - #unzip - suppressWarnings(unzip(zipfile, unzip="unzip")) - - #get the directory name - filesInZip=unzip(zipfile, list=T); - directories=unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1]))); - directories=directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] - directory = "." - if (length(directories) == 1) directory = directories - - cat("files_root_directory\t",directory,"\n") - } + if (!exists("zipfile")) zipfile=NULL + if (!exists("singlefile")) singlefile=NULL + rawFilePath = getRawfilePathFromArguments(singlefile, zipfile, listArguments) + zipfile = rawFilePath$zipfile + singlefile = rawFilePath$singlefile + listArguments = rawFilePath$listArguments + directory = retrieveRawfileInTheWorkingDirectory(singlefile, zipfile) } - #addition of xset object to the list of arguments in the first position if (exists("xset") != 0){ - listArguments=append(list(xset), listArguments) + listArguments=append(list(xset), listArguments) } cat("\n\n") @@ -149,25 +124,32 @@ if (thefunction %in% c("annotatediff")) { - results_list=annotatediff(xset=xset,listArguments=listArguments,variableMetadataOutput=variableMetadataOutput,dataMatrixOutput=dataMatrixOutput,new_file_path=new_file_path) - xa=results_list[["xa"]] - diffrep=results_list[["diffrep"]] - variableMetadata=results_list[["variableMetadata"]] + results_list=annotatediff(xset=xset,listArguments=listArguments,variableMetadataOutput=variableMetadataOutput,dataMatrixOutput=dataMatrixOutput) + xa=results_list[["xa"]] + diffrep=results_list[["diffrep"]] + variableMetadata=results_list[["variableMetadata"]] - cat("\n\n") - cat("\tXSET OBJECT INFO\n") - print(xa) + cat("\n\n") + cat("\tXSET OBJECT INFO\n") + print(xa) } if (thefunction %in% c("combinexsAnnos")) { - cAnnot=combinexsAnnos_function(xaP=xaP,xaN=xaN,listOFlistArgumentsP=listOFlistArgumentsP,listOFlistArgumentsN=listOFlistArgumentsN,diffrepP=diffrepP,diffrepN=diffrepN,convert_param=listArguments[["convert_param"]],pos=listArguments[["pos"]],tol=listArguments[["tol"]],ruleset=listArguments[["ruleset"]],keep_meta=listArguments[["keep_meta"]],variableMetadataOutput=variableMetadataOutput) + cAnnot=combinexsAnnos_function( + xaP=xaP,xaN=xaN, + listOFlistArgumentsP=listOFlistArgumentsP,listOFlistArgumentsN=listOFlistArgumentsN, + diffrepP=diffrepP,diffrepN=diffrepN, + pos=listArguments[["pos"]],tol=listArguments[["tol"]],ruleset=listArguments[["ruleset"]],keep_meta=listArguments[["keep_meta"]], + convertRTMinute=listArguments[["convertRTMinute"]], numDigitsMZ=listArguments[["numDigitsMZ"]], numDigitsRT=listArguments[["numDigitsRT"]], + variableMetadataOutput=variableMetadataOutput + ) } dev.off() #saving R data in .Rdata file to save the variables used in the present tool -objects2save = c("xa","variableMetadata","diffrep","cAnnot","listOFlistArguments","zipfile") +objects2save = c("xa","variableMetadata","diffrep","cAnnot","listOFlistArguments","zipfile","singlefile") save(list=objects2save[objects2save %in% ls()], file=xsetRdataOutput) cat("\n\n") diff -r c23aa0cbc550 -r 198b035d4848 README.rst --- a/README.rst Wed Feb 01 12:24:21 2017 -0500 +++ b/README.rst Fri Apr 07 07:42:38 2017 -0400 @@ -2,6 +2,16 @@ Changelog/News -------------- +**Version 2.0.6 - 10/02/2017** + +- IMPROVEMENT: Synchronize the variableMetadata export option with the other tools (xcms.group, xcms.fillpeaks, camera.annotate) + + +**Version 2.0.5 - 22/12/2016** + +- IMPROVEMENT: add the possibility to add a personal Matrix of matching rules (ruleset) + + **Version 2.0.4 - 21/04/2016** - UPGRADE: upgrate the CAMERA version from 1.22.0 to 1.26.0 diff -r c23aa0cbc550 -r 198b035d4848 abims_CAMERA_combinexsAnnos.xml --- a/abims_CAMERA_combinexsAnnos.xml Wed Feb 01 12:24:21 2017 -0500 +++ b/abims_CAMERA_combinexsAnnos.xml Fri Apr 07 07:42:38 2017 -0400 @@ -1,7 +1,7 @@ - + Wrapper function for the combinexsAnnos CAMERA function. Returns a dataframe with recalculated annotations. - + macros.xml @@ -11,20 +11,24 @@ - + @@ -32,9 +36,13 @@ - +
+ + + +
@@ -52,13 +60,18 @@ +
+ + + +
- - + + @@ -222,5 +248,3 @@
- - diff -r c23aa0cbc550 -r 198b035d4848 lib.r --- a/lib.r Wed Feb 01 12:24:21 2017 -0500 +++ b/lib.r Fri Apr 07 07:42:38 2017 -0400 @@ -1,188 +1,304 @@ -# lib.r version="2.2.1" +# lib.r + +#@author G. Le Corguille +#The function create a pdf from the different png generated by diffreport +diffreport_png2pdf <- function(filebase) { + dir.create("pdf") -#The function create a pdf from the different png generated by diffreport -diffreport_png2pdf <- function(filebase, new_file_path) { + pdfEicOutput = paste0("pdf/",filebase,"-eic_pdf.pdf") + pdfBoxOutput = paste0("pdf/",filebase,"-box_pdf.pdf") + + system(paste0("gm convert ",filebase,"_eic/*.png ",pdfEicOutput)) + system(paste0("gm convert ",filebase,"_box/*.png ",pdfBoxOutput)) + +} - pdfEicOutput = paste(new_file_path,filebase,"-eic_visible_pdf",sep="") - pdfBoxOutput = paste(new_file_path,filebase,"-box_visible_pdf",sep="") +#@author G. Le Corguille +#This function convert if it is required the Retention Time in minutes +RTSecondToMinute <- function(variableMetadata, convertRTMinute) { + if (convertRTMinute){ + #converting the retention times (seconds) into minutes + print("converting the retention times into minutes in the variableMetadata") + variableMetadata[,"rt"]=variableMetadata[,"rt"]/60 + variableMetadata[,"rtmin"]=variableMetadata[,"rtmin"]/60 + variableMetadata[,"rtmax"]=variableMetadata[,"rtmax"]/60 + } + return (variableMetadata) +} - system(paste("gm convert ",filebase,"_eic/*.png ",filebase,"_eic.pdf",sep="")) - system(paste("gm convert ",filebase,"_box/*.png ",filebase,"_box.pdf",sep="")) - - file.copy(paste(filebase,"_eic.pdf",sep=""), pdfEicOutput) - file.copy(paste(filebase,"_box.pdf",sep=""), pdfBoxOutput) +#@author G. Le Corguille +#This function format ions identifiers +formatIonIdentifiers <- function(variableMetadata, numDigitsRT=0, numDigitsMZ=0) { + splitDeco = strsplit(as.character(variableMetadata$name),"_") + idsDeco = sapply(splitDeco, function(x) { deco=unlist(x)[2]; if (is.na(deco)) return ("") else return(paste0("_",deco)) }) + namecustom = make.unique(paste0("M",round(variableMetadata[,"mz"],numDigitsMZ),"T",round(variableMetadata[,"rt"],numDigitsRT),idsDeco)) + variableMetadata=cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))]) + return(variableMetadata) } #The function annotateDiffreport without the corr function which bugs -annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv", dataMatrixOutput="dataMatrix.tsv",new_file_path=NULL) { - # Resolve the bug with x11, with the function png - options(bitmapType='cairo') - - #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. - res=try(is.null(xset@filled)) - - # ------ annot ------- - listArguments[["calcCiS"]]=as.logical(listArguments[["calcCiS"]]) - listArguments[["calcIso"]]=as.logical(listArguments[["calcIso"]]) - listArguments[["calcCaS"]]=as.logical(listArguments[["calcCaS"]]) +annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv", dataMatrixOutput="dataMatrix.tsv") { + # Resolve the bug with x11, with the function png + options(bitmapType='cairo') - #graphMethod parameter bugs where this parameter is not defined in quick=true - if(listArguments[["quick"]]==TRUE) { - 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"]]) - } - else { - 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"]]) - - } - peakList=getPeaklist(xa,intval=listArguments[["intval"]]) - peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); - - - # --- Multi condition : diffreport --- - diffrep=NULL - if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) { #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. res=try(is.null(xset@filled)) - classes=levels(sampclass(xset)) - x=1:(length(classes)-1) - for (i in seq(along=x) ) { - y=1:(length(classes)) - for (n in seq(along=y)){ - if(i+n <= length(classes)){ - filebase=paste(classes[i],class2=classes[i+n],sep="-vs-") + + # ------ annot ------- + listArguments[["calcCiS"]]=as.logical(listArguments[["calcCiS"]]) + listArguments[["calcIso"]]=as.logical(listArguments[["calcIso"]]) + listArguments[["calcCaS"]]=as.logical(listArguments[["calcCaS"]]) - 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"]]) - #combines results - diffreportTSV=merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F) - diffreportTSV=cbind(diffreportTSV[,!(colnames(diffreportTSV) %in% c(sampnames(xa@xcmsSet)))],diffreportTSV[,(colnames(diffreportTSV) %in% c(sampnames(xa@xcmsSet)))]) + # common parameters + listArguments4annotate = list(object=xset, + nSlaves=listArguments[["nSlaves"]],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"]]) - if(listArguments[["sortpval"]]){ - diffreportTSV=diffreportTSV[order(diffreportTSV$pvalue), ] - } - - if (listArguments[["convert_param"]]){ - #converting the retention times (seconds) into minutes - diffreportTSV$rt=diffreportTSV$rt/60;diffreportTSV$rtmin=diffreportTSV$rtmin/60; diffreportTSV$rtmax=diffreportTSV$rtmax/60; - } - write.table(diffreportTSV, sep="\t", quote=FALSE, row.names=FALSE, file=paste(new_file_path,filebase,"-tabular_visible_tabular",sep="")) + # quick == FALSE + if(listArguments[["quick"]]==FALSE) { + listArguments4annotate = append(listArguments4annotate, + list(graphMethod=listArguments[["graphMethod"]],cor_eic_th=listArguments[["cor_eic_th"]],pval=listArguments[["pval"]], + calcCiS=listArguments[["calcCiS"]],calcIso=listArguments[["calcIso"]],calcCaS=listArguments[["calcCaS"]])) + # no ruleset + if (!is.null(listArguments[["multiplier"]])) { + listArguments4annotate = append(listArguments4annotate, + list(multiplier=listArguments[["multiplier"]])) + } + # ruleset + else { + rulset=read.table(listArguments[["rules"]], h=T, sep=";") + if (ncol(rulset) < 4) rulset=read.table(listArguments[["rules"]], h=T, sep="\t") + if (ncol(rulset) < 4) rulset=read.table(listArguments[["rules"]], h=T, sep=",") + if (ncol(rulset) < 4) { + error_message="Your ruleset file seems not well formatted. The column separators accepted are ; , and tabulation" + print(error_message) + stop(error_message) + } - if (listArguments[["eicmax"]] != 0) { - diffreport_png2pdf(filebase, new_file_path) - } + listArguments4annotate = append(listArguments4annotate, + list(rules=rulset)) } - } } - } + # launch annotate + xa = do.call("annotate", listArguments4annotate) + peakList=getPeaklist(xa,intval=listArguments[["intval"]]) + peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); + + # --- dataMatrix --- + dataMatrix = peakList[,(make.names(colnames(peakList)) %in% c("name", make.names(sampnames(xa@xcmsSet))))] + write.table(dataMatrix, sep="\t", quote=FALSE, row.names=FALSE, file=dataMatrixOutput) - # --- variableMetadata --- - variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] - # if we have 2 conditions, we keep stat of diffrep - if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))==2) { - variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F) - if(exists("listArguments[[\"sortpval\"]]")){ - variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] + # --- Multi condition : diffreport --- + diffrepOri=NULL + if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) { + #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. + res=try(is.null(xset@filled)) + classes=levels(sampclass(xset)) + x=1:(length(classes)-1) + for (i in seq(along=x) ) { + y=1:(length(classes)) + for (n in seq(along=y)){ + if(i+n <= length(classes)){ + filebase=paste(classes[i],class2=classes[i+n],sep="-vs-") + + 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"]]) + + diffrepOri = diffrep + + # renamming of the column rtmed to rt to fit with camera peaklist function output + colnames(diffrep)[colnames(diffrep)=="rtmed"] <- "rt" + colnames(diffrep)[colnames(diffrep)=="mzmed"] <- "mz" + + # combines results and reorder columns + diffrep = merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F) + diffrep = cbind(diffrep[,!(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))],diffrep[,(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))]) + + diffrep = RTSecondToMinute(diffrep, listArguments[["convertRTMinute"]]) + diffrep = formatIonIdentifiers(diffrep, numDigitsRT=listArguments[["numDigitsRT"]], numDigitsMZ=listArguments[["numDigitsMZ"]]) + + if(listArguments[["sortpval"]]){ + diffrep=diffrep[order(diffrep$pvalue), ] + } + + dir.create("tabular") + write.table(diffrep, sep="\t", quote=FALSE, row.names=FALSE, file=paste("tabular/",filebase,"_tsv.tabular",sep="")) + + if (listArguments[["eicmax"]] != 0) { + diffreport_png2pdf(filebase) + } + } + } + } } - } - variableMetadataOri=variableMetadata - if (listArguments[["convert_param"]]){ - #converting the retention times (seconds) into minutes - print("converting the retention times into minutes in the variableMetadata") - variableMetadata$rt=variableMetadata$rt/60;variableMetadata$rtmin=variableMetadata$rtmin/60; variableMetadata$rtmax=variableMetadata$rtmax/60; - } - #Transform metabolites name - variableMetadata$name= paste("M",round(variableMetadata$mz,digits=listArguments[["num_digits"]]),"T",round(variableMetadata$rt),sep="") - write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) - # --- dataMatrix --- - dataMatrix = peakList[,(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] - dataMatrix=cbind(peakList$name,dataMatrix); colnames(dataMatrix)[1] = c("name"); + # --- variableMetadata --- + variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] + variableMetadata = RTSecondToMinute(variableMetadata, listArguments[["convertRTMinute"]]) + variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=listArguments[["numDigitsRT"]], numDigitsMZ=listArguments[["numDigitsMZ"]]) + # if we have 2 conditions, we keep stat of diffrep + if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))==2) { + variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F) + if(exists("listArguments[[\"sortpval\"]]")){ + variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] + } + } - if (listArguments[["convert_param"]]){ - #converting the retention times (seconds) into minutes - print("converting the retention times into minutes in the dataMatrix ids") - peakList$rt=peakList$rt/60 - } - dataMatrix$name= paste("M",round(peakList$mz,digits=listArguments[["num_digits"]]),"T",round(peakList$rt),sep="") - write.table(dataMatrix, sep="\t", quote=FALSE, row.names=FALSE, file=dataMatrixOutput) - - return(list("xa"=xa,"diffrep"=diffrep,"variableMetadata"=variableMetadataOri)); + variableMetadataOri=variableMetadata + write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) + + return(list("xa"=xa,"diffrep"=diffrepOri,"variableMetadata"=variableMetadataOri)); } -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"){ +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"){ - #Load the two Rdata to extract the xset objects from positive and negative mode - cat("\tObject xset from positive mode\n") - print(xaP) - cat("\n") + #Load the two Rdata to extract the xset objects from positive and negative mode + cat("\tObject xset from positive mode\n") + print(xaP) + cat("\n") + + cat("\tObject xset from negative mode\n") + print(xaN) + cat("\n") - cat("\tObject xset from negative mode\n") - print(xaN) - cat("\n") - - cat("\n") - cat("\tCombining...\n") - #Convert the string to numeric for creating matrix - row=as.numeric(strsplit(ruleset,",")[[1]][1]) - column=as.numeric(strsplit(ruleset,",")[[1]][2]) - ruleset=cbind(row,column) - #Test if the file comes from an older version tool - if ((!is.null(xaP)) & (!is.null(xaN))) { - #Launch the combinexsannos function from CAMERA - cAnnot=combinexsAnnos(xaP, xaN,pos=pos,tol=tol,ruleset=ruleset) - } else { - stop("You must relauch the CAMERA.annotate step with the lastest version.") - } - - + cat("\n") + cat("\tCombining...\n") + #Convert the string to numeric for creating matrix + row=as.numeric(strsplit(ruleset,",")[[1]][1]) + column=as.numeric(strsplit(ruleset,",")[[1]][2]) + ruleset=cbind(row,column) + #Test if the file comes from an older version tool + if ((!is.null(xaP)) & (!is.null(xaN))) { + #Launch the combinexsannos function from CAMERA + cAnnot=combinexsAnnos(xaP, xaN,pos=pos,tol=tol,ruleset=ruleset) + } else { + stop("You must relauch the CAMERA.annotate step with the lastest version.") + } - if(pos){ - xa=xaP - listOFlistArgumentsP=listOFlistArguments - mode="neg. Mode" - } else { - xa=xaN - listOFlistArgumentsN=listOFlistArguments - mode="pos. Mode" - } - intval = "into"; for (steps in names(listOFlistArguments)) { if (!is.null(listOFlistArguments[[steps]]$intval)) intval = listOFlistArguments[[steps]]$intval } - peakList=getPeaklist(xa,intval=intval) - peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); - variableMetadata=cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup",mode)]); - variableMetadata=variableMetadata[,!(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))] + if(pos){ + xa=xaP + listOFlistArgumentsP=listOFlistArguments + mode="neg. Mode" + } else { + xa=xaN + listOFlistArgumentsN=listOFlistArguments + mode="pos. Mode" + } + + peakList=getPeaklist(xa) + peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); + variableMetadata=cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup",mode)]); + variableMetadata=variableMetadata[,!(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))] + + #Test if there are more than two classes (conditions) + if ( nlevels(sampclass(xaP@xcmsSet))==2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) { + diffrepP = diffrepP[,c("name","fold","tstat","pvalue")]; colnames(diffrepP) = paste("P.",colnames(diffrepP),sep="") + diffrepN = diffrepN[,c("name","fold","tstat","pvalue")]; colnames(diffrepN) = paste("N.",colnames(diffrepN),sep="") - #Test if there are more than two classes (conditions) - if ( nlevels(sampclass(xaP@xcmsSet))==2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) { - diffrepP = diffrepP[,c("name","fold","tstat","pvalue")]; colnames(diffrepP) = paste("P.",colnames(diffrepP),sep="") - diffrepN = diffrepN[,c("name","fold","tstat","pvalue")]; colnames(diffrepN) = paste("N.",colnames(diffrepN),sep="") - - variableMetadata = merge(variableMetadata, diffrepP, by.x="name", by.y="P.name") - variableMetadata = merge(variableMetadata, diffrepN, by.x="name", by.y="N.name") - } - - rownames(variableMetadata) = NULL - #TODO: checker - #colnames(variableMetadata)[1:2] = c("name","mz/rt"); + variableMetadata = merge(variableMetadata, diffrepP, by.x="name", by.y="P.name") + variableMetadata = merge(variableMetadata, diffrepN, by.x="name", by.y="N.name") + } + + rownames(variableMetadata) = NULL + #TODO: checker + #colnames(variableMetadata)[1:2] = c("name","mz/rt"); - #If the user want to convert the retention times (seconds) into minutes. - if (listArguments[["convert_param"]]){ - #converting the retention times (seconds) into minutes - cat("\tConverting the retention times into minutes\n") - variableMetadata$rtmed=cAnnot$rt/60; variableMetadata$rtmin=cAnnot$rtmin/60; variableMetadata$rtmax=cAnnot$rtmax/60; - } + variableMetadata = RTSecondToMinute(variableMetadata, convertRTMinute) + variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=numDigitsRT, numDigitsMZ=numDigitsMZ) - #If the user want to keep only the metabolites which match a difference - if(keep_meta){ - variableMetadata=variableMetadata[variableMetadata[,c(mode)]!="",] - } - - #Write the output into a tsv file - write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) - return(variableMetadata); + #If the user want to keep only the metabolites which match a difference + if(keep_meta){ + variableMetadata=variableMetadata[variableMetadata[,c(mode)]!="",] + } + + #Write the output into a tsv file + write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) + return(variableMetadata); } + +# This function get the raw file path from the arguments +getRawfilePathFromArguments <- function(singlefile, zipfile, listArguments) { + if (!is.null(listArguments[["zipfile"]])) zipfile = listArguments[["zipfile"]] + if (!is.null(listArguments[["zipfilePositive"]])) zipfile = listArguments[["zipfilePositive"]] + if (!is.null(listArguments[["zipfileNegative"]])) zipfile = listArguments[["zipfileNegative"]] + + if (!is.null(listArguments[["singlefile_galaxyPath"]])) { + singlefile_galaxyPaths = listArguments[["singlefile_galaxyPath"]]; + singlefile_sampleNames = listArguments[["singlefile_sampleName"]] + } + if (!is.null(listArguments[["singlefile_galaxyPathPositive"]])) { + singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathPositive"]]; + singlefile_sampleNames = listArguments[["singlefile_sampleNamePositive"]] + } + if (!is.null(listArguments[["singlefile_galaxyPathNegative"]])) { + singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathNegative"]]; + singlefile_sampleNames = listArguments[["singlefile_sampleNameNegative"]] + } + if (exists("singlefile_galaxyPaths")){ + singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,",")) + singlefile_sampleNames = unlist(strsplit(singlefile_sampleNames,",")) + + singlefile=NULL + for (singlefile_galaxyPath_i in seq(1:length(singlefile_galaxyPaths))) { + singlefile_galaxyPath=singlefile_galaxyPaths[singlefile_galaxyPath_i] + singlefile_sampleName=singlefile_sampleNames[singlefile_galaxyPath_i] + singlefile[[singlefile_sampleName]] = singlefile_galaxyPath + } + } + for (argument in c("zipfile","zipfilePositive","zipfileNegative","singlefile_galaxyPath","singlefile_sampleName","singlefile_galaxyPathPositive","singlefile_sampleNamePositive","singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { + listArguments[[argument]]=NULL + } + return(list(zipfile=zipfile, singlefile=singlefile, listArguments=listArguments)) +} + + +# This function retrieve the raw file in the working directory +# - if zipfile: unzip the file with its directory tree +# - if singlefiles: set symlink with the good filename +retrieveRawfileInTheWorkingDirectory <- function(singlefile, zipfile) { + if(!is.null(singlefile) && (length("singlefile")>0)) { + for (singlefile_sampleName in names(singlefile)) { + singlefile_galaxyPath = singlefile[[singlefile_sampleName]] + if(!file.exists(singlefile_galaxyPath)){ + error_message=paste("Cannot access the sample:",singlefile_sampleName,"located:",singlefile_galaxyPath,". Please, contact your administrator ... if you have one!") + print(error_message); stop(error_message) + } + + file.symlink(singlefile_galaxyPath,singlefile_sampleName) + } + directory = "." + + } + if(!is.null(zipfile) && (zipfile!="")) { + if(!file.exists(zipfile)){ + error_message=paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!") + print(error_message) + stop(error_message) + } + + #list all file in the zip file + #zip_files=unzip(zipfile,list=T)[,"Name"] + + #unzip + suppressWarnings(unzip(zipfile, unzip="unzip")) + + #get the directory name + filesInZip=unzip(zipfile, list=T); + directories=unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1]))); + directories=directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] + directory = "." + if (length(directories) == 1) directory = directories + + cat("files_root_directory\t",directory,"\n") + + } + return (directory) +} diff -r c23aa0cbc550 -r 198b035d4848 macros.xml --- a/macros.xml Wed Feb 01 12:24:21 2017 -0500 +++ b/macros.xml Fri Apr 07 07:42:38 2017 -0400 @@ -2,12 +2,11 @@ - r-snow + r-snow bioconductor-camera bioconductor-multtest - r-batch - libpng - graphicsmagick + r-batch + graphicsmagick @@ -19,33 +18,137 @@ LANG=C Rscript $__tool_directory__/CAMERA.r - - - - #if $zipfile_load_conditional.zipfile_load_select == "yes": - #if $zipfile_load_conditional.zip_file: - zipfile $zipfile_load_conditional.zip_file + + + + #if $file_load_section.file_load_conditional.file_load_select == "yes": + #if $file_load_section.file_load_conditional.input[0].is_of_type("mzxml") or $file_load_section.file_load_conditional.input[0].is_of_type("mzml") or $file_load_section.file_load_conditional.input[0].is_of_type("mzdata") or $file_load_section.file_load_conditional.input[0].is_of_type("netcdf"): + #set singlefile_galaxyPath = ','.join( [ str( $single_file ) for $single_file in $file_load_section.file_load_conditional.input ] ) + #set singlefile_sampleName = ','.join( [ str( $single_file.name ) for $single_file in $file_load_section.file_load_conditional.input ] ) + singlefile_galaxyPath '$singlefile_galaxyPath' singlefile_sampleName '$singlefile_sampleName' + #else + zipfile '$file_load_section.file_load_conditional.input' #end if - #end if + #end if + + + +
+ + + + + + + + + + + +
+
+ + +
+ + + + +
+
+ + +
+ + + + +
+
+ + + + convertRTMinute $export.convertRTMinute + numDigitsMZ $export.numDigitsMZ + numDigitsRT $export.numDigitsRT + intval $export.intval - - - - - + + +
+ + + + + + + - - - - - +
+
+ + +
+ + + + +
+
+ + + +
+ + +
+
+ + + +
+
+ + + +
+
+ + + + + + + + + + +
+ +
+ + + +
+ + + + + + +
+
+ + + + - + .. class:: infomark -**Authors** Colin A. Smith csmith@scripps.edu, Ralf Tautenhahn rtautenh@gmail.com, Steffen Neumann sneumann@ipb-halle.de, Paul Benton hpaul.benton08@imperial.ac.uk and Christopher Conley cjconley@ucdavis.edu +**Authors** Colin A. Smith csmith@scripps.edu, Ralf Tautenhahn rtautenh@gmail.com, Steffen Neumann sneumann@ipb-halle.de, Paul Benton hpaul.benton08@imperial.ac.uk and Christopher Conley cjconley@ucdavis.edu .. class:: infomark diff -r c23aa0cbc550 -r 198b035d4848 static/images/combinexsannos_workflow.png Binary file static/images/combinexsannos_workflow.png has changed diff -r c23aa0cbc550 -r 198b035d4848 static/images/combinexsannos_workflow_zoom.png Binary file static/images/combinexsannos_workflow_zoom.png has changed diff -r c23aa0cbc550 -r 198b035d4848 test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv --- a/test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv Wed Feb 01 12:24:21 2017 -0500 +++ b/test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv Fri Apr 07 07:42:38 2017 -0400 @@ -1,116 +1,116 @@ -name mz mzmin mzmax rt rtmin rtmax npeaks KO WT isotopes adduct pcgroup isotopes.1 adduct.1 pcgroup.1 neg. Mode -M208T3291 207.800003051758 207.800003051758 207.800003051758 3291.29196703023 3291.29196703023 3291.29196703023 1 1 0 2102 [M+H]+ 206.793 2102 Found [M+H]+/[M-H]- -M210T3110 210.199996948242 210.199996948242 210.199996948242 3110.11088685014 3110.11088685014 3110.11088685014 1 1 0 5340 [M+H]+ 209.193 5340 Found [M+H]+/[M-H]- -M228T3846 228.199996948242 228.199996948242 228.199996948242 3846.02686621606 3844.71679072309 3847.33694170903 2 1 1 [M+H-C6H8O6]+ 403.216 [M+2H-NH3]2+ 471.41 21 [M+H]+ 227.193 21 Found [M+H]+/[M-H]- -M235T3976 234.900009155273 234.900009155273 234.900009155273 3976.03175698205 3976.03175698205 3976.03175698205 1 0 1 2000 [M+H]+ 233.893 2000 Found [M+H]+/[M-H]- -M236T3873 236.199996948242 236.199996948242 236.199996948242 3872.50458166888 3872.50458166888 3872.50458166888 1 0 1 2733 [M+H]+ 235.193 2733 Found [M+H]+/[M-H]- -M238T2755 238.199996948242 238.199996948242 238.199996948242 2754.64826033204 2754.64826033204 2754.64826033204 1 0 1 4595 [M+H]+ 237.193 4595 Found [M+H]+/[M-H]- -M239T4130 239 239 239 4130.33844192957 4130.33844192957 4130.33844192957 1 0 1 1473 [M+H]+ 237.993 1473 Found [M+H]+/[M-H]- -M250T4052 250.199996948242 250.199996948242 250.199996948242 4051.60950608857 4051.60950608857 4051.60950608857 1 1 0 77 [M+H]+ 249.193 77 Found [M+H]+/[M-H]- -M258T3448 258.200012207031 258.200012207031 258.200012207031 3448.2651342683 3446.56346688244 3449.96680165415 2 1 1 2922 [M+H]+ 257.193 2922 Found [M+H]+/[M-H]- -M261T2686 261.200012207031 261.200012207031 261.200012207031 2685.68075810517 2685.68075810517 2685.68075810517 1 0 1 640 [M+H]+ 260.193 640 Found [M+H]+/[M-H]- -M266T3323 266.399993896484 266.399993896484 266.399993896484 3322.77149725563 3322.77149725563 3322.77149725563 1 0 1 16 [M+H]+ 265.393 16 Found [M+H]+/[M-H]- -M275T2920 275.200012207031 275.200012207031 275.200012207031 2920.28496696996 2920.28496696996 2920.28496696996 1 0 1 2868 [M+H]+ 274.193 2868 Found [M+H]+/[M-H]- -M276T3867_1 275.899993896484 275.899993896484 275.899993896484 3866.89893599656 3866.89893599656 3866.89893599656 1 1 0 21 [M+H]+ 274.893 21 Found [M+H]+/[M-H]- -M276T2603 276.200012207031 276.200012207031 276.200012207031 2602.85397459635 2602.85397459635 2602.85397459635 1 1 0 5243 [M+H]+ 275.193 5243 Found [M+H]+/[M-H]- -M284T3653 284.100006103516 284.100006103516 284.100006103516 3652.85708680252 3652.85708680252 3652.85708680252 1 1 0 [M+H-CH3]+ 298.114 47 [M+H]+ 283.093 47 Found [M+H]+/[M-H]- -M287T4128 287.100006103516 287.100006103516 287.100006103516 4128.44542811787 4128.44542811787 4128.44542811787 1 1 0 23 [M+H]+ 286.093 23 Found [M+H]+/[M-H]- -M304T3912 304 304 304 3911.73383581848 3911.73383581848 3911.73383581848 1 0 1 4817 [M+H]+ 302.993 4817 Found [M+H]+/[M-H]- -M304T2622 304 304 304 2621.82968780046 2621.82968780046 2621.82968780046 1 0 1 2642 [M+H]+ 302.993 2642 Found [M+H]+/[M-H]- -M310T3484 310.200012207031 310.200012207031 310.200012207031 3483.91470694154 3483.91470694154 3483.91470694154 1 1 0 [M+H-H20]+ 327.208 31 [M+H]+ 309.193 31 Found [M+H]+/[M-H]- -M311T3667 311.200012207031 311.200012207031 311.200012207031 3667.39351291676 3667.39351291676 3667.39351291676 1 1 0 [M+H]+ 310.189 2 [M+H]+ 310.189 2 Found [M+H]+/[M-H]- -M317T4122 317 317 317 4122.17726376076 4122.17726376076 4122.17726376076 1 1 0 1716 [M+H]+ 315.993 1716 Found [M+H]+/[M-H]- -M319T3963 319.300018310547 319.300018310547 319.300018310547 3963.24477198361 3963.24477198361 3963.24477198361 1 0 1 1982 [M+H]+ 318.293 1982 Found [M+H]+/[M-H]- -M326T3910 326.300018310547 326.300018310547 326.300018310547 3910.16592439504 3910.16592439504 3910.16592439504 1 0 1 4822 [M+H]+ 325.293 4822 Found [M+H]+/[M-H]- -M329T3539 329 329 329 3538.57945160982 3538.57945160982 3538.57945160982 1 0 1 1952 [M+H]+ 327.993 1952 Found [M+H]+/[M-H]- -M330T3500 330.200012207031 330.200012207031 330.200012207031 3500.20040677211 3496.75308645138 3503.64772709283 2 1 1 [2M+Na+K]2+ 299.215 76 [M+H]+ 329.193 76 Found [M+H]+/[M-H]- -M333T3521 333 333 333 3520.57714024828 3520.57714024828 3520.57714024828 1 0 1 368 [M+H]+ 331.993 368 Found [M+H]+/[M-H]- -M341T3309 341.200012207031 341.200012207031 341.200012207031 3308.58072998214 3308.58072998214 3308.58072998214 1 0 1 4 [M+H]+ 340.193 4 Found [M+H]+/[M-H]- -M341T4172 341.399993896484 341.399993896484 341.399993896484 4172.42311655854 4172.42311655854 4172.42311655854 1 1 0 4369 [M+H]+ 340.393 4369 Found [M+H]+/[M-H]- -M342T3038 342.300018310547 342.300018310547 342.300018310547 3038.15131755569 3038.15131755569 3038.15131755569 1 0 1 3220 [M+H]+ 341.293 3220 Found [M+H]+/[M-H]- -M345T3788 345 345 345 3788.06929478123 3788.06929478123 3788.06929478123 1 0 1 4445 [M+H]+ 343.993 4445 Found [M+H]+/[M-H]- -M348T3493 348.200012207031 348.200012207031 348.200012207031 3493.19473595505 3488.78600287563 3495.99683372091 3 1 2 31 [M+H]+ 347.193 31 Found [M+H]+/[M-H]- -M349T4038 348.899993896484 348.899993896484 348.899993896484 4038.4655434023 4038.4655434023 4038.4655434023 1 0 1 3765 [M+H]+ 347.893 3765 Found [M+H]+/[M-H]- -M350T3215 350 350 350 3214.6396934876 3214.6396934876 3214.6396934876 1 1 0 4315 [M+H]+ 348.993 4315 Found [M+H]+/[M-H]- -M350T3484 350.200012207031 350.200012207031 350.200012207031 3484.15058009239 3484.15058009239 3484.15058009239 1 0 1 [41][M]+ [M+Na]+ 327.208 31 [41][M]+ [M+H]+ 349.193 31 Found [M+H]+/[M-H]- -M354T4176 354.300018310547 354.300018310547 354.300018310547 4176.48836940693 4176.48836940693 4176.48836940693 1 0 1 4388 [M+H]+ 353.293 4388 Found [M+H]+/[M-H]- -M361T3500 361 361 361 3499.90373818767 3499.90373818767 3499.90373818767 1 1 0 3374 [M+H]+ 359.993 3374 Found [M+H]+/[M-H]- -M362T3394 362.300018310547 362.300018310547 362.300018310547 3394.46678522768 3394.46678522768 3394.46678522768 1 0 1 502 [M+H]+ 361.293 502 Found [M+H]+/[M-H]- -M363T3890 363 363 363 3889.77519285019 3889.77519285019 3889.77519285019 1 0 1 2235 [M+H]+ 361.993 2235 Found [M+H]+/[M-H]- -M369T4287 369.100006103516 369.100006103516 369.100006103516 4286.86322276304 4286.86322276304 4286.86322276304 1 1 0 6094 [M+H]+ 368.093 6094 Found [M+H]+/[M-H]- -M371T4218 371.300018310547 371.300018310547 371.300018310547 4217.96617539246 4217.96617539246 4217.96617539246 1 1 0 5327 [M+H]+ 370.293 5327 Found [M+H]+/[M-H]- -M372T4221 372.300018310547 372.300018310547 372.300018310547 4221.33434899811 4221.33434899811 4221.33434899811 1 0 1 5985 [M+H]+ 371.293 5985 Found [M+H]+/[M-H]- -M375T2994 375.200012207031 375.200012207031 375.200012207031 2994.06985896253 2994.06985896253 2994.06985896253 1 0 1 32 [M+H]+ 374.193 32 Found [M+H]+/[M-H]- -M378T3345 377.899993896484 377.899993896484 377.899993896484 3344.8775026371 3344.8775026371 3344.8775026371 1 1 0 802 [M+H]+ 376.893 802 Found [M+H]+/[M-H]- -M396T4099 396.300018310547 396.300018310547 396.300018310547 4098.66503647187 4098.66503647187 4098.66503647187 2 1 0 150 [M+H]+ 395.293 150 Found [M+H]+/[M-H]- -M399T3288 399 399 399 3287.55118520376 3287.55118520376 3287.55118520376 1 0 1 2111 [M+H]+ 397.993 2111 Found [M+H]+/[M-H]- -M404T2691 404.100006103516 404.100006103516 404.100006103516 2690.57128216482 2690.57128216482 2690.57128216482 1 0 1 [M+H-H20]+ 421.11 6 [M+H]+ 403.093 6 Found [M+H]+/[M-H]- -M406T3575 406 406 406 3574.63014348789 3574.63014348789 3574.63014348789 1 0 1 1668 [M+H]+ 404.993 1668 Found [M+H]+/[M-H]- -M408T3956 408.300018310547 408.300018310547 408.300018310547 3955.84913291293 3955.84913291293 3955.84913291293 1 1 0 5459 [M+H]+ 407.293 5459 Found [M+H]+/[M-H]- -M413T4059 413 413 413 4059.4167690378 4059.4167690378 4059.4167690378 1 0 1 4700 [M+H]+ 411.993 4700 Found [M+H]+/[M-H]- -M415T3626 415.200012207031 415.200012207031 415.200012207031 3625.889727528 3625.889727528 3625.889727528 1 1 0 26 [M+H]+ 414.193 26 Found [M+H]+/[M-H]- -M418T3317 418.399993896484 418.399993896484 418.399993896484 3316.91873178114 3316.91873178114 3316.91873178114 1 0 1 539 [M+H]+ 417.393 539 Found [M+H]+/[M-H]- -M420T4187 420.399993896484 420.399993896484 420.399993896484 4186.55782122692 4186.55782122692 4186.55782122692 1 1 0 6064 [M+H]+ 419.393 6064 Found [M+H]+/[M-H]- -M424T3310 424.399993896484 424.399993896484 424.399993896484 3310.1554922049 3310.1554922049 3310.1554922049 1 0 1 541 [M+H]+ 423.393 541 Found [M+H]+/[M-H]- -M440T4055 440.300018310547 440.300018310547 440.300018310547 4055.33424681125 4054.35262823827 4056.31586538424 2 2 0 [M+H]+ 439.295 77 [M+H]+ 439.295 77 Found [M+H]+/[M-H]- -M441T4111 441.100006103516 441.100006103516 441.100006103516 4111.42132545829 4111.42132545829 4111.42132545829 1 0 1 [M+K]+ 402.132 43 [M+H]+ 440.093 43 Found [M+H]+/[M-H]- -M441T4127_2 441.100006103516 441.100006103516 441.100006103516 4126.89956529202 4126.89956529202 4126.89956529202 1 0 1 [M+Na]+ 418.1 23 [M+H]+ 440.093 23 Found [M+H]+/[M-H]- -M443T3159 443 443 443 3158.51557850104 3158.51557850104 3158.51557850104 1 1 0 838 [M+H]+ 441.993 838 Found [M+H]+/[M-H]- -M445T4143 444.899993896484 444.899993896484 444.899993896484 4142.9532295589 4142.9532295589 4142.9532295589 1 0 1 4236 [M+H]+ 443.893 4236 Found [M+H]+/[M-H]- -M446T2893 446.200012207031 446.200012207031 446.200012207031 2892.58722465327 2892.58722465327 2892.58722465327 1 1 0 [M+Na]+ 423.211 95 [M+H]+ 445.193 95 Found [M+H]+/[M-H]- -M447T4144 446.899993896484 446.899993896484 446.899993896484 4143.9632134336 4143.9632134336 4143.9632134336 1 0 1 5839 [M+H]+ 445.893 5839 Found [M+H]+/[M-H]- -M447T4119 447.100006103516 447.100006103516 447.100006103516 4119.30268860621 4119.30268860621 4119.30268860621 1 0 1 120 [M+H]+ 446.093 120 Found [M+H]+/[M-H]- -M453T3745 453.100006103516 453.100006103516 453.100006103516 3745.49127859189 3745.49127859189 3745.49127859189 1 1 0 [M+H]+ 452.1 14 [M+H]+ 452.1 14 Found [M+H]+/[M-H]- -M461T3139 461.100006103516 461.100006103516 461.100006103516 3139.30178915582 3139.30178915582 3139.30178915582 1 0 1 [2M+Na+K-H]+ 200.089 67 [M+H]+ 460.093 67 Found [M+H]+/[M-H]- -M462T2597 461.899993896484 461.899993896484 461.899993896484 2596.59397459635 2596.59397459635 2596.59397459635 1 1 0 2880 [M+H]+ 460.893 2880 Found [M+H]+/[M-H]- -M465T4110 465.100006103516 465.100006103516 465.100006103516 4109.84516095031 4106.73892937947 4109.84516095031 3 0 2 [M+H-CO]+ 492.092 43 [M+H]+ 464.093 43 Found [M+H]+/[M-H]- -M469T4110 469 469 469 4109.84004353069 4109.84004353069 4109.84004353069 1 0 1 43 [M+H]+ 467.993 43 Found [M+H]+/[M-H]- -M482T3312 482.200012207031 482.200012207031 482.200012207031 3311.84592526338 3310.1554922049 3320.00602941677 3 1 2 4 [M+H]+ 481.193 4 Found [M+H]+/[M-H]- -M486T3726_2 486 486 486 3725.70378168979 3723.46990095085 3727.93766242873 2 1 1 4683 [M+H]+ 484.993 4683 Found [M+H]+/[M-H]- -M486T3654 486.100006103516 486.100006103516 486.100006103516 3654.3034227609 3654.3034227609 3654.3034227609 1 0 1 2410 [M+H]+ 485.093 2410 Found [M+H]+/[M-H]- -M493T2872 493 493 493 2872.43169931851 2872.43169931851 2872.43169931851 1 0 1 4766 [M+H]+ 491.993 4766 Found [M+H]+/[M-H]- -M494T3069 494.300018310547 494.300018310547 494.300018310547 3069.1084825778 3069.1084825778 3069.1084825778 1 1 0 48 [M+H]+ 493.293 48 Found [M+H]+/[M-H]- -M495T3465 495 495 495 3465.11864061023 3465.11864061023 3465.11864061023 1 1 0 1283 [M+H]+ 493.993 1283 Found [M+H]+/[M-H]- -M518T3975 518 518 518 3975.06650309073 3975.06650309073 3975.06650309073 1 1 0 2059 [M+H]+ 516.993 2059 Found [M+H]+/[M-H]- -M520T4132 520.400024414062 520.400024414062 520.400024414062 4131.5173144866 4131.5173144866 4131.5173144866 1 1 0 [M+H]+ 519.397 23 [M+H]+ 519.397 23 Found [M+H]+/[M-H]- -M522T2525 522 522 522 2524.60597459635 2524.60597459635 2524.60597459635 1 1 0 [M+H]+ 520.991 5042 [M+H]+ 520.991 5042 Found [M+H]+/[M-H]- -M528T4044 528.299987792969 528.299987792969 528.299987792969 4043.65478609327 4043.65478609327 4043.65478609327 1 0 1 106 [M+H]+ 527.293 106 Found [M+H]+/[M-H]- -M534T2893_1 534 534 534 2893.43940086615 2893.43940086615 2893.43940086615 1 0 1 95 [M+H]+ 532.993 95 Found [M+H]+/[M-H]- -M534T3169 534.299987792969 534.299987792969 534.299987792969 3169.25148487446 3169.25148487446 3169.25148487446 1 1 0 791 [M+H]+ 533.293 791 Found [M+H]+/[M-H]- -M539T2671 538.900024414062 538.900024414062 538.900024414062 2671.01298815173 2671.01298815173 2671.01298815173 1 1 0 4057 [M+H]+ 537.893 4057 Found [M+H]+/[M-H]- -M541T2916 541.200012207031 541.200012207031 541.200012207031 2915.96882550519 2915.96882550519 2915.96882550519 1 1 0 56 [M+H]+ 540.193 56 Found [M+H]+/[M-H]- -M542T4146 542.5 542.5 542.5 4145.51429793861 4145.51429793861 4145.51429793861 1 0 1 219 [M+H]+ 541.493 219 Found [M+H]+/[M-H]- -M545T3858 545 545 545 3857.79163814401 3857.79163814401 3857.79163814401 1 1 0 1418 [M+H]+ 543.993 1418 Found [M+H]+/[M-H]- -M546T3196 546.200012207031 546.200012207031 546.200012207031 3196.03297484936 3194.01201990731 3198.0539297914 2 1 1 [M+H]+ 545.2 30 [M+H]+ 545.2 30 Found [M+H]+/[M-H]- -M546T3373 546.299987792969 546.299987792969 546.299987792969 3372.50532490707 3372.50532490707 3372.50532490707 1 0 1 1591 [M+H]+ 545.293 1591 Found [M+H]+/[M-H]- -M547T2882 546.900024414062 546.900024414062 546.900024414062 2881.52679761665 2881.52679761665 2881.52679761665 1 1 0 131 [M+H]+ 545.893 131 Found [M+H]+/[M-H]- -M547T2930 546.900024414062 546.900024414062 546.900024414062 2929.96472679346 2929.96472679346 2929.96472679346 1 0 1 3632 [M+H]+ 545.893 3632 Found [M+H]+/[M-H]- -M548T4180_2 548.100036621094 548.100036621094 548.100036621094 4180.12028828767 4180.12028828767 4180.12028828767 1 1 0 6024 [M+H]+ 547.093 6024 Found [M+H]+/[M-H]- -M551T3507 551.100036621094 551.100036621094 551.100036621094 3507.17741350176 3507.17741350176 3507.17741350176 1 1 0 76 [M+H]+ 550.093 76 Found [M+H]+/[M-H]- -M552T3631 552.299987792969 552.299987792969 552.299987792969 3630.7372705795 3630.7372705795 3630.7372705795 1 0 1 2359 [M+H]+ 551.293 2359 Found [M+H]+/[M-H]- -M552T3836 552.400024414062 552.400024414062 552.400024414062 3835.51794589405 3835.51794589405 3835.51794589405 1 0 1 3360 [M+H]+ 551.393 3360 Found [M+H]+/[M-H]- -M552T2806 552.5 552.5 552.5 2805.77058037431 2805.77058037431 2805.77058037431 1 0 1 154 [M+H]+ 551.493 154 Found [M+H]+/[M-H]- -M555T2628 554.799987792969 554.799987792969 554.799987792969 2628.03802468566 2628.03802468566 2628.03802468566 1 1 0 2677 [M+H]+ 553.793 2677 Found [M+H]+/[M-H]- -M560T3524 560.100036621094 560.100036621094 560.100036621094 3524.45539948538 3524.45539948538 3524.45539948538 1 1 0 363 [M+H]+ 559.093 363 Found [M+H]+/[M-H]- -M561T3500 560.900024414062 560.900024414062 560.900024414062 3499.5907337547 3499.5907337547 3499.5907337547 1 0 1 3396 [M+H]+ 559.893 3396 Found [M+H]+/[M-H]- -M566T2712 566 566 566 2712.46713466996 2712.46713466996 2712.46713466996 1 1 0 2531 [M+H]+ 564.993 2531 Found [M+H]+/[M-H]- -M567T2630 566.799987792969 566.799987792969 566.799987792969 2629.63309270258 2629.63309270258 2629.63309270258 1 1 0 2685 [M+H]+ 565.793 2685 Found [M+H]+/[M-H]- -M570T3689 570.5 570.5 570.5 3689.29376228834 3689.29376228834 3689.29376228834 1 0 1 617 [M+H]+ 569.493 617 Found [M+H]+/[M-H]- -M572T2893 571.600036621094 571.600036621094 571.600036621094 2892.58722465327 2892.58722465327 2892.58722465327 1 1 0 95 [M+H]+ 570.593 95 Found [M+H]+/[M-H]- -M574T2913 573.700012207031 573.700012207031 573.700012207031 2912.8908895169 2912.8908895169 2912.8908895169 1 1 0 [M+H]+ 572.692 56 [M+H]+ 572.692 56 Found [M+H]+/[M-H]- -M575T2527 574.700012207031 574.700012207031 574.700012207031 2527.16708488001 2527.16708488001 2527.16708488001 1 0 1 5962 [M+H]+ 573.693 5962 Found [M+H]+/[M-H]- -M578T2852 578.299987792969 578.299987792969 578.299987792969 2852.41195305107 2849.90816808503 2854.91573801711 2 1 1 111 [M+H]+ 577.293 111 Found [M+H]+/[M-H]- -M578T3834 578.400024414062 578.400024414062 578.400024414062 3834.20284641246 3834.20284641246 3834.20284641246 1 1 0 3346 [M+H]+ 577.393 3346 Found [M+H]+/[M-H]- -M580T3296 579.5 579.5 579.5 3296.04055494637 3296.04055494637 3296.04055494637 1 1 0 2610 [M+H]+ 578.493 2610 Found [M+H]+/[M-H]- -M582T3848_2 582.5 582.5 582.5 3847.90453079719 3847.90453079719 3847.90453079719 1 1 0 [M+H]+ 581.493 21 [M+H]+ 581.493 21 Found [M+H]+/[M-H]- -M583T3496 583 583 583 3496.27878193711 3496.27878193711 3496.27878193711 1 1 0 3516 [M+H]+ 581.993 3516 Found [M+H]+/[M-H]- -M583T2581 583.400024414062 583.400024414062 583.400024414062 2581.23728676082 2581.23728676082 2581.23728676082 1 1 0 5692 [M+H]+ 582.393 5692 Found [M+H]+/[M-H]- -M584T2539 584.400024414062 584.400024414062 584.400024414062 2538.69097459635 2538.69097459635 2538.69097459635 1 1 0 5558 [M+H]+ 583.393 5558 Found [M+H]+/[M-H]- -M586T2762 585.900024414062 585.900024414062 585.900024414062 2761.59491820405 2761.59491820405 2761.59491820405 1 1 0 94 [M+H]+ 584.893 94 Found [M+H]+/[M-H]- -M592T4176 591.5 591.5 591.5 4175.56395558154 4175.56395558154 4175.56395558154 1 1 0 115 [M+H]+ 590.493 115 Found [M+H]+/[M-H]- -M593T3448 593.299987792969 593.299987792969 593.299987792969 3448.42769567721 3448.42769567721 3448.42769567721 1 0 1 2939 [M+H]+ 592.293 2939 Found [M+H]+/[M-H]- -M596T4172 596.100036621094 596.100036621094 596.100036621094 4172.42311655854 4172.42311655854 4172.42311655854 1 1 0 4425 [M+H]+ 595.093 4425 Found [M+H]+/[M-H]- -M597T2724 596.799987792969 596.799987792969 596.799987792969 2723.73277209484 2723.73277209484 2723.73277209484 1 0 1 2540 [M+H]+ 595.793 2540 Found [M+H]+/[M-H]- -M598T2738 597.799987792969 597.799987792969 597.799987792969 2737.68724200948 2737.68724200948 2737.68724200948 1 0 1 4444 [M+H]+ 596.793 4444 Found [M+H]+/[M-H]- -M598T3811 598.299987792969 598.299987792969 598.299987792969 3810.99738439489 3810.99738439489 3810.99738439489 1 1 0 46 [M+H]+ 597.293 46 Found [M+H]+/[M-H]- -M598T3177 598.5 598.5 598.5 3176.86596447828 3176.86596447828 3176.86596447828 1 1 0 801 [M+H]+ 597.493 801 Found [M+H]+/[M-H]- +name namecustom mz mzmin mzmax rt rtmin rtmax npeaks KO WT isotopes adduct pcgroup isotopes.1 adduct.1 pcgroup.1 neg. Mode +M208T3291 M207.8T54.9 207.800003051758 207.800003051758 207.800003051758 54.8548661171705 54.8548661171705 54.8548661171705 1 1 0 2102 [M+H]+ 206.793 2102 Found [M+H]+/[M-H]- +M210T3110 M210.2T51.8 210.199996948242 210.199996948242 210.199996948242 51.8351814475023 51.8351814475023 51.8351814475023 1 1 0 5340 [M+H]+ 209.193 5340 Found [M+H]+/[M-H]- +M228T3846 M228.2T64.1 228.199996948242 228.199996948242 228.199996948242 64.1004477702677 64.0786131787182 64.1222823618172 2 1 1 [M+H-C6H8O6]+ 403.216 [M+2H-NH3]2+ 471.41 21 [M+H]+ 227.193 21 Found [M+H]+/[M-H]- +M235T3976 M234.9T66.3 234.900009155273 234.900009155273 234.900009155273 66.2671959497008 66.2671959497008 66.2671959497008 1 0 1 2000 [M+H]+ 233.893 2000 Found [M+H]+/[M-H]- +M236T3873 M236.2T64.5 236.199996948242 236.199996948242 236.199996948242 64.5417430278147 64.5417430278147 64.5417430278147 1 0 1 2733 [M+H]+ 235.193 2733 Found [M+H]+/[M-H]- +M238T2755 M238.2T45.9 238.199996948242 238.199996948242 238.199996948242 45.9108043388673 45.9108043388673 45.9108043388673 1 0 1 4595 [M+H]+ 237.193 4595 Found [M+H]+/[M-H]- +M239T4130 M239T68.8 239 239 239 68.8389740321595 68.8389740321595 68.8389740321595 1 0 1 1473 [M+H]+ 237.993 1473 Found [M+H]+/[M-H]- +M250T4052 M250.2T67.5 250.199996948242 250.199996948242 250.199996948242 67.5268251014762 67.5268251014762 67.5268251014762 1 1 0 77 [M+H]+ 249.193 77 Found [M+H]+/[M-H]- +M258T3448 M258.2T57.5 258.200012207031 258.200012207031 258.200012207031 57.4710855711383 57.4427244480407 57.4994466942358 2 1 1 2922 [M+H]+ 257.193 2922 Found [M+H]+/[M-H]- +M261T2686 M261.2T44.8 261.200012207031 261.200012207031 261.200012207031 44.7613459684195 44.7613459684195 44.7613459684195 1 0 1 640 [M+H]+ 260.193 640 Found [M+H]+/[M-H]- +M266T3323 M266.4T55.4 266.399993896484 266.399993896484 266.399993896484 55.3795249542604 55.3795249542604 55.3795249542604 1 0 1 16 [M+H]+ 265.393 16 Found [M+H]+/[M-H]- +M275T2920 M275.2T48.7 275.200012207031 275.200012207031 275.200012207031 48.671416116166 48.671416116166 48.671416116166 1 0 1 2868 [M+H]+ 274.193 2868 Found [M+H]+/[M-H]- +M276T3867_1 M275.9T64.4_1 275.899993896484 275.899993896484 275.899993896484 64.4483155999427 64.4483155999427 64.4483155999427 1 1 0 21 [M+H]+ 274.893 21 Found [M+H]+/[M-H]- +M276T2603 M276.2T43.4 276.200012207031 276.200012207031 276.200012207031 43.3808995766058 43.3808995766058 43.3808995766058 1 1 0 5243 [M+H]+ 275.193 5243 Found [M+H]+/[M-H]- +M284T3653 M284.1T60.9 284.100006103516 284.100006103516 284.100006103516 60.8809514467087 60.8809514467087 60.8809514467087 1 1 0 [M+H-CH3]+ 298.114 47 [M+H]+ 283.093 47 Found [M+H]+/[M-H]- +M287T4128 M287.1T68.8 287.100006103516 287.100006103516 287.100006103516 68.8074238019644 68.8074238019644 68.8074238019644 1 1 0 23 [M+H]+ 286.093 23 Found [M+H]+/[M-H]- +M304T3912 M304T65.2 304 304 304 65.195563930308 65.195563930308 65.195563930308 1 0 1 4817 [M+H]+ 302.993 4817 Found [M+H]+/[M-H]- +M304T2622 M304T43.7 304 304 304 43.697161463341 43.697161463341 43.697161463341 1 0 1 2642 [M+H]+ 302.993 2642 Found [M+H]+/[M-H]- +M310T3484 M310.2T58.1 310.200012207031 310.200012207031 310.200012207031 58.0652451156923 58.0652451156923 58.0652451156923 1 1 0 [M+H-H20]+ 327.208 31 [M+H]+ 309.193 31 Found [M+H]+/[M-H]- +M311T3667 M311.2T61.1 311.200012207031 311.200012207031 311.200012207031 61.1232252152794 61.1232252152794 61.1232252152794 1 1 0 [M+H]+ 310.189 2 [M+H]+ 310.189 2 Found [M+H]+/[M-H]- +M317T4122 M317T68.7 317 317 317 68.7029543960126 68.7029543960126 68.7029543960126 1 1 0 1716 [M+H]+ 315.993 1716 Found [M+H]+/[M-H]- +M319T3963 M319.3T66.1 319.300018310547 319.300018310547 319.300018310547 66.0540795330602 66.0540795330602 66.0540795330602 1 0 1 1982 [M+H]+ 318.293 1982 Found [M+H]+/[M-H]- +M326T3910 M326.3T65.2 326.300018310547 326.300018310547 326.300018310547 65.1694320732506 65.1694320732506 65.1694320732506 1 0 1 4822 [M+H]+ 325.293 4822 Found [M+H]+/[M-H]- +M329T3539 M329T59 329 329 329 58.976324193497 58.976324193497 58.976324193497 1 0 1 1952 [M+H]+ 327.993 1952 Found [M+H]+/[M-H]- +M330T3500 M330.2T58.3 330.200012207031 330.200012207031 330.200012207031 58.3366734462018 58.279218107523 58.3941287848805 2 1 1 [2M+Na+K]2+ 299.215 76 [M+H]+ 329.193 76 Found [M+H]+/[M-H]- +M333T3521 M333T58.7 333 333 333 58.6762856708046 58.6762856708046 58.6762856708046 1 0 1 368 [M+H]+ 331.993 368 Found [M+H]+/[M-H]- +M341T3309 M341.2T55.1 341.200012207031 341.200012207031 341.200012207031 55.1430121663691 55.1430121663691 55.1430121663691 1 0 1 4 [M+H]+ 340.193 4 Found [M+H]+/[M-H]- +M341T4172 M341.4T69.5 341.399993896484 341.399993896484 341.399993896484 69.5403852759756 69.5403852759756 69.5403852759756 1 1 0 4369 [M+H]+ 340.393 4369 Found [M+H]+/[M-H]- +M342T3038 M342.3T50.6 342.300018310547 342.300018310547 342.300018310547 50.6358552925949 50.6358552925949 50.6358552925949 1 0 1 3220 [M+H]+ 341.293 3220 Found [M+H]+/[M-H]- +M345T3788 M345T63.1 345 345 345 63.1344882463539 63.1344882463539 63.1344882463539 1 0 1 4445 [M+H]+ 343.993 4445 Found [M+H]+/[M-H]- +M348T3493 M348.2T58.2 348.200012207031 348.200012207031 348.200012207031 58.2199122659174 58.1464333812605 58.2666138953485 3 1 2 31 [M+H]+ 347.193 31 Found [M+H]+/[M-H]- +M349T4038 M348.9T67.3 348.899993896484 348.899993896484 348.899993896484 67.3077590567051 67.3077590567051 67.3077590567051 1 0 1 3765 [M+H]+ 347.893 3765 Found [M+H]+/[M-H]- +M350T3215 M350T53.6 350 350 350 53.5773282247933 53.5773282247933 53.5773282247933 1 1 0 4315 [M+H]+ 348.993 4315 Found [M+H]+/[M-H]- +M350T3484 M350.2T58.1 350.200012207031 350.200012207031 350.200012207031 58.0691763348732 58.0691763348732 58.0691763348732 1 0 1 [41][M]+ [M+Na]+ 327.208 31 [41][M]+ [M+H]+ 349.193 31 Found [M+H]+/[M-H]- +M354T4176 M354.3T69.6 354.300018310547 354.300018310547 354.300018310547 69.6081394901155 69.6081394901155 69.6081394901155 1 0 1 4388 [M+H]+ 353.293 4388 Found [M+H]+/[M-H]- +M361T3500 M361T58.3 361 361 361 58.3317289697945 58.3317289697945 58.3317289697945 1 1 0 3374 [M+H]+ 359.993 3374 Found [M+H]+/[M-H]- +M362T3394 M362.3T56.6 362.300018310547 362.300018310547 362.300018310547 56.5744464204614 56.5744464204614 56.5744464204614 1 0 1 502 [M+H]+ 361.293 502 Found [M+H]+/[M-H]- +M363T3890 M363T64.8 363 363 363 64.8295865475032 64.8295865475032 64.8295865475032 1 0 1 2235 [M+H]+ 361.993 2235 Found [M+H]+/[M-H]- +M369T4287 M369.1T71.4 369.100006103516 369.100006103516 369.100006103516 71.4477203793839 71.4477203793839 71.4477203793839 1 1 0 6094 [M+H]+ 368.093 6094 Found [M+H]+/[M-H]- +M371T4218 M371.3T70.3 371.300018310547 371.300018310547 371.300018310547 70.2994362565411 70.2994362565411 70.2994362565411 1 1 0 5327 [M+H]+ 370.293 5327 Found [M+H]+/[M-H]- +M372T4221 M372.3T70.4 372.300018310547 372.300018310547 372.300018310547 70.3555724833019 70.3555724833019 70.3555724833019 1 0 1 5985 [M+H]+ 371.293 5985 Found [M+H]+/[M-H]- +M375T2994 M375.2T49.9 375.200012207031 375.200012207031 375.200012207031 49.9011643160422 49.9011643160422 49.9011643160422 1 0 1 32 [M+H]+ 374.193 32 Found [M+H]+/[M-H]- +M378T3345 M377.9T55.7 377.899993896484 377.899993896484 377.899993896484 55.7479583772851 55.7479583772851 55.7479583772851 1 1 0 802 [M+H]+ 376.893 802 Found [M+H]+/[M-H]- +M396T4099 M396.3T68.3 396.300018310547 396.300018310547 396.300018310547 68.3110839411979 68.3110839411979 68.3110839411979 2 1 0 150 [M+H]+ 395.293 150 Found [M+H]+/[M-H]- +M399T3288 M399T54.8 399 399 399 54.7925197533959 54.7925197533959 54.7925197533959 1 0 1 2111 [M+H]+ 397.993 2111 Found [M+H]+/[M-H]- +M404T2691 M404.1T44.8 404.100006103516 404.100006103516 404.100006103516 44.8428547027469 44.8428547027469 44.8428547027469 1 0 1 [M+H-H20]+ 421.11 6 [M+H]+ 403.093 6 Found [M+H]+/[M-H]- +M406T3575 M406T59.6 406 406 406 59.5771690581316 59.5771690581316 59.5771690581316 1 0 1 1668 [M+H]+ 404.993 1668 Found [M+H]+/[M-H]- +M408T3956 M408.3T65.9 408.300018310547 408.300018310547 408.300018310547 65.9308188818822 65.9308188818822 65.9308188818822 1 1 0 5459 [M+H]+ 407.293 5459 Found [M+H]+/[M-H]- +M413T4059 M413T67.7 413 413 413 67.65694615063 67.65694615063 67.65694615063 1 0 1 4700 [M+H]+ 411.993 4700 Found [M+H]+/[M-H]- +M415T3626 M415.2T60.4 415.200012207031 415.200012207031 415.200012207031 60.4314954588001 60.4314954588001 60.4314954588001 1 1 0 26 [M+H]+ 414.193 26 Found [M+H]+/[M-H]- +M418T3317 M418.4T55.3 418.399993896484 418.399993896484 418.399993896484 55.281978863019 55.281978863019 55.281978863019 1 0 1 539 [M+H]+ 417.393 539 Found [M+H]+/[M-H]- +M420T4187 M420.4T69.8 420.399993896484 420.399993896484 420.399993896484 69.7759636871153 69.7759636871153 69.7759636871153 1 1 0 6064 [M+H]+ 419.393 6064 Found [M+H]+/[M-H]- +M424T3310 M424.4T55.2 424.399993896484 424.399993896484 424.399993896484 55.1692582034151 55.1692582034151 55.1692582034151 1 0 1 541 [M+H]+ 423.393 541 Found [M+H]+/[M-H]- +M440T4055 M440.3T67.6 440.300018310547 440.300018310547 440.300018310547 67.5889041135209 67.5725438039712 67.6052644230706 2 2 0 [M+H]+ 439.295 77 [M+H]+ 439.295 77 Found [M+H]+/[M-H]- +M441T4111 M441.1T68.5 441.100006103516 441.100006103516 441.100006103516 68.5236887576381 68.5236887576381 68.5236887576381 1 0 1 [M+K]+ 402.132 43 [M+H]+ 440.093 43 Found [M+H]+/[M-H]- +M441T4127_2 M441.1T68.8_2 441.100006103516 441.100006103516 441.100006103516 68.7816594215337 68.7816594215337 68.7816594215337 1 0 1 [M+Na]+ 418.1 23 [M+H]+ 440.093 23 Found [M+H]+/[M-H]- +M443T3159 M443T52.6 443 443 443 52.6419263083506 52.6419263083506 52.6419263083506 1 1 0 838 [M+H]+ 441.993 838 Found [M+H]+/[M-H]- +M445T4143 M444.9T69 444.899993896484 444.899993896484 444.899993896484 69.0492204926483 69.0492204926483 69.0492204926483 1 0 1 4236 [M+H]+ 443.893 4236 Found [M+H]+/[M-H]- +M446T2893 M446.2T48.2 446.200012207031 446.200012207031 446.200012207031 48.2097870775546 48.2097870775546 48.2097870775546 1 1 0 [M+Na]+ 423.211 95 [M+H]+ 445.193 95 Found [M+H]+/[M-H]- +M447T4144 M446.9T69.1 446.899993896484 446.899993896484 446.899993896484 69.0660535572266 69.0660535572266 69.0660535572266 1 0 1 5839 [M+H]+ 445.893 5839 Found [M+H]+/[M-H]- +M447T4119 M447.1T68.7 447.100006103516 447.100006103516 447.100006103516 68.6550448101035 68.6550448101035 68.6550448101035 1 0 1 120 [M+H]+ 446.093 120 Found [M+H]+/[M-H]- +M453T3745 M453.1T62.4 453.100006103516 453.100006103516 453.100006103516 62.4248546431982 62.4248546431982 62.4248546431982 1 1 0 [M+H]+ 452.1 14 [M+H]+ 452.1 14 Found [M+H]+/[M-H]- +M461T3139 M461.1T52.3 461.100006103516 461.100006103516 461.100006103516 52.3216964859304 52.3216964859304 52.3216964859304 1 0 1 [2M+Na+K-H]+ 200.089 67 [M+H]+ 460.093 67 Found [M+H]+/[M-H]- +M462T2597 M461.9T43.3 461.899993896484 461.899993896484 461.899993896484 43.2765662432725 43.2765662432725 43.2765662432725 1 1 0 2880 [M+H]+ 460.893 2880 Found [M+H]+/[M-H]- +M465T4110 M465.1T68.5 465.100006103516 465.100006103516 465.100006103516 68.4974193491718 68.4456488229912 68.4974193491718 3 0 2 [M+H-CO]+ 492.092 43 [M+H]+ 464.093 43 Found [M+H]+/[M-H]- +M469T4110 M469T68.5 469 469 469 68.4973340588448 68.4973340588448 68.4973340588448 1 0 1 43 [M+H]+ 467.993 43 Found [M+H]+/[M-H]- +M482T3312 M482.2T55.2 482.200012207031 482.200012207031 482.200012207031 55.1974320877231 55.1692582034151 55.3334338236129 3 1 2 4 [M+H]+ 481.193 4 Found [M+H]+/[M-H]- +M486T3726_2 M486T62.1_2 486 486 486 62.0950630281632 62.0578316825142 62.1322943738121 2 1 1 4683 [M+H]+ 484.993 4683 Found [M+H]+/[M-H]- +M486T3654 M486.1T60.9 486.100006103516 486.100006103516 486.100006103516 60.9050570460149 60.9050570460149 60.9050570460149 1 0 1 2410 [M+H]+ 485.093 2410 Found [M+H]+/[M-H]- +M493T2872 M493T47.9 493 493 493 47.8738616553085 47.8738616553085 47.8738616553085 1 0 1 4766 [M+H]+ 491.993 4766 Found [M+H]+/[M-H]- +M494T3069 M494.3T51.2 494.300018310547 494.300018310547 494.300018310547 51.1518080429633 51.1518080429633 51.1518080429633 1 1 0 48 [M+H]+ 493.293 48 Found [M+H]+/[M-H]- +M495T3465 M495T57.8 495 495 495 57.7519773435038 57.7519773435038 57.7519773435038 1 1 0 1283 [M+H]+ 493.993 1283 Found [M+H]+/[M-H]- +M518T3975 M518T66.3 518 518 518 66.2511083848454 66.2511083848454 66.2511083848454 1 1 0 2059 [M+H]+ 516.993 2059 Found [M+H]+/[M-H]- +M520T4132 M520.4T68.9 520.400024414062 520.400024414062 520.400024414062 68.85862190811 68.85862190811 68.85862190811 1 1 0 [M+H]+ 519.397 23 [M+H]+ 519.397 23 Found [M+H]+/[M-H]- +M522T2525 M522T42.1 522 522 522 42.0767662432725 42.0767662432725 42.0767662432725 1 1 0 [M+H]+ 520.991 5042 [M+H]+ 520.991 5042 Found [M+H]+/[M-H]- +M528T4044 M528.3T67.4 528.299987792969 528.299987792969 528.299987792969 67.3942464348878 67.3942464348878 67.3942464348878 1 0 1 106 [M+H]+ 527.293 106 Found [M+H]+/[M-H]- +M534T2893_1 M534T48.2_1 534 534 534 48.2239900144358 48.2239900144358 48.2239900144358 1 0 1 95 [M+H]+ 532.993 95 Found [M+H]+/[M-H]- +M534T3169 M534.3T52.8 534.299987792969 534.299987792969 534.299987792969 52.820858081241 52.820858081241 52.820858081241 1 1 0 791 [M+H]+ 533.293 791 Found [M+H]+/[M-H]- +M539T2671 M538.9T44.5 538.900024414062 538.900024414062 538.900024414062 44.5168831358622 44.5168831358622 44.5168831358622 1 1 0 4057 [M+H]+ 537.893 4057 Found [M+H]+/[M-H]- +M541T2916 M541.2T48.6 541.200012207031 541.200012207031 541.200012207031 48.5994804250865 48.5994804250865 48.5994804250865 1 1 0 56 [M+H]+ 540.193 56 Found [M+H]+/[M-H]- +M542T4146 M542.5T69.1 542.5 542.5 542.5 69.0919049656436 69.0919049656436 69.0919049656436 1 0 1 219 [M+H]+ 541.493 219 Found [M+H]+/[M-H]- +M545T3858 M545T64.3 545 545 545 64.2965273024001 64.2965273024001 64.2965273024001 1 1 0 1418 [M+H]+ 543.993 1418 Found [M+H]+/[M-H]- +M546T3196 M546.2T53.3 546.200012207031 546.200012207031 546.200012207031 53.2672162474893 53.2335336651218 53.3008988298567 2 1 1 [M+H]+ 545.2 30 [M+H]+ 545.2 30 Found [M+H]+/[M-H]- +M546T3373 M546.3T56.2 546.299987792969 546.299987792969 546.299987792969 56.2084220817844 56.2084220817844 56.2084220817844 1 0 1 1591 [M+H]+ 545.293 1591 Found [M+H]+/[M-H]- +M547T2882 M546.9T48 546.900024414062 546.900024414062 546.900024414062 48.0254466269442 48.0254466269442 48.0254466269442 1 1 0 131 [M+H]+ 545.893 131 Found [M+H]+/[M-H]- +M547T2930 M546.9T48.8 546.900024414062 546.900024414062 546.900024414062 48.8327454465577 48.8327454465577 48.8327454465577 1 0 1 3632 [M+H]+ 545.893 3632 Found [M+H]+/[M-H]- +M548T4180_2 M548.1T69.7_2 548.100036621094 548.100036621094 548.100036621094 69.6686714714612 69.6686714714612 69.6686714714612 1 1 0 6024 [M+H]+ 547.093 6024 Found [M+H]+/[M-H]- +M551T3507 M551.1T58.5 551.100036621094 551.100036621094 551.100036621094 58.452956891696 58.452956891696 58.452956891696 1 1 0 76 [M+H]+ 550.093 76 Found [M+H]+/[M-H]- +M552T3631 M552.3T60.5 552.299987792969 552.299987792969 552.299987792969 60.5122878429917 60.5122878429917 60.5122878429917 1 0 1 2359 [M+H]+ 551.293 2359 Found [M+H]+/[M-H]- +M552T3836 M552.4T63.9 552.400024414062 552.400024414062 552.400024414062 63.9252990982341 63.9252990982341 63.9252990982341 1 0 1 3360 [M+H]+ 551.393 3360 Found [M+H]+/[M-H]- +M552T2806 M552.5T46.8 552.5 552.5 552.5 46.7628430062386 46.7628430062386 46.7628430062386 1 0 1 154 [M+H]+ 551.493 154 Found [M+H]+/[M-H]- +M555T2628 M554.8T43.8 554.799987792969 554.799987792969 554.799987792969 43.800633744761 43.800633744761 43.800633744761 1 1 0 2677 [M+H]+ 553.793 2677 Found [M+H]+/[M-H]- +M560T3524 M560.1T58.7 560.100036621094 560.100036621094 560.100036621094 58.7409233247563 58.7409233247563 58.7409233247563 1 1 0 363 [M+H]+ 559.093 363 Found [M+H]+/[M-H]- +M561T3500 M560.9T58.3 560.900024414062 560.900024414062 560.900024414062 58.3265122292451 58.3265122292451 58.3265122292451 1 0 1 3396 [M+H]+ 559.893 3396 Found [M+H]+/[M-H]- +M566T2712 M566T45.2 566 566 566 45.2077855778326 45.2077855778326 45.2077855778326 1 1 0 2531 [M+H]+ 564.993 2531 Found [M+H]+/[M-H]- +M567T2630 M566.8T43.8 566.799987792969 566.799987792969 566.799987792969 43.8272182117096 43.8272182117096 43.8272182117096 1 1 0 2685 [M+H]+ 565.793 2685 Found [M+H]+/[M-H]- +M570T3689 M570.5T61.5 570.5 570.5 570.5 61.4882293714724 61.4882293714724 61.4882293714724 1 0 1 617 [M+H]+ 569.493 617 Found [M+H]+/[M-H]- +M572T2893 M571.6T48.2 571.600036621094 571.600036621094 571.600036621094 48.2097870775546 48.2097870775546 48.2097870775546 1 1 0 95 [M+H]+ 570.593 95 Found [M+H]+/[M-H]- +M574T2913 M573.7T48.5 573.700012207031 573.700012207031 573.700012207031 48.5481814919484 48.5481814919484 48.5481814919484 1 1 0 [M+H]+ 572.692 56 [M+H]+ 572.692 56 Found [M+H]+/[M-H]- +M575T2527 M574.7T42.1 574.700012207031 574.700012207031 574.700012207031 42.1194514146668 42.1194514146668 42.1194514146668 1 0 1 5962 [M+H]+ 573.693 5962 Found [M+H]+/[M-H]- +M578T2852 M578.3T47.5 578.299987792969 578.299987792969 578.299987792969 47.5401992175178 47.4984694680838 47.5819289669518 2 1 1 111 [M+H]+ 577.293 111 Found [M+H]+/[M-H]- +M578T3834 M578.4T63.9 578.400024414062 578.400024414062 578.400024414062 63.903380773541 63.903380773541 63.903380773541 1 1 0 3346 [M+H]+ 577.393 3346 Found [M+H]+/[M-H]- +M580T3296 M579.5T54.9 579.5 579.5 579.5 54.9340092491062 54.9340092491062 54.9340092491062 1 1 0 2610 [M+H]+ 578.493 2610 Found [M+H]+/[M-H]- +M582T3848_2 M582.5T64.1_2 582.5 582.5 582.5 64.1317421799532 64.1317421799532 64.1317421799532 1 1 0 [M+H]+ 581.493 21 [M+H]+ 581.493 21 Found [M+H]+/[M-H]- +M583T3496 M583T58.3 583 583 583 58.2713130322852 58.2713130322852 58.2713130322852 1 1 0 3516 [M+H]+ 581.993 3516 Found [M+H]+/[M-H]- +M583T2581 M583.4T43 583.400024414062 583.400024414062 583.400024414062 43.0206214460137 43.0206214460137 43.0206214460137 1 1 0 5692 [M+H]+ 582.393 5692 Found [M+H]+/[M-H]- +M584T2539 M584.4T42.3 584.400024414062 584.400024414062 584.400024414062 42.3115162432725 42.3115162432725 42.3115162432725 1 1 0 5558 [M+H]+ 583.393 5558 Found [M+H]+/[M-H]- +M586T2762 M585.9T46 585.900024414062 585.900024414062 585.900024414062 46.0265819700675 46.0265819700675 46.0265819700675 1 1 0 94 [M+H]+ 584.893 94 Found [M+H]+/[M-H]- +M592T4176 M591.5T69.6 591.5 591.5 591.5 69.5927325930257 69.5927325930257 69.5927325930257 1 1 0 115 [M+H]+ 590.493 115 Found [M+H]+/[M-H]- +M593T3448 M593.3T57.5 593.299987792969 593.299987792969 593.299987792969 57.4737949279535 57.4737949279535 57.4737949279535 1 0 1 2939 [M+H]+ 592.293 2939 Found [M+H]+/[M-H]- +M596T4172 M596.1T69.5 596.100036621094 596.100036621094 596.100036621094 69.5403852759756 69.5403852759756 69.5403852759756 1 1 0 4425 [M+H]+ 595.093 4425 Found [M+H]+/[M-H]- +M597T2724 M596.8T45.4 596.799987792969 596.799987792969 596.799987792969 45.3955462015806 45.3955462015806 45.3955462015806 1 0 1 2540 [M+H]+ 595.793 2540 Found [M+H]+/[M-H]- +M598T2738 M597.8T45.6 597.799987792969 597.799987792969 597.799987792969 45.628120700158 45.628120700158 45.628120700158 1 0 1 4444 [M+H]+ 596.793 4444 Found [M+H]+/[M-H]- +M598T3811 M598.3T63.5 598.299987792969 598.299987792969 598.299987792969 63.5166230732481 63.5166230732481 63.5166230732481 1 1 0 46 [M+H]+ 597.293 46 Found [M+H]+/[M-H]- +M598T3177 M598.5T52.9 598.5 598.5 598.5 52.947766074638 52.947766074638 52.947766074638 1 1 0 801 [M+H]+ 597.493 801 Found [M+H]+/[M-H]- diff -r c23aa0cbc550 -r 198b035d4848 tool_dependencies.xml --- a/tool_dependencies.xml Wed Feb 01 12:24:21 2017 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,12 +0,0 @@ - - - - - - - - - - - -