Skip to content

Commit 5e0b3c0

Browse files
committed
Add plot,MSnExp,missing, type = "XIC" plot (issue #313)
- Add parameter type to plot,MSnExp,missing to allow plotting either all spectra, or the XIC. - Update documentation and add unit tests.
1 parent 061c324 commit 5e0b3c0

7 files changed

+207
-21
lines changed

NAMESPACE

+2-1
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ importFrom(XML, xmlInternalTreeParse, getDefaultNamespace, xpathApply,
1717
xmlAttrs)
1818

1919
importFrom(graphics, abline, axis, grid, legend, lines, points, text,
20-
barplot, layout, par, matplot)
20+
barplot, layout, par, matplot, mtext)
2121
importFrom(stats, ave, median, medpolish, quantile, reorder, setNames,
2222
weighted.mean, dist)
2323
importFrom(utils, combn, head, ls.str, object.size,
@@ -49,6 +49,7 @@ importFrom(affy, MAplot, ma.plot, mva.pairs)
4949
importFrom(mzID, mzID, flatten)
5050
importClassesFrom(mzID, mzID, mzIDCollection)
5151
importFrom(digest, digest)
52+
importFrom(grDevices, topo.colors)
5253

5354
export(MSnSet,
5455
abstract,

R/functions-MSnExp.R

+27
Original file line numberDiff line numberDiff line change
@@ -355,3 +355,30 @@ removeReporters_MSnExp <- function(object, reporters = NULL,
355355
return(object)
356356
}
357357

358+
plotXIC_MSnExp <- function(x, ...) {
359+
## Restrict to MS level 1
360+
x <- filterMsLevel(x, 1L)
361+
if (!length(x))
362+
stop("No MS1 data available")
363+
fns <- basename(fileNames(x))
364+
if (isMSnbaseVerbose())
365+
message("Retrieving data ...", appendLF = FALSE)
366+
x <- as(x, "data.frame")
367+
x <- split(x, x$file)
368+
if (isMSnbaseVerbose())
369+
message("OK")
370+
## Check if we are greedy and plot a too large area
371+
if (any(unlist(lapply(x, nrow)) > 20000))
372+
warning("The MS area to be plotted seems rather large. It is suggested",
373+
" to restrict the data first using 'filterRt' and 'filterMz'. ",
374+
"See also ?chromatogram and ?Chromatogram for more efficient ",
375+
"functions to plot a total ion chromatogram or base peak ",
376+
"chromatogram.",
377+
immediate = TRUE, call = FALSE)
378+
## Define the layout.
379+
dots <- list(...)
380+
layout(.vertical_sub_layout(length(x)))
381+
tmp <- mapply(x, fns, FUN = function(z, main, ...) {
382+
.plotXIC(x = z, main = main, layout = NULL, ...)
383+
}, MoreArgs = dots)
384+
}

R/functions-plotting.R

+76
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,76 @@
1+
#' Takes the values for a single file.
2+
#'
3+
#' @param x `data.frame` with columns `"mz"`, `"rt"` and `"i"`.
4+
#'
5+
#' @param main `character(1)` with the title of the plot.
6+
#'
7+
#' @param col color for the circles.
8+
#'
9+
#' @param colramp color ramp to be used for the points' background.
10+
#'
11+
#' @param grid.color color to be used for the grid lines (or `NA` if they should
12+
#' not be plotted.
13+
#'
14+
#' @param pch The plotting character.
15+
#'
16+
#' @param layout `matrix` defining the layout of the plot, or `NULL` if
17+
#' `layout` was already called.
18+
#'
19+
#' @param ... additional parameters to be passed to the `plot` function.
20+
#'
21+
#' @md
22+
#'
23+
#' @author Johannes Rainer
24+
#'
25+
#' @noRd
26+
.plotXIC <- function(x, main = "", col = "grey", colramp = topo.colors,
27+
grid.color = "lightgrey", pch = 21,
28+
layout = matrix(1:2, ncol = 1), ...) {
29+
if (is.matrix(layout))
30+
layout(layout)
31+
## Chromatogram.
32+
bpi <- unlist(lapply(split(x$i, x$rt), max, na.rm = TRUE))
33+
brks <- do.breaks(range(x$i), nint = 256)
34+
par(mar = c(0, 4, 2, 1))
35+
plot(as.numeric(names(bpi)), bpi, xaxt = "n", col = col, main = main,
36+
bg = level.colors(bpi, at = brks, col.regions = colramp), xlab = "",
37+
pch = pch, ylab = "", las = 2, ...)
38+
mtext(side = 4, line = 0, "Intensity", cex = par("cex.lab"))
39+
grid(col = grid.color)
40+
par(mar = c(3.5, 4, 0, 1))
41+
plot(x$rt, x$mz, main = "", pch = pch, col = col, xlab = "", ylab = "",
42+
yaxt = "n", bg = level.colors(x$i, at = brks, col.regions = colramp),
43+
...)
44+
axis(side = 2, las = 2)
45+
grid(col = grid.color)
46+
mtext(side = 1, line = 2.5, "Retention time", cex = par("cex.lab"))
47+
mtext(side = 4, line = 0, "m/z", cex = par("cex.lab"))
48+
}
49+
50+
#' Create a `matrix` to be used for the `layout` function to allow plotting of
51+
#' vertically arranged *sub-plots* consisting of `sub_plot` plots.
52+
#'
53+
#' @param x `integer(1)` with the number of sub-plots.
54+
#'
55+
#' @param sub_plot `integer(1)` with the number of sub-plots per cell/plot.
56+
#'
57+
#' @author Johannes Rainer
58+
#'
59+
#' @md
60+
#'
61+
#' @noRd
62+
#'
63+
#' @examples
64+
#'
65+
#' ## Assum we've got 5 *features* to plot and we want to have a two plots for
66+
#' ## each feature arranged below each other.
67+
#'
68+
#' .vertical_sub_layout(5, sub_plot = 2)
69+
.vertical_sub_layout <- function(x, sub_plot = 2) {
70+
sqrt_x <- sqrt(x)
71+
ncol <- ceiling(sqrt_x)
72+
nrow <- round(sqrt_x)
73+
rws <- split(1:(ncol * nrow * sub_plot), f = rep(1:nrow,
74+
each = sub_plot * ncol))
75+
do.call(rbind, lapply(rws, matrix, ncol = ncol))
76+
}

R/methods-MSnExp.R

+13-3
Original file line numberDiff line numberDiff line change
@@ -85,7 +85,13 @@ setMethod("show", "MSnExp",
8585

8686

8787
setMethod("plot", c("MSnExp","missing"),
88-
function(x, y ,...) plot_MSnExp(x, ...))
88+
function(x, y , type = c("spectra", "XIC"), ...) {
89+
type <- match.arg(type)
90+
if (type == "spectra")
91+
plot_MSnExp(x, ...)
92+
if (type == "XIC")
93+
plotXIC_MSnExp(x, ...)
94+
})
8995

9096
setMethod("plot2d", c("MSnExp"),
9197
function(object, z, alpha = 1/3, plot = TRUE)
@@ -538,8 +544,12 @@ setMethod("chromatogram", "MSnExp", function(object, rt, mz,
538544

539545
setAs("MSnExp", "data.frame", function(from) {
540546
do.call(rbind, unname(spectrapply(from, function(z) {
541-
## Directly accessing slots is faster than using methods
542-
data.frame(file = z@fromFile, rt = z@rt, mz = z@mz, i = z@intensity)
547+
if (length(z@mz))
548+
## Directly accessing slots is faster than using methods
549+
data.frame(file = z@fromFile, rt = z@rt, mz = z@mz, i = z@intensity)
550+
else
551+
data.frame(file = integer(), rt = numeric(), mz = numeric(),
552+
i = numeric())
543553
})))
544554
})
545555
as.data.frame.MSnExp <- function(x, row.names = NULL, optional=FALSE, ...)

man/MSnExp-class.Rd

+3-3
Original file line numberDiff line numberDiff line change
@@ -186,9 +186,9 @@
186186
the noise in all profile spectra of \code{object}. See
187187
\code{\link{estimateNoise}} documentation for more details and
188188
examples. }
189-
\item{plot}{\code{signature(x = "MSnExp", y = "missing")}: Plots all
190-
the spectra of the \code{MSnExp} instance. See
191-
\code{\link{plot.MSnExp}} documentation for more details. }
189+
\item{plot}{\code{signature(x = "MSnExp", y = "missing")}: Plots
190+
the \code{MSnExp} instance. See \code{\link{plot.MSnExp}}
191+
documentation for more details. }
192192
\item{plot2d}{\code{signature(object = "MSnExp", ...)}:
193193
Plots retention time against precursor MZ for \code{MSnExp}
194194
instances. See \code{\link{plot2d}} documentation for more

man/plot-methods.Rd

+75-14
Original file line numberDiff line numberDiff line change
@@ -9,12 +9,17 @@
99
\alias{plot.Spectrum.character}
1010
\alias{plot}
1111

12-
\title{ Plotting 'Spectrum' object(s) }
12+
\title{ Plotting 'MSnExp' and 'Spectrum' object(s) }
1313

1414
\description{
1515

16-
These method plot mass spectra MZ values against the intensities. Full
17-
spectra (using the \code{full} parameter) or specific peaks of
16+
These methods provide the functionality to plot mass spectrometry data
17+
provided as \code{\linkS4class{MSnExp}},
18+
\code{\linkS4class{OnDiskMSnExp}} or \code{\linkS4class{Spectrum}}
19+
objects. Most functions plot mass spectra M/Z values against
20+
intensities.
21+
22+
Full spectra (using the \code{full} parameter) or specific peaks of
1823
interest can be plotted using the \code{reporters} parameter. If
1924
\code{reporters} are specified and \code{full} is set to 'TRUE', a
2025
sub-figure of the reporter ions is inlaid inside the full spectrum.
@@ -24,8 +29,8 @@
2429
extract spectra of interest using the \code{[} operator or
2530
\code{\link{extractPrecSpectra}} methods.
2631

27-
The methods make use the \code{ggplot2} system. An object of class
28-
'ggplot' is returned invisibly.
32+
Most methods make use the \code{ggplot2} system in which case an
33+
object of class 'ggplot' is returned invisibly.
2934

3035
If a single \code{"\linkS4class{Spectrum2}"} and a \code{"character"}
3136
representing a valid peptide sequence are passed as argument, the
@@ -46,17 +51,22 @@
4651
\item{reporters}{ An object of class
4752
\code{"\linkS4class{ReporterIons}"} that defines the peaks to be
4853
plotted. If not specified, \code{full} must be set to 'TRUE'.}
54+
4955
\item{full}{Logical indicating whether full spectrum (respectively
5056
spectra) of only reporter ions of interest should be
5157
plotted. Default is 'FALSE', in which case \code{reporters} must be
5258
defined. }
59+
5360
\item{centroided.}{Logical indicating if spectrum or spectra are in
5461
centroided mode, in which case peaks are plotted as histograms,
5562
rather than curves.}
63+
5664
\item{plot}{Logical specifying whether plot should be printed to
5765
current device. Default is 'TRUE'.}
66+
5867
\item{w1}{Width of sticks for full centroided spectra. Default is to
5968
use maximum MZ value divided by 500. }
69+
6070
\item{w2}{Width of histogram bars for centroided reporter ions
6171
plots. Default is 0.01. }
6272

@@ -66,14 +76,51 @@
6676

6777
\section{Methods}{
6878
\describe{
69-
\item{\code{signature(x = "MSnExp", y = "missing", reporters =
70-
"ReporterIons", full = "logical", plot = "logical")}}{ Plots
71-
all the spectra in the \code{MSnExp} object vertically. One of
72-
\code{reporters} must be defined or \code{full} set to 'TRUE'. In
73-
case of \code{MSnExp} objects, repoter ions are not inlaid when
74-
\code{full} is 'TRUE'.
79+
\item{\code{plot(signature(x = "MSnExp", y = "missing"),
80+
type = c("spectra", "XIC"), reporters = "ReporterIons",
81+
full = "logical", plot = "logical", ...)}}{
82+
83+
For \code{type = "spectra"}: Plots all the spectra in the
84+
\code{MSnExp} object vertically. One of \code{reporters} must be
85+
defined or \code{full} set to 'TRUE'. In case of \code{MSnExp}
86+
objects, repoter ions are not inlaid when \code{full} is 'TRUE'.
87+
88+
For \code{type = "XIC"}: Plots a combined plot of retention time
89+
against m/z values and retention time against largest signal per
90+
spectrum for each file. Data points are colored by intensity. The
91+
lower part of the plot represents the location of the individual
92+
signals in the retention time - m/z space, the upper part the base
93+
peak chromatogram of the data (i.e. the largest signal for each
94+
spectrum). This plot type is restricted to MS level 1 data and is
95+
most useful for LC-MS data.
96+
Ideally, the \code{MSnExp} (or \code{OnDiskMSnExp})
97+
object should be filtered first using the \code{\link{filterRt}}
98+
and \code{\link{filterMz}} functions to narrow on an ion of
99+
interest. See examples below. This plot uses base R
100+
plotting. Additional arguments to the \code{plot} function can be
101+
passed with \code{...}.
102+
103+
Additional arguments for \code{type = "XIC"} are:
104+
\describe{
105+
\item{\code{col}}{color for the border of the points. Defaults to
106+
\code{col = "grey"}.}
107+
108+
\item{\code{colramp}}{color function/ramp to be used for the
109+
intensity-dependent background color of data points. Defaults
110+
to \code{colramp = topo.colors}.}
111+
112+
\item{\code{grid.color}}{color for the grid lines. Defaults to
113+
\code{grid.color = "lightgrey"}; use \code{grid.color = NA} to
114+
disable grid lines altogether.}
115+
116+
\item{\code{pch}}{point character. Defaults to \code{pch = 21}}.
117+
118+
\item{\code{...}}{additional parameters for the low-level
119+
\code{plot} function.}
120+
121+
}
75122
}
76-
\item{\code{signature(x = "Spectrum", y = "missing", reporters =
123+
\item{\code{plot(signature(x = "Spectrum", y = "missing"), reporters =
77124
"ReporterIons", full = "logical", centroided. = "logical", plot =
78125
"logical", w1, w2)}}{ Displays the MZs against intensities of
79126
the \code{Spectrum} object as a line plot.
@@ -85,7 +132,7 @@
85132
by default.
86133
}
87134

88-
\item{\code{signature(x = "Spectrum2", y = "character", orientation
135+
\item{\code{plot(signature(x = "Spectrum2", y = "character"), orientation
89136
= "numeric", add = "logical", col = "character", pch, xlab =
90137
"character", ylab = "character", xlim = "numeric", ylim =
91138
"numeric", tolerance = "numeric", relative = "logical", type =
@@ -111,10 +158,12 @@
111158
\code{\link{calculateFragments}} to calculate ions produced by
112159
fragmentation and \code{\link{plot.Spectrum.Spectrum}} to plot and
113160
compare 2 spectra and their shared peaks.
161+
162+
\code{\link{Chromatogram}} for plotting of chromatographic data.
114163
}
115164

116165
\author{
117-
Laurent Gatto <lg390@cam.ac.uk> and Sebastian Gibb
166+
Laurent Gatto <lg390@cam.ac.uk>, Johannes Rainer and Sebastian Gibb
118167
}
119168

120169
\examples{
@@ -129,6 +178,18 @@ itraqdata2 <- pickPeaks(itraqdata)
129178
i <- 14
130179
s <- as.character(fData(itraqdata2)[i, "PeptideSequence"])
131180
plot(itraqdata2[[i]], s, main = s)
181+
182+
## Load profile-mode LC-MS files
183+
library(msdata)
184+
od <- readMSData(dir(system.file("sciex", package = "msdata"),
185+
full.names = TRUE), mode = "onDisk")
186+
## Restrict the MS data to signal for serine
187+
serine <- filterMz(filterRt(od, rt = c(175, 190)), mz = c(106.04, 106.06))
188+
plot(serine, type = "XIC")
189+
190+
## Same plot but using heat.colors, rectangles and no point border
191+
plot(serine, type = "XIC", pch = 22, colramp = heat.colors, col = NA)
192+
132193
}
133194

134195
\keyword{methods}

tests/testthat/test_MSnExp.R

+11
Original file line numberDiff line numberDiff line change
@@ -506,3 +506,14 @@ test_that("setAs,MSnExp,data.frame works", {
506506
expect_equal(unlist(mz(res), use.names = FALSE), df$mz)
507507
expect_equal(unlist(intensity(res), use.names = FALSE), df$i)
508508
})
509+
510+
511+
test_that("plotXIC_MSnExp works", {
512+
im <- microtofq_in_mem_ms1
513+
expect_warning(plotXIC_MSnExp(filterMz(im, c(600, 680))))
514+
plotXIC_MSnExp(filterMz(im, c(610, 615)), pch = 23)
515+
## filter to get only one
516+
plotXIC_MSnExp(filterMz(filterRt(im, c(270, 280)), c(610, 615)), cex = 2)
517+
518+
expect_error(plotXIC_MSnExp(tmt_erwinia_in_mem_ms2))
519+
})

0 commit comments

Comments
 (0)