| plot-methods {Cardinal} | R Documentation |
Create and display plots for the feature data of an imaging dataset. This uses a formula interface inspired by the lattice graphics package.
## Methods for Cardinal version >= 2.0.0 classes
## S4 method for signature 'XDataFrame,missing'
plot(x, formula,
groups = NULL,
superpose = FALSE,
strip = TRUE,
key = superpose || !is.null(groups),
...,
xlab, xlim,
ylab, ylim,
layout,
col = discrete.colors,
subset = TRUE,
add = FALSE)
## S4 method for signature 'SparseImagingExperiment,missing'
plot(x, formula,
pixel,
pixel.groups,
groups = NULL,
superpose = FALSE,
strip = TRUE,
key = superpose || !is.null(groups),
fun = mean,
...,
xlab, xlim,
ylab, ylim,
layout,
col = discrete.colors,
subset = TRUE,
add = FALSE)
## S4 method for signature 'MSImagingExperiment,missing'
plot(x, formula,
pixel = pixels(x, coord=coord),
pixel.groups,
coord,
plusminus,
...,
xlab, ylab,
type = if (centroided(x)) 'h' else 'l')
## Methods for Cardinal version >= 1.0.0 classes
## S4 method for signature 'SImageSet,missing'
plot(x, formula = ~ Feature,
pixel,
pixel.groups,
groups = NULL,
superpose = FALSE,
strip = TRUE,
key = FALSE,
fun = mean,
...,
xlab,
xlim,
ylab,
ylim,
layout,
type = 'l',
col = "black",
subset = TRUE,
lattice = FALSE)
## S4 method for signature 'MSImageSet,missing'
plot(x, formula = ~ mz,
pixel = pixels(x, coord=coord),
pixel.groups,
coord,
plusminus,
...,
type = if (centroided(x)) 'h' else 'l')
## S4 method for signature 'ResultSet,missing'
plot(x, formula,
model = pData(modelData(x)),
pixel,
pixel.groups,
superpose = TRUE,
strip = TRUE,
key = superpose,
...,
xlab,
ylab,
column,
col = if (superpose) rainbow(nlevels(pixel.groups)) else "black",
lattice = FALSE)
## S4 method for signature 'CrossValidated,missing'
plot(x, fold = 1:length(x), layout, ...)
## S4 method for signature 'PCA,missing'
plot(x, formula = substitute(mode ~ mz),
mode = "loadings",
type = 'h',
...)
## S4 method for signature 'PLS,missing'
plot(x, formula = substitute(mode ~ mz),
mode = c("coefficients", "loadings",
"weights", "projection"),
type = 'h',
...)
## S4 method for signature 'OPLS,missing'
plot(x, formula = substitute(mode ~ mz),
mode = c("coefficients", "loadings", "Oloadings",
"weights", "Oweights", "projection"),
type = 'h',
...)
## S4 method for signature 'SpatialShrunkenCentroids,missing'
plot(x, formula = substitute(mode ~ mz),
mode = c("centers", "tstatistics"),
type = 'h',
...)
## S4 method for signature 'SpatialKMeans,missing'
plot(x, formula = substitute(mode ~ mz),
mode = c("centers", "betweenss", "withinss"),
type = 'h',
...)
x |
An imaging dataset. |
formula |
A formula of the form 'y ~ x | g1 * g2 * ...' (or equivalently, 'y ~ x | g1 + g2 + ...'), indicating a LHS 'y' (on the y-axis) versus a RHS 'x' (on the x-axis) and conditioning variables 'g1, g2, ...'. Usually, the LHS is not supplied, and the formula is of the form '~ x | g1 * g2 * ...', and the y-axis is implicityl assumed to be the feature vectors corresponding to each pixel in the imaging dataset specified by the object 'x'. However, a variable evaluating to a feature vector, or a sequence of such variables, can also be supplied. The RHS is evaluated in The conditioning variables are evaluated in |
model |
A vector or |
pixel |
The pixel or vector of pixels for which to plot the feature vectors. This is an expression that evaluates to a logical or integer indexing vector. |
pixel.groups |
An alternative way to express a single conditioning variable. This is a variable or expression to be evaluated in |
groups |
A variable or expression to be evaluated in |
superpose |
Should feature vectors from different pixel groups specified by 'pixel.groups' be superposed on the same plot? |
strip |
Should strip labels indicating the plotting group be plotting along with the each panel? Passed to 'strip' in |
key |
A logical, or |
fun |
A function to apply over feature vectors grouped together by 'pixel.groups'. By default, this is used for averaging over pixels. |
xlab |
Character or expression giving the label for the x-axis. |
ylab |
Character or expression giving the label for the x-axis. |
xlim |
A numeric vector of length 2 giving the left and right limits for the x-axis. |
ylim |
A numeric vector of length 2 giving the lower and upper limits for the y-axis. |
layout |
The layout of the plots, given by a length 2 numeric as |
col |
A specification for the default plotting color(s). |
type |
A character indicating the type of plotting. |
subset |
An expression that evaluates to a logical or integer indexing vector to be evaluated in |
lattice |
Should lattice graphics be used to create the plot? |
add |
Should the method call |
... |
Additional arguments passed to the underlying |
coord |
A named vector or list giving the coordinate of the pixel to plot. |
plusminus |
If specified, a window of pixels surrounding the one given by |
fold |
What folds of the cross-validation should be plotted. |
mode |
What kind of results should be plotted. This is the name of the object to plot in the |
column |
What columns of the results should be plotted. If the results are a matrix, this corresponds to the columns to be plotted, which can be indicated either by numeric index or by name. |
Kylie A. Bemis
data <- matrix(c(NA, NA, 1, 1, NA, NA, NA, NA, NA, NA, 1, 1, NA, NA,
NA, NA, NA, NA, NA, 0, 1, 1, NA, NA, NA, NA, NA, 1, 0, 0, 1,
1, NA, NA, NA, NA, NA, 0, 1, 1, 1, 1, NA, NA, NA, NA, 0, 1, 1,
1, 1, 1, NA, NA, NA, NA, 1, 1, 1, 1, 1, 1, 1, NA, NA, NA, 1,
1, NA, NA, NA, NA, NA, NA, 1, 1, NA, NA, NA, NA, NA), nrow=9, ncol=9)
set.seed(1)
sset <- generateImage(data, range=c(1000,5000), centers=c(3000,4000), resolution=100)
pData(sset)$pg <- factor(data[is.finite(data)], labels=c("black", "red"))
fData(sset)$fg <- factor(rep("bg", nrow(fData(sset))), levels=c("bg", "black", "red"))
fData(sset)$fg[2950 < fData(sset)$t & fData(sset)$t < 3050] <- "black"
fData(sset)$fg[3950 < fData(sset)$t & fData(sset)$t < 4050] <- "red"
plot(sset, pixel=1)
plot(sset, ~ t, pixel=1:ncol(sset))
plot(sset, ~ t | pg, pixel=1:ncol(sset), lattice=TRUE)
plot(sset, ~ t, pixel.groups=pg, pixel=1:ncol(sset), lattice=TRUE, superpose=TRUE)
plot(sset, ~ t | pg, groups=fg, pixel=1:ncol(sset), lattice=TRUE)
set.seed(1)
msset <- generateImage(data, as="MSImageSet", resolution=50)
plot(msset, pixel=1)
plot(msset, coord=list(x=3, y=1))
plot(msset, coord=list(x=3, y=1), plusminus=1)
plot(msset, coord=list(x=5, y=5), plusminus=c(2, 1))