\name{do.gene.set.analysis}
\alias{do.gene.set.analysis}
%- Also NEED an '\alias' for EACH other topic documented here.
\title{
Implements gene-set analysis methods.
}
\description{
This function implements the gene-set analysis methods. It returns a data-frame
with p-values and q-values for all the methods selected.
}
\usage{
do.gene.set.analysis(EventsBySample,
		     Scores,
		     GeneSizes, 
		     GeneSets, 
		     passenger.rates = t(data.frame(0.55*rep(1.0e-6,25))),
		     Coverage, 
		     ID2name,
		     BH = TRUE,
		     gene.method = TRUE, 
		     perm.null.method = TRUE, 
		     perm.null.het.method = TRUE,
		     pass.null.method = TRUE, 
		     pass.null.het.method = TRUE)
}
%- maybe also 'usage' for other objects documented here.
\arguments{
  \item{EventsBySample}{
  Data frame giving the specific mutations for each gene
  and each tumor sample. See \code{EventsBySampleBrain} for an
  example.
}
  \item{Scores}{
  Data frame of gene scores. The logLRT scores are used for the gene.method
  option. It can be the output of \code{cma.scores}. 
  If the gene.method option is set
  to FALSE, this parameter is not needed.
}
  \item{GeneSizes}{
  Data frame of gene sizes. See \code{GeneSizes08} object for an example.
}
  \item{GeneSets}{
  An object which annotates genes to gene-sets; it can either be a list
  with each component representing a set, or an object of the class
  AnnDbBimap.
}
  \item{passenger.rates}{
  Data frame with 1 row and 25 columns, of passenger mutation rates per
  nucleotide, by type, or "context". Columns denote types and must be
  in the same order as the first 25 columns in the 
  \code{MutationsBrain} objects. 
}
  \item{Coverage}{
  Data frame with coverage information, by gene, phase,
  and type. See \code{CoverageBrain} for an example.
}
  \item{ID2name}{
  Vector mapping the gene identifiers used in the GeneSets object
  to the gene names used in the other objects; if they are the same,
  this parameter is not needed. See \code{ID2name} for an example.
}
  \item{BH}{
  If set to \code{TRUE}, uses the Benjamini-Hochberg method to get q-values;
  if set to \code{FALSE}, uses the Storey method from the 
  \code{qvalue} package.
}
  \item{gene.method}{
  If set to \code{TRUE}, implements gene-oriented method.
}
  \item{perm.null.method}{
  If set to \code{TRUE}, implements patient-oriented method 
  with permutation null and no heterogeneity.
}
  \item{perm.null.het.method}{
  If set to \code{TRUE}, implements patient-oriented method 
  with permutation null and heterogeneity.
}
  \item{pass.null.method}{
  If set to \code{TRUE}, implements patient-oriented method 
  with passenger null and no heterogeneity.
}
  \item{pass.null.het.method}{
  If set to \code{TRUE}, implements patient-oriented method 
  with passenger null and heterogeneity.
}
}
\value{
A data frame, with the rows representing set names and the columns
representing the p-values and q-values corresponding to the different
methods.
}
\references{
Boca SM, Kinzler K, Velculescu VE, Vogelstein B,
Parmigiani G.
Patient-oriented gene-set analysis for cancer mutation data.
\emph{Submitted}, 2010.

Parmigiani G, Lin J, Boca S, Sjoeblom T, Kinzler WK,
Velculescu VE, Vogelstein B. Statistical methods for the analysis of
cancer genome sequencing data. 
\url{http://www.bepress.com/jhubiostat/paper126/}
  
Benjamini Y and Hochberg Y. 
Controlling the false discovery rate: a practical and powerful
approach to multiple testing.
\emph{Journal of the Royal Statistical Society B},
57:289-300, 995.

Storey JD and Tibshirani R.
Statistical significance for genome-wide experimens.
\emph{Proceedings of the National Academy of Sciences.}
DOI: 10.1073/pnas.1530509100

Schaeffer EM, Marchionni L, Huang Z, Simons B, Blackman A, Yu W,
Parmigiani G, Berman DM.
Androgen-induced programs for prostate epithelial growth and invasion
arise in embryogenesis and are reactivated in cancer.
\emph{Oncogene.}
DOI: 10.1038/onc.2008.327

Thomas MA, Taub AE.
Calculating binomial probabilities when the trial probabilities are
unequal.
\emph{Journal of Statistical Computation and Simulation.}
DOI: 10.1080/00949658208810534

Parsons DW, Jones S, Zhang X, Lin JCH, Leary RJ, Angenendt P, Mankoo P,
Carter H, Siu I, et al. 
An Integrated Genomic Analysis of Human Glioblastoma Multiforme. 
\emph{Science.} DOI: 10.1126/science.1164382

Wood LD, Parsons DW, Jones S, Lin J, Sjoeblom, Leary RJ, Shen D,
Boca SM, Barber T, Ptak J, et al. The Genomic Landscapes of Human
Breast and Colorectal Cancer. \emph{Science.} DOI: 10.1126/science.1145720
}
\author{
Simina M. Boca, Giovanni Parmigiani, Luigi Marchionni, Michael A. Newton.
}

\seealso{
\code{CoverageBrain},
\code{EventsBySampleBrain}, \code{GeneSizes08},
\code{MutationsBrain}, \code{ID2name}
}

\examples{
library(KEGG.db)
data(Parsons)
data(ID2name)

resultsBrain <- do.gene.set.analysis(EventsBySample = EventsBySampleBrain,
 GeneSizes = GeneSizes08, GeneSets = KEGGPATHID2EXTID[c("hsa05213",
 "hsa05223", "hsa00250")], Coverage = CoverageBrain, ID2name = ID2name,
 gene.method = FALSE, perm.null.method = TRUE, perm.null.het.method = FALSE,
 pass.null.method = TRUE, pass.null.het.method = FALSE)

resultsBrain
}
% Add one or more standard keywords, see file 'KEYWORDS' in the
% R documentation directory.
\keyword{htest}