Skip to content
Snippets Groups Projects
Commit 261786a3 authored by ermueller's avatar ermueller
Browse files

FInish refactoring and adjusted other small things, 1 unit test added

parent 8f7a0ef4
No related branches found
No related tags found
No related merge requests found
......@@ -8,7 +8,7 @@
#' @param conflict Either "isotopic"(Peak formulas are always chosen if they fit the requirements for an isotopic peak)
#' or "strict"(Peaks are only marked as isotopic when there hasn't been a formula assigned before.)
#' @param isolationWindow Half of the width of the isolation window in Da
#' @param evalMode Currently no function yet, but planned
#' @param evalMode Currently no function yet, but planned. Currently must be "complete"
#' @param plotSpectrum A boolean specifiying whether the spectrumshould be plotted
#' @param settings Options to be used for processing. Defaults to the options loaded via
#' \code{\link{loadRmbSettings}} et al. Refer to there for specific settings.
......
......@@ -1104,8 +1104,12 @@ cleanElnoise <- function(peaks, noise=getOption("RMassBank")$electronicNoise,
problematicPeaks <- function(peaks_unmatched, peaks_matched, mode="pH")
{
# find spectrum maximum for each peak, and merge into table
assIntMax <- as.data.frame(aggregate(peaks_matched$intensity,
if(nrow(peaks_matched) == 0){
assIntMax <- data.frame(list(integer(0),integer(0),integer(0)))
} else{
assIntMax <- as.data.frame(aggregate(peaks_matched$intensity,
by=list(peaks_matched$cpdID, peaks_matched$scan), max))
}
colnames(assIntMax) <- c("cpdID", "scan", "aMax")
peaks_unmatched <- merge(peaks_unmatched, assIntMax)
# which of these peaks are intense?
......@@ -1818,8 +1822,12 @@ filterPeaksMultiplicity <- function(peaks, formulacol, recalcBest = TRUE)
if(!is.data.frame(peaks) || (nrow(peaks) == 0) )
{
warning("filterPeaksMultiplicity: All peaks have been filtered.")
peaks <- cbind(peaks, data.frame(formulaMultiplicity=numeric()))
if(recalcBest){
warning("filterPeaksMultiplicity: All peaks have been filtered. The workflow can not be continued beyond this point.")
peaks$fM_factor <- as.factor(peaks$formulaMultiplicity)
return(peaks)
}
}
else
{
......@@ -1960,7 +1968,7 @@ filterPeaksMultiplicity <- function(peaks, formulacol, recalcBest = TRUE)
#' @examples
#' \dontrun{
#' refilteredRcSpecs <- filterMultiplicity(
#' reanalyzedRcSpecs, "myarchive", "pH")
#' w, "myarchive", "pH")
#' }
#' @export
filterMultiplicity <- function(w, archivename=NA, mode="pH", recalcBest = TRUE,
......@@ -1972,7 +1980,7 @@ filterMultiplicity <- function(w, archivename=NA, mode="pH", recalcBest = TRUE,
if(is.null(multiplicityFilter))
multiplicityFilter <- 2
specs <- w@aggregated
specs <- w@aggregated
peaksFiltered <- filterPeaksMultiplicity(peaksMatched(specs),
"formula", recalcBest)
......@@ -1998,7 +2006,11 @@ filterMultiplicity <- function(w, archivename=NA, mode="pH", recalcBest = TRUE,
specs <- addProperty(specs, "filterOK", "logical", FALSE)
specs[specs$formulaMultiplicity > (multiplicityFilter - 1),"filterOK"] <- TRUE
OKindex <- which(specs$formulaMultiplicity > (multiplicityFilter - 1))
if(length(OKindex)){
specs[OKindex,"filterOK"] <- TRUE
}
peaksReanOK <- specs[
specs$filterOK & !is.na(specs$matchedReanalysis) & specs$matchedReanalysis,,drop=FALSE]
......@@ -2009,7 +2021,10 @@ filterMultiplicity <- function(w, archivename=NA, mode="pH", recalcBest = TRUE,
peaksReanBad <- peaksReanOK[
!((peaksReanOK$mzFound < peaksReanOK$mzCenter - 1) |
(peaksReanOK$mzFound > peaksReanOK$mzCenter + 1)),]
specs[match(peaksReanBad$index, specs$index),"filterOK"] <- FALSE
notOKindex <- match(peaksReanBad$index, specs$index)
if(length(notOKindex)){
specs[notOKindex,"filterOK"] <- FALSE
}
return(specs)
......
......@@ -19,8 +19,8 @@
#' @export
validate <- function(path, simple = TRUE) {
requireNamespace("ontoCAT",quietly=TRUE)
requireNamespace("RUnit",quietly=TRUE)
requireNamespace("ontoCAT",quietly=TRUE)
requireNamespace("RUnit",quietly=TRUE)
# Is the argument a directory?
# If yes, list the files
......@@ -216,7 +216,12 @@ smiles2mass <- function(SMILES){
package="RMassBank"), testFileRegexp = "runit.DA.R",
#testFuncRegexp = "^test.+",
rngKind = "Marsaglia-Multicarry",
rngNormalKind = "Kinderman-Ramage")
rngNormalKind = "Kinderman-Ramage")
testSuite3 <- RUnit::defineTestSuite("Evaluation of correct handling ig no peaks are found", dirs = system.file("unitTests",
package="RMassBank"), testFileRegexp = "runit.NOPEAKS.R",
#testFuncRegexp = "^test.+",
rngKind = "Marsaglia-Multicarry",
rngNormalKind = "Kinderman-Ramage")
testData <- suppressWarnings(RUnit::runTestSuite(testSuite))
testData2 <- suppressWarnings(RUnit::runTestSuite(testSuite2))
......
......@@ -26,5 +26,5 @@ test.mzRRead <- function(){
}
}
checkTrue(allOK)
RUnit::checkTrue(allOK)
}
\ No newline at end of file
test.eletronicnoise <- function(){
failpeaks <- read.csv("pH_narcotics_Failpeaks.csv")
checkTrue(!any(apply(failpeaks,1,function(x) all(x[2:5] == c(1738,2819,668,201.69144)))))
RUnit::checkTrue(!any(apply(failpeaks,1,function(x) all(x[2:5] == c(1738,2819,668,201.69144)))))
}
test.formulacalculation <- function(){
failpeaks <- read.csv("pH_narcotics_Failpeaks.csv")
checkTrue(!any(apply(failpeaks,1,function(x) all(x[2:5] == c(70,2758,321,56.04933)))))
RUnit::checkTrue(!any(apply(failpeaks,1,function(x) all(x[2:5] == c(70,2758,321,56.04933)))))
}
\ No newline at end of file
test.nopeaks <- function(){
w <- newMsmsWorkspace()
w@aggregated <- data.frame(mzFound = numeric(0), intensity = numeric(0), good = logical(0), mzCalc = numeric(0), formula = character(0), dbe = numeric(0),
formulaCount = integer(0), dppm = numeric(0), dppmBest = numeric(0), scan = integer(0), cpdID = character(0), parentScan = integer(0), dppmRc = numeric(0),
index = integer(0), noise = logical(0), reanalyzed.formula = character(0), reanalyzed.mzCalc = numeric(0), reanalyzed.dppm = numeric(0),reanalyzed.formulaCount = numeric(0),
reanalyzed.dbe = numeric(0),matchedReanalysis = logical(0))
filterMultiplicity(w, mode="pH")
RUnit::checkTrue(TRUE)
}
\ No newline at end of file
test.NA <- function(){
checkTrue(!(NA %in% as.matrix(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['PK$PEAK']])))
RUnit::checkTrue(!(NA %in% as.matrix(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['PK$PEAK']])))
}
test.peaksvsprecursor <- function(){
Max_Peak <- unname(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['PK$PEAK']][dim(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['PK$PEAK']])[1],1])
Precursor <- RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']]
if(is.na(Precursor)){
checkTrue(TRUE)
RUnit::checkTrue(TRUE)
}else{
checkEquals(Max_Peak, Precursor, tolerance = Precursor/100)
RUnit::checkEquals(Max_Peak, Precursor, tolerance = Precursor/100)
}
}
test.precursormz <- function(){
precursorlist <- c("[M+H]+","[M+Na]+","[M-H]-","[M+HCOO-]-","[M]+","[M]-")
if(is.na(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']]) || is.na(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']])){
checkTrue(TRUE)
RUnit::checkTrue(TRUE)
} else{
precursor <- grep(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']],precursorlist, value = TRUE, fixed = TRUE)
if(precursor == "[M+H]+"){
checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] + 1.008,tolerance = 0.002)
RUnit::checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] + 1.008,tolerance = 0.002)
}
if(precursor == "[M+Na]+"){
checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] + 22.989,tolerance = 0.002)
RUnit::checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] + 22.989,tolerance = 0.002)
}
if(precursor == "[M-H]-"){
checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] - 1.008,tolerance = 0.002)
RUnit::checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] - 1.008,tolerance = 0.002)
}
if(precursor == "[M+HCOO-]-"){
checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] + 45.017,tolerance = 0.002)
RUnit::checkEquals(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']],RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']] + 45.017,tolerance = 0.002)
}
}
}
......@@ -36,28 +36,28 @@ test.precursormz <- function(){
test.PrecursorType <- function(){
precursorlist <- c("[M+H]+","[M+Na]+","[M-H]-","[M+HCOO-]-","[M]+","[M]-")
if(is.na(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']])){
checkTrue(TRUE)
RUnit::checkTrue(TRUE)
}else{
checkTrue(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']] %in% precursorlist)
RUnit::checkTrue(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']] %in% precursorlist)
}
}
test.smilesvsexactmass <- function(){
Mass_Calculated_Through_Smiles <- smiles2mass(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$SMILES']])
Exact_Mass <- RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['CH$EXACT_MASS']]
checkEquals(Mass_Calculated_Through_Smiles, Exact_Mass, tolerance = Exact_Mass/100)
RUnit::checkEquals(Mass_Calculated_Through_Smiles, Exact_Mass, tolerance = Exact_Mass/100)
}
test.sumintensities <- function(){
sumOfIntensities <- sum(RMassBank.env$mb[[RMassBank.env$testnumber]]@compiled_ok[[1]][['PK$PEAK']][,2])
checkTrue(sumOfIntensities > 0)
RUnit::checkTrue(sumOfIntensities > 0)
}
test.TitleVsType <- function(){
RMassBank.env$testnumber <- RMassBank.env$testnumber + 1
if(is.na(RMassBank.env$mb[[RMassBank.env$testnumber-1]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']])){
checkTrue(TRUE)
RUnit::checkTrue(TRUE)
}else{
checkTrue(grepl(RMassBank.env$mb[[RMassBank.env$testnumber-1]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']], RMassBank.env$mb[[RMassBank.env$testnumber-1]]@compiled_ok[[1]][['RECORD_TITLE']], fixed = TRUE))
RUnit::checkTrue(grepl(RMassBank.env$mb[[RMassBank.env$testnumber-1]]@compiled_ok[[1]][['MS$FOCUSED_ION']][['PRECURSOR_TYPE']], RMassBank.env$mb[[RMassBank.env$testnumber-1]]@compiled_ok[[1]][['RECORD_TITLE']], fixed = TRUE))
}
}
test.slashes <- function(){
Type <- as.numeric(substring(mb@compiled_ok[[testNumber]][['AC$MASS_SPECTROMETRY']][['MS_TYPE']],first = 3))
slashes <- length(gregexpr('/', mb@compiled_ok[[testNumber]][['MS$FOCUSED_ION']][['PRECURSOR_M/Z']]))
checkEquals(Type - 2,slashes)
RUnit::checkEquals(Type - 2,slashes)
}
\ No newline at end of file
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