Browse code

add packages to the repository

edge/ pwOmics/ EMDomics/



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

Sonali Arora authored on 14/04/2015 17:06:48
Showing 59 changed files

1 1
new file mode 100644
... ...
@@ -0,0 +1,34 @@
1
+Package: edge
2
+Type: Package
3
+Title: Extraction of Differential Gene Expression
4
+Date: 2015-03-26
5
+Version: 0.99.4
6
+Authors@R: c( person("John D.", "Storey", email =
7
+        "jstorey@princeton.edu", role = c("aut", "cre", "cph")),
8
+        person("Jeffrey T.", "Leek", email = "jleek@jhsph.edu ", role =
9
+        c("aut")), person("Andrew J.", "Bass", email =
10
+        "ajbass@princeton.edu", role = c("aut")) )
11
+Maintainer: John D. Storey <jstorey@princeton.edu>
12
+biocViews: MultipleComparison, DifferentialExpression, TimeCourse,
13
+        Regression, GeneExpression, DataImport
14
+Description: The edge package implements methods for carrying out
15
+        differential expression analyses of genome-wide gene expression
16
+        studies. Significance testing using the optimal discovery
17
+        procedure and generalized likelihood ratio tests (equivalent to
18
+        F-tests and t-tests) are implemented for general study designs.
19
+        Special functions are available to facilitate the analysis of
20
+        common study designs, including time course experiments. Other
21
+        packages such as snm, sva, and qvalue are integrated in edge to
22
+        provide a wide range of tools for gene expression analysis.
23
+VignetteBuilder: knitr
24
+Imports: methods, splines, sva, snm, qvalue(>= 1.99.0), MASS
25
+Suggests: testthat, knitr, ggplot2, reshape2
26
+Depends: R(>= 3.2.0), Biobase
27
+URL: https://github.com/jdstorey/edge
28
+BugReports: https://github.com/jdstorey/edge/issues
29
+LazyData: true
30
+License: GPL
31
+Copyright: 2005-2015 John D. Storey
32
+NeedsCompilation: yes
33
+Author: John D. Storey [aut, cre, cph], Jeffrey T. Leek [aut], Andrew
34
+        J. Bass [aut]
0 35
new file mode 100644
... ...
@@ -0,0 +1,43 @@
1
+# Generated by roxygen2 (4.1.0): do not edit by hand
2
+
3
+export("fullMatrix<-")
4
+export("fullModel<-")
5
+export("individual<-")
6
+export("nullMatrix<-")
7
+export("nullModel<-")
8
+export("qvalueObj<-")
9
+export(apply_qvalue)
10
+export(apply_snm)
11
+export(apply_sva)
12
+export(betaCoef)
13
+export(build_models)
14
+export(build_study)
15
+export(deSet)
16
+export(fitFull)
17
+export(fitNull)
18
+export(fullMatrix)
19
+export(fullModel)
20
+export(individual)
21
+export(lrt)
22
+export(nullMatrix)
23
+export(odp)
24
+export(qvalueObj)
25
+export(resFull)
26
+export(resNull)
27
+export(show)
28
+export(summary)
29
+exportClasses(deFit)
30
+exportClasses(deSet)
31
+exportMethods(fit_models)
32
+exportMethods(kl_clust)
33
+exportMethods(nullModel)
34
+exportMethods(sType)
35
+import(Biobase)
36
+import(MASS)
37
+import(methods)
38
+import(qvalue)
39
+import(snm)
40
+import(splines)
41
+import(sva)
42
+useDynLib(edge,kldistance)
43
+useDynLib(edge,odpScoreCluster)
0 44
new file mode 100644
... ...
@@ -0,0 +1,201 @@
1
+# Allows to set qvalue to S4 slot
2
+setOldClass("qvalue")
3
+
4
+deSetCheck <- function(object) {
5
+  errors <- character()
6
+  epsilon <- 10e-8
7
+  # Allow easy conversion for an ExpressionSet using function 'as'
8
+  if (is.list(object@null.model) && is.list(object@full.model) &&
9
+        length(object@individual) == 0) {
10
+    return(TRUE)
11
+  }
12
+  # Name mismatch
13
+  f.vars <- all.vars(object@full.model)
14
+  n.vars <- all.vars(object@null.model)
15
+  names <- unique(c(f.vars, n.vars))
16
+  if (sum((f.vars %in% c("grp", "bio.var", "time.basis"))) == 0) {
17
+    if (sum(!(names %in% varLabels(object))) != 0) {
18
+      msg <- paste("naming mismatch between phenoData covariates and models.")
19
+      errors <- c(errors, msg)
20
+      return(errors)
21
+    }
22
+  }
23
+  # Singular matrix
24
+  xx0 <- model.matrix(object@null.model, data=object)
25
+  xx1 <- model.matrix(object@full.model, data=object)
26
+  #  sCheck.null <- min(svd(xx0)$d) < epsilon
27
+  sCheck.full <- min(svd(xx1)$d) < epsilon
28
+  #  if (sCheck.null) {
29
+  #   msg <- paste("null model matrix is near singular.")
30
+  #   errors <- c(errors, msg)
31
+  #  }
32
+  if (sCheck.full) {
33
+    msg <- paste("full model matrix is near singular.")
34
+    errors <- c(errors, msg)
35
+  }
36
+  # Dimensionality test- this may be impossible to make in deSet
37
+  dataDim <- dim(exprs(object))
38
+  if (dataDim[2] != nrow(xx1)) {
39
+    msg <- paste( "dimension mismatch between full model and assayData.")
40
+    errors <- c(errors, msg)
41
+  }
42
+  if (dataDim[2] != nrow(xx0)) {
43
+    msg <- paste( "dimension mismatch between null model and assayData.")
44
+    errors <- c(errors, msg)
45
+  }
46
+  # inidividual input size
47
+  if (length(object@individual) != 0) {
48
+    if (length(object@individual) != ncol(exprs(object))) {
49
+      msg <- paste("individual must be the same length as the number of arrays")
50
+      errors <- c(errors, msg)
51
+    }
52
+  }
53
+  if (length(errors) == 0) {
54
+    TRUE
55
+  } else {
56
+    errors
57
+  }
58
+}
59
+
60
+deFitCheck <- function(object) {
61
+  errors <- character()
62
+  # Dimensionality test
63
+  if (!(    (ncol(object@fit.full)==ncol(object@fit.null)
64
+             && (ncol(object@res.full) == ncol(object@res.null))
65
+             && (length(object@dH.full) == ncol(object@fit.full))
66
+             && (ncol(object@fit.full) == ncol(object@res.null))))) {
67
+    msg <- paste("column length of fitted matrices, dH.full and residuals",
68
+                 "must be the same.")
69
+    errors <- c(errors, msg)
70
+  }
71
+  if (!((nrow(object@fit.full) == nrow(object@fit.null))
72
+        && (nrow(object@res.full) == nrow(object@res.null))
73
+        && (nrow(object@res.full) == nrow(object@fit.full))
74
+        && (nrow(object@beta.coef) == nrow(object@fit.null)))) {
75
+    msg <- paste("row length of fitted matrices and residuals",
76
+                 "must be the same.")
77
+    errors <- c(errors, msg)
78
+  }
79
+  # Correct statistic input check
80
+  if (!(object@stat.type %in% c("lrt", "odp"))) {
81
+    msg <- paste("stat.type must be lrt or odp. Inputted stat.type: ",
82
+                 object@stat.type)
83
+    errors <- c(errors, msg)
84
+  }
85
+  if (length(errors) == 0) {
86
+    TRUE
87
+  } else {
88
+    errors
89
+  }
90
+}
91
+
92
+#' The differential expression class (deSet)
93
+#'
94
+#' The \code{deSet} class is designed in order to complement the
95
+#' \code{\link{ExpressionSet}} class. While the \code{ExpressionSet} class
96
+#' contains information about the experiment, the \code{deSet} class
97
+#' contains both experimental information and additional information relevant
98
+#' for differential expression analysis.
99
+#'
100
+#' @slot null.model \code{formula}: contains the adjustment variables in the
101
+#' experiment. The null model is used for comparison when fitting the
102
+#' full model.
103
+#' @slot full.model \code{formula}: contains the adjustment variables and the
104
+#' biological variables of interest.
105
+#' @slot null.matrix \code{matrix}: the null model as a matrix.
106
+#' @slot full.matrix \code{matrix}: the full model as a matrix.
107
+#' @slot individual \code{factor}: contains information on which sample
108
+#' is from which individual in the experiment.
109
+#' @slot qvalueObj \code{S3 object}: containing \code{qvalue} object.
110
+#' See \code{\link{qvalue}} for additional details.
111
+#'
112
+#' @section Methods:
113
+#'  \describe{
114
+#'  \item{\code{as(ExpressionSet, "deSet")}}{Coerce objects of
115
+#'  \code{ExpressionSet} to \code{deSet}.}
116
+#'  \item{\code{lrt(deSet, ...)}}{Performs a generalized likelihood ratio test
117
+#'  using the full and null models.}
118
+#'  \item{\code{odp(deSet, ...)}}{Performs the optimal discovery procedure,
119
+#'  which is a new approach for optimally performing many hypothesis tests in
120
+#'  a high-dimensional study.}
121
+#'  \item{\code{kl_clust(deSet, ...)}}{An implementation of mODP that assigns
122
+#'  genes to modules based off of the Kullback-Leibler distance.}
123
+#'  \item{\code{fit_models(deSet, ...)}}{Fits a linear model to each gene by
124
+#'  method of least squares.}
125
+#'  \item{\code{apply_qvalue(deSet, ...)}}{Applies \code{\link{qvalue}}
126
+#'  function.}
127
+#'  \item{\code{apply_snm(deSet, ...)}}{Applies surpervised normalization of
128
+#'   microarrays (\code{\link{snm}}) on gene expression data.}
129
+#'  \item{\code{apply_sva(deSet, ...)}}{Applies surrogate variable analysis
130
+#'  (\code{\link{sva}}).}
131
+#'  \item{\code{fullMatrix(deSet)}}{Access and set full matrix.}
132
+#'  \item{\code{nullMatrix(deSet)}}{Access and set null matrix.}
133
+#'  \item{\code{fullModel(deSet)}}{Access and set full model.}
134
+#'  \item{\code{nullModel(deSet)}}{Access and set null model.}
135
+#'  \item{\code{individual(deSet)}}{Access and set individual slot.}
136
+#'  \item{\code{qvalueObj(deSet)}}{Access \code{qvalue} object.
137
+#'  See \code{\link{qvalue}}.}
138
+#'  \item{\code{validObject(deSet)}}{Check validity of \code{deSet} object.}
139
+#'  }
140
+#'
141
+#' @note
142
+#' See \code{\link{ExpressionSet}} for additional slot information.
143
+#'
144
+#' @author
145
+#' John Storey, Jeffrey Leek, Andrew Bass
146
+#' @inheritParams ExpressionSet
147
+#' @exportClass deSet
148
+setClass("deSet", slots=c(null.model = "formula",
149
+                          full.model = "formula",
150
+                          null.matrix = "matrix",
151
+                          full.matrix = "matrix",
152
+                          individual = "factor",
153
+                          qvalueObj = "qvalue"),
154
+         prototype=prototype(null.model = formula(NULL),
155
+                             full.model = formula(NULL),
156
+                             null.matrix = matrix(),
157
+                             full.matrix = matrix(),
158
+                             individual = as.factor(NULL),
159
+                             qvalueObj = structure(list(),
160
+                                                    class = "qvalue")),
161
+         validity = deSetCheck,
162
+         contains = c("ExpressionSet"))
163
+
164
+#' The differential expression class for the model fits
165
+#'
166
+#' Object returned from \code{\link{fit_models}} containing information
167
+#' regarding the model fits for the experiment.
168
+#'
169
+#' @slot fit.full \code{matrix}: containing fitted values for the full model.
170
+#' @slot fit.null \code{matrix}: containing fitted values for the null model.
171
+#' @slot res.full \code{matrix}: the residuals of the full model.
172
+#' @slot res.null \code{matrix}: the residuals of the null model.
173
+#' @slot dH.full \code{vector}: contains diagonal elements in the projection
174
+#' matrix for the full model.
175
+#' @slot beta.coef \code{matrix}: fitted coefficients for the full model.
176
+#' @slot stat.type \code{string}: information on the statistic of interest.
177
+#' Currently, the only options are ``lrt'' and ``odp''.
178
+#'
179
+#' @section Methods:
180
+#'  \describe{
181
+#'  \item{\code{fitNull(deFit)}}{Access fitted data from null model.}
182
+#'  \item{\code{fitFull(deFit)}}{Access fitted data from full model.}
183
+#'  \item{\code{resNull(deFit)}}{Access residuals from null model fit.}
184
+#'  \item{\code{resFull(deFit)}}{Access residuals from full model fit.}
185
+#'  \item{\code{betaCoef(deFit)}}{Access beta coefficients in linear model.}
186
+#'  \item{\code{sType(deFit)}}{Access statistic type of model fitting utilized
187
+#'  in function.}
188
+#'  }
189
+#'
190
+#' @author
191
+#' John Storey, Jeffrey Leek, Andrew Bass
192
+#'
193
+#' @exportClass deFit
194
+setClass("deFit", slots=c(fit.full = "matrix",
195
+                          fit.null = "matrix",
196
+                          res.full = "matrix",
197
+                          res.null = "matrix",
198
+                          dH.full = "vector",
199
+                          beta.coef = "matrix",
200
+                          stat.type = "character"),
201
+         validity = deFitCheck)
0 202
new file mode 100644
... ...
@@ -0,0 +1,1116 @@
1
+#' Performs F-test (likelihood ratio test using Normal likelihood)
2
+#'
3
+#' \code{lrt} performs a generalized likelihood ratio test using the full and
4
+#' null models.
5
+#'
6
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}.
7
+#' @param de.fit \code{S4 object}: \code{\linkS4class{deFit}}. Optional.
8
+#' @param nullDistn \code{character}: either "normal" or "bootstrap", If
9
+#' "normal" then the p-values are calculated using the F distribution. If
10
+#' "bootstrap" then a bootstrap algorithm is implemented to simulate
11
+#' statistics from the null distribution. In the "bootstrap" case, empirical
12
+#' p-values are calculated using the observed and null statistics (see
13
+#' \code{\link{empPvals}}). Default is "normal".
14
+#' @param bs.its \code{integer}: number of null statistics generated (only
15
+#' applicable for "bootstrap" method). Default is 100.
16
+#' @param seed \code{integer}: set the seed value. Default is NULL.
17
+#' @param verbose \code{boolean}: print iterations for bootstrap method.
18
+#' Default is TRUE.
19
+#' @param ... Additional arguments for \code{\link{apply_qvalue}} and
20
+#' \code{\link{empPvals}} function.
21
+#'
22
+#' @details
23
+#' \code{lrt} fits the full and null models to each gene using the function
24
+#' \code{\link{fit_models}} and then performs a likelihood ratio test. The
25
+#' user has the option to calculate p-values from either the F distribution or
26
+#' through a bootstrap algorithm. If \code{nullDistn} is "bootstrap"
27
+#' then empirical p-values will be determined from the \code{\link{qvalue}}
28
+#' package (see \code{\link{empPvals}}).
29
+#'
30
+#' @author John Storey, Andrew Bass
31
+#'
32
+#' @return \code{\linkS4class{deSet}} object
33
+#'
34
+#' @examples
35
+#' # import data
36
+#' library(splines)
37
+#' data(kidney)
38
+#' age <- kidney$age
39
+#' sex <- kidney$sex
40
+#' kidexpr <- kidney$kidexpr
41
+#' cov <- data.frame(sex = sex, age = age)
42
+#'
43
+#' # create models
44
+#' null_model <- ~sex
45
+#' full_model <- ~sex + ns(age, df = 4)
46
+#'
47
+#' # create deSet object from data
48
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
49
+#' full.model = full_model)
50
+#'
51
+#' # lrt method
52
+#' de_lrt <- lrt(de_obj, nullDistn = "normal")
53
+#'
54
+#' # to generate p-values from bootstrap
55
+#' de_lrt <- lrt(de_obj, nullDistn = "bootstrap", bs.its = 30)
56
+#'
57
+#' # input a deFit object directly
58
+#' de_fit <- fit_models(de_obj, stat.type = "lrt")
59
+#' de_lrt <- lrt(de_obj, de.fit = de_fit)
60
+#'
61
+#' # summarize object
62
+#' summary(de_lrt)
63
+#'
64
+#' @references
65
+#' Storey JD, Xiao W, Leek JT, Tompkins RG, and Davis RW. (2005) Significance
66
+#' analysis of time course microarray experiments. Proceedings of the National
67
+#' Academy of Sciences, 102: 12837-12842.
68
+#'
69
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{build_models}},
70
+#' \code{\link{odp}}
71
+#'
72
+#' @export
73
+setGeneric("lrt", function(object, de.fit,
74
+                           nullDistn = c("normal","bootstrap"), bs.its = 100,
75
+                           seed = NULL, verbose = TRUE, ...)
76
+  standardGeneric("lrt"))
77
+
78
+
79
+#' The optimal discovery procedure
80
+#'
81
+#' \code{odp} performs the optimal discovery procedure, which is a new
82
+#' approach for optimally performing many hypothesis tests in a
83
+#' high-dimensional study. When testing whether a feature is significant, the
84
+#' optimal discovery procedure uses information across all features when
85
+#' testing for significance.
86
+#'
87
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
88
+#' @param de.fit \code{S4 object}: \code{\linkS4class{deFit}}. Optional.
89
+#' @param odp.parms \code{list}: parameters for each cluster. See
90
+#' \code{\link{kl_clust}}.
91
+#' @param bs.its \code{numeric}: number of null bootstrap iterations. Default
92
+#' is 100.
93
+#' @param n.mods \code{integer}: number of clusters used in
94
+#' \code{\link{kl_clust}}. Default is 50.
95
+#' @param seed \code{integer}: set the seed value. Default is NULL.
96
+#' @param verbose \code{boolean}: print iterations for bootstrap method.
97
+#' Default is TRUE.
98
+#' @param ... Additional arguments for \code{\link{qvalue}} and
99
+#' \code{\link{empPvals}}.
100
+#'
101
+#'
102
+#' @details
103
+#' The full ODP estimator computationally grows quadratically with
104
+#' respect to the number of genes. This becomes computationally infeasible at
105
+#' a certain point. Therefore, an alternative method called mODP is used which
106
+#' has been shown to provide results that are very similar. mODP utilizes a
107
+#' k-means clustering algorithm where genes are assigned to a cluster based on
108
+#' the Kullback-Leiber distance. Each gene is assigned an module-average
109
+#' parameter to calculate the ODP score and it reduces the computations time
110
+#' to linear (See Woo, Leek and Storey 2010). If the number of clusters is equal
111
+#' to the number of genes then the original ODP is implemented. Depending on
112
+#' the number of hypothesis tests, this can take some time.
113
+#'
114
+#' @return \code{\linkS4class{deSet}} object
115
+#'
116
+#' @examples
117
+#' # import data
118
+#' library(splines)
119
+#' data(kidney)
120
+#' age <- kidney$age
121
+#' sex <- kidney$sex
122
+#' kidexpr <- kidney$kidexpr
123
+#' cov <- data.frame(sex = sex, age = age)
124
+#'
125
+#' # create models
126
+#' null_model <- ~sex
127
+#' full_model <- ~sex + ns(age, df = 4)
128
+#'
129
+#' # create deSet object from data
130
+#' de_obj <- build_models(data = kidexpr, cov = cov,
131
+#' null.model = null_model, full.model = full_model)
132
+#'
133
+#' # odp method
134
+#' de_odp <- odp(de_obj, bs.its = 30)
135
+#'
136
+#' # input a deFit object or ODP parameters ... not necessary
137
+#' de_fit <- fit_models(de_obj, stat.type = "odp")
138
+#' de_clust <- kl_clust(de_obj, n.mods = 10)
139
+#' de_odp <- odp(de_obj, de.fit = de_fit, odp.parms = de_clust,
140
+#' bs.its = 30)
141
+#'
142
+#' # summarize object
143
+#' summary(de_odp)
144
+#'
145
+#' @references
146
+#' Storey JD. (2007) The optimal discovery procedure: A new approach to
147
+#' simultaneous significance testing. Journal of the Royal Statistical
148
+#' Society, Series B, 69: 347-368.
149
+#'
150
+#' Storey JD, Dai JY, and Leek JT. (2007) The optimal discovery procedure for
151
+#' large-scale significance testing, with applications to comparative
152
+#' microarray experiments. Biostatistics, 8: 414-432.
153
+#'
154
+#' Woo S, Leek JT, Storey JD (2010) A computationally efficient modular
155
+#' optimal discovery procedure. Bioinformatics, 27(4): 509-515.
156
+#'
157
+#' @author John Storey, Jeffrey Leek, Andrew Bass
158
+#'
159
+#' @seealso \code{\link{kl_clust}}, \code{\link{build_models}} and
160
+#' \code{\linkS4class{deSet}}
161
+#'
162
+#' @export
163
+setGeneric("odp", function(object, de.fit, odp.parms = NULL, bs.its = 100,
164
+                           n.mods = 50, seed = NULL, verbose = TRUE, ...)
165
+  standardGeneric("odp"))
166
+
167
+
168
+#' Modular optimal discovery procedure (mODP)
169
+#'
170
+#' \code{kl_clust} is an implementation of mODP that assigns genes to modules
171
+#' based off of the Kullback-Leibler distance.
172
+#'
173
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}.
174
+#' @param de.fit \code{S4 object}: \code{\linkS4class{deFit}}.
175
+#' @param n.mods \code{integer}: number of clusters.
176
+#'
177
+#' @details mODP utilizes a k-means clustering algorithm where genes are
178
+#' assigned to a cluster based on the Kullback-Leiber distance. Each gene is
179
+#' assigned an module-average parameter to calculate the ODP score (See Woo,
180
+#' Leek and Storey 2010 for more details). The mODP and full ODP produce near
181
+#' exact results but mODP has the advantage of being computationally
182
+#' feasible.
183
+#'
184
+#' @note The results are generally insensitive to the number of modules after a
185
+#' certain threshold of about n.mods>=50. It is recommended that users
186
+#' experiment with the number of clusters. If the number of clusters is equal
187
+#' to the number of genes then the original ODP is implemented. Depending on
188
+#' the number of hypothesis tests, this can take some time.
189
+#'
190
+#' @return
191
+#' A list with the following slots:
192
+#' \itemize{
193
+#'   \item {mu.full: cluster means from full model.}
194
+#'   \item {mu.null: cluster means from null model.}
195
+#'   \item {sig.full: cluster standard deviations from full model.}
196
+#'   \item {sig.null: cluster standard deviations from null model.}
197
+#'   \item {n.per.mod: total members in each cluster.}
198
+#'   \item {clustMembers: cluster membership for each gene.}
199
+#' }
200
+#'
201
+#' @examples
202
+#' # import data
203
+#' library(splines)
204
+#' data(kidney)
205
+#' age <- kidney$age
206
+#' sex <- kidney$sex
207
+#' kidexpr <- kidney$kidexpr
208
+#' cov <- data.frame(sex = sex, age = age)
209
+#'
210
+#' # create models
211
+#' null_model <- ~sex
212
+#' full_model <- ~sex + ns(age, df = 4)
213
+#'
214
+#' # create deSet object from data
215
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
216
+#' full.model = full_model)
217
+#'
218
+#' # mODP method
219
+#' de_clust <- kl_clust(de_obj)
220
+#'
221
+#' # change the number of clusters
222
+#' de_clust <- kl_clust(de_obj, n.mods = 10)
223
+#'
224
+#' # input a deFit object
225
+#' de_fit <- fit_models(de_obj, stat.type = "odp")
226
+#' de_clust <- kl_clust(de_obj, de.fit = de_fit)
227
+#'
228
+#' @references
229
+#' Storey JD. (2007) The optimal discovery procedure: A new approach to
230
+#' simultaneous significance testing. Journal of the Royal Statistical
231
+#' Society, Series B, 69: 347-368.
232
+#'
233
+#' Storey JD, Dai JY, and Leek JT. (2007) The optimal discovery procedure for
234
+#' large-scale significance testing, with applications to comparative
235
+#' microarray experiments. Biostatistics, 8: 414-432.
236
+#'
237
+#' Woo S, Leek JT, Storey JD (2010) A computationally efficient modular optimal
238
+#'  discovery procedure. Bioinformatics, 27(4): 509-515.
239
+#'
240
+#' @author John Storey, Jeffrey Leek
241
+#'
242
+#' @seealso \code{\link{odp}}, \code{\link{lrt}} and
243
+#' \code{\link{fit_models}}
244
+#'
245
+#' @exportMethod kl_clust
246
+setGeneric("kl_clust", function(object, de.fit = NULL, n.mods = 50)
247
+  standardGeneric("kl_clust"))
248
+
249
+#' Linear regression of the null and full models
250
+#'
251
+#' \code{fit_models} fits a linear model to each gene by using the least
252
+#' squares method. Model fits can be either statistic type "odp" (optimal
253
+#' discovery procedure) or "lrt" (likelihood ratio test).
254
+#'
255
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}.
256
+#' @param stat.type \code{character}: type of statistic to be used. Either
257
+#' "lrt" or "odp". Default is "lrt".
258
+#'
259
+#' @details
260
+#' If "odp" method is implemented then the null model is removed from the full
261
+#' model (see Storey 2007).
262
+#'
263
+#' @note \code{fit_models} does not have to be called by the user to use
264
+#' \code{\link{odp}}, \code{\link{lrt}} or \code{\link{kl_clust}} as it is an
265
+#' optional input and is implemented in the methods. The
266
+#' \code{\linkS4class{deFit}} object can be created by the user if a different
267
+#' statistical implementation is required.
268
+#'
269
+#' @return \code{\linkS4class{deFit}} object
270
+#'
271
+#' @examples
272
+#' # import data
273
+#' library(splines)
274
+#' data(kidney)
275
+#' age <- kidney$age
276
+#' sex <- kidney$sex
277
+#' kidexpr <- kidney$kidexpr
278
+#' cov <- data.frame(sex = sex, age = age)
279
+#'
280
+#' # create models
281
+#' null_model <- ~sex
282
+#' full_model <- ~sex + ns(age, df = 4)
283
+#'
284
+#' # create deSet object from data
285
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
286
+#' full.model = full_model)
287
+#'
288
+#' # retrieve statistics from linear regression for each gene
289
+#' fit_lrt <- fit_models(de_obj, stat.type = "lrt") # lrt method
290
+#' fit_odp <- fit_models(de_obj, stat.type = "odp") # odp method
291
+#'
292
+#' # summarize object
293
+#' summary(fit_odp)
294
+#'
295
+#' @references
296
+#' Storey JD. (2007) The optimal discovery procedure: A new approach to
297
+#' simultaneous significance testing. Journal of the Royal Statistical
298
+#' Society, Series B, 69: 347-368.
299
+#'
300
+#' Storey JD, Dai JY, and Leek JT. (2007) The optimal discovery procedure for
301
+#' large-scale significance testing, with applications to comparative
302
+#' microarray experiments. Biostatistics, 8: 414-432.
303
+#'
304
+#' Storey JD, Xiao W, Leek JT, Tompkins RG, and Davis RW. (2005) Significance
305
+#' analysis of time course microarray experiments. Proceedings of the National
306
+#' Academy of Sciences, 102: 12837-12842.
307
+#'
308
+#' @seealso \code{\linkS4class{deFit}}, \code{\link{odp}} and
309
+#' \code{\link{lrt}}
310
+#'
311
+#' @author John Storey
312
+#' @exportMethod fit_models
313
+setGeneric("fit_models",
314
+           function(object, stat.type = c("lrt", "odp")) {
315
+             standardGeneric("fit_models")
316
+           })
317
+
318
+#' Create a deSet object from an ExpressionSet
319
+#'
320
+#' Creates a \code{\linkS4class{deSet}} object that extends the
321
+#' \code{\link{ExpressionSet}} object.
322
+#'
323
+#' @param object \code{S4 object}: \code{\link{ExpressionSet}}
324
+#' @param full.model \code{formula}: full model containing the both the
325
+#' adjustment and the biological variables for the experiment.
326
+#' @param null.model \code{formula}: null model containing the adjustment
327
+#' variables for the experiment.
328
+#' @param individual \code{factor}: information on repeated samples in
329
+#' experiment.
330
+#'
331
+#' @note It is essential that the null and full models have the same variables
332
+#' as the ExpressionSet phenoType column names.
333
+#'
334
+#' @return \code{\linkS4class{deSet}} object
335
+#'
336
+#' @examples
337
+#' # import data
338
+#' library(splines)
339
+#' data(kidney)
340
+#' age <- kidney$age
341
+#' sex <- kidney$sex
342
+#' kidexpr <- kidney$kidexpr
343
+#' cov <- data.frame(sex = sex, age = age)
344
+#' pDat <- as(cov, "AnnotatedDataFrame")
345
+#' exp_set <- ExpressionSet(assayData = kidexpr, phenoData = pDat)
346
+#'
347
+#' # create models
348
+#' null_model <- ~sex
349
+#' full_model <- ~sex + ns(age, df = 4)
350
+#'
351
+#' # create deSet object from data
352
+#' de_obj <- deSet(exp_set, null.model = null_model,
353
+#' full.model = full_model)
354
+#'
355
+#' # optionally add individuals to experiment, in this case there are 36
356
+#' # individuals that were sampled twice
357
+#' indSamples <- as.factor(rep(1:36, each = 2))
358
+#' de_obj <- deSet(exp_set, null.model = null_model,
359
+#' full.model = full_model, ind = indSamples)
360
+#' summary(de_obj)
361
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{odp}} and
362
+#' \code{\link{lrt}}
363
+#'
364
+#' @author John Storey, Andrew Bass
365
+#'
366
+#' @export
367
+setGeneric("deSet", function(object, full.model, null.model,
368
+                             individual=NULL) standardGeneric("deSet"))
369
+
370
+#' Estimate the q-values for a given set of p-values
371
+#'
372
+#' Runs \code{\link{qvalue}} on a \code{\linkS4class{deSet}} object.
373
+#'
374
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
375
+#' @param ... Additional arguments for \code{\link{qvalue}}
376
+#'
377
+#' @return \code{\linkS4class{deSet}} object
378
+#'
379
+#' @examples
380
+#' # import data
381
+#' library(splines)
382
+#' data(kidney)
383
+#' age <- kidney$age
384
+#' sex <- kidney$sex
385
+#' kidexpr <- kidney$kidexpr
386
+#' cov <- data.frame(sex = sex, age = age)
387
+#'
388
+#' # create models
389
+#' null_model <- ~sex
390
+#' full_model <- ~sex + ns(age, df = 4)
391
+#'
392
+#' # create deSet object from data
393
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
394
+#' full.model = full_model)
395
+#'
396
+#' # Run lrt (or odp) and apply_qvalue
397
+#' de_lrt <- lrt(de_obj)
398
+#' de_lrt <- apply_qvalue(de_lrt, fdr.level = 0.05,
399
+#' pi0.method = "bootstrap", adj=1.2)
400
+#' summary(de_lrt)
401
+#'
402
+#' @references
403
+#' Storey JD and Tibshirani R. (2003) Statistical significance for
404
+#' genome-wide studies. Proceedings of the National Academy of Sciences,
405
+#' 100: 9440-9445
406
+#'
407
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{odp}} and
408
+#' \code{\link{lrt}}
409
+#'
410
+#' @author John Storey, Andrew Bass
411
+#'
412
+#' @export
413
+setGeneric("apply_qvalue", function(object, ...)
414
+  standardGeneric("apply_qvalue"))
415
+
416
+#' Estimate surrogate variables
417
+#'
418
+#' Runs \code{\link{sva}} on the null and full models in
419
+#' \code{\linkS4class{deSet}}. See \code{\link{sva}} for additional details.
420
+#'
421
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
422
+#' @param ... Additional arguments for \code{\link{sva}}
423
+#'
424
+#' @return \code{\linkS4class{deSet}} object
425
+#'
426
+#' @examples
427
+#' # import data
428
+#' library(splines)
429
+#' data(kidney)
430
+#' age <- kidney$age
431
+#' sex <- kidney$sex
432
+#' kidexpr <- kidney$kidexpr
433
+#' cov <- data.frame(sex = sex, age = age)
434
+#'
435
+#' # create models
436
+#' null_model <- ~sex
437
+#' full_model <- ~sex + ns(age, df = 4)
438
+#'
439
+#' # create deSet object from data
440
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
441
+#' full.model = full_model)
442
+#'
443
+#' # run surrogate variable analysis
444
+#' de_sva <- apply_sva(de_obj)
445
+#'
446
+#' # run odp/lrt with surrogate variables added
447
+#' de_odp <- odp(de_sva, bs.its = 30)
448
+#' summary(de_odp)
449
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{odp}} and
450
+#' \code{\link{lrt}}
451
+#'
452
+#' @references
453
+#' Leek JT, Storey JD (2007) Capturing Heterogeneity in Gene Expression
454
+#' Studies by Surrogate Variable Analysis. PLoS Genet 3(9): e161.
455
+#' doi:10.1371/journal.pgen.0030161
456
+#'
457
+#' @author John Storey, Jeffrey Leek, Andrew Bass
458
+#' @export
459
+setGeneric("apply_sva", function(object, ...)
460
+  standardGeneric("apply_sva"))
461
+
462
+#' Supervised normalization of data in edge
463
+#'
464
+#' Runs \code{snm} on a deSet object based on the null and full models in
465
+#' \code{\linkS4class{deSet}}. See \code{\link{snm}} for additional details
466
+#' on the algorithm.
467
+#'
468
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
469
+#' @param int.var \code{data frame}: intensity-dependent effects.
470
+#' @param ... Additional arguments for \code{\link{snm}}
471
+#'
472
+#' @return \code{apply_snm} returns an \code{\linkS4class{deSet}} object.
473
+#'
474
+#' @references
475
+#' Mechan BH, Nelson PS, Storey JD. Supervised normalization of microarrays.
476
+#' Bioinformatics 2010;26:1308-15
477
+#'
478
+#' @examples
479
+#' # simulate data
480
+#' library(snm)
481
+#' singleChannel <- sim.singleChannel(12345)
482
+#' data <- singleChannel$raw.data
483
+#'
484
+#' # create deSet object using build_models (can use ExpressionSet see manual)
485
+#' cov <- data.frame(grp = singleChannel$bio.var[,2])
486
+#' full_model <- ~grp
487
+#' null_model <- ~1
488
+#'
489
+#' # create deSet object using build_models
490
+#' de_obj <- build_models(data = data, cov = cov, full.model = full_model,
491
+#' null.model = null_model)
492
+#'
493
+#' # run snm using intensity-dependent adjustment variable
494
+#' de_snm <- apply_snm(de_obj, int.var = singleChannel$int.var,
495
+#' verbose = FALSE, num.iter = 1)
496
+#'
497
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{odp}} and
498
+#' \code{\link{lrt}}
499
+#'
500
+#' @author John Storey, Andrew Bass
501
+#' @export
502
+setGeneric("apply_snm", function(object, int.var, ...)
503
+  standardGeneric("apply_snm"))
504
+
505
+#' Full model equation
506
+#'
507
+#' These generic functions access and set the full model for
508
+#' \code{\linkS4class{deSet}} object.
509
+#'
510
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
511
+#' @param value \code{formula}: The experiment design for the full model.
512
+#'
513
+#' @examples
514
+#' # import data
515
+#' library(splines)
516
+#' data(kidney)
517
+#' age <- kidney$age
518
+#' sex <- kidney$sex
519
+#' kidexpr <- kidney$kidexpr
520
+#' cov <- data.frame(sex = sex, age = age)
521
+#'
522
+#' # create models
523
+#' null_model <- ~sex
524
+#' full_model <- ~sex + ns(age, df = 4)
525
+#'
526
+#' # create deSet object from data
527
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
528
+#' full.model = full_model)
529
+#'
530
+#' # extract out the full model equation
531
+#' mod_full <- fullModel(de_obj)
532
+#'
533
+#' # change the full model in the experiment
534
+#' fullModel(de_obj) <- ~sex + ns(age, df = 2)
535
+#'
536
+#'
537
+#' @return the formula for the full model.
538
+#'
539
+#' @author John Storey, Andrew Bass
540
+#'
541
+#' @seealso \code{\linkS4class{deSet}}
542
+#'
543
+#' @export
544
+setGeneric("fullModel", function(object) standardGeneric("fullModel"))
545
+
546
+#' @rdname fullModel
547
+#' @export
548
+setGeneric("fullModel<-", function(object, value) {
549
+  standardGeneric("fullModel<-")
550
+})
551
+
552
+#' Null model equation from deSet object
553
+#'
554
+#' These generic functions access and set the null model for
555
+#' \code{\linkS4class{deSet}} object.
556
+#'
557
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
558
+#' @param value \code{formula}: The experiment design for the null model.
559
+#'
560
+#' @return \code{nullModel} returns the formula for the null model.
561
+#'
562
+#' @examples
563
+#' # import data
564
+#' library(splines)
565
+#' data(kidney)
566
+#' age <- kidney$age
567
+#' sex <- kidney$sex
568
+#' kidexpr <- kidney$kidexpr
569
+#' cov <- data.frame(sex = sex, age = age)
570
+#'
571
+#' # create models
572
+#' null_model <- ~sex
573
+#' full_model <- ~sex + ns(age, df = 4)
574
+#'
575
+#' # create deSet object from data
576
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
577
+#' full.model = full_model)
578
+#'
579
+#' # extract the null model equation
580
+#' mod_null <- nullModel(de_obj)
581
+#'
582
+#' # change null model in experiment but must update full model
583
+#' nullModel(de_obj) <- ~1
584
+#' fullModel(de_obj) <- ~1 + ns(age, df=4)
585
+#' @author John Storey, Andrew Bass
586
+#'
587
+#' @seealso \code{\linkS4class{deSet}}
588
+#'
589
+#' @keywords nullModel, nullModel<-
590
+#'
591
+#' @exportMethod nullModel
592
+setGeneric("nullModel", function(object) standardGeneric("nullModel"))
593
+
594
+#' @rdname nullModel
595
+#' @export
596
+setGeneric("nullModel<-", function(object, value) {
597
+  standardGeneric("nullModel<-")
598
+})
599
+
600
+#' Matrix representation of null model
601
+#'
602
+#' These generic functions access and set the null matrix for
603
+#' \code{\linkS4class{deSet}} object.
604
+#'
605
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
606
+#' @param value \code{matrix}: null model matrix where columns are covariates
607
+#' and rows are observations
608
+#'
609
+#' @return \code{nullMatrix} returns the value of the null model matrix.
610
+#'
611
+#' @examples
612
+#' # import data
613
+#' library(splines)
614
+#' data(kidney)
615
+#' age <- kidney$age
616
+#' sex <- kidney$sex
617
+#' kidexpr <- kidney$kidexpr
618
+#' cov <- data.frame(sex = sex, age = age)
619
+#'
620
+#' # create models
621
+#' null_model <- ~sex
622
+#' full_model <- ~sex + ns(age, df = 4)
623
+#'
624
+#' # create deSet object from data
625
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
626
+#' full.model = full_model)
627
+#'
628
+#' # extract the null model as a matrix
629
+#' mat_null <- nullMatrix(de_obj)
630
+#'
631
+#' @author John Storey, Andrew Bass
632
+#'
633
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{fullModel}} and
634
+#' \code{\link{fullModel}}
635
+#'
636
+#' @export
637
+setGeneric("nullMatrix", function(object) standardGeneric("nullMatrix"))
638
+
639
+#' @rdname nullMatrix
640
+#' @export
641
+setGeneric("nullMatrix<-", function(object, value) {
642
+  standardGeneric("nullMatrix<-")
643
+})
644
+
645
+#' Matrix representation of full model
646
+#'
647
+#' These generic functions access and set the full matrix for
648
+#' \code{\linkS4class{deSet}} object.
649
+#'
650
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
651
+#' @param value \code{matrix}: full model matrix where the columns are the
652
+#' covariates and rows are observations
653
+#'
654
+#' @return \code{fullMatrix} returns the value of the full model matrix.
655
+#'
656
+#' @examples
657
+#' # import data
658
+#' library(splines)
659
+#' data(kidney)
660
+#' age <- kidney$age
661
+#' sex <- kidney$sex
662
+#' kidexpr <- kidney$kidexpr
663
+#' cov <- data.frame(sex = sex, age = age)
664
+#'
665
+#' # create models
666
+#' null_model <- ~sex
667
+#' full_model <- ~sex + ns(age, df = 4)
668
+#'
669
+#' # create deSet object from data
670
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
671
+#' full.model = full_model)
672
+#'
673
+#' # extract the full model equation as a matrix
674
+#' mat_full <- fullMatrix(de_obj)
675
+#' @author Andrew Bass, John Storey
676
+#'
677
+#' @seealso \code{\linkS4class{deSet}}, \code{\link{fullModel}}
678
+#'
679
+#' @export
680
+setGeneric("fullMatrix", function(object) standardGeneric("fullMatrix"))
681
+
682
+#' @rdname fullMatrix
683
+#' @export
684
+setGeneric("fullMatrix<-", function(object, value) {
685
+  standardGeneric("fullMatrix<-")
686
+})
687
+
688
+
689
+#' Access/set qvalue slot
690
+#'
691
+#' These generic functions access and set the \code{qvalue} object in the
692
+#' \code{\linkS4class{deSet}} object.
693
+#'
694
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
695
+#' @param value S3 \code{object}: \code{\link{qvalue}}
696
+#'
697
+#' @return  \code{qvalueObj} returns a \code{\link{qvalue}} object.
698
+#'
699
+#' @examples
700
+#' # import data
701
+#' library(splines)
702
+#' library(qvalue)
703
+#' data(kidney)
704
+#' age <- kidney$age
705
+#' sex <- kidney$sex
706
+#' kidexpr <- kidney$kidexpr
707
+#' cov <- data.frame(sex = sex, age = age)
708
+#'
709
+#' # create models
710
+#' null_model <- ~sex
711
+#' full_model <- ~sex + ns(age, df = 4)
712
+#'
713
+#' # create deSet object from data
714
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
715
+#' full.model = full_model)
716
+#'
717
+#' # run the odp method
718
+#' de_odp <- odp(de_obj, bs.its = 20)
719
+#'
720
+#' # extract out significance results
721
+#' qval_obj <- qvalueObj(de_odp)
722
+#'
723
+#' # run qvalue and assign it to deSet slot
724
+#' pvals <- qval_obj$pvalues
725
+#' qval_new <- qvalue(pvals, pfdr = TRUE, fdr.level = 0.1)
726
+#' qvalueObj(de_odp) <- qval_new
727
+#'
728
+#' @author John Storey, Andrew Bass
729
+#'
730
+#' @seealso \code{\link{lrt}}, \code{\link{odp}} and
731
+#' \code{\linkS4class{deSet}}
732
+#'
733
+#' @export
734
+setGeneric("qvalueObj", function(object) standardGeneric("qvalueObj"))
735
+
736
+#' @rdname qvalueObj
737
+#' @export
738
+setGeneric("qvalueObj<-", function(object, value) {
739
+  standardGeneric("qvalueObj<-")
740
+})
741
+
742
+#' Individuals sampled in experiment
743
+#'
744
+#' These generic functions access and set the individual slot in
745
+#' \code{\linkS4class{deSet}}.
746
+#'
747
+#' @param object \code{\linkS4class{deSet}}
748
+#' @param value \code{factor}: identifier for each observation. Important
749
+#' if the same individuals are sampled multiple times.
750
+#'
751
+#' @return \code{individual} returns information regarding individuals
752
+#' in the experiment.
753
+#'
754
+#' @examples
755
+#' library(splines)
756
+#' # import data
757
+#' data(endotoxin)
758
+#' ind <- endotoxin$ind
759
+#' time <- endotoxin$t
760
+#' class <- endotoxin$class
761
+#' endoexpr <- endotoxin$endoexpr
762
+#' cov <- data.frame(individual = ind, time = time, class = class)
763
+#'
764
+#' # create ExpressionSet object
765
+#' pDat <- as(cov, "AnnotatedDataFrame")
766
+#' exp_set <- ExpressionSet(assayData = endoexpr, phenoData = pDat)
767
+#'
768
+#' # formulate null and full models in experiement
769
+#' # note: interaction term is a way of taking into account group effects
770
+#' mNull <- ~ns(time, df=4, intercept = FALSE)
771
+#' mFull <- ~ns(time, df=4, intercept = FALSE) +
772
+#' ns(time, df=4, intercept = FALSE):class + class
773
+#'
774
+#' # create deSet object
775
+#' de_obj <- deSet(exp_set, full.model = mFull, null.model = mNull,
776
+#' individual = ind)
777
+#'
778
+#' # extract out the individuals factor
779
+#' ind_exp <- individual(de_obj)
780
+#'
781
+#' @author John Storey, Andrew Bass
782
+#'
783
+#' @seealso \code{\linkS4class{deSet}}
784
+#'
785
+#' @export
786
+setGeneric("individual", function(object) standardGeneric("individual"))
787
+
788
+#' @rdname individual
789
+#' @export
790
+setGeneric("individual<-", function(object, value) {
791
+  standardGeneric("individual<-")
792
+})
793
+
794
+#' Regression coefficients from full model fit
795
+#'
796
+#' Access the full model fitted coefficients of a
797
+#' \code{\linkS4class{deFit}} object.
798
+#'
799
+#' @param object \code{S4 object}: \code{\linkS4class{deFit}}
800
+#'
801
+#' @return \code{betaCoef} returns the regression coefficients.
802
+#'
803
+#' @author John Storey, Andrew Bass
804
+#'
805
+#' @seealso \code{\link{fit_models}}
806
+#'
807
+#' @examples
808
+#' # import data
809
+#' library(splines)
810
+#' data(kidney)
811
+#' age <- kidney$age
812
+#' sex <- kidney$sex
813
+#' kidexpr <- kidney$kidexpr
814
+#' cov <- data.frame(sex = sex, age = age)
815
+#'
816
+#' # create models
817
+#' null_model <- ~sex
818
+#' full_model <- ~sex + ns(age, df = 4)
819
+#'
820
+#' # create deSet object from data
821
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
822
+#' full.model = full_model)
823
+#'
824
+#' # run fit_models to get model fits
825
+#' de_fit <- fit_models(de_obj)
826
+#'
827
+#' # extract beta coefficients
828
+#' beta <- betaCoef(de_fit)
829
+#'
830
+#' @export
831
+setGeneric("betaCoef", function(object) standardGeneric("betaCoef"))
832
+
833
+#' Statistical method used in analysis
834
+#'
835
+#' Access the statistic type in a \code{\linkS4class{deFit}} object. Can
836
+#' either be the optimal discovery procedure (odp) or the likelihood ratio
837
+#' test (lrt).
838
+#'
839
+#' @param object \code{S4 object}: \code{\linkS4class{deFit}}
840
+#'
841
+#' @examples
842
+#' # import data
843
+#' library(splines)
844
+#' data(kidney)
845
+#' age <- kidney$age
846
+#' sex <- kidney$sex
847
+#' kidexpr <- kidney$kidexpr
848
+#' cov <- data.frame(sex = sex, age = age)
849
+#'
850
+#' # create models
851
+#' null_model <- ~sex
852
+#' full_model <- ~sex + ns(age, df = 4)
853
+#'
854
+#' # create deSet object from data
855
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
856
+#' full.model = full_model)
857
+#'
858
+#' # run fit_models to get model fits
859
+#' de_fit <- fit_models(de_obj)
860
+#'
861
+#' # extract the statistic type of model fits
862
+#' stat_type <- sType(de_fit)
863
+#'
864
+#' @return \code{sType} returns the statistic type- either "odp" or "lrt".
865
+#'
866
+#' @author John Storey, Andrew Bass
867
+#'
868
+#' @seealso \code{\link{fit_models}}, \code{\linkS4class{deFit}} and
869
+#' \code{\linkS4class{deSet}}
870
+#'
871
+#' @keywords sType
872
+#'
873
+#' @exportMethod sType
874
+setGeneric("sType", function(object) standardGeneric("sType"))
875
+
876
+#' Fitted data from the full model
877
+#'
878
+#' Access the fitted data from the full model in a
879
+#' \code{\linkS4class{deFit}} object.
880
+#'
881
+#' @param object \code{S4 object}: \code{\linkS4class{deFit}}
882
+#'
883
+#' @usage fitFull(object)
884
+#'
885
+#' @return \code{fitFull} returns a matrix of fitted values from full model.
886
+#'
887
+#' @examples
888
+#' # import data
889
+#' library(splines)
890
+#' data(kidney)
891
+#' age <- kidney$age
892
+#' sex <- kidney$sex
893
+#' kidexpr <- kidney$kidexpr
894
+#' cov <- data.frame(sex = sex, age = age)
895
+#'
896
+#' # create models
897
+#' null_model <- ~sex
898
+#' full_model <- ~sex + ns(age, df = 4)
899
+#'
900
+#' # create deSet object from data
901
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
902
+#' full.model = full_model)
903
+#'
904
+#' # run fit_models to get model fits
905
+#' de_fit <- fit_models(de_obj)
906
+#'
907
+#' # extract fitted values for full model
908
+#' fitted_full <- fitFull(de_fit)
909
+#'
910
+#' @author John Storey, Andrew Bass
911
+#'
912
+#' @seealso \code{\link{fit_models}}
913
+#'
914
+#' @export
915
+setGeneric("fitFull", function(object) standardGeneric("fitFull"))
916
+
917
+#' Fitted data from the null model
918
+#'
919
+#' Access the fitted data from the null model in an
920
+#' \code{\linkS4class{deFit}} object.
921
+#'
922
+#' @param object \code{S4 object}: \code{\linkS4class{deFit}}
923
+#'
924
+#' @usage fitNull(object)
925
+#'
926
+#' @return \code{fitNull} returns a matrix of fitted values from null model.
927
+#'
928
+#' @examples
929
+#' # import data
930
+#' library(splines)
931
+#' data(kidney)
932
+#' age <- kidney$age
933
+#' sex <- kidney$sex
934
+#' kidexpr <- kidney$kidexpr
935
+#' cov <- data.frame(sex = sex, age = age)
936
+#'
937
+#' # create models
938
+#' null_model <- ~sex
939
+#' full_model <- ~sex + ns(age, df = 4)
940
+#'
941
+#' # create deSet object from data
942
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
943
+#' full.model = full_model)
944
+#'
945
+#' # run fit_models to get model fits
946
+#' de_fit <- fit_models(de_obj)
947
+#'
948
+#' # extract fitted values from null model
949
+#' fitted_null <- fitNull(de_fit)
950
+#'
951
+#' @author  John Storey, Andrew Bass
952
+#'
953
+#' @seealso \code{\link{fit_models}}
954
+#'
955
+#' @export
956
+setGeneric("fitNull", function(object) standardGeneric("fitNull"))
957
+
958
+#' Residuals of full model fit
959
+#'
960
+#' Access the fitted full model residuals in an \code{\linkS4class{deFit}}
961
+#' object.
962
+#'
963
+#' @param object \code{S4 object}: \code{\linkS4class{deFit}}
964
+#'
965
+#' @usage resFull(object)
966
+#'
967
+#' @return \code{resFull} returns a matrix of residuals from full model.
968
+#'
969
+#' @examples
970
+#' # import data
971
+#' library(splines)
972
+#' data(kidney)
973
+#' age <- kidney$age
974
+#' sex <- kidney$sex
975
+#' kidexpr <- kidney$kidexpr
976
+#' cov <- data.frame(sex = sex, age = age)
977
+#'
978
+#' # create models
979
+#' null_model <- ~sex
980
+#' full_model <- ~sex + ns(age, df = 4)
981
+#'
982
+#' # create deSet object from data
983
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
984
+#' full.model = full_model)
985
+#'
986
+#' # run fit_models to get model fits
987
+#' de_fit <- fit_models(de_obj)
988
+#'
989
+#' # extract out the full residuals from the model fit
990
+#' res_full <- resFull(de_fit)
991
+#'
992
+#' @author John Storey, Andrew Bass
993
+#'
994
+#' @seealso \code{\link{fit_models}}
995
+#'
996
+#' @export
997
+setGeneric("resFull", function(object) standardGeneric("resFull"))
998
+
999
+#' Residuals of null model fit
1000
+#'
1001
+#' Access the fitted null model residuals in an \code{\linkS4class{deFit}}
1002
+#' object.
1003
+#'
1004
+#' @param object \code{S4 object}: \code{\linkS4class{deFit}}
1005
+#'
1006
+#' @usage resNull(object)
1007
+#'
1008
+#' @return \code{resNull} returns a matrix of residuals from null model.
1009
+#'
1010
+#' @examples
1011
+#' # import data
1012
+#' library(splines)
1013
+#' data(kidney)
1014
+#' age <- kidney$age
1015
+#' sex <- kidney$sex
1016
+#' kidexpr <- kidney$kidexpr
1017
+#' cov <- data.frame(sex = sex, age = age)
1018
+#'
1019
+#' # create models
1020
+#' null_model <- ~sex
1021
+#' full_model <- ~sex + ns(age, df = 4)
1022
+#'
1023
+#' # create deSet object from data
1024
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
1025
+#' full.model = full_model)
1026
+#'
1027
+#' # run fit_models to get model fits
1028
+#' de_fit <- fit_models(de_obj)
1029
+#'
1030
+#' # extract out the null residuals from the model fits
1031
+#' res_null <- resNull(de_fit)
1032
+#' @author John Storey, Andrew Bass
1033
+#'
1034
+#' @seealso  \code{\link{fit_models}}
1035
+#'
1036
+#' @export
1037
+setGeneric("resNull", function(object) standardGeneric("resNull"))
1038
+
1039
+#' Summary of deFit and deSet
1040
+#'
1041
+#' Summary of \code{\linkS4class{deFit}} and \code{\linkS4class{deSet}} objects.
1042
+#'
1043
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
1044
+#' @param \dots additional parameters
1045
+#'
1046
+#' @examples
1047
+#' # import data
1048
+#' library(splines)
1049
+#' data(kidney)
1050
+#' age <- kidney$age
1051
+#' sex <- kidney$sex
1052
+#' kidexpr <- kidney$kidexpr
1053
+#' cov <- data.frame(sex = sex, age = age)
1054
+#'
1055
+#' # create models
1056
+#' null_model <- ~sex
1057
+#' full_model <- ~sex + ns(age, df = 4)
1058
+#'
1059
+#' # create deSet object from data
1060
+#' de_obj <- build_models(data = kidexpr, cov = cov, null.model = null_model,
1061
+#' full.model = full_model)
1062
+#'
1063
+#' # get summary
1064
+#' summary(de_obj)
1065
+#'
1066
+#' # run odp and summarize
1067
+#' de_odp <- odp(de_obj, bs.its= 20)
1068
+#' summary(de_odp)
1069
+#' @author John Storey, Andrew Bass
1070
+#'
1071
+#' @return
1072
+#' Summary of \code{\linkS4class{deSet}} object
1073
+#'
1074
+#' @keywords summary
1075
+#'
1076
+#' @export summary
1077
+setGeneric("summary")
1078
+
1079
+#' Show function for deFit and deSet
1080
+#'
1081
+#' Show function for \code{\linkS4class{deFit}} and \code{\linkS4class{deSet}}
1082
+#' objects.
1083
+#'
1084
+#' @param object \code{S4 object}: \code{\linkS4class{deSet}}
1085
+#' @param \dots additional parameters
1086
+#'
1087
+#' @examples
1088
+#' # import data
1089
+#' library(splines)
1090
+#' data(kidney)
1091
+#' age <- kidney$age
1092
+#' sex <- kidney$sex
1093
+#' kidexpr <- kidney$kidexpr
1094
+#' cov <- data.frame(sex = sex, age = age)
1095
+#'
1096
+#' # create models