Previous changeset 3:4ca5c7bbc6cf (2016-02-22) Next changeset 5:65770fbcb319 (2016-07-04) |
Commit message:
planemo upload commit 9d47e3b467dbbe0af0d90a937c5e9f2c4b958c4b |
modified:
README.rst abims_CAMERA_combinexsAnnos.xml repository_dependencies.xml tool_dependencies.xml |
added:
CAMERA.r lib.r macros.xml planemo_test.sh test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.negative.Rdata test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.Rdata test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv |
removed:
planemo.sh test-data/xset.group.retcor.group.fillPeaks.annotate.negative.Rdata test-data/xset.group.retcor.group.fillPeaks.annotate.positive.Rdata test-data/xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 CAMERA.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/CAMERA.r Mon Apr 25 11:07:23 2016 -0400 |
[ |
@@ -0,0 +1,175 @@ +#!/usr/bin/env Rscript +# CAMERA.r version="2.2.1" + + + +# ----- PACKAGE ----- +cat("\tPACKAGE INFO\n") + +setRepositories(graphics=F, ind=31) + +#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="") +} +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"); + + + +# ----- ARGUMENTS ----- +cat("\tARGUMENTS INFO\n") + +listArguments = parseCommandArgs(evaluate=FALSE) #interpretation of arguments given in command line as an R list of objects +write.table(as.matrix(listArguments), col.names=F, quote=F, sep='\t') + +cat("\n\n"); + + +# ----- PROCESSING INFILE ----- +cat("\tINFILE PROCESSING INFO\n") + +#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 +} + +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_neg"]]) + xaN=xa + listOFlistArgumentsN=listOFlistArguments + if (exists("xsAnnotate_object")) xaN=xsAnnotate_object + + diffrepN=NULL + if (exists("diffrep")) diffrepN=diffrep +} + + +cat("\n\n") + + +# ----- ARGUMENTS PROCESSING ----- +cat("\tARGUMENTS PROCESSING INFO\n") + +# Save arguments to generate a report +if (!exists("listOFlistArguments")) listOFlistArguments=list() +listOFlistArguments[[paste(format(Sys.time(), "%y%m%d-%H:%M:%S_"),listArguments[["xfunction"]],sep="")]] = listArguments + + +#saving the commun parameters +thefunction = listArguments[["xfunction"]] +listArguments[["xfunction"]]=NULL #delete from the list of arguments + +xsetRdataOutput = paste(thefunction,"RData",sep=".") +if (!is.null(listArguments[["xsetRdataOutput"]])){ + xsetRdataOutput = listArguments[["xsetRdataOutput"]]; listArguments[["xsetRdataOutput"]]=NULL +} + +rplotspdf = "Rplots.pdf" +if (!is.null(listArguments[["rplotspdf"]])){ + rplotspdf = listArguments[["rplotspdf"]]; listArguments[["rplotspdf"]]=NULL +} + +dataMatrixOutput = "dataMatrix.tsv" +if (!is.null(listArguments[["dataMatrixOutput"]])){ + 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 +} + +#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") + } +} + + + +#addition of xset object to the list of arguments in the first position +if (exists("xset") != 0){ + listArguments=append(list(xset), listArguments) +} + +cat("\n\n") + + + + +# ----- PROCESSING INFO ----- +cat("\tMAIN PROCESSING INFO\n") + +#change the default display settings +pdf(file=rplotspdf, width=16, height=12) + + +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"]] + + 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) +} + +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") +save(list=objects2save[objects2save %in% ls()], file=xsetRdataOutput) + +cat("\n\n") + +cat("\tDONE\n") |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 README.rst --- a/README.rst Mon Feb 22 16:49:04 2016 -0500 +++ b/README.rst Mon Apr 25 11:07:23 2016 -0400 |
b |
@@ -2,6 +2,11 @@ Changelog/News -------------- +**Version 2.0.4 - 21/04/2016** + +- UPGRADE: upgrate the CAMERA version from 1.22.0 to 1.26.0 + + **Version 2.0.3 - 10/02/2016** - BUGFIX: better management of errors. Datasets remained green although the process failed @@ -20,3 +25,12 @@ - NEW: combinexsAnnos Check CAMERA ion species annotation due to matching with opposite ion mode + +Test Status +----------- + +Planemo test using conda: passed + +Planemo test using source env.sh: passed + +Planemo shed_test : passed |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 abims_CAMERA_combinexsAnnos.xml --- a/abims_CAMERA_combinexsAnnos.xml Mon Feb 22 16:49:04 2016 -0500 +++ b/abims_CAMERA_combinexsAnnos.xml Mon Apr 25 11:07:23 2016 -0400 |
[ |
@@ -1,21 +1,16 @@ -<tool id="abims_CAMERA_combinexsAnnos" name="CAMERA.combinexsAnnos" version="2.0.3"> +<tool id="abims_CAMERA_combinexsAnnos" name="CAMERA.combinexsAnnos" version="2.0.4"> <description>Wrapper function for the combinexsAnnos CAMERA function. Returns a dataframe with recalculated annotations.</description> - <requirements> - <requirement type="package" version="3.1.2">R</requirement> - <requirement type="binary">Rscript</requirement> - <requirement type="package" version="1.44.0">xcms</requirement> - <requirement type="package" version="1.22.0">camera</requirement> - <requirement type="package" version="2.2.0">camera_w4m_script</requirement> - </requirements> + <macros> + <import>macros.xml</import> + </macros> - <stdio> - <exit_code range="1:" level="fatal" /> - </stdio> + <expand macro="requirements"/> + <expand macro="stdio"/> <command><![CDATA[ - CAMERA.r + @COMMAND_CAMERA_SCRIPT@ xfunction combinexsAnnos image_pos $image_pos image_neg $image_neg @@ -52,31 +47,19 @@ <tests> <test> <!-- TODO: generer des vrais dataset pos et neg--> - <param name="image_pos" value="xset.group.retcor.group.fillPeaks.annotate.positive.Rdata"/> - <param name="image_neg" value="xset.group.retcor.group.fillPeaks.annotate.negative.Rdata"/> + <param name="image_pos" value="faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.Rdata"/> + <param name="image_neg" value="faahOK.xset.group.retcor.group.fillPeaks.annotate.negative.Rdata"/> <param name="pos" value="TRUE"/> <param name="tol" value="2"/> <param name="ruleset" value="1,1"/> - <output name="variableMetadata" file="xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv" /> + <output name="variableMetadata" file="faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv" /> </test> </tests> <help><![CDATA[ - -.. class:: infomark - -**Authors** Carsten Kuhl ckuhl@ipb-halle.de, Ralf Tautenhahn rtautenh@scripps.edu, Steffen Neumann sneumann@@ipb-halle.de - -.. class:: infomark - -**Galaxy integration** ABiMS TEAM - UPMC/CNRS - Station biologique de Roscoff and Yann Guitton yann.guitton@univ-nantes.fr - part of Workflow4Metabolomics.org [W4M] - - | Contact support@workflow4metabolomics.org for any questions or concerns about the Galaxy implementation of this tool. - ---------------------------------------------------- - - + +@HELP_AUTHORS@ ======================= Xcms.combinexsAnnos @@ -209,6 +192,11 @@ Changelog/News -------------- +**Version 2.0.4 - 21/04/2016** + +- UPGRADE: upgrate the CAMERA version from 1.22.0 to 1.26.0 + + **Version 2.0.3 - 10/02/2016** - BUGFIX: better management of errors. Datasets remained green although the process failed @@ -230,10 +218,7 @@ ]]></help> - <citations> - <citation type="doi"> 10.1021/ac202450g</citation> - <citation type="doi">10.1093/bioinformatics/btu813</citation> - </citations> + <expand macro="citation" /> </tool> |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 lib.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/lib.r Mon Apr 25 11:07:23 2016 -0400 |
[ |
b'@@ -0,0 +1,188 @@\n+# lib.r version="2.2.1"\n+\n+#The function create a pdf from the different png generated by diffreport\n+diffreport_png2pdf <- function(filebase, new_file_path) {\n+\n+ pdfEicOutput = paste(new_file_path,filebase,"-eic_visible_pdf",sep="")\n+ pdfBoxOutput = paste(new_file_path,filebase,"-box_visible_pdf",sep="")\n+\n+ system(paste("gm convert ",filebase,"_eic/*.png ",filebase,"_eic.pdf",sep=""))\n+ system(paste("gm convert ",filebase,"_box/*.png ",filebase,"_box.pdf",sep=""))\n+\n+ file.copy(paste(filebase,"_eic.pdf",sep=""), pdfEicOutput)\n+ file.copy(paste(filebase,"_box.pdf",sep=""), pdfBoxOutput)\n+}\n+\n+#The function annotateDiffreport without the corr function which bugs\n+annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv", dataMatrixOutput="dataMatrix.tsv",new_file_path=NULL) {\n+ # Resolve the bug with x11, with the function png\n+ options(bitmapType=\'cairo\')\n+\n+ #Check if the fillpeaks step has been done previously, if it hasn\'t, there is an error message and the execution is stopped.\n+ res=try(is.null(xset@filled))\n+\n+ # ------ annot -------\n+ listArguments[["calcCiS"]]=as.logical(listArguments[["calcCiS"]])\n+ listArguments[["calcIso"]]=as.logical(listArguments[["calcIso"]])\n+ listArguments[["calcCaS"]]=as.logical(listArguments[["calcCaS"]])\n+\n+ #graphMethod parameter bugs where this parameter is not defined in quick=true\n+ if(listArguments[["quick"]]==TRUE) {\n+ 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"]])\n+ }\n+ else {\n+ 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"]])\n+\n+ } \n+ peakList=getPeaklist(xa,intval=listArguments[["intval"]])\n+ peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name");\n+\n+\n+ # --- Multi condition : diffreport --- \n+ diffrep=NULL\n+ if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) {\n+ #Check if the fillpeaks step has been done previously, if it hasn\'t, there is an error message and the execution is stopped.\n+ res=try(is.null(xset@filled))\n+ classes=levels(sampclass(xset))\n+ x=1:(length(classes)-1)\n+ for (i in seq(along=x) ) {\n+ y=1:(length(classes))\n+ for (n in seq(along=y)){\n+ if(i+n <= length(classes)){\n+ filebase=paste(classes[i],class2=classes[i+n],sep="-vs-")\n+\n+ 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"]])\n+ #combines results\n+ diffreportTSV=merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F)\n+ diffreportTSV=cbind(diffreportTSV[,!(colnames(diffreportTSV) %in% c(sampnames(xa@xcmsSet)))],diffreportTSV[,(colnames(diffreportTSV) %in% c(sampnames(xa@xcmsSet)))])\n+\n+ if(listArguments[["sortpval"]]){\n+ diffreportTSV=diffr'..b'["num_digits"]]),"T",round(variableMetadata$rt),sep="") \n+ write.table(variableMetadata, sep="\\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput)\n+\n+ # --- dataMatrix ---\n+ dataMatrix = peakList[,(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))]\n+ dataMatrix=cbind(peakList$name,dataMatrix); colnames(dataMatrix)[1] = c("name");\n+\n+ if (listArguments[["convert_param"]]){\n+ #converting the retention times (seconds) into minutes\n+ print("converting the retention times into minutes in the dataMatrix ids")\n+ peakList$rt=peakList$rt/60\n+ }\n+ dataMatrix$name= paste("M",round(peakList$mz,digits=listArguments[["num_digits"]]),"T",round(peakList$rt),sep="")\n+ write.table(dataMatrix, sep="\\t", quote=FALSE, row.names=FALSE, file=dataMatrixOutput)\n+ \n+ return(list("xa"=xa,"diffrep"=diffrep,"variableMetadata"=variableMetadataOri));\n+\n+}\n+\n+\n+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"){\n+\n+ #Load the two Rdata to extract the xset objects from positive and negative mode\n+ cat("\\tObject xset from positive mode\\n")\n+ print(xaP)\n+ cat("\\n") \n+\n+ cat("\\tObject xset from negative mode\\n")\n+ print(xaN)\n+ cat("\\n")\n+ \n+ cat("\\n")\n+ cat("\\tCombining...\\n")\n+ #Convert the string to numeric for creating matrix\n+ row=as.numeric(strsplit(ruleset,",")[[1]][1])\n+ column=as.numeric(strsplit(ruleset,",")[[1]][2])\n+ ruleset=cbind(row,column)\n+ #Test if the file comes from an older version tool\n+ if ((!is.null(xaP)) & (!is.null(xaN))) {\n+ #Launch the combinexsannos function from CAMERA\n+ cAnnot=combinexsAnnos(xaP, xaN,pos=pos,tol=tol,ruleset=ruleset)\n+ } else {\n+ stop("You must relauch the CAMERA.annotate step with the lastest version.")\n+ }\n+\n+ \n+\n+ if(pos){\n+ xa=xaP\n+ listOFlistArgumentsP=listOFlistArguments\n+ mode="neg. Mode"\n+ } else {\n+ xa=xaN\n+ listOFlistArgumentsN=listOFlistArguments\n+ mode="pos. Mode"\n+ }\n+ intval = "into"; for (steps in names(listOFlistArguments)) { if (!is.null(listOFlistArguments[[steps]]$intval)) intval = listOFlistArguments[[steps]]$intval }\n+ peakList=getPeaklist(xa,intval=intval)\n+ peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name");\n+ variableMetadata=cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup",mode)]);\n+ variableMetadata=variableMetadata[,!(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))]\n+\n+ #Test if there are more than two classes (conditions)\n+ if ( nlevels(sampclass(xaP@xcmsSet))==2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) {\n+ diffrepP = diffrepP[,c("name","fold","tstat","pvalue")]; colnames(diffrepP) = paste("P.",colnames(diffrepP),sep="")\n+ diffrepN = diffrepN[,c("name","fold","tstat","pvalue")]; colnames(diffrepN) = paste("N.",colnames(diffrepN),sep="")\n+ \n+ variableMetadata = merge(variableMetadata, diffrepP, by.x="name", by.y="P.name")\n+ variableMetadata = merge(variableMetadata, diffrepN, by.x="name", by.y="N.name")\n+ } \n+ \n+ rownames(variableMetadata) = NULL\n+ #TODO: checker\n+ #colnames(variableMetadata)[1:2] = c("name","mz/rt");\n+\n+ #If the user want to convert the retention times (seconds) into minutes.\n+ if (listArguments[["convert_param"]]){\n+ #converting the retention times (seconds) into minutes\n+ cat("\\tConverting the retention times into minutes\\n")\n+ variableMetadata$rtmed=cAnnot$rt/60; variableMetadata$rtmin=cAnnot$rtmin/60; variableMetadata$rtmax=cAnnot$rtmax/60;\n+ }\n+\n+ #If the user want to keep only the metabolites which match a difference\n+ if(keep_meta){\n+ variableMetadata=variableMetadata[variableMetadata[,c(mode)]!="",]\n+ }\n+ \n+ #Write the output into a tsv file\n+ write.table(variableMetadata, sep="\\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput)\n+ return(variableMetadata);\n+\n+}\n' |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 macros.xml --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/macros.xml Mon Apr 25 11:07:23 2016 -0400 |
[ |
@@ -0,0 +1,46 @@ +<?xml version="1.0"?> +<macros> + <xml name="requirements"> + <requirements> + <requirement type="package" version="3.1.2">R</requirement> + <requirement type="package" version="0.4_1">r-snow</requirement> + <requirement type="package" version="1.26.0">bioconductor-camera</requirement> + <requirement type="package" version="2.26.0">bioconductor-multtest</requirement> + <requirement type="package" version="1.1_4">r-batch</requirement> + <requirement type="package" version="1.6.17">libpng</requirement> + <requirement type="package" version="1.3.20">graphicsmagick</requirement> + </requirements> + </xml> + <xml name="stdio"> + <stdio> + <exit_code range="1" level="fatal" /> + </stdio> + </xml> + + <token name="@COMMAND_CAMERA_SCRIPT@"> + LANG=C Rscript $__tool_directory__/CAMERA.r + </token> + + <token name="@HELP_AUTHORS@"> +.. 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 + +.. class:: infomark + +**Galaxy integration** ABiMS TEAM - UPMC/CNRS - Station biologique de Roscoff and Yann Guitton yann.guitton@oniris-nantes.fr - part of Workflow4Metabolomics.org [W4M] + + | Contact support@workflow4metabolomics.org for any questions or concerns about the Galaxy implementation of this tool. + +--------------------------------------------------- + + </token> + + + <xml name="citation"> + <citations> + <citation type="doi">10.1021/ac202450g</citation> + <citation type="doi">10.1093/bioinformatics/btu813</citation> + </citations> + </xml> +</macros> |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 planemo.sh --- a/planemo.sh Mon Feb 22 16:49:04 2016 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 |
[ |
@@ -1,1 +0,0 @@ -planemo shed_init -f --name=camera_combinexsannos --owner=lecorguille --description="[W4M][GC-MS] CAMERA R Package - Preprocessing - combinexsAnnos Check CAMERA ion species annotation due to matching with opposite ion mode" --homepage_url="http://workflow4metabolomics.org" --long_description="Part of the W4M project: http://workflow4metabolomics.org CAMERA: http://bioconductor.org/packages/release/bioc/html/CAMERA.html This function check annotations of ion species with the help of a sample from opposite ion mode. As first step it searches for pseudospectra from the positive and the negative sample within a retention time window. For every result the m/z differences between both samples are matched against specific rules, which are combinations from pos. and neg. ion species. As example M+H and M-H with a m/z difference of 2.014552. If two ions matches such a difference, the ion annotations are changed (previous annotation is wrong), confirmed or added. Returns the peaklist from one ion mode with recalculated annotations. BEWARE: this tool don't come with its script. You will need to install the dedicated package_camara_w4m_script too" --category="Metabolomics" |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 planemo_test.sh --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/planemo_test.sh Mon Apr 25 11:07:23 2016 -0400 |
[ |
@@ -0,0 +1,19 @@ +# Example of planemo command to launch test + +# Note: --galaxy_branch "dev" is set to deal with zip file + + +# -- Use of conda dependencies +planemo conda_init --conda_prefix /tmp/mc +planemo conda_install --conda_prefix /tmp/mc . +planemo test --install_galaxy --conda_prefix /tmp/mc --conda_dependency_resolution --galaxy_branch "dev" + +#All 1 test(s) executed passed. +#abims_CAMERA_combinexsAnnos[0]: passed + + +# -- Use of shed_test +planemo shed_test --install_galaxy -t testtoolshed + +#All 1 test(s) executed passed. +#testtoolshed.g2.bx.psu.edu/repos/mmonsoor/camera_combinexsannos/abims_CAMERA_combinexsAnnos/2.0.4[0]: passed |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 repository_dependencies.xml --- a/repository_dependencies.xml Mon Feb 22 16:49:04 2016 -0500 +++ b/repository_dependencies.xml Mon Apr 25 11:07:23 2016 -0400 |
b |
@@ -1,4 +1,5 @@ <?xml version="1.0"?> <repositories> <repository changeset_revision="4a51ab3d8ecf" name="rdata_camera_datatypes" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" /> + <repository changeset_revision="d64562a4ebb3" name="rdata_xcms_datatypes" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" /> </repositories> |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.negative.Rdata |
b |
Binary file test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.negative.Rdata has changed |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.Rdata |
b |
Binary file test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.Rdata has changed |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/faahOK.xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv Mon Apr 25 11:07:23 2016 -0400 |
[ |
b'@@ -0,0 +1,116 @@\n+name\tmz\tmzmin\tmzmax\trt\trtmin\trtmax\tnpeaks\tKO\tWT\tisotopes\tadduct\tpcgroup\tisotopes.1\tadduct.1\tpcgroup.1\tneg. Mode\n+M208T3291\t207.800003051758\t207.800003051758\t207.800003051758\t3291.29196703023\t3291.29196703023\t3291.29196703023\t1\t1\t0\t\t\t2102\t\t[M+H]+ 206.793\t2102\tFound [M+H]+/[M-H]-\n+M210T3110\t210.199996948242\t210.199996948242\t210.199996948242\t3110.11088685014\t3110.11088685014\t3110.11088685014\t1\t1\t0\t\t\t5340\t\t[M+H]+ 209.193\t5340\tFound [M+H]+/[M-H]-\n+M228T3846\t228.199996948242\t228.199996948242\t228.199996948242\t3846.02686621606\t3844.71679072309\t3847.33694170903\t2\t1\t1\t\t[M+H-C6H8O6]+ 403.216 [M+2H-NH3]2+ 471.41\t21\t\t[M+H]+ 227.193\t21\tFound [M+H]+/[M-H]-\n+M235T3976\t234.900009155273\t234.900009155273\t234.900009155273\t3976.03175698205\t3976.03175698205\t3976.03175698205\t1\t0\t1\t\t\t2000\t\t[M+H]+ 233.893\t2000\tFound [M+H]+/[M-H]-\n+M236T3873\t236.199996948242\t236.199996948242\t236.199996948242\t3872.50458166888\t3872.50458166888\t3872.50458166888\t1\t0\t1\t\t\t2733\t\t[M+H]+ 235.193\t2733\tFound [M+H]+/[M-H]-\n+M238T2755\t238.199996948242\t238.199996948242\t238.199996948242\t2754.64826033204\t2754.64826033204\t2754.64826033204\t1\t0\t1\t\t\t4595\t\t[M+H]+ 237.193\t4595\tFound [M+H]+/[M-H]-\n+M239T4130\t239\t239\t239\t4130.33844192957\t4130.33844192957\t4130.33844192957\t1\t0\t1\t\t\t1473\t\t[M+H]+ 237.993\t1473\tFound [M+H]+/[M-H]-\n+M250T4052\t250.199996948242\t250.199996948242\t250.199996948242\t4051.60950608857\t4051.60950608857\t4051.60950608857\t1\t1\t0\t\t\t77\t\t[M+H]+ 249.193\t77\tFound [M+H]+/[M-H]-\n+M258T3448\t258.200012207031\t258.200012207031\t258.200012207031\t3448.2651342683\t3446.56346688244\t3449.96680165415\t2\t1\t1\t\t\t2922\t\t[M+H]+ 257.193\t2922\tFound [M+H]+/[M-H]-\n+M261T2686\t261.200012207031\t261.200012207031\t261.200012207031\t2685.68075810517\t2685.68075810517\t2685.68075810517\t1\t0\t1\t\t\t640\t\t[M+H]+ 260.193\t640\tFound [M+H]+/[M-H]-\n+M266T3323\t266.399993896484\t266.399993896484\t266.399993896484\t3322.77149725563\t3322.77149725563\t3322.77149725563\t1\t0\t1\t\t\t16\t\t[M+H]+ 265.393\t16\tFound [M+H]+/[M-H]-\n+M275T2920\t275.200012207031\t275.200012207031\t275.200012207031\t2920.28496696996\t2920.28496696996\t2920.28496696996\t1\t0\t1\t\t\t2868\t\t[M+H]+ 274.193\t2868\tFound [M+H]+/[M-H]-\n+M276T3867_1\t275.899993896484\t275.899993896484\t275.899993896484\t3866.89893599656\t3866.89893599656\t3866.89893599656\t1\t1\t0\t\t\t21\t\t[M+H]+ 274.893\t21\tFound [M+H]+/[M-H]-\n+M276T2603\t276.200012207031\t276.200012207031\t276.200012207031\t2602.85397459635\t2602.85397459635\t2602.85397459635\t1\t1\t0\t\t\t5243\t\t[M+H]+ 275.193\t5243\tFound [M+H]+/[M-H]-\n+M284T3653\t284.100006103516\t284.100006103516\t284.100006103516\t3652.85708680252\t3652.85708680252\t3652.85708680252\t1\t1\t0\t\t[M+H-CH3]+ 298.114\t47\t\t[M+H]+ 283.093\t47\tFound [M+H]+/[M-H]-\n+M287T4128\t287.100006103516\t287.100006103516\t287.100006103516\t4128.44542811787\t4128.44542811787\t4128.44542811787\t1\t1\t0\t\t\t23\t\t[M+H]+ 286.093\t23\tFound [M+H]+/[M-H]-\n+M304T3912\t304\t304\t304\t3911.73383581848\t3911.73383581848\t3911.73383581848\t1\t0\t1\t\t\t4817\t\t[M+H]+ 302.993\t4817\tFound [M+H]+/[M-H]-\n+M304T2622\t304\t304\t304\t2621.82968780046\t2621.82968780046\t2621.82968780046\t1\t0\t1\t\t\t2642\t\t[M+H]+ 302.993\t2642\tFound [M+H]+/[M-H]-\n+M310T3484\t310.200012207031\t310.200012207031\t310.200012207031\t3483.91470694154\t3483.91470694154\t3483.91470694154\t1\t1\t0\t\t[M+H-H20]+ 327.208\t31\t\t[M+H]+ 309.193\t31\tFound [M+H]+/[M-H]-\n+M311T3667\t311.200012207031\t311.200012207031\t311.200012207031\t3667.39351291676\t3667.39351291676\t3667.39351291676\t1\t1\t0\t\t[M+H]+ 310.189\t2\t\t[M+H]+ 310.189\t2\tFound [M+H]+/[M-H]-\n+M317T4122\t317\t317\t317\t4122.17726376076\t4122.17726376076\t4122.17726376076\t1\t1\t0\t\t\t1716\t\t[M+H]+ 315.993\t1716\tFound [M+H]+/[M-H]-\n+M319T3963\t319.300018310547\t319.300018310547\t319.300018310547\t3963.24477198361\t3963.24477198361\t3963.24477198361\t1\t0\t1\t\t\t1982\t\t[M+H]+ 318.293\t1982\tFound [M+H]+/[M-H]-\n+M326T3910\t326.300018310547\t326.300018310547\t326.300018310547\t3910.16592439504\t3910.16592439504\t3910.16592439504\t1\t0\t1\t\t\t4822\t\t[M+H]+ 325.293\t4822\tFound [M+H]+/[M-H]-\n+M329T3539\t329\t329\t329\t3538.57945160982\t3538.57945160982\t3538.57945160982\t1\t0\t1\t\t\t1952\t\t[M+H]+ 327.993\t1952\tFound [M+H]+/[M-H]-'..b'62\t3835.51794589405\t3835.51794589405\t3835.51794589405\t1\t0\t1\t\t\t3360\t\t[M+H]+ 551.393\t3360\tFound [M+H]+/[M-H]-\n+M552T2806\t552.5\t552.5\t552.5\t2805.77058037431\t2805.77058037431\t2805.77058037431\t1\t0\t1\t\t\t154\t\t[M+H]+ 551.493\t154\tFound [M+H]+/[M-H]-\n+M555T2628\t554.799987792969\t554.799987792969\t554.799987792969\t2628.03802468566\t2628.03802468566\t2628.03802468566\t1\t1\t0\t\t\t2677\t\t[M+H]+ 553.793\t2677\tFound [M+H]+/[M-H]-\n+M560T3524\t560.100036621094\t560.100036621094\t560.100036621094\t3524.45539948538\t3524.45539948538\t3524.45539948538\t1\t1\t0\t\t\t363\t\t[M+H]+ 559.093\t363\tFound [M+H]+/[M-H]-\n+M561T3500\t560.900024414062\t560.900024414062\t560.900024414062\t3499.5907337547\t3499.5907337547\t3499.5907337547\t1\t0\t1\t\t\t3396\t\t[M+H]+ 559.893\t3396\tFound [M+H]+/[M-H]-\n+M566T2712\t566\t566\t566\t2712.46713466996\t2712.46713466996\t2712.46713466996\t1\t1\t0\t\t\t2531\t\t[M+H]+ 564.993\t2531\tFound [M+H]+/[M-H]-\n+M567T2630\t566.799987792969\t566.799987792969\t566.799987792969\t2629.63309270258\t2629.63309270258\t2629.63309270258\t1\t1\t0\t\t\t2685\t\t[M+H]+ 565.793\t2685\tFound [M+H]+/[M-H]-\n+M570T3689\t570.5\t570.5\t570.5\t3689.29376228834\t3689.29376228834\t3689.29376228834\t1\t0\t1\t\t\t617\t\t[M+H]+ 569.493\t617\tFound [M+H]+/[M-H]-\n+M572T2893\t571.600036621094\t571.600036621094\t571.600036621094\t2892.58722465327\t2892.58722465327\t2892.58722465327\t1\t1\t0\t\t\t95\t\t[M+H]+ 570.593\t95\tFound [M+H]+/[M-H]-\n+M574T2913\t573.700012207031\t573.700012207031\t573.700012207031\t2912.8908895169\t2912.8908895169\t2912.8908895169\t1\t1\t0\t\t[M+H]+ 572.692\t56\t\t[M+H]+ 572.692\t56\tFound [M+H]+/[M-H]-\n+M575T2527\t574.700012207031\t574.700012207031\t574.700012207031\t2527.16708488001\t2527.16708488001\t2527.16708488001\t1\t0\t1\t\t\t5962\t\t[M+H]+ 573.693\t5962\tFound [M+H]+/[M-H]-\n+M578T2852\t578.299987792969\t578.299987792969\t578.299987792969\t2852.41195305107\t2849.90816808503\t2854.91573801711\t2\t1\t1\t\t\t111\t\t[M+H]+ 577.293\t111\tFound [M+H]+/[M-H]-\n+M578T3834\t578.400024414062\t578.400024414062\t578.400024414062\t3834.20284641246\t3834.20284641246\t3834.20284641246\t1\t1\t0\t\t\t3346\t\t[M+H]+ 577.393\t3346\tFound [M+H]+/[M-H]-\n+M580T3296\t579.5\t579.5\t579.5\t3296.04055494637\t3296.04055494637\t3296.04055494637\t1\t1\t0\t\t\t2610\t\t[M+H]+ 578.493\t2610\tFound [M+H]+/[M-H]-\n+M582T3848_2\t582.5\t582.5\t582.5\t3847.90453079719\t3847.90453079719\t3847.90453079719\t1\t1\t0\t\t[M+H]+ 581.493\t21\t\t[M+H]+ 581.493\t21\tFound [M+H]+/[M-H]-\n+M583T3496\t583\t583\t583\t3496.27878193711\t3496.27878193711\t3496.27878193711\t1\t1\t0\t\t\t3516\t\t[M+H]+ 581.993\t3516\tFound [M+H]+/[M-H]-\n+M583T2581\t583.400024414062\t583.400024414062\t583.400024414062\t2581.23728676082\t2581.23728676082\t2581.23728676082\t1\t1\t0\t\t\t5692\t\t[M+H]+ 582.393\t5692\tFound [M+H]+/[M-H]-\n+M584T2539\t584.400024414062\t584.400024414062\t584.400024414062\t2538.69097459635\t2538.69097459635\t2538.69097459635\t1\t1\t0\t\t\t5558\t\t[M+H]+ 583.393\t5558\tFound [M+H]+/[M-H]-\n+M586T2762\t585.900024414062\t585.900024414062\t585.900024414062\t2761.59491820405\t2761.59491820405\t2761.59491820405\t1\t1\t0\t\t\t94\t\t[M+H]+ 584.893\t94\tFound [M+H]+/[M-H]-\n+M592T4176\t591.5\t591.5\t591.5\t4175.56395558154\t4175.56395558154\t4175.56395558154\t1\t1\t0\t\t\t115\t\t[M+H]+ 590.493\t115\tFound [M+H]+/[M-H]-\n+M593T3448\t593.299987792969\t593.299987792969\t593.299987792969\t3448.42769567721\t3448.42769567721\t3448.42769567721\t1\t0\t1\t\t\t2939\t\t[M+H]+ 592.293\t2939\tFound [M+H]+/[M-H]-\n+M596T4172\t596.100036621094\t596.100036621094\t596.100036621094\t4172.42311655854\t4172.42311655854\t4172.42311655854\t1\t1\t0\t\t\t4425\t\t[M+H]+ 595.093\t4425\tFound [M+H]+/[M-H]-\n+M597T2724\t596.799987792969\t596.799987792969\t596.799987792969\t2723.73277209484\t2723.73277209484\t2723.73277209484\t1\t0\t1\t\t\t2540\t\t[M+H]+ 595.793\t2540\tFound [M+H]+/[M-H]-\n+M598T2738\t597.799987792969\t597.799987792969\t597.799987792969\t2737.68724200948\t2737.68724200948\t2737.68724200948\t1\t0\t1\t\t\t4444\t\t[M+H]+ 596.793\t4444\tFound [M+H]+/[M-H]-\n+M598T3811\t598.299987792969\t598.299987792969\t598.299987792969\t3810.99738439489\t3810.99738439489\t3810.99738439489\t1\t1\t0\t\t\t46\t\t[M+H]+ 597.293\t46\tFound [M+H]+/[M-H]-\n+M598T3177\t598.5\t598.5\t598.5\t3176.86596447828\t3176.86596447828\t3176.86596447828\t1\t1\t0\t\t\t801\t\t[M+H]+ 597.493\t801\tFound [M+H]+/[M-H]-\n' |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 test-data/xset.group.retcor.group.fillPeaks.annotate.negative.Rdata |
b |
Binary file test-data/xset.group.retcor.group.fillPeaks.annotate.negative.Rdata has changed |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 test-data/xset.group.retcor.group.fillPeaks.annotate.positive.Rdata |
b |
Binary file test-data/xset.group.retcor.group.fillPeaks.annotate.positive.Rdata has changed |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 test-data/xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv --- a/test-data/xset.group.retcor.group.fillPeaks.annotate.positive.combinexsAnnos.variableMetadata.tsv Mon Feb 22 16:49:04 2016 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 |
[ |
b'@@ -1,443 +0,0 @@\n-name\tmz\tmzmin\tmzmax\trt\trtmin\trtmax\tnpeaks\tbio\tblank\tisotopes\tadduct\tpcgroup\tisotopes.1\tadduct.1\tpcgroup.1\tneg. Mode\tP.fold\tP.tstat\tP.pvalue\tN.fold\tN.tstat\tN.pvalue\n-M100T333\t99.7608703656017\t99.7579925622581\t99.7637481689453\t333.27937598949\t328.522653453703\t338.036098525276\t2\t2\t0\t\t\t2685\t\t[M+H]+ 98.7536\t2685\tFound [M+H]+/[M-H]-\tInf\t-1.55778367320295\t0.194281864373894\tInf\t-1.55778367320295\t0.194281864373894\n-M105T334\t104.969993591309\t104.969123840332\t104.974052429199\t334.478718537907\t324.592900472048\t337.651441387759\t3\t3\t0\t\t\t447\t\t[M+H]+ 103.963\t447\tFound [M+H]+/[M-H]-\tInf\t-2.22723998769578\t0.0898860418679983\tInf\t-2.22723998769578\t0.0898860418679983\n-M105T351\t105.068378448486\t105.067970275879\t105.068786621094\t351.386774186232\t347.221611236822\t355.551937135641\t2\t2\t0\t\t\t3997\t\t[M+H]+ 104.061\t3997\tFound [M+H]+/[M-H]-\tInf\t-1.59651904953616\t0.185608721674373\tInf\t-1.59651904953616\t0.185608721674373\n-M105T50\t104.953605944178\t104.953545099449\t104.953649972076\t50.3907155634095\t49.6178104857725\t50.9443283160701\t9\t5\t4\t\t\t2764\t\t[M+H]+ 103.946\t2764\tFound [M+H]+/[M-H]-\t10.5982737604496\t-4.05989724028937\t0.0149522950904051\t10.5982737604496\t-4.05989724028937\t0.0149522950904051\n-M107T612\t106.961769104004\t106.957008361816\t106.966850280762\t612.036721541263\t601.253270307699\t622.647860267903\t4\t2\t1\t\t\t788\t\t[M+H]+ 105.954\t788\tFound [M+H]+/[M-H]-\t1.61172067848418\t-0.435354993611172\t0.676729042644553\t1.61172067848418\t-0.435354993611172\t0.676729042644553\n-M108T158\t107.96764755249\t107.966781616211\t107.96851348877\t157.956646561526\t155.536586952915\t160.376706170137\t2\t2\t0\t\t\t2023\t\t[M+H]+ 106.96\t2023\tFound [M+H]+/[M-H]-\tInf\t-1.60266546596844\t0.184269691166154\tInf\t-1.60266546596844\t0.184269691166154\n-M109T449\t108.816116377336\t108.814308255161\t108.817924499512\t448.912893881038\t444.074090249992\t453.751697512084\t2\t0\t2\t\t\t3088\t\t[M+H]+ 107.809\t3088\tFound [M+H]+/[M-H]-\t6.03160239028391\t1.10590709850315\t0.342684415671412\t6.03160239028391\t1.10590709850315\t0.342684415671412\n-M111T338\t111.044788224338\t111.044772467703\t111.044904694196\t338.333820229404\t334.093721862283\t339.181512181095\t5\t4\t0\t\t\t4073\t\t[M+H]+ 110.038\t4073\tFound [M+H]+/[M-H]-\tInf\t-3.36915704173404\t0.0280656260833783\tInf\t-3.36915704173404\t0.0280656260833783\n-M111T51\t110.898692794353\t110.898632566322\t110.898796114692\t51.2816141527486\t50.8226098386928\t52.1310769607387\t7\t5\t2\t\t[M+K]+ 71.9347 [M+2K]2+ 143.871\t63\t\t[M+H]+ 109.891\t63\tFound [M+H]+/[M-H]-\t107.234435520687\t-4.24543895866595\t0.0131782897563633\t107.234435520687\t-4.24543895866595\t0.0131782897563633\n-M112T292\t112.051302298222\t112.051191770866\t112.051437223534\t292.479304705274\t281.990468509378\t306.031931766139\t5\t3\t0\t\t\t4962\t\t[M+H]+ 111.044\t4962\tFound [M+H]+/[M-H]-\t3.11039852357677\t-2.54193654908641\t0.0575392267614276\t3.11039852357677\t-2.54193654908641\t0.0575392267614276\n-M112T54\t112.034626289918\t112.034597639046\t112.034654940791\t54.2708182035323\t54.189059479882\t54.3525769271825\t2\t2\t0\t\t\t1882\t\t[M+H]+ 111.027\t1882\tFound [M+H]+/[M-H]-\tInf\t-1.43289475153763\t0.22517090560669\tInf\t-1.43289475153763\t0.22517090560669\n-M115T362\t115.384078451829\t115.37760925293\t115.386878791104\t361.822851128408\t349.607330357367\t373.480686196319\t4\t3\t0\t\t\t4461\t\t[M+H]+ 114.377\t4461\tFound [M+H]+/[M-H]-\t6.1389696929279\t-2.3140345769744\t0.0614626991247251\t6.1389696929279\t-2.3140345769744\t0.0614626991247251\n-M117T1003\t116.986084037063\t116.985864459183\t116.986171601532\t1003.08654761905\t1002.26449783404\t1003.37086206897\t6\t4\t2\t\t\t56\t\t[M+H]+ 115.979\t56\tFound [M+H]+/[M-H]-\t1.16186314694844\t-0.431871845029389\t0.68206694932652\t1.16186314694844\t-0.431871845029389\t0.68206694932652\n-M117T334\t117.055379354362\t117.055256466333\t117.055456904176\t333.599102436066\t323.266073818252\t345.570157046166\t6\t0\t4\t\t\t329\t\t[M+H]+ 116.048\t329\tFound [M+H]+/[M-H]-\t1.04067368497756\t0.112630170269711\t0.91507328485967\t1.04067368497756\t0.112630170269711\t0.91507328485967\n-M117T63\t117.019027709961\t117.018931618196\t117.020763384489\t62.5229250816841\t47.7978384913575\t66.9158144421358\t11\t5\t2\t\t\t210\t\t[M+H]+ 116.012\t210\tFound ['..b'9663797\t419.488400614393\t407.274452193971\t426.34541610187\t6\t2\t0\t\t\t1728\t\t[M+H]+ 85.0164\t1728\tFound [M+H]+/[M-H]-\t3.9910944370495\t-1.99764848698304\t0.087945013683814\t3.9910944370495\t-1.99764848698304\t0.087945013683814\n-M87T337\t87.0199502464982\t87.019907261533\t87.0267369890098\t336.857160220154\t328.932758486912\t344.28868709373\t7\t3\t1\t\t\t4643\t\t[M+H]+ 86.0127\t4643\tFound [M+H]+/[M-H]-\t1.0231555537257\t0.0216918661556346\t0.983578214014113\t1.0231555537257\t0.0216918661556346\t0.983578214014113\n-M88T3\t88.003937285107\t88.003870306136\t88.0039746411383\t2.71092167699327\t1.92957542883381\t3.49564865755637\t3\t2\t1\t\t\t6803\t\t[M+H]+ 86.9967\t6803\tFound [M+H]+/[M-H]-\t2.33576893925853\t-1.25666602118248\t0.24997178856222\t2.33576893925853\t-1.25666602118248\t0.24997178856222\n-M88T458\t88.0185585021973\t88.0152587890625\t88.021858215332\t457.959290701411\t452.676572903508\t463.242008499313\t2\t0\t2\t\t\t5602\t\t[M+H]+ 87.0113\t5602\tFound [M+H]+/[M-H]-\tInf\t1.44852163980223\t0.243310495086352\tInf\t1.44852163980223\t0.243310495086352\n-M89T64\t89.0243134715871\t89.024305313763\t89.0243231692396\t63.8922475455658\t63.3707071240408\t63.9963946755224\t5\t4\t1\t\t[M+H]+ 88.0182\t7\t\t[M+H]+ 88.0182\t7\tFound [M+H]+/[M-H]-\t16.1528119551747\t-1.03515204589124\t0.359042148560027\t16.1528119551747\t-1.03515204589124\t0.359042148560027\n-M91T1\t91.0033922955555\t91.0033753323285\t91.0067366323557\t1.41157542883381\t1.35357583604733\t2.35198434456501\t3\t2\t1\t\t\t1749\t\t[M+H]+ 89.9961\t1749\tFound [M+H]+/[M-H]-\t3.15067858492482\t-2.98969115607355\t0.0469844699556694\t3.15067858492482\t-2.98969115607355\t0.0469844699556694\n-M91T339\t91.0392595211286\t91.0369474170237\t91.0413033140847\t339.179079677904\t333.806024335278\t343.775887067181\t4\t2\t1\t\t\t4054\t\t[M+H]+ 90.032\t4054\tFound [M+H]+/[M-H]-\t1.27508799527139\t-0.767595915184883\t0.47263895614649\t1.27508799527139\t-0.767595915184883\t0.47263895614649\n-M91T39\t91.0058136949774\t91.0057984660018\t91.005828923953\t39.3535347020167\t37.2530586504323\t41.4540107536011\t2\t2\t0\t\t\t158\t\t[M+H]+ 89.9985\t158\tFound [M+H]+/[M-H]-\t1.92573609266283\t-2.67072815023994\t0.0381096040398106\t1.92573609266283\t-2.67072815023994\t0.0381096040398106\n-M91T423\t90.9909457133066\t90.9907158124115\t90.9913751844474\t422.858327731071\t422.212797352317\t423.368109719466\t4\t2\t2\t\t\t5339\t\t[M+H]+ 89.9837\t5339\tFound [M+H]+/[M-H]-\t1.15287316165338\t0.370332731499949\t0.735566188411213\t1.15287316165338\t0.370332731499949\t0.735566188411213\n-M91T489\t91.0061254704578\t91.0056699208023\t91.006897304032\t489.18888042301\t475.866300646512\t500.998044796665\t11\t4\t3\t\t\t5127\t\t[M+H]+ 89.9988\t5127\tFound [M+H]+/[M-H]-\t1.42711085805442\t-1.39306056669814\t0.234314698378762\t1.42711085805442\t-1.39306056669814\t0.234314698378762\n-M93T1139\t93.007435459113\t93.0074176861003\t93.0075309882347\t1138.62792777493\t1138.27211147432\t1140.13540632002\t4\t3\t1\t\t[M+Na]+ 70.0196\t1572\t\t[M+H]+ 92.0002\t1572\tFound [M+H]+/[M-H]-\t1.59009319750693\t-0.681982679785331\t0.523170237759166\t1.59009319750693\t-0.681982679785331\t0.523170237759166\n-M94T350\t94.3168182373047\t94.3153457641602\t94.3189315795898\t349.607330357367\t347.735718771342\t358.059383781547\t3\t2\t1\t\t\t1473\t\t[M+H]+ 93.3095\t1473\tFound [M+H]+/[M-H]-\t2.80229014861983\t-0.90073218215456\t0.401405710076714\t2.80229014861983\t-0.90073218215456\t0.401405710076714\n-M95T318\t95.049995288381\t95.0499807014968\t95.0500098752651\t317.554122209402\t317.280399895152\t317.827844523652\t2\t2\t0\t\t\t2905\t\t[M+H]+ 94.0427\t2905\tFound [M+H]+/[M-H]-\tInf\t-1.94473686063201\t0.12370242993634\tInf\t-1.94473686063201\t0.12370242993634\n-M95T51\t94.9248156739247\t94.9247322803157\t94.9248737933546\t51.2847918882257\t50.3907155634095\t51.7152796793536\t8\t5\t3\t\t[M+Na]+ 71.9347 [M+2Na]2+ 143.871\t63\t\t[M+H]+ 93.9175\t63\tFound [M+H]+/[M-H]-\t37.4722940942457\t-4.91560913738868\t0.00781676528602571\t37.4722940942457\t-4.91560913738868\t0.00781676528602571\n-M99T61\t98.9555595192691\t98.9554203289135\t98.9590278194966\t60.5444205123284\t48.0328368453438\t77.1960803122144\t15\t5\t1\t\t\t2597\t\t[M+H]+ 97.9483\t2597\tFound [M+H]+/[M-H]-\t203.432997864313\t-5.93938762972869\t0.00402557203229015\t203.432997864313\t-5.93938762972869\t0.00402557203229015\n' |
b |
diff -r 4ca5c7bbc6cf -r 87570e9b71f5 tool_dependencies.xml --- a/tool_dependencies.xml Mon Feb 22 16:49:04 2016 -0500 +++ b/tool_dependencies.xml Mon Apr 25 11:07:23 2016 -0400 |
b |
@@ -1,12 +1,12 @@ <?xml version="1.0"?> <tool_dependency> <package name="R" version="3.1.2"> - <repository changeset_revision="c987143177d4" name="package_r_3_1_2" owner="iuc" toolshed="https://toolshed.g2.bx.psu.edu" /> + <repository changeset_revision="4d2fd1413b56" name="package_r_3_1_2" owner="iuc" toolshed="https://toolshed.g2.bx.psu.edu" /> </package> - <package name="camera" version="1.22.0"> - <repository changeset_revision="845eb883bd1b" name="package_r_camera_1_22_0" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" /> + <package name="bioconductor-camera" version="1.26.0"> + <repository changeset_revision="fd308c76626b" name="package_bioconductor_camera_1_26_0" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" /> </package> - <package name="camera_w4m_script" version="2.2.1"> - <repository changeset_revision="91b0d23c9d52" name="package_camera_w4m_script_2_2_1" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" /> + <package name="graphicsmagick" version="1.3.20"> + <repository changeset_revision="f2855f4cbc8f" name="package_graphicsmagick_1_3_20" owner="iuc" toolshed="https://toolshed.g2.bx.psu.edu" /> </package> </tool_dependency> |