# HG changeset patch # User workflow4metabolomics # Date 1564171218 14400 # Node ID db9bc2c27a0ac0e5f64780cd8f5b394645db0469 # Parent 2184c0435edf3ecb8e46594ac335a3dc712eca9f planemo upload commit d51a0d0a26833671b79711ee18d782e84f301e76 diff -r 2184c0435edf -r db9bc2c27a0a CAMERA.r --- a/CAMERA.r Fri Apr 12 10:45:52 2019 -0400 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,157 +0,0 @@ -#!/usr/bin/env Rscript -# CAMERA.r version="2.2.1" - - - -# ----- PACKAGE ----- -cat("\tSESSION INFO\n") - -pkgs=c("CAMERA","multtest","batch") -for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) - -sessioninfo = sessionInfo() -cat(sessioninfo$R.version$version.string,"\n") -cat("Main packages:\n") -for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") -cat("Other loaded packages:\n") -for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") - -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 -} - -variableMetadataOutput = "variableMetadata.tsv" -if (!is.null(listArguments[["variableMetadataOutput"]])){ - variableMetadataOutput = listArguments[["variableMetadataOutput"]]; listArguments[["variableMetadataOutput"]]=NULL -} - -#Import the different functions -source_local("lib.r") - -# We unzip automatically the chromatograms from the zip files. -if (thefunction %in% c("annotatediff")) { - 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) -} - -# Because so far CAMERA isn't compatible with the new XCMSnExp object -if (exists("xdata")){ - xset <- getxcmsSetObject(xdata) -} - -# addition of xset object to the list of arguments in the first position -if (exists("xset")){ - 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) - 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, - 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","singlefile") -save(list=objects2save[objects2save %in% ls()], file=xsetRdataOutput) - -cat("\n\n") - -cat("\tDONE\n") diff -r 2184c0435edf -r db9bc2c27a0a CAMERA_annotateDiffreport.r --- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/CAMERA_annotateDiffreport.r Fri Jul 26 16:00:18 2019 -0400 @@ -0,0 +1,78 @@ +#!/usr/bin/env Rscript + +# ----- PACKAGE ----- +cat("\tSESSION INFO\n") + +#Import the different functions +source_local <- function(fname){ argv <- commandArgs(trailingOnly=FALSE); base_dir <- dirname(substring(argv[grep("--file=", argv)], 8)); source(paste(base_dir, fname, sep="/")) } +source_local("lib.r") + +pkgs=c("CAMERA","multtest","batch") +loadAndDisplayPackages(pkgs) +cat("\n\n"); + +# ----- ARGUMENTS ----- +cat("\tARGUMENTS INFO\n") + +args = parseCommandArgs(evaluate=FALSE) #interpretation of arguments given in command line as an R list of objects +write.table(as.matrix(args), 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 +load(args$image); args$image=NULL + +cat("\n\n") + + +# ----- ARGUMENTS PROCESSING ----- +cat("\tARGUMENTS PROCESSING INFO\n") + +# Save arguments to generate a report +if (!exists("listOFargs")) listOFargs=list() +listOFargs[[format(Sys.time(), "%y%m%d-%H:%M:%S_annotatediff")]] = args + +# We unzip automatically the chromatograms from the zip files. +if (!exists("zipfile")) zipfile=NULL +if (!exists("singlefile")) singlefile=NULL +rawFilePath = getRawfilePathFromArguments(singlefile, zipfile, args) +zipfile = rawFilePath$zipfile +singlefile = rawFilePath$singlefile +args = rawFilePath$args +directory = retrieveRawfileInTheWorkingDirectory(singlefile, zipfile) + +# Because so far CAMERA isn't compatible with the new XCMSnExp object +if (exists("xdata")){ + xset <- getxcmsSetObject(xdata) +} + +cat("\n\n") + + +# ----- PROCESSING INFO ----- +cat("\tMAIN PROCESSING INFO\n") + +results_list=annotatediff(xset=xset,args=args,variableMetadataOutput="variableMetadata.tsv") +xa=results_list$xa +diffrep=results_list$diffrep +variableMetadata=results_list$variableMetadata + +cat("\n\n") + +# ----- EXPORT ----- + +cat("\tXSET OBJECT INFO\n") +print(xa) +cat("\n\n") + +#saving R data in .Rdata file to save the variables used in the present tool +objects2save = c("xa","variableMetadata","diffrep","cAnnot","listOFargs","zipfile","singlefile") +save(list=objects2save[objects2save %in% ls()], file="annotatediff.RData") + +cat("\n\n") + +cat("\tDONE\n") diff -r 2184c0435edf -r db9bc2c27a0a README.rst --- a/README.rst Fri Apr 12 10:45:52 2019 -0400 +++ b/README.rst Fri Jul 26 16:00:18 2019 -0400 @@ -5,8 +5,11 @@ **Version 2.2.5 - 09/04/2019** - NEW: zip export are back for pictures (eic and boxplot) and diffreport tables + - UPGRADE: upgrade the CAMERA version from 1.34.0 to 1.38.1 (see CAMERA News_) +- UPGRADE: refactoring of internal code + **Version 2.2.4 - 09/10/2018** - NES: CAMERA.annotate no longer export a DataMatrix. fillChromPeaks does the job diff -r 2184c0435edf -r db9bc2c27a0a abims_CAMERA_annotateDiffreport.xml --- a/abims_CAMERA_annotateDiffreport.xml Fri Apr 12 10:45:52 2019 -0400 +++ b/abims_CAMERA_annotateDiffreport.xml Fri Jul 26 16:00:18 2019 -0400 @@ -10,15 +10,11 @@ - - + + quick_block['quick'] == 'FALSE' - + quick_block['quick'] == 'TRUE' @@ -447,8 +439,11 @@ **Version 2.2.5 - 09/04/2019** - NEW: zip export are back for pictures (eic and boxplot) and diffreport tables + - UPGRADE: upgrade the CAMERA version from 1.34.0 to 1.38.1 (see CAMERA News_) +- UPGRADE: refactoring of internal code + **Version 2.2.4 - 09/10/2018** - NEW: CAMERA.annotate no longer export a DataMatrix. fillChromPeaks does the job diff -r 2184c0435edf -r db9bc2c27a0a lib.r --- a/lib.r Fri Apr 12 10:45:52 2019 -0400 +++ b/lib.r Fri Jul 26 16:00:18 2019 -0400 @@ -1,5 +1,31 @@ # lib.r +#@author G. Le Corguille +# solve an issue with batch if arguments are logical TRUE/FALSE +parseCommandArgs <- function(...) { + args <- batch::parseCommandArgs(...) + for (key in names(args)) { + if (args[key] %in% c("TRUE","FALSE")) + args[key] = as.logical(args[key]) + } + return(args) +} + +#@author G. Le Corguille +# This function will +# - load the packages +# - display the sessionInfo +loadAndDisplayPackages <- function(pkgs) { + for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) + + sessioninfo = sessionInfo() + cat(sessioninfo$R.version$version.string,"\n") + cat("Main packages:\n") + for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") + cat("Other loaded packages:\n") + for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") +} + # This function retrieve a xset like object #@author Gildas Le Corguille lecorguille@sb-roscoff.fr getxcmsSetObject <- function(xobject) { @@ -69,7 +95,7 @@ } #The function annotateDiffreport without the corr function which bugs -annotatediff <- function(xset=xset, listArguments=listArguments, variableMetadataOutput="variableMetadata.tsv") { +annotatediff <- function(xset=xset, args=args, variableMetadataOutput="variableMetadata.tsv") { # Resolve the bug with x11, with the function png options(bitmapType='cairo') @@ -77,52 +103,52 @@ 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"]]) + args$calcCiS=as.logical(args$calcCiS) + args$calcIso=as.logical(args$calcIso) + args$calcCaS=as.logical(args$calcCaS) # 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"]]) + args4annotate = list(object=xset, + nSlaves=args$nSlaves,sigma=args$sigma,perfwhm=args$perfwhm, + maxcharge=args$maxcharge,maxiso=args$maxiso,minfrac=args$minfrac, + ppm=args$ppm,mzabs=args$mzabs,quick=args$quick, + polarity=args$polarity,max_peaks=args$max_peaks,intval=args$intval) # 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"]])) + if(args$quick==FALSE) { + args4annotate = append(args4annotate, + list(graphMethod=args$graphMethod,cor_eic_th=args$cor_eic_th,pval=args$pval, + calcCiS=args$calcCiS,calcIso=args$calcIso,calcCaS=args$calcCaS)) # no ruleset - if (!is.null(listArguments[["multiplier"]])) { - listArguments4annotate = append(listArguments4annotate, - list(multiplier=listArguments[["multiplier"]])) + if (!is.null(args$multiplier)) { + args4annotate = append(args4annotate, + list(multiplier=args$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=",") + rulset=read.table(args$rules, h=T, sep=";") + if (ncol(rulset) < 4) rulset=read.table(args$rules, h=T, sep="\t") + if (ncol(rulset) < 4) rulset=read.table(args$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) } - listArguments4annotate = append(listArguments4annotate, + args4annotate = append(args4annotate, list(rules=rulset)) } } # launch annotate - xa = do.call("annotate", listArguments4annotate) - peakList=getPeaklist(xa,intval=listArguments[["intval"]]) + xa = do.call("annotate", args4annotate) + peakList=getPeaklist(xa,intval=args$intval) peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); # --- Multi condition : diffreport --- diffrepOri=NULL - if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))>=2) { + if (!is.null(args$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)) @@ -133,7 +159,10 @@ 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"]],missing=0) + diffrep=diffreport( + object=xset,class1=classes[i],class2=classes[i+n], + filebase=filebase,eicmax=args$eicmax,eicwidth=args$eicwidth, + sortpval=TRUE,value=args$value,h=args$h,w=args$w,mzdec=args$mzdec,missing=0) diffrepOri = diffrep @@ -145,37 +174,37 @@ 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"]]) + diffrep = RTSecondToMinute(diffrep, args$convertRTMinute) + diffrep = formatIonIdentifiers(diffrep, numDigitsRT=args$numDigitsRT, numDigitsMZ=args$numDigitsMZ) - if(listArguments[["sortpval"]]){ + if(args$sortpval){ diffrep=diffrep[order(diffrep$pvalue), ] } dir.create("tabular", showWarnings = FALSE) write.table(diffrep, sep="\t", quote=FALSE, row.names=FALSE, file=paste("tabular/",filebase,"_tsv.tabular",sep="")) - if (listArguments[["eicmax"]] != 0) { - if (listArguments[["png2"]] == "pdf") + if (args$eicmax != 0) { + if (args$png2 == "pdf") diffreport_png2pdf(filebase) } } } } - if (listArguments[["png2"]] == "zip") + if (args$png2 == "zip") diffreport_png2zip() - if (listArguments[["tabular2"]] == "zip") + if (args$tabular2 == "zip") diffreport_tabular2zip() } # --- 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"]]) + variableMetadata = RTSecondToMinute(variableMetadata, args$convertRTMinute) + variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=args$numDigitsRT, numDigitsMZ=args$numDigitsMZ) # if we have 2 conditions, we keep stat of diffrep - if (!is.null(listArguments[["runDiffreport"]]) & nlevels(sampclass(xset))==2) { + if (!is.null(args$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\"]]")){ + if(exists("args[[\"sortpval\"]]")){ variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] } } @@ -188,7 +217,9 @@ } -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"){ +combinexsAnnos_function <- function(xaP, xaN, 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") @@ -215,11 +246,9 @@ if(pos){ xa=xaP - listOFlistArgumentsP=listOFlistArguments mode="neg. Mode" } else { xa=xaN - listOFlistArgumentsN=listOFlistArguments mode="pos. Mode" } @@ -256,22 +285,22 @@ } # 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"]] +getRawfilePathFromArguments <- function(singlefile, zipfile, args) { + if (!is.null(args$zipfile)) zipfile = args$zipfile + if (!is.null(args$zipfilePositive)) zipfile = args$zipfilePositive + if (!is.null(args$zipfileNegative)) zipfile = args$zipfileNegative - if (!is.null(listArguments[["singlefile_galaxyPath"]])) { - singlefile_galaxyPaths = listArguments[["singlefile_galaxyPath"]]; - singlefile_sampleNames = listArguments[["singlefile_sampleName"]] + if (!is.null(args$singlefile_galaxyPath)) { + singlefile_galaxyPaths = args$singlefile_galaxyPath; + singlefile_sampleNames = args$singlefile_sampleName } - if (!is.null(listArguments[["singlefile_galaxyPathPositive"]])) { - singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathPositive"]]; - singlefile_sampleNames = listArguments[["singlefile_sampleNamePositive"]] + if (!is.null(args$singlefile_galaxyPathPositive)) { + singlefile_galaxyPaths = args$singlefile_galaxyPathPositive; + singlefile_sampleNames = args$singlefile_sampleNamePositive } - if (!is.null(listArguments[["singlefile_galaxyPathNegative"]])) { - singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathNegative"]]; - singlefile_sampleNames = listArguments[["singlefile_sampleNameNegative"]] + if (!is.null(args$singlefile_galaxyPathNegative)) { + singlefile_galaxyPaths = args$singlefile_galaxyPathNegative; + singlefile_sampleNames = args$singlefile_sampleNameNegative } if (exists("singlefile_galaxyPaths")){ singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,",")) @@ -284,10 +313,13 @@ 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 + for (argument in c("zipfile", "zipfilePositive", "zipfileNegative", + "singlefile_galaxyPath", "singlefile_sampleName", + "singlefile_galaxyPathPositive", "singlefile_sampleNamePositive", + "singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { + args[[argument]]=NULL } - return(list(zipfile=zipfile, singlefile=singlefile, listArguments=listArguments)) + return(list(zipfile=zipfile, singlefile=singlefile, args=args)) } diff -r 2184c0435edf -r db9bc2c27a0a macros.xml --- a/macros.xml Fri Apr 12 10:45:52 2019 -0400 +++ b/macros.xml Fri Jul 26 16:00:18 2019 -0400 @@ -15,9 +15,7 @@ - - LC_ALL=C Rscript $__tool_directory__/CAMERA.r - + LC_ALL=C Rscript $__tool_directory__/ diff -r 2184c0435edf -r db9bc2c27a0a repository_dependencies.xml --- a/repository_dependencies.xml Fri Apr 12 10:45:52 2019 -0400 +++ b/repository_dependencies.xml Fri Jul 26 16:00:18 2019 -0400 @@ -1,5 +1,5 @@ - + \ No newline at end of file