Mercurial > repos > workflow4metabolomics > metams_plot
comparison lib_metams.r @ 0:b60dc620bd14 draft
planemo upload for repository https://github.com/workflow4metabolomics/metaMS commit 174a1713024f246c1485cbd75218577e89353522
| author | workflow4metabolomics |
|---|---|
| date | Wed, 03 Jul 2019 05:08:14 -0400 |
| parents | |
| children | 708ab9928a70 |
comparison
equal
deleted
inserted
replaced
| -1:000000000000 | 0:b60dc620bd14 |
|---|---|
| 1 # lib_metams.r version 2.1.1 | |
| 2 # R function for metaMS runGC under W4M | |
| 3 # author Yann GUITTON CNRS IRISA/LINA Idealg project 2014-2015 | |
| 4 # author Yann GUITTON Oniris Laberca 2015-2017 | |
| 5 | |
| 6 | |
| 7 #@author G. Le Corguille | |
| 8 # This function will | |
| 9 # - load the packages | |
| 10 # - display the sessionInfo | |
| 11 loadAndDisplayPackages <- function(pkgs) { | |
| 12 for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) | |
| 13 | |
| 14 sessioninfo = sessionInfo() | |
| 15 cat(sessioninfo$R.version$version.string,"\n") | |
| 16 cat("Main packages:\n") | |
| 17 for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") | |
| 18 cat("Other loaded packages:\n") | |
| 19 for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") | |
| 20 } | |
| 21 | |
| 22 #This function list the compatible files within the directory as xcms did | |
| 23 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM | |
| 24 getMSFiles <- function (directory) { | |
| 25 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") | |
| 26 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|") | |
| 27 info <- file.info(directory) | |
| 28 listed <- list.files(directory[info$isdir], pattern=filepattern,recursive=TRUE, full.names=TRUE) | |
| 29 files <- c(directory[!info$isdir], listed) | |
| 30 exists <- file.exists(files) | |
| 31 files <- files[exists] | |
| 32 return(files) | |
| 33 } | |
| 34 | |
| 35 # This function retrieve a xset like object | |
| 36 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr | |
| 37 getxcmsSetObject <- function(xobject) { | |
| 38 # XCMS 1.x | |
| 39 if (class(xobject) == "xcmsSet") | |
| 40 return (xobject) | |
| 41 # XCMS 3.x | |
| 42 if (class(xobject) == "XCMSnExp") { | |
| 43 # Get the legacy xcmsSet object | |
| 44 suppressWarnings(xset <- as(xobject, 'xcmsSet')) | |
| 45 if (!is.null(xset@phenoData$sample_group)) | |
| 46 sampclass(xset) <- xset@phenoData$sample_group | |
| 47 else | |
| 48 sampclass(xset) <- "." | |
| 49 return (xset) | |
| 50 } | |
| 51 } | |
| 52 | |
| 53 #J.Saint-Vanne | |
| 54 #Function to correct the file names which can be written like "..alg8.mzData" and we just want "alg8" | |
| 55 getCorrectFileName <- function(peaktable,sampleMetadata){ | |
| 56 | |
| 57 #Try to start for the first sample, avoid description of line with colnamesdontwant | |
| 58 i <- 1 | |
| 59 while(!(sampleMetadata[1,1] %in% strsplit(colnames(peaktable)[i],"\\.")[[1]])) { | |
| 60 if(i < length(peaktable)) { | |
| 61 i <- i + 1 | |
| 62 } else { | |
| 63 break | |
| 64 } | |
| 65 } | |
| 66 #i now correspond to the first column with a sample | |
| 67 for(j in 1:(nrow(sampleMetadata))) { | |
| 68 col <- j + i-1 #minus 1 cause i is the good column to start and j start at 1 | |
| 69 if(col <= length(colnames(peaktable))) { | |
| 70 newname <- gsub("(^.*)(\\..*$)","\\1",colnames(peaktable)[col]) | |
| 71 if(newname != sampleMetadata[j,1]){ | |
| 72 #Correction for 2 points starting the name (I don't know why they are here...) | |
| 73 if(".." == gsub("(^\\.+)(.*)","\\1",newname)){ | |
| 74 newname <- sub("(^\\.+)(.*)","\\2",newname) | |
| 75 } | |
| 76 } | |
| 77 colnames(peaktable)[col] <- newname | |
| 78 } | |
| 79 } | |
| 80 return(peaktable) | |
| 81 } | |
| 82 | |
| 83 | |
| 84 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr | |
| 85 # This function get the raw file path from the arguments | |
| 86 getRawfilePathFromArguments <- function(singlefile, zipfile, listArguments) { | |
| 87 if (!is.null(listArguments[["zipfile"]])) zipfile = listArguments[["zipfile"]] | |
| 88 if (!is.null(listArguments[["zipfilePositive"]])) zipfile = listArguments[["zipfilePositive"]] | |
| 89 if (!is.null(listArguments[["zipfileNegative"]])) zipfile = listArguments[["zipfileNegative"]] | |
| 90 | |
| 91 if (!is.null(listArguments[["singlefile_galaxyPath"]])) { | |
| 92 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPath"]]; | |
| 93 singlefile_sampleNames = listArguments[["singlefile_sampleName"]] | |
| 94 } | |
| 95 if (!is.null(listArguments[["singlefile_galaxyPathPositive"]])) { | |
| 96 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathPositive"]]; | |
| 97 singlefile_sampleNames = listArguments[["singlefile_sampleNamePositive"]] | |
| 98 } | |
| 99 if (!is.null(listArguments[["singlefile_galaxyPathNegative"]])) { | |
| 100 singlefile_galaxyPaths = listArguments[["singlefile_galaxyPathNegative"]]; | |
| 101 singlefile_sampleNames = listArguments[["singlefile_sampleNameNegative"]] | |
| 102 } | |
| 103 if (exists("singlefile_galaxyPaths")){ | |
| 104 singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,",")) | |
| 105 singlefile_sampleNames = unlist(strsplit(singlefile_sampleNames,",")) | |
| 106 | |
| 107 singlefile=NULL | |
| 108 for (singlefile_galaxyPath_i in seq(1:length(singlefile_galaxyPaths))) { | |
| 109 singlefile_galaxyPath=singlefile_galaxyPaths[singlefile_galaxyPath_i] | |
| 110 singlefile_sampleName=singlefile_sampleNames[singlefile_galaxyPath_i] | |
| 111 singlefile[[singlefile_sampleName]] = singlefile_galaxyPath | |
| 112 } | |
| 113 } | |
| 114 for (argument in c("zipfile","zipfilePositive","zipfileNegative","singlefile_galaxyPath","singlefile_sampleName","singlefile_galaxyPathPositive","singlefile_sampleNamePositive","singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { | |
| 115 listArguments[[argument]]=NULL | |
| 116 } | |
| 117 return(list(zipfile=zipfile, singlefile=singlefile, listArguments=listArguments)) | |
| 118 } | |
| 119 | |
| 120 | |
| 121 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr | |
| 122 # This function retrieve the raw file in the working directory | |
| 123 # - if zipfile: unzip the file with its directory tree | |
| 124 # - if singlefiles: set symlink with the good filename | |
| 125 retrieveRawfileInTheWorkingDirectory <- function(singlefile, zipfile) { | |
| 126 if(!is.null(singlefile) && (length("singlefile")>0)) { | |
| 127 for (singlefile_sampleName in names(singlefile)) { | |
| 128 singlefile_galaxyPath = singlefile[[singlefile_sampleName]] | |
| 129 if(!file.exists(singlefile_galaxyPath)){ | |
| 130 error_message=paste("Cannot access the sample:",singlefile_sampleName,"located:",singlefile_galaxyPath,". Please, contact your administrator ... if you have one!") | |
| 131 print(error_message); stop(error_message) | |
| 132 } | |
| 133 file.symlink(singlefile_galaxyPath,singlefile_sampleName) | |
| 134 } | |
| 135 directory = "." | |
| 136 } | |
| 137 if(!is.null(zipfile) && (zipfile!="")) { | |
| 138 if(!file.exists(zipfile)){ | |
| 139 error_message=paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!") | |
| 140 print(error_message) | |
| 141 stop(error_message) | |
| 142 } | |
| 143 | |
| 144 #list all file in the zip file | |
| 145 #zip_files=unzip(zipfile,list=T)[,"Name"] | |
| 146 | |
| 147 #unzip | |
| 148 suppressWarnings(unzip(zipfile, unzip="unzip")) | |
| 149 | |
| 150 #get the directory name | |
| 151 filesInZip=unzip(zipfile, list=T); | |
| 152 directories=unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1]))); | |
| 153 directories=directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] | |
| 154 directory = "." | |
| 155 if (length(directories) == 1) directory = directories | |
| 156 | |
| 157 cat("files_root_directory\t",directory,"\n") | |
| 158 } | |
| 159 return (directory) | |
| 160 } | |
| 161 | |
| 162 ##ADDITIONS FROM Y. Guitton | |
| 163 getBPC <- function(file,rtcor=NULL, ...) { | |
| 164 object <- xcmsRaw(file) | |
| 165 sel <- profRange(object, ...) | |
| 166 cbind(if (is.null(rtcor)) object@scantime[sel$scanidx] else rtcor ,xcms:::colMax(object@env$profile[sel$massidx,sel$scanidx,drop=FALSE])) | |
| 167 } | |
| 168 | |
| 169 getBPC2s <- function (files, xset = NULL, pdfname="BPCs.pdf", rt = c("raw","corrected"), scanrange=NULL) { | |
| 170 require(xcms) | |
| 171 | |
| 172 #create sampleMetadata, get sampleMetadata and class | |
| 173 if(!is.null(xset)) { | |
| 174 #When files come from XCMS3 directly before metaMS | |
| 175 sampleMetadata <- xset@phenoData | |
| 176 } else { | |
| 177 #When files come from a zip directory with raw files before metaMS | |
| 178 sampleMetadata<-xcms:::phenoDataFromPaths(files) | |
| 179 } | |
| 180 class<-unique(sampleMetadata[,"class"]) #create phenoData like table | |
| 181 classnames<-vector("list",length(class)) | |
| 182 for (i in 1:length(class)){ | |
| 183 classnames[[i]]<-which( sampleMetadata[,"class"]==class[i]) | |
| 184 } | |
| 185 | |
| 186 N <- dim(sampleMetadata)[1] | |
| 187 TIC <- vector("list",N) | |
| 188 | |
| 189 for (j in 1:N) { | |
| 190 TIC[[j]] <- getBPC(files[j]) | |
| 191 #good for raw | |
| 192 # seems strange for corrected | |
| 193 #errors if scanrange used in xcmsSetgeneration | |
| 194 if (!is.null(xcmsSet) && rt == "corrected"){ | |
| 195 rtcor <- xcmsSet@rt$corrected[[j]] | |
| 196 }else{ | |
| 197 rtcor <- NULL | |
| 198 } | |
| 199 TIC[[j]] <- getBPC(files[j],rtcor=rtcor) | |
| 200 } | |
| 201 | |
| 202 pdf(pdfname,w=16,h=10) | |
| 203 cols <- rainbow(N) | |
| 204 lty = 1:N | |
| 205 pch = 1:N | |
| 206 #search for max x and max y in BPCs | |
| 207 xlim = range(sapply(TIC, function(x) range(x[,1]))) | |
| 208 ylim = range(sapply(TIC, function(x) range(x[,2]))) | |
| 209 ylim = c(-ylim[2], ylim[2]) | |
| 210 | |
| 211 ##plot start | |
| 212 if (length(class)>2){ | |
| 213 for (k in 1:(length(class)-1)){ | |
| 214 for (l in (k+1):length(class)){ | |
| 215 cat(paste(class[k],"vs",class[l],sep=" ","\n")) | |
| 216 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") | |
| 217 colvect<-NULL | |
| 218 for (j in 1:length(classnames[[k]])) { | |
| 219 tic <- TIC[[classnames[[k]][j]]] | |
| 220 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") | |
| 221 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") | |
| 222 colvect<-append(colvect,cols[classnames[[k]][j]]) | |
| 223 } | |
| 224 for (j in 1:length(classnames[[l]])) { | |
| 225 # i=class2names[j] | |
| 226 tic <- TIC[[classnames[[l]][j]]] | |
| 227 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") | |
| 228 colvect<-append(colvect,cols[classnames[[l]][j]]) | |
| 229 } | |
| 230 legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]],classnames[[l]])]))), col = colvect, lty = lty, pch = pch) | |
| 231 } | |
| 232 } | |
| 233 }#end if length >2 | |
| 234 | |
| 235 if (length(class)==2){ | |
| 236 k=1 | |
| 237 l=2 | |
| 238 colvect<-NULL | |
| 239 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") | |
| 240 | |
| 241 for (j in 1:length(classnames[[k]])) { | |
| 242 tic <- TIC[[classnames[[k]][j]]] | |
| 243 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") | |
| 244 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") | |
| 245 colvect<-append(colvect,cols[classnames[[k]][j]]) | |
| 246 } | |
| 247 for (j in 1:length(classnames[[l]])) { | |
| 248 # i=class2names[j] | |
| 249 tic <- TIC[[classnames[[l]][j]]] | |
| 250 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") | |
| 251 colvect<-append(colvect,cols[classnames[[l]][j]]) | |
| 252 } | |
| 253 legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]],classnames[[l]])]))), col = colvect, lty = lty, pch = pch) | |
| 254 }#end length ==2 | |
| 255 | |
| 256 if (length(class)==1){ | |
| 257 k=1 | |
| 258 ylim = range(sapply(TIC, function(x) range(x[,2]))) | |
| 259 colvect<-NULL | |
| 260 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") | |
| 261 | |
| 262 for (j in 1:length(classnames[[k]])) { | |
| 263 tic <- TIC[[classnames[[k]][j]]] | |
| 264 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") | |
| 265 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") | |
| 266 colvect<-append(colvect,cols[classnames[[k]][j]]) | |
| 267 } | |
| 268 legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]])]))), col = colvect, lty = lty, pch = pch) | |
| 269 }#end length ==1 | |
| 270 dev.off() | |
| 271 } | |
| 272 | |
| 273 getTIC <- function(file,rtcor=NULL) { | |
| 274 object <- xcmsRaw(file) | |
| 275 cbind(if (is.null(rtcor)) object@scantime else rtcor, rawEIC(object,mzrange=range(object@env$mz))$intensity) | |
| 276 } | |
| 277 | |
| 278 ## overlay TIC from all files in current folder or from xcmsSet, create pdf | |
| 279 getTIC2s <- function(files, xset=NULL, pdfname="TICs.pdf", rt=c("raw","corrected")) { | |
| 280 require(xcms) | |
| 281 | |
| 282 #create sampleMetadata, get sampleMetadata and class | |
| 283 if(!is.null(xset)){ | |
| 284 #When files come from XCMS3 before metaMS treatment | |
| 285 sampleMetadata<-xset@phenoData | |
| 286 } else { | |
| 287 #When files come from a zip directory with raw files before metaMS | |
| 288 sampleMetadata<-xcms:::phenoDataFromPaths(files) | |
| 289 } | |
| 290 class<-as.vector(levels(sampleMetadata[,"class"])) #create phenoData like table | |
| 291 classnames<-vector("list",length(class)) | |
| 292 for (i in 1:length(class)){ | |
| 293 classnames[[i]]<-which( sampleMetadata[,"class"]==class[i]) | |
| 294 } | |
| 295 | |
| 296 N <- dim(sampleMetadata)[1] | |
| 297 TIC <- vector("list",N) | |
| 298 | |
| 299 for (i in 1:N) { | |
| 300 cat(files[i],"\n") | |
| 301 if (!is.null(xcmsSet) && rt == "corrected") | |
| 302 rtcor <- xcmsSet@rt$corrected[[i]] | |
| 303 else | |
| 304 rtcor <- NULL | |
| 305 TIC[[i]] <- getTIC(files[i],rtcor=rtcor) | |
| 306 } | |
| 307 | |
| 308 pdf(pdfname,w=16,h=10) | |
| 309 cols <- rainbow(N) | |
| 310 lty = 1:N | |
| 311 pch = 1:N | |
| 312 #search for max x and max y in TICs | |
| 313 xlim = range(sapply(TIC, function(x) range(x[,1]))) | |
| 314 ylim = range(sapply(TIC, function(x) range(x[,2]))) | |
| 315 ylim = c(-ylim[2], ylim[2]) | |
| 316 | |
| 317 ##plot start | |
| 318 if (length(class)>2){ | |
| 319 for (k in 1:(length(class)-1)){ | |
| 320 for (l in (k+1):length(class)){ | |
| 321 print(paste(class[k],"vs",class[l],sep=" ")) | |
| 322 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") | |
| 323 colvect<-NULL | |
| 324 for (j in 1:length(classnames[[k]])) { | |
| 325 tic <- TIC[[classnames[[k]][j]]] | |
| 326 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") | |
| 327 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") | |
| 328 colvect<-append(colvect,cols[classnames[[k]][j]]) | |
| 329 } | |
| 330 for (j in 1:length(classnames[[l]])) { | |
| 331 # i=class2names[j] | |
| 332 tic <- TIC[[classnames[[l]][j]]] | |
| 333 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") | |
| 334 colvect<-append(colvect,cols[classnames[[l]][j]]) | |
| 335 } | |
| 336 legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]],classnames[[l]])]))), col = colvect, lty = lty, pch = pch) | |
| 337 } | |
| 338 } | |
| 339 }#end if length >2 | |
| 340 | |
| 341 if (length(class)==2){ | |
| 342 k=1 | |
| 343 l=2 | |
| 344 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") | |
| 345 colvect<-NULL | |
| 346 for (j in 1:length(classnames[[k]])) { | |
| 347 tic <- TIC[[classnames[[k]][j]]] | |
| 348 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") | |
| 349 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") | |
| 350 colvect<-append(colvect,cols[classnames[[k]][j]]) | |
| 351 } | |
| 352 for (j in 1:length(classnames[[l]])) { | |
| 353 # i=class2names[j] | |
| 354 tic <- TIC[[classnames[[l]][j]]] | |
| 355 points(tic[,1]/60, -tic[,2], col = cols[classnames[[l]][j]], pch = pch[classnames[[l]][j]], type="l") | |
| 356 colvect<-append(colvect,cols[classnames[[l]][j]]) | |
| 357 } | |
| 358 legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]],classnames[[l]])]))), col = colvect, lty = lty, pch = pch) | |
| 359 }#end length ==2 | |
| 360 | |
| 361 if (length(class)==1){ | |
| 362 k=1 | |
| 363 ylim = range(sapply(TIC, function(x) range(x[,2]))) | |
| 364 plot(0, 0, type="n", xlim = xlim/60, ylim = ylim, main = paste("Total Ion Chromatograms \n","TICs_",class[k], sep=""), xlab = "Retention Time (min)", ylab = "TIC") | |
| 365 colvect<-NULL | |
| 366 for (j in 1:length(classnames[[k]])) { | |
| 367 tic <- TIC[[classnames[[k]][j]]] | |
| 368 # points(tic[,1]/60, tic[,2], col = cols[i], pch = pch[i], type="l") | |
| 369 points(tic[,1]/60, tic[,2], col = cols[classnames[[k]][j]], pch = pch[classnames[[k]][j]], type="l") | |
| 370 colvect<-append(colvect,cols[classnames[[k]][j]]) | |
| 371 } | |
| 372 legend("topright",paste(gsub("(^.+)\\..*$","\\1",basename(files[c(classnames[[k]])]))), col = colvect, lty = lty, pch = pch) | |
| 373 }#end length ==1 | |
| 374 dev.off() | |
| 375 } | |
| 376 | |
| 377 | |
| 378 #Update by J.Saint-Vanne | |
| 379 ##addition for quality control of peak picking | |
| 380 #metaMS EIC and pspectra plotting option | |
| 381 #version 20190520 | |
| 382 #only for Galaxy | |
| 383 plotUnknowns<-function(resGC, unkn="", DB=NULL, fileFrom=NULL){ | |
| 384 | |
| 385 ##Annotation table each value is a pcgrp associated to the unknown | |
| 386 ##NOTE pcgrp index are different between xcmsSet and resGC due to filtering steps in metaMS | |
| 387 ##R. Wehrens give me some clues on that and we found a correction | |
| 388 | |
| 389 #correction of annotation matrix due to pcgrp removal by quality check in runGCresult | |
| 390 #matrix of correspondance between an@pspectra and filtered pspectra from runGC | |
| 391 #Select only pspectra which correpond to them select in metaMS | |
| 392 # col1 = filtered spectra from runGC and col2 = an@spectra | |
| 393 allPCGRPs <-lapply(1:length(resGC$xset), | |
| 394 function(i) { | |
| 395 an <- resGC$xset[[i]] | |
| 396 huhn <- an@pspectra[which(sapply(an@pspectra, length) >= | |
| 397 metaSetting(resGC$settings, | |
| 398 "DBconstruction.minfeat"))] | |
| 399 matCORR<-cbind(1:length(huhn), match(huhn, an@pspectra)) | |
| 400 }) | |
| 401 #Build a new annotation list with sampnames and pseudospectra number from xset | |
| 402 helpannotation <- list() | |
| 403 for(j in 1:length(resGC$xset)){ | |
| 404 helpannotation[[j]] <- resGC$annotation[[j]][1:2] | |
| 405 pspvector <- vector() | |
| 406 for(i in 1: nrow(helpannotation[[j]])){ | |
| 407 #Find corresponding pspec | |
| 408 psplink <- allPCGRPs[[j]][match(helpannotation[[j]][i,1],allPCGRPs[[j]]),2] | |
| 409 pspvector <- c(pspvector,psplink) | |
| 410 #Change the annotation column into sampname column | |
| 411 if(helpannotation[[j]][i,2] < 0){ | |
| 412 #It's an unknown | |
| 413 new_name <- paste("Unknown",abs(as.integer(helpannotation[[j]][i,2]))) | |
| 414 helpannotation[[j]][i,2] <- new_name | |
| 415 }else{ | |
| 416 #It has been found in local database | |
| 417 for(k in 1:length(DB)){ | |
| 418 if(helpannotation[[j]][i,2] == k){ | |
| 419 helpannotation[[j]][i,2] <- DB[[k]]$Name | |
| 420 break | |
| 421 } | |
| 422 } | |
| 423 } | |
| 424 } | |
| 425 helpannotation[[j]] <- cbind(helpannotation[[j]],pspvector) | |
| 426 names(helpannotation)[j] <- names(resGC$annotation[j]) | |
| 427 } | |
| 428 peaktable <- resGC$PeakTable | |
| 429 | |
| 430 par (mar=c(5, 4, 4, 2) + 0.1) | |
| 431 #For each unknown | |
| 432 for (l in 1:length(unkn)){ | |
| 433 #recordPlot | |
| 434 perpage=3 #if change change layout also! | |
| 435 dev.new(width=21/2.54, height=29.7/2.54, file=paste("Unknown_",unkn[l],".pdf", sep="")) #A4 pdf | |
| 436 # par(mfrow=c(perpage,2)) | |
| 437 layout(matrix(c(1,1,2,3,4,4,5,6,7,7,8,9), 6, 2, byrow = TRUE), widths=rep(c(1,1),perpage), heights=rep(c(1,5),perpage)) | |
| 438 # layout.show(6) | |
| 439 oma.saved <- par("oma") | |
| 440 par(oma = rep.int(0, 4)) | |
| 441 par(oma = oma.saved) | |
| 442 o.par <- par(mar = rep.int(0, 4)) | |
| 443 on.exit(par(o.par)) | |
| 444 #For each sample | |
| 445 for (c in 1:length(resGC$xset)) { | |
| 446 #get sample name | |
| 447 sampname<-basename(resGC$xset[[c]]@xcmsSet@filepaths) | |
| 448 #remove .cdf, .mzXML filepattern | |
| 449 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]", | |
| 450 "[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") | |
| 451 filepattern <- paste(paste("\\.", filepattern, "$", sep = ""), collapse = "|") | |
| 452 sampname<-gsub(filepattern, "",sampname) | |
| 453 title1<-paste(peaktable[unkn[l],1],"from",sampname, sep = " ") | |
| 454 an<-resGC$xset[[c]] | |
| 455 if(fileFrom == "zipfile") { | |
| 456 an@xcmsSet@filepaths <- paste0("./",an@xcmsSet@phenoData[,"class"],"/",basename(an@xcmsSet@filepaths)) | |
| 457 }#else { | |
| 458 #print(an@xcmsSet@filepaths) | |
| 459 #an@xcmsSet@filepaths <- paste0("./",basename(an@xcmsSet@filepaths)) | |
| 460 #} | |
| 461 #Find the good annotation for this sample | |
| 462 for(a in 1:length(helpannotation)){ | |
| 463 if(gsub(filepattern, "", names(helpannotation)[a]) == paste0("./",sampname)){ | |
| 464 #Find the unkn or the matched std in this sample | |
| 465 findunkn <- FALSE | |
| 466 for(r in 1:nrow(helpannotation[[a]])){ | |
| 467 if(helpannotation[[a]][r,"annotation"] == peaktable[unkn[l],1]){ | |
| 468 findunkn <- TRUE | |
| 469 pcgrp <- helpannotation[[a]][r,"pspvector"] | |
| 470 par (mar=c(0, 0, 0, 0) + 0.1) | |
| 471 #Write title | |
| 472 plot.new() | |
| 473 box() | |
| 474 text(0.5, 0.5, title1, cex=2) | |
| 475 par (mar=c(3, 2.5, 3, 1.5) + 0.1) | |
| 476 #Window for EIC | |
| 477 plotEICs(an, pspec=pcgrp, maxlabel=2) | |
| 478 #Window for pseudospectra | |
| 479 plotPsSpectrum(an, pspec=pcgrp, maxlabel=2) | |
| 480 } | |
| 481 } | |
| 482 if(!findunkn) { | |
| 483 par (mar=c(0, 0, 0, 0) + 0.1) | |
| 484 #Write title | |
| 485 plot.new() | |
| 486 box() | |
| 487 text(0.5, 0.5, title1, cex=2) | |
| 488 #Window for EIC | |
| 489 plot.new() | |
| 490 box() | |
| 491 text(0.5, 0.5, "NOT FOUND", cex=2) | |
| 492 #Window for pseudospectra | |
| 493 plot.new() | |
| 494 box() | |
| 495 text(0.5, 0.5, "NOT FOUND", cex=2) | |
| 496 } | |
| 497 break | |
| 498 } | |
| 499 } | |
| 500 } | |
| 501 graphics.off() | |
| 502 }#end for unkn[l] | |
| 503 }#end function |
