Skip to content
Snippets Groups Projects
Commit 8087a4a7 authored by Michele Stravs's avatar Michele Stravs
Browse files

Refactoring: Vignette working until step 2

parent 27687857
No related branches found
No related tags found
No related merge requests found
...@@ -26,7 +26,7 @@ SystemRequirements: OpenBabel ...@@ -26,7 +26,7 @@ SystemRequirements: OpenBabel
biocViews: Bioinformatics, MassSpectrometry, Metabolomics, Software biocViews: Bioinformatics, MassSpectrometry, Metabolomics, Software
Depends: Rcpp Depends: Rcpp
Imports: Imports:
XML,RCurl,rjson, rcdk,yaml,mzR,methods,Biobase,MSnbase XML,RCurl,rjson, rcdk,yaml,mzR,methods,Biobase,MSnbase,S4Vectors
Suggests: Suggests:
gplots,RMassBankData, gplots,RMassBankData,
xcms (>= 1.37.1), xcms (>= 1.37.1),
......
...@@ -339,6 +339,6 @@ ppm <- function(mass, dppm, l=FALSE, p=FALSE) ...@@ -339,6 +339,6 @@ ppm <- function(mass, dppm, l=FALSE, p=FALSE)
} }
## # auxiliaries ## # auxiliaries
## emass <- 0.0005485799 .emass <- 0.0005485799
## pmass <- 1.007276565 ## pmass <- 1.007276565
## hmass <- 1.007825 ## hmass <- 1.007825
...@@ -95,7 +95,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec ...@@ -95,7 +95,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec
nProg <- 0 nProg <- 0
message("msmsWorkflow: Step 1. Acquire all MSMS spectra from files") message("msmsWorkflow: Step 1. Acquire all MSMS spectra from files")
pb <- do.call(progressbar, list(object=NULL, value=0, min=0, max=nLen)) pb <- do.call(progressbar, list(object=NULL, value=0, min=0, max=nLen))
w@spectra <- lapply(w@files, function(fileName) { w@spectra <- as(lapply(w@files, function(fileName) {
# Find compound ID # Find compound ID
splitfn <- strsplit(fileName,'_') splitfn <- strsplit(fileName,'_')
...@@ -115,7 +115,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec ...@@ -115,7 +115,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec
pb <- do.call(progressbar, list(object=pb, value= nProg)) pb <- do.call(progressbar, list(object=pb, value= nProg))
return(spec) return(spec)
} ) } ), "SimpleList")
names(w@spectra) <- basename(as.character(w@files)) names(w@spectra) <- basename(as.character(w@files))
# close progress bar # close progress bar
do.call(progressbar, list(object=pb, close=TRUE)) do.call(progressbar, list(object=pb, close=TRUE))
...@@ -176,7 +176,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec ...@@ -176,7 +176,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec
nProg <- 0 nProg <- 0
message("msmsWorkflow: Step 2. First analysis pre recalibration") message("msmsWorkflow: Step 2. First analysis pre recalibration")
pb <- do.call(progressbar, list(object=NULL, value=0, min=0, max=nLen)) pb <- do.call(progressbar, list(object=NULL, value=0, min=0, max=nLen))
w@spectra <- lapply(w@spectra, function(spec) { w@spectra <- as(lapply(w@spectra, function(spec) {
#print(spec$id) #print(spec$id)
s <- analyzeMsMs(spec, mode=mode, detail=TRUE, run="preliminary", s <- analyzeMsMs(spec, mode=mode, detail=TRUE, run="preliminary",
filterSettings = settings$filterSettings, filterSettings = settings$filterSettings,
...@@ -186,7 +186,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec ...@@ -186,7 +186,7 @@ msmsWorkflow <- function(w, mode="pH", steps=c(1:8), confirmMode = FALSE, newRec
pb <- do.call(progressbar, list(object=pb, value= nProg)) pb <- do.call(progressbar, list(object=pb, value= nProg))
return(s) return(s)
}) }), "SimpleList")
for(f in w@files) for(f in w@files)
w@spectra[[basename(as.character(f))]]@name <- basename(as.character(f)) w@spectra[[basename(as.character(f))]]@name <- basename(as.character(f))
do.call(progressbar, list(object=pb, close=TRUE)) do.call(progressbar, list(object=pb, close=TRUE))
...@@ -705,21 +705,26 @@ analyzeMsMs.formula <- function(msmsPeaks, mode="pH", detail=FALSE, run="prelimi ...@@ -705,21 +705,26 @@ analyzeMsMs.formula <- function(msmsPeaks, mode="pH", detail=FALSE, run="prelimi
childPeaksFilt <- filterLowaccResults(childPeaks, filterMode, filterSettings) childPeaksFilt <- filterLowaccResults(childPeaks, filterMode, filterSettings)
childPeaksGood <- childPeaksFilt[["TRUE"]] childPeaksGood <- childPeaksFilt[["TRUE"]]
childPeaksBad <- childPeaksFilt[["FALSE"]] childPeaksBad <- childPeaksFilt[["FALSE"]]
if(is.null(childPeaksGood))
childPeaksGood <- childPeaks[c(),,drop=FALSE]
if(is.null(childPeaksBad))
childPeaksBad <- childPeaks[c(),,drop=FALSE]
childPeaksUnassigned <- childPeaks[is.na(childPeaks$dppm),,drop=FALSE] childPeaksUnassigned <- childPeaks[is.na(childPeaks$dppm),,drop=FALSE]
childPeaksUnassigned$good <- FALSE childPeaksUnassigned$good <- rep(FALSE, nrow(childPeaksUnassigned))
# count formulas within new limits # count formulas within new limits
# (the results of the "old" count stay in childPeaksInt and are returned # (the results of the "old" count stay in childPeaksInt and are returned
# in $childPeaks) # in $childPeaks)
if(!is.null(childPeaksGood)) countFormulasTab <- xtabs( ~formula + mz, data=childPeaksGood)
{ countFormulas <- colSums(countFormulasTab)
countFormulasTab <- xtabs( ~formula + mz, data=childPeaksGood) childPeaksGood$formulaCount <- countFormulas[as.character(childPeaksGood$mz)]
countFormulas <- colSums(countFormulasTab)
childPeaksGood$formulaCount <- countFormulas[as.character(childPeaksGood$mz)] childPeaksUnassigned$formulaCount <- rep(NA, nrow(childPeaksUnassigned))
} childPeaksBad$formulaCount <- rep(NA, nrow(childPeaksBad))
childPeaksUnassigned$formulaCount <- NA childPeaksBad$good <- rep(FALSE, nrow(childPeaksBad))
childPeaksBad$formulaCount <- NA
# Now: childPeaksGood (containing the new, recounted peaks with good = TRUE), and childPeaksBad (containing the # Now: childPeaksGood (containing the new, recounted peaks with good = TRUE), and childPeaksBad (containing the
# peaks with good=FALSE, i.e. outside filter criteria, with the old formula count even though it is worthless) # peaks with good=FALSE, i.e. outside filter criteria, with the old formula count even though it is worthless)
...@@ -732,18 +737,18 @@ analyzeMsMs.formula <- function(msmsPeaks, mode="pH", detail=FALSE, run="prelimi ...@@ -732,18 +737,18 @@ analyzeMsMs.formula <- function(msmsPeaks, mode="pH", detail=FALSE, run="prelimi
# to match order in childPeaks. After that, setData to the child slot. # to match order in childPeaks. After that, setData to the child slot.
childPeaksOmitted <- getData(child) childPeaksOmitted <- getData(child)
childPeaksOmitted <- childPeaksOmitted[child@low | child@satellite,,drop=FALSE] childPeaksOmitted <- childPeaksOmitted[child@low | child@satellite,,drop=FALSE]
childPeaksOmitted$rawOK <- FALSE childPeaksOmitted$rawOK <- rep(FALSE, nrow(childPeaksOmitted))
childPeaksOmitted$good <- FALSE childPeaksOmitted$good <- rep(FALSE, nrow(childPeaksOmitted))
childPeaksOmitted$dppm <- NA childPeaksOmitted$dppm <- rep(NA, nrow(childPeaksOmitted))
childPeaksOmitted$formula <- NA childPeaksOmitted$formula <- rep(NA, nrow(childPeaksOmitted))
childPeaksOmitted$mzCalc <- NA childPeaksOmitted$mzCalc <- rep(NA, nrow(childPeaksOmitted))
childPeaksOmitted$dbe <- NA childPeaksOmitted$dbe <- rep(NA, nrow(childPeaksOmitted))
childPeaksOmitted$dppmBest <- NA childPeaksOmitted$dppmBest <- rep(NA, nrow(childPeaksOmitted))
childPeaksOmitted$formulaCount <- 0 childPeaksOmitted$formulaCount <- rep(0, nrow(childPeaksOmitted))
childPeaks$satellite <- FALSE childPeaks$satellite <- rep(FALSE, nrow(childPeaks))
childPeaks$low <- FALSE childPeaks$low <- rep(FALSE, nrow(childPeaks))
childPeaks$rawOK <- TRUE childPeaks$rawOK <- rep(TRUE, nrow(childPeaks))
childPeaks <- childPeaks[,colnames(childPeaksOmitted), drop=FALSE] childPeaks <- childPeaks[,colnames(childPeaksOmitted), drop=FALSE]
......
...@@ -220,7 +220,9 @@ findMsMsHR.mass <- function(msRaw, mz, limit.coarse, limit.fine, rtLimits = NA, ...@@ -220,7 +220,9 @@ findMsMsHR.mass <- function(msRaw, mz, limit.coarse, limit.fine, rtLimits = NA,
centroided = TRUE centroided = TRUE
) )
}) })
msmsSpecs <- do.call(c, msmsSpecs) msmsSpecs <- as(do.call(c, msmsSpecs), "SimpleList")
# build the new objects # build the new objects
masterSpec <- new("Spectrum1", masterSpec <- new("Spectrum1",
...@@ -285,7 +287,7 @@ findMsMsHR.direct <- function(msRaw, cpdID, mode = "pH", confirmMode = 0, useRtL ...@@ -285,7 +287,7 @@ findMsMsHR.direct <- function(msRaw, cpdID, mode = "pH", confirmMode = 0, useRtL
sp <- spectra[[confirmMode + 1]] sp <- spectra[[confirmMode + 1]]
#sp@mz <- mzLimits #sp@mz <- mzLimits
sp@id <- as.integer(cpdID) sp@id <- as.character(as.integer(cpdID))
sp@name <- findName(cpdID) sp@name <- findName(cpdID)
sp@formula <- findFormula(cpdID) sp@formula <- findFormula(cpdID)
return(sp) return(sp)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment