%\VignetteIndexEntry{MANOR overview} %\VignetteDepends{GLAD} %\VignetteKeywords{array-CGH, normalization, spatial normalization} %\VignettePackage{MANOR} \documentclass[11pt]{article} \usepackage{amsmath} \usepackage[authoryear,round]{natbib} \usepackage{html, float} \usepackage{Sweave} % not understood by latex2html :( % add the content of Sweave.sty :-/ \usepackage{cite} \usepackage{graphicx} \usepackage{hyperref} \newcommand{\Robject}[1]{{\texttt{#1}}} \newcommand{\Rfunction}[1]{{\texttt{#1}}} \newcommand{\Rpackage}[1]{{\textit{#1}}} \newcommand{\Rclass}[1]{{\textit{#1}}} \newcommand{\Rmethod}[1]{{\textit{#1}}} \newcommand{\Rfunarg}[1]{{\textit{#1}}} \newcommand{\htmldoc}{} % inclus seulement dans la doc HTML \newcommand{\pdfdoc}{} % inclus seulement dans la vignette pdf %\SweaveOpts{echo=FALSE, width=10, height=6, eval=FALSE} \SweaveOpts{echo=FALSE, width=10, height=6, eval=TRUE} % \setlength{\hoffset}{-18pt} % \setlength{\oddsidemargin}{20pt} % Marge gauche sur pages impaires % %\setlength{\evensidemargin}{20pt} % Marge gauche sur pages paires % \setlength{\marginparwidth}{54pt} % Largeur de note dans la marge % \setlength{\textwidth}{16cm} % Largeur de la zone de texte (17cm) % \setlength{\marginparsep}{7pt} % Separation de la marge % \setlength{\topmargin}{-20pt} % Marge en haut % \setlength{\headheight}{13pt} % Haut de page % \setlength{\headsep}{10pt} % Entre le haut de page et le texte % \setlength{\footskip}{2cm} % Bas de page + separation % \setlength{\textheight}{22cm} % Hauteur de la zone de texte (25cm) %\usepackage{fancyvrb} \begin{document} \title{\bf MANOR: Micro-Array NORmalization of array-CGH data} \author{Pierre Neuvial$^{\rm ~1,2,3}$, Philippe Hup\'e$^{\rm ~1,2,3,4}$, Isabel Brito$^{\rm ~1,2,3}$, Emmanuel Barillot$^{\rm ~1,2,3}$} \maketitle \begin{center} 1. Institut Curie, 26 rue d'Ulm, Paris cedex 05, F-75248 France\\ 2. INSERM, U900, Paris, F-75248 France\\ 3. \'Ecole des Mines de Paris, ParisTech, Fontainebleau, F-77300 France\\ 4. UMR 144 CNRS, Paris, F-75248 France\\ {\tt manor@curie.fr} \end{center} \tableofcontents \section{Overview} This document gives an overview of the \Rpackage{MANOR} package, which is devoted to the normalization of Array Comparative Genomic Hybridization (array-CGH) data\citep{solinas97, pinkel98, snijders01, ishkanian04, phupe04}. Normalization is a crucial step of microarray analysis which aims at separating biologically relevant signal from experimental artifacts. Typical input data is a file generated by an image analysis software such as \htmladdnormallink{Genepix}{http://www.moleculardevices.com/Products/Instruments/Microarray-Scanners.html} or SPOT \citep{Jain02}, containing several measurements for each biological variable of interest, i.e. several replicated \emph{spots} for each \emph{clone}; this spot-level data is filtered with various statistical criteria (including a spatial bias detection step which is described in \citep{NeuvialHupeBarillot06}), and aggregated into clean clone-level data. Using the \Rclass{arrayCGH} framework developped in the package \htmladdnormallink{GLAD}{http://bioinfo.curie.fr/projects/glad}, which is available under \htmladdnormallink{Bioconductor}{http://www.bioconductor.org}. We propose the formalism of \Robject{flags} to handle clone and spot filtering: the core of the normalization process consists in applying to an \Rclass{arrayCGH} object a list of flags that successively exclude from the data all irrelevant spots or clones. We also define quality scores (\Robject{qscores}) that quantify the quality of an array after normalization: these scores can be used directly to compare the quality of different arrays after the same normalization process, or to compare the efficiency of different normalization processes on a given array or on a given batch of arrays. This document is organized as follows: after a short description of optional items we add to \Rclass{arrayCGH} objects (section \ref{sec:arrayCGH}, we introduce the classes \Rclass{flag} (section \ref{sec:flag}) and \Rclass{qscore} (section \ref{sec:qscore}) with their attributes and dedicated methods; then we describe two useful graphical representation functions (section \ref{sec:graph}), namely \Rfunction{genome.plot} and \Rfunction{report.plot}; Afterwards we give a short description of the array-CGH datasets we provide (section \ref{sec:data}); finally we illustrate the usage of \Rpackage{MANOR} by a sample R script (section \ref{sec:session}). <>= require(MANOR) @ % \pdfdoc{Due to space limitations, figures are not included in this vignette. A full html version of this document is available on Institut Curie Bioinformatics Group web page:\\ % \htmladdnormallink{http://bioinfo.curie.fr/projects/manor}{http://bioinfo.curie.fr/projects/manor} % } \section{\Rclass{arrayCGH} class} \label{sec:arrayCGH} For the purpose of normalization we have added several optional items to the \Rclass{arrayCGH} objects defined in the R package \Rpackage{GLAD}, including: \begin{description} \item[cloneValues] a data frame with aggregated (clone-level) information, quite similar to \Rclass{profileCGH} objects of \Rpackage{GLAD} \item[id.rep] the name of a variable common to \Robject{cloneValues} and \Robject{arrayValues}, that can be used as an identifier for the replicates. \end{description} \section{\Rclass{flag} class} \label{sec:flag} We view the process of filtering microarray data, and especially array-CGH data, as a succession of steps consisting in \emph{excluding} from the data unreliable spots or clones (according to criteria such as signal to noise ratio or replicate consistency), and \emph{correcting} signal values from various non-biologically relevant sources of variations (such as spotting effects, spatial effects, or intensity effects). We introduce the formalism of \emph{flags} to deal with this filtering issue: in the two following subsections, we describe the attributes and methods devoted to \Rclass{flag} objects. \subsection{Attributes} \label{sec:flag-attributes} A \Rclass{flag} object \Robject{f} is a list whose most important items are a function (\Rfunction{f\$FUN}) which has to be applied to an object of class \Rclass{arrayCGH}, and a character value (\Robject{f\$char}) which identifies flagged spots. Optionally further arguments can be passed to \Rfunction{f\$FUN} via \Robject{f\$args}, and a label can be added via \Robject{f\$label}. The examples of this subsection use the function \Rfunction{to.flag}, which is explained in subsection \ref{sec:flag-methods}. \subsubsection{Exclusion and correction flags} As stated above, we make the distinction between flags that \emph{exclude} spots from further analysis and flags that \emph{correct} signal values: \paragraph*{exclusion flags} If \Robject{f} is an exclusion flag, \Rfunction{f\$FUN} returns a list of spots to exclude and \Robject{f\$char} is a non \Robject{NULL} value that quickly identifies the flag. In the following example, we define \Robject{SNR.flag}, a \Rclass{flag} objects that excludes spots whose signal to noise ratio lower than the threshold \Robject{snr.thr}. <>= SNR.FUN <- function(arrayCGH, var.FG, var.BG, snr.thr) { which(arrayCGH$arrayValues[[var.FG]] < arrayCGH$arrayValues[[var.BG]]*snr.thr) } SNR.char <- "B" SNR.label <- "Low signal to noise ratio" SNR.flag <- to.flag(SNR.FUN, SNR.char, args=alist(var.FG="REF_F_MEAN", var.BG="REF_B_MEAN", snr.thr=3)) @ \paragraph*{correction flags} If \Robject{f} is a correction flag, \Rfunction{f\$FUN} returns an object of type \Rclass{arrayCGH} and \Robject{f\$char} is \Robject{NULL}. In the following example, \Robject{global.spatial.flag} computes a spatial trend on the array, and corrects the signal log-ratios from this spatial trend: <>= global.spatial.FUN <- function(arrayCGH, var) { if (!is.null(arrayCGH$arrayValues$Flag)) arrayCGH$arrayValues$LogRatio[which(arrayCGH$arrayValues$Flag!="")] <- NA ## Trend <- arrayTrend(arrayCGH, var, span=0.03, degree=1, iterations=3, family="symmetric") Trend <- arrayTrend(arrayCGH, var, span=0.03, degree=1, iterations=3) arrayCGH$arrayValues[[var]] <- Trend$arrayValues[[var]]-Trend$arrayValues$Trend arrayCGH } global.spatial.flag <- to.flag(global.spatial.FUN, args=alist(var="LogRatio")) @ \subsubsection{Permanent and temporary flags} We introduce an additional distinction between \emph{permanent} and \emph{temporary} flags in order to deal with the case of spots or clone that are known to be biologically relevant, but that have not to be taken into account for the computation of a scaling normalization coefficient. For example in breast cancer, when the reference DNA comes from a male, we expect a gain of the X chromosome and a loss of the Y chromosome in the tumoral sample, and we do not want log-ratio values for X and Y chromosome to bias the estimation of a scaling normalization coefficient. Any \Rclass{flag} object therefore contains an argument called \Robject{type}, which defaults to \Robject{"perm"} (\emph{permanent}) but can be set to \Robject{"temp"} in the case of a temporary flag. In the following example, \Robject{chromosome.flag} is a \emph{temporary} flag that identifies clones correcponding to X and Y chromosome: <>= chromosome.FUN <- function(arrayCGH, var) { var.rep <- arrayCGH$id.rep w <- which(!is.na(match(as.character(arrayCGH$cloneValues[[var]]), c("X", "Y")))) l <- arrayCGH$cloneValues[w, var.rep] which(!is.na(match(arrayCGH$arrayValues[[var.rep]], as.character(l)))) } chromosome.char <- "X" chromosome.label <- "Sexual chromosome" chromosome.flag <- to.flag(chromosome.FUN, chromosome.char, type="temp.flag", args=alist(var="Chromosome"), label=chromosome.label) @ \subsection{Methods} \label{sec:flag-methods} \subsubsection{to.flag} The function \Rfunction{to.flag} is used of the creation of \Rclass{flag} objects, with the specificities described in subsection \ref{sec:flag-attributes}. <>= args(to.flag) @ \subsubsection{flag.arrayCGH} Function \Rfunction{flag.arrayCGH} simply applies function \Rfunction{flag\$FUN} to a \Rclass{flag} object for filtering, and returns: \begin{itemize} \item a filtered array with field \Robject{arrayCGH\$arrayValues\$Flag} filled with the value of \Robject{flag\$char} for each spot to be excluded from further analysis in the case of an exclusion flag; \item an array with corrected signal value in the case of a correction flag. \end{itemize} <>= args(flag.arrayCGH) @ \subsubsection{flag.summary} Function \Rfunction{flag.summary} computes spot-level information about normalization (including the number of flagged spots and numeric normalization parameters), and displays it in a convenient way. This function can either be applied to an object of type \Rclass{arrayCGH}: <>= args(flag.summary.arrayCGH) @ or to plain spot-level information, by using the default method: <>= args(flag.summary.default) @ \section{\Rclass{qscore} class} \label{sec:qscore} As we point out in the introduction of this document, evaluating the quality of an array-CGH after normalization is of major importance, since it helps answering the following questions: \begin{itemize} \item[-] which is the best normalization process ? \item[-] which array is of best quality ? \item[-] what is the quality of a given array ? \end{itemize} To this purpose we define quality scores (\emph{qscores}), which attributes and methods are explianed in the two following subsections. \subsection{Attributes} \label{sec:qscore-attributes} A \Rclass{qscore} object \Robject{qs} is a list which contains a function (\Rfunction{qs\$FUN}), a name (\Robject{qs\$name}), and optionnally a label (\Robject{qs\$label}) and arguments to be passed to \Rfunction{qs\$FUN} (\Robject{qs\$args}). In the following example, the quality score \Robject{pct.spot.qscore} evaluates the percentage of spots that have passed the filtering steps of normalization; it provides an evaluation of the array quality for a given normalization process. The function \Rfunction{to.qscore} is explained in subsection \ref{sec:qscore-methods}. <>= pct.spot.FUN <- function(arrayCGH, var) { 100*sum(!is.na(arrayCGH$arrayValues[[var]]))/dim(arrayCGH$arrayValues)[1] } pct.spot.name <- "SPOT_PCT" pct.spot.label <- "Proportion of spots after normalization" pct.spot.qscore <- to.qscore(pct.spot.FUN, name=pct.spot.name, args=alist(var="LogRatioNorm"), label=pct.spot.label) @ \subsection{Methods} \label{sec:qscore-methods} \subsubsection{to.qscore} The function \Rfunction{to.qscore} is used of the creation of \Rclass{qscore} objects, with the specificities described in subsection \ref{sec:qscore-attributes}. <>= args(to.qscore) @ \subsubsection{qscore.arrayCGH} Function \Rfunction{qscore.arrayCGH} simply computes and returns the value of \Rclass{qscore} for \Rclass{arrayCGH}: <>= args(qscore.arrayCGH) @ \subsubsection{qscore.summary.arrayCGH} Function \Rfunction{qscore.summary.arrayCGH} computes all quality scores of a list (using function \Rfunction{qscore.arrayCGH}), and displays the results in a convenient way. <>= args(qscore.summary.arrayCGH) @ \section{Data} \label{sec:data} \setkeys{Gin}{width=0.99\linewidth} We provide examples of array-CGH data coming from two different platforms. These data illustrate the need for appropriate within-array normalization methods, and especially the need for methods that handle spatial effects. %These methods are described in detail in \cite{NeuvialHupeBarillot06}. <>= data(spatial) @ For each array we provide raw data (generated by \htmladdnormallink{Genepix}{http://www.axon.com/gn_GenePixSoftware.html} or SPOT \citep{Jain02}), as well as the corresponding \Rclass{arrayCGH} object before and after normalization. These arrays illustrate the main source of non biological variability of these data sets, namely spatial effects. We classify these effects into two non exclusive types: local bias and global gradients. In the case of \emph{local bias}, entire areas of the array show lower or higher signal values than the rest of the array, with no biological explanation (array \Robject{edge}); to our experience, this particular type of artifact roughly affects an array out of two. In the case of \emph{global gradients}, the array shows an obvious signal gradient from one side of the slide to the other (array \Robject{gradient}). \subsection{\Robject{edge}} Bladder cancer tumors were collected at Henri Mondor Hospital (Cr\'eteil, France) \citep{billerey01} and hybridized on arrays CGH composed of 2464 Bacterian Artificial Chromosomes (F. Radvanyi, D. Pinkel et al., unpublished results); each of these BAC is spotted three times on the array, and the three replicates are neighbors on the array. We give the example of an \Robject{arrayCGH} with local spatial effects \htmldoc{(figure \ref{fig:edge})}: high log-ratios cluster in the upper-right corner of the array. \SweaveOpts{width=7,height=8} \begin{figure}[!htp] \centering <>= data(spatial) ## edge: example of array with local spatial effects arrayPlot(edge, "LogRatio", main="Local spatial effects", zlim=c(-1,1), mediancenter=TRUE, bar="h") @ \caption{\emph{array with local spatial effects.}} \label{fig:edge} \end{figure} \subsection{\Robject{gradient}} We give the example of two arrays from a breast cancer data set from Institut Curie (O. Delattre, A. Aurias et al., unpublished results). These arrays consist of 3342 clones, organized as a $4 \times 4$ superblock that is replicated three times%; therefore in this data set replicated spots are not neighbors on the array . This data set is affected by the two types of spatial effects: local bias areas (as for the previous data set), and spatial gradients from one side of the array to the other. The array \Robject{gradient} illustrates this second type of spatial effect. \SweaveOpts{width=7,height=8} \begin{figure}[!htp] \centering <>= data(spatial) arrayPlot(gradient, "LogRatio", main="Spatial gradient" , zlim=c(-2,2), mediancenter=TRUE, bar="h") @ \caption{\emph{Example of array with spatial gradient}.} \label{fig:gradient} \end{figure} \section{Graphical representations} \label{sec:graph} \setkeys{Gin}{width=0.8\linewidth} As for any type of data analysis, appropriate graphical representations are of major importance for data understanding. Array-CGH data are typically ratios or log-ratios, that correspond to locations on the array (spots) and to locations on the genome (clones). Therefore in the case of array-CGH data normalization, two complementary types of representations are necessary: \begin{itemize} \item[-] a dotplot of the array, that takes into account the array design. This is a crucial tool in the case of array-CGH data normalization for two reasons: first it provides an easy way to \emph{identify} spatial artifacts such as row, column, print-tip group effects, as well as spatial bias and spatial gradients on the array; then it performs a post-normalization \emph{control}, to ensure that the normalization procedure reached its goals, i.e. significantly reduced the observed effects. \item[-] a plot of the signal values along the genome, which gives a visual impression of the array quality on the edge of biological relevance; comparing the signal shape before and after normalization provides a qualitative idea of the imrpovement in data quality provided by the normalization method. \end{itemize} The \Rfunction{arrayPlot} method provided by the \Rpackage{GLAD} package and based on \Rfunction{maImage} \citep{dudoit03} addresses the first point; we add two methods to this toolbox: \begin{itemize} \item[-] the \Rfunction{genome.plot} method displays a plot of any signal value (e.g. log-ratios) along the genome; \item[-] the \Rfunction{report.plot} method successively calls \Rfunction{arrayPlot} and \Rfunction{genome.plot} in order to provide a simultaneous vision of the data using the two relevant metrics (array and genome), with approproate color scales. \end{itemize} \SweaveOpts{width=10,height=6} \subsection{genome.plot} This method provides a convenient way to plot a given signal along the genome; the signal values can be colored according to their level (which is the default comportment of the function) or to the level of any other variable, in the following way: \begin{itemize} \item[-] if the variable is numeric (e.g. signal to noise ratio), the function assumes that it is a quantitative variable and adapts a color palette to its values \htmldoc{(figure \ref{fig:genome.plot-quant})} \begin{figure}[!htp] \centering <>= data(spatial) par(mfrow=c(7,5), mar=par("mar")/2) genome.plot(edge.norm, chrLim="LimitChr", cex=1) @ \caption{\emph{Pan-genomic profile of the array. Colors are proportional to log-ratio values.}} \label{fig:genome.plot-quant} \end{figure} \item[-] if the variable is not numeric (e.g. the copy number variation as estimated by \Rpackage{GLAD}, or a character variable making the disitnction between flagged and un-flagged clones), the function counts the number of modalities of the variable and defines an appropriate color scale using the \Rfunction{rainbow} function\htmldoc{ (figure \ref{fig:genome.plot-qual})}. \begin{figure}[!htp] \centering <>= data(spatial) edge.norm$cloneValues$ZoneGNL <- as.factor(edge.norm$cloneValues$ZoneGNL) par(mfrow=c(7,5), mar=par("mar")/2) genome.plot(edge.norm, col.var="ZoneGNL", chrLim="LimitChr", cex=1) @ \caption{\emph{Pan-genomic profile of the array. Colors correspond to the values of the variable ``ZoneGNL''.}} \label{fig:genome.plot-qual} \end{figure} \end{itemize} \SweaveOpts{width=10,height=6} \subsection{report.plot} This method successively calls \Rfunction{arrayPlot} and \Rfunction{genome.plot}; it checks for color scale consistency between plots, and can automatically set the plot layout\htmldoc{ (figure \ref{fig:report.plot})}. \SweaveOpts{width=14,height=6} \begin{figure}[!htp] \centering <>= data(spatial) report.plot(edge.norm, chrLim="LimitChr", zlim=c(-1,1), cex=1) @ \caption{\emph{\Rfunction{report.plot}: array image and pan-genomic profile after normalization.}} \label{fig:report.plot} \end{figure} \section{Sample {\tt MANOR} sessions} \label{sec:session} In this section we illustrate the use of \Rpackage{MANOR} on two CGH arrays. Our examples contain several steps, including data preparation, flag definition, array normalization, quality criteria definition, and quality assessment of the array, and highlights of the normalization process. \subsection{array \Robject{edge}} \subsubsection{Data preparation: \Rfunction{import}} <>= dir.in <- system.file("extdata", package="MANOR") ## import from 'spot' files spot.names <- c("LogRatio", "RefFore", "RefBack", "DapiFore", "DapiBack", "SpotFlag", "ScaledLogRatio") clone.names <- c("PosOrder", "Chromosome") edge <- import(paste(dir.in, "/edge.txt", sep=""), type="spot", spot.names=spot.names, clone.names=clone.names, add.lines=TRUE) @ \subsubsection{Normalization: \Rfunction{norm}} \htmldoc{Figure \ref{fig:edge-norm} shows the results of the normalization process.} <>= data(flags) data(spatial) ## local.spatial.flag$args <- alist(var="ScaledLogRatio", by.var=NULL, nk=5, prop=0.25, thr=0.15, beta=1, family="symmetric") local.spatial.flag$args <- alist(var="ScaledLogRatio", by.var=NULL, nk=5, prop=0.25, thr=0.15, beta=1, family="gaussian") flag.list <- list(spatial=local.spatial.flag, spot=spot.corr.flag, ref.snr=ref.snr.flag, dapi.snr=dapi.snr.flag, rep=rep.flag, unique=unique.flag) edge.norm <- norm(edge, flag.list=flag.list, FUN=median, na.rm=TRUE) edge.norm <- sort(edge.norm, position.var="PosOrder") @ \SweaveOpts{width=14,height=6} \begin{figure}[!htp] \centering <>= report.plot(edge.norm, chrLim="LimitChr", zlim=c(-1,1), cex=1) @ \caption{\emph{array 'edge' after normalization}.} \label{fig:edge-norm} \end{figure} \SweaveOpts{width=10,height=6} \subsubsection{Quality assessment: \Rfunction{qscore.summary.arrayCGH}} <>= ##DNA copy number assessment: GLAD profileCGH <- as.profileCGH(edge.norm$cloneValues) profileCGH <- daglad(profileCGH, smoothfunc="lawsglad", lkern="Exponential", model="Gaussian", qlambda=0.999, bandwidth=10, base=FALSE, round=2, lambdabreak=6, lambdaclusterGen=20, param=c(d=6), alpha=0.001, msize=2, method="centroid", nmin=1, nmax=8, amplicon=1, deletion=-5, deltaN=0.10, forceGL=c(-0.15,0.15), nbsigma=3, MinBkpWeight=0.35, verbose=FALSE) edge.norm$cloneValues <- as.data.frame(profileCGH) edge.norm$cloneValues$ZoneGNL <- as.factor(edge.norm$cloneValues$ZoneGNL) data(qscores) ## list of relevant quality scores qscore.list <- list(smoothness=smoothness.qscore, var.replicate=var.replicate.qscore, dynamics=dynamics.qscore) edge.norm$quality <- qscore.summary.arrayCGH(edge.norm, qscore.list) edge.norm$quality @ \subsubsection{Highlights of the normalization process: \Rfunction{html.report}} Function \Rfunction{html.report} generates an HTML file with key features of the normalization process: array image and genomic profile before and after normalization, spot-level flag report, and value of the quality criteria. <>= html.report(edge.norm, dir.out=".", array.name="an array with local bias", chrLim="LimitChr", light=FALSE, pch=20, zlim=c(-2,2), file.name="edge") @ The results of the previous command can be viewed in the file \htmladdnormallink{edge.html}{edge.html}. \subsection{array \Robject{gradient}} Here we give the example of the normalization of an array with spatial gradient. \subsubsection{Data preparation: \Rfunction{import}} <>= ## import from 'gpr' files spot.names <- c("Clone", "FLAG", "TEST_B_MEAN", "REF_B_MEAN", "TEST_F_MEAN", "REF_F_MEAN", "ChromosomeArm") clone.names <- c("Clone", "Chromosome", "Position", "Validation") ac <- import(paste(dir.in, "/gradient.gpr", sep=""), type="gpr", spot.names=spot.names, clone.names=clone.names, sep="\t", comment.char="@", add.lines=TRUE) ## compute log-ratio ac$arrayValues$F1 <- log(ac$arrayValues[["TEST_F_MEAN"]], 2) ac$arrayValues$F2 <- log(ac$arrayValues[["REF_F_MEAN"]], 2) ac$arrayValues$B1 <- log(ac$arrayValues[["TEST_B_MEAN"]], 2) ac$arrayValues$B2 <- log(ac$arrayValues[["REF_B_MEAN"]], 2) Ratio <- (ac$arrayValues[["TEST_F_MEAN"]]-ac$arrayValues[["TEST_B_MEAN"]])/ (ac$arrayValues[["REF_F_MEAN"]]-ac$arrayValues[["REF_B_MEAN"]]) Ratio[(Ratio<=0)|(abs(Ratio)==Inf)] <- NA ac$arrayValues$LogRatio <- log(Ratio, 2) gradient <- ac @ \subsubsection{Normalization: \Rfunction{norm}} \htmldoc{Figure \ref{fig:gradient-norm} shows the results of the normalization process.} <>= data(spatial) data(flags) flag.list <- list(local.spatial=local.spatial.flag, spot=spot.flag, SNR=SNR.flag, global.spatial=global.spatial.flag, val.mark=val.mark.flag, position=position.flag, unique=unique.flag, amplicon=amplicon.flag, chromosome=chromosome.flag, replicate=replicate.flag) gradient.norm <- norm(gradient, flag.list=flag.list, FUN=median, na.rm=TRUE) gradient.norm <- sort(gradient.norm) @ \begin{figure}[!htp] \centering <>= genome.plot(gradient.norm, chrLim="LimitChr", cex=1) @ \caption{\emph{array \Robject{gradient} after normalization}.} \label{fig:gradient-norm} \end{figure} \subsubsection{Quality assessment: \Rfunction{qscore.summary.arrayCGH}} <>= ##DNA copy number assessment: GLAD profileCGH <- as.profileCGH(gradient.norm$cloneValues) profileCGH <- daglad(profileCGH, smoothfunc="lawsglad", lkern="Exponential", model="Gaussian", qlambda=0.999, bandwidth=10, base=FALSE, round=2, lambdabreak=6, lambdaclusterGen=20, param=c(d=6), alpha=0.001, msize=2, method="centroid", nmin=1, nmax=8, amplicon=1, deletion=-5, deltaN=0.10, forceGL=c(-0.15,0.15), nbsigma=3, MinBkpWeight=0.35, verbose=FALSE) gradient.norm$cloneValues <- as.data.frame(profileCGH) gradient.norm$cloneValues$ZoneGNL <- as.factor(gradient.norm$cloneValues$ZoneGNL) data(qscores) ## list of relevant quality scores qscore.list <- list(smoothness=smoothness.qscore, var.replicate=var.replicate.qscore, dynamics=dynamics.qscore) gradient.norm$quality <- qscore.summary.arrayCGH(gradient.norm, qscore.list) gradient.norm$quality @ \subsubsection{Highlights of the normalization process: \Rfunction{html.report}} Function \Rfunction{html.report} generates an HTML file with key features of the normalization process: array image and genomic profile before and after normalization, spot-level flag report, and value of the quality criteria. <>= html.report(gradient.norm, dir.out=".", array.name="an array with spatial gradient", chrLim="LimitChr", light=FALSE, pch=20, zlim=c(-2,2), file.name="gradient") @ The results of the previous command can be viewed in the file \htmladdnormallink{gradient.html}{gradient.html}. \section{Session information} The version number of R and packages loaded for generating this document are: <>= sessionInfo() @ % A silly work-around for the 'R CMD build' intermittent issue on Windows: % * creating vignettes ...Warning in file(con, "r") : % cannot open file 'D:\biocbld\bbs-2.7-bioc\tmpdir\Rtmp6N8fzb\xshell3bf51a24': Permission denied % Error in file(con, "r") : cannot open the connection % Execution halted <>= Sys.sleep(20) @ \htmldoc{ \section{Supplementary data} \label{sec:suppl-data} The package \Rpackage{MANOR} provides sample gpr and spot files, as examples to the \Rfunction{import} funciton. However, due to space limitations, only the first 100 lines these file are provided in the current distribution of \Rpackage{MANOR}. The full files can be downloaded from here: \begin{itemize} \item 'gpr' file: \htmladdnormallink{gradient.gpr}{gradient.gpr} \item 'spot' file: \htmladdnormallink{edge.txt}{edge.txt} \end{itemize} } \bibliographystyle{plain} \bibliography{MANOR} \end{document}