Skip to content

Commit

Permalink
addition of addCollmns.. parameters and documentation
Browse files Browse the repository at this point in the history
  • Loading branch information
philouail committed Nov 21, 2024
1 parent 1d3e482 commit 971db33
Show file tree
Hide file tree
Showing 8 changed files with 192 additions and 71 deletions.
67 changes: 54 additions & 13 deletions R/AllGenerics.R
Original file line number Diff line number Diff line change
Expand Up @@ -411,14 +411,21 @@ setGeneric("chromPeakData<-", function(object, value)
#'
#' Parameter `return.type` allows to specify the *type* of the result object.
#' With `return.type = "Spectra"` (the default) a [Spectra] object with all
#' matching spectra is returned. The spectra variable `"peak_id"` of the
#' returned `Spectra` contains the ID of the chromatographic peak (i.e., the
#' rowname of the peak in the `chromPeaks` matrix) for each spectrum.
#' With `return.type = "Spectra"` a `List` of `Spectra` is returned. The
#' length of the list is equal to the number of rows of `chromPeaks`. Each
#' element of the list contains thus a `Spectra` with all spectra for one
#' chromatographic peak (or a `Spectra` of length 0 if no spectrum was found
#' for the respective chromatographic peak).
#' matching spectra is returned. With `return.type = "Spectra"` a `List` of
#' `Spectra` is returned. The length of the list is equal to the number of rows
#' of `chromPeaks`. Each element of the list contains thus a `Spectra` with all
#' spectra for one chromatographic peak (or a `Spectra` of length 0 if no
#' spectrum was found for the respective chromatographic peak).
#'
#' Parameters `addColumnsChromPeaks` allow the user to add specific metadata
#' columns from the chromatographic peaks (`chromPeaks`) to the returned
#' spectra object. This can be useful to retain information such as retention
#' time (`rt`), m/z (`mz`). The columns will be named as they is written in the
#' `chromPeaks` object with a prefix that is defined by the parameter
#' `addColumnsChromPeaksPrefix`. The *peak ID* (i.e., the row name of the
#' peak in the `chromPeaks` matrix) is always added to the spectra object as
#' metadata column `paste0(addColumnsChromPeaksPrefix,id)`, by default it will
#' be `"chrom_peak_id"`.
#'
#' See also the *LC-MS/MS data analysis* vignette for more details and examples.
#'
Expand Down Expand Up @@ -453,6 +460,16 @@ setGeneric("chromPeakData<-", function(object, value)
#' @param return.type `character(1)` defining the type of result object that
#' should be returned.
#'
#' @param addColumnsChromPeaks `character` vector with the names of the columns
#' from `chromPeaks` that should be added to the returned spectra object.
#' The columns will be named as they are written in the `chromPeaks` object
#' with a prefix that is defined by the parameter
#' `addColumnsChromPeaksPrefix`. Defaults to `c("mz", "rt")`.
#'
#' @param addColumnsChromPeaksPrefix `character(1)` defining the prefix that
#' should be used for the columns from `chromPeaks` that are added to the
#' returned spectra object. Defaults to `"chrom_peak_"`.
#'
#' @param BPPARAM parallel processing setup. Defaults to [bpparam()].
#'
#' @param ... ignored.
Expand Down Expand Up @@ -503,7 +520,7 @@ setGeneric("chromPeakData<-", function(object, value)
#' ## spectra variable *peak_id* contain the row names of the peaks in the
#' ## chromPeak matrix and allow thus to map chromatographic peaks to the
#' ## returned MS2 spectra
#' ms2_sps$peak_id
#' ms2_sps$chrom_peak_id
#' chromPeaks(dda)
#'
#' ## Alternatively, return the result as a List of Spectra objects. This list
Expand Down Expand Up @@ -799,10 +816,24 @@ setGeneric("featureDefinitions<-", function(object, value)
#' spectrum **per chromatographic peak** will be returned (hence multiple
#' spectra per feature).
#'
#' The ID of each chromatographic peak (i.e. its row name in `chromPeaks`)
#' and each feature (i.e., its row name in `featureDefinitions`) are
#' available in the returned [Spectra()] with spectra variables `"peak_id"`
#' and `"feature_id"`, respectively.
#' The information from `featureDefinitions` for each feature can be included
#' in the returned [Spectra()] object using the `addColumnsFeatures` parameter.
#' This is useful for retaining details such as the median retention time (`rtmed`)
#' or median m/z (`mzmed`). The columns will retain their names as specified
#' in the `featureDefinitions` object, prefixed by the value of the
#' `addColumnsFeaturesPrefix` parameter. Additionally, the *feature ID*
#' (i.e., the row name of the feature in the `featureDefinitions` data.frame)
#' is always added as a metadata column with the name
#' `paste0(addColumnsFeaturesPrefix, "id")`, which defaults to `"feature_id"`.
#'
#' See also [chromPeakSpectra()], as it supports a similar parameter for
#' including columns from the chromatographic peaks in the returned spectra object.
#' These parameters can be used in combination to include information from both
#' the chromatographic peaks and the features in the returned [Spectra()].
#' The *peak ID* (i.e., the row name of the peak in the `chromPeaks` matrix)
#' is added as a metadata column with the name
#' `paste0(addColumnsChromPeaksPrefix, "id")`, which defaults to
#' `"chrom_peak_id"`.
#'
#' @param object [XcmsExperiment] or [XCMSnExp] object with feature defitions.
#'
Expand All @@ -815,6 +846,16 @@ setGeneric("featureDefinitions<-", function(object, value)
#' `featureDefinitions(x)`). This parameter overrides `skipFilled` and is
#' only supported for `return.type` being either `"Spectra"` or `"List"`.
#'
#' @param addColumnsFeatures `character` vector with the names of the columns
#' from `featureDefinitions` that should be added to the returned spectra
#' object. The columns will be named as they are written in the
#' `featureDefinitions` object with a prefix that is defined by the parameter
#' `addColumnsFeaturesPrefix`. Defaults to `c("mzmed", "rtmed")`.
#'
#' @param addColumnsFeaturesPrefix `character(1)` defining the prefix that
#' should be used for the columns from `featureDefinitions` that are added
#' to the returned spectra object. Defaults to `"feature_"`.
#'
#' @param ... additional arguments to be passed along to [chromPeakSpectra()],
#' such as `method`.
#'
Expand Down
34 changes: 25 additions & 9 deletions R/XcmsExperiment-functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -795,7 +795,7 @@
ppm = 0, skipFilled = FALSE,
peaks = integer(),
addColumnsChromPeaks = c("rt", "mz"),
addColumnsChrompeaksPrefix = "chrom_peak_",
addColumnsChromPeaksPrefix = "chrom_peak_",
BPPARAM = bpparam()) {
method <- match.arg(method)
pks <- .chromPeaks(x)[, c("mz", "mzmin", "mzmax", "rt",
Expand All @@ -822,8 +822,8 @@
split.data.frame(pks, f),
split(spectra(x), factor(fromFile(x), levels = levels(f))),
FUN = function(pk, sp, msLevel, method, addColumnsChromPeaks,
addColumnsChrompeaksPrefix) {
sp <- filterMsLevel(sp, msLevel)
addColumnsChromPeaksPrefix) {
sp <- Spectra::filterMsLevel(sp, msLevel)
idx <- switch(
method,
all = .spectra_index_list(sp, pk, msLevel),
Expand All @@ -833,21 +833,37 @@
largest_bpi = .spectra_index_list_largest_bpi(sp, pk, msLevel))
ids <- rep(rownames(pk), lengths(idx))
res <- sp[unlist(idx)]
pk_data <- DataFrame(pk[ids, addColumnsChromPeaks, drop = FALSE])
pk_data$id <- ids
colnames(pk_data) <- paste0(addColumnsChrompeaksPrefix,
pk_data <- pk[ids, addColumnsChromPeaks, drop = FALSE]
pk_data <- cbind(pk_data, id = ids)
colnames(pk_data) <- paste0(addColumnsChromPeaksPrefix,
colnames(pk_data))
pk_data$spectrumId <- res$spectrumId
res <- Spectra::joinSpectraData(res, pk_data)
res <- .add_spectra_data(res, pk_data)
res
},
MoreArgs = list(msLevel = msLevel, method = method,
addColumnsChromPeaks = addColumnsChromPeaks,
addColumnsChrompeaksPrefix = addColumnsChrompeaksPrefix),
addColumnsChromPeaksPrefix = addColumnsChromPeaksPrefix),
BPPARAM = BPPARAM)
Spectra:::.concatenate_spectra(res)
}

#' @param x `Spectra` object.
#'
#' @param data `data.frame` or `matrix` with the data to be added to the
#' spectra object.
#'
#' @noRd
.add_spectra_data <- function(x, data) {
if (is(data, "matrix"))
data <- as.data.frame(data)
if (nrow(data) != length(x))
stop("Length of 'data' does not match the number of spectra in 'x'")
for (i in colnames(data)) {
x[[i]] <- data[, i]
}
x
}

#' @param peaks `matrix` with chrom peaks.
#'
#' @param peakIdx `list` of `integer` indices defining which chromatographic
Expand Down
21 changes: 13 additions & 8 deletions R/XcmsExperiment.R
Original file line number Diff line number Diff line change
Expand Up @@ -515,10 +515,6 @@
#' indicating the identified chromatographic peaks. Only a single color
#' is supported. Defaults to `peakCol = "#ff000060".
#'
#' @param peaksInfo For `chromPeakSpectra`: `character` vector of additional
#' information from `chromPeaks()` to be added to the spectra object. The
#' columns names will be appended with "peaks_".
#'
#' @param ppm For `chromPeaks` and `featureDefinitions`: optional `numeric(1)`
#' specifying the ppm by which the m/z range (defined by `mz` should be
#' extended. For a value of `ppm = 10`, all peaks within `mz[1] - ppm / 1e6`
Expand Down Expand Up @@ -1784,7 +1780,11 @@ setMethod(
"featureSpectra", "XcmsExperiment",
function(object, msLevel = 2L, expandRt = 0, expandMz = 0, ppm = 0,
skipFilled = FALSE, return.type = c("Spectra", "List"),
features = character(), ...) {
features = character(),
addColumnsFeatures = c("rtmed", "mzmed"),
addColumnsFeaturesPrefix = "feature_",
addColumnsChromPeaksPrefix = "chrom_peak_",
...) {
return.type <- match.arg(return.type)
if (!hasFeatures(object))
stop("No feature definitions present. Please run ",
Expand All @@ -1803,13 +1803,18 @@ setMethod(
sps <- .mse_spectra_for_peaks(
object, msLevel = msLevel, expandRt = expandRt,
expandMz = expandMz, ppm = ppm, skipFilled = skipFilled,
peaks = unique(pindex), ...)
peaks = unique(pindex),
addColumnsChromPeaksPrefix = addColumnsChromPeaksPrefix)
col <- paste0(addColumnsChromPeaksPrefix, "id")
mtch <- as.matrix(
findMatches(sps$peak_id, rownames(.chromPeaks(object))[pindex]))
findMatches(sps[[col]], rownames(.chromPeaks(object))[pindex]))
sps <- sps[mtch[, 1L]]
fid <- rep(
ufeatures, lengths(featureDefinitions(object)$peakidx[findex]))
sps$feature_id <- fid[mtch[, 2L]]
f_data <- featureDefinitions(object)[fid[mtch[, 2L]], addColumnsFeatures]
f_data$id <- fid[mtch[, 2L]]
colnames(f_data) <- paste0(addColumnsFeaturesPrefix, colnames(f_data))
sps <- .add_spectra_data(sps, f_data)
if (return.type == "List") {
sps <- List(split(sps, f = factor(sps$feature_id,
levels = ufeatures)))
Expand Down
4 changes: 0 additions & 4 deletions man/XcmsExperiment.Rd

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

38 changes: 28 additions & 10 deletions man/chromPeakSpectra.Rd

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

39 changes: 35 additions & 4 deletions man/featureSpectra.Rd

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

Loading

0 comments on commit 971db33

Please sign in to comment.