annotate lib.r @ 11:67ab853b89f3 draft

planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
author lecorguille
date Tue, 03 Apr 2018 11:38:21 -0400
parents 47e953d9da82
children 9efcd7620cde
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
1 #@authors ABiMS TEAM, Y. Guitton
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
2 # lib.r for Galaxy Workflow4Metabolomics xcms tools
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
3
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
4 #@author G. Le Corguille
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
5 # solve an issue with batch if arguments are logical TRUE/FALSE
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
6 parseCommandArgs <- function(...) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
7 args <- batch::parseCommandArgs(...)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
8 for (key in names(args)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
9 if (args[key] %in% c("TRUE","FALSE"))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
10 args[key] = as.logical(args[key])
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
11 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
12 return(args)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
13 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
14
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
15 #@author G. Le Corguille
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
16 # This function will
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
17 # - load the packages
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
18 # - display the sessionInfo
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
19 loadAndDisplayPackages <- function(pkgs) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
20 for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE)))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
21
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
22 sessioninfo = sessionInfo()
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
23 cat(sessioninfo$R.version$version.string,"\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
24 cat("Main packages:\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
25 for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
26 cat("Other loaded packages:\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
27 for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
28 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
29
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
30 #@author G. Le Corguille
11
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
31 # This function merge several xdata into one.
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
32 mergeXData <- function(args) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
33 for(image in args$images) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
34 load(image)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
35 # Handle infiles
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
36 if (!exists("singlefile")) singlefile <- NULL
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
37 if (!exists("zipfile")) zipfile <- NULL
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
38 rawFilePath <- getRawfilePathFromArguments(singlefile, zipfile, args)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
39 zipfile <- rawFilePath$zipfile
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
40 singlefile <- rawFilePath$singlefile
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
41 retrieveRawfileInTheWorkingDirectory(singlefile, zipfile)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
42 if (exists("raw_data")) xdata <- raw_data
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
43 if (!exists("xdata")) stop("\n\nERROR: The RData doesn't contain any object called 'xdata'. This RData should have been created by an old version of XMCS 2.*")
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
44 cat(sampleNamesList$sampleNamesOrigin,"\n")
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
45 if (!exists("xdata_merged")) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
46 xdata_merged <- xdata
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
47 singlefile_merged <- singlefile
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
48 md5sumList_merged <- md5sumList
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
49 sampleNamesList_merged <- sampleNamesList
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
50 } else {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
51 if (is(xdata, "XCMSnExp")) xdata_merged <- c(xdata_merged,xdata)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
52 else if (is(xdata, "OnDiskMSnExp")) xdata_merged <- .concatenate_OnDiskMSnExp(xdata_merged,xdata)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
53 else stop("\n\nERROR: The RData either a OnDiskMSnExp object called raw_data or a XCMSnExp object called xdata")
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
54 singlefile_merged <- c(singlefile_merged,singlefile)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
55 md5sumList_merged$origin <- rbind(md5sumList_merged$origin,md5sumList$origin)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
56 sampleNamesList_merged$sampleNamesOrigin <- c(sampleNamesList_merged$sampleNamesOrigin,sampleNamesList$sampleNamesOrigin)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
57 sampleNamesList_merged$sampleNamesMakeNames <- c(sampleNamesList_merged$sampleNamesMakeNames,sampleNamesList$sampleNamesMakeNames)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
58 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
59 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
60 rm(image)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
61 xdata <- xdata_merged; rm(xdata_merged)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
62 singlefile <- singlefile_merged; rm(singlefile_merged)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
63 md5sumList <- md5sumList_merged; rm(md5sumList_merged)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
64 sampleNamesList <- sampleNamesList_merged; rm(sampleNamesList_merged)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
65
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
66 if (!is.null(args$sampleMetadata)) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
67 cat("\tXSET PHENODATA SETTING...\n")
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
68 sampleMetadataFile <- args$sampleMetadata
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
69 sampleMetadata <- getDataFrameFromFile(sampleMetadataFile, header=F)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
70 xdata@phenoData@data$sample_group=sampleMetadata$V2[match(xdata@phenoData@data$sample_name,sampleMetadata$V1)]
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
71
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
72 if (any(is.na(pData(xdata)$sample_group))) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
73 sample_missing <- pData(xdata)$sample_name[is.na(pData(xdata)$sample_group)]
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
74 error_message <- paste("Those samples are missing in your sampleMetadata:", paste(sample_missing, collapse=" "))
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
75 print(error_message)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
76 stop(error_message)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
77 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
78 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
79 return(list("xdata"=xdata, "singlefile"=singlefile, "md5sumList"=md5sumList,"sampleNamesList"=sampleNamesList))
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
80 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
81
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
82 #@author G. Le Corguille
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
83 # This function convert if it is required the Retention Time in minutes
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
84 RTSecondToMinute <- function(variableMetadata, convertRTMinute) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
85 if (convertRTMinute){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
86 #converting the retention times (seconds) into minutes
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
87 print("converting the retention times into minutes in the variableMetadata")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
88 variableMetadata[,"rt"] <- variableMetadata[,"rt"]/60
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
89 variableMetadata[,"rtmin"] <- variableMetadata[,"rtmin"]/60
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
90 variableMetadata[,"rtmax"] <- variableMetadata[,"rtmax"]/60
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
91 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
92 return (variableMetadata)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
93 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
94
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
95 #@author G. Le Corguille
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
96 # This function format ions identifiers
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
97 formatIonIdentifiers <- function(variableMetadata, numDigitsRT=0, numDigitsMZ=0) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
98 splitDeco <- strsplit(as.character(variableMetadata$name),"_")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
99 idsDeco <- sapply(splitDeco, function(x) { deco=unlist(x)[2]; if (is.na(deco)) return ("") else return(paste0("_",deco)) })
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
100 namecustom <- make.unique(paste0("M",round(variableMetadata[,"mz"],numDigitsMZ),"T",round(variableMetadata[,"rt"],numDigitsRT),idsDeco))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
101 variableMetadata <- cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))])
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
102 return(variableMetadata)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
103 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
104
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
105 #@author G. Le Corguille
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
106 # Draw the plotChromPeakDensity 3 per page in a pdf file
8
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
107 getPlotChromPeakDensity <- function(xdata, mzdigit=4) {
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
108 pdf(file="plotChromPeakDensity.pdf", width=16, height=12)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
109
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
110 par(mfrow = c(3, 1), mar = c(4, 4, 1, 0.5))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
111
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
112 group_colors <- brewer.pal(3, "Set1")[1:length(unique(xdata$sample_group))]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
113 names(group_colors) <- unique(xdata$sample_group)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
114
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
115 xlim <- c(min(featureDefinitions(xdata)$rtmin), max(featureDefinitions(xdata)$rtmax))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
116 for (i in 1:nrow(featureDefinitions(xdata))) {
8
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
117 mzmin = featureDefinitions(xdata)[i,]$mzmin
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
118 mzmax = featureDefinitions(xdata)[i,]$mzmax
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
119 plotChromPeakDensity(xdata, mz=c(mzmin,mzmax), col=group_colors, pch=16, xlim=xlim, main=paste(round(mzmin,mzdigit),round(mzmax,mzdigit)))
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
120 legend("topright", legend=names(group_colors), col=group_colors, cex=0.8, lty=1)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
121 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
122
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
123 dev.off()
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
124 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
125
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
126 #@author G. Le Corguille
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
127 # Draw the plotChromPeakDensity 3 per page in a pdf file
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
128 getPlotAdjustedRtime <- function(xdata) {
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
129
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
130 pdf(file="raw_vs_adjusted_rt.pdf", width=16, height=12)
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
131
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
132 # Color by group
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
133 group_colors <- brewer.pal(3, "Set1")[1:length(unique(xdata$sample_group))]
11
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
134 if (length(group_colors) > 1) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
135 names(group_colors) <- unique(xdata$sample_group)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
136 plotAdjustedRtime(xdata, col = group_colors[xdata$sample_group])
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
137 legend("topright", legend=names(group_colors), col=group_colors, cex=0.8, lty=1)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
138 }
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
139
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
140 # Color by sample
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
141 plotAdjustedRtime(xdata, col = rainbow(length(xdata@phenoData@data$sample_name)))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
142 legend("topright", legend=xdata@phenoData@data$sample_name, col=rainbow(length(xdata@phenoData@data$sample_name)), cex=0.8, lty=1)
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
143
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
144 dev.off()
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
145 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
146
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
147 #@author G. Le Corguille
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
148 # value: intensity values to be used into, maxo or intb
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
149 getPeaklistW4M <- function(xdata, intval="into", convertRTMinute=F, numDigitsMZ=4, numDigitsRT=0, variableMetadataOutput, dataMatrixOutput) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
150 dataMatrix <- featureValues(xdata, method="medret", value=intval)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
151 colnames(dataMatrix) <- tools::file_path_sans_ext(colnames(dataMatrix))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
152 dataMatrix = cbind(name=groupnamesW4M(xdata), dataMatrix)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
153 variableMetadata <- featureDefinitions(xdata)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
154 colnames(variableMetadata)[1] = "mz"; colnames(variableMetadata)[4] = "rt"
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
155 variableMetadata = data.frame(name=groupnamesW4M(xdata), variableMetadata)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
156
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
157 variableMetadata <- RTSecondToMinute(variableMetadata, convertRTMinute)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
158 variableMetadata <- formatIonIdentifiers(variableMetadata, numDigitsRT=numDigitsRT, numDigitsMZ=numDigitsMZ)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
159
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
160 write.table(variableMetadata, file=variableMetadataOutput,sep="\t",quote=F,row.names=F)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
161 write.table(dataMatrix, file=dataMatrixOutput,sep="\t",quote=F,row.names=F)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
162
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
163 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
164
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
165 #@author G. Le Corguille
11
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
166 # It allow different of field separators
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
167 getDataFrameFromFile <- function(filename, header=T) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
168 myDataFrame <- read.table(filename, header=header, sep=";", stringsAsFactors=F)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
169 if (ncol(myDataFrame) < 2) myDataFrame <- read.table(filename, header=header, sep="\t", stringsAsFactors=F)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
170 if (ncol(myDataFrame) < 2) myDataFrame <- read.table(filename, header=header, sep=",", stringsAsFactors=F)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
171 if (ncol(myDataFrame) < 2) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
172 error_message="Your tabular file seems not well formatted. The column separators accepted are ; , and tabulation"
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
173 print(error_message)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
174 stop(error_message)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
175 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
176 return(myDataFrame)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
177 }
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
178
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
179 getPlotChromatogram <- function(xdata, pdfname="Chromatogram.pdf", aggregationFun = "max") {
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
180
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
181 chrom <- chromatogram(xdata, aggregationFun = aggregationFun)
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
182 if (aggregationFun == "sum")
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
183 type="Total Ion Chromatograms"
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
184 else
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
185 type="Base Peak Intensity Chromatograms"
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
186
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
187 adjusted="Raw"
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
188 if (hasAdjustedRtime(xdata))
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
189 adjusted="Adjusted"
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
190
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
191 main <- paste(type,":",adjusted,"data")
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
192
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
193 pdf(pdfname, width=16, height=10)
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
194
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
195 # Color by group
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
196 group_colors <- brewer.pal(3, "Set1")[1:length(unique(xdata$sample_group))]
11
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
197 if (length(group_colors) > 1) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
198 names(group_colors) <- unique(xdata$sample_group)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
199 plot(chrom, col = group_colors[chrom$sample_group], main=main)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
200 legend("topright", legend=names(group_colors), col=group_colors, cex=0.8, lty=1)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
201 }
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
202
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
203 # Color by sample
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
204 plot(chrom, col = rainbow(length(xdata@phenoData@data$sample_name)), main=main)
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
205 legend("topright", legend=xdata@phenoData@data$sample_name, col=rainbow(length(xdata@phenoData@data$sample_name)), cex=0.8, lty=1)
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
206
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
207 dev.off()
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
208 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
209
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
210 #@author G. Le Corguille
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
211 getPlotTICs <- function(xdata, pdfname="TICs.pdf") {
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
212 getPlotChromatogram(xdata, pdfname, aggregationFun = "sum")
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
213 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
214
10
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
215 #@author G. Le Corguille
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
216 getPlotBPIs <- function(xdata, pdfname="BPIs.pdf") {
47e953d9da82 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 49203f8a5271fa5e6bb889e907df71ebf7757309
lecorguille
parents: 8
diff changeset
217 getPlotChromatogram(xdata, pdfname, aggregationFun = "max")
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
218 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
219
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
220
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
221 # Get the polarities from all the samples of a condition
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
222 #@author Misharl Monsoor misharl.monsoor@sb-roscoff.fr ABiMS TEAM
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
223 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
224 getSampleMetadata <- function(xdata=NULL, sampleMetadataOutput="sampleMetadata.tsv") {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
225 cat("Creating the sampleMetadata file...\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
226
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
227 #Create the sampleMetada dataframe
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
228 sampleMetadata <- xdata@phenoData@data
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
229 rownames(sampleMetadata) <- NULL
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
230 colnames(sampleMetadata) <- c("sampleMetadata", "class")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
231
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
232 sampleNamesOrigin <- sampleMetadata$sampleMetadata
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
233 sampleNamesMakeNames <- make.names(sampleNamesOrigin)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
234
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
235 if (any(duplicated(sampleNamesMakeNames))) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
236 write("\n\nERROR: Usually, R has trouble to deal with special characters in its column names, so it rename them using make.names().\nIn your case, at least two columns after the renaming obtain the same name, thus XCMS will collapse those columns per name.", stderr())
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
237 for (sampleName in sampleNamesOrigin) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
238 write(paste(sampleName,"\t->\t",make.names(sampleName)),stderr())
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
239 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
240 stop("\n\nERROR: One or more of your files will not be import by xcmsSet. It may due to bad characters in their filenames.")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
241 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
242
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
243 if (!all(sampleNamesOrigin == sampleNamesMakeNames)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
244 cat("\n\nWARNING: Usually, R has trouble to deal with special characters in its column names, so it rename them using make.names()\nIn your case, one or more sample names will be renamed in the sampleMetadata and dataMatrix files:\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
245 for (sampleName in sampleNamesOrigin) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
246 cat(paste(sampleName,"\t->\t",make.names(sampleName),"\n"))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
247 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
248 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
249
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
250 sampleMetadata$sampleMetadata <- sampleNamesMakeNames
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
251
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
252
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
253 #For each sample file, the following actions are done
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
254 for (fileIdx in 1:length(fileNames(xdata))) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
255 #Check if the file is in the CDF format
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
256 if (!mzR:::netCDFIsFile(fileNames(xdata))) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
257
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
258 # If the column isn't exist, with add one filled with NA
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
259 if (is.null(sampleMetadata$polarity)) sampleMetadata$polarity <- NA
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
260
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
261 #Extract the polarity (a list of polarities)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
262 polarity <- fData(xdata)[fData(xdata)$fileIdx == fileIdx,"polarity"]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
263 #Verify if all the scans have the same polarity
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
264 uniq_list <- unique(polarity)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
265 if (length(uniq_list)>1){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
266 polarity <- "mixed"
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
267 } else {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
268 polarity <- as.character(uniq_list)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
269 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
270
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
271 #Set the polarity attribute
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
272 sampleMetadata$polarity[fileIdx] <- polarity
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
273 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
274
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
275 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
276
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
277 write.table(sampleMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=sampleMetadataOutput)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
278
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
279 return(list("sampleNamesOrigin"=sampleNamesOrigin, "sampleNamesMakeNames"=sampleNamesMakeNames))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
280
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
281 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
282
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
283
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
284 # This function check if xcms will found all the files
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
285 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
286 checkFilesCompatibilityWithXcms <- function(directory) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
287 cat("Checking files filenames compatibilities with xmcs...\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
288 # WHAT XCMS WILL FIND
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
289 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
290 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
291 info <- file.info(directory)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
292 listed <- list.files(directory[info$isdir], pattern=filepattern, recursive=TRUE, full.names=TRUE)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
293 files <- c(directory[!info$isdir], listed)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
294 files_abs <- file.path(getwd(), files)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
295 exists <- file.exists(files_abs)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
296 files[exists] <- files_abs[exists]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
297 files[exists] <- sub("//","/",files[exists])
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
298
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
299 # WHAT IS ON THE FILESYSTEM
8
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
300 filesystem_filepaths <- system(paste0("find \"$PWD/",directory,"\" -not -name '\\.*' -not -path '*conda-env*' -type f -name \"*\""), intern=T)
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
301 filesystem_filepaths <- filesystem_filepaths[grep(filepattern, filesystem_filepaths, perl=T)]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
302
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
303 # COMPARISON
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
304 if (!is.na(table(filesystem_filepaths %in% files)["FALSE"])) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
305 write("\n\nERROR: List of the files which will not be imported by xcmsSet",stderr())
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
306 write(filesystem_filepaths[!(filesystem_filepaths %in% files)],stderr())
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
307 stop("\n\nERROR: One or more of your files will not be import by xcmsSet. It may due to bad characters in their filenames.")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
308 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
309 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
310
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
311
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
312 #This function list the compatible files within the directory as xcms did
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
313 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
314 getMSFiles <- function (directory) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
315 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
316 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
317 info <- file.info(directory)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
318 listed <- list.files(directory[info$isdir], pattern=filepattern,recursive=TRUE, full.names=TRUE)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
319 files <- c(directory[!info$isdir], listed)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
320 exists <- file.exists(files)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
321 files <- files[exists]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
322 return(files)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
323 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
324
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
325 # This function check if XML contains special caracters. It also checks integrity and completness.
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
326 #@author Misharl Monsoor misharl.monsoor@sb-roscoff.fr ABiMS TEAM
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
327 checkXmlStructure <- function (directory) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
328 cat("Checking XML structure...\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
329
8
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
330 cmd <- paste0("IFS=$'\n'; for xml in $(find '",directory,"' -not -name '\\.*' -not -path '*conda-env*' -type f -iname '*.*ml*'); do if [ $(xmllint --nonet --noout \"$xml\" 2> /dev/null; echo $?) -gt 0 ]; then echo $xml;fi; done;")
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
331 capture <- system(cmd, intern=TRUE)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
332
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
333 if (length(capture)>0){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
334 #message=paste("The following mzXML or mzML file is incorrect, please check these files first:",capture)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
335 write("\n\nERROR: The following mzXML or mzML file(s) are incorrect, please check these files first:", stderr())
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
336 write(capture, stderr())
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
337 stop("ERROR: xcmsSet cannot continue with incorrect mzXML or mzML files")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
338 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
339
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
340 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
341
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
342
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
343 # This function check if XML contain special characters
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
344 #@author Misharl Monsoor misharl.monsoor@sb-roscoff.fr ABiMS TEAM
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
345 deleteXmlBadCharacters<- function (directory) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
346 cat("Checking Non ASCII characters in the XML...\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
347
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
348 processed <- F
8
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
349 l <- system( paste0("find '",directory, "' -not -name '\\.*' -not -path '*conda-env*' -type f -iname '*.*ml*'"), intern=TRUE)
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
350 for (i in l){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
351 cmd <- paste("LC_ALL=C grep '[^ -~]' \"", i, "\"", sep="")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
352 capture <- suppressWarnings(system(cmd, intern=TRUE))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
353 if (length(capture)>0){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
354 cmd <- paste("perl -i -pe 's/[^[:ascii:]]//g;'",i)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
355 print( paste("WARNING: Non ASCII characters have been removed from the ",i,"file") )
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
356 c <- system(cmd, intern=TRUE)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
357 capture <- ""
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
358 processed <- T
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
359 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
360 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
361 if (processed) cat("\n\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
362 return(processed)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
363 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
364
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
365
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
366 # This function will compute MD5 checksum to check the data integrity
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
367 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
368 getMd5sum <- function (directory) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
369 cat("Compute md5 checksum...\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
370 # WHAT XCMS WILL FIND
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
371 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
372 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
373 info <- file.info(directory)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
374 listed <- list.files(directory[info$isdir], pattern=filepattern, recursive=TRUE, full.names=TRUE)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
375 files <- c(directory[!info$isdir], listed)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
376 exists <- file.exists(files)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
377 files <- files[exists]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
378
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
379 library(tools)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
380
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
381 #cat("\n\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
382
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
383 return(as.matrix(md5sum(files)))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
384 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
385
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
386
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
387 # This function get the raw file path from the arguments
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
388 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
389 getRawfilePathFromArguments <- function(singlefile, zipfile, args) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
390 if (!is.null(args$zipfile)) zipfile <- args$zipfile
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
391 if (!is.null(args$zipfilePositive)) zipfile <- args$zipfilePositive
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
392 if (!is.null(args$zipfileNegative)) zipfile <- args$zipfileNegative
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
393
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
394 if (!is.null(args$singlefile_galaxyPath)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
395 singlefile_galaxyPaths <- args$singlefile_galaxyPath;
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
396 singlefile_sampleNames <- args$singlefile_sampleName
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
397 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
398 if (!is.null(args$singlefile_galaxyPathPositive)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
399 singlefile_galaxyPaths <- args$singlefile_galaxyPathPositive;
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
400 singlefile_sampleNames <- args$singlefile_sampleNamePositive
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
401 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
402 if (!is.null(args$singlefile_galaxyPathNegative)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
403 singlefile_galaxyPaths <- args$singlefile_galaxyPathNegative;
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
404 singlefile_sampleNames <- args$singlefile_sampleNameNegative
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
405 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
406 if (exists("singlefile_galaxyPaths")){
8
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
407 singlefile_galaxyPaths <- unlist(strsplit(singlefile_galaxyPaths,"\\|"))
6b5504f877ff planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents: 7
diff changeset
408 singlefile_sampleNames <- unlist(strsplit(singlefile_sampleNames,"\\|"))
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
409
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
410 singlefile <- NULL
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
411 for (singlefile_galaxyPath_i in seq(1:length(singlefile_galaxyPaths))) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
412 singlefile_galaxyPath <- singlefile_galaxyPaths[singlefile_galaxyPath_i]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
413 singlefile_sampleName <- singlefile_sampleNames[singlefile_galaxyPath_i]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
414 singlefile[[singlefile_sampleName]] <- singlefile_galaxyPath
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
415 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
416 }
11
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
417 return(list(zipfile=zipfile, singlefile=singlefile))
7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
418 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
419
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
420
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
421 # This function retrieve the raw file in the working directory
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
422 # - if zipfile: unzip the file with its directory tree
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
423 # - if singlefiles: set symlink with the good filename
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
424 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
425 retrieveRawfileInTheWorkingDirectory <- function(singlefile, zipfile) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
426 if(!is.null(singlefile) && (length("singlefile")>0)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
427 for (singlefile_sampleName in names(singlefile)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
428 singlefile_galaxyPath <- singlefile[[singlefile_sampleName]]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
429 if(!file.exists(singlefile_galaxyPath)){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
430 error_message <- paste("Cannot access the sample:",singlefile_sampleName,"located:",singlefile_galaxyPath,". Please, contact your administrator ... if you have one!")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
431 print(error_message); stop(error_message)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
432 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
433
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
434 if (!suppressWarnings( try (file.link(singlefile_galaxyPath, singlefile_sampleName), silent=T)))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
435 file.copy(singlefile_galaxyPath, singlefile_sampleName)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
436
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
437 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
438 directory <- "."
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
439
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
440 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
441 if(!is.null(zipfile) && (zipfile != "")) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
442 if(!file.exists(zipfile)){
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
443 error_message <- paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
444 print(error_message)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
445 stop(error_message)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
446 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
447
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
448 #list all file in the zip file
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
449 #zip_files <- unzip(zipfile,list=T)[,"Name"]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
450
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
451 #unzip
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
452 suppressWarnings(unzip(zipfile, unzip="unzip"))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
453
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
454 #get the directory name
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
455 suppressWarnings(filesInZip <- unzip(zipfile, list=T))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
456 directories <- unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1])))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
457 directories <- directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
458 directory <- "."
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
459 if (length(directories) == 1) directory <- directories
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
460
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
461 cat("files_root_directory\t",directory,"\n")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
462
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
463 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
464 return (directory)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
465 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
466
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
467
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
468 # This function retrieve a xset like object
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
469 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
470 getxcmsSetObject <- function(xobject) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
471 # XCMS 1.x
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
472 if (class(xobject) == "xcmsSet")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
473 return (xobject)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
474 # XCMS 3.x
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
475 if (class(xobject) == "XCMSnExp") {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
476 # Get the legacy xcmsSet object
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
477 suppressWarnings(xset <- as(xobject, 'xcmsSet'))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
478 sampclass(xset) <- xset@phenoData$sample_group
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
479 return (xset)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
480 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
481 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
482
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
483
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
484 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
485 # https://github.com/sneumann/xcms/issues/250
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
486 groupnamesW4M <- function(xdata, mzdec = 0, rtdec = 0) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
487 mzfmt <- paste("%.", mzdec, "f", sep = "")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
488 rtfmt <- paste("%.", rtdec, "f", sep = "")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
489
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
490 gnames <- paste("M", sprintf(mzfmt, featureDefinitions(xdata)[,"mzmed"]), "T",
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
491 sprintf(rtfmt, featureDefinitions(xdata)[,"rtmed"]), sep = "")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
492
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
493 if (any(dup <- duplicated(gnames)))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
494 for (dupname in unique(gnames[dup])) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
495 dupidx <- which(gnames == dupname)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
496 gnames[dupidx] <- paste(gnames[dupidx], seq(along = dupidx), sep = "_")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
497 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
498
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
499 return (gnames)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
500 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
501
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
502 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
503 # https://github.com/sneumann/xcms/issues/247
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
504 .concatenate_XCMSnExp <- function(...) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
505 x <- list(...)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
506 if (length(x) == 0)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
507 return(NULL)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
508 if (length(x) == 1)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
509 return(x[[1]])
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
510 ## Check that all are XCMSnExp objects.
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
511 if (!all(unlist(lapply(x, function(z) is(z, "XCMSnExp")))))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
512 stop("All passed objects should be 'XCMSnExp' objects")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
513 new_x <- as(.concatenate_OnDiskMSnExp(...), "XCMSnExp")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
514 ## If any of the XCMSnExp has alignment results or detected features drop
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
515 ## them!
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
516 x <- lapply(x, function(z) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
517 if (hasAdjustedRtime(z)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
518 z <- dropAdjustedRtime(z)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
519 warning("Adjusted retention times found, had to drop them.")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
520 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
521 if (hasFeatures(z)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
522 z <- dropFeatureDefinitions(z)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
523 warning("Feature definitions found, had to drop them.")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
524 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
525 z
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
526 })
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
527 ## Combine peaks
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
528 fls <- lapply(x, fileNames)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
529 startidx <- cumsum(lengths(fls))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
530 pks <- lapply(x, chromPeaks)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
531 procH <- lapply(x, processHistory)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
532 for (i in 2:length(fls)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
533 pks[[i]][, "sample"] <- pks[[i]][, "sample"] + startidx[i - 1]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
534 procH[[i]] <- lapply(procH[[i]], function(z) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
535 z@fileIndex <- as.integer(z@fileIndex + startidx[i - 1])
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
536 z
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
537 })
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
538 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
539 pks <- do.call(rbind, pks)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
540 new_x@.processHistory <- unlist(procH)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
541 chromPeaks(new_x) <- pks
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
542 if (validObject(new_x))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
543 new_x
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
544 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
545
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
546 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
547 # https://github.com/sneumann/xcms/issues/247
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
548 .concatenate_OnDiskMSnExp <- function(...) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
549 x <- list(...)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
550 if (length(x) == 0)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
551 return(NULL)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
552 if (length(x) == 1)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
553 return(x[[1]])
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
554 ## Check that all are XCMSnExp objects.
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
555 if (!all(unlist(lapply(x, function(z) is(z, "OnDiskMSnExp")))))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
556 stop("All passed objects should be 'OnDiskMSnExp' objects")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
557 ## Check processingQueue
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
558 procQ <- lapply(x, function(z) z@spectraProcessingQueue)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
559 new_procQ <- procQ[[1]]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
560 is_ok <- unlist(lapply(procQ, function(z)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
561 !is.character(all.equal(new_procQ, z))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
562 ))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
563 if (any(!is_ok)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
564 warning("Processing queues from the submitted objects differ! ",
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
565 "Dropping the processing queue.")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
566 new_procQ <- list()
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
567 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
568 ## processingData
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
569 fls <- lapply(x, function(z) z@processingData@files)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
570 startidx <- cumsum(lengths(fls))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
571 ## featureData
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
572 featd <- lapply(x, fData)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
573 ## Have to update the file index and the spectrum names.
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
574 for (i in 2:length(featd)) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
575 featd[[i]]$fileIdx <- featd[[i]]$fileIdx + startidx[i - 1]
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
576 rownames(featd[[i]]) <- MSnbase:::formatFileSpectrumNames(
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
577 fileIds = featd[[i]]$fileIdx,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
578 spectrumIds = featd[[i]]$spIdx,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
579 nSpectra = nrow(featd[[i]]),
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
580 nFiles = length(unlist(fls))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
581 )
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
582 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
583 featd <- do.call(rbind, featd)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
584 featd$spectrum <- 1:nrow(featd)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
585 ## experimentData
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
586 expdata <- lapply(x, function(z) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
587 ed <- z@experimentData
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
588 data.frame(instrumentManufacturer = ed@instrumentManufacturer,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
589 instrumentModel = ed@instrumentModel,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
590 ionSource = ed@ionSource,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
591 analyser = ed@analyser,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
592 detectorType = ed@detectorType,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
593 stringsAsFactors = FALSE)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
594 })
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
595 expdata <- do.call(rbind, expdata)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
596 expdata <- new("MIAPE",
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
597 instrumentManufacturer = expdata$instrumentManufacturer,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
598 instrumentModel = expdata$instrumentModel,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
599 ionSource = expdata$ionSource,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
600 analyser = expdata$analyser,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
601 detectorType = expdata$detectorType)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
602
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
603 ## protocolData
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
604 protodata <- lapply(x, function(z) z@protocolData)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
605 if (any(unlist(lapply(protodata, nrow)) > 0))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
606 warning("Found non-empty protocol data, but merging protocol data is",
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
607 " currently not supported. Skipped.")
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
608 ## phenoData
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
609 pdata <- do.call(rbind, lapply(x, pData))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
610 res <- new(
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
611 "OnDiskMSnExp",
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
612 phenoData = new("NAnnotatedDataFrame", data = pdata),
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
613 featureData = new("AnnotatedDataFrame", featd),
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
614 processingData = new("MSnProcess",
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
615 processing = paste0("Concatenated [", date(), "]"),
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
616 files = unlist(fls), smoothed = NA),
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
617 experimentData = expdata,
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
618 spectraProcessingQueue = new_procQ)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
619 if (validObject(res))
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
620 res
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
621 }
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
622
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
623 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
624 # https://github.com/sneumann/xcms/issues/247
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
625 c.XCMSnExp <- function(...) {
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
626 .concatenate_XCMSnExp(...)
dca722aecb67 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
diff changeset
627 }
11
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
628
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
629 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
630 # https://github.com/sneumann/xcms/issues/247
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
631 c.MSnbase <- function(...) {
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
632 .concatenate_OnDiskMSnExp(...)
67ab853b89f3 planemo upload for repository https://github.com/workflow4metabolomics/xcms commit f01148783819c37e474790dbd56619862960448a
lecorguille
parents: 10
diff changeset
633 }