git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45608 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,28 +1,27 @@ |
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.5.42 |
|
4 |
+Version: 1.5.43 |
|
5 | 5 |
Date: 2010-02-05 |
6 |
-Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au> |
|
7 |
-Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
|
6 |
+Author: Rafael A Irizarry, Benilton S Carvalho <carvalho@bclab.org>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au> |
|
7 |
+Maintainer: Benilton S Carvalho <carvalho@bclab.org>, 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 5.0, 6.0, and Illumina platforms |
9 | 9 |
License: Artistic-2.0 |
10 | 10 |
Depends: R (>= 2.11.0), |
11 | 11 |
methods, |
12 | 12 |
Biobase (>= 2.7.2), |
13 |
- oligoClasses (>= 1.9.35) |
|
13 |
+ oligoClasses (>= 1.9.50) |
|
14 | 14 |
Imports: affyio (>= 1.15.2), |
15 |
- preprocessCore, |
|
16 |
- utils, |
|
17 |
- stats, |
|
15 |
+ ellipse, |
|
16 |
+ ff, |
|
18 | 17 |
genefilter, |
19 |
- splines, |
|
20 | 18 |
mvtnorm, |
21 |
- ellipse, |
|
22 |
- SNPchip,ff |
|
23 |
-Suggests: hapmapsnp5, |
|
24 |
- hapmapsnp6, |
|
25 |
- genomewidesnp5Crlmm (>= 1.0.2), |
|
19 |
+ preprocessCore, |
|
20 |
+ splines, |
|
21 |
+ stats, |
|
22 |
+ SNPchip, |
|
23 |
+ utils |
|
24 |
+Suggests: hapmapsnp6, |
|
26 | 25 |
genomewidesnp6Crlmm (>= 1.0.2), |
27 | 26 |
snpMatrix, |
28 | 27 |
metaArray |
... | ... |
@@ -27,13 +27,12 @@ importFrom(Biobase, assayDataElement, assayDataElementNames, |
27 | 27 |
importClassesFrom(oligoClasses, SnpSuperSet, AlleleSet, CNSet) |
28 | 28 |
|
29 | 29 |
importMethodsFrom(oligoClasses, allele, calls, "calls<-", confs, |
30 |
- "confs<-", cnConfidence, "cnConfidence<-", |
|
31 |
- isSnp, chromosome, position, CA, "CA<-", CB, "CB<-", A, B, "A<-", "B<-") |
|
30 |
+ "confs<-", cnConfidence, "cnConfidence<-", isSnp, |
|
31 |
+ chromosome, position, CA, "CA<-", CB, "CB<-", A, B, |
|
32 |
+ "A<-", "B<-") |
|
32 | 33 |
|
33 |
- |
|
34 |
-importFrom(oligoClasses, chromosome2integer, celfileDate, list.celfiles) |
|
35 |
- |
|
36 |
-importFrom(oligoClasses, copyNumber) |
|
34 |
+importFrom(oligoClasses, chromosome2integer, celfileDate, list.celfiles, |
|
35 |
+ copyNumber, initializeBigMatrix, initializeBigVector) |
|
37 | 36 |
|
38 | 37 |
importFrom(graphics, abline, axis, layout, legend, mtext, par, plot, |
39 | 38 |
polygon, rect, segments, text, points, boxplot) |
... | ... |
@@ -54,6 +53,8 @@ importFrom(mvtnorm, dmvnorm) |
54 | 53 |
|
55 | 54 |
importFrom(ellipse, ellipse) |
56 | 55 |
|
56 |
+importFrom(ff, ffdf) |
|
57 |
+ |
|
57 | 58 |
exportClasses(CNSetLM) |
58 | 59 |
exportMethods(copyNumber, open, "[", show, lM, "lM<-") |
59 | 60 |
export(crlmm, |
... | ... |
@@ -68,7 +69,7 @@ export(crlmm, |
68 | 69 |
snprma2, |
69 | 70 |
crlmm2) |
70 | 71 |
|
71 |
-export(initializeBigMatrix, initializeParamObject) |
|
72 |
+export(initializeParamObject) |
|
72 | 73 |
|
73 | 74 |
|
74 | 75 |
|
... | ... |
@@ -795,27 +795,29 @@ crlmmWrapper <- function(filenames, cnOptions, ...){ |
795 | 795 |
return(crlmmResults) |
796 | 796 |
} |
797 | 797 |
|
798 |
-validCdfNames <- function(){ |
|
799 |
- c("genomewidesnp6", |
|
800 |
- "genomewidesnp5", |
|
801 |
- "human370v1c", |
|
802 |
- "human370quadv3c", |
|
803 |
- "human550v3b", |
|
804 |
- "human650v3a", |
|
805 |
- "human610quadv1b", |
|
806 |
- "human660quadv1a", |
|
807 |
- "human1mduov3b") |
|
808 |
-} |
|
809 |
- |
|
810 |
-isValidCdfName <- function(cdfName){ |
|
811 |
- chipList <- validCdfNames() |
|
812 |
- result <- cdfName %in% chipList |
|
813 |
- if(!(result)){ |
|
814 |
- warning("cdfName must be one of the following: ", |
|
815 |
- chipList) |
|
816 |
- } |
|
817 |
- return(result) |
|
818 |
-} |
|
798 |
+## NOTE: THIS IS ALSO IN UTILS.R |
|
799 |
+## validCdfNames <- function(){ |
|
800 |
+## c("genomewidesnp6", |
|
801 |
+## "genomewidesnp5", |
|
802 |
+## "human370v1c", |
|
803 |
+## "human370quadv3c", |
|
804 |
+## "human550v3b", |
|
805 |
+## "human650v3a", |
|
806 |
+## "human610quadv1b", |
|
807 |
+## "human660quadv1a", |
|
808 |
+## "human1mduov3b") |
|
809 |
+## } |
|
810 |
+ |
|
811 |
+## NOTE: THIS IS ALSO IN UTILS.R |
|
812 |
+## isValidCdfName <- function(cdfName){ |
|
813 |
+## chipList <- validCdfNames() |
|
814 |
+## result <- cdfName %in% chipList |
|
815 |
+## if(!(result)){ |
|
816 |
+## warning("cdfName must be one of the following: ", |
|
817 |
+## chipList) |
|
818 |
+## } |
|
819 |
+## return(result) |
|
820 |
+## } |
|
819 | 821 |
|
820 | 822 |
whichPlatform <- function(cdfName){ |
821 | 823 |
index <- grep("genomewidesnp", cdfName) |
... | ... |
@@ -205,78 +205,5 @@ initializeParamObject <- function(dimnames){ |
205 | 205 |
return(ll) |
206 | 206 |
} |
207 | 207 |
|
208 |
-## BC: how about moving initializeBigMatrix to oligoClasses? |
|
209 |
-initializeBigMatrix <- function(name, nr, nc, vmode="integer"){ |
|
210 |
- if(isPackageLoaded("ff")){ |
|
211 |
- if(prod(nr, nc) > 2^31){ |
|
212 |
- ##Need multiple matrices |
|
213 |
- ## -- use ffdf |
|
214 |
- ## How many samples per ff object |
|
215 |
- S <- floor(2^31/nr - 1) |
|
216 |
- ## How many ff objects |
|
217 |
- L <- ceiling(nc/S) |
|
218 |
- name <- paste(name, 1:L, sep="_") |
|
219 |
- resultsff <- vector("list", L) |
|
220 |
- ##resultsB <- vector("list", L) |
|
221 |
- for(i in 1:(L-1)){ ## the Lth object may have fewer than nc columns |
|
222 |
- resultsff[[i]] <- createFF(name=name[i], |
|
223 |
- dim=c(nr, S), |
|
224 |
- vmode=vmode) |
|
225 |
- } |
|
226 |
- ##the Lth element |
|
227 |
- leftOver <- nc - ((L-1)*S) |
|
228 |
- resultsff[[L]] <- createFF(name=name[L], |
|
229 |
- dim=c(nr, leftOver), |
|
230 |
- vmode=vmode) |
|
231 |
- resultsff[[L]][,] <- NA |
|
232 |
- results <- do.call(ffdf, resultsff) |
|
233 |
- rm(resultsff); gc() |
|
234 |
- ##dimnames(resultsff) <- dns |
|
235 |
- } else { |
|
236 |
- results <- createFF(name=name, |
|
237 |
- dim=c(nr, nc), |
|
238 |
- vmode=vmode) |
|
239 |
- results[,] <- NA |
|
240 |
- } |
|
241 |
- } else { |
|
242 |
- theNA <- switch(vmode, |
|
243 |
- integer=NA_integer_, |
|
244 |
- double=NA_real_, |
|
245 |
- character=NA_character_, |
|
246 |
- stop("Mode ", vmode, " not implemented for regular matrices")) |
|
247 |
- results <- matrix(theNA, nr, nc) |
|
248 |
- } |
|
249 |
- return(results) |
|
250 |
-} |
|
251 |
- |
|
252 |
-initializeBigVector <- function(name, n, vmode="integer"){ |
|
253 |
- if(isPackageLoaded("ff")){ |
|
254 |
- results <- ff(vmode=vmode, length=n, pattern=file.path(ldPath(), basename(name))) |
|
255 |
- } else { |
|
256 |
- theNA <- switch(vmode, |
|
257 |
- integer=NA_integer_, |
|
258 |
- double=NA_real_, |
|
259 |
- character=NA_character_, |
|
260 |
- stop("Mode ", vmode, " not implemented for regular matrices")) |
|
261 |
- results <- rep(theNA, n) |
|
262 |
- } |
|
263 |
- return(results) |
|
264 |
-} |
|
265 |
- |
|
266 |
- |
|
267 | 208 |
setMethod("annotatedDataFrameFrom", "ff_matrix", Biobase:::annotatedDataFrameFromMatrix) |
268 | 209 |
setMethod("annotatedDataFrameFrom", "ffdf", Biobase:::annotatedDataFrameFromMatrix) |
269 |
- |
|
270 |
- |
|
271 |
-##annotatedDataFrameFromFF <- function (object, byrow = FALSE, ...){ |
|
272 |
-## dims <- dim(object) |
|
273 |
-## if (is.null(dims) || all(dims == 0)) |
|
274 |
-## annotatedDataFrameFrom(NULL, byrow = byrow, ...) |
|
275 |
-## else { |
|
276 |
-## N <- if (byrow) dims[1] else dims[2] |
|
277 |
-## nms <- if (byrow) rownames(object) else colnames(object) |
|
278 |
-## data <- data.frame(numeric(N), row.names = nms)[, FALSE] |
|
279 |
-## dimLabels <- if (byrow) c("featureNames", "featureColumns") else c("sampleNames", "sampleColumns") |
|
280 |
-## new("AnnotatedDataFrame", data = data, dimLabels = dimLabels) |
|
281 |
-## } |
|
282 |
-##} |
283 | 210 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,34 @@ |
1 |
+citHeader("To cite crlmm in publications use:") |
|
2 |
+ |
|
3 |
+citEntry(entry="article", |
|
4 |
+ title = "Quantifying uncertainty in genotype calls", |
|
5 |
+ author = paste("Benilton S Carvalho and", |
|
6 |
+ "Thomas A Louis and", |
|
7 |
+ "Rafael A Irizarry"), |
|
8 |
+ journal = "Bioinformatics", |
|
9 |
+ year = "2010", |
|
10 |
+ volume = "15;26(2)", |
|
11 |
+ pages = "242-9", |
|
12 |
+ textVersion = paste("Carvalho BS, Louis TA, Irizarry RA.", |
|
13 |
+ "Quantifying uncertainty in genotype calls.", |
|
14 |
+ "Bioinformatics. 2010 Jan 15;26(2):242-9.")) |
|
15 |
+ |
|
16 |
+citEntry(entry="article", |
|
17 |
+ title = "R/Bioconductor software for Illumina's Infinium whole-genome genotyping BeadChips", |
|
18 |
+ author = paste("Matthew E Ritchie and", |
|
19 |
+ "Benilton S Carvalho and", |
|
20 |
+ "Kurt N Hetrick and", |
|
21 |
+ "Simon Tavar\'e and", |
|
22 |
+ "Rafael A Irizarry"), |
|
23 |
+ journal = "Bioinformatics", |
|
24 |
+ year = "2009", |
|
25 |
+ volume = "25(19)", |
|
26 |
+ pages = "2621-3", |
|
27 |
+ textVersion = paste("Ritchie ME, Carvalho BS, Hetrick KN, Tavar\'e S.", |
|
28 |
+ "R/Bioconductor software for Illumina's Infinium whole-genome genotyping BeadChips.", |
|
29 |
+ "Bioinformatics. 2009 Oct 1;25(19):2621-3.")) |
|
30 |
+ |
|
31 |
+ |
|
32 |
+citFooter("We have invested a lot of time and effort in creating crlmm,", |
|
33 |
+ "please cite it when using it for data analysis.") |
|
34 |
+ |
... | ... |
@@ -1,5 +1,5 @@ |
1 | 1 |
%\VignetteIndexEntry{crlmm Vignette - Genotyping} |
2 |
-%\VignetteDepends{crlmm, hapmapsnp5, genomewidesnp5Crlmm} |
|
2 |
+%\VignetteDepends{crlmm, hapmapsnp6, genomewidesnp6Crlmm} |
|
3 | 3 |
%\VignetteKeywords{genotype, crlmm, SNP 5, SNP 6} |
4 | 4 |
%\VignettePackage{crlmm} |
5 | 5 |
\documentclass{article} |
... | ... |
@@ -51,8 +51,8 @@ package. |
51 | 51 |
<<crlmm>>= |
52 | 52 |
require(oligoClasses) |
53 | 53 |
library(crlmm) |
54 |
-library(hapmapsnp5) |
|
55 |
-path <- system.file("celFiles", package="hapmapsnp5") |
|
54 |
+library(hapmapsnp6) |
|
55 |
+path <- system.file("celFiles", package="hapmapsnp6") |
|
56 | 56 |
celFiles <- list.celfiles(path, full.names=TRUE) |
57 | 57 |
system.time(crlmmResult <- crlmm(celFiles, verbose=FALSE)) |
58 | 58 |
@ |
... | ... |
@@ -25,10 +25,10 @@ To use this package, the user must have additional data packages: |
25 | 25 |
} |
26 | 26 |
\author{ |
27 | 27 |
Rafael A Irizarry |
28 |
-Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu> |
|
28 |
+Maintainer: Benilton S Carvalho <carvalho@bclab.org> |
|
29 | 29 |
} |
30 | 30 |
\references{ |
31 |
- Carvalho B, Louis TA, Irizarry RA. Describing Uncertainty in |
|
32 |
- Genome-wide Genotype Calling. (in prep) |
|
31 |
+ Carvalho BS, Louis TA, Irizarry RA. Quantifying uncertainty in genotype |
|
32 |
+ calls. Bioinformatics. 2010 Jan 15;26(2):242-9. Epub 2009 Nov 11. |
|
33 | 33 |
} |
34 | 34 |
\keyword{ package } |
... | ... |
@@ -72,8 +72,8 @@ crlmm2(filenames, row.names=TRUE, col.names=TRUE, |
72 | 72 |
} |
73 | 73 |
\examples{ |
74 | 74 |
## this can be slow |
75 |
-if (require(genomewidesnp5Crlmm) & require(hapmapsnp5)){ |
|
76 |
- path <- system.file("celFiles", package="hapmapsnp5") |
|
75 |
+if (require(genomewidesnp6Crlmm) & require(hapmapsnp6)){ |
|
76 |
+ path <- system.file("celFiles", package="hapmapsnp6") |
|
77 | 77 |
|
78 | 78 |
## the filenames with full path... |
79 | 79 |
## very useful when genotyping samples not in the working directory |
... | ... |
@@ -91,7 +91,7 @@ ocProbesets(50000) |
91 | 91 |
## setup cluster - 8 cores on the machine |
92 | 92 |
setCluster(8, "SOCK") |
93 | 93 |
|
94 |
-path <- system.file("celFiles", package="hapmapsnp5") |
|
94 |
+path <- system.file("celFiles", package="hapmapsnp6") |
|
95 | 95 |
cels <- list.celfiles(path, full.names=TRUE) |
96 | 96 |
crlmmOutput <- crlmm2(cels) |
97 | 97 |
|
... | ... |
@@ -2,14 +2,15 @@ |
2 | 2 |
\alias{crlmmCopynumber} |
3 | 3 |
\title{Locus- and allele-specific estimation of copy number} |
4 | 4 |
\description{ |
5 |
+ Locus- and allele-specific estimation of copy number. |
|
5 | 6 |
} |
6 | 7 |
\usage{ |
7 |
-crlmmCopynumber(object, batch, chromosome = 1:23, MIN.SAMPLES = 10, SNRMin = 5, MIN.OBS = 3, DF.PRIOR = 50, bias.adj = FALSE, prior.prob = rep(1/4, 4), seed = 1, verbose = TRUE, GT.CONF.THR = 0.99, PHI.THR = 2^6, nHOM.THR = 5, MIN.NU = 2^3, MIN.PHI = 2^3, THR.NU.PHI = TRUE, thresholdCopynumber = TRUE) |
|
8 |
+crlmmCopynumber(object, chromosome = 1:23, which.batches, MIN.SAMPLES = 10, SNRMin = 5, MIN.OBS = 3, DF.PRIOR = 50, bias.adj = FALSE, prior.prob = rep(1/4, 4), seed = 1, verbose = TRUE, GT.CONF.THR = 0.99, PHI.THR = 2^6, nHOM.THR = 5, MIN.NU = 2^3, MIN.PHI = 2^3, THR.NU.PHI = TRUE, thresholdCopynumber = TRUE) |
|
8 | 9 |
} |
9 | 10 |
\arguments{ |
10 | 11 |
\item{object}{object of class \code{SnpSuperSet}. |
11 | 12 |
} |
12 |
- \item{batch}{ Character vector with length equal to the number of |
|
13 |
+ \item{which.batches}{ Character vector with length equal to the number of |
|
13 | 14 |
samples. Used to adjust for batch effects. Chemistry plate or |
14 | 15 |
date often work well. See examples. |
15 | 16 |
} |
... | ... |
@@ -105,15 +106,7 @@ crlmmCopynumber(object, batch, chromosome = 1:23, MIN.SAMPLES = 10, SNRMin = 5, |
105 | 106 |
5 are assigned the value 5. |
106 | 107 |
} |
107 | 108 |
} |
108 |
-\details{ |
|
109 |
-} |
|
110 |
-\value{ |
|
111 |
-} |
|
112 |
-\references{ |
|
113 |
-} |
|
114 | 109 |
\author{R. Scharpf} |
115 |
-\note{} |
|
116 |
-\seealso{} |
|
117 | 110 |
\examples{ |
118 | 111 |
## data(example.callSet) |
119 | 112 |
## cnSet <- crlmmCopynumber(example.callSet) |
... | ... |
@@ -29,8 +29,7 @@ genotype(filenames, cdfName, mixtureSampleSize = 10^5, eps = 0.1, verbose = TRUE |
29 | 29 |
\item{returnParams}{'logical'. Return recalibrated parameters from crlmm.} |
30 | 30 |
\item{badSNP}{'numeric'. Threshold to flag as bad SNP (affects batchQC)} |
31 | 31 |
} |
32 |
-\details{ |
|
33 |
-} |
|
32 |
+ |
|
34 | 33 |
\value{ A \code{SnpSuperSet} instance.} |
35 | 34 |
\references{ |
36 | 35 |
|
... | ... |
@@ -51,17 +50,16 @@ this will greatly reduce the RAM required for big jobs. See |
51 | 50 |
|
52 | 51 |
\seealso{ |
53 | 52 |
\code{\link{snprma}}, \code{\link{crlmm}}, |
54 |
- \code{\link{validCdfNames}}, |
|
55 |
- \code{\link{oligoClasses}{ocSamples}}, |
|
56 |
- \code{\link{oligoClasses}{ldOpts}} |
|
53 |
+ \code{\link[oligoClasses]{ocSamples}}, |
|
54 |
+ \code{\link[oligoClasses]{ldOpts}} |
|
57 | 55 |
} |
58 | 56 |
\examples{ |
59 |
-if (require(genomewidesnp5Crlmm) & require(hapmapsnp5)){ |
|
60 |
- path <- system.file("celFiles", package="hapmapsnp5") |
|
57 |
+if (require(genomewidesnp6Crlmm) & require(hapmapsnp6)){ |
|
58 |
+ path <- system.file("celFiles", package="hapmapsnp6") |
|
61 | 59 |
## the filenames with full path... |
62 | 60 |
## very useful when genotyping samples not in the working directory |
63 | 61 |
cels <- list.celfiles(path, full.names=TRUE) |
64 |
- (crlmmOutput <- genotype(cels, cdfName="genomewidesnp5")) |
|
62 |
+ (crlmmOutput <- genotype(cels, cdfName="genomewidesnp6")) |
|
65 | 63 |
} |
66 | 64 |
} |
67 | 65 |
\keyword{ classif } |
... | ... |
@@ -56,8 +56,8 @@ snprma2(filenames, mixtureSampleSize = 10^5, fitMixture = FALSE, eps = 0.1, verb |
56 | 56 |
the use of clusters or multiple cores (via snow package) to speed up preprocessing. |
57 | 57 |
} |
58 | 58 |
\examples{ |
59 |
-if (require(genomewidesnp5Crlmm) & require(hapmapsnp5) & require(oligoClasses)){ |
|
60 |
- path <- system.file("celFiles", package="hapmapsnp5") |
|
59 |
+if (require(genomewidesnp6Crlmm) & require(hapmapsnp6) & require(oligoClasses)){ |
|
60 |
+ path <- system.file("celFiles", package="hapmapsnp6") |
|
61 | 61 |
|
62 | 62 |
## the filenames with full path... |
63 | 63 |
## very useful when genotyping samples not in the working directory |
... | ... |
@@ -76,7 +76,7 @@ ocProbesets(50000) |
76 | 76 |
## setup cluster - 8 cores on the machine |
77 | 77 |
setCluster(8, "SOCK") |
78 | 78 |
|
79 |
-path <- system.file("celFiles", package="hapmapsnp5") |
|
79 |
+path <- system.file("celFiles", package="hapmapsnp6") |
|
80 | 80 |
cels <- list.celfiles(path, full.names=TRUE) |
81 | 81 |
snprmaOutput <- snprma2(cels) |
82 | 82 |
|