Skip to content

Commit

Permalink
feat: add parameter addOriginalQueryIndex to matchSpectra
Browse files Browse the repository at this point in the history
- `matchSpectra()` gains parameter `addOriginalQueryIndex` and adds by default a
  new spectra variable with the index for each spectrum in the original query
  object.
  • Loading branch information
jorainer committed Apr 25, 2024
1 parent 0fdfc4d commit 14cfc15
Show file tree
Hide file tree
Showing 10 changed files with 247 additions and 109 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: MetaboAnnotation
Title: Utilities for Annotation of Metabolomics Data
Version: 1.7.4
Version: 1.7.5
Description:
High level functions to assist in annotation of (metabolomics) data sets.
These include functions to perform simple tentative annotations based on
Expand Down
6 changes: 6 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,11 @@
# MetaboAnnotation 1.7

## Changes in 1.7.5

- Add parameter `addOriginalQueryIndex` to `matchSpectra()` that allows to add
an additional spectra variable to the `query` `Spectra` with the index in
the original object (issue #114).

## Changes in 1.7.4

- Import `setBackend()` generic from `ProtGenerics`.
Expand Down
8 changes: 5 additions & 3 deletions R/CompDbSource.R
Original file line number Diff line number Diff line change
Expand Up @@ -130,12 +130,14 @@ setMethod("show", "CompDbSource", function(object) {
setMethod(
"matchSpectra", signature(query = "Spectra", target = "CompDbSource",
param = "Param"),
function(query, target, param, BPPARAM = BiocParallel::SerialParam()) {
function(query, target, param, BPPARAM = BiocParallel::SerialParam(),
addOriginalQueryIndex = TRUE) {
## connect to the database
db <- CompDb(target@dbfile)
## get the Spectra from the source and call matchSpectra
res <- matchSpectra(query, Spectra(db), param = param,
BPPARAM = BPPARAM)
res <- matchSpectra(
query, Spectra(db), param = param, BPPARAM = BPPARAM,
addOriginalQueryIndex = addOriginalQueryIndex)
## keep only matching reference/target spectra and change the
## backend to MsBackendDataFrame
res <- pruneTarget(res)
Expand Down
28 changes: 23 additions & 5 deletions R/matchSpectra.R
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,13 @@
#' `THRESHFUN_REVERSE` are returned. With the default
#' `THRESHFUN_REVERSE = NULL` all matches passing `THRESHFUN` are reported.
#'
#' @param addOriginalQueryIndex for `matchSpectra()`: `logical(1)` whether an
#' additional spectra variable `".original_query_index"` should be added to
#' the `query` `Spectra` object providing the index of the spectrum in this
#' originally provided object. This spectra variable can be useful to link
#' back to the original `Spectra` object if the `MatchedSpectra` object gets
#' subsetted/processed.
#'
#' @param BPPARAM for `matchSpectra`: parallel processing setup (see the
#' `BiocParallel` package for more information). Parallel processing is
#' disabled by default (with the default setting `BPPARAM = SerialParam()`).
Expand Down Expand Up @@ -393,8 +400,15 @@ setMethod(
signature(query = "Spectra", target = "Spectra",
param = "CompareSpectraParam"),
function(query, target, param, rtColname = c("rtime", "rtime"),
BPPARAM = BiocParallel::SerialParam()) {
BPPARAM = BiocParallel::SerialParam(),
addOriginalQueryIndex = TRUE) {
BPPARAM <- .check_bpparam(query, target, BPPARAM)
if (addOriginalQueryIndex) {
if (any(spectraVariables(query) == ".original_query_index"))
warning("Overwriting already present spectra variable ",
"\".original_query_index\"")
query$.original_query_index <- seq_along(query)
}
if (length(query) == 1 || param@requirePrecursor ||
param@requirePrecursorPeak || any(is.finite(param@toleranceRt)) ||
any(param@percentRt != 0))
Expand Down Expand Up @@ -422,9 +436,11 @@ setMethod(
"matchSpectra", signature(query = "Spectra", target = "CompDb",
param = "Param"),
function(query, target, param, rtColname = c("rtime", "rtime"),
BPPARAM = BiocParallel::SerialParam()) {
BPPARAM = BiocParallel::SerialParam(),
addOriginalQueryIndex = TRUE) {
matchSpectra(query, Spectra(target), param = param,
rtColname = rtColname, BPPARAM = BPPARAM)
rtColname = rtColname, BPPARAM = BPPARAM,
addOriginalQueryIndex = addOriginalQueryIndex)
})

.match_spectra <- function(query, target, param,
Expand Down Expand Up @@ -548,9 +564,11 @@ setMethod(
signature(query = "Spectra", target = "Spectra",
param = "MatchForwardReverseParam"),
function(query, target, param, rtColname = c("rtime", "rtime"),
BPPARAM = BiocParallel::SerialParam()) {
BPPARAM = BiocParallel::SerialParam(),
addOriginalQueryIndex = TRUE) {
res <- matchSpectra(query, target, as(param, "CompareSpectraParam"),
rtColname = rtColname, BPPARAM = BPPARAM)
rtColname = rtColname, BPPARAM = BPPARAM,
addOriginalQueryIndex = addOriginalQueryIndex)
## Loop over the matches and assign additional stuff...
nm <- nrow(res@matches)
res@matches$reverse_score <- rep(NA_real_, nm)
Expand Down
36 changes: 25 additions & 11 deletions R/validateMatchedSpectra.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,10 @@
#' button the app is closed and a filtered `MatchedSpectra` is returned,
#' containing only *validated* matches.
#'
#' Note that column `"query_index_"` and `"target_index_"` are temporarily
#' added to the query and target `Spectra` object to display them in the
#' interactive graphics for easier identification of the compared spectra.
#'
#' @param object A non-empty instance of class `MatchedSpectra`.
#'
#' @return A `MatchedSpectra` with validated results.
Expand Down Expand Up @@ -45,23 +49,27 @@
#' ## validate matches using the shiny app. Note: the call is only executed
#' ## in interactive mode.
#' if (interactive()) {
#' validateMatchedSpectra(ms)
#' res <- validateMatchedSpectra(ms)
#' }
validateMatchedSpectra <- function(object) {
if (!requireNamespace("shiny", quietly = TRUE))
stop("The use of 'validateMatchedSpectra' requires package 'shiny'.",
" Please install with 'BiocInstaller::install(\"shiny\")'")
" Please install with 'BiocManager::install(\"shiny\")'")
if (!requireNamespace("shinyjs", quietly = TRUE))
stop("The use of 'validateMatchedSpectra' requires package 'shinyjs'.",
" Please install with 'BiocInstaller::install(\"shinyjs\")'")
" Please install with 'BiocManager::install(\"shinyjs\")'")
if (!requireNamespace("DT", quietly = TRUE))
stop("The use of 'validateMatchedSpectra' requires package 'DT'.",
" Please install with 'BiocInstaller::install(\"DT\")'")
" Please install with 'BiocManager::install(\"DT\")'")

stopifnot(inherits(object, "MatchedSpectra"))
if (!length(object))
stop("The 'MatchedSpectra' object is empty.")

## Add query and target index
object@query$query_index_ <- seq_along(object@query)
object@target$index_ <- seq_along(object@target)

bpp <- bpparam()
on.exit(register(bpp))
register(SerialParam())
Expand All @@ -77,8 +85,8 @@ validateMatchedSpectra <- function(object) {
),
shiny::mainPanel(
plotly::plotlyOutput("plot"),
shiny::checkboxInput("valid", "Current match OK?", value = TRUE,
width = NULL),
shiny::checkboxInput("valid", "Current match OK?",
value = TRUE, width = NULL),
DT::DTOutput("targets")
)
))
Expand All @@ -96,7 +104,7 @@ validateMatchedSpectra <- function(object) {
if (nrow(dt)) {
dt <- data.frame(valid = TRUE, dt)
} else dt <- data.frame(valid = logical(), dt)
dtl <- split(dt, factor(object@matches$query_idx, seq_along(object)))
dtl <- split(dt, factor(dt$query_index_, seq_along(object)))
rv <- shiny::reactiveValues(
queries = query_ids,
dtl = dtl
Expand All @@ -122,7 +130,8 @@ validateMatchedSpectra <- function(object) {
## rv_target$idx <- input$targets_rows_selected
shinyjs::enable("valid")
current_valid <- rv$dtl[[rv_query$idx]]$valid[rv_target$idx]
shiny::updateCheckboxInput(session, "valid", value = current_valid)
shiny::updateCheckboxInput(session, "valid",
value = current_valid)
} else
shinyjs::disable("valid")
output$plot <- plotly::renderPlotly(
Expand All @@ -139,7 +148,8 @@ validateMatchedSpectra <- function(object) {
if (nrow(current_match@matches)) {
tidx <- current_match@matches$target_idx[rv_target$idx]
current_valid <- rv$dtl[[rv_query$idx]]$valid[rv_target$idx]
shiny::updateCheckboxInput(session, "valid", value = current_valid)
shiny::updateCheckboxInput(session, "valid",
value = current_valid)
output$plot <- plotly::renderPlotly(
.plotlySpectraMirror(query(current_match),
target(current_match)[tidx],
Expand All @@ -157,6 +167,7 @@ validateMatchedSpectra <- function(object) {
}
})
shiny::observeEvent(input$b_store, {
## Collect all the selections from all data frames
idx <- which(do.call(rbind, rv$dtl)$valid)
shiny::stopApp(filterMatches(object, index = idx))
})
Expand Down Expand Up @@ -298,12 +309,15 @@ validateMatchedSpectra <- function(object) {
}

.create_dt <- function(x){
.sel_cols <- c("precursorMz", "target_precursorMz", "rtime",
"target_rtime", "target_name", "target_compound_name",
.sel_cols <- c("query_index_", "target_index_", "precursorMz",
"target_precursorMz", "rtime", "target_rtime",
"target_name", "target_compound_name",
"score", "reverse_score", "presence_ratio")
cols <- .sel_cols[.sel_cols %in% spectraVariables(x)]
tbl <- as.data.frame(matchedData(x, cols))
tbl$score <- round(tbl$score, 3)
if (any(colnames(tbl) == "precursorMz"))
tbl$precursorMz <- round(tbl$precursorMz, 3)
if (any(colnames(tbl) == "reverse_score"))
tbl$reverse_score <- round(tbl$reverse_score, 3)
if (any(colnames(tbl) == "presence_ratio"))
Expand Down
24 changes: 20 additions & 4 deletions man/CompareSpectraParam.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

6 changes: 5 additions & 1 deletion man/validateMatchedSpectra.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

3 changes: 2 additions & 1 deletion tests/testthat/test_CompDbSource.R
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,8 @@ test_that("matchSpectra,Spectra,CompDbSource works", {
fl <- system.file("sql", "CompDb.MassBank.sql", package = "CompoundDb")
src <- new("CompDbSource", dbfile = fl)

res <- matchSpectra(pest_ms2, src, param = CompareSpectraParam())
res <- matchSpectra(pest_ms2, src, param = CompareSpectraParam(),
addOriginalQueryIndex = FALSE)
expect_s4_class(res, "MatchedSpectra")
expect_equal(query(res), pest_ms2)
expect_s4_class(target(res)@backend, "MsBackendDataFrame")
Expand Down
6 changes: 6 additions & 0 deletions tests/testthat/test_matchSpectra.R
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,10 @@ test_that(".get_matches_spectra, matchSpectra,CompareSpectraParam works", {
res <- matchSpectra(pest_ms2, minimb, csp)
expect_equal(res@matches$query_idx, 1:13)
expect_equal(length(unique(res$target_spectrum_id)), 11)
expect_true(any(spectraVariables(res) == ".original_query_index"))
expect_equal(res@query$.original_query_index, seq_along(pest_ms2))
res <- matchSpectra(pest_ms2, minimb, csp, addOriginalQueryIndex = FALSE)
expect_false(any(spectraVariables(res) == ".original_query_index"))

mb2 <- minimb
spectraNames(mb2) <- seq_along(mb2)
Expand Down Expand Up @@ -193,6 +197,8 @@ test_that("matchSpectra,MatchForwardReverseParam works", {
expect_equal(colnames(res@matches), c("query_idx", "target_idx", "score",
"reverse_score", "presence_ratio",
"matched_peaks_count"))
expect_true(any(spectraVariables(res) == ".original_query_index"))
expect_equal(query(res)$.original_query_index, seq_along(pest_ms2))

mp <- MatchForwardReverseParam(requirePrecursor = TRUE,
THRESHFUN = function(x) which.max(x))
Expand Down
Loading

0 comments on commit 14cfc15

Please sign in to comment.