# HG changeset patch # User workflow4metabolomics # Date 1567764728 14400 # Node ID 96debae917e469b9f4817e8cb4232ff986ebbcb6 # Parent 708ab9928a70c0ac44368f2f84633b6377413ce8 planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit c7a518686137f6d62b7415715152e8d5a9953ed7 diff -r 708ab9928a70 -r 96debae917e4 lib_metams.r --- a/lib_metams.r Tue Jul 16 09:57:10 2019 -0400 +++ b/lib_metams.r Fri Sep 06 06:12:08 2019 -0400 @@ -162,27 +162,12 @@ ##ADDITIONS FROM Y. Guitton getBPC <- function(file,rtcor=NULL, ...) { object <- xcmsRaw(file) - sel <- profRange(object, ...) - cbind(if (is.null(rtcor)) object@scantime[sel$scanidx] else rtcor ,xcms:::colMax(object@env$profile[sel$massidx,sel$scanidx,drop=FALSE])) + sel <- profRange(object, ...) + cbind(if (is.null(rtcor)) object@scantime[sel$scanidx] else rtcor ,xcms:::colMax(object@env$profile[sel$massidx,sel$scanidx,drop=FALSE])) } getBPC2s <- function (files, xset = NULL, pdfname="BPCs.pdf", rt = c("raw","corrected"), scanrange=NULL) { require(xcms) - - #Verification for cdf files - stop=FALSE - for(i in 1:length(files)){ - extension <- unlist(strsplit(basename(files[i]),"\\."))[length(unlist(strsplit(basename(files[i]),"\\.")))] - if(extension == "CDF" || extension == "cdf"){ - stop = TRUE - break - } - } - if(stop){ - error_message <- "You have a CDF file and there is an issue to resolve on them for chromatograms.... !" - print(error_message) - stop(error_message) - } #create sampleMetadata, get sampleMetadata and class if(!is.null(xset)) { @@ -199,10 +184,10 @@ } N <- dim(sampleMetadata)[1] - TIC <- vector("list",N) + BPC <- vector("list",N) for (j in 1:N) { - TIC[[j]] <- getBPC(files[j]) + BPC[[j]] <- getBPC(files[j]) #good for raw # seems strange for corrected #errors if scanrange used in xcmsSetgeneration @@ -211,7 +196,7 @@ }else{ rtcor <- NULL } - TIC[[j]] <- getBPC(files[j],rtcor=rtcor) + BPC[[j]] <- getBPC(files[j],rtcor=rtcor) } pdf(pdfname,w=16,h=10) @@ -219,8 +204,10 @@ lty = 1:N pch = 1:N #search for max x and max y in BPCs - xlim = range(sapply(TIC, function(x) range(x[,1]))) - ylim = range(sapply(TIC, function(x) range(x[,2]))) + + xlim = range(sapply(BPC, function(x) range(x[,1]))) + ylim = range(sapply(BPC, function(x) range(x[,2]))) + ylim = c(-ylim[2], ylim[2]) ##plot start @@ -231,15 +218,15 @@ plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Base Peak Chromatograms \n","BPCs_",class[k]," vs ",class[l], sep=""), xlab = "Retention Time (min)", ylab = "BPC") colvect<-NULL for (j in 1:length(classnames[[k]])) { - tic <- TIC[[classnames[[k]][j]]] - # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") - points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") + bpc <- BPC[[classnames[[k]][j]]] + # points(bpc[,1]/60, bpc[,2], col = cols[i], pch = pch[i], type="l") + points(bpc[,1]/60, bpc[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") colvect<-append(colvect,cols[classnames[[k]][j]]) } for (j in 1:length(classnames[[l]])) { # i=class2names[j] - tic <- TIC[[classnames[[l]][j]]] - points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") + bpc <- BPC[[classnames[[l]][j]]] + points(bpc[,1]/60, -bpc[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") colvect<-append(colvect,cols[classnames[[l]][j]]) } legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]],classnames[[l]])]))), col = colvect, lty = lty, pch = pch) @@ -254,15 +241,15 @@ plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Base Peak Chromatograms \n","BPCs_",class[k],"vs",class[l], sep=""), xlab = "Retention Time (min)", ylab = "BPC") for (j in 1:length(classnames[[k]])) { - tic <- TIC[[classnames[[k]][j]]] - # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") - points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") + bpc <- BPC[[classnames[[k]][j]]] + # points(bpc[,1]/60, bpc[,2], col = cols[i], pch = pch[i], type="l") + points(bpc[,1]/60, bpc[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") colvect<-append(colvect,cols[classnames[[k]][j]]) } for (j in 1:length(classnames[[l]])) { # i=class2names[j] - tic <- TIC[[classnames[[l]][j]]] - points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") + bpc <- BPC[[classnames[[l]][j]]] + points(bpc[,1]/60, -bpc[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") colvect<-append(colvect,cols[classnames[[l]][j]]) } legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]],classnames[[l]])]))), col = colvect, lty = lty, pch = pch) @@ -270,14 +257,16 @@ if (length(class)==1){ k=1 - ylim = range(sapply(TIC, function(x) range(x[,2]))) + + ylim = range(sapply(BPC, function(x) range(x[,2]))) + colvect<-NULL plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Base Peak Chromatograms \n","BPCs_",class[k], sep=""), xlab = "Retention Time (min)", ylab = "BPC") for (j in 1:length(classnames[[k]])) { - tic <- TIC[[classnames[[k]][j]]] - # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") - points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") + bpc <- BPC[[classnames[[k]][j]]] + # points(bpc[,1]/60, bpc[,2], col = cols[i], pch = pch[i], type="l") + points(bpc[,1]/60, bpc[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") colvect<-append(colvect,cols[classnames[[k]][j]]) } legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]])]))), col = colvect, lty = lty, pch = pch) @@ -294,21 +283,6 @@ getTIC2s <- function(files, xset=NULL, pdfname="TICs.pdf", rt=c("raw","corrected")) { require(xcms) - #Verification for cdf files - stop=FALSE - for(i in 1:length(files)){ - extension <- unlist(strsplit(basename(files[i]),"\\."))[length(unlist(strsplit(basename(files[i]),"\\.")))] - if(extension == "CDF" || extension == "cdf"){ - stop = TRUE - break - } - } - if(stop){ - error_message <- "You have a CDF file and there is an issue to resolve on them for chromatograms.... !" - print(error_message) - stop(error_message) - } - #create sampleMetadata, get sampleMetadata and class if(!is.null(xset)){ #When files come from XCMS3 before metaMS treatment @@ -327,7 +301,6 @@ TIC <- vector("list",N) for (i in 1:N) { - cat(files[i],"\n") if (!is.null(xcmsSet) && rt == "corrected") rtcor <- xcmsSet@rt$corrected[[i]] else @@ -348,7 +321,7 @@ if (length(class)>2){ for (k in 1:(length(class)-1)){ for (l in (k+1):length(class)){ - print(paste(class[k],"vs",class[l],sep=" ")) + cat(paste(class[k],"vs",class[l],"\n",sep=" ")) plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Total Ion Chromatograms \n","TICs_",class[k]," vs ",class[l], sep=""), xlab = "Retention Time (min)", ylab = "TIC") colvect<-NULL for (j in 1:length(classnames[[k]])) { @@ -412,21 +385,6 @@ #only for Galaxy plotUnknowns<-function(resGC, unkn="", DB=NULL, fileFrom=NULL){ - #Verification for cdf files - stop=FALSE - for(i in 1:length(names(resGC$annotation))){ - extension <- unlist(strsplit(basename(names(resGC$annotation)[i]),"\\."))[length(unlist(strsplit(basename(names(resGC$annotation)[i]),"\\.")))] - if(extension == "CDF" || extension == "cdf"){ - stop = TRUE - break - } - } - if(stop){ - error_message <- "You have a CDF file and there is an issue to resolve on them for chromatograms.... !" - print(error_message) - stop(error_message) - } - ##Annotation table each value is a pcgrp associated to the unknown ##NOTE pcgrp index are different between xcmsSet and resGC due to filtering steps in metaMS ##R. Wehrens give me some clues on that and we found a correction @@ -545,4 +503,4 @@ } graphics.off() }#end for unkn[l] -}#end function \ No newline at end of file +}#end function diff -r 708ab9928a70 -r 96debae917e4 metaMS_plot.r --- a/metaMS_plot.r Tue Jul 16 09:57:10 2019 -0400 +++ b/metaMS_plot.r Fri Sep 06 06:12:08 2019 -0400 @@ -96,6 +96,12 @@ if(!is.null(singlefile)) { files <- paste("./",names(singlefile),sep="") + #WARNING if user has CDF files (not yet good for plotting) + if(MSnbase:::isCdfFile(files)){ + warning_message <- "You have CDF files, for the moment you can't obtain plot after runGC! A new update will follow with the good correction\n" + warning(warning_message) + cat(paste("\n","/!\\Warning/!\\",warning_message,sep="\n")) + } if(!is.null(files)){ if(args$selectbpc){ cat("\n\tProcessing BPC(s) from XCMS files...\n")