- remove col argument from plotMDS(), as it handled by ... as are
other graphics arguments.
- vennDiagram() now supports circles of different colors for any
number of circles. Previously this was supported only up to three
sets.
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/limma@91932 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,6 +1,6 @@ |
1 | 1 |
Package: limma |
2 |
-Version: 3.21.9 |
|
3 |
-Date: 2014/06/24 |
|
2 |
+Version: 3.21.10 |
|
3 |
+Date: 2014/06/27 |
|
4 | 4 |
Title: Linear Models for Microarray Data |
5 | 5 |
Description: Data analysis, linear models and differential expression for microarray data. |
6 | 6 |
Author: Gordon Smyth [cre,aut], Matthew Ritchie [ctb], Jeremy Silver [ctb], James Wettenhall [ctb], Natalie Thorne [ctb], Davis McCarthy [ctb], Di Wu [ctb], Yifang Hu [ctb], Wei Shi [ctb], Belinda Phipson [ctb], Alicia Oshlack [ctb], Carolyn de Graaf [ctb], Mette Langaas [ctb], Egil Ferkingstad [ctb], Marcus Davy [ctb], Francois Pepin [ctb], Dongseok Choi [ctb] |
... | ... |
@@ -10,11 +10,11 @@ setMethod("show","MDS",function(object) { |
10 | 10 |
|
11 | 11 |
plotMDS <- function(x,...) UseMethod("plotMDS") |
12 | 12 |
|
13 |
-plotMDS.MDS <- function(x,labels=NULL,pch=NULL,col=NULL,cex=1,dim.plot=x$dim.plot,xlab=paste("Dimension",dim.plot[1]),ylab=paste("Dimension",dim.plot[2]),...) |
|
13 |
+plotMDS.MDS <- function(x,labels=NULL,pch=NULL,cex=1,dim.plot=x$dim.plot,xlab=paste("Dimension",dim.plot[1]),ylab=paste("Dimension",dim.plot[2]),...) |
|
14 | 14 |
# Method for MDS objects |
15 | 15 |
# Create a new plot using MDS coordinates or distances previously created |
16 | 16 |
# Gordon Smyth and Yifang Hu |
17 |
-# 21 May 2011. Last modified 2 June 2014 |
|
17 |
+# 21 May 2011. Last modified 26 June 2014 |
|
18 | 18 |
{ |
19 | 19 |
# Check labels |
20 | 20 |
if(is.null(labels) & is.null(pch)) { |
... | ... |
@@ -33,7 +33,7 @@ plotMDS.MDS <- function(x,labels=NULL,pch=NULL,col=NULL,cex=1,dim.plot=x$dim.plo |
33 | 33 |
# Make the plot |
34 | 34 |
if(is.null(labels)){ |
35 | 35 |
# Plot symbols instead of text |
36 |
- plot(x$x, x$y, pch = pch, xlab = xlab, ylab = ylab, col = col, cex = cex, ...) |
|
36 |
+ plot(x$x, x$y, pch = pch, xlab = xlab, ylab = ylab, cex = cex, ...) |
|
37 | 37 |
} else { |
38 | 38 |
# Plot text. Need to estimate width of labels in plot coordinates. |
39 | 39 |
# Estimate will be ok for default plot width, but maybe too small for smaller plots. |
... | ... |
@@ -42,16 +42,16 @@ plotMDS.MDS <- function(x,labels=NULL,pch=NULL,col=NULL,cex=1,dim.plot=x$dim.plo |
42 | 42 |
left.x <- x$x-StringRadius |
43 | 43 |
right.x <- x$x+StringRadius |
44 | 44 |
plot(c(left.x, right.x), c(x$y, x$y), type = "n", xlab = xlab, ylab = ylab, ...) |
45 |
- text(x$x, x$y, labels = labels, col = col, cex = cex) |
|
45 |
+ text(x$x, x$y, labels = labels, cex = cex, ...) |
|
46 | 46 |
} |
47 | 47 |
|
48 | 48 |
return(invisible(x)) |
49 | 49 |
} |
50 | 50 |
|
51 |
-plotMDS.default <- function(x,top=500,labels=NULL,pch=NULL,col=NULL,cex=1,dim.plot=c(1,2),ndim=max(dim.plot),gene.selection="pairwise",xlab=paste("Dimension",dim.plot[1]),ylab=paste("Dimension",dim.plot[2]),...) |
|
51 |
+plotMDS.default <- function(x,top=500,labels=NULL,pch=NULL,cex=1,dim.plot=c(1,2),ndim=max(dim.plot),gene.selection="pairwise",xlab=paste("Dimension",dim.plot[1]),ylab=paste("Dimension",dim.plot[2]),...) |
|
52 | 52 |
# Multi-dimensional scaling with top-distance |
53 | 53 |
# Di Wu and Gordon Smyth |
54 |
-# 19 March 2009. Last modified 22 May 2014 |
|
54 |
+# 19 March 2009. Last modified 26 June 2014 |
|
55 | 55 |
{ |
56 | 56 |
# Check x |
57 | 57 |
x <- as.matrix(x) |
... | ... |
@@ -105,5 +105,5 @@ plotMDS.default <- function(x,top=500,labels=NULL,pch=NULL,col=NULL,cex=1,dim.pl |
105 | 105 |
mds <- new("MDS",list(dim.plot=dim.plot,distance.matrix=dd,cmdscale.out=a1,top=top,gene.selection=gene.selection)) |
106 | 106 |
mds$x <- a1[,dim.plot[1]] |
107 | 107 |
mds$y <- a1[,dim.plot[2]] |
108 |
- plotMDS(mds,labels=labels,pch=pch,col=col,cex=cex,xlab=xlab,ylab=ylab,...) |
|
108 |
+ plotMDS(mds,labels=labels,pch=pch,cex=cex,xlab=xlab,ylab=ylab,...) |
|
109 | 109 |
} |
... | ... |
@@ -161,9 +161,9 @@ vennDiagram <- function(object,include="both",names=NULL,mar=rep(1,4),cex=c(1.5, |
161 | 161 |
rect(-20, -20, 420, 400) |
162 | 162 |
elps <- cbind(162*cos(seq(0,2*pi,len=1000)), 108*sin(seq(0,2*pi,len=1000))) |
163 | 163 |
polygon(relocate_elp(elps, 45, 130, 170),border=circle.col[1],lwd=lwd) |
164 |
- polygon(relocate_elp(elps, 45, 200, 200),border=circle.col[1],lwd=lwd) |
|
165 |
- polygon(relocate_elp(elps, 135, 200, 200),border=circle.col[1],lwd=lwd) |
|
166 |
- polygon(relocate_elp(elps, 135, 270, 170),border=circle.col[1],lwd=lwd) |
|
164 |
+ polygon(relocate_elp(elps, 45, 200, 200),border=circle.col[2],lwd=lwd) |
|
165 |
+ polygon(relocate_elp(elps, 135, 200, 200),border=circle.col[3],lwd=lwd) |
|
166 |
+ polygon(relocate_elp(elps, 135, 270, 170),border=circle.col[4],lwd=lwd) |
|
167 | 167 |
|
168 | 168 |
text( 35, 315, names[1], cex=cex[1]) |
169 | 169 |
text(138, 350, names[2], cex=cex[1]) |
... | ... |
@@ -221,10 +221,10 @@ vennDiagram <- function(object,include="both",names=NULL,mar=rep(1,4),cex=c(1.5, |
221 | 221 |
|
222 | 222 |
elps <- cbind(150*cos(seq(0,2*pi,len=1000)), 60*sin(seq(0,2*pi,len=1000))) |
223 | 223 |
polygon(relocate_elp(elps, 90,200, 250),border=circle.col[1],lwd=lwd) |
224 |
- polygon(relocate_elp(elps, 162,250, 220),border=circle.col[1],lwd=lwd) |
|
225 |
- polygon(relocate_elp(elps, 234,250, 150),border=circle.col[1],lwd=lwd) |
|
226 |
- polygon(relocate_elp(elps, 306,180, 125),border=circle.col[1],lwd=lwd) |
|
227 |
- polygon(relocate_elp(elps, 378,145, 200),border=circle.col[1],lwd=lwd) |
|
224 |
+ polygon(relocate_elp(elps, 162,250, 220),border=circle.col[2],lwd=lwd) |
|
225 |
+ polygon(relocate_elp(elps, 234,250, 150),border=circle.col[3],lwd=lwd) |
|
226 |
+ polygon(relocate_elp(elps, 306,180, 125),border=circle.col[4],lwd=lwd) |
|
227 |
+ polygon(relocate_elp(elps, 378,145, 200),border=circle.col[5],lwd=lwd) |
|
228 | 228 |
|
229 | 229 |
text( 50, 285, names[1],cex=cex[1]) |
230 | 230 |
text(200, 415, names[2],cex=cex[1]) |
... | ... |
@@ -1,3 +1,12 @@ |
1 |
+27 June 2014: limma 3.21.10 |
|
2 |
+ |
|
3 |
+- remove col argument from plotMDS(), as it handled by ... as are |
|
4 |
+ other graphics arguments. |
|
5 |
+ |
|
6 |
+- vennDiagram() now supports circles of different colors for any |
|
7 |
+ number of circles. Previously this was supported only up to three |
|
8 |
+ sets. |
|
9 |
+ |
|
1 | 10 |
23 June 2014: limma 3.21.9 |
2 | 11 |
|
3 | 12 |
- new function goana() for gene ontology analysis of DE results from |
... | ... |
@@ -8,14 +8,14 @@ Produces an ANOVA table useful for quality assessment by decomposing between and |
8 | 8 |
This method produces a single ANOVA Table rather than one for each gene and is not used to identify differentially expressed genes. |
9 | 9 |
} |
10 | 10 |
\section{Usage}{ |
11 |
-\code{anova(object,design=NULL,ndups=2,...)} |
|
11 |
+\code{anova(object,design=NULL,ndups=2,\dots)} |
|
12 | 12 |
} |
13 | 13 |
\section{Arguments}{ |
14 | 14 |
\describe{ |
15 | 15 |
\item{\code{object}}{object of class \code{MAList}. Missing values in the M-values are not allowed.} |
16 | 16 |
\item{\code{design}}{numeric vector or single-column matrix containing the design matrix for linear model. The length of the vector or the number of rows of the matrix should agree with the number of columns of M.} |
17 | 17 |
\item{\code{ndups}}{number of duplicate spots. Each gene is printed ndups times in adjacent spots on each array.} |
18 |
- \item{\code{...}}{other arguments are not used} |
|
18 |
+ \item{\code{\dots}}{other arguments are not used} |
|
19 | 19 |
} |
20 | 20 |
} |
21 | 21 |
\section{Details}{ |
... | ... |
@@ -8,7 +8,7 @@ |
8 | 8 |
Turn a \code{MArrayLM} object into a \code{data.frame}. |
9 | 9 |
} |
10 | 10 |
\usage{ |
11 |
-\method{as.data.frame}{MArrayLM}(x, row.names = NULL, optional = FALSE, ...) |
|
11 |
+\method{as.data.frame}{MArrayLM}(x, row.names = NULL, optional = FALSE, \dots) |
|
12 | 12 |
} |
13 | 13 |
\arguments{ |
14 | 14 |
\item{x}{an object of class \code{MArrayLM}} |
... | ... |
@@ -6,7 +6,7 @@ Fit a linear model genewise to expression data from a series of microarrays. |
6 | 6 |
The fit is by generalized least squares allowing for correlation between duplicate spots or related arrays. |
7 | 7 |
This is a utility function for \code{lmFit}. |
8 | 8 |
} |
9 |
-\usage{gls.series(M,design=NULL,ndups=2,spacing=1,block=NULL,correlation=NULL,weights=NULL,...)} |
|
9 |
+\usage{gls.series(M,design=NULL,ndups=2,spacing=1,block=NULL,correlation=NULL,weights=NULL,\dots)} |
|
10 | 10 |
\arguments{ |
11 | 11 |
\item{M}{numeric matrix containing log-ratio or log-expression values for a series of microarrays, rows correspond to genes and columns to arrays.} |
12 | 12 |
\item{design}{numeric design matrix defining the linear model, with rows corresponding to arrays and columns to comparisons to be estimated. The number of rows must match the number of columns of \code{M}. Defaults to the unit vector meaning that the arrays are treated as replicates.} |
... | ... |
@@ -16,7 +16,7 @@ This is a utility function for \code{lmFit}. |
16 | 16 |
Same length as \code{ncol(M)}.} |
17 | 17 |
\item{correlation}{numeric value specifying the inter-duplicate or inter-block correlation.} |
18 | 18 |
\item{weights}{an optional numeric matrix of the same dimension as \code{M} containing weights for each spot. If it is of different dimension to \code{M}, it will be filled out to the same size.} |
19 |
- \item{...}{other optional arguments to be passed to \code{dupcor.series}.} |
|
19 |
+ \item{\dots}{other optional arguments to be passed to \code{dupcor.series}.} |
|
20 | 20 |
} |
21 | 21 |
\value{ |
22 | 22 |
A list with components |
... | ... |
@@ -8,10 +8,10 @@ Creates a heat diagram showing the co-regulation of genes under one condition wi |
8 | 8 |
\usage{ |
9 | 9 |
heatDiagram(results, coef, primary=1, names=NULL, treatments=colnames(coef), limit=NULL, |
10 | 10 |
orientation="landscape", low="green", high="red", cex=1, mar=NULL, |
11 |
- ncolors=123, ...) |
|
11 |
+ ncolors=123, \dots) |
|
12 | 12 |
heatdiagram(stat, coef, primary=1, names=NULL, treatments=colnames(stat), |
13 | 13 |
critical.primary=4, critical.other=3, limit=NULL, orientation="landscape", |
14 |
- low="green", high="red", cex=1, mar=NULL, ncolors=123, ...) |
|
14 |
+ low="green", high="red", cex=1, mar=NULL, ncolors=123, \dots) |
|
15 | 15 |
} |
16 | 16 |
\arguments{ |
17 | 17 |
\item{results}{\code{TestResults} matrix, containing elements -1, 0 or 1, from \code{\link{decideTests}}} |
... | ... |
@@ -30,7 +30,7 @@ heatdiagram(stat, coef, primary=1, names=NULL, treatments=colnames(stat), |
30 | 30 |
\item{cex}{factor to increase or decrease size of column and row text} |
31 | 31 |
\item{mar}{numeric vector of length four giving the size of the margin widths. |
32 | 32 |
Default is \code{cex*c(5,6,1,1)} for landscape and \code{cex*c(1,1,4,3)} for portrait.} |
33 |
- \item{...}{any other arguments will be passed to the \code{image} function} |
|
33 |
+ \item{\dots}{any other arguments will be passed to the \code{image} function} |
|
34 | 34 |
} |
35 | 35 |
\details{ |
36 | 36 |
Users are encouraged to use \code{heatDiagram} rather than \code{heatdiagram} as the later function may be removed in future versions of limma. |
... | ... |
@@ -8,7 +8,7 @@ This function can be used to explore any spatial effects across the microarray. |
8 | 8 |
} |
9 | 9 |
\usage{ |
10 | 10 |
imageplot(z, layout, low = NULL, high = NULL, ncolors = 123, zerocenter = NULL, |
11 |
-zlim = NULL, mar=c(2,1,1,1), legend=TRUE, ...) |
|
11 |
+zlim = NULL, mar=c(2,1,1,1), legend=TRUE, \dots) |
|
12 | 12 |
} |
13 | 13 |
\arguments{ |
14 | 14 |
\item{z}{numeric vector or array. This vector can contain any spot |
... | ... |
@@ -32,7 +32,7 @@ the interval \code{zlim} will be truncated to the relevant limit.} |
32 | 32 |
\item{mar}{numeric vector of length 4 specifying the width of the margin around the plot. |
33 | 33 |
This argument is passed to \code{\link[graphics]{par}}.} |
34 | 34 |
\item{legend}{logical, if \code{TRUE} the range of \code{z} and \code{zlim} is shown in the bottom margin} |
35 |
-\item{...}{any other arguments will be passed to the function image} |
|
35 |
+\item{\dots}{any other arguments will be passed to the function image} |
|
36 | 36 |
} |
37 | 37 |
\details{ |
38 | 38 |
This function may be used to plot the values of any spot-specific statistic, such as the log intensity ratio, background intensity or a quality |
... | ... |
@@ -6,7 +6,7 @@ Write imageplots to files in PNG format, six plots to a file in a 3 by 2 grid ar |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 | 8 |
imageplot3by2(RG, z="Gb", prefix=paste("image",z,sep="-"), path=NULL, |
9 |
- zlim=NULL, common.lim=TRUE, ...) |
|
9 |
+ zlim=NULL, common.lim=TRUE, \dots) |
|
10 | 10 |
} |
11 | 11 |
\arguments{ |
12 | 12 |
\item{RG}{an \code{RGList} or \code{MAList} object, or any list with component named by \code{z}} |
... | ... |
@@ -15,7 +15,7 @@ imageplot3by2(RG, z="Gb", prefix=paste("image",z,sep="-"), path=NULL, |
15 | 15 |
\item{path}{character string specifying directory for output files} |
16 | 16 |
\item{zlim}{numeric vector of length 2, giving limits of response vector to be associated with saturated colors} |
17 | 17 |
\item{common.lim}{logical, should all plots on a page use the same axis limits} |
18 |
- \item{...}{any other arguments are passed to \code{imageplot}} |
|
18 |
+ \item{\dots}{any other arguments are passed to \code{imageplot}} |
|
19 | 19 |
} |
20 | 20 |
|
21 | 21 |
\details{ |
... | ... |
@@ -4,7 +4,7 @@ |
4 | 4 |
\description{Fit linear model for each gene given a series of arrays} |
5 | 5 |
\usage{ |
6 | 6 |
lmFit(object, design=NULL, ndups=1, spacing=1, block=NULL, correlation, weights=NULL, |
7 |
- method="ls", ...) |
|
7 |
+ method="ls", \dots) |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{object}{object of class \code{numeric}, \code{matrix}, \code{MAList}, \code{EList}, \code{marrayNorm}, \code{ExpressionSet} or \code{PLMset} containing log-ratios or log-values of expression for a series of microarrays} |
... | ... |
@@ -15,7 +15,7 @@ lmFit(object, design=NULL, ndups=1, spacing=1, block=NULL, correlation, weights= |
15 | 15 |
\item{correlation}{the inter-duplicate or inter-technical replicate correlation} |
16 | 16 |
\item{weights}{non-negative observation weights. Can be a numeric matrix of individual weights, of same size as the object expression matrix, or a numeric vector of array weights with length equal to \code{ncol} of the expression matrix, or a numeric vector of gene weights with length equal to \code{nrow} of the expression matrix.} |
17 | 17 |
\item{method}{fitting method; \code{"ls"} for least squares or \code{"robust"} for robust regression} |
18 |
- \item{...}{other optional arguments to be passed to \code{lm.series}, \code{gls.series} or \code{mrlm}} |
|
18 |
+ \item{\dots}{other optional arguments to be passed to \code{lm.series}, \code{gls.series} or \code{mrlm}} |
|
19 | 19 |
} |
20 | 20 |
|
21 | 21 |
\value{ |
... | ... |
@@ -39,7 +39,7 @@ When unequal \code{weights} are provided, this function calls \code{weightedLowe |
39 | 39 |
\code{weightedLowess} implements a similar algorithm to \code{lowess} except that it uses the prior weights both in the local regressions and in determining which other observations to include in the local neighbourhood of each observation. |
40 | 40 |
|
41 | 41 |
Two alternative algorithms for weighted lowess curve fitting are provided as options. |
42 |
-If \code{method="loess"}, then a call is made to \code{loess(y~x,weights=weights,span=span,degree=1,family="symmetric",...)}. |
|
42 |
+If \code{method="loess"}, then a call is made to \code{loess(y~x,weights=weights,span=span,degree=1,family="symmetric",\dots)}. |
|
43 | 43 |
This method differs from \code{weightedLowess} in that the prior weights are ignored when determining the neighbourhood of each observation. |
44 | 44 |
|
45 | 45 |
If \code{method="locfit"}, then repeated calls are made to \code{locfit:::locfit.raw} with \code{deg=1}. |
... | ... |
@@ -6,14 +6,14 @@ |
6 | 6 |
Apply a specified function to each to each value of a matrix and its immediate neighbors. |
7 | 7 |
} |
8 | 8 |
\usage{ |
9 |
-ma3x3.matrix(x,FUN=mean,na.rm=TRUE,...) |
|
10 |
-ma3x3.spottedarray(x,printer,FUN=mean,na.rm=TRUE,...) |
|
9 |
+ma3x3.matrix(x,FUN=mean,na.rm=TRUE,\dots) |
|
10 |
+ma3x3.spottedarray(x,printer,FUN=mean,na.rm=TRUE,\dots) |
|
11 | 11 |
} |
12 | 12 |
\arguments{ |
13 | 13 |
\item{x}{numeric matrix} |
14 | 14 |
\item{FUN}{function to apply to each window of values} |
15 | 15 |
\item{na.rm}{logical value, should missing values be removed when applying \code{FUN}} |
16 |
- \item{...}{other arguments are passed to \code{FUN}} |
|
16 |
+ \item{\dots}{other arguments are passed to \code{FUN}} |
|
17 | 17 |
\item{printer}{list giving the printer layout, see \code{\link{PrintLayout-class}}} |
18 | 18 |
} |
19 | 19 |
\details{ |
... | ... |
@@ -5,11 +5,11 @@ |
5 | 5 |
Creates a mean-difference plot. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 |
-mdplot(x, ...) |
|
8 |
+mdplot(x, \dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{x}{numeric \code{matrix} with at least two columns} |
12 |
- \item{...}{any other arguments are passed to \code{plot}} |
|
12 |
+ \item{\dots}{any other arguments are passed to \code{plot}} |
|
13 | 13 |
} |
14 | 14 |
|
15 | 15 |
\details{ |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
The fit is by robust M-estimation allowing for a small proportion of outliers. |
6 | 6 |
This is a utility function for \code{lmFit}.} |
7 | 7 |
\usage{ |
8 |
-mrlm(M,design=NULL,ndups=1,spacing=1,weights=NULL,...) |
|
8 |
+mrlm(M,design=NULL,ndups=1,spacing=1,weights=NULL,\dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{M}{numeric matrix containing log-ratio or log-expression values for a series of microarrays, rows correspond to genes and columns to arrays.} |
... | ... |
@@ -13,7 +13,7 @@ mrlm(M,design=NULL,ndups=1,spacing=1,weights=NULL,...) |
13 | 13 |
\item{ndups}{a positive integer giving the number of times each gene is printed on an array. \code{nrow(M)} must be divisible by \code{ndups}.} |
14 | 14 |
\item{spacing}{the spacing between the rows of \code{M} corresponding to duplicate spots, \code{spacing=1} for consecutive spots.} |
15 | 15 |
\item{weights}{numeric matrix of the same dimension as \code{M} containing weights. If it is of different dimension to \code{M}, it will be filled out to the same size. \code{NULL} is equivalent to equal weights.} |
16 |
- \item{...}{any other arguments are passed to \code{rlm.default}.} |
|
16 |
+ \item{\dots}{any other arguments are passed to \code{rlm.default}.} |
|
17 | 17 |
} |
18 | 18 |
\value{ |
19 | 19 |
A list with components |
... | ... |
@@ -2,12 +2,13 @@ |
2 | 2 |
\alias{nec} |
3 | 3 |
\alias{neqc} |
4 | 4 |
\title{NormExp Background Correction and Normalization Using Control Probes} |
5 |
-\description{Perform normexp background correction using negative control probes and quantile normalization using negative and positive control probes.} |
|
5 |
+\description{Perform normexp background correction using negative control probes and quantile normalization using negative and positive control probes. |
|
6 |
+Particularly useful for Illumina BeadChips.} |
|
6 | 7 |
\usage{ |
7 | 8 |
nec(x, status=NULL, negctrl="negative", regular="regular", offset=16, |
8 | 9 |
robust=FALSE, detection.p="Detection") |
9 | 10 |
neqc(x, status=NULL, negctrl="negative", regular="regular", offset=16, |
10 |
- robust=FALSE, detection.p="Detection", ...) |
|
11 |
+ robust=FALSE, detection.p="Detection", \dots) |
|
11 | 12 |
} |
12 | 13 |
\arguments{ |
13 | 14 |
\item{x}{object of class \code{EListRaw} or \code{matrix} containing raw intensities for regular and control probes from a series of microarrays.} |
... | ... |
@@ -17,7 +18,7 @@ neqc(x, status=NULL, negctrl="negative", regular="regular", offset=16, |
17 | 18 |
\item{offset}{numeric value added to the intensities after background correction.} |
18 | 19 |
\item{robust}{logical. Should robust estimators be used for the background mean and standard deviation?} |
19 | 20 |
\item{detection.p}{dection p-values. Only used when no negative control probes can be found in the data. Can be a numeric matrix or a character string giving the name of the component of \code{x$other} containing the matrix.} |
20 |
- \item{...}{any other arguments are passed to \code{normalizeBetweenArrays.}} |
|
21 |
+ \item{\dots}{any other arguments are passed to \code{normalizeBetweenArrays.}} |
|
21 | 22 |
} |
22 | 23 |
\details{ |
23 | 24 |
\code{neqc} performs background correction followed by quantile normalization, using negative control probes for background correction and both negative and positive controls for normalization (Shi et al, 2010). |
... | ... |
@@ -82,4 +83,5 @@ yr <- neqc(xr) |
82 | 83 |
} |
83 | 84 |
} |
84 | 85 |
|
85 |
-\keyword{models} |
|
86 |
+\keyword{background correction} |
|
87 |
+\keyword{illumina beadchips} |
... | ... |
@@ -10,12 +10,12 @@ Apply variance stabilizing normalization (vsn) to limma data objects. |
10 | 10 |
} |
11 | 11 |
|
12 | 12 |
\usage{ |
13 |
-normalizeVSN(x, ...) |
|
13 |
+normalizeVSN(x, \dots) |
|
14 | 14 |
} |
15 | 15 |
|
16 | 16 |
\arguments{ |
17 | 17 |
\item{x}{a numeric \code{matrix}, \code{EListRaw} or \code{\link[limma:rglist]{RGList}} object.} |
18 |
- \item{...}{other arguments are passed to \code{vsn}} |
|
18 |
+ \item{\dots}{other arguments are passed to \code{vsn}} |
|
19 | 19 |
} |
20 | 20 |
|
21 | 21 |
\details{ |
... | ... |
@@ -7,7 +7,7 @@ Normalizes expression intensities so that the intensities or log-ratios have sim |
7 | 7 |
} |
8 | 8 |
|
9 | 9 |
\usage{ |
10 |
-normalizeBetweenArrays(object, method=NULL, targets=NULL, cyclic.method="fast", ...) |
|
10 |
+normalizeBetweenArrays(object, method=NULL, targets=NULL, cyclic.method="fast", \dots) |
|
11 | 11 |
} |
12 | 12 |
|
13 | 13 |
\arguments{ |
... | ... |
@@ -20,7 +20,7 @@ normalizeBetweenArrays(object, method=NULL, targets=NULL, cyclic.method="fast", |
20 | 20 |
The default is \code{"Aquantile"} for two-color data objects or \code{"quantile"} for single-channel objects.} |
21 | 21 |
\item{targets}{vector, factor or matrix of length twice the number of arrays, used to indicate target groups if \code{method="Tquantile"}} |
22 | 22 |
\item{cyclic.method}{character string indicating the variant of \code{normalizeCyclicLoess} to be used if \code{method=="cyclicloess"}, see \code{\link{normalizeCyclicLoess}} for possible values.} |
23 |
- \item{...}{other arguments are passed to \code{normalizeQuantiles} or \code{normalizeCyclicLoess}} |
|
23 |
+ \item{\dots}{other arguments are passed to \code{normalizeQuantiles} or \code{normalizeCyclicLoess}} |
|
24 | 24 |
} |
25 | 25 |
|
26 | 26 |
\details{ |
... | ... |
@@ -10,11 +10,11 @@ |
10 | 10 |
Plot the density of expression values for multiple arrays on the same plot. |
11 | 11 |
} |
12 | 12 |
\usage{ |
13 |
-\method{plotDensities}{RGList}(object, log=TRUE, group=NULL, col=NULL, main="RG Densities",...) |
|
14 |
-\method{plotDensities}{MAList}(object, log=TRUE, group=NULL, col=NULL, main="RG Densities",...) |
|
15 |
-\method{plotDensities}{EListRaw}(object, log=TRUE, group=NULL, col=NULL, main=NULL,...) |
|
16 |
-\method{plotDensities}{EList}(object, log=TRUE, group=NULL, col=NULL, main=NULL,...) |
|
17 |
-\method{plotDensities}{default}(object, group=NULL, col=NULL, main=NULL,...) |
|
13 |
+\method{plotDensities}{RGList}(object, log=TRUE, group=NULL, col=NULL, main="RG Densities",\dots) |
|
14 |
+\method{plotDensities}{MAList}(object, log=TRUE, group=NULL, col=NULL, main="RG Densities",\dots) |
|
15 |
+\method{plotDensities}{EListRaw}(object, log=TRUE, group=NULL, col=NULL, main=NULL,\dots) |
|
16 |
+\method{plotDensities}{EList}(object, log=TRUE, group=NULL, col=NULL, main=NULL,\dots) |
|
17 |
+\method{plotDensities}{default}(object, group=NULL, col=NULL, main=NULL,\dots) |
|
18 | 18 |
} |
19 | 19 |
\arguments{ |
20 | 20 |
\item{object}{an \code{RGList}, \code{MAList}, \code{EListRaw} or \code{EList} object containing expression data. Or any data object that can be coerced to a matrix.} |
... | ... |
@@ -8,8 +8,8 @@ |
8 | 8 |
Creates foreground-background plots. |
9 | 9 |
} |
10 | 10 |
\usage{ |
11 |
-\method{plotFB}{RGList}(x, array=1, lim="separate", pch=16, cex=0.2, ...) |
|
12 |
-\method{plotFB}{EListRaw}(x, array=1, pch=16, cex=0.2, ...) |
|
11 |
+\method{plotFB}{RGList}(x, array=1, lim="separate", pch=16, cex=0.2, \dots) |
|
12 |
+\method{plotFB}{EListRaw}(x, array=1, pch=16, cex=0.2, \dots) |
|
13 | 13 |
} |
14 | 14 |
\arguments{ |
15 | 15 |
\item{x}{an \code{RGList} or \code{EListRaw} object.} |
... | ... |
@@ -17,7 +17,7 @@ Creates foreground-background plots. |
17 | 17 |
\item{lim}{character string indicating whether the red and green plots should have \code{"separate"} or \code{"common"} x- and y- co-ordinate limits.} |
18 | 18 |
\item{pch}{vector or list of plotting characters. Defaults to integer code 16.} |
19 | 19 |
\item{cex}{numeric vector of plot symbol expansions.} |
20 |
- \item{...}{any other arguments are passed to \code{plot}} |
|
20 |
+ \item{\dots}{any other arguments are passed to \code{plot}} |
|
21 | 21 |
} |
22 | 22 |
|
23 | 23 |
\details{ |
... | ... |
@@ -12,11 +12,11 @@ Distances on the plot can be interpreted in terms of \emph{leading log2-fold-cha |
12 | 12 |
} |
13 | 13 |
|
14 | 14 |
\usage{ |
15 |
-\method{plotMDS}{default}(x, top=500, labels=NULL, pch=NULL, col=NULL, cex=1, |
|
15 |
+\method{plotMDS}{default}(x, top=500, labels=NULL, pch=NULL, cex=1, |
|
16 | 16 |
dim.plot=c(1,2), ndim=max(dim.plot), gene.selection="pairwise", |
17 |
- xlab=paste("Dimension",dim.plot[1]), ylab=paste("Dimension",dim.plot[2]), ...) |
|
18 |
-\method{plotMDS}{MDS}(x, labels=NULL, pch=NULL, col=NULL, cex=1, dim.plot=x$dim.plot, |
|
19 |
- xlab=paste("Dimension",dim.plot[1]), ylab=paste("Dimension",dim.plot[2]),...) |
|
17 |
+ xlab=paste("Dimension",dim.plot[1]), ylab=paste("Dimension",dim.plot[2]), \dots) |
|
18 |
+\method{plotMDS}{MDS}(x, labels=NULL, pch=NULL, cex=1, dim.plot=x$dim.plot, |
|
19 |
+ xlab=paste("Dimension",dim.plot[1]), ylab=paste("Dimension",dim.plot[2]), \dots) |
|
20 | 20 |
} |
21 | 21 |
|
22 | 22 |
\arguments{ |
... | ... |
@@ -24,14 +24,13 @@ Distances on the plot can be interpreted in terms of \emph{leading log2-fold-cha |
24 | 24 |
\item{top}{number of top genes used to calculate pairwise distances.} |
25 | 25 |
\item{labels}{character vector of sample names or labels. If \code{x} has no column names, then defaults the index of the samples.} |
26 | 26 |
\item{pch}{plotting symbol or symbols. See \code{\link{points}} for possible values. Ignored if \code{labels} is non-\code{NULL}.} |
27 |
- \item{col}{numeric or character vector of colors for the plotting characters.} |
|
28 | 27 |
\item{cex}{numeric vector of plot symbol expansions.} |
29 | 28 |
\item{dim.plot}{which two dimensions should be plotted, numeric vector of length two.} |
30 | 29 |
\item{ndim}{number of dimensions in which data is to be represented} |
31 | 30 |
\item{gene.selection}{character, \code{"pairwise"} to choose the top genes separately for each pairwise comparison between the samples or \code{"common"} to select the same genes for all comparisons} |
32 | 31 |
\item{xlab}{title for the x-axis} |
33 | 32 |
\item{ylab}{title for the y-axis} |
34 |
- \item{...}{any other arguments are passed to \code{plot}.} |
|
33 |
+ \item{\dots}{any other arguments are passed to \code{plot}, and also to \code{text} (if \code{pch} is \code{NULL}).} |
|
35 | 34 |
} |
36 | 35 |
|
37 | 36 |
\details{ |
... | ... |
@@ -6,7 +6,7 @@ Plot of regularized linear discriminant functions for microarray data. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 | 8 |
plotRLDF(y,design=NULL,z=NULL,labels.y=NULL,labels.z=NULL,col.y=1,col.z=1, |
9 |
-df.prior=5,show.dimensions=c(1,2),main=NULL,nprobes=500,...)} |
|
9 |
+df.prior=5,show.dimensions=c(1,2),main=NULL,nprobes=500,\dots)} |
|
10 | 10 |
\arguments{ |
11 | 11 |
\item{y}{any data object which can be coerced to a matrix, such as \code{ExpressionSet} or \code{EList}. The training dataset.} |
12 | 12 |
\item{z}{any data object which can be coerced to a matrix, such as \code{ExpressionSet} or \code{EList}. The dataset to be classified.} |
... | ... |
@@ -19,7 +19,7 @@ df.prior=5,show.dimensions=c(1,2),main=NULL,nprobes=500,...)} |
19 | 19 |
\item{show.dimensions}{which two dimensions should be plotted, numeric vector of length two.} |
20 | 20 |
\item{main}{title of the plot.} |
21 | 21 |
\item{nprobes}{number of probes to be used for the calculations. Selected by moderated F tests.} |
22 |
- \item{...}{any other arguments are passed to \code{plot}.} |
|
22 |
+ \item{\dots}{any other arguments are passed to \code{plot}.} |
|
23 | 23 |
} |
24 | 24 |
\details{ |
25 | 25 |
This function is a variation on the plot of usual linear discriminant fuction, in that the within-group covariance matrix is regularized to ensure that it is invertible, with eigenvalues bounded away from zero. |
... | ... |
@@ -6,7 +6,7 @@ Plot log residual standard deviation versus average log expression for a fitted |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 | 8 |
plotSA(fit, xlab="Average log-expression", ylab="log2(sigma)", |
9 |
- zero.weights=FALSE, pch=16, cex=0.2, ...) |
|
9 |
+ zero.weights=FALSE, pch=16, cex=0.2, \dots) |
|
10 | 10 |
} |
11 | 11 |
\arguments{ |
12 | 12 |
\item{fit}{an \code{MArrayLM} object.} |
... | ... |
@@ -16,7 +16,7 @@ plotSA(fit, xlab="Average log-expression", ylab="log2(sigma)", |
16 | 16 |
\item{cex}{numeric expansion factor for plotting character. |
17 | 17 |
Defaults to 0.2.} |
18 | 18 |
\item{zero.weights}{logical, should spots with zero or negative weights be plotted?} |
19 |
- \item{...}{any other arguments are passed to \code{plot}} |
|
19 |
+ \item{\dots}{any other arguments are passed to \code{plot}} |
|
20 | 20 |
} |
21 | 21 |
|
22 | 22 |
\details{ |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
Time course style plot of expression data. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 |
-plotlines(x,first.column.origin=FALSE,xlab="Column",ylab="x",col="black",lwd=1,...) |
|
8 |
+plotlines(x,first.column.origin=FALSE,xlab="Column",ylab="x",col="black",lwd=1,\dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{x}{numeric matrix or object containing expression data.} |
... | ... |
@@ -14,7 +14,7 @@ plotlines(x,first.column.origin=FALSE,xlab="Column",ylab="x",col="black",lwd=1,. |
14 | 14 |
\item{ylab}{y-axis label} |
15 | 15 |
\item{col}{vector of colors for lines} |
16 | 16 |
\item{lwd}{line width multiplier} |
17 |
- \item{...}{any other arguments are passed to \code{plot}} |
|
17 |
+ \item{\dots}{any other arguments are passed to \code{plot}} |
|
18 | 18 |
} |
19 | 19 |
|
20 | 20 |
\details{ |
... | ... |
@@ -6,7 +6,7 @@ Write MA-plots to files in PNG format, six plots to a file in a 3 by 2 grid arra |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 | 8 |
plotMA3by2(MA, prefix="MA", path=NULL, main=colnames(MA), |
9 |
- zero.weights=FALSE, common.lim=TRUE, device="png", ...) |
|
9 |
+ zero.weights=FALSE, common.lim=TRUE, device="png", \dots) |
|
10 | 10 |
} |
11 | 11 |
\arguments{ |
12 | 12 |
\item{MA}{an \code{MAList}, \code{RGList}, \code{EListRaw} or \code{EList} object, or a matrix containing log-intensities.} |
... | ... |
@@ -16,7 +16,7 @@ plotMA3by2(MA, prefix="MA", path=NULL, main=colnames(MA), |
16 | 16 |
\item{zero.weights}{logical, should points with non-positive weights be plotted} |
17 | 17 |
\item{common.lim}{logical, should all plots on a page use the same axis limits} |
18 | 18 |
\item{device}{device driver for the plot. Choices are \code{"png"}, \code{"jpeg"}, \code{"pdf"}, \code{"postscript"}.} |
19 |
- \item{...}{any other arguments are passed to \code{plotMA}} |
|
19 |
+ \item{\dots}{any other arguments are passed to \code{plotMA}} |
|
20 | 20 |
} |
21 | 21 |
|
22 | 22 |
\details{ |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
Creates a coplot giving MA-plots with loess curves by print-tip groups. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 |
-plotPrintTipLoess(object,layout,array=1,span=0.4,...) |
|
8 |
+plotPrintTipLoess(object,layout,array=1,span=0.4,\dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{object}{\code{MAList} or \code{RGList} object or list with components \code{M} containing log-ratios and \code{A} containing average intensities} |
... | ... |
@@ -13,7 +13,7 @@ plotPrintTipLoess(object,layout,array=1,span=0.4,...) |
13 | 13 |
Defaults to \code{MA$printer} if that is non-null.} |
14 | 14 |
\item{array}{integer giving the array to be plotted. Corresponds to columns of \code{M} and \code{A}.} |
15 | 15 |
\item{span}{span of window for \code{lowess} curve} |
16 |
- \item{...}{other arguments passed to \code{panel.smooth}} |
|
16 |
+ \item{\dots}{other arguments passed to \code{panel.smooth}} |
|
17 | 17 |
} |
18 | 18 |
\details{ |
19 | 19 |
Note that spot quality weights in \code{object} are not used for computing the loess curves for this plot even though such weights would be used for loess normalization using \code{normalizeWithinArrays}. |
... | ... |
@@ -6,7 +6,7 @@ Reads specified columns from a file in table format and creates a data frame fro |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 | 8 |
read.columns(file, required.col=NULL, text.to.search="", sep="\t", quote="\"", skip=0, |
9 |
- fill=TRUE, blank.lines.skip=TRUE, comment.char="", allowEscapes=FALSE, ...) |
|
9 |
+ fill=TRUE, blank.lines.skip=TRUE, comment.char="", allowEscapes=FALSE, \dots) |
|
10 | 10 |
} |
11 | 11 |
\arguments{ |
12 | 12 |
\item{file}{the name of the file which the data are to be read from.} |
... | ... |
@@ -3,11 +3,11 @@ |
3 | 3 |
\title{Read Illumina Data from a Target Dataframe} |
4 | 4 |
\description{Read Illumina data from a target dataframe} |
5 | 5 |
\usage{ |
6 |
-read.ilmn.targets(targets, ...) |
|
6 |
+read.ilmn.targets(targets, \dots) |
|
7 | 7 |
} |
8 | 8 |
\arguments{ |
9 | 9 |
\item{targets}{ data frame including names of profile files.} |
10 |
- \item{...}{ any other parameters are passed on to \code{\link{read.ilmn}}.} |
|
10 |
+ \item{\dots}{ any other parameters are passed on to \code{\link{read.ilmn}}.} |
|
11 | 11 |
} |
12 | 12 |
\details{ |
13 | 13 |
\code{targets} is often created by calling the function \code{\link{readTargets}}. |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
Read a table giving regular expressions to identify different types of spots in the gene-dataframe. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 |
-readSpotTypes(file="SpotTypes.txt",path=NULL,sep="\t",check.names=FALSE,...) |
|
8 |
+readSpotTypes(file="SpotTypes.txt",path=NULL,sep="\t",check.names=FALSE,\dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{file}{character string giving the name of the file specifying the spot types.} |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
Read targets file for a microarray experiment into a dataframe. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 |
-readTargets(file="Targets.txt", path=NULL, sep="\t", row.names=NULL, quote="\"",...) |
|
8 |
+readTargets(file="Targets.txt", path=NULL, sep="\t", row.names=NULL, quote="\"",\dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{file}{character string giving the name of the targets file.} |
... | ... |
@@ -14,7 +14,7 @@ readTargets(file="Targets.txt", path=NULL, sep="\t", row.names=NULL, quote="\"", |
14 | 14 |
\item{sep}{field separator character} |
15 | 15 |
\item{row.names}{character string giving the name of a column from which to obtain row names} |
16 | 16 |
\item{quote}{the set of quoting characters} |
17 |
- \item{...}{other arguments are passed to \code{\link{read.table}}} |
|
17 |
+ \item{\dots}{other arguments are passed to \code{\link{read.table}}} |
|
18 | 18 |
} |
19 | 19 |
\details{ |
20 | 20 |
The targets file is a text file containing information about the RNA samples used as targets in the microarray experiment. |
... | ... |
@@ -5,7 +5,7 @@ |
5 | 5 |
Read a GenePix Array List (GAL) file into a dataframe. |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 |
-readGAL(galfile=NULL,path=NULL,header=TRUE,sep="\t",quote="\"",skip=NULL,as.is=TRUE,...) |
|
8 |
+readGAL(galfile=NULL,path=NULL,header=TRUE,sep="\t",quote="\"",skip=NULL,as.is=TRUE,\dots) |
|
9 | 9 |
} |
10 | 10 |
\arguments{ |
11 | 11 |
\item{galfile}{character string giving the name of the GAL file. If \code{NULL} then a file with extension \code{.gal} is found in the directory specified by \code{path}.} |
... | ... |
@@ -15,7 +15,7 @@ readGAL(galfile=NULL,path=NULL,header=TRUE,sep="\t",quote="\"",skip=NULL,as.is=T |
15 | 15 |
\item{quote}{the set of quoting characters} |
16 | 16 |
\item{skip}{number of lines of the GAL file to skip before reading data. If \code{NULL} then this number is determined by searching the file for column headings.} |
17 | 17 |
\item{as.is}{logical variable, if \code{TRUE} then read in character columns as vectors rather than factors.} |
18 |
- \item{...}{any other arguments are passed to \code{read.table}} |
|
18 |
+ \item{\dots}{any other arguments are passed to \code{read.table}} |
|
19 | 19 |
} |
20 | 20 |
\details{ |
21 | 21 |
A GAL file is a list of genes IDs and associated information produced by an Axon microarray scanner. |
... | ... |
@@ -3,7 +3,7 @@ |
3 | 3 |
\title{Select Appropriate Linear Model} |
4 | 4 |
\description{Select the best fitting linear model for each gene by minimizing an information criterion.} |
5 | 5 |
\usage{ |
6 |
-selectModel(y, designlist, criterion="aic", df.prior=0, s2.prior=NULL, s2.true=NULL, ...) |
|
6 |
+selectModel(y, designlist, criterion="aic", df.prior=0, s2.prior=NULL, s2.true=NULL, \dots) |
|
7 | 7 |
} |
8 | 8 |
\arguments{ |
9 | 9 |
\item{y}{a matrix-like data object, containing log-ratios or log-values of expression for a series of microarrays. |
... | ... |
@@ -13,7 +13,7 @@ selectModel(y, designlist, criterion="aic", df.prior=0, s2.prior=NULL, s2.true=N |
13 | 13 |
\item{df.prior}{prior degrees of freedom for residual variances. See \code{\link{squeezeVar}}} |
14 | 14 |
\item{s2.prior}{prior value for residual variances, to be used if \code{df.prior}>0.} |
15 | 15 |
\item{s2.true}{numeric vector of true variances, to be used if \code{criterion="mallowscp"}.} |
16 |
- \item{...}{other optional arguments to be passed to \code{lmFit}} |
|
16 |
+ \item{\dots}{other optional arguments to be passed to \code{lmFit}} |
|
17 | 17 |
} |
18 | 18 |
|
19 | 19 |
\value{ |
... | ... |
@@ -9,11 +9,11 @@ |
9 | 9 |
Briefly summarize microarray data objects. |
10 | 10 |
} |
11 | 11 |
\usage{ |
12 |
-\method{summary}{RGList}(object, ...) |
|
12 |
+\method{summary}{RGList}(object, \dots) |
|
13 | 13 |
} |
14 | 14 |
\arguments{ |
15 | 15 |
\item{object}{an object of class \code{RGList}, \code{MAList} or \code{MArrayLM}} |
16 |
- \item{...}{other arguments are not used} |
|
16 |
+ \item{\dots}{other arguments are not used} |
|
17 | 17 |
} |
18 | 18 |
\details{ |
19 | 19 |
The data objects are summarized as if they were lists, i.e., brief information about the length and type of the components is given. |
... | ... |
@@ -6,7 +6,7 @@ Creates a volcano plot of log-fold changes versus log-odds of differential expre |
6 | 6 |
} |
7 | 7 |
\usage{ |
8 | 8 |
volcanoplot(fit, coef=1, highlight=0, names=fit$genes$ID, |
9 |
- xlab="Log Fold Change", ylab="Log Odds", pch=16, cex=0.35, ...) |
|
9 |
+ xlab="Log Fold Change", ylab="Log Odds", pch=16, cex=0.35, \dots) |
|
10 | 10 |
} |
11 | 11 |
\arguments{ |
12 | 12 |
\item{fit}{an \code{MArrayLM} fitted linear model object} |
... | ... |
@@ -17,7 +17,7 @@ volcanoplot(fit, coef=1, highlight=0, names=fit$genes$ID, |
17 | 17 |
\item{ylab}{character string giving label for y-axis} |
18 | 18 |
\item{pch}{vector or list of plotting characters. Default is integer code 16 which gives a solid circle.} |
19 | 19 |
\item{cex}{numeric vector of plot symbol expansions. Default is 0.35.} |
20 |
- \item{...}{any other arguments are passed to \code{plot}} |
|
20 |
+ \item{\dots}{any other arguments are passed to \code{plot}} |
|
21 | 21 |
} |
22 | 22 |
|
23 | 23 |
\details{ |
... | ... |
@@ -8,7 +8,7 @@ The data are then ready for linear modelling. |
8 | 8 |
|
9 | 9 |
\usage{ |
10 | 10 |
voom(counts, design = NULL, lib.size = NULL, normalize.method = "none", |
11 |
- plot = FALSE, span=0.5, ...) |
|
11 |
+ plot = FALSE, span=0.5, \dots) |
|
12 | 12 |
} |
13 | 13 |
\arguments{ |
14 | 14 |
\item{counts}{a numeric \code{matrix} containing raw counts, or an \code{ExpressionSet} containing raw counts, or a \code{DGEList} object.} |
... | ... |
@@ -20,7 +20,7 @@ voom(counts, design = NULL, lib.size = NULL, normalize.method = "none", |
20 | 20 |
Choices are as for the \code{method} argument of \code{normalizeBetweenArrays} when the data is single-channel.} |
21 | 21 |
\item{plot}{\code{logical}, should a plot of the mean-variance trend be displayed?} |
22 | 22 |
\item{span}{width of the lowess smoothing window as a proportion.} |
23 |
- \item{...}{other arguments are passed to \code{lmFit}.} |
|
23 |
+ \item{\dots}{other arguments are passed to \code{lmFit}.} |
|
24 | 24 |
} |
25 | 25 |
|
26 | 26 |
\details{ |
... | ... |
@@ -29,7 +29,7 @@ This function extends the lowess algorithm to handle non-negative prior weights. |
29 | 29 |
used during span calculations such that the span distance for each point must include the |
30 | 30 |
specified proportion of all weights. They are also applied during weighted linear regression to |
31 | 31 |
compute the fitted value (in addition to the tricube weights determined by \code{span}). For integer |
32 |
-weights, the prior weights are equivalent to using \code{rep(..., w)} on \code{x} and \code{y} prior to fitting. |
|
32 |
+weights, the prior weights are equivalent to using \code{rep(\dots, w)} on \code{x} and \code{y} prior to fitting. |
|
33 | 33 |
|
34 | 34 |
For large vectors, running time is reduced by only performing locally weighted regression for |
35 | 35 |
several points. Fitted values for all points adjacent to the chosen points are computed by |