Browse code

added scanDates<- for CrlmmSetList. Suggests VanillaICE>=1.7.8

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

Rob Scharp authored on 16/07/2009 13:32:48
Showing 10 changed files

... ...
@@ -224,3 +224,12 @@ is decoded and scanned
224 224
 * computeCopynumber requires 10 or more samples
225 225
 
226 226
 
227
+2009-07-16 R Scharpf - committed version 1.3.12
228
+
229
+* scanDates replacement method for CrlmmSetList objects
230
+
231
+* added .man page for .computeCopynumber 
232
+
233
+* Suggests VanillaICE (>= 1.7.8)  -- needed to run the copynumber.Rnw vignette
234
+
235
+
... ...
@@ -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.3.11
4
+Version: 1.3.12
5 5
 Date: 2009-06-17
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>
... ...
@@ -9,7 +9,8 @@ Description: Faster implementation of CRLMM specific to SNP 5.0 and 6.0 arrays,
9 9
 License: Artistic-2.0
10 10
 Depends: methods
11 11
 Imports: affyio, preprocessCore, utils, stats, genefilter, splines, Biobase (>= 2.5.3), mvtnorm, oligoClasses, ellipse, methods
12
-Suggests: hapmapsnp5, hapmapsnp6, genomewidesnp5Crlmm (>= 1.0.2), genomewidesnp6Crlmm (>= 1.0.2), GGdata, snpMatrix
12
+Suggests: hapmapsnp5, hapmapsnp6, genomewidesnp5Crlmm (>= 1.0.2),
13
+genomewidesnp6Crlmm (>= 1.0.2), GGdata, snpMatrix, VanillaICE (>= 1.7.8)
13 14
 Collate: AllClasses.R
14 15
 	 AllGenerics.R
15 16
 	 methods-ABset.R
... ...
@@ -77,6 +77,8 @@ export(batch,
77 77
 ##       ellipse,
78 78
 ##       computeEmission,
79 79
        list.celfiles,
80
+       ncol,
81
+       nrow,
80 82
        position,
81 83
        readIdatFiles,
82 84
        sampleNames,
... ...
@@ -482,6 +482,7 @@ computeCopynumber <- function(object,
482 482
 	##previous version of compute copy number
483 483
 	envir <- new.env()
484 484
 	message("Fitting model for copy number estimation...")
485
+	message("Using ", DF.PRIOR, " df for inverse chi squares.")	
485 486
 	.computeCopynumber(chrom=CHR,
486 487
 			   A=A(ABset),
487 488
 			   B=B(ABset),
... ...
@@ -1050,7 +1051,8 @@ withinGenotypeMoments <- function(p, A, B, calls, conf, CONF.THR, DF.PRIOR, envi
1050 1051
 	plate <- envir[["plate"]]
1051 1052
 	uplate <- envir[["uplate"]]
1052 1053
 	normal <- envir[["normal"]][, plate==uplate[p]]
1053
-	G <- calls; rm(calls); gc()	
1054
+	G <- calls; rm(calls); gc()
1055
+
1054 1056
 
1055 1057
 	highConf <- 1-exp(-conf/1000)
1056 1058
 	highConf <- highConf > CONF.THR
... ...
@@ -91,6 +91,11 @@ setMethod("points", signature(x="CrlmmSetList"),
91 91
 
92 92
 setMethod("sampleNames", "CrlmmSetList", function(object) sampleNames(object[[1]]))
93 93
 setMethod("scanDates", "CrlmmSetList", function(object) scanDates(object[[1]]))
94
+setReplaceMethod("scanDates", signature(object="CrlmmSetList", value="character"), function(object, value){
95
+	scanDates(object[[1]]) <- value
96
+	return(object)
97
+}) 
98
+
94 99
 setMethod("show", "CrlmmSetList", function(object){
95 100
 	for(i in seq(along=object)) show(object[[i]])
96 101
 })
... ...
@@ -36,18 +36,10 @@ HapMap samples.
36 36
 We preprocess and genotype the samples as described in the CRLMM
37 37
 vignette.
38 38
 
39
-<<test, eval=FALSE, echo=FALSE>>=
40
-library(crlmm)
41
-load("~/madman/Rpacks/crlmm/inst/scripts/example.cnset.rda")
42
-chromosome(example.cnset)[1:5]
43
-position(example.cnset)[1:5]
44
-scanDates(example.cnset)[1:5]
45
-@ 
46
-
47 39
 <<requiredPackages>>=
48 40
 library(crlmm)
49 41
 library(genomewidesnp6Crlmm)
50
-library(Biobase)
42
+library(Biobase) 
51 43
 @ 
52 44
 
53 45
 Specify the complete path for the CEL files and a directory in which to
... ...
@@ -55,7 +47,8 @@ store intermediate files:
55 47
 
56 48
 
57 49
 <<celfiles>>=
58
-celFiles <- list.celfiles("/thumper/ctsa/snpmicroarray/hapmap/raw/affy/1m", full.names=TRUE, pattern=".CEL")
50
+celFiles <- list.celfiles("/thumper/ctsa/snpmicroarray/hapmap/raw/affy/1m", 
51
+			  full.names=TRUE, pattern=".CEL")
59 52
 outdir <- "/thumper/ctsa/snpmicroarray/rs/data/hapmap/1m/affy"
60 53
 @ 
61 54
 
... ...
@@ -115,6 +108,7 @@ sns[1]
115 108
 plate <- substr(basename(sns), 13, 13)
116 109
 table(plate)
117 110
 table(format(as.POSIXlt(scanDates(crlmmResults)), "%d %b %Y"), plate)
111
+dts <- scanDates(crlmmResults)
118 112
 @ 
119 113
 
120 114
 As all of these samples were run on the first week of March, we would
... ...
@@ -58,7 +58,6 @@ hist(crlmmOut$SNR) ##approx. 5-fold higher than what we see in Affy!
58 58
 ##cnAB was assigned to the global environment
59 59
 NP = (cnAB$A+cnAB$B)/2 # average normalized A and B intensities
60 60
 colnames(NP) <- colnames(crlmm:::calls(crlmmOut))
61
-cnenv = new.env()
62 61
 chr22 <- computeCopynumber(chrom=22, A=res[["A"]], B=res[["B"]], 
63 62
 			   calls=crlmm:::calls(crlmmOut),
64 63
 			   conf=confs(crlmmOut), 
65 64
new file mode 100644
... ...
@@ -0,0 +1,113 @@
1
+\name{.computeCopynumber}
2
+\alias{.computeCopynumber}
3
+\title{Internal function for computing copy number}
4
+\description{
5
+
6
+  This function is not meant to be called directly by the user and is
7
+  not exported in the package namespace.  Arguments to this function can
8
+  be specified in the 'computeCopynumber' (no '.' preceding the name)
9
+  function.
10
+  
11
+}
12
+\usage{
13
+.computeCopynumber(chrom, A, B, calls, conf, NP, plate, MIN.OBS=1, 
14
+envir, P, DF.PRIOR = 50, CONF.THR = 0.99, bias.adj=FALSE,
15
+priorProb, gender=NULL, SNR, SNRmin, seed=123, cdfName="genomewidesnp6",
16
+verbose=TRUE, ...)
17
+}
18
+\arguments{
19
+  \item{chrom}{Chromosome (an integer).  Use 23 for X and 24 for Y.}
20
+  \item{A}{The A allele intensities from \code{snprma}}
21
+  \item{B}{The B allele intensities from \code{snprma}}
22
+  \item{calls}{The genotype calls from \code{crlmm}}
23
+  \item{conf}{The genotype confidence scores from \code{crlmm}}
24
+  \item{NP}{The quantile normalized intensities of the nonpolymorphic probes}
25
+  \item{plate}{The bach variable.  Should be the same length as the
26
+    number of columns in A}
27
+  \item{MIN.OBS}{Integer: The minimum number of observations in a genotype
28
+    cluster for which a SNP is deemed complete.}
29
+  \item{envir}{An environment to save intermediate objects}
30
+  \item{P}{Mainly for debugging a particular plate/batch.}
31
+  \item{DF.PRIOR}{The degrees of freedom for the prior.  Higher numbers
32
+    will shrink the variance and correlation more.}
33
+  \item{CONF.THR}{A threshold for the genotype confidence scores.
34
+    Genotypes with scores below the threshold are ignored when computing
35
+  SNP-specific  within-genotype estimates of location and scale.}
36
+  \item{bias.adj}{Logical: whether to adjust the location and scale
37
+    parameters to account for biases due to common copy number
38
+    variants.  This is a SNP-specific adjustment.  Parameters for
39
+    background and slope must have already been estimated and available
40
+    from the environment variable.}
41
+  \item{priorProb}{Numerical vector of length 4.  The prior probability
42
+    of each copy number state (0, 1, 2, 3, and 4). The default is a
43
+    uniform prior.  Ignored if bias.adj=FALSE}
44
+  \item{gender}{Gender of subjects. If not specified, we predict the
45
+    gender from the X chromosome.}
46
+  \item{SNR}{Signal to noise ratio from crlmm.}
47
+  \item{SNRmin}{The minimum value for the SNR -- we suggest 5. Samples
48
+    with SNR below SNRmin are excluded.}
49
+  \item{seed}{Seed used for random samples}
50
+  \item{cdfName}{Annotation package }
51
+  \item{verbose}{Logical: verbose output}
52
+  \item{\dots}{Currently ignored}
53
+}
54
+
55
+\details{
56
+  
57
+  This function transforms the intensities to a copy number scale.  We
58
+  assume that the median within-SNP intensity across samples is 2.  We
59
+  make no assumption about the chromosomal copy number. This function is
60
+  useful for detecting rare variants (e.g., variants that would not
61
+  affect the SNP-specific quantile-based estimators of location and
62
+  scale).  A correction for more common variants is coming, as well as
63
+  improved estimates of the uncertainty.
64
+  
65
+}
66
+
67
+\value{
68
+
69
+All objects created by this function are stored in the environment
70
+  passed to this function.  In addition, each of the elements are
71
+  specific to the chromosome(s) specified by the argument \code{chrom}.
72
+  For instance the element \code{A} is the matrix of quantile-normalized
73
+  intensities for the A-allele on chromosome(s) \code{chrom}.  The
74
+  element of this environment are as follows
75
+
76
+  \item{A}{Matrix of quantile-normalized intensities for the A-allele}
77
+  \item{B}{Matrix of quantile-normalized intensities for the A-allele}
78
+  \item{CA}{Copy number estimate for the A-allele (x 100)} 
79
+  \item{CB}{Copy number estimate for the B-allele (x 100)}
80
+  \item{calls}{CRLMM genotype calls (AA=1, AB=2, BB=3)}
81
+  \item{chrom}{Integer(s) indicating the chromosome(s)} 
82
+  \item{cnvs}{Names of the nonpolymorphic probes.  These are the
83
+  rownames of \code{NP} and \code{CT}.}
84
+  \item{conf}{CRLMM confidence scores for the genotypes: 'round(-1000*log2(1-p))'}
85
+  \item{corr}{Correlation of the A and B alleles for genotypes AB}
86
+  \item{corrA.BB}{Correlation of A and B alleles for genotypes BB}
87
+  \item{corrB.AA}{Correlation of A and B alleles for genotypes AA}
88
+  \item{CT}{Copy number estimates for nonpolymorphic probe.  See
89
+  \code{cnvs} for the rownames.}
90
+  \item{CT.sds}{Standard deviation estimates for \code{CT}}
91
+  \item{npflags}{Flags for the nonpolymorphic probes.}
92
+  \item{Ns}{The number of observations for each genotype/plate}
93
+  \item{nuA}{Background/cross-hyb for the A allele (plate- and locus-specific)}
94
+  \item{nuB}{Background/cross-hyb for the B allele (plate- and locus-specific)}
95
+  \item{nuT}{Background for the nonpolymorphic probes (plate- and locus-specific)}
96
+  \item{phiA}{Slope for the A allele (plate- and locus-specific)}
97
+  \item{phiB}{Slope for the B allele (plate- and locus-specific)}
98
+  \item{phiT}{Slope for the nonpolymorphic probes (plate- and locus-specific)}
99
+  \item{plate}{Factor indicating batch (same length as number of cel files)}
100
+  \item{sig2A}{Variance estimate for the A-allele signal (plate- and locus-specific)}
101
+  \item{sig2B}{Variance estimate for the B-allele signal (plate- and locus-specific)}
102
+  \item{sig2T}{Variance estimate for the nonpolymorphic signal (plate- and locus-specific)}
103
+  \item{snpflags}{Flags for polymorphic probes}
104
+  \item{snps}{Rownames for \code{A}, \code{B}, \code{CA}, \code{CB}, ...}
105
+  \item{sns}{ Sample names -- the column names for \code{A}, \code{B}, ...}
106
+  \item{steps}{Steps completed. For internal use.}
107
+  \item{tau2A}{Variance estimate for the B-allele background/cross-hyb (plate- and locus-specific)}
108
+  \item{tau2B}{Variance estimate for the B-allele background/cross-hyb (plate- and locus-specific)}
109
+}
110
+\references{Nothing yet.}
111
+\author{Rob Scharpf}
112
+\keyword{manip}
113
+
... ...
@@ -21,6 +21,7 @@
21 21
 \alias{position,CrlmmSetList-method}
22 22
 \alias{sampleNames,CrlmmSetList-method}
23 23
 \alias{scanDates,CrlmmSetList-method}
24
+\alias{scanDates<-,CrlmmSetList,character-method}
24 25
 \alias{show,CrlmmSetList-method}
25 26
 \alias{snpIndex,CrlmmSetList-method}
26 27
 
... ...
@@ -121,10 +122,16 @@
121 122
     \item{"sampleNames"}{\code{signature(object = "CrlmmSetList")}:
122 123
       Accessor for the column identifiers of the assay data elements.  }
123 124
 
125
+    \item{"scanDates"}{\code{signature(object = "CrlmmSetList")}:
126
+      Accessor for the timestamp when the array was processed.  }
127
+
128
+    \item{"scanDates<-"}{\code{signature(object = "CrlmmSetList",
129
+      value="character")}: Add dates to the scanDates slot in the first
130
+      element of the \code{CrlmmSetList} object.  }
131
+
124 132
     \item{"show"}{\code{signature(object = "CrlmmSetList")}:
125 133
       Shows the \code{ABset} and \code{SnpSet} elements of the list.  }
126 134
 
127
-
128 135
     \item{"snpIndex"}{\code{signature(object = "CrlmmSetList")}: returns
129 136
       the row indices of the polymorphic probes.}
130 137
     
... ...
@@ -20,8 +20,7 @@ computeCopynumber(object, CHR, bias.adj=FALSE, batch, SNRmin=5, cdfName="genomew
20 20
   \item{SNRmin}{The minimum value for the SNR -- we suggest 5. Samples
21 21
     with SNR below SNRmin are dropped.}
22 22
   \item{cdfName}{Annotation package }
23
-  \item{\dots}{arguments to \code{.computeCopynumber} -- not called by
24
-    the user.}
23
+  \item{\dots}{arguments to \code{.computeCopynumber}.}
25 24
 }
26 25
 
27 26
 \details{
... ...
@@ -48,9 +47,8 @@ computeCopynumber(object, CHR, bias.adj=FALSE, batch, SNRmin=5, cdfName="genomew
48 47
 }
49 48
 
50 49
 \seealso{
51
-  \code{\linkS4class{CopyNumberSet-class}}
50
+  \code{\linkS4class{CopyNumberSet}},   \code{\link{".computeCopynumber"}}
52 51
 }
53
-\references{Nothing yet.}
54 52
 \author{Rob Scharpf}
55 53
 \keyword{manip}
56 54
 \keyword{models}