git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@58649 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
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.11.27 |
|
4 |
+Version: 1.11.28 |
|
5 | 5 |
Date: 2010-12-10 |
6 | 6 |
Author: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au>, Ingo Ruczinski <iruczins@jhsph.edu>, Rafael A Irizarry |
7 | 7 |
Maintainer: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
... | ... |
@@ -2675,15 +2675,25 @@ posteriorMean.snp <- function(stratum, object, index.list, CN, |
2675 | 2675 |
## return(list2SnpSet(res2, returnParams=returnParams)) |
2676 | 2676 |
##} |
2677 | 2677 |
|
2678 |
-genotypes <- function(copyNumber){ |
|
2678 |
+genotypes <- function(copyNumber, is.snp=TRUE){ |
|
2679 | 2679 |
stopifnot(copyNumber %in% 0:4) |
2680 | 2680 |
cn <- paste("x", copyNumber, sep="") |
2681 |
- switch(cn, |
|
2682 |
- x0="NULL", |
|
2683 |
- x1=LETTERS[1:2], |
|
2684 |
- x2=c("AA", "AB", "BB"), |
|
2685 |
- x3=c("AAA", "AAB", "ABB", "BBB"), |
|
2686 |
- x4=c("AAAA", "AAAB", "AABB", "ABBB", "BBBB")) |
|
2681 |
+ if(is.snp){ |
|
2682 |
+ res <- switch(cn, |
|
2683 |
+ x0="NULL", |
|
2684 |
+ x1=LETTERS[1:2], |
|
2685 |
+ x2=c("AA", "AB", "BB"), |
|
2686 |
+ x3=c("AAA", "AAB", "ABB", "BBB"), |
|
2687 |
+ x4=c("AAAA", "AAAB", "AABB", "ABBB", "BBBB")) |
|
2688 |
+ } else { |
|
2689 |
+ res <- switch(cn, |
|
2690 |
+ x0="NULL", |
|
2691 |
+ x1="A", |
|
2692 |
+ x2="AA", |
|
2693 |
+ x3="AAA", |
|
2694 |
+ x4="AAAA") |
|
2695 |
+ } |
|
2696 |
+ return(res) |
|
2687 | 2697 |
} |
2688 | 2698 |
|
2689 | 2699 |
dbvn <- function(x, mu, Sigma){ |
... | ... |
@@ -446,5 +446,9 @@ setMethod("xyplotcrlmm", signature(x="formula", data="CNSet", predictRegion="lis |
446 | 446 |
}) |
447 | 447 |
setMethod("xyplot", signature(x="formula", data="CNSet"), |
448 | 448 |
function(x, data, ...){ |
449 |
- xyplotcrlmm(x, data, ...) |
|
449 |
+ if("predictRegion" %in% names(list(...))){ |
|
450 |
+ xyplotcrlmm(x, data, ...) |
|
451 |
+ } else{ |
|
452 |
+ callNextMethod() |
|
453 |
+ } |
|
450 | 454 |
}) |
... | ... |
@@ -74,11 +74,12 @@ rawCopynumber(object,...) |
74 | 74 |
|
75 | 75 |
Subsetting the \code{CNSet} object before extracting copy number can be |
76 | 76 |
very inefficient when the data set is very large, particularly if using |
77 |
-ff objects. The \code{[] method will subset all of the assay data |
|
77 |
+ff objects. The \code{[} method will subset all of the assay data |
|
78 | 78 |
elements and all of the elements in the LinearModelParameter slot. |
79 | 79 |
|
80 | 80 |
} |
81 | 81 |
|
82 |
+ |
|
82 | 83 |
\seealso{ |
83 | 84 |
|
84 | 85 |
\code{\link{crlmmCopynumber}}, \code{\link{CNSet-class}} |
... | ... |
@@ -8,12 +8,15 @@ |
8 | 8 |
The possible genotypes for an integer copy number (0-4). |
9 | 9 |
} |
10 | 10 |
\usage{ |
11 |
-genotypes(copyNumber) |
|
11 |
+genotypes(copyNumber, is.snp=TRUE) |
|
12 | 12 |
} |
13 | 13 |
|
14 | 14 |
\arguments{ |
15 | 15 |
\item{copyNumber}{ |
16 | 16 |
Integer (0-4 allowed).} |
17 |
+ |
|
18 |
+ \item{is.snp}{Logical. If TRUE, possible genotypes for a polymorphic |
|
19 |
+ SNP is returned. If FALSE, only monomorphic genotypes returned.} |
|
17 | 20 |
} |
18 | 21 |
|
19 | 22 |
\value{ |
... | ... |
@@ -27,6 +30,7 @@ R. Scharpf |
27 | 30 |
\examples{ |
28 | 31 |
|
29 | 32 |
for(i in 0:4) print(genotypes(i)) |
33 |
+for(i in 0:4) print(genotypes(i, FALSE)) |
|
30 | 34 |
|
31 | 35 |
} |
32 | 36 |
|
... | ... |
@@ -110,7 +110,7 @@ all.equal(cn4, cn2) |
110 | 110 |
|
111 | 111 |
## markers 1-5, all samples |
112 | 112 |
cn5 <- totalCopynumber(sample.CNSet, i=1:5) |
113 |
-## all markers, samples 1-5 |
|
114 |
-cn6 <- totalCopynumber(sample.CNSet, j=1:5) |
|
113 |
+## all markers, samples 1-2 |
|
114 |
+cn6 <- totalCopynumber(sample.CNSet, j=1:2) |
|
115 | 115 |
} |
116 | 116 |
\keyword{datasets} |
... | ... |
@@ -78,10 +78,22 @@ xyplot(B~A|snpid, data=sample.CNSet2[1:10, sample.index], |
78 | 78 |
|
79 | 79 |
|
80 | 80 |
## nonpolymorphic markers |
81 |
-np.index <- which(!isSnp(sample.CNSet2)) |
|
82 |
-sample.index <- which(batch(sample.CNSet2) %in% bns) |
|
83 |
-pr <- predictionRegion(sample.CNSet2[np.index, sample.index], copyNumber=0:4) |
|
81 |
+data(sample.CNSet2) |
|
82 |
+tab <- table(batch(sample.CNSet2)) |
|
83 |
+bns <- names(tab)[tab > 50] |
|
84 |
+sample.index <- which(batch(sample.CNSet2) %in% bns[1:3]) |
|
85 |
+np.index <- which(!isSnp(sample.CNSet2))[1:10] |
|
86 |
+taus <- tau2(sample.CNSet)[np.index, , , ] |
|
87 |
+trace(predictionRegion, browser, signature=c("CNSet", "integer")) |
|
88 |
+pr <- predictionRegion(sample.CNSet2[np.index, sample.index], |
|
89 |
+ copyNumber=0:4) |
|
90 |
+trace(posteriorProbability, browser, signature="CNSet") |
|
91 |
+pp <- posteriorProbability(sample.CNSet2[np.index, sample.index], |
|
92 |
+ predictRegion=pr, |
|
93 |
+ copyNumber=0:4) |
|
94 |
+pm <- calculatePosteriorMean(sample.CNSet2[np.index, sample.index], posteriorProb=pp) |
|
95 |
+ |
|
84 | 96 |
} |
85 | 97 |
|
86 | 98 |
\keyword{dplot} |
87 |
-\keyword{hplot} |
|
88 | 99 |
\ No newline at end of file |
100 |
+\keyword{hplot} |