inst/scripts/copynumber.Rnw
16fadf14
   Copy number routines in the \crlmm{} package are available for
   Affymetrix 5.0 and 6.0 platforms, as well as several Illumina
   platforms.  This vignette assumes that the arrays have already been
   successfully preprocessed and genotyped as per the instructions in
   the \verb+AffymetrixPreprocessCN+ and \verb+IlluminaPreprocessCN+
   vignettes for the Affymetrix and Illumina platforms,
   respectively. While this vignette uses Affymetrix 6.0 arrays for
   illustration, the steps at this point are identical for both
669c6a90
   platforms.  See \citep{Scharpf2011} for details regarding the
16fadf14
   methodology implemented in \crlmm{} for copy number analysis.  In
   addition, a compendium describing copy number analysis using the
   \crlmm{} package is available from the author's website:
0621b63a
   \url{http://www.biostat.jhsph.edu/~rscharpf/crlmmCompendium/index.html}.
e63564bc
 
7ae22f52
 
16fadf14
 \textbf{Limitations:} While a minimum number of samples is not
 required for preprocessing and genotyping, copy number estimation in
 the \crlmm{} package currently requires at least 10 samples per batch.
 The parameter estimates for copy number and the corresponding
 estimates of raw copy number will tend to be more noisy for batches
 with small sample sizes (e.g., $<$ 50).  Chemistry plate or scan date
669c6a90
 are often useful surrogates for batch.  Samples that were processed at
 similar times (e.g., in the same month) can be grouped together in the
 same batch.
518a2908
 
16fadf14
 \section{Quality control}
518a2908
 
16fadf14
 The signal to noise ratio (SNR) estimated by the CRLMM genotyping
 algorithm is an overall measure of the separation of the diallelic
 genotype clusters at polymorphic loci and can be a useful measure of
 array quality.  Small SNR values can indicate possible problems with
 the DNA.  Depending on the size of the dataset and the number of
 samples with low SNR, users may wish to rerun the preprocessing and
 genotyping steps after excluding samples with low SNR.  The SNR is
 stored in the \verb+phenoData+ slot of the \Robject{CNSet} object and
 is available after preprocessing and genotyping. SNR values below 5
 for Affymetrix or below 25 for Illumina may indicate poor sample
 quality.  The following code chunk makes a histogram of the SNR values
 for the HapMap samples.
518a2908
 
16fadf14
 <<snr,fig=TRUE,include=FALSE,width=6, height=4>>=
7c0c9ac5
 library(lattice)
669c6a90
 invisible(open(cnSet$SNR))
16fadf14
 snr <- cnSet$SNR[]
 close(cnSet$SNR)
7c0c9ac5
 print(histogram(~snr,
 		panel=function(...){
 			panel.histogram(...)},
 		breaks=25, xlim=range(snr), xlab="SNR"))
e63564bc
 @
7c0c9ac5
 
2ae7850e
 
0198a9ad
 
16fadf14
 \section{Copy number estimation}
 
669c6a90
 As described in \cite{Scharpf2011}, the CRLMM-CopyNumber algorithm
16fadf14
 fits a linear model to the normalized intensities stratified by the
 diallic genotype call.  The intercept and slope from the linear model
 are both SNP- and batch-specific.  The implementation in the \crlmm{}
 package is encapsulated by the function \Rfunction{crlmmCopynumber}
 that, using the default settings, can be called by passing a single
669c6a90
 object of class \Rclass{CNSet}.  See the appropriate
16fadf14
 preprocessing/genotyping vignette for the construction of an object of
 class \Rclass{CNSet}.
 <<LDS_copynumber,cache=TRUE>>=
 (cnSet.updated <- crlmmCopynumber(cnSet))
 @
66900fea
 
16fadf14
 The following steps were performed by the \Rfunction{crlmmCopynumber}
 function:
0198a9ad
 \begin{itemize}
16fadf14
 \item sufficient statistics for the genotype clusters for
   each batch
 \item unobserved genotype centers imputed
 \item posterior summaries of sufficient statistics
 \item intercept and slope for linear model
ac19c848
 \end{itemize}
16fadf14
 Depending on the value of \verb+ocProbesets()+, these summaries are
 computed for subsets of the markers to reduce the required RAM. Note
 that the value returned by the \Rfunction{crlmmCopynumber} function in
 the above example is \verb+TRUE+.  The reason the function returns
 \verb+TRUE+ in the above example is that the elements of the
7c0c9ac5
 \verb+batchStatistics+ slot have the class \Rclass{ff\_matrix}.
 Rather than keep the statistical summaries in memory, the summaries
 are written to files on disk using protocols described in the
16fadf14
 \Rpackage{ff} package. Hence, while the \Robject{cnSet} object itself
 is unchanged as a result of the \Rfunction{crlmmCopynumber} function,
 the data on disk is updated accordingly.  Users that are interested in
 accessing these low-level summaries can refer to the
7c0c9ac5
 \verb+Infrastructure+ vignette.  Note that the data structure depends
 on whether the elements of the \verb+batchStatistics+ slot are
 \Robject{ff} objects or ordinary matrices.  In this example, the
 elements of \verb+batchStatistics+ have the class \Rclass{ff\_matrix}.
518a2908
 
669c6a90
 <<classes>>=
16fadf14
 nms <- ls(batchStatistics(cnSet))
 cls <- rep(NA, length(nms))
 for(i in seq_along(nms)) cls[i] <- class(batchStatistics(cnSet)[[nms[i]]])[1]
 all(cls == "ff_matrix")
 @
 
 The batch-specific statistical summaries computed by
 \Robject{crlmmCopynumber} are written to files on disk using protocols
 described in the \R{} package \Rpackage{ff}. The value returned by
 \Rfunction{crlmmCopynumber} is \verb+TRUE+, indicating that the files
 on disk have been successfully updated.  Note that while the
 \Robject{cnSet} object is unchanged, the values on disk are different.
7c0c9ac5
 On the other hand, subsetting the \Robject{cnSet} with the `[' method
 coerces all of the elements to class \Rclass{matrix}. The
16fadf14
 batch-specific summaries are now ordinary matrices stored in RAM. The
 object returned by \Robject{crlmmCopynumber} is an object of class
 \Rclass{CNSet} with the matrices in the \verb+batchStatistics+ slot
 updated.
 
 <<chr1index>>=
 chr1.index <- which(chromosome(cnSet) == 1)
453e688a
 open(cnSet)
e63564bc
 @
518a2908
 
16fadf14
 <<subset,cache=TRUE>>=
 cnSet2 <- cnSet[chr1.index, ]
 @
 
 <<valuematrix>>=
 close(cnSet)
 for(i in seq_along(nms)) cls[i] <- class(batchStatistics(cnSet2)[[nms[i]]])[1]
 all(cls == "matrix")
 @
 
 <<matrix_copynumber,cache=TRUE>>=
 cnSet3 <- crlmmCopynumber(cnSet2)
 class(cnSet3)
 @
 
 <<clean, echo=FALSE, results=hide>>=
 rm(cnSet2); gc()
 @
 
7c0c9ac5
 \subsection{Marker-specific estimates}
 %\subsection{Raw copy number}
 
 %\paragraph{Log R ratios and B allele frequencies.}
16fadf14
 
7c0c9ac5
 \paragraph{Raw total copy number.}
16fadf14
 Several functions are available that will compute relatively quickly
 the allele-specific, \emph{raw} copy number estimates. At allele $k$,
0198a9ad
 marker $i$, sample $j$, and batch $p$, the estimate of allele-specific
 copy number is computed by subtracting the estimated background from
7c0c9ac5
 the normalized intensity and scaling by the slope coefficient. More
 formally, \newcommand{\A}{A} \newcommand{\B}{B}
66900fea
 \begin{eqnarray}
   \label{eq:cnK}
 {\hat c}_{k,ijp} &=& \mbox{max}\left\{\frac{1}{{\hat
     \phi}_{k,ip}}\left(I_{k,ijp}-{\hat \nu}_{k,ip}\right), ~0\right\}
 \mbox{~for~} k \in \{\A, \B\}.
0198a9ad
 \end{eqnarray}
66900fea
 \noindent See \cite{Scharpf2010} for details.
 
16fadf14
 The function \Rfunction{totalCopynumber} translates the normalized
 intensities to an estimate of raw copy number by adding the
 allele-specific summaries in Equation \eqref{eq:cnK}. For large
 datasets, the calculation will not be instantaneous as the I/O can be
 substantial.  Users should specify either a subset of the markers or a
 subset of the samples to avoid using all of the available RAM.  For
 example, in the following code chunk we compute the total copy number
 at all markers for the first 2 samples, and the total copy number for
 chromosome 20 for the first 50 samples.
 
 <<totalCopynumber>>=
7c0c9ac5
 tmp <- totalCopynumber(cnSet, i=seq_len(nrow(cnSet)), j=1:2)
16fadf14
 dim(tmp)
7c0c9ac5
 tmp2 <- totalCopynumber(cnSet, i=which(chromosome(cnSet) == 20), j=seq_len(ncol(cnSet)))
16fadf14
 dim(tmp2)
 @
 
 Alternatively, the functions \Rfunction{CA} and \Rfunction{CB} compute
 the allele-specific copy number.  For instance, the following code
 chunk computes the allele-specific summaries at all polymorphic loci.
66900fea
 
 <<ca>>=
7eaf43e8
 snp.index <- which(isSnp(cnSet) & !is.na(chromosome(cnSet)))
7c0c9ac5
 ca <- CA(cnSet, i=snp.index, j=seq_len(ncol(cnSet)))
 cb <- CB(cnSet, i=snp.index, j=seq_len(ncol(cnSet)))
16fadf14
 @
 
0198a9ad
 
7c0c9ac5
 \subsection{Container for raw copy number}
16fadf14
 
 A useful container for storing the \crlmm{} genotypes, genotype
 confidence scores, and the total copy number at each marker is the
 \Rclass{oligoSnpSet} class.  Coercion of a \Rclass{CNSet} object to a
 \Rfunction{oligoSnpSet} object can be acheived by using the method
 \Rfunction{as} (as illustrated below). Users should note that if the
 \verb+assayData+ elements in the \Rclass{CNSet} instance are
 \Rpackage{ff} objects, the \verb+assayData+ elements of the
669c6a90
 instantiated \Rclass{oligoSnpSet} will also be \Rpackage{ff}-dervied
 objects (a new \verb+total_cn*.ff+ file will be created in the
 \verb+ldPath()+ directory).
 
16fadf14
 <<oligoSnpSet>>=
 open(cnSet3)
 oligoSet <- as(cnSet3, "oligoSnpSet")
 close(cnSet3)
 class(copyNumber(oligoSet))
 @
 
 \noindent Note that the raw copy number estimates stored in the
 \Robject{oligoSnpSet} object can be retrieved by the
669c6a90
 \Rfunction{copyNumber} accessor and is equivalent to that returned by
16fadf14
 the \Rfunction{totalCopynumber} function defined over the same row and
 column indices.
 
 <<testEqual>>=
7c0c9ac5
 total.cn3 <- totalCopynumber(cnSet3, i=1:nrow(cnSet3), j=seq_len(ncol(cnSet3)))
16fadf14
 all.equal(copyNumber(oligoSet), total.cn3)
7c0c9ac5
 @