Browse code

4 June 2008: limma 2.15.7

- new S3 generic function avereps() for averaging over irregularly
spaced replicate spots. A method is defined for MAList objects
and a default method intended for matrices.


git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/limma@32117 bc3139a8-67e5-0310-9ffc-ced21a209358

Gordon Smyth authored on 04/06/2008 09:54:23
Showing 5 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: limma
2
-Version: 2.15.6
3
-Date: 2008/06/01
2
+Version: 2.15.7
3
+Date: 2008/06/04
4 4
 Title: Linear Models for Microarray Data
5 5
 Author: Gordon Smyth with contributions from Matthew Ritchie, Jeremy Silver, James Wettenhall, Natalie Thorne, Mette Langaas, Egil Ferkingstad, Marcus Davy, Francois Pepin and Dongseok Choi.
6 6
 Maintainer: Gordon Smyth <[email protected]>
... ...
@@ -20,6 +20,7 @@ S3method(as.matrix,ExpressionSet)
20 20
 S3method(as.matrix,LumiBatch)
21 21
 S3method(as.matrix,vsn)
22 22
 S3method(avedups,MAList)
23
+S3method(avereps,MAList)
23 24
 S3method(cbind,MAList)
24 25
 S3method(cbind,RGList)
25 26
 S3method(dim,MAList)
... ...
@@ -147,7 +147,50 @@ avedups.MAList <- function(x,ndups=x$printer$ndups,spacing=x$printer$spacing,wei
147 147
 	for (a in other) object$other[[a]] <- avedups(object$other[[a]],ndups=ndups,spacing=spacing,weights=weights)
148 148
 	y$weights <- avedups(x$weights,ndups=ndups,spacing=spacing)
149 149
 	y$genes <- uniquegenelist(x$genes,ndups=ndups,spacing=spacing)
150
-    y$printer <- NULL
150
+	y$printer <- NULL
151
+	y
152
+}
153
+
154
+avereps <- function(x,ID) UseMethod("avereps")
155
+#  4 June 2008
156
+
157
+avereps.default <- function(x,ID=rownames(x))
158
+#	Average over irregular replicate spots, for matrices or vectors
159
+#	Gordon Smyth
160
+#	3 June 2008.
161
+{
162
+	if(is.null(x)) return(NULL)
163
+	x <- as.matrix(x)
164
+	nspots <- nrow(x)
165
+	narrays <- ncol(x)
166
+	ID <- as.character(ID)
167
+	iu <- !duplicated(ID)
168
+	if(mode(x)=="character") return(x[iu,,drop=FALSE])
169
+	u <- ID[iu]
170
+	nprobes <- length(u)
171
+	y <- x[iu,,drop=FALSE]
172
+	for (i in 1:length(u)) y[i,] <- colMeans(x[ID==u[i],,drop=FALSE],na.rm=TRUE)
173
+	y
174
+}
175
+
176
+avereps.MAList <- function(x,ID=NULL)
177
+#	Average over irregular replicate spots for MAList objects
178
+#	Gordon Smyth
179
+#	3 June 2008.
180
+{
181
+	if(is.null(ID)) {
182
+		ID <- x$genes$ID
183
+		if(is.null(ID)) ID <- rownames(x)
184
+		if(is.null(ID)) stop("Cannot find probe IDs")
185
+	}
186
+	y <- x
187
+	y$M <- avereps(x$M,ID=ID)
188
+	y$A <- avereps(x$A,ID=ID)
189
+	other <- names(x$other)
190
+	for (a in other) object$other[[a]] <- avereps(object$other[[a]],ID=ID)
191
+	y$weights <- avereps(x$weights,ID=ID)
192
+	y$genes <- x$genes[!duplicated(ID),]
193
+   y$printer <- NULL
151 194
 	y
152 195
 }
153 196
 
... ...
@@ -1,3 +1,9 @@
1
+4 June 2008: limma 2.15.7
2
+
3
+- new S3 generic function avereps() for averaging over irregularly
4
+  spaced replicate spots.  A method is defined for MAList objects
5
+  and a default method intended for matrices.
6
+
1 7
 1 June 2008: limma 2.15.6
2 8
 
3 9
 - gls.series() now preserves rownames (probe IDs) of the expression
4 10
new file mode 100644
... ...
@@ -0,0 +1,34 @@
1
+\name{avereps}
2
+\alias{avereps}
3
+\alias{avereps.default}
4
+\alias{avereps.MAList}
5
+\title{Average Over Irregular Replicate Spots}
6
+\description{
7
+Condense a microarray data object so that values for within-array replicate spots are replaced with their average.
8
+}
9
+\usage{
10
+\method{avereps}{default}(x, ID=rownames(x))
11
+\method{avereps}{MAList}(x, ID=NULL)
12
+}
13
+\arguments{
14
+  \item{x}{a matrix-like object, usually a matrix or an \code{MAList} object.}
15
+  \item{ID}{probe identifier.}
16
+}
17
+\details{
18
+A new data object is computed in which each probe is represented by the average of its replicate spots.
19
+For an \code{MAList} object, the components \code{M} and \code{A} are both averaged in this way, as \code{weights} and any matrices found in \code{object$other}.
20
+
21
+For an \code{MAList} object, \code{ID} defaults to \code{MA$genes$ID} is that exists, otherwise to \code{rownames(MA$M)}.
22
+
23
+If \code{x} is of mode \code{"character"}, then the replicate values are assumed to be equal and the first is taken as the average.
24
+}
25
+\value{
26
+A data object of the same class as \code{x} with a row for each unique value of \code{ID}.
27
+}
28
+\author{Gordon Smyth}
29
+\seealso{
30
+  \code{\link[base]{dimnames}} in the base package.
31
+  
32
+  \link{02.Classes} gives an overview of data classes used in LIMMA.
33
+}
34
+\keyword{array}