Mercurial > repos > lecorguille > xcms_xcmsset
annotate lib.r @ 33:c363b9f1caef draft
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
author | lecorguille |
---|---|
date | Mon, 05 Mar 2018 04:15:34 -0500 |
parents | 2bf1cb023c94 |
children | efd23113d5f4 |
rev | line source |
---|---|
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
1 #@authors ABiMS TEAM, Y. Guitton |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
2 # lib.r for Galaxy Workflow4Metabolomics xcms tools |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
3 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
4 #@author G. Le Corguille |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
5 # solve an issue with batch if arguments are logical TRUE/FALSE |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
6 parseCommandArgs <- function(...) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
7 args <- batch::parseCommandArgs(...) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
8 for (key in names(args)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
9 if (args[key] %in% c("TRUE","FALSE")) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
10 args[key] = as.logical(args[key]) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
11 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
12 return(args) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
13 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
14 |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
15 #@author G. Le Corguille |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
16 # This function will |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
17 # - load the packages |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
18 # - display the sessionInfo |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
19 loadAndDisplayPackages <- function(pkgs) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
20 for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
21 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
22 sessioninfo = sessionInfo() |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
23 cat(sessioninfo$R.version$version.string,"\n") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
24 cat("Main packages:\n") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
25 for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
26 cat("Other loaded packages:\n") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
27 for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
28 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
29 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
30 #@author G. Le Corguille |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
31 # This function convert if it is required the Retention Time in minutes |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
32 RTSecondToMinute <- function(variableMetadata, convertRTMinute) { |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
33 if (convertRTMinute){ |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
34 #converting the retention times (seconds) into minutes |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
35 print("converting the retention times into minutes in the variableMetadata") |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
36 variableMetadata[,"rt"] <- variableMetadata[,"rt"]/60 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
37 variableMetadata[,"rtmin"] <- variableMetadata[,"rtmin"]/60 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
38 variableMetadata[,"rtmax"] <- variableMetadata[,"rtmax"]/60 |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
39 } |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
40 return (variableMetadata) |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
41 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
42 |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
43 #@author G. Le Corguille |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
44 # This function format ions identifiers |
21
ab238b104c3f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 481448087f0e09c131b24f7d552db69f3552d371-dirty
lecorguille
parents:
20
diff
changeset
|
45 formatIonIdentifiers <- function(variableMetadata, numDigitsRT=0, numDigitsMZ=0) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
46 splitDeco <- strsplit(as.character(variableMetadata$name),"_") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
47 idsDeco <- sapply(splitDeco, function(x) { deco=unlist(x)[2]; if (is.na(deco)) return ("") else return(paste0("_",deco)) }) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
48 namecustom <- make.unique(paste0("M",round(variableMetadata[,"mz"],numDigitsMZ),"T",round(variableMetadata[,"rt"],numDigitsRT),idsDeco)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
49 variableMetadata <- cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))]) |
21
ab238b104c3f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 481448087f0e09c131b24f7d552db69f3552d371-dirty
lecorguille
parents:
20
diff
changeset
|
50 return(variableMetadata) |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
51 } |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
52 |
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
53 #@author G. Le Corguille |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
54 # Draw the plotChromPeakDensity 3 per page in a pdf file |
33
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
55 getPlotChromPeakDensity <- function(xdata, mzdigit=4) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
56 pdf(file="plotChromPeakDensity.pdf", width=16, height=12) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
57 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
58 par(mfrow = c(3, 1), mar = c(4, 4, 1, 0.5)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
59 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
60 group_colors <- brewer.pal(3, "Set1")[1:length(unique(xdata$sample_group))] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
61 names(group_colors) <- unique(xdata$sample_group) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
62 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
63 xlim <- c(min(featureDefinitions(xdata)$rtmin), max(featureDefinitions(xdata)$rtmax)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
64 for (i in 1:nrow(featureDefinitions(xdata))) { |
33
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
65 mzmin = featureDefinitions(xdata)[i,]$mzmin |
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
66 mzmax = featureDefinitions(xdata)[i,]$mzmax |
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
67 plotChromPeakDensity(xdata, mz=c(mzmin,mzmax), col=group_colors, pch=16, xlim=xlim, main=paste(round(mzmin,mzdigit),round(mzmax,mzdigit))) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
68 legend("topright", legend=names(group_colors), col=group_colors, cex=0.8, lty=1) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
69 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
70 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
71 dev.off() |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
72 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
73 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
74 #@author G. Le Corguille |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
75 # Draw the plotChromPeakDensity 3 per page in a pdf file |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
76 getPlotAdjustedRtime <- function(xdata) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
77 pdf(file="raw_vs_adjusted_rt.pdf", width=16, height=12) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
78 # Color by group |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
79 group_colors <- brewer.pal(3, "Set1")[1:length(unique(xdata$sample_group))] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
80 names(group_colors) <- unique(xdata$sample_group) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
81 plotAdjustedRtime(xdata, col = group_colors[xdata$sample_group]) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
82 legend("topright", legend=names(group_colors), col=group_colors, cex=0.8, lty=1) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
83 # Color by sample |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
84 plotAdjustedRtime(xdata, col = rainbow(length(xdata@phenoData@data$sample_name))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
85 legend("topright", legend=xdata@phenoData@data$sample_name, col=rainbow(length(xdata@phenoData@data$sample_name)), cex=0.8, lty=1) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
86 dev.off() |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
87 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
88 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
89 #@author G. Le Corguille |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
90 # value: intensity values to be used into, maxo or intb |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
91 getPeaklistW4M <- function(xdata, intval="into", convertRTMinute=F, numDigitsMZ=4, numDigitsRT=0, variableMetadataOutput, dataMatrixOutput) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
92 dataMatrix <- featureValues(xdata, method="medret", value=intval) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
93 colnames(dataMatrix) <- tools::file_path_sans_ext(colnames(dataMatrix)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
94 dataMatrix = cbind(name=groupnamesW4M(xdata), dataMatrix) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
95 variableMetadata <- featureDefinitions(xdata) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
96 colnames(variableMetadata)[1] = "mz"; colnames(variableMetadata)[4] = "rt" |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
97 variableMetadata = data.frame(name=groupnamesW4M(xdata), variableMetadata) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
98 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
99 variableMetadata <- RTSecondToMinute(variableMetadata, convertRTMinute) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
100 variableMetadata <- formatIonIdentifiers(variableMetadata, numDigitsRT=numDigitsRT, numDigitsMZ=numDigitsMZ) |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
101 |
21
ab238b104c3f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 481448087f0e09c131b24f7d552db69f3552d371-dirty
lecorguille
parents:
20
diff
changeset
|
102 write.table(variableMetadata, file=variableMetadataOutput,sep="\t",quote=F,row.names=F) |
ab238b104c3f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 481448087f0e09c131b24f7d552db69f3552d371-dirty
lecorguille
parents:
20
diff
changeset
|
103 write.table(dataMatrix, file=dataMatrixOutput,sep="\t",quote=F,row.names=F) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
104 |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
105 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
106 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
107 #@author Y. Guitton |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
108 getBPC <- function(file,rtcor=NULL, ...) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
109 object <- xcmsRaw(file) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
110 sel <- profRange(object, ...) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
111 cbind(if (is.null(rtcor)) object@scantime[sel$scanidx] else rtcor ,xcms:::colMax(object@env$profile[sel$massidx,sel$scanidx,drop=FALSE])) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
112 #plotChrom(xcmsRaw(file), base=T) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
113 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
114 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
115 #@author Y. Guitton |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
116 getBPCs <- function (xcmsSet=NULL, pdfname="BPCs.pdf",rt=c("raw","corrected"), scanrange=NULL) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
117 cat("Creating BIC pdf...\n") |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
118 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
119 if (is.null(xcmsSet)) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
120 cat("Enter an xcmsSet \n") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
121 stop() |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
122 } else { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
123 files <- filepaths(xcmsSet) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
124 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
125 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
126 phenoDataClass <- as.vector(levels(xcmsSet@phenoData[,"class"])) #sometime phenoData have more than 1 column use first as class |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
127 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
128 classnames <- vector("list",length(phenoDataClass)) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
129 for (i in 1:length(phenoDataClass)){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
130 classnames[[i]] <- which( xcmsSet@phenoData[,"class"]==phenoDataClass[i]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
131 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
132 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
133 N <- dim(phenoData(xcmsSet))[1] |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
134 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
135 TIC <- vector("list",N) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
136 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
137 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
138 for (j in 1:N) { |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
139 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
140 TIC[[j]] <- getBPC(files[j]) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
141 #good for raw |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
142 # seems strange for corrected |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
143 #errors if scanrange used in xcmsSetgeneration |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
144 if (!is.null(xcmsSet) && rt == "corrected") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
145 rtcor <- xcmsSet@rt$corrected[[j]] |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
146 else |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
147 rtcor <- NULL |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
148 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
149 TIC[[j]] <- getBPC(files[j],rtcor=rtcor) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
150 # TIC[[j]][,1]<-rtcor |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
151 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
152 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
153 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
154 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
155 pdf(pdfname,w=16,h=10) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
156 cols <- rainbow(N) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
157 lty <- 1:N |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
158 pch <- 1:N |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
159 #search for max x and max y in BPCs |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
160 xlim <- range(sapply(TIC, function(x) range(x[,1]))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
161 ylim <- range(sapply(TIC, function(x) range(x[,2]))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
162 ylim <- c(-ylim[2], ylim[2]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
163 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
164 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
165 ##plot start |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
166 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
167 if (length(phenoDataClass)>2){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
168 for (k in 1:(length(phenoDataClass)-1)){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
169 for (l in (k+1):length(phenoDataClass)){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
170 #print(paste(phenoDataClass[k],"vs",phenoDataClass[l],sep=" ")) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
171 plot(0, 0, type="n", xlim=xlim/60, ylim=ylim, main=paste("Base Peak Chromatograms \n","BPCs_",phenoDataClass[k]," vs ",phenoDataClass[l], sep=""), xlab="Retention Time (min)", ylab="BPC") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
172 colvect <- NULL |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
173 for (j in 1:length(classnames[[k]])) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
174 tic <- TIC[[classnames[[k]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
175 # points(tic[,1]/60, tic[,2], col=cols[i], pch=pch[i], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
176 points(tic[,1]/60, tic[,2], col=cols[classnames[[k]][j]], pch=pch[classnames[[k]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
177 colvect <- append(colvect,cols[classnames[[k]][j]]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
178 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
179 for (j in 1:length(classnames[[l]])) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
180 # i <- class2names[j] |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
181 tic <- TIC[[classnames[[l]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
182 points(tic[,1]/60, -tic[,2], col=cols[classnames[[l]][j]], pch=pch[classnames[[l]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
183 colvect <- append(colvect,cols[classnames[[l]][j]]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
184 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
185 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col=colvect, lty=lty, pch=pch) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
186 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
187 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
188 }#end if length >2 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
189 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
190 if (length(phenoDataClass)==2){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
191 k <- 1 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
192 l <- 2 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
193 colvect <- NULL |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
194 plot(0, 0, type="n", xlim=xlim/60, ylim=ylim, main=paste("Base Peak Chromatograms \n","BPCs_",phenoDataClass[k],"vs",phenoDataClass[l], sep=""), xlab="Retention Time (min)", ylab="BPC") |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
195 |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
196 for (j in 1:length(classnames[[k]])) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
197 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
198 tic <- TIC[[classnames[[k]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
199 # points(tic[,1]/60, tic[,2], col=cols[i], pch=pch[i], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
200 points(tic[,1]/60, tic[,2], col=cols[classnames[[k]][j]], pch=pch[classnames[[k]][j]], type="l") |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
201 colvect<-append(colvect,cols[classnames[[k]][j]]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
202 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
203 for (j in 1:length(classnames[[l]])) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
204 # i <- class2names[j] |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
205 tic <- TIC[[classnames[[l]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
206 points(tic[,1]/60, -tic[,2], col=cols[classnames[[l]][j]], pch=pch[classnames[[l]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
207 colvect <- append(colvect,cols[classnames[[l]][j]]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
208 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
209 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col=colvect, lty=lty, pch=pch) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
210 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
211 }#end length ==2 |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
212 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
213 #case where only one class |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
214 if (length(phenoDataClass)==1){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
215 k <- 1 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
216 ylim <- range(sapply(TIC, function(x) range(x[,2]))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
217 colvect <- NULL |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
218 plot(0, 0, type="n", xlim=xlim/60, ylim=ylim, main=paste("Base Peak Chromatograms \n","BPCs_",phenoDataClass[k], sep=""), xlab="Retention Time (min)", ylab="BPC") |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
219 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
220 for (j in 1:length(classnames[[k]])) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
221 tic <- TIC[[classnames[[k]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
222 # points(tic[,1]/60, tic[,2], col=cols[i], pch=pch[i], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
223 points(tic[,1]/60, tic[,2], col=cols[classnames[[k]][j]], pch=pch[classnames[[k]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
224 colvect <- append(colvect,cols[classnames[[k]][j]]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
225 } |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
226 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
227 legend("topright",paste(basename(files[c(classnames[[k]])])), col=colvect, lty=lty, pch=pch) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
228 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
229 }#end length ==1 |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
230 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
231 dev.off() #pdf(pdfname,w=16,h=10) |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
232 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
233 invisible(TIC) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
234 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
235 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
236 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
237 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
238 #@author Y. Guitton |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
239 getTIC <- function(file, rtcor=NULL) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
240 object <- xcmsRaw(file) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
241 cbind(if (is.null(rtcor)) object@scantime else rtcor, rawEIC(object, mzrange=range(object@env$mz))$intensity) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
242 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
243 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
244 #overlay TIC from all files in current folder or from xcmsSet, create pdf |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
245 #@author Y. Guitton |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
246 getTICs <- function(xcmsSet=NULL,files=NULL, pdfname="TICs.pdf", rt=c("raw","corrected")) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
247 cat("Creating TIC pdf...\n") |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
248 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
249 if (is.null(xcmsSet)) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
250 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]", "[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
251 filepattern <- paste(paste("\\.", filepattern, "$", sep=""), collapse="|") |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
252 if (is.null(files)) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
253 files <- getwd() |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
254 info <- file.info(files) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
255 listed <- list.files(files[info$isdir], pattern=filepattern, recursive=TRUE, full.names=TRUE) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
256 files <- c(files[!info$isdir], listed) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
257 } else { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
258 files <- filepaths(xcmsSet) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
259 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
260 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
261 phenoDataClass <- as.vector(levels(xcmsSet@phenoData[,"class"])) #sometime phenoData have more than 1 column use first as class |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
262 classnames <- vector("list",length(phenoDataClass)) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
263 for (i in 1:length(phenoDataClass)){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
264 classnames[[i]] <- which( xcmsSet@phenoData[,"class"]==phenoDataClass[i]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
265 } |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
266 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
267 N <- length(files) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
268 TIC <- vector("list",N) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
269 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
270 for (i in 1:N) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
271 if (!is.null(xcmsSet) && rt == "corrected") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
272 rtcor <- xcmsSet@rt$corrected[[i]] else |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
273 rtcor <- NULL |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
274 TIC[[i]] <- getTIC(files[i], rtcor=rtcor) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
275 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
276 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
277 pdf(pdfname, w=16, h=10) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
278 cols <- rainbow(N) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
279 lty <- 1:N |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
280 pch <- 1:N |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
281 #search for max x and max y in TICs |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
282 xlim <- range(sapply(TIC, function(x) range(x[,1]))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
283 ylim <- range(sapply(TIC, function(x) range(x[,2]))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
284 ylim <- c(-ylim[2], ylim[2]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
285 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
286 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
287 ##plot start |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
288 if (length(phenoDataClass)>2){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
289 for (k in 1:(length(phenoDataClass)-1)){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
290 for (l in (k+1):length(phenoDataClass)){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
291 #print(paste(phenoDataClass[k],"vs",phenoDataClass[l],sep=" ")) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
292 plot(0, 0, type="n", xlim=xlim/60, ylim=ylim, main=paste("Total Ion Chromatograms \n","TICs_",phenoDataClass[k]," vs ",phenoDataClass[l], sep=""), xlab="Retention Time (min)", ylab="TIC") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
293 colvect <- NULL |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
294 for (j in 1:length(classnames[[k]])) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
295 tic <- TIC[[classnames[[k]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
296 # points(tic[,1]/60, tic[,2], col=cols[i], pch=pch[i], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
297 points(tic[,1]/60, tic[,2], col=cols[classnames[[k]][j]], pch=pch[classnames[[k]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
298 colvect <- append(colvect,cols[classnames[[k]][j]]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
299 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
300 for (j in 1:length(classnames[[l]])) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
301 # i=class2names[j] |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
302 tic <- TIC[[classnames[[l]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
303 points(tic[,1]/60, -tic[,2], col=cols[classnames[[l]][j]], pch=pch[classnames[[l]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
304 colvect <- append(colvect,cols[classnames[[l]][j]]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
305 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
306 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col=colvect, lty=lty, pch=pch) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
307 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
308 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
309 }#end if length >2 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
310 if (length(phenoDataClass)==2){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
311 k <- 1 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
312 l <- 2 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
313 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
314 plot(0, 0, type="n", xlim=xlim/60, ylim=ylim, main=paste("Total Ion Chromatograms \n","TICs_",phenoDataClass[k],"vs",phenoDataClass[l], sep=""), xlab="Retention Time (min)", ylab="TIC") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
315 colvect <- NULL |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
316 for (j in 1:length(classnames[[k]])) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
317 tic <- TIC[[classnames[[k]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
318 # points(tic[,1]/60, tic[,2], col=cols[i], pch=pch[i], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
319 points(tic[,1]/60, tic[,2], col=cols[classnames[[k]][j]], pch=pch[classnames[[k]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
320 colvect <- append(colvect,cols[classnames[[k]][j]]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
321 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
322 for (j in 1:length(classnames[[l]])) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
323 # i <- class2names[j] |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
324 tic <- TIC[[classnames[[l]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
325 points(tic[,1]/60, -tic[,2], col=cols[classnames[[l]][j]], pch=pch[classnames[[l]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
326 colvect <- append(colvect,cols[classnames[[l]][j]]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
327 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
328 legend("topright",paste(basename(files[c(classnames[[k]],classnames[[l]])])), col=colvect, lty=lty, pch=pch) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
329 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
330 }#end length ==2 |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
331 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
332 #case where only one class |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
333 if (length(phenoDataClass)==1){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
334 k <- 1 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
335 ylim <- range(sapply(TIC, function(x) range(x[,2]))) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
336 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
337 plot(0, 0, type="n", xlim=xlim/60, ylim=ylim, main=paste("Total Ion Chromatograms \n","TICs_",phenoDataClass[k], sep=""), xlab="Retention Time (min)", ylab="TIC") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
338 colvect <- NULL |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
339 for (j in 1:length(classnames[[k]])) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
340 tic <- TIC[[classnames[[k]][j]]] |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
341 # points(tic[,1]/60, tic[,2], col=cols[i], pch=pch[i], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
342 points(tic[,1]/60, tic[,2], col=cols[classnames[[k]][j]], pch=pch[classnames[[k]][j]], type="l") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
343 colvect <- append(colvect,cols[classnames[[k]][j]]) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
344 } |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
345 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
346 legend("topright",paste(basename(files[c(classnames[[k]])])), col=colvect, lty=lty, pch=pch) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
347 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
348 }#end length ==1 |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
349 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
350 dev.off() #pdf(pdfname,w=16,h=10) |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
351 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
352 invisible(TIC) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
353 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
354 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
355 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
356 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
357 # Get the polarities from all the samples of a condition |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
358 #@author Misharl Monsoor misharl.monsoor@sb-roscoff.fr ABiMS TEAM |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
359 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
360 getSampleMetadata <- function(xdata=NULL, sampleMetadataOutput="sampleMetadata.tsv") { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
361 cat("Creating the sampleMetadata file...\n") |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
362 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
363 #Create the sampleMetada dataframe |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
364 sampleMetadata <- xdata@phenoData@data |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
365 rownames(sampleMetadata) <- NULL |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
366 colnames(sampleMetadata) <- c("sampleMetadata", "class") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
367 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
368 sampleNamesOrigin <- sampleMetadata$sampleMetadata |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
369 sampleNamesMakeNames <- make.names(sampleNamesOrigin) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
370 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
371 if (any(duplicated(sampleNamesMakeNames))) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
372 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()) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
373 for (sampleName in sampleNamesOrigin) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
374 write(paste(sampleName,"\t->\t",make.names(sampleName)),stderr()) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
375 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
376 stop("\n\nERROR: One or more of your files will not be import by xcmsSet. It may due to bad characters in their filenames.") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
377 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
378 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
379 if (!all(sampleNamesOrigin == sampleNamesMakeNames)) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
380 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") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
381 for (sampleName in sampleNamesOrigin) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
382 cat(paste(sampleName,"\t->\t",make.names(sampleName),"\n")) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
383 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
384 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
385 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
386 sampleMetadata$sampleMetadata <- sampleNamesMakeNames |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
387 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
388 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
389 #For each sample file, the following actions are done |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
390 for (fileIdx in 1:length(fileNames(xdata))) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
391 #Check if the file is in the CDF format |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
392 if (!mzR:::netCDFIsFile(fileNames(xdata))) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
393 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
394 # If the column isn't exist, with add one filled with NA |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
395 if (is.null(sampleMetadata$polarity)) sampleMetadata$polarity <- NA |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
396 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
397 #Extract the polarity (a list of polarities) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
398 polarity <- fData(xdata)[fData(xdata)$fileIdx == fileIdx,"polarity"] |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
399 #Verify if all the scans have the same polarity |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
400 uniq_list <- unique(polarity) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
401 if (length(uniq_list)>1){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
402 polarity <- "mixed" |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
403 } else { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
404 polarity <- as.character(uniq_list) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
405 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
406 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
407 #Set the polarity attribute |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
408 sampleMetadata$polarity[fileIdx] <- polarity |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
409 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
410 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
411 } |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
412 |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
413 write.table(sampleMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=sampleMetadataOutput) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
414 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
415 return(list("sampleNamesOrigin"=sampleNamesOrigin, "sampleNamesMakeNames"=sampleNamesMakeNames)) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
416 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
417 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
418 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
419 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
420 # This function check if xcms will found all the files |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
421 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
422 checkFilesCompatibilityWithXcms <- function(directory) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
423 cat("Checking files filenames compatibilities with xmcs...\n") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
424 # WHAT XCMS WILL FIND |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
425 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
426 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|") |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
427 info <- file.info(directory) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
428 listed <- list.files(directory[info$isdir], pattern=filepattern, recursive=TRUE, full.names=TRUE) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
429 files <- c(directory[!info$isdir], listed) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
430 files_abs <- file.path(getwd(), files) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
431 exists <- file.exists(files_abs) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
432 files[exists] <- files_abs[exists] |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
433 files[exists] <- sub("//","/",files[exists]) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
434 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
435 # WHAT IS ON THE FILESYSTEM |
33
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
436 filesystem_filepaths <- system(paste0("find \"$PWD/",directory,"\" -not -name '\\.*' -not -path '*conda-env*' -type f -name \"*\""), intern=T) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
437 filesystem_filepaths <- filesystem_filepaths[grep(filepattern, filesystem_filepaths, perl=T)] |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
438 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
439 # COMPARISON |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
440 if (!is.na(table(filesystem_filepaths %in% files)["FALSE"])) { |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
441 write("\n\nERROR: List of the files which will not be imported by xcmsSet",stderr()) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
442 write(filesystem_filepaths[!(filesystem_filepaths %in% files)],stderr()) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
443 stop("\n\nERROR: One or more of your files will not be import by xcmsSet. It may due to bad characters in their filenames.") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
444 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
445 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
446 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
447 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
448 #This function list the compatible files within the directory as xcms did |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
449 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr ABiMS TEAM |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
450 getMSFiles <- function (directory) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
451 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
452 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
453 info <- file.info(directory) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
454 listed <- list.files(directory[info$isdir], pattern=filepattern,recursive=TRUE, full.names=TRUE) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
455 files <- c(directory[!info$isdir], listed) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
456 exists <- file.exists(files) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
457 files <- files[exists] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
458 return(files) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
459 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
460 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
461 # This function check if XML contains special caracters. It also checks integrity and completness. |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
462 #@author Misharl Monsoor misharl.monsoor@sb-roscoff.fr ABiMS TEAM |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
463 checkXmlStructure <- function (directory) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
464 cat("Checking XML structure...\n") |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
465 |
33
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
466 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;") |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
467 capture <- system(cmd, intern=TRUE) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
468 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
469 if (length(capture)>0){ |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
470 #message=paste("The following mzXML or mzML file is incorrect, please check these files first:",capture) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
471 write("\n\nERROR: The following mzXML or mzML file(s) are incorrect, please check these files first:", stderr()) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
472 write(capture, stderr()) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
473 stop("ERROR: xcmsSet cannot continue with incorrect mzXML or mzML files") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
474 } |
16
f28041d2180a
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 08e7f269a5c59687a7768be8db5fcb4e4d736093
lecorguille
parents:
15
diff
changeset
|
475 |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
476 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
477 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
478 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
479 # This function check if XML contain special characters |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
480 #@author Misharl Monsoor misharl.monsoor@sb-roscoff.fr ABiMS TEAM |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
481 deleteXmlBadCharacters<- function (directory) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
482 cat("Checking Non ASCII characters in the XML...\n") |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
483 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
484 processed <- F |
33
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
485 l <- system( paste0("find '",directory, "' -not -name '\\.*' -not -path '*conda-env*' -type f -iname '*.*ml*'"), intern=TRUE) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
486 for (i in l){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
487 cmd <- paste("LC_ALL=C grep '[^ -~]' \"", i, "\"", sep="") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
488 capture <- suppressWarnings(system(cmd, intern=TRUE)) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
489 if (length(capture)>0){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
490 cmd <- paste("perl -i -pe 's/[^[:ascii:]]//g;'",i) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
491 print( paste("WARNING: Non ASCII characters have been removed from the ",i,"file") ) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
492 c <- system(cmd, intern=TRUE) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
493 capture <- "" |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
494 processed <- T |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
495 } |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
496 } |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
497 if (processed) cat("\n\n") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
498 return(processed) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
499 } |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
500 |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
501 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
502 # This function will compute MD5 checksum to check the data integrity |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
503 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr |
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
504 getMd5sum <- function (directory) { |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
505 cat("Compute md5 checksum...\n") |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
506 # WHAT XCMS WILL FIND |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
507 filepattern <- c("[Cc][Dd][Ff]", "[Nn][Cc]", "([Mm][Zz])?[Xx][Mm][Ll]","[Mm][Zz][Dd][Aa][Tt][Aa]", "[Mm][Zz][Mm][Ll]") |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
508 filepattern <- paste(paste("\\.", filepattern, "$", sep=""),collapse="|") |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
509 info <- file.info(directory) |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
510 listed <- list.files(directory[info$isdir], pattern=filepattern, recursive=TRUE, full.names=TRUE) |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
511 files <- c(directory[!info$isdir], listed) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
512 exists <- file.exists(files) |
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
513 files <- files[exists] |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
514 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
515 library(tools) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
516 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
517 #cat("\n\n") |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
518 |
17
602acc32b549
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 22c4e92909198328fc7439ff47e4546a273eb907
lecorguille
parents:
16
diff
changeset
|
519 return(as.matrix(md5sum(files))) |
5
b9a87af62223
planemo upload commit 5a5b747865d7fb76f711bce2d9ce2a0f82a2a374-dirty
lecorguille
parents:
diff
changeset
|
520 } |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
521 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
522 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
523 # This function get the raw file path from the arguments |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
524 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
525 getRawfilePathFromArguments <- function(singlefile, zipfile, args) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
526 if (!is.null(args$zipfile)) zipfile <- args$zipfile |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
527 if (!is.null(args$zipfilePositive)) zipfile <- args$zipfilePositive |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
528 if (!is.null(args$zipfileNegative)) zipfile <- args$zipfileNegative |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
529 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
530 if (!is.null(args$singlefile_galaxyPath)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
531 singlefile_galaxyPaths <- args$singlefile_galaxyPath; |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
532 singlefile_sampleNames <- args$singlefile_sampleName |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
533 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
534 if (!is.null(args$singlefile_galaxyPathPositive)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
535 singlefile_galaxyPaths <- args$singlefile_galaxyPathPositive; |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
536 singlefile_sampleNames <- args$singlefile_sampleNamePositive |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
537 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
538 if (!is.null(args$singlefile_galaxyPathNegative)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
539 singlefile_galaxyPaths <- args$singlefile_galaxyPathNegative; |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
540 singlefile_sampleNames <- args$singlefile_sampleNameNegative |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
541 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
542 if (exists("singlefile_galaxyPaths")){ |
33
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
543 singlefile_galaxyPaths <- unlist(strsplit(singlefile_galaxyPaths,"\\|")) |
c363b9f1caef
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 7b226c3ba91a3cf654ec1c14b3ef85090968bb0f
lecorguille
parents:
32
diff
changeset
|
544 singlefile_sampleNames <- unlist(strsplit(singlefile_sampleNames,"\\|")) |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
545 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
546 singlefile <- NULL |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
547 for (singlefile_galaxyPath_i in seq(1:length(singlefile_galaxyPaths))) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
548 singlefile_galaxyPath <- singlefile_galaxyPaths[singlefile_galaxyPath_i] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
549 singlefile_sampleName <- singlefile_sampleNames[singlefile_galaxyPath_i] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
550 singlefile[[singlefile_sampleName]] <- singlefile_galaxyPath |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
551 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
552 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
553 for (argument in c("zipfile","zipfilePositive","zipfileNegative","singlefile_galaxyPath","singlefile_sampleName","singlefile_galaxyPathPositive","singlefile_sampleNamePositive","singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
554 args[[argument]] <- NULL |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
555 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
556 return(list(zipfile=zipfile, singlefile=singlefile, args=args)) |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
557 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
558 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
559 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
560 # This function retrieve the raw file in the working directory |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
561 # - if zipfile: unzip the file with its directory tree |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
562 # - if singlefiles: set symlink with the good filename |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
563 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
564 retrieveRawfileInTheWorkingDirectory <- function(singlefile, zipfile) { |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
565 if(!is.null(singlefile) && (length("singlefile")>0)) { |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
566 for (singlefile_sampleName in names(singlefile)) { |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
567 singlefile_galaxyPath <- singlefile[[singlefile_sampleName]] |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
568 if(!file.exists(singlefile_galaxyPath)){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
569 error_message <- paste("Cannot access the sample:",singlefile_sampleName,"located:",singlefile_galaxyPath,". Please, contact your administrator ... if you have one!") |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
570 print(error_message); stop(error_message) |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
571 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
572 |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
573 if (!suppressWarnings( try (file.link(singlefile_galaxyPath, singlefile_sampleName), silent=T))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
574 file.copy(singlefile_galaxyPath, singlefile_sampleName) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
575 |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
576 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
577 directory <- "." |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
578 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
579 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
580 if(!is.null(zipfile) && (zipfile != "")) { |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
581 if(!file.exists(zipfile)){ |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
582 error_message <- paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!") |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
583 print(error_message) |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
584 stop(error_message) |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
585 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
586 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
587 #list all file in the zip file |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
588 #zip_files <- unzip(zipfile,list=T)[,"Name"] |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
589 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
590 #unzip |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
591 suppressWarnings(unzip(zipfile, unzip="unzip")) |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
592 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
593 #get the directory name |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
594 suppressWarnings(filesInZip <- unzip(zipfile, list=T)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
595 directories <- unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1]))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
596 directories <- directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
597 directory <- "." |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
598 if (length(directories) == 1) directory <- directories |
24
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
599 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
600 cat("files_root_directory\t",directory,"\n") |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
601 |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
602 } |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
603 return (directory) |
d8915395681f
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit 87dc789d7cd70a3733a1ad0b5a427f4d5905795d
lecorguille
parents:
21
diff
changeset
|
604 } |
32
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
605 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
606 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
607 # This function retrieve a xset like object |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
608 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
609 getxcmsSetObject <- function(xobject) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
610 # XCMS 1.x |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
611 if (class(xobject) == "xcmsSet") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
612 return (xobject) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
613 # XCMS 3.x |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
614 if (class(xobject) == "XCMSnExp") { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
615 # Get the legacy xcmsSet object |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
616 suppressWarnings(xset <- as(xobject, 'xcmsSet')) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
617 sampclass(xset) <- xset@phenoData$sample_group |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
618 return (xset) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
619 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
620 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
621 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
622 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
623 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
624 # https://github.com/sneumann/xcms/issues/250 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
625 groupnamesW4M <- function(xdata, mzdec = 0, rtdec = 0) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
626 mzfmt <- paste("%.", mzdec, "f", sep = "") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
627 rtfmt <- paste("%.", rtdec, "f", sep = "") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
628 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
629 gnames <- paste("M", sprintf(mzfmt, featureDefinitions(xdata)[,"mzmed"]), "T", |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
630 sprintf(rtfmt, featureDefinitions(xdata)[,"rtmed"]), sep = "") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
631 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
632 if (any(dup <- duplicated(gnames))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
633 for (dupname in unique(gnames[dup])) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
634 dupidx <- which(gnames == dupname) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
635 gnames[dupidx] <- paste(gnames[dupidx], seq(along = dupidx), sep = "_") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
636 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
637 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
638 return (gnames) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
639 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
640 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
641 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
642 # https://github.com/sneumann/xcms/issues/247 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
643 .concatenate_XCMSnExp <- function(...) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
644 x <- list(...) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
645 if (length(x) == 0) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
646 return(NULL) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
647 if (length(x) == 1) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
648 return(x[[1]]) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
649 ## Check that all are XCMSnExp objects. |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
650 if (!all(unlist(lapply(x, function(z) is(z, "XCMSnExp"))))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
651 stop("All passed objects should be 'XCMSnExp' objects") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
652 new_x <- as(.concatenate_OnDiskMSnExp(...), "XCMSnExp") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
653 ## If any of the XCMSnExp has alignment results or detected features drop |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
654 ## them! |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
655 x <- lapply(x, function(z) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
656 if (hasAdjustedRtime(z)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
657 z <- dropAdjustedRtime(z) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
658 warning("Adjusted retention times found, had to drop them.") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
659 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
660 if (hasFeatures(z)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
661 z <- dropFeatureDefinitions(z) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
662 warning("Feature definitions found, had to drop them.") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
663 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
664 z |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
665 }) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
666 ## Combine peaks |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
667 fls <- lapply(x, fileNames) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
668 startidx <- cumsum(lengths(fls)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
669 pks <- lapply(x, chromPeaks) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
670 procH <- lapply(x, processHistory) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
671 for (i in 2:length(fls)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
672 pks[[i]][, "sample"] <- pks[[i]][, "sample"] + startidx[i - 1] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
673 procH[[i]] <- lapply(procH[[i]], function(z) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
674 z@fileIndex <- as.integer(z@fileIndex + startidx[i - 1]) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
675 z |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
676 }) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
677 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
678 pks <- do.call(rbind, pks) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
679 new_x@.processHistory <- unlist(procH) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
680 chromPeaks(new_x) <- pks |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
681 if (validObject(new_x)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
682 new_x |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
683 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
684 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
685 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
686 # https://github.com/sneumann/xcms/issues/247 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
687 .concatenate_OnDiskMSnExp <- function(...) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
688 x <- list(...) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
689 if (length(x) == 0) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
690 return(NULL) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
691 if (length(x) == 1) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
692 return(x[[1]]) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
693 ## Check that all are XCMSnExp objects. |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
694 if (!all(unlist(lapply(x, function(z) is(z, "OnDiskMSnExp"))))) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
695 stop("All passed objects should be 'OnDiskMSnExp' objects") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
696 ## Check processingQueue |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
697 procQ <- lapply(x, function(z) z@spectraProcessingQueue) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
698 new_procQ <- procQ[[1]] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
699 is_ok <- unlist(lapply(procQ, function(z) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
700 !is.character(all.equal(new_procQ, z)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
701 )) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
702 if (any(!is_ok)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
703 warning("Processing queues from the submitted objects differ! ", |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
704 "Dropping the processing queue.") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
705 new_procQ <- list() |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
706 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
707 ## processingData |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
708 fls <- lapply(x, function(z) z@processingData@files) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
709 startidx <- cumsum(lengths(fls)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
710 ## featureData |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
711 featd <- lapply(x, fData) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
712 ## Have to update the file index and the spectrum names. |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
713 for (i in 2:length(featd)) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
714 featd[[i]]$fileIdx <- featd[[i]]$fileIdx + startidx[i - 1] |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
715 rownames(featd[[i]]) <- MSnbase:::formatFileSpectrumNames( |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
716 fileIds = featd[[i]]$fileIdx, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
717 spectrumIds = featd[[i]]$spIdx, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
718 nSpectra = nrow(featd[[i]]), |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
719 nFiles = length(unlist(fls)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
720 ) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
721 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
722 featd <- do.call(rbind, featd) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
723 featd$spectrum <- 1:nrow(featd) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
724 ## experimentData |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
725 expdata <- lapply(x, function(z) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
726 ed <- z@experimentData |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
727 data.frame(instrumentManufacturer = ed@instrumentManufacturer, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
728 instrumentModel = ed@instrumentModel, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
729 ionSource = ed@ionSource, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
730 analyser = ed@analyser, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
731 detectorType = ed@detectorType, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
732 stringsAsFactors = FALSE) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
733 }) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
734 expdata <- do.call(rbind, expdata) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
735 expdata <- new("MIAPE", |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
736 instrumentManufacturer = expdata$instrumentManufacturer, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
737 instrumentModel = expdata$instrumentModel, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
738 ionSource = expdata$ionSource, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
739 analyser = expdata$analyser, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
740 detectorType = expdata$detectorType) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
741 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
742 ## protocolData |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
743 protodata <- lapply(x, function(z) z@protocolData) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
744 if (any(unlist(lapply(protodata, nrow)) > 0)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
745 warning("Found non-empty protocol data, but merging protocol data is", |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
746 " currently not supported. Skipped.") |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
747 ## phenoData |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
748 pdata <- do.call(rbind, lapply(x, pData)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
749 res <- new( |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
750 "OnDiskMSnExp", |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
751 phenoData = new("NAnnotatedDataFrame", data = pdata), |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
752 featureData = new("AnnotatedDataFrame", featd), |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
753 processingData = new("MSnProcess", |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
754 processing = paste0("Concatenated [", date(), "]"), |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
755 files = unlist(fls), smoothed = NA), |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
756 experimentData = expdata, |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
757 spectraProcessingQueue = new_procQ) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
758 if (validObject(res)) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
759 res |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
760 } |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
761 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
762 #@TODO: remove this function as soon as we can use xcms 3.x.x from Bioconductor 3.7 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
763 # https://github.com/sneumann/xcms/issues/247 |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
764 c.XCMSnExp <- function(...) { |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
765 .concatenate_XCMSnExp(...) |
2bf1cb023c94
planemo upload for repository https://github.com/workflow4metabolomics/xcms commit e384d6dd5f410799ec211f73bca0b5d5d7bc651e
lecorguille
parents:
31
diff
changeset
|
766 } |