Skip to content

Commit

Permalink
Add groupnames,XCMSnExp method (issue #250).
Browse files Browse the repository at this point in the history
  • Loading branch information
jorainer committed Feb 8, 2018
1 parent 34ca319 commit d66fd8f
Show file tree
Hide file tree
Showing 5 changed files with 98 additions and 1 deletion.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: xcms
Version: 3.1.1
Date: 2017-11-28
Date: 2018-03-08
Title: LC/MS and GC/MS Data Analysis
Author: Colin A. Smith <csmith@scripps.edu>,
Ralf Tautenhahn <rtautenh@gmail.com>,
Expand Down
57 changes: 57 additions & 0 deletions R/methods-XCMSnExp.R
Original file line number Diff line number Diff line change
Expand Up @@ -2794,3 +2794,60 @@ setMethod("split", "XCMSnExp", function(x, f,
c.XCMSnExp <- function(...) {
.concatenate_XCMSnExp(...)
}

#' @title Generate unique group (feature) names based on mass and retention time
#'
#' @description
#'
#' `groupnames` generates names for the identified features from the
#' correspondence analysis based in their mass and retention time. This
#' generates feature names that are equivalent to the group names of the *old*
#' user interface (aka xcms1).
#'
#' @param object `XCMSnExp` object containing correspondence results.
#'
#' @param mzdec `integer(1)` with the number of decimal places to use for m/z (
#' defaults to `0`).
#'
#' @param rtdec `integer(1)` with the number of decimal places to use for the
#' retention time (defaults to `0`).
#'
#' @param template `character` with existing group names whose format should
#' be emulated.
#'
#' @return `character` with unique names for each feature in `object`. The
#' format is `M(m/z)T(time in seconds)`.
#'
#' @seealso [XCMSnExp].
#'
#' @md
#'
#' @rdname groupnames-XCMSnExp
setMethod("groupnames", "XCMSnExp", function(object, mzdec = 0, rtdec = 0,
template = NULL) {
if (!hasFeatures(object))
stop("No feature data present! Use 'groupChromPeaks' first")
if (!missing(template)) {
tempsplit <- strsplit(template[1], "[T_]")
tempsplit <- strsplit(unlist(tempsplit), "\\.")
if (length(tempsplit[[1]]) > 1)
mzdec <- nchar(tempsplit[[1]][2])
else
mzdec <- 0
if (length(tempsplit[[2]]) > 1)
rtdec <- nchar(tempsplit[[2]][2])
else
rtdec <- 0
}
mzfmt <- paste0("%.", mzdec, "f")
rtfmt <- paste0("%.", rtdec, "f")
gnames <- paste0("M", sprintf(mzfmt, featureDefinitions(object)$mzmed),
"T", sprintf(rtfmt, featureDefinitions(object)$rtmed))
if (any(dup <- duplicated(gnames)))
for (dupname in unique(gnames[dup])) {
dupidx <- which(gnames == dupname)
gnames[dupidx] <- paste(gnames[dupidx], seq(along = dupidx),
sep = "_")
}
gnames
})
1 change: 1 addition & 0 deletions inst/NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ NEW FEATURES
- Reading raw files using xcmsSet or xcmsRaw uses now the automatic file type
detection feature from mzR.
- c function to concatenate XCMSnExp objects.
- groupnames method for XCMSnExp objects (issue #250).

BUG FIXES:
- Fix #237: findPeaks.MSW was not throwing an error if applied to multi-spectrum
Expand Down
4 changes: 4 additions & 0 deletions inst/unitTests/runit.XCMSnExp.R
Original file line number Diff line number Diff line change
Expand Up @@ -1547,6 +1547,10 @@ test_split <- function() {
checkTrue(!all(rtime(tmp[[3]]) == rtime(tmp[[3]], adjusted = FALSE)))
}

test_groupnames_XCMSnExp <- function() {
gn <- groupnames(xod_xgrg)
checkException(groupnames(xod_x))
}

############################################################
## Test getEIC alternatives.
Expand Down
35 changes: 35 additions & 0 deletions man/groupnames-XCMSnExp.Rd

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

0 comments on commit d66fd8f

Please sign in to comment.