It's an S4
method.
> errBarchart
standardGeneric for "errBarchart" defined from package "ddCt"
function (object, by, ...)
standardGeneric("errBarchart")
<bytecode: 0x0000016d025959c8>
<environment: 0x0000016d02592068>
Methods may be defined for arguments: object, by
Use showMethods(errBarchart) for currently available ones.
And you should note that the message at the bottom gives you a hint!
> showMethods(errBarchart)
Function: errBarchart (package ddCt)
object="ddCtExpression", by="character"
object="ddCtExpression", by="missing"
But that's pretty boring, and no helpful messages! If you search around, you will find that there are two choices for showing the function body. Use the 'includeDefs' argument to showMethods
(useful if there aren't too many things that it dispatches on), or selectMethod
. Let's try both.
> showMethods(errBarchart, includeDefs = TRUE)
Function: errBarchart (package ddCt)
object="ddCtExpression", by="character"
function (object, by, ...)
{
res <- elist(object)
ddCtErrBarchart(res, by = by, ...)
}
object="ddCtExpression", by="missing"
function (object, by, ...)
{
res <- elist(object)
ddCtErrBarchart(res, by = "Sample", ...)
}
> selectMethod(errBarchart, c(object="ddCtExpression", by="character"))
Method Definition:
function (object, by, ...)
{
res <- elist(object)
ddCtErrBarchart(res, by = by, ...)
}
<bytecode: 0x0000016d02598e68>
<environment: namespace:ddCt>
Signatures:
object by
target "ddCtExpression" "character"
defined "ddCtExpression" "character"
So now we know that it's just passing data to another function called ddCtErrBarchart
. Let's look at that.
> ddCtErrBarchart
Error: object 'ddCtErrBarchart' not found
It seems unlikely that the function doesn't exist (it does exist!), so why can't it be found? It's because the function is not exported from the NAMESPACE
for ddCt
, which is good, because you don't want to pollute the search path with extraneous functions. But how to get the function?
> getAnywhere(ddCtErrBarchart)
A single object matching 'ddCtErrBarchart' was found
It was found in the following places
namespace:ddCt
with value
function (x, by = c("Sample", "Detector"), thr = 3, ylab = "Expression fold change",
cols = brewer.pal(12, "Set3"), round = 0, outText = TRUE,
rot = 45, parameter = new("errBarchartParameter"), detector.levels = levels(factor(as.character(x$Detector))),
sample.levels = levels(factor(as.character(x$Sample))), ...)
{
if (all(is.na(x$exprs)))
stop("All expressions are NA!\n")
x$Sample <- factor(as.character(x$Sample), sample.levels)
x$Detector <- factor(as.character(x$Detector), detector.levels)
by <- match.arg(by, choices = c("Sample", "Detector"))
if (by == "Sample") {
formula <- as.formula("exprs + level.err ~ Sample | Detector")
}
else {
formula <- as.formula("exprs + level.err ~ Detector | Sample")
}
xlab <- by
barchart(formula, data = x, scales = list(x = list(rot = rot),
y = list(alternating = 1, at = seq(0, thr, 0.5))), ylim = c(0,
thr * 1.1), panel = function(x, y, ...) panel.ddCtErrBarchart(x = x,
y = y, thr = thr, round = round, outText = outText, parameter = parameter,
...), xlab = xlab, ylab = ylab, col = cols, ...)
}
<bytecode: 0x0000016d03ab7938>
<environment: namespace:ddCt>
Note at the bottom that it says the namespace for the function, so (if you already know where it lives) you can access using the :::
function
> ddCt:::ddCtErrBarchart
function (x, by = c("Sample", "Detector"), thr = 3, ylab = "Expression fold change",
cols = brewer.pal(12, "Set3"), round = 0, outText = TRUE,
rot = 45, parameter = new("errBarchartParameter"), detector.levels = levels(factor(as.character(x$Detector))),
sample.levels = levels(factor(as.character(x$Sample))), ...)
{
if (all(is.na(x$exprs)))
stop("All expressions are NA!\n")
x$Sample <- factor(as.character(x$Sample), sample.levels)
x$Detector <- factor(as.character(x$Detector), detector.levels)
by <- match.arg(by, choices = c("Sample", "Detector"))
if (by == "Sample") {
formula <- as.formula("exprs + level.err ~ Sample | Detector")
}
else {
formula <- as.formula("exprs + level.err ~ Detector | Sample")
}
xlab <- by
barchart(formula, data = x, scales = list(x = list(rot = rot),
y = list(alternating = 1, at = seq(0, thr, 0.5))), ylim = c(0,
thr * 1.1), panel = function(x, y, ...) panel.ddCtErrBarchart(x = x,
y = y, thr = thr, round = round, outText = outText, parameter = parameter,
...), xlab = xlab, ylab = ylab, col = cols, ...)
}
<bytecode: 0x0000016d03ab7938>
<environment: namespace:ddCt>
Anyway, errBarchart
allows you to pass arbitrary arguments down to subsequent functions via the ...
argument, and you can see that the 'thr' argument controls the vertical axis limits, so you can just add 'thr = 4' to your call and you will then get a wider range for the vertical axis.