CompleteChannel-class {PreProcess} | R Documentation |
An object of the CompleteChannel class represents one channel (red or green) of a two-color fluorescence microarray experiment. Alternatively, it can also represent the entirety of a radioactive microarray experiment. Affymetrix experiments produce data with a somewhat different structure because they use multiple probes for each target gene.
CompleteChannel(name, type, data) ## S4 method for signature 'CompleteChannel': print(x, ...) ## S4 method for signature 'CompleteChannel': summary(object, ...) ## S4 method for signature 'CompleteChannel': as.data.frame(x, row.names=NULL, optional=FALSE) ## S4 method for signature 'CompleteChannel, missing': plot(x, useLog=FALSE, ...) ## S4 method for signature 'CompleteChannel': image(x, ...) ## S4 method for signature 'CompleteChannel': analyze(object, useLog=FALSE, ...) ## S4 method for signature 'CompleteChannel, Processor': process(object, action, parameter) ## S4 method for signature 'CompleteChannel': channelize(object)
name |
A string containing the name of the object |
type |
A ChannelType object |
data |
A data frame. For the pre-defined ``extraction''
processors to work correctly, this should include columns called
vol , bkgd , svol , SD , and SN . |
x |
A CompleteChannel object |
object |
A CompleteChannel object |
useLog |
A logical value |
action |
A Processor object used to process a
CompleteChannel . |
parameter |
Any object that makes sense as a parameter to the
function represented by the Processor action |
row.names |
See as.data.frame |
optional |
See as.data.frame |
... |
Additional arguments are as in the underlying generic methods. |
The names come from the default column names in the ArrayVision software package used at M.D. Anderson for quantifying glass or nylon microarrays. Column names used by other software packages should be mapped to these.
The analyze
method returns a list of three density functions.
The return value of the process
function depends on the
Processor
performing the action, but is typically a
Channel
object.
Graphical methods invisibly return the object on which they were
invoked.
name
:type
:ChannelType
objectdata
:history
:CompleteChannel
object into a data frame. As you might
expect, this simply returns the data frame in the data
slot
of the object.useLog
determines
whether the data are log-transformed before estimating and
plotting densities.Channel
objects to produce geographically aligned
images of the log-transformed intensity and background estimates.CompleteChannel
object.Processor
action
to process the
CompleteChannel
object
. Returns an object of the
class described by channelize
, which defaults to
Channel
.
The library comes with several Processor
objects already
defined; each one takes a CompleteChannel
as input, extracts a
single value per spot, and produces a Channel
as output.
PROC.BACKGROUND
PROC.SIGNAL
PROC.CORRECTED.SIGNAL
PROC.NEG.CORRECTED.SIGNAL
PROC.SD.SIGNAL
PROC.SIGNAL.TO.NOISE
Kevin R. Coombes <kcoombes@mdanderson.org>
process
, Processor
,
Pipeline
, Channel
, as.data.frame
# simulate a complete channel object v <- rexp(10000, 1/1000) b <- rnorm(10000, 60, 6) s <- sapply(v-b, function(x) {max(0, x)}) ct <- ChannelType('user', 'random', 100, 100, 'fake') x <- CompleteChannel(name='fraud', type=ct, data=data.frame(vol=v, bkgd=b, svol=s)) rm(v, b, s, ct) summary(x) opar <- par(mfrow=c(2,3)) plot(x) plot(x, main='Log Scale', useLog=TRUE) par(opar) opar <- par(mfrow=c(2,1)) image(x) par(opar) b <- process(x, PROC.NEG.CORRECTED.SIGNAL) summary(b) q <- process(b, PIPELINE.STANDARD) summary(q) q <- process(x, PIPELINE.MDACC.DEFAULT) summary(q) # cleanup rm(x, b, q, opar)