... | ... |
@@ -1,8 +1,8 @@ |
1 | 1 |
Package: crlmm |
2 | 2 |
Type: Package |
3 | 3 |
Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for Affymetrix SNP 5.0 and 6.0 and Illumina arrays. |
4 |
-Version: 1.3.23 |
|
5 |
-Date: 2009-09-29 |
|
4 |
+Version: 1.3.24 |
|
5 |
+Date: 2009-10-25 |
|
6 | 6 |
Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
7 | 7 |
Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
8 | 8 |
Description: Faster implementation of CRLMM specific to SNP 5.0 and 6.0 arrays, as well as a copy number tool specific to 6.0. |
... | ... |
@@ -12,14 +12,18 @@ readIdatFiles <- function(sampleSheet=NULL, |
12 | 12 |
sep="_", |
13 | 13 |
fileExt=list(green="Grn.idat", red="Red.idat"), |
14 | 14 |
saveDate=FALSE) { |
15 |
- if(is.null(arrayNames)) { |
|
16 |
- arrayNames = gsub(paste(sep, fileExt$green, sep=""), "", dir(pattern=fileExt$green, path=path)) |
|
17 |
- if(!is.null(sampleSheet)) { |
|
18 |
- sampleSheet=NULL |
|
19 |
- cat("Could not find required info in \'sampleSheet\' - ignoring. Check \'sampleSheet\' and/or \'arrayInfoColNames\'\n") |
|
20 |
- } |
|
21 |
- pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames)) |
|
22 |
- } |
|
15 |
+# if(!is.null(arrayNames)) { |
|
16 |
+# arrayNames = gsub(paste(sep, fileExt$green, sep=""), "", dir(pattern=fileExt$green, path=path)) |
|
17 |
+# if(!is.null(sampleSheet)) { |
|
18 |
+# sampleSheet=NULL |
|
19 |
+# cat("Could not find required info in \'sampleSheet\' - ignoring. Check \'sampleSheet\' and/or \'arrayInfoColNames\'\n") |
|
20 |
+# } |
|
21 |
+# pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames)) |
|
22 |
+# } |
|
23 |
+ if(!is.null(arrayNames)) { |
|
24 |
+ pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames)) |
|
25 |
+ } |
|
26 |
+ |
|
23 | 27 |
if(!is.null(sampleSheet)) { # get array info from Illumina's sample sheet |
24 | 28 |
if(is.null(arrayNames)){ |
25 | 29 |
##arrayNames=NULL |
... | ... |
@@ -41,8 +45,17 @@ readIdatFiles <- function(sampleSheet=NULL, |
41 | 45 |
} |
42 | 46 |
} |
43 | 47 |
pd = new("AnnotatedDataFrame", data = sampleSheet) |
44 |
- sampleNames(pd) <- basename(arrayNames) |
|
48 |
+ sampleNames(pd) <- basename(arrayNames) |
|
49 |
+ } |
|
50 |
+ if(is.null(arrayNames)) { |
|
51 |
+ arrayNames = gsub(paste(sep, fileExt$green, sep=""), "", dir(pattern=fileExt$green, path=path)) |
|
52 |
+ if(!is.null(sampleSheet)) { |
|
53 |
+ sampleSheet=NULL |
|
54 |
+ cat("Could not find required info in \'sampleSheet\' - ignoring. Check \'sampleSheet\' and/or \'arrayInfoColNames\'\n") |
|
55 |
+ } |
|
56 |
+ pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames)) |
|
45 | 57 |
} |
58 |
+ |
|
46 | 59 |
narrays = length(arrayNames) |
47 | 60 |
grnfiles = paste(arrayNames, fileExt$green, sep=sep) |
48 | 61 |
redfiles = paste(arrayNames, fileExt$red, sep=sep) |
... | ... |
@@ -57,8 +70,8 @@ readIdatFiles <- function(sampleSheet=NULL, |
57 | 70 |
grnidats <- grnfiles |
58 | 71 |
redidats <- redfiles |
59 | 72 |
} |
60 |
- if(!all(file.exists(grnfiles))) stop("Missing some of the *Grn.idat files") |
|
61 |
- if(!all(file.exists(redfiles))) stop("Missing some of the *Red.idat files") |
|
73 |
+ if(!all(file.exists(grnidats))) stop("Missing some of the *Grn.idat files") |
|
74 |
+ if(!all(file.exists(redidats))) stop("Missing some of the *Red.idat files") |
|
62 | 75 |
## if(!all(c(redfiles,grnfiles) %in% dir(path=path))){ |
63 | 76 |
## stop("Missing .idat files: red\n", paste(redfiles[!(redfiles %in% dir(path=path))], sep=" "), "\n green\n", |
64 | 77 |
## paste(grnfiles[!(grnfiles %in% dir(path=path))], sep=" ")) |
... | ... |
@@ -80,7 +80,7 @@ was 1.2 GB of RAM on our linux system. |
80 | 80 |
The \Robject{RG} object is an \Rclass{NChannelSet} which stores the |
81 | 81 |
Red and Green intensities, the number of beads and standard errors for |
82 | 82 |
each bead-type. |
83 |
-The scanning date of each array is stored in the \Robject{protocolData} slot. |
|
83 |
+The scanning date of each array is stored in \Robject{protocolData}. |
|
84 | 84 |
|
85 | 85 |
<<explore>>= |
86 | 86 |
class(RG) |
... | ... |
@@ -104,8 +104,8 @@ with poor signal. |
104 | 104 |
|
105 | 105 |
<<boxplots, fig=TRUE, width=8, height=8>>= |
106 | 106 |
par(mfrow=c(2,1), mai=c(0.4,0.4,0.4,0.1), oma=c(1,1,0,0)) |
107 |
-boxplot(log2(exprs(channel(RG, "R"))), xlab="Array", ylab="", main="Red channel", outline=FALSE, las=2) |
|
108 |
-boxplot(log2(exprs(channel(RG, "G"))), xlab="Array", ylab="", main="Green channel", outline=FALSE, las=2) |
|
107 |
+boxplot(log2(exprs(channel(RG, "R"))), xlab="Array", ylab="", names=1:40, main="Red channel", outline=FALSE, las=2) |
|
108 |
+boxplot(log2(exprs(channel(RG, "G"))), xlab="Array", ylab="", names=1:40, main="Green channel", outline=FALSE, las=2) |
|
109 | 109 |
mtext(expression(log[2](intensity)), side=2, outer=TRUE) |
110 | 110 |
mtext("Array", side=1, outer=TRUE) |
111 | 111 |
@ |