Mercurial > repos > lecorguille > camera_annotate
comparison lib.r @ 23:abf1775ac14d draft
"planemo upload commit c1e276cf53b3c54d4702ab26d4f40a525a720998"
author | workflow4metabolomics |
---|---|
date | Thu, 22 Apr 2021 10:27:38 +0000 |
parents | b979ba5888f7 |
children | 4b9ab71be05e |
comparison
equal
deleted
inserted
replaced
22:01bbba6d57ff | 23:abf1775ac14d |
---|---|
3 #@author G. Le Corguille | 3 #@author G. Le Corguille |
4 # solve an issue with batch if arguments are logical TRUE/FALSE | 4 # solve an issue with batch if arguments are logical TRUE/FALSE |
5 parseCommandArgs <- function(...) { | 5 parseCommandArgs <- function(...) { |
6 args <- batch::parseCommandArgs(...) | 6 args <- batch::parseCommandArgs(...) |
7 for (key in names(args)) { | 7 for (key in names(args)) { |
8 if (args[key] %in% c("TRUE","FALSE")) | 8 if (args[key] %in% c("TRUE", "FALSE")) |
9 args[key] = as.logical(args[key]) | 9 args[key] <- as.logical(args[key]) |
10 } | 10 } |
11 return(args) | 11 return(args) |
12 } | 12 } |
13 | 13 |
14 #@author G. Le Corguille | 14 #@author G. Le Corguille |
15 # This function will | 15 # This function will |
16 # - load the packages | 16 # - load the packages |
17 # - display the sessionInfo | 17 # - display the sessionInfo |
18 loadAndDisplayPackages <- function(pkgs) { | 18 loadAndDisplayPackages <- function(pkgs) { |
19 for(pkg in pkgs) suppressPackageStartupMessages( stopifnot( library(pkg, quietly=TRUE, logical.return=TRUE, character.only=TRUE))) | 19 for (pkg in pkgs) suppressPackageStartupMessages(stopifnot(library(pkg, quietly = TRUE, logical.return = TRUE, character.only = TRUE))) |
20 | 20 |
21 sessioninfo = sessionInfo() | 21 sessioninfo <- sessionInfo() |
22 cat(sessioninfo$R.version$version.string,"\n") | 22 cat(sessioninfo$R.version$version.string, "\n") |
23 cat("Main packages:\n") | 23 cat("Main packages:\n") |
24 for (pkg in names(sessioninfo$otherPkgs)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") | 24 for (pkg in names(sessioninfo$otherPkgs)) { |
25 cat(paste(pkg, packageVersion(pkg)), "\t") | |
26 } | |
27 cat("\n") | |
25 cat("Other loaded packages:\n") | 28 cat("Other loaded packages:\n") |
26 for (pkg in names(sessioninfo$loadedOnly)) { cat(paste(pkg,packageVersion(pkg)),"\t") }; cat("\n") | 29 for (pkg in names(sessioninfo$loadedOnly)) { |
30 cat(paste(pkg, packageVersion(pkg)), "\t") | |
31 } | |
32 cat("\n") | |
27 } | 33 } |
28 | 34 |
29 # This function retrieve a xset like object | 35 # This function retrieve a xset like object |
30 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr | 36 #@author Gildas Le Corguille lecorguille@sb-roscoff.fr |
31 getxcmsSetObject <- function(xobject) { | 37 getxcmsSetObject <- function(xobject) { |
32 # XCMS 1.x | 38 # XCMS 1.x |
33 if (class(xobject) == "xcmsSet") | 39 if (class(xobject) == "xcmsSet") |
34 return (xobject) | 40 return(xobject) |
35 # XCMS 3.x | 41 # XCMS 3.x |
36 if (class(xobject) == "XCMSnExp") { | 42 if (class(xobject) == "XCMSnExp") { |
37 # Get the legacy xcmsSet object | 43 # Get the legacy xcmsSet object |
38 suppressWarnings(xset <- as(xobject, 'xcmsSet')) | 44 suppressWarnings(xset <- as(xobject, "xcmsSet")) |
39 if (is.null(xset@phenoData$sample_group)) | 45 if (is.null(xset@phenoData$sample_group)) |
40 sampclass(xset) = "." | 46 sampclass(xset) <- "." |
41 else | 47 else |
42 sampclass(xset) <- xset@phenoData$sample_group | 48 sampclass(xset) <- xset@phenoData$sample_group |
43 if (!is.null(xset@phenoData$sample_name)) | 49 if (!is.null(xset@phenoData$sample_name)) |
44 rownames(xset@phenoData) = xset@phenoData$sample_name | 50 rownames(xset@phenoData) <- xset@phenoData$sample_name |
45 return (xset) | 51 return(xset) |
46 } | 52 } |
47 } | 53 } |
48 | 54 |
49 #@author G. Le Corguille | 55 #@author G. Le Corguille |
50 #The function create a pdf from the different png generated by diffreport | 56 #The function create a pdf from the different png generated by diffreport |
51 diffreport_png2pdf <- function(filebase) { | 57 diffreport_png2pdf <- function(filebase) { |
52 dir.create("pdf") | 58 dir.create("pdf") |
53 | 59 |
54 pdfEicOutput = paste0("pdf/",filebase,"-eic_pdf.pdf") | 60 pdfEicOutput <- paste0("pdf/", filebase, "-eic_pdf.pdf") |
55 pdfBoxOutput = paste0("pdf/",filebase,"-box_pdf.pdf") | 61 pdfBoxOutput <- paste0("pdf/", filebase, "-box_pdf.pdf") |
56 | 62 |
57 system(paste0("gm convert ",filebase,"_eic/*.png ",pdfEicOutput)) | 63 system(paste0("gm convert ", filebase, "_eic/*.png ", pdfEicOutput)) |
58 system(paste0("gm convert ",filebase,"_box/*.png ",pdfBoxOutput)) | 64 system(paste0("gm convert ", filebase, "_box/*.png ", pdfBoxOutput)) |
59 | 65 |
60 } | 66 } |
61 | 67 |
62 #@author G. Le Corguille | 68 #@author G. Le Corguille |
63 #The function create a zip archive from the different png generated by diffreport | 69 #The function create a zip archive from the different png generated by diffreport |
64 diffreport_png2zip <- function() { | 70 diffreport_png2zip <- function() { |
65 zip("eic.zip", dir(pattern="_eic"), zip=Sys.which("zip")) | 71 zip("eic.zip", dir(pattern = "_eic"), zip = Sys.which("zip")) |
66 zip("box.zip", dir(pattern="_box"), zip=Sys.which("zip")) | 72 zip("box.zip", dir(pattern = "_box"), zip = Sys.which("zip")) |
67 } | 73 } |
68 | 74 |
69 #The function create a zip archive from the different tabular generated by diffreport | 75 #The function create a zip archive from the different tabular generated by diffreport |
70 diffreport_tabular2zip <- function() { | 76 diffreport_tabular2zip <- function() { |
71 zip("tabular.zip", dir(pattern="tabular/*"), zip=Sys.which("zip")) | 77 zip("tabular.zip", dir(pattern = "tabular/*"), zip = Sys.which("zip")) |
72 } | 78 } |
73 | 79 |
74 #@author G. Le Corguille | 80 #@author G. Le Corguille |
75 #This function convert if it is required the Retention Time in minutes | 81 #This function convert if it is required the Retention Time in minutes |
76 RTSecondToMinute <- function(variableMetadata, convertRTMinute) { | 82 RTSecondToMinute <- function(variableMetadata, convertRTMinute) { |
77 if (convertRTMinute){ | 83 if (convertRTMinute) { |
78 #converting the retention times (seconds) into minutes | 84 #converting the retention times (seconds) into minutes |
79 print("converting the retention times into minutes in the variableMetadata") | 85 print("converting the retention times into minutes in the variableMetadata") |
80 variableMetadata[,"rt"]=variableMetadata[,"rt"]/60 | 86 variableMetadata[, "rt"] <- variableMetadata[, "rt"] / 60 |
81 variableMetadata[,"rtmin"]=variableMetadata[,"rtmin"]/60 | 87 variableMetadata[, "rtmin"] <- variableMetadata[, "rtmin"] / 60 |
82 variableMetadata[,"rtmax"]=variableMetadata[,"rtmax"]/60 | 88 variableMetadata[, "rtmax"] <- variableMetadata[, "rtmax"] / 60 |
83 } | 89 } |
84 return (variableMetadata) | 90 return(variableMetadata) |
85 } | 91 } |
86 | 92 |
87 #@author G. Le Corguille | 93 #@author G. Le Corguille |
88 #This function format ions identifiers | 94 #This function format ions identifiers |
89 formatIonIdentifiers <- function(variableMetadata, numDigitsRT=0, numDigitsMZ=0) { | 95 formatIonIdentifiers <- function(variableMetadata, numDigitsRT = 0, numDigitsMZ = 0) { |
90 splitDeco = strsplit(as.character(variableMetadata$name),"_") | 96 splitDeco <- strsplit(as.character(variableMetadata$name), "_") |
91 idsDeco = sapply(splitDeco, function(x) { deco=unlist(x)[2]; if (is.na(deco)) return ("") else return(paste0("_",deco)) }) | 97 idsDeco <- sapply(splitDeco, function(x) { |
92 namecustom = make.unique(paste0("M",round(variableMetadata[,"mz"],numDigitsMZ),"T",round(variableMetadata[,"rt"],numDigitsRT),idsDeco)) | 98 deco <- unlist(x)[2]; if (is.na(deco)) return("") else return(paste0("_", deco)) |
93 variableMetadata=cbind(name=variableMetadata$name, namecustom=namecustom, variableMetadata[,!(colnames(variableMetadata) %in% c("name"))]) | 99 }) |
100 namecustom <- make.unique(paste0("M", round(variableMetadata[, "mz"], numDigitsMZ), "T", round(variableMetadata[, "rt"], numDigitsRT), idsDeco)) | |
101 variableMetadata <- cbind(name = variableMetadata$name, namecustom = namecustom, variableMetadata[, !(colnames(variableMetadata) %in% c("name"))]) | |
94 return(variableMetadata) | 102 return(variableMetadata) |
95 } | 103 } |
96 | 104 |
97 #The function annotateDiffreport without the corr function which bugs | 105 #The function annotateDiffreport without the corr function which bugs |
98 annotatediff <- function(xset=xset, args=args, variableMetadataOutput="variableMetadata.tsv") { | 106 annotatediff <- function(xset = xset, args = args, variableMetadataOutput = "variableMetadata.tsv") { |
99 # Resolve the bug with x11, with the function png | 107 # Resolve the bug with x11, with the function png |
100 options(bitmapType='cairo') | 108 options(bitmapType = "cairo") |
101 | 109 |
102 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. | 110 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. |
103 res=try(is.null(xset@filled)) | 111 res <- try(is.null(xset@filled)) |
104 | 112 |
105 # ------ annot ------- | 113 # ------ annot ------- |
106 args$calcCiS=as.logical(args$calcCiS) | 114 args$calcCiS <- as.logical(args$calcCiS) |
107 args$calcIso=as.logical(args$calcIso) | 115 args$calcIso <- as.logical(args$calcIso) |
108 args$calcCaS=as.logical(args$calcCaS) | 116 args$calcCaS <- as.logical(args$calcCaS) |
109 | 117 |
110 # common parameters | 118 # common parameters |
111 args4annotate = list(object=xset, | 119 args4annotate <- list(object = xset, |
112 nSlaves=args$nSlaves,sigma=args$sigma,perfwhm=args$perfwhm, | 120 nSlaves = args$nSlaves, sigma = args$sigma, perfwhm = args$perfwhm, |
113 maxcharge=args$maxcharge,maxiso=args$maxiso,minfrac=args$minfrac, | 121 maxcharge = args$maxcharge, maxiso = args$maxiso, minfrac = args$minfrac, |
114 ppm=args$ppm,mzabs=args$mzabs,quick=args$quick, | 122 ppm = args$ppm, mzabs = args$mzabs, quick = args$quick, |
115 polarity=args$polarity,max_peaks=args$max_peaks,intval=args$intval) | 123 polarity = args$polarity, max_peaks = args$max_peaks, intval = args$intval) |
116 | 124 |
117 # quick == FALSE | 125 if (args$quick == FALSE) { |
118 if(args$quick==FALSE) { | 126 args4annotate <- append(args4annotate, |
119 args4annotate = append(args4annotate, | 127 list(graphMethod = args$graphMethod, cor_eic_th = args$cor_eic_th, pval = args$pval, |
120 list(graphMethod=args$graphMethod,cor_eic_th=args$cor_eic_th,pval=args$pval, | 128 calcCiS = args$calcCiS, calcIso = args$calcIso, calcCaS = args$calcCaS)) |
121 calcCiS=args$calcCiS,calcIso=args$calcIso,calcCaS=args$calcCaS)) | |
122 # no ruleset | 129 # no ruleset |
123 if (!is.null(args$multiplier)) { | 130 if (!is.null(args$multiplier)) { |
124 args4annotate = append(args4annotate, | 131 args4annotate <- append(args4annotate, |
125 list(multiplier=args$multiplier)) | 132 list(multiplier = args$multiplier)) |
126 } | 133 } |
127 # ruleset | 134 # ruleset |
128 else { | 135 else { |
129 rulset=read.table(args$rules, h=T, sep=";") | 136 rulset <- read.table(args$rules, h = T, sep = ";") |
130 if (ncol(rulset) < 4) rulset=read.table(args$rules, h=T, sep="\t") | 137 if (ncol(rulset) < 4) rulset <- read.table(args$rules, h = T, sep = "\t") |
131 if (ncol(rulset) < 4) rulset=read.table(args$rules, h=T, sep=",") | 138 if (ncol(rulset) < 4) rulset <- read.table(args$rules, h = T, sep = ",") |
132 if (ncol(rulset) < 4) { | 139 if (ncol(rulset) < 4) { |
133 error_message="Your ruleset file seems not well formatted. The column separators accepted are ; , and tabulation" | 140 error_message <- "Your ruleset file seems not well formatted. The column separators accepted are ; , and tabulation" |
134 print(error_message) | 141 print(error_message) |
135 stop(error_message) | 142 stop(error_message) |
136 } | 143 } |
137 | 144 |
138 args4annotate = append(args4annotate, | 145 args4annotate <- append(args4annotate, |
139 list(rules=rulset)) | 146 list(rules = rulset)) |
140 } | 147 } |
141 } | 148 } |
142 | 149 |
143 | 150 |
144 # launch annotate | 151 # launch annotate |
145 xa = do.call("annotate", args4annotate) | 152 xa <- do.call("annotate", args4annotate) |
146 peakList=getPeaklist(xa,intval=args$intval) | 153 peakList <- getPeaklist(xa, intval = args$intval) |
147 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); | 154 peakList <- cbind(groupnames(xa@xcmsSet), peakList); colnames(peakList)[1] <- c("name"); |
148 | 155 |
149 # --- Multi condition : diffreport --- | 156 # --- Multi condition : diffreport --- |
150 diffrepOri=NULL | 157 diffrepOri <- NULL |
151 if (!is.null(args$runDiffreport) & nlevels(sampclass(xset))>=2) { | 158 if (!is.null(args$runDiffreport) & nlevels(sampclass(xset)) >= 2) { |
152 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. | 159 #Check if the fillpeaks step has been done previously, if it hasn't, there is an error message and the execution is stopped. |
153 res=try(is.null(xset@filled)) | 160 res <- try(is.null(xset@filled)) |
154 classes=levels(sampclass(xset)) | 161 classes <- levels(sampclass(xset)) |
155 x=1:(length(classes)-1) | 162 x <- 1:(length(classes) - 1) |
156 for (i in seq(along=x) ) { | 163 for (i in seq(along = x)) { |
157 y=1:(length(classes)) | 164 y <- 1:(length(classes)) |
158 for (n in seq(along=y)){ | 165 for (n in seq(along = y)) { |
159 if(i+n <= length(classes)){ | 166 if (i + n <= length(classes)) { |
160 filebase=paste(classes[i],class2=classes[i+n],sep="-vs-") | 167 filebase <- paste(classes[i], class2 = classes[i + n], sep = "-vs-") |
161 | 168 |
162 diffrep=diffreport( | 169 diffrep <- diffreport( |
163 object=xset,class1=classes[i],class2=classes[i+n], | 170 object = xset, class1 = classes[i], class2 = classes[i + n], |
164 filebase=filebase,eicmax=args$eicmax,eicwidth=args$eicwidth, | 171 filebase = filebase, eicmax = args$eicmax, eicwidth = args$eicwidth, |
165 sortpval=TRUE,value=args$value,h=args$h,w=args$w,mzdec=args$mzdec,missing=0) | 172 sortpval = TRUE, value = args$value, h = args$h, w = args$w, mzdec = args$mzdec, missing = 0) |
166 | 173 |
167 diffrepOri = diffrep | 174 diffrepOri <- diffrep |
168 | 175 |
169 # renamming of the column rtmed to rt to fit with camera peaklist function output | 176 # renamming of the column rtmed to rt to fit with camera peaklist function output |
170 colnames(diffrep)[colnames(diffrep)=="rtmed"] <- "rt" | 177 colnames(diffrep)[colnames(diffrep) == "rtmed"] <- "rt" |
171 colnames(diffrep)[colnames(diffrep)=="mzmed"] <- "mz" | 178 colnames(diffrep)[colnames(diffrep) == "mzmed"] <- "mz" |
172 | 179 |
173 # combines results and reorder columns | 180 # combines results and reorder columns |
174 diffrep = merge(peakList, diffrep[,c("name","fold","tstat","pvalue")], by.x="name", by.y="name", sort=F) | 181 diffrep <- merge(peakList, diffrep[, c("name", "fold", "tstat", "pvalue")], by.x = "name", by.y = "name", sort = F) |
175 diffrep = cbind(diffrep[,!(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))],diffrep[,(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))]) | 182 diffrep <- cbind(diffrep[, !(colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))], diffrep[, (colnames(diffrep) %in% c(sampnames(xa@xcmsSet)))]) |
176 | 183 |
177 diffrep = RTSecondToMinute(diffrep, args$convertRTMinute) | 184 diffrep <- RTSecondToMinute(diffrep, args$convertRTMinute) |
178 diffrep = formatIonIdentifiers(diffrep, numDigitsRT=args$numDigitsRT, numDigitsMZ=args$numDigitsMZ) | 185 diffrep <- formatIonIdentifiers(diffrep, numDigitsRT = args$numDigitsRT, numDigitsMZ = args$numDigitsMZ) |
179 | 186 |
180 if(args$sortpval){ | 187 if (args$sortpval) { |
181 diffrep=diffrep[order(diffrep$pvalue), ] | 188 diffrep <- diffrep[order(diffrep$pvalue), ] |
182 } | 189 } |
183 | 190 |
184 dir.create("tabular", showWarnings = FALSE) | 191 dir.create("tabular", showWarnings = FALSE) |
185 write.table(diffrep, sep="\t", quote=FALSE, row.names=FALSE, file=paste("tabular/",filebase,"_tsv.tabular",sep="")) | 192 write.table(diffrep, sep = "\t", quote = FALSE, row.names = FALSE, file = paste("tabular/", filebase, "_tsv.tabular", sep = "")) |
186 | 193 |
187 if (args$eicmax != 0) { | 194 if (args$eicmax != 0) { |
188 if (args$png2 == "pdf") | 195 if (args$png2 == "pdf") |
189 diffreport_png2pdf(filebase) | 196 diffreport_png2pdf(filebase) |
190 if (args$png2 == "zip") | 197 if (args$png2 == "zip") |
196 if (args$tabular2 == "zip") | 203 if (args$tabular2 == "zip") |
197 diffreport_tabular2zip() | 204 diffreport_tabular2zip() |
198 } | 205 } |
199 | 206 |
200 # --- variableMetadata --- | 207 # --- variableMetadata --- |
201 variableMetadata=peakList[,!(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] | 208 variableMetadata <- peakList[, !(make.names(colnames(peakList)) %in% c(make.names(sampnames(xa@xcmsSet))))] |
202 variableMetadata = RTSecondToMinute(variableMetadata, args$convertRTMinute) | 209 variableMetadata <- RTSecondToMinute(variableMetadata, args$convertRTMinute) |
203 variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=args$numDigitsRT, numDigitsMZ=args$numDigitsMZ) | 210 variableMetadata <- formatIonIdentifiers(variableMetadata, numDigitsRT = args$numDigitsRT, numDigitsMZ = args$numDigitsMZ) |
204 # if we have 2 conditions, we keep stat of diffrep | 211 # if we have 2 conditions, we keep stat of diffrep |
205 if (!is.null(args$runDiffreport) & nlevels(sampclass(xset))==2) { | 212 if (!is.null(args$runDiffreport) & nlevels(sampclass(xset)) == 2) { |
206 variableMetadata = merge(variableMetadata, diffrep[,c("name","fold","tstat","pvalue")],by.x="name", by.y="name", sort=F) | 213 variableMetadata <- merge(variableMetadata, diffrep[, c("name", "fold", "tstat", "pvalue")], by.x = "name", by.y = "name", sort = F) |
207 if(exists("args[[\"sortpval\"]]")){ | 214 if (exists("args[[\"sortpval\"]]")) { |
208 variableMetadata=variableMetadata[order(variableMetadata$pvalue), ] | 215 variableMetadata <- variableMetadata[order(variableMetadata$pvalue), ] |
209 } | 216 } |
210 } | 217 } |
211 | 218 |
212 variableMetadataOri=variableMetadata | 219 variableMetadataOri <- variableMetadata |
213 write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) | 220 write.table(variableMetadata, sep = "\t", quote = FALSE, row.names = FALSE, file = variableMetadataOutput) |
214 | 221 |
215 return(list("xa"=xa,"diffrep"=diffrepOri,"variableMetadata"=variableMetadataOri)); | 222 return(list("xa" = xa, "diffrep" = diffrepOri, "variableMetadata" = variableMetadataOri)); |
216 | 223 |
217 } | 224 } |
218 | 225 |
219 | 226 |
220 combinexsAnnos_function <- function(xaP, xaN, diffrepP=NULL,diffrepN=NULL, | 227 combinexsAnnos_function <- function(xaP, xaN, diffrepP = NULL, diffrepN = NULL, |
221 pos=TRUE,tol=2,ruleset=NULL,keep_meta=TRUE, convertRTMinute=F, numDigitsMZ=0, | 228 pos = TRUE, tol = 2, ruleset = NULL, keep_meta = TRUE, convertRTMinute = F, numDigitsMZ = 0, |
222 numDigitsRT=0, variableMetadataOutput="variableMetadata.tsv"){ | 229 numDigitsRT = 0, variableMetadataOutput = "variableMetadata.tsv") { |
223 | 230 |
224 #Load the two Rdata to extract the xset objects from positive and negative mode | 231 #Load the two Rdata to extract the xset objects from positive and negative mode |
225 cat("\tObject xset from positive mode\n") | 232 cat("\tObject xset from positive mode\n") |
226 print(xaP) | 233 print(xaP) |
227 cat("\n") | 234 cat("\n") |
231 cat("\n") | 238 cat("\n") |
232 | 239 |
233 cat("\n") | 240 cat("\n") |
234 cat("\tCombining...\n") | 241 cat("\tCombining...\n") |
235 #Convert the string to numeric for creating matrix | 242 #Convert the string to numeric for creating matrix |
236 row=as.numeric(strsplit(ruleset,",")[[1]][1]) | 243 row <- as.numeric(strsplit(ruleset, ",")[[1]][1]) |
237 column=as.numeric(strsplit(ruleset,",")[[1]][2]) | 244 column <- as.numeric(strsplit(ruleset, ",")[[1]][2]) |
238 ruleset=cbind(row,column) | 245 ruleset <- cbind(row, column) |
239 #Test if the file comes from an older version tool | 246 #Test if the file comes from an older version tool |
240 if ((!is.null(xaP)) & (!is.null(xaN))) { | 247 if ((!is.null(xaP)) & (!is.null(xaN))) { |
241 #Launch the combinexsannos function from CAMERA | 248 #Launch the combinexsannos function from CAMERA |
242 cAnnot=combinexsAnnos(xaP, xaN,pos=pos,tol=tol,ruleset=ruleset) | 249 cAnnot <- combinexsAnnos(xaP, xaN, pos = pos, tol = tol, ruleset = ruleset) |
243 } else { | 250 } else { |
244 stop("You must relauch the CAMERA.annotate step with the lastest version.") | 251 stop("You must relauch the CAMERA.annotate step with the lastest version.") |
245 } | 252 } |
246 | 253 |
247 if(pos){ | 254 if (pos) { |
248 xa=xaP | 255 xa <- xaP |
249 mode="neg. Mode" | 256 mode <- "neg. Mode" |
250 } else { | 257 } else { |
251 xa=xaN | 258 xa <- xaN |
252 mode="pos. Mode" | 259 mode <- "pos. Mode" |
253 } | 260 } |
254 | 261 |
255 peakList=getPeaklist(xa) | 262 peakList <- getPeaklist(xa) |
256 peakList=cbind(groupnames(xa@xcmsSet),peakList); colnames(peakList)[1] = c("name"); | 263 peakList <- cbind(groupnames(xa@xcmsSet), peakList); colnames(peakList)[1] <- c("name"); |
257 variableMetadata=cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup",mode)]); | 264 variableMetadata <- cbind(peakList, cAnnot[, c("isotopes", "adduct", "pcgroup", mode)]); |
258 variableMetadata=variableMetadata[,!(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))] | 265 variableMetadata <- variableMetadata[, !(colnames(variableMetadata) %in% c(sampnames(xa@xcmsSet)))] |
259 | 266 |
260 #Test if there are more than two classes (conditions) | 267 #Test if there are more than two classes (conditions) |
261 if ( nlevels(sampclass(xaP@xcmsSet))==2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) { | 268 if (nlevels(sampclass(xaP@xcmsSet)) == 2 & (!is.null(diffrepN)) & (!is.null(diffrepP))) { |
262 diffrepP = diffrepP[,c("name","fold","tstat","pvalue")]; colnames(diffrepP) = paste("P.",colnames(diffrepP),sep="") | 269 diffrepP <- diffrepP[, c("name", "fold", "tstat", "pvalue")]; colnames(diffrepP) <- paste("P.", colnames(diffrepP), sep = "") |
263 diffrepN = diffrepN[,c("name","fold","tstat","pvalue")]; colnames(diffrepN) = paste("N.",colnames(diffrepN),sep="") | 270 diffrepN <- diffrepN[, c("name", "fold", "tstat", "pvalue")]; colnames(diffrepN) <- paste("N.", colnames(diffrepN), sep = "") |
264 | 271 |
265 variableMetadata = merge(variableMetadata, diffrepP, by.x="name", by.y="P.name") | 272 variableMetadata <- merge(variableMetadata, diffrepP, by.x = "name", by.y = "P.name") |
266 variableMetadata = merge(variableMetadata, diffrepN, by.x="name", by.y="N.name") | 273 variableMetadata <- merge(variableMetadata, diffrepN, by.x = "name", by.y = "N.name") |
267 } | 274 } |
268 | 275 |
269 rownames(variableMetadata) = NULL | 276 rownames(variableMetadata) <- NULL |
270 #TODO: checker | 277 #TODO: checker colnames(variableMetadata)[1:2] = c("name", "mz/rt"); |
271 #colnames(variableMetadata)[1:2] = c("name","mz/rt"); | 278 |
272 | 279 variableMetadata <- RTSecondToMinute(variableMetadata, convertRTMinute) |
273 variableMetadata = RTSecondToMinute(variableMetadata, convertRTMinute) | 280 variableMetadata <- formatIonIdentifiers(variableMetadata, numDigitsRT = numDigitsRT, numDigitsMZ = numDigitsMZ) |
274 variableMetadata = formatIonIdentifiers(variableMetadata, numDigitsRT=numDigitsRT, numDigitsMZ=numDigitsMZ) | |
275 | 281 |
276 #If the user want to keep only the metabolites which match a difference | 282 #If the user want to keep only the metabolites which match a difference |
277 if(keep_meta){ | 283 if (keep_meta) { |
278 variableMetadata=variableMetadata[variableMetadata[,c(mode)]!="",] | 284 variableMetadata <- variableMetadata[variableMetadata[, c(mode)] != "", ] |
279 } | 285 } |
280 | 286 |
281 #Write the output into a tsv file | 287 #Write the output into a tsv file |
282 write.table(variableMetadata, sep="\t", quote=FALSE, row.names=FALSE, file=variableMetadataOutput) | 288 write.table(variableMetadata, sep = "\t", quote = FALSE, row.names = FALSE, file = variableMetadataOutput) |
283 return(variableMetadata); | 289 return(variableMetadata); |
284 | 290 |
285 } | 291 } |
286 | 292 |
287 # This function get the raw file path from the arguments | 293 # This function get the raw file path from the arguments |
288 getRawfilePathFromArguments <- function(singlefile, zipfile, args) { | 294 getRawfilePathFromArguments <- function(singlefile, zipfile, args) { |
289 if (!is.null(args$zipfile)) zipfile = args$zipfile | 295 if (!is.null(args$zipfile)) zipfile <- args$zipfile |
290 if (!is.null(args$zipfilePositive)) zipfile = args$zipfilePositive | 296 if (!is.null(args$zipfilePositive)) zipfile <- args$zipfilePositive |
291 if (!is.null(args$zipfileNegative)) zipfile = args$zipfileNegative | 297 if (!is.null(args$zipfileNegative)) zipfile <- args$zipfileNegative |
292 | 298 |
293 if (!is.null(args$singlefile_galaxyPath)) { | 299 if (!is.null(args$singlefile_galaxyPath)) { |
294 singlefile_galaxyPaths = args$singlefile_galaxyPath; | 300 singlefile_galaxyPaths <- args$singlefile_galaxyPath; |
295 singlefile_sampleNames = args$singlefile_sampleName | 301 singlefile_sampleNames <- args$singlefile_sampleName |
296 } | 302 } |
297 if (!is.null(args$singlefile_galaxyPathPositive)) { | 303 if (!is.null(args$singlefile_galaxyPathPositive)) { |
298 singlefile_galaxyPaths = args$singlefile_galaxyPathPositive; | 304 singlefile_galaxyPaths <- args$singlefile_galaxyPathPositive; |
299 singlefile_sampleNames = args$singlefile_sampleNamePositive | 305 singlefile_sampleNames <- args$singlefile_sampleNamePositive |
300 } | 306 } |
301 if (!is.null(args$singlefile_galaxyPathNegative)) { | 307 if (!is.null(args$singlefile_galaxyPathNegative)) { |
302 singlefile_galaxyPaths = args$singlefile_galaxyPathNegative; | 308 singlefile_galaxyPaths <- args$singlefile_galaxyPathNegative; |
303 singlefile_sampleNames = args$singlefile_sampleNameNegative | 309 singlefile_sampleNames <- args$singlefile_sampleNameNegative |
304 } | 310 } |
305 if (exists("singlefile_galaxyPaths")){ | 311 if (exists("singlefile_galaxyPaths")) { |
306 singlefile_galaxyPaths = unlist(strsplit(singlefile_galaxyPaths,",")) | 312 singlefile_galaxyPaths <- unlist(strsplit(singlefile_galaxyPaths, ",")) |
307 singlefile_sampleNames = unlist(strsplit(singlefile_sampleNames,",")) | 313 singlefile_sampleNames <- unlist(strsplit(singlefile_sampleNames, ",")) |
308 | 314 |
309 singlefile=NULL | 315 singlefile <- NULL |
310 for (singlefile_galaxyPath_i in seq(1:length(singlefile_galaxyPaths))) { | 316 for (singlefile_galaxyPath_i in seq_len(length(singlefile_galaxyPaths))) { |
311 singlefile_galaxyPath=singlefile_galaxyPaths[singlefile_galaxyPath_i] | 317 singlefile_galaxyPath <- singlefile_galaxyPaths[singlefile_galaxyPath_i] |
312 singlefile_sampleName=singlefile_sampleNames[singlefile_galaxyPath_i] | 318 singlefile_sampleName <- singlefile_sampleNames[singlefile_galaxyPath_i] |
313 singlefile[[singlefile_sampleName]] = singlefile_galaxyPath | 319 singlefile[[singlefile_sampleName]] <- singlefile_galaxyPath |
314 } | 320 } |
315 } | 321 } |
316 for (argument in c("zipfile", "zipfilePositive", "zipfileNegative", | 322 for (argument in c("zipfile", "zipfilePositive", "zipfileNegative", |
317 "singlefile_galaxyPath", "singlefile_sampleName", | 323 "singlefile_galaxyPath", "singlefile_sampleName", |
318 "singlefile_galaxyPathPositive", "singlefile_sampleNamePositive", | 324 "singlefile_galaxyPathPositive", "singlefile_sampleNamePositive", |
319 "singlefile_galaxyPathNegative","singlefile_sampleNameNegative")) { | 325 "singlefile_galaxyPathNegative", "singlefile_sampleNameNegative")) { |
320 args[[argument]]=NULL | 326 args[[argument]] <- NULL |
321 } | 327 } |
322 return(list(zipfile=zipfile, singlefile=singlefile, args=args)) | 328 return(list(zipfile = zipfile, singlefile = singlefile, args = args)) |
323 } | 329 } |
324 | 330 |
325 | 331 |
326 # This function retrieve the raw file in the working directory | 332 # This function retrieve the raw file in the working directory |
327 # - if zipfile: unzip the file with its directory tree | 333 # - if zipfile: unzip the file with its directory tree |
328 # - if singlefiles: set symlink with the good filename | 334 # - if singlefiles: set symlink with the good filename |
329 retrieveRawfileInTheWorkingDirectory <- function(singlefile, zipfile) { | 335 retrieveRawfileInTheWorkingDir <- function(singlefile, zipfile) { |
330 if(!is.null(singlefile) && (length("singlefile")>0)) { | 336 if (!is.null(singlefile) && (length("singlefile") > 0)) { |
331 for (singlefile_sampleName in names(singlefile)) { | 337 for (singlefile_sampleName in names(singlefile)) { |
332 singlefile_galaxyPath = singlefile[[singlefile_sampleName]] | 338 singlefile_galaxyPath <- singlefile[[singlefile_sampleName]] |
333 if(!file.exists(singlefile_galaxyPath)){ | 339 if (!file.exists(singlefile_galaxyPath)) { |
334 error_message=paste("Cannot access the sample:",singlefile_sampleName,"located:",singlefile_galaxyPath,". Please, contact your administrator ... if you have one!") | 340 error_message <- paste("Cannot access the sample:", singlefile_sampleName, "located:", singlefile_galaxyPath, ". Please, contact your administrator ... if you have one!") |
335 print(error_message); stop(error_message) | 341 print(error_message); stop(error_message) |
336 } | 342 } |
337 | 343 |
338 file.symlink(singlefile_galaxyPath,singlefile_sampleName) | 344 file.symlink(singlefile_galaxyPath, singlefile_sampleName) |
339 } | 345 } |
340 directory = "." | 346 directory <- "." |
341 | 347 |
342 } | 348 } |
343 if(!is.null(zipfile) && (zipfile!="")) { | 349 if (!is.null(zipfile) && (zipfile != "")) { |
344 if(!file.exists(zipfile)){ | 350 if (!file.exists(zipfile)) { |
345 error_message=paste("Cannot access the Zip file:",zipfile,". Please, contact your administrator ... if you have one!") | 351 error_message <- paste("Cannot access the Zip file:", zipfile, ". Please, contact your administrator ... if you have one!") |
346 print(error_message) | 352 print(error_message) |
347 stop(error_message) | 353 stop(error_message) |
348 } | 354 } |
349 | 355 |
350 #list all file in the zip file | |
351 #zip_files=unzip(zipfile,list=T)[,"Name"] | |
352 | |
353 #unzip | 356 #unzip |
354 suppressWarnings(unzip(zipfile, unzip="unzip")) | 357 suppressWarnings(unzip(zipfile, unzip = "unzip")) |
355 | 358 |
356 #get the directory name | 359 #get the directory name |
357 filesInZip=unzip(zipfile, list=T); | 360 filesInZip <- unzip(zipfile, list = T); |
358 directories=unique(unlist(lapply(strsplit(filesInZip$Name,"/"), function(x) x[1]))); | 361 directories <- unique(unlist(lapply(strsplit(filesInZip$Name, "/"), function(x) x[1]))); |
359 directories=directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] | 362 directories <- directories[!(directories %in% c("__MACOSX")) & file.info(directories)$isdir] |
360 directory = "." | 363 directory <- "." |
361 if (length(directories) == 1) directory = directories | 364 if (length(directories) == 1) directory <- directories |
362 | 365 |
363 cat("files_root_directory\t",directory,"\n") | 366 cat("files_root_directory\t", directory, "\n") |
364 | 367 |
365 } | 368 } |
366 return (directory) | 369 return(directory) |
367 } | 370 } |
368 |