Browse code

1 Jan 2007: limma 2.9.7

- old functions designed to read image data files into data.frames
are now deprecated. This affects functions: read.matrix, rg.series.spot,
read.series, m.spot, a.spot, rg.spot, rg.quantarray, rg.genepix.
- wtVariables() renamed to namesInFun()
- new argument other.columns for read.imagene()


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

Gordon Smyth authored on 01/01/2007 06:13:45
Showing 17 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: limma
2
-Version: 2.9.6
3
-Date: 2006/12/19
2
+Version: 2.9.7
3
+Date: 2006/12/30
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 and Francois Pepin.
6 6
 Maintainer: Gordon Smyth <[email protected]>
... ...
@@ -1,5 +1,6 @@
1 1
 .onLoad <- function(lib, pkg) require(methods)
2 2
 
3
+#  All functions exported other than those starting with "."
3 4
 exportPattern("^[^\\.]")
4 5
 
5 6
 #importClassesFrom(Biobase,exprSet)
... ...
@@ -1,9 +1,9 @@
1
-read.imagene <- function(files,path=NULL,ext=NULL,names=NULL,columns=NULL,wt.fun=NULL,verbose=TRUE,sep="\t",quote="\"",...) {
1
+read.imagene <- function(files,path=NULL,ext=NULL,names=NULL,columns=NULL,other.columns=NULL,wt.fun=NULL,verbose=TRUE,sep="\t",quote="\"",...) {
2 2
 #	Extracts an RG list from a series of Imagene analysis output files.
3 3
 #	Imagene requires special treatment because red and green channel
4 4
 #	intensities are in different files.
5 5
 #	Gordon Smyth
6
-#	14 Aug 2003.  Last modified 29 July 2006.
6
+#	14 Aug 2003.  Last modified 30 Dec 2006.
7 7
 
8 8
 	if(is.null(dim(files))) {
9 9
 		if(length(files)%%2==0)
... ...
@@ -39,11 +39,28 @@ read.imagene <- function(files,path=NULL,ext=NULL,names=NULL,columns=NULL,wt.fun
39 39
 	}
40 40
 	if(is.null(columns$f) || is.null(columns$b)) stop("'columns' should have components 'f' and 'b'")
41 41
 
42
-#	Now read data
42
+#	Initialize data object
43 43
 	Y <- matrix(0,nspots,narrays)
44 44
 	colnames(Y) <- names
45
-	RG <- list(R=Y,G=Y,Rb=Y,Gb=Y,Image.Program="ImaGene",Field.Dimensions=FD)
45
+	RG <- list(R=Y,G=Y,Rb=Y,Gb=Y,source="imagene",Field.Dimensions=FD)
46 46
 	if(!is.null(wt.fun)) RG$weights <- Y
47
+
48
+#	Other columns
49
+	if(!is.null(other.columns)) {
50
+		other.columns <- as.character(other.columns)
51
+		if(length(other.columns)) {
52
+			RG$other <- list()
53
+			G.other.columns <- paste("G",other.columns)
54
+			colnames(Y) <- removeExt(files[,1])
55
+			for (a in G.other.columns) RG$other[[a]] <- Y 
56
+			R.other.columns <- paste("R",other.columns)
57
+			colnames(Y) <- removeExt(files[,2])
58
+			for (a in R.other.columns) RG$other[[a]] <- Y 
59
+		} else {
60
+			other.columns <- NULL
61
+		}
62
+	}
63
+
47 64
 	printer <- list(ngrid.r=FD[1,"Metarows"],ngrid.c=FD[1,"Metacols"],nspot.r=FD[1,"Rows"],nspot.c=FD[1,"Cols"])
48 65
 	if(nrow(FD)==1) {
49 66
 		RG$printer <- printer
... ...
@@ -53,7 +70,11 @@ read.imagene <- function(files,path=NULL,ext=NULL,names=NULL,columns=NULL,wt.fun
53 70
 			all(printer$nspot.r==FD[,"Rows"]) &&
54 71
 			all(printer$nspot.c==FD[,"Cols"]) ) RG$printer <- printer
55 72
 	}
73
+
74
+#	Now read data
56 75
 	for (i in 1:narrays) {
76
+
77
+#		Green channel
57 78
 		fullname <- files[i,1]
58 79
 		if(!is.null(path)) fullname <- file.path(path,fullname)
59 80
 		if(i > 1) {
... ...
@@ -67,6 +88,11 @@ read.imagene <- function(files,path=NULL,ext=NULL,names=NULL,columns=NULL,wt.fun
67 88
 		if(i==1) RG$genes <- obj[,c("Field","Meta Row","Meta Column","Row","Column","Gene ID")]
68 89
 		RG$G[,i] <- obj[,columns$f]
69 90
 		RG$Gb[,i] <- obj[,columns$b]
91
+		if(!is.null(other.columns)) {
92
+			for (j in 1:length(other.columns)) RG$other[[G.other.columns[j]]][,i] <- obj[,other.columns[j]]
93
+		}
94
+
95
+#		Red channel		
70 96
 		fullname <- files[i,2]
71 97
 		if(!is.null(path)) fullname <- file.path(path,fullname)
72 98
 		obj<- read.table(fullname,skip=skip,header=TRUE,sep=sep,quote=quote,check.names=FALSE,comment.char="",fill=TRUE,nrows=nspots,...)
... ...
@@ -74,6 +100,9 @@ read.imagene <- function(files,path=NULL,ext=NULL,names=NULL,columns=NULL,wt.fun
74 100
 		RG$R[,i] <- obj[,columns$f]
75 101
 		RG$Rb[,i] <- obj[,columns$b]
76 102
 		if(!is.null(wt.fun)) RG$weights[,i] <- wt.fun(obj)
103
+		if(!is.null(other.columns)) {
104
+			for (j in 1:length(other.columns)) RG$other[[R.other.columns[j]]][,i] <- obj[,other.columns[j]]
105
+		}
77 106
 	}
78 107
 	new("RGList",RG)
79 108
 }
... ...
@@ -32,7 +32,7 @@ read.maimages <- function(files=NULL,source="generic",path=NULL,ext=NULL,names=N
32 32
 #	source2 is the source type with qualifications removed
33 33
 	source2 <- strsplit(source,split=".",fixed=TRUE)[[1]][1]
34 34
 	if(is.null(quote)) if(source=="agilent") quote <- "" else quote <- "\""
35
-	if(source2=="imagene") return(read.imagene(files=files,path=path,ext=ext,names=names,columns=columns,wt.fun=wt.fun,verbose=verbose,sep=sep,quote=quote,...))
35
+	if(source2=="imagene") return(read.imagene(files=files,path=path,ext=ext,names=names,columns=columns,other.columns=other.columns,wt.fun=wt.fun,verbose=verbose,sep=sep,quote=quote,...))
36 36
 
37 37
 	if(is.data.frame(files)) {
38 38
 		targets <- files
... ...
@@ -241,7 +241,7 @@ read.maimages <- function(files=NULL,source="generic",path=NULL,ext=NULL,names=N
241 241
 	new("RGList",RG)
242 242
 }
243 243
 
244
-wtVariables <- function(x,fun)
244
+namesInFun <- function(x,fun)
245 245
 #	Finds variable names in user-defined functions
246 246
 #	Gordon Smyth
247 247
 #	3 Nov 2004. Last modified 2 Jan 2006.
... ...
@@ -258,7 +258,7 @@ wtVariables <- function(x,fun)
258 258
 
259 259
 getColClasses <- function(cols, ...)
260 260
 #	Construct a colClasses vector for read.table from a vector of possible columns 'cols' 
261
-#	Uses wtVariables and ellipsis vectors and lists of character string variable names
261
+#	Uses namesInFun and ellipsis vectors and lists of character string variable names
262 262
 #	to match against 'cols'
263 263
 #	Marcus Davy 
264 264
 #	16 Nov 2004. Last revised 2 Jan 2006.
... ...
@@ -269,7 +269,7 @@ getColClasses <- function(cols, ...)
269 269
 	wanted <- list(...)
270 270
 	for(i in 1:length(wanted)) {
271 271
 		if(is.null(wanted[[i]])) next
272
-		if(is.function(wanted[[i]])) include <- wtVariables(cols, wanted[[i]])
272
+		if(is.function(wanted[[i]])) include <- namesInFun(cols, wanted[[i]])
273 273
 		if(is.list(wanted[[i]])) wanted[[i]] <- unlist(wanted[[i]])
274 274
 		if(is.character(wanted[[i]])) include <- wanted[[i]]
275 275
 		ind <- match(include, cols, nomatch=0)
... ...
@@ -277,3 +277,4 @@ getColClasses <- function(cols, ...)
277 277
 	}
278 278
 	x
279 279
 }
280
+
... ...
@@ -249,6 +249,7 @@ read.matrix <- function(file,nrows=0,skip=0,...) {
249 249
 #	Gordon Smyth
250 250
 #	9 Mar 2003.
251 251
 
252
+	.Deprecated("read.maimages")  # 31 Dec 2006
252 253
 	h <- scan(file,what="character",skip=skip,nlines=1,quote="\"",quiet=TRUE,...)
253 254
 	x <- matrix(scan(file,skip=skip+1,nlines=nrows,quiet=TRUE,...),byrow=TRUE,ncol=length(h))
254 255
 	colnames(x) <- h
... ...
@@ -260,6 +261,7 @@ rg.series.spot <- function(slides,path=NULL,names.slides=names(slides),suffix="s
260 261
 #	Gordon Smyth
261 262
 #	1 Nov 2002.  Last revised 23 Mar 2003.
262 263
 
264
+	.Deprecated("read.maimages")  # 31 Dec 2006
263 265
 	slides <- as.vector(as.character(slides))
264 266
 	if(is.null(names.slides)) names.slides <- slides
265 267
 	nslides <- length(slides)
... ...
@@ -299,6 +301,7 @@ read.series <- function(slides,path=NULL,suffix="spot",...) {
299 301
 #	Gordon Smyth
300 302
 #	11 Mar 2002.  Last revised 2 Mar 2003.
301 303
 
304
+	.Deprecated("read.maimages")  # 31 Dec 2006
302 305
 	slides <- as.vector(as.character(slides))
303 306
 	nslides <- length(slides)
304 307
 	for (i in 1:nslides) {
... ...
@@ -318,6 +321,7 @@ m.spot <- function(spot) {
318 321
 #	Gordon Smyth
319 322
 #	18 Nov 2001.  Last revised 2 Mar 2003.
320 323
 
324
+	.Deprecated("read.maimages")  # 31 Dec 2006
321 325
 	R <- spot[,"Rmean"] - spot[,"morphR"]
322 326
 	G <- spot[,"Gmean"] - spot[,"morphG"]
323 327
 	log(R,2) - log(G,2)
... ...
@@ -328,6 +332,7 @@ a.spot <- function(spot) {
328 332
 #	Gordon Smyth
329 333
 #	18 Nov 2001.  Last revised 2 Mar 2003.
330 334
 
335
+	.Deprecated("read.maimages")  # 31 Dec 2006
331 336
 	R <- spot[,"Rmean"] - spot[,"morphR"]
332 337
 	G <- spot[,"Gmean"] - spot[,"morphG"]
333 338
 	(log(R,2) + log(G,2))/2
... ...
@@ -338,6 +343,7 @@ rg.spot <- function(slides,names.slides=names(slides),suffix="spot",area=FALSE)
338 343
 #	Gordon Smyth
339 344
 #	17 Jan 2002. Last revised 1 Nov 2002.
340 345
 
346
+	.Deprecated("read.maimages")  # 31 Dec 2006
341 347
 	slides <- as.vector(as.character(slides))
342 348
 	if(is.null(names.slides)) names.slides <- slides
343 349
 	nslides <- length(slides)
... ...
@@ -362,6 +368,7 @@ rg.quantarray <- function(slides,names.slides=names(slides),suffix="qta") {
362 368
 #	Gordon Smyth
363 369
 #	23 July 2002
364 370
 
371
+	.Deprecated("read.maimages")  # 31 Dec 2006
365 372
 	slides <- as.vector(as.character(slides))
366 373
 	if(is.null(names.slides)) names.slides <- slides
367 374
 	nslides <- length(slides)
... ...
@@ -384,6 +391,7 @@ rg.genepix <- function(slides,names.slides=names(slides),suffix="gpr") {
384 391
 #	Gordon Smyth
385 392
 #	23 July 2002. Last revised 13 Feb 2003.
386 393
 
394
+	.Deprecated("read.maimages")  # 31 Dec 2006
387 395
 	slides <- as.vector(as.character(slides))
388 396
 	if(is.null(names.slides)) names.slides <- slides
389 397
 	nslides <- length(slides)
... ...
@@ -1,3 +1,11 @@
1
+1 Jan 2007: limma 2.9.7
2
+
3
+- old functions designed to read image data files into data.frames
4
+  are now deprecated. This affects functions: read.matrix, rg.series.spot,
5
+  read.series, m.spot, a.spot, rg.spot, rg.quantarray, rg.genepix.
6
+- wtVariables() renamed to namesInFun()
7
+- new argument other.columns for read.imagene()
8
+
1 9
 19 Dec 2006: limma 2.9.6
2 10
 
3 11
 - new function as.matrix.ExpressionSet
... ...
@@ -4,6 +4,8 @@
4 4
 \title{Extract M or A-values from SPOT data.frame or matrix}
5 5
 \description{
6 6
 Extract M-values or A-values from a SPOT data.frame or matrix.
7
+
8
+These functions are deprecated in limma 2.9.7, 1 January 2007.
7 9
 }
8 10
 \usage{
9 11
 m.spot(spot)
10 12
new file mode 100644
... ...
@@ -0,0 +1,36 @@
1
+\name{namesInFun}
2
+\alias{namesInFun}
3
+\title{Find names in a function definition}
4
+\description{
5
+Given a list of names, detect whether these names appear in the definition of a function.
6
+}	 
7
+\usage{
8
+namesInFun(x, fun)
9
+}
10
+\arguments{
11
+ \item{x}{A character vector of names}
12
+ \item{fun}{A function}
13
+}
14
+\details{
15
+This function is used by \code{read.maimages} as part of determining which columns needs to be read from the data file.
16
+It is used to find detect which of the column headings in the data file appear in the definition of the weight function specified by \code{wt.fun}.
17
+}
18
+
19
+\value{
20
+Character of vector of names found in the definition of \code{fun}
21
+}
22
+\author{Gordon Smyth}
23
+\seealso{
24
+\code{\link{getColClasses}}
25
+\code{\link{read.maimages}}
26
+
27
+An overview of limma read functions is given in \link{03.ReadingData}.
28
+}
29
+\examples{
30
+searchcols <- c("area","Flags","Ignore Filter")
31
+namesInFun(searchcols, wtarea)
32
+namesInFun(searchcols, wtflags)
33
+namesInFun(searchcols, wtIgnore.Filter)
34
+rm(searchcols) # tidy up
35
+}
36
+\keyword{file}
... ...
@@ -31,8 +31,7 @@ The function is based on unpublished work by the author.
31 31
 \examples{
32 32
 library(sma)
33 33
 data(MouseArray)
34
-M <- m.spot(mouse1)
35
-A <- a.spot(mouse1)
36
-M <- normalizeRobustSpline(M,A,mouse.setup)
34
+MA <- MA.RG(mouse.data)
35
+normM <- normalizeRobustSpline(MA$M[,1],MA$A[,1],mouse.setup)
37 36
 }
38 37
 \keyword{models}
... ...
@@ -7,7 +7,7 @@ Reads an RGList from a series of microarray image analysis output files
7 7
 }
8 8
 \usage{
9 9
 read.maimages(files=NULL,source="generic",path=NULL,ext=NULL,names=NULL,columns=NULL,other.columns=NULL,annotation=NULL,wt.fun=NULL,verbose=TRUE,sep="\t",quote=NULL,DEBUG=FALSE,\dots)
10
-read.imagene(files,path=NULL,ext=NULL,names=NULL,columns=NULL,wt.fun=NULL,verbose=TRUE,sep="\t",quote="\"",...)
10
+read.imagene(files,path=NULL,ext=NULL,names=NULL,columns=NULL,other.columns=NULL,wt.fun=NULL,verbose=TRUE,sep="\t",quote="\"",...)
11 11
 }
12 12
 \arguments{
13 13
   \item{files}{character vector giving the names of the files containing image analysis output or, for Imagene data, a character matrix of names of files.
... ...
@@ -58,12 +58,14 @@ The function \code{read.imagene} is called by \code{read.maimages} when \code{so
58 58
 It does not need to be called directly by users.
59 59
 
60 60
 The argument \code{other.columns} allows arbitrary columns of the image analysis output files to be preserved in the data object.
61
+These become matrices in the component \code{other} component.
62
+For ImaGene data, the other column headings with be prefixed with \code{"R "} or \code{"G "} as appropriate.
61 63
 }
62 64
 
63 65
 \section{Warnings}{
64 66
 All image analysis files being read are assumed to contain data for the same genelist in the same order.
65 67
 No checking is done to confirm that this is true.
66
-Annotation information, when it is available, is set from the first file only.
68
+Probe annotation information is read from the first file only.
67 69
 }
68 70
 
69 71
 \value{
... ...
@@ -4,6 +4,8 @@
4 4
 \description{
5 5
 Read a numeric matrix from a file assuming column headings on the first line.
6 6
 Not normally used directly by users.
7
+
8
+This function is deprecated in limma 2.9.7 (1 January 2007).
7 9
 }
8 10
 \usage{
9 11
 read.matrix(file,nrows=0,skip=0,...)
... ...
@@ -3,6 +3,8 @@
3 3
 \title{Read series of image files}
4 4
 \description{
5 5
 Read in a series of array image analysis output files as data frames.
6
+
7
+This function is deprecated in limma 2.9.7 (1 January 2007).
6 8
 }
7 9
 \usage{
8 10
 read.series(slides, path=NULL, suffix="spot", ...)
... ...
@@ -3,6 +3,8 @@
3 3
 \title{Extract RGList from data.frames Containing GenePix Data}
4 4
 \description{
5 5
 Extracts an RGList from GenePix image analysis output when the data has already been read from files into data.frames objects.
6
+
7
+This function is deprecated in limma 2.9.7 (1 January 2007).
6 8
 }
7 9
 \usage{
8 10
 rg.genepix(slides,names.slides=names(slides),suffix="gpr")
... ...
@@ -3,6 +3,8 @@
3 3
 \title{Extract RGList from data.frames Containing Quantarray Data}
4 4
 \description{
5 5
 Extracts an RGList from Quantarray image analysis output when the data has already been read from files into data.frames objects.
6
+
7
+This function is deprecated in limma 2.9.7 (1 January 2007).
6 8
 }
7 9
 \usage{
8 10
 rg.quantarray(slides,names.slides=names(slides),suffix="qta")
... ...
@@ -3,6 +3,7 @@
3 3
 \title{Read RGList from SPOT Image Analysis Output Files}
4 4
 \description{
5 5
 Extracts an RGList from a series of Spot image analysis files.
6
+
6 7
 This is a depreciated function.
7 8
 Use \code{\link{read.maimages}} instead.
8 9
 }
... ...
@@ -3,6 +3,8 @@
3 3
 \title{Extract RGList from data.frames Containing SPOT Data}
4 4
 \description{
5 5
 Extracts an RGList from Spot image analysis output when the data has already been read from files into data.frames objects.
6
+
7
+This function is deprecated in limma 2.9.7 (1 January 2007).
6 8
 }
7 9
 \usage{
8 10
 rg.spot(slides,names.slides=names(slides),suffix="spot",area=FALSE)
9 11
deleted file mode 100644
... ...
@@ -1,33 +0,0 @@
1
-\name{wtVariables}
2
-\alias{wtVariables}
3
-\title{Read RGList from Image Analysis Output Files}
4
-\description{
5
-  Extracts variable names from weight functions such as \code{wtarea}, \code{wtflags}, \code{wtIgnore.Filter} and user defined functions for fast loading in \code{read.maimages}. 
6
-}	 
7
-\usage{
8
-wtVariables(x, fun)
9
-}
10
-\arguments{
11
- \item{x}{A character vector of all columns to search against}
12
- \item{fun}{A weight function to search for any of the possible columns in x}
13
-}
14
-\details{
15
-This is an internally called function by \code{getColClasses} which constructs a colClasses vector for fast loading of only required columns in \code{read.maimages}
16
-}
17
-
18
-\value{
19
-Vector of columns required within read.maimages
20
-}
21
-\author{Gordon Smyth}
22
-\seealso{
23
-\code{\link[limma]{getColClasses}}
24
-\code{\link[base]{read.table}}
25
-}
26
-\examples{
27
-searchcols <- c("area","Flags","Ignore Filter")
28
-wtVariables(searchcols, wtarea)
29
-wtVariables(searchcols, wtflags)
30
-wtVariables(searchcols, wtIgnore.Filter)
31
-rm(searchcols) # tidy up
32
-}
33
-\keyword{file}