Browse code

Modified documentation, more examples and exported getters, added links between SconeExperiment and methods, and apply getters to setValidate

mbcole authored on 14/12/2016 00:54:28
Showing 31 changed files

... ...
@@ -1,5 +1,5 @@
1 1
 Package: scone
2
-Version: 0.99.5
2
+Version: 0.99.6
3 3
 Title: Single Cell Overview of Normalized Expression data
4 4
 Description: SCONE is an R package for comparing and ranking the performance of
5 5
 	different normalization schemes for single-cell RNA-seq and other 
... ...
@@ -4,6 +4,7 @@ export(DESEQ_FN)
4 4
 export(DESEQ_FN_POS)
5 5
 export(FQT_FN)
6 6
 export(FQ_FN)
7
+export(SconeExperiment)
7 8
 export(TMM_FN)
8 9
 export(UQ_FN)
9 10
 export(UQ_FN_POS)
... ...
@@ -16,19 +17,24 @@ export(impute_null)
16 17
 export(lm_adjust)
17 18
 export(make_design)
18 19
 export(metric_sample_filter)
19
-export(sconeExperiment)
20 20
 export(sconeReport)
21 21
 export(scone_easybake)
22 22
 export(score_matrix)
23 23
 export(simple_FNR_params)
24 24
 exportClasses(SconeExperiment)
25
+exportMethods(SconeExperiment)
26
+exportMethods(get_batch)
27
+exportMethods(get_bio)
25 28
 exportMethods(get_design)
29
+exportMethods(get_negconeval)
30
+exportMethods(get_negconruv)
26 31
 exportMethods(get_normalized)
27 32
 exportMethods(get_params)
33
+exportMethods(get_poscon)
34
+exportMethods(get_qc)
28 35
 exportMethods(get_score_ranks)
29 36
 exportMethods(get_scores)
30 37
 exportMethods(scone)
31
-exportMethods(sconeExperiment)
32 38
 exportMethods(select_methods)
33 39
 import(BiocParallel)
34 40
 import(SummarizedExperiment)
... ...
@@ -6,7 +6,7 @@
6 6
 #'   batch information, and biological classes of interest (if available).
7 7
 #'   
8 8
 #' @description The typical way of creating \code{SconeExperiment} objects is 
9
-#'   via a call to the \code{\link{sconeExperiment}} function or to the 
9
+#'   via a call to the \code{\link{SconeExperiment}} function or to the 
10 10
 #'   \code{\link{scone}} function. If the object is a result to a 
11 11
 #'   \code{\link{scone}} call, it will contain the results, e.g., the 
12 12
 #'   performance metrics, scores, and normalization workflow comparisons. (See 
... ...
@@ -66,6 +66,14 @@
66 66
 #' @slot rezero logical. TRUE if \code{\link{scone}} was run with 
67 67
 #'   \code{rezero=TRUE}.
68 68
 #' @slot impute_args list. Arguments passed to all imputation functions.
69
+#' 
70
+#' @seealso \code{\link{get_normalized}}, \code{\link{get_params}},
71
+#' \code{\link{get_batch}}, \code{\link{get_bio}}, \code{\link{get_design}},
72
+#' \code{\link{get_negconeval}}, \code{\link{get_negconruv}},
73
+#' \code{\link{get_poscon}}, \code{\link{get_qc}}, 
74
+#' \code{\link{get_scores}}, and \code{\link{get_score_ranks}} 
75
+#' to access internal fields, \code{\link{select_methods}} for subsetting
76
+#' by method, and \code{\link{scone}} for running scone workflows.
69 77
 #'   
70 78
 setClass(
71 79
   Class = "SconeExperiment",
... ...
@@ -140,38 +148,38 @@ setValidity("SconeExperiment", function(object) {
140 148
 
141 149
   ## check that all QC columns are numeric
142 150
   if(length(object@which_qc) > 0) {
143
-    if(any(lapply(colData(object)[,object@which_qc], class) != "numeric")) {
151
+    if(any(lapply(get_qc(object), class) != "numeric")) {
144 152
       return("Only numeric QC metrics are allowed.")
145 153
     }
146 154
   }
147 155
 
148 156
   ## check that bio is a factor
149 157
   if(length(object@which_bio) > 0) {
150
-    if(!is.factor(colData(object)[,object@which_bio])) {
158
+    if(!is.factor(get_bio(object))) {
151 159
       return("`bio` must be a factor.")
152 160
     }
153 161
   }
154 162
 
155 163
   ## check that batch is a factor
156 164
   if(length(object@which_batch) > 0) {
157
-    if(!is.factor(colData(object)[,object@which_batch])) {
165
+    if(!is.factor(get_batch(object))) {
158 166
       return("`batch` must be a factor.")
159 167
     }
160 168
   }
161 169
 
162 170
   ## check that poscon and negcon are logical
163 171
   if(length(object@which_negconruv) > 0) {
164
-    if(!is.logical(rowData(object)[,object@which_negconruv])) {
172
+    if(!is.logical(get_negconruv(object))) {
165 173
       return("`negconruv` must be a logical vector.")
166 174
     }
167 175
   }
168 176
   if(length(object@which_negconeval) > 0) {
169
-    if(!is.logical(rowData(object)[,object@which_negconeval])) {
177
+    if(!is.logical(get_negconeval(object))) {
170 178
       return("`negconeval` must be a logical vector.")
171 179
     }
172 180
   }
173 181
   if(length(object@which_poscon) > 0) {
174
-    if(!is.logical(rowData(object)[,object@which_poscon])) {
182
+    if(!is.logical(get_poscon(object))) {
175 183
       return("`poscon` must be a logical vector.")
176 184
     }
177 185
   }
... ...
@@ -195,7 +203,7 @@ setValidity("SconeExperiment", function(object) {
195 203
 
196 204
 #' @rdname SconeExperiment-class
197 205
 #'   
198
-#' @description The constructor \code{sconeExperiment} creates an object of the
206
+#' @description The constructor \code{SconeExperiment} creates an object of the
199 207
 #'   class \code{SconeExperiment}.
200 208
 #'   
201 209
 #' @param object Either a matrix or a \code{\link{SummarizedExperiment}} 
... ...
@@ -204,7 +212,7 @@ setValidity("SconeExperiment", function(object) {
204 212
 #' @export
205 213
 #' 
206 214
 #' @examples
207
-#' 
215
+#' set.seed(42)
208 216
 #' nrows <- 200
209 217
 #' ncols <- 6
210 218
 #' counts <- matrix(rpois(nrows * ncols, lambda=10), nrows)
... ...
@@ -213,15 +221,15 @@ setValidity("SconeExperiment", function(object) {
213 221
 #' se <- SummarizedExperiment(assays=SimpleList(counts=counts),
214 222
 #'                           rowData=rowdata, colData=coldata)
215 223
 #' 
216
-#' scone1 <- sconeExperiment(assay(se), bio=coldata$bio, poscon=rowdata$poscon)
224
+#' scone1 <- SconeExperiment(assay(se), bio=coldata$bio, poscon=rowdata$poscon)
217 225
 #' 
218
-#' scone2 <- sconeExperiment(se, which_bio=1L, which_poscon=1L)
226
+#' scone2 <- SconeExperiment(se, which_bio=1L, which_poscon=1L)
219 227
 #' 
220 228
 #' 
221 229
 setGeneric(
222
-  name = "sconeExperiment",
230
+  name = "SconeExperiment",
223 231
   def = function(object, ...) {
224
-    standardGeneric("sconeExperiment")
232
+    standardGeneric("SconeExperiment")
225 233
   }
226 234
 )
227 235
 
... ...
@@ -243,7 +251,7 @@ setGeneric(
243 251
 #' @export
244 252
 #' 
245 253
 setMethod(
246
-  f = "sconeExperiment",
254
+  f = "SconeExperiment",
247 255
   signature = signature("SummarizedExperiment"),
248 256
   definition = function(object, which_qc=integer(), which_bio=integer(),
249 257
                         which_batch=integer(),
... ...
@@ -291,10 +299,10 @@ setMethod(
291 299
 #'   
292 300
 #' @export
293 301
 #' 
294
-#' @return A \code{\link{sconeExperiment}} object.
302
+#' @return A \code{\link{SconeExperiment}} object.
295 303
 #'   
296 304
 setMethod(
297
-  f = "sconeExperiment",
305
+  f = "SconeExperiment",
298 306
   signature = signature("matrix"),
299 307
   definition = function(object, qc, bio, batch,
300 308
                         negcon_ruv=NULL, negcon_eval=negcon_ruv,
... ...
@@ -338,7 +346,7 @@ setMethod(
338 346
     }
339 347
 
340 348
     se <- SummarizedExperiment(object, rowData=rowdata, colData=coldata)
341
-    sconeExperiment(se,  which_qc, which_bio, which_batch,
349
+    SconeExperiment(se,  which_qc, which_bio, which_batch,
342 350
                     which_negconruv, which_negconeval, which_poscon, is_log)
343 351
   }
344 352
 )
... ...
@@ -21,7 +21,7 @@ setGeneric(
21 21
 #' @details If \code{\link{scone}} was run with \code{return_norm="no"}, this 
22 22
 #'   function will compute the normalized matrix on the fly.
23 23
 #'   
24
-#' @param x a \code{\link{sconeExperiment}} object containing the results of 
24
+#' @param x a \code{\link{SconeExperiment}} object containing the results of 
25 25
 #'   \code{\link{scone}}.
26 26
 #' @param method character or numeric. Either a string identifying the 
27 27
 #'   normalization scheme to be retrieved, or a numeric index with the rank of 
... ...
@@ -32,13 +32,14 @@ setGeneric(
32 32
 #' @return A matrix of normalized counts in log-scale.
33 33
 #'   
34 34
 #' @examples
35
+#' set.seed(42)
35 36
 #' mat <- matrix(rpois(500, lambda = 5), ncol=10)
36 37
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
37
-#' obj <- sconeExperiment(mat)
38
-#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
38
+#' obj <- SconeExperiment(mat)
39
+#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
39 40
 #'            evaluate=TRUE, k_ruv=0, k_qc=0, 
40 41
 #'            eval_kclust=2, bpparam = BiocParallel::SerialParam())
41
-#' norm = get_normalized(res,1)
42
+#' top_norm = get_normalized(res,1)
42 43
 #'            
43 44
 #' 
44 45
 setGeneric(
... ...
@@ -53,7 +54,7 @@ setGeneric(
53 54
 #' Given a \code{SconeExperiment} object created by a call to scone, it will
54 55
 #' return the design matrix of the selected method.
55 56
 #'
56
-#' @param x a \code{\link{sconeExperiment}} object containing the results of
57
+#' @param x a \code{\link{SconeExperiment}} object containing the results of
57 58
 #'   \code{\link{scone}}.
58 59
 #' @param method character or numeric. Either a string identifying the
59 60
 #'   normalization scheme to be retrieved, or a numeric index with the rank of
... ...
@@ -63,13 +64,16 @@ setGeneric(
63 64
 #' @return The design matrix.
64 65
 #' 
65 66
 #' @examples
67
+#' set.seed(42)
66 68
 #' mat <- matrix(rpois(500, lambda = 5), ncol=10)
67 69
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
68
-#' obj <- sconeExperiment(mat)
69
-#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
70
+#' obj <- SconeExperiment(mat, bio = factor(rep(c(1,2),each = 5)),
71
+#'            batch = factor(rep(c(1,2),times = 5)))
72
+#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
70 73
 #'            evaluate=TRUE, k_ruv=0, k_qc=0, 
74
+#'            adjust_batch = "yes", adjust_bio = "yes",
71 75
 #'            eval_kclust=2, bpparam = BiocParallel::SerialParam())
72
-#' null_design = get_design(res,1)
76
+#' design_top = get_design(res,1)
73 77
 #' 
74 78
 setGeneric(
75 79
   name = "get_design",
... ...
@@ -95,10 +99,11 @@ setGeneric(
95 99
 #' @return A \code{SconeExperiment} object with selected method data.
96 100
 #'   
97 101
 #' @examples
102
+#' set.seed(42)
98 103
 #' mat <- matrix(rpois(500, lambda = 5), ncol=10)
99 104
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
100
-#' obj <- sconeExperiment(mat)
101
-#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
105
+#' obj <- SconeExperiment(mat)
106
+#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
102 107
 #'            evaluate=TRUE, k_ruv=0, k_qc=0, 
103 108
 #'            eval_kclust=2, bpparam = BiocParallel::SerialParam())
104 109
 #' select_res = select_methods(res,1:2)
... ...
@@ -114,6 +119,18 @@ setGeneric(
114 119
 #' 
115 120
 #' @aliases get_negconeval get_poscon get_negconruv,SconeExperiment-method 
116 121
 #'   get_negconeval,SconeExperiment-method get_poscon,SconeExperiment-method
122
+#' 
123
+#' @examples
124
+#' set.seed(42)
125
+#' mat <- matrix(rpois(500, lambda = 5), ncol=10)
126
+#' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
127
+#' obj <- SconeExperiment(mat,negcon_ruv = 1:50 %in% 1:10,
128
+#'            negcon_eval = 1:50 %in% 11:20,
129
+#'            poscon = 1:50 %in% 21:30)
130
+#' negcon_ruv = get_negconruv(obj)
131
+#' negcon_eval = get_negconeval(obj)
132
+#' poscon = get_poscon(obj)
133
+#'
117 134
 setGeneric(
118 135
   name = "get_negconruv",
119 136
   def = function(x) {
... ...
@@ -139,6 +156,14 @@ setGeneric(
139 156
 
140 157
 #' Get Quality Control Matrix
141 158
 #' 
159
+#' @examples
160
+#' set.seed(42)
161
+#' mat <- matrix(rpois(500, lambda = 5), ncol=10)
162
+#' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
163
+#' obj <- SconeExperiment(mat,
164
+#'          qc = cbind(colSums(mat),colSums(mat > 0)))
165
+#' qc = get_qc(obj)
166
+#'
142 167
 #' @aliases get_qc,SconeExperiment-method
143 168
 setGeneric(
144 169
   name = "get_qc",
... ...
@@ -149,8 +174,18 @@ setGeneric(
149 174
 
150 175
 #' Get Factor of Biological Conditions and Batch
151 176
 #'
152
-#' @aliases get_batch get_bio,SconeExperiment-method
177
+#' @aliases get_bio get_batch get_bio,SconeExperiment-method
153 178
 #'   get_batch,SconeExperiment-method
179
+#'   
180
+#' @examples 
181
+#' set.seed(42)
182
+#' mat <- matrix(rpois(500, lambda = 5), ncol=10)
183
+#' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
184
+#' obj <- SconeExperiment(mat, bio = factor(rep(c(1,2),each = 5)),
185
+#'            batch = factor(rep(c(1,2),times = 5)))
186
+#' bio = get_bio(obj)
187
+#' batch = get_batch(obj)
188
+#' 
154 189
 setGeneric(
155 190
   name = "get_bio",
156 191
   def = function(x) {
... ...
@@ -168,14 +203,15 @@ setGeneric(
168 203
 
169 204
 #' Extract scone scores
170 205
 #' 
171
-#' @aliases get_scores get_score,SconeExperiment-method get_score_ranks 
206
+#' @aliases get_scores get_scores,SconeExperiment-method get_score_ranks 
172 207
 #'   get_score_ranks,SconeExperiment-method
173 208
 #'   
174 209
 #' @examples
210
+#' set.seed(42)
175 211
 #' mat <- matrix(rpois(500, lambda = 5), ncol=10)
176 212
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
177
-#' obj <- sconeExperiment(mat)
178
-#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
213
+#' obj <- SconeExperiment(mat)
214
+#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
179 215
 #'            evaluate=TRUE, k_ruv=0, k_qc=0, 
180 216
 #'            eval_kclust=2, bpparam = BiocParallel::SerialParam())
181 217
 #' scores = get_scores(res)
... ...
@@ -199,11 +235,13 @@ setGeneric(
199 235
 #' Extract scone parameters
200 236
 #' 
201 237
 #' @aliases get_params get_params,SconeExperiment-method
238
+#' 
202 239
 #' @examples
240
+#' set.seed(42)
203 241
 #' mat <- matrix(rpois(500, lambda = 5), ncol=10)
204 242
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
205
-#' obj <- sconeExperiment(mat)
206
-#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
243
+#' obj <- SconeExperiment(mat)
244
+#' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
207 245
 #'            run = FALSE, k_ruv=0, k_qc=0, eval_kclust=2)
208 246
 #' params = get_params(res)
209 247
 #' 
... ...
@@ -7,7 +7,7 @@
7 7
 #'   in static documents, such as vignettes or markdown / knitr documents. See
8 8
 #'   \code{biplot_color} for more details on the internals.
9 9
 #'   
10
-#' @param x a \code{\link{sconeExperiment}} object.
10
+#' @param x a \code{\link{SconeExperiment}} object.
11 11
 #' @param ... passed to \code{\link{biplot_color}}.
12 12
 #'   
13 13
 #' @importFrom miniUI gadgetTitleBar miniContentPanel miniPage gadgetTitleBar
... ...
@@ -16,13 +16,13 @@
16 16
 #'   
17 17
 #' @export
18 18
 #' 
19
-#' @return A \code{\link{sconeExperiment}} object representing 
19
+#' @return A \code{\link{SconeExperiment}} object representing 
20 20
 #'   selected methods.
21 21
 #'   
22 22
 #' @examples
23 23
 #' mat <- matrix(rpois(1000, lambda = 5), ncol=10)
24 24
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
25
-#' obj <- sconeExperiment(mat)
25
+#' obj <- SconeExperiment(mat)
26 26
 #' res <- scone(obj, scaling=list(none=identity,
27 27
 #'    uq=UQ_FN, deseq=DESEQ_FN,  fq=FQT_FN),
28 28
 #' evaluate=TRUE, k_ruv=0, k_qc=0, eval_kclust=2,
... ...
@@ -1,6 +1,6 @@
1 1
 #' @rdname get_params
2 2
 #'   
3
-#' @param x an object of class \code{\link{sconeExperiment}}.
3
+#' @param x an object of class \code{\link{SconeExperiment}}.
4 4
 #'   
5 5
 #' @return A data.frame containing workflow parameters for each scone workflow.
6 6
 #'   
... ...
@@ -15,7 +15,7 @@ setMethod(
15 15
 
16 16
 #' @rdname get_scores
17 17
 #'   
18
-#' @param x an object of class \code{\link{sconeExperiment}}.
18
+#' @param x an object of class \code{\link{SconeExperiment}}.
19 19
 #'   
20 20
 #' @return \code{get_scores} returns a matrix with all (non-missing) scone 
21 21
 #'   scores, ordered by average score rank.
... ...
@@ -46,12 +46,15 @@ setMethod(
46 46
 
47 47
 #' @rdname get_negconruv
48 48
 #'   
49
-#' @param x an object of class \code{\link{sconeExperiment}}.
49
+#' @param x an object of class \code{\link{SconeExperiment}}.
50 50
 #'   
51 51
 #' @return NULL or a logical vector.
52 52
 #'   
53 53
 #' @return For \code{get_negconruv} the returned vector indicates which genes
54 54
 #'   are negative controls to be used for RUV.
55
+#'   
56
+#' @export
57
+#' 
55 58
 setMethod(
56 59
   f = "get_negconruv",
57 60
   signature = signature(x = "SconeExperiment"),
... ...
@@ -68,6 +71,9 @@ setMethod(
68 71
 #'   
69 72
 #' @return For \code{get_negconeval} the returned vector indicates which genes
70 73
 #'   are negative controls to be used for evaluation.
74
+#'
75
+#' @export
76
+#' 
71 77
 setMethod(
72 78
   f = "get_negconeval",
73 79
   signature = signature(x = "SconeExperiment"),
... ...
@@ -84,6 +90,9 @@ setMethod(
84 90
 #'   
85 91
 #' @return For \code{get_poscon} the returned vector indicates which genes are 
86 92
 #'   positive controls to be used for evaluation.
93
+#'
94
+#' @export
95
+#'
87 96
 setMethod(
88 97
   f = "get_poscon",
89 98
   signature = signature(x = "SconeExperiment"),
... ...
@@ -98,9 +107,12 @@ setMethod(
98 107
 
99 108
 #' @rdname get_qc
100 109
 #'   
101
-#' @param x an object of class \code{\link{sconeExperiment}}.
110
+#' @param x an object of class \code{\link{SconeExperiment}}.
102 111
 #'   
103 112
 #' @return NULL or the quality control (QC) metric matrix.
113
+#'
114
+#' @export
115
+#'
104 116
 setMethod(
105 117
   f = "get_qc",
106 118
   signature = signature(x = "SconeExperiment"),
... ...
@@ -116,9 +128,12 @@ setMethod(
116 128
 
117 129
 #' @rdname get_bio
118 130
 #'   
119
-#' @param x an object of class \code{\link{sconeExperiment}}.
131
+#' @param x an object of class \code{\link{SconeExperiment}}.
120 132
 #'   
121 133
 #' @return NULL or a factor containing bio or batch covariate.
134
+#'
135
+#' @export
136
+#'
122 137
 setMethod(
123 138
   f = "get_bio",
124 139
   signature = signature(x = "SconeExperiment"),
... ...
@@ -132,6 +147,9 @@ setMethod(
132 147
 )
133 148
 
134 149
 #' @rdname get_bio
150
+#'
151
+#' @export
152
+#'
135 153
 setMethod(
136 154
   f = "get_batch",
137 155
   signature = signature(x = "SconeExperiment"),
... ...
@@ -38,7 +38,7 @@
38 38
 #' set.seed(101)
39 39
 #' mat <- matrix(rpois(1000, lambda = 5), ncol=10)
40 40
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
41
-#' obj <- sconeExperiment(mat)
41
+#' obj <- SconeExperiment(mat)
42 42
 #' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
43 43
 #'            evaluate=TRUE, k_ruv=0, k_qc=0, eval_kclust=2, 
44 44
 #'            bpparam = BiocParallel::SerialParam())
... ...
@@ -121,7 +121,7 @@
121 121
 #' @examples
122 122
 #' mat <- matrix(rpois(1000, lambda = 5), ncol=10)
123 123
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
124
-#' obj <- sconeExperiment(mat)
124
+#' obj <- SconeExperiment(mat)
125 125
 #' no_results <- scone(obj, scaling=list(none=identity,
126 126
 #'            uq=UQ_FN, deseq=DESEQ_FN),
127 127
 #'            run=FALSE, k_ruv=0, k_qc=0, eval_kclust=2)
... ...
@@ -92,7 +92,7 @@
92 92
 #' set.seed(101)
93 93
 #' mat <- matrix(rpois(1000, lambda = 5), ncol=10)
94 94
 #' colnames(mat) <- paste("X", 1:ncol(mat), sep="")
95
-#' obj <- sconeExperiment(mat)
95
+#' obj <- SconeExperiment(mat)
96 96
 #' res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
97 97
 #'            evaluate=TRUE, k_ruv=0, k_qc=0, eval_kclust=2, 
98 98
 #'            bpparam = BiocParallel::SerialParam())
... ...
@@ -420,7 +420,7 @@ scone_easybake <- function(expr, qc,
420 420
     args_list = c( args_list, list( batch = batch ))
421 421
   }
422 422
   
423
-  my_scone <- do.call(sconeExperiment,args_list)
423
+  my_scone <- do.call(SconeExperiment,args_list)
424 424
   
425 425
   my_scone <- scone(my_scone,
426 426
                     imputation = imputation, impute_args = impute_args,
... ...
@@ -3,20 +3,19 @@
3 3
 \docType{class}
4 4
 \name{SconeExperiment-class}
5 5
 \alias{SconeExperiment}
6
+\alias{SconeExperiment,SummarizedExperiment-method}
7
+\alias{SconeExperiment,matrix-method}
6 8
 \alias{SconeExperiment-class}
7
-\alias{sconeExperiment}
8
-\alias{sconeExperiment,SummarizedExperiment-method}
9
-\alias{sconeExperiment,matrix-method}
10 9
 \title{Class SconeExperiment}
11 10
 \usage{
12
-sconeExperiment(object, ...)
11
+SconeExperiment(object, ...)
13 12
 
14
-\S4method{sconeExperiment}{SummarizedExperiment}(object, which_qc = integer(),
13
+\S4method{SconeExperiment}{SummarizedExperiment}(object, which_qc = integer(),
15 14
   which_bio = integer(), which_batch = integer(),
16 15
   which_negconruv = integer(), which_negconeval = integer(),
17 16
   which_poscon = integer(), is_log = FALSE)
18 17
 
19
-\S4method{sconeExperiment}{matrix}(object, qc, bio, batch, negcon_ruv = NULL,
18
+\S4method{SconeExperiment}{matrix}(object, qc, bio, batch, negcon_ruv = NULL,
20 19
   negcon_eval = negcon_ruv, poscon = NULL, is_log = FALSE)
21 20
 }
22 21
 \arguments{
... ...
@@ -61,7 +60,7 @@ negative controls for evaluation.}
61 60
 controls.}
62 61
 }
63 62
 \value{
64
-A \code{\link{sconeExperiment}} object.
63
+A \code{\link{SconeExperiment}} object.
65 64
 }
66 65
 \description{
67 66
 Objects of this class store, at minimum, a gene expression 
... ...
@@ -70,7 +69,7 @@ Objects of this class store, at minimum, a gene expression
70 69
   batch information, and biological classes of interest (if available).
71 70
 
72 71
 The typical way of creating \code{SconeExperiment} objects is 
73
-  via a call to the \code{\link{sconeExperiment}} function or to the 
72
+  via a call to the \code{\link{SconeExperiment}} function or to the 
74 73
   \code{\link{scone}} function. If the object is a result to a 
75 74
   \code{\link{scone}} call, it will contain the results, e.g., the 
76 75
   performance metrics, scores, and normalization workflow comparisons. (See 
... ...
@@ -79,7 +78,7 @@ The typical way of creating \code{SconeExperiment} objects is
79 78
 This object extends the 
80 79
   \code{\linkS4class{SummarizedExperiment}} class.
81 80
 
82
-The constructor \code{sconeExperiment} creates an object of the
81
+The constructor \code{SconeExperiment} creates an object of the
83 82
   class \code{SconeExperiment}.
84 83
 }
85 84
 \details{
... ...
@@ -146,7 +145,7 @@ run and in which mode ("no", "in_memory", "hdf5").}
146 145
 \item{\code{impute_args}}{list. Arguments passed to all imputation functions.}
147 146
 }}
148 147
 \examples{
149
-
148
+set.seed(42)
150 149
 nrows <- 200
151 150
 ncols <- 6
152 151
 counts <- matrix(rpois(nrows * ncols, lambda=10), nrows)
... ...
@@ -155,10 +154,19 @@ coldata <- data.frame(bio=gl(2, 3))
155 154
 se <- SummarizedExperiment(assays=SimpleList(counts=counts),
156 155
                           rowData=rowdata, colData=coldata)
157 156
 
158
-scone1 <- sconeExperiment(assay(se), bio=coldata$bio, poscon=rowdata$poscon)
157
+scone1 <- SconeExperiment(assay(se), bio=coldata$bio, poscon=rowdata$poscon)
159 158
 
160
-scone2 <- sconeExperiment(se, which_bio=1L, which_poscon=1L)
159
+scone2 <- SconeExperiment(se, which_bio=1L, which_poscon=1L)
161 160
 
162 161
 
163 162
 }
163
+\seealso{
164
+\code{\link{get_normalized}}, \code{\link{get_params}},
165
+\code{\link{get_batch}}, \code{\link{get_bio}}, \code{\link{get_design}},
166
+\code{\link{get_negconeval}}, \code{\link{get_negconruv}},
167
+\code{\link{get_poscon}}, \code{\link{get_qc}}, 
168
+\code{\link{get_scores}}, and \code{\link{get_score_ranks}} 
169
+to access internal fields, \code{\link{select_methods}} for subsetting
170
+by method, and \code{\link{scone}} for running scone workflows.
171
+}
164 172
 
... ...
@@ -7,12 +7,12 @@
7 7
 biplot_interactive(x, ...)
8 8
 }
9 9
 \arguments{
10
-\item{x}{a \code{\link{sconeExperiment}} object.}
10
+\item{x}{a \code{\link{SconeExperiment}} object.}
11 11
 
12 12
 \item{...}{passed to \code{\link{biplot_color}}.}
13 13
 }
14 14
 \value{
15
-A \code{\link{sconeExperiment}} object representing 
15
+A \code{\link{SconeExperiment}} object representing 
16 16
   selected methods.
17 17
 }
18 18
 \description{
... ...
@@ -27,7 +27,7 @@ Since this is based on the shiny gadget feature, it will not work
27 27
 \examples{
28 28
 mat <- matrix(rpois(1000, lambda = 5), ncol=10)
29 29
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
30
-obj <- sconeExperiment(mat)
30
+obj <- SconeExperiment(mat)
31 31
 res <- scone(obj, scaling=list(none=identity,
32 32
    uq=UQ_FN, deseq=DESEQ_FN,  fq=FQT_FN),
33 33
 evaluate=TRUE, k_ruv=0, k_qc=0, eval_kclust=2,
... ...
@@ -17,7 +17,7 @@ get_batch(x)
17 17
 \S4method{get_batch}{SconeExperiment}(x)
18 18
 }
19 19
 \arguments{
20
-\item{x}{an object of class \code{\link{sconeExperiment}}.}
20
+\item{x}{an object of class \code{\link{SconeExperiment}}.}
21 21
 }
22 22
 \value{
23 23
 NULL or a factor containing bio or batch covariate.
... ...
@@ -25,4 +25,14 @@ NULL or a factor containing bio or batch covariate.
25 25
 \description{
26 26
 Get Factor of Biological Conditions and Batch
27 27
 }
28
+\examples{
29
+set.seed(42)
30
+mat <- matrix(rpois(500, lambda = 5), ncol=10)
31
+colnames(mat) <- paste("X", 1:ncol(mat), sep="")
32
+obj <- SconeExperiment(mat, bio = factor(rep(c(1,2),each = 5)),
33
+           batch = factor(rep(c(1,2),times = 5)))
34
+bio = get_bio(obj)
35
+batch = get_batch(obj)
36
+
37
+}
28 38
 
... ...
@@ -14,7 +14,7 @@ get_design(x, method)
14 14
 \S4method{get_design}{SconeExperiment,numeric}(x, method)
15 15
 }
16 16
 \arguments{
17
-\item{x}{a \code{\link{sconeExperiment}} object containing the results of
17
+\item{x}{a \code{\link{SconeExperiment}} object containing the results of
18 18
 \code{\link{scone}}.}
19 19
 
20 20
 \item{method}{character or numeric. Either a string identifying the
... ...
@@ -51,13 +51,16 @@ by the character string. The string must be one of the
51 51
 according to the scone ranking.
52 52
 }}
53 53
 \examples{
54
+set.seed(42)
54 55
 mat <- matrix(rpois(500, lambda = 5), ncol=10)
55 56
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
56
-obj <- sconeExperiment(mat)
57
-res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
57
+obj <- SconeExperiment(mat, bio = factor(rep(c(1,2),each = 5)),
58
+           batch = factor(rep(c(1,2),times = 5)))
59
+res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
58 60
            evaluate=TRUE, k_ruv=0, k_qc=0, 
61
+           adjust_batch = "yes", adjust_bio = "yes",
59 62
            eval_kclust=2, bpparam = BiocParallel::SerialParam())
60
-null_design = get_design(res,1)
63
+design_top = get_design(res,1)
61 64
 
62 65
 }
63 66
 
... ...
@@ -23,7 +23,7 @@ get_poscon(x)
23 23
 \S4method{get_poscon}{SconeExperiment}(x)
24 24
 }
25 25
 \arguments{
26
-\item{x}{an object of class \code{\link{sconeExperiment}}.}
26
+\item{x}{an object of class \code{\link{SconeExperiment}}.}
27 27
 }
28 28
 \value{
29 29
 NULL or a logical vector.
... ...
@@ -40,4 +40,16 @@ For \code{get_poscon} the returned vector indicates which genes are
40 40
 \description{
41 41
 Get Negative and Positive Controls
42 42
 }
43
+\examples{
44
+set.seed(42)
45
+mat <- matrix(rpois(500, lambda = 5), ncol=10)
46
+colnames(mat) <- paste("X", 1:ncol(mat), sep="")
47
+obj <- SconeExperiment(mat,negcon_ruv = 1:50 \%in\% 1:10,
48
+           negcon_eval = 1:50 \%in\% 11:20,
49
+           poscon = 1:50 \%in\% 21:30)
50
+negcon_ruv = get_negconruv(obj)
51
+negcon_eval = get_negconeval(obj)
52
+poscon = get_poscon(obj)
53
+
54
+}
43 55
 
... ...
@@ -14,7 +14,7 @@ get_normalized(x, method, ...)
14 14
 \S4method{get_normalized}{SconeExperiment,numeric}(x, method, log = FALSE)
15 15
 }
16 16
 \arguments{
17
-\item{x}{a \code{\link{sconeExperiment}} object containing the results of 
17
+\item{x}{a \code{\link{SconeExperiment}} object containing the results of 
18 18
 \code{\link{scone}}.}
19 19
 
20 20
 \item{method}{character or numeric. Either a string identifying the 
... ...
@@ -65,13 +65,14 @@ by the character string.The string must be one of the
65 65
 matrix according to the scone ranking.
66 66
 }}
67 67
 \examples{
68
+set.seed(42)
68 69
 mat <- matrix(rpois(500, lambda = 5), ncol=10)
69 70
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
70
-obj <- sconeExperiment(mat)
71
-res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
71
+obj <- SconeExperiment(mat)
72
+res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
72 73
            evaluate=TRUE, k_ruv=0, k_qc=0, 
73 74
            eval_kclust=2, bpparam = BiocParallel::SerialParam())
74
-norm = get_normalized(res,1)
75
+top_norm = get_normalized(res,1)
75 76
            
76 77
 
77 78
 }
... ...
@@ -11,7 +11,7 @@ get_params(x)
11 11
 \S4method{get_params}{SconeExperiment}(x)
12 12
 }
13 13
 \arguments{
14
-\item{x}{an object of class \code{\link{sconeExperiment}}.}
14
+\item{x}{an object of class \code{\link{SconeExperiment}}.}
15 15
 }
16 16
 \value{
17 17
 A data.frame containing workflow parameters for each scone workflow.
... ...
@@ -20,10 +20,11 @@ A data.frame containing workflow parameters for each scone workflow.
20 20
 Extract scone parameters
21 21
 }
22 22
 \examples{
23
+set.seed(42)
23 24
 mat <- matrix(rpois(500, lambda = 5), ncol=10)
24 25
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
25
-obj <- sconeExperiment(mat)
26
-res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
26
+obj <- SconeExperiment(mat)
27
+res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
27 28
            run = FALSE, k_ruv=0, k_qc=0, eval_kclust=2)
28 29
 params = get_params(res)
29 30
 
... ...
@@ -11,7 +11,7 @@ get_qc(x)
11 11
 \S4method{get_qc}{SconeExperiment}(x)
12 12
 }
13 13
 \arguments{
14
-\item{x}{an object of class \code{\link{sconeExperiment}}.}
14
+\item{x}{an object of class \code{\link{SconeExperiment}}.}
15 15
 }
16 16
 \value{
17 17
 NULL or the quality control (QC) metric matrix.
... ...
@@ -19,4 +19,13 @@ NULL or the quality control (QC) metric matrix.
19 19
 \description{
20 20
 Get Quality Control Matrix
21 21
 }
22
+\examples{
23
+set.seed(42)
24
+mat <- matrix(rpois(500, lambda = 5), ncol=10)
25
+colnames(mat) <- paste("X", 1:ncol(mat), sep="")
26
+obj <- SconeExperiment(mat,
27
+         qc = cbind(colSums(mat),colSums(mat > 0)))
28
+qc = get_qc(obj)
29
+
30
+}
22 31
 
... ...
@@ -2,7 +2,6 @@
2 2
 % Please edit documentation in R/AllGenerics.R, R/helper.R
3 3
 \docType{methods}
4 4
 \name{get_scores}
5
-\alias{get_score,SconeExperiment-method}
6 5
 \alias{get_score_ranks}
7 6
 \alias{get_score_ranks,SconeExperiment-method}
8 7
 \alias{get_scores}
... ...
@@ -18,7 +17,7 @@ get_score_ranks(x)
18 17
 \S4method{get_score_ranks}{SconeExperiment}(x)
19 18
 }
20 19
 \arguments{
21
-\item{x}{an object of class \code{\link{sconeExperiment}}.}
20
+\item{x}{an object of class \code{\link{SconeExperiment}}.}
22 21
 }
23 22
 \value{
24 23
 \code{get_scores} returns a matrix with all (non-missing) scone 
... ...
@@ -30,10 +29,11 @@ get_score_ranks(x)
30 29
 Extract scone scores
31 30
 }
32 31
 \examples{
32
+set.seed(42)
33 33
 mat <- matrix(rpois(500, lambda = 5), ncol=10)
34 34
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
35
-obj <- sconeExperiment(mat)
36
-res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
35
+obj <- SconeExperiment(mat)
36
+res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
37 37
            evaluate=TRUE, k_ruv=0, k_qc=0, 
38 38
            eval_kclust=2, bpparam = BiocParallel::SerialParam())
39 39
 scores = get_scores(res)
... ...
@@ -149,7 +149,7 @@ In all cases, the normalized matrices can be retrieved via the
149 149
 \examples{
150 150
 mat <- matrix(rpois(1000, lambda = 5), ncol=10)
151 151
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
152
-obj <- sconeExperiment(mat)
152
+obj <- SconeExperiment(mat)
153 153
 no_results <- scone(obj, scaling=list(none=identity,
154 154
            uq=UQ_FN, deseq=DESEQ_FN),
155 155
            run=FALSE, k_ruv=0, k_qc=0, eval_kclust=2)
... ...
@@ -39,7 +39,7 @@ of a variety of normalization schemes.
39 39
 set.seed(101)
40 40
 mat <- matrix(rpois(1000, lambda = 5), ncol=10)
41 41
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
42
-obj <- sconeExperiment(mat)
42
+obj <- SconeExperiment(mat)
43 43
 res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
44 44
            evaluate=TRUE, k_ruv=0, k_qc=0, eval_kclust=2, 
45 45
            bpparam = BiocParallel::SerialParam())
... ...
@@ -128,7 +128,7 @@ Wrapper for Running Essential SCONE Modules
128 128
 set.seed(101)
129 129
 mat <- matrix(rpois(1000, lambda = 5), ncol=10)
130 130
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
131
-obj <- sconeExperiment(mat)
131
+obj <- SconeExperiment(mat)
132 132
 res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
133 133
            evaluate=TRUE, k_ruv=0, k_qc=0, eval_kclust=2, 
134 134
            bpparam = BiocParallel::SerialParam())
... ...
@@ -52,10 +52,11 @@ string must be a subset of the \code{row.names} of the slot
52 52
 according to the scone ranking.
53 53
 }}
54 54
 \examples{
55
+set.seed(42)
55 56
 mat <- matrix(rpois(500, lambda = 5), ncol=10)
56 57
 colnames(mat) <- paste("X", 1:ncol(mat), sep="")
57
-obj <- sconeExperiment(mat)
58
-res <- scone(obj, scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
58
+obj <- SconeExperiment(mat)
59
+res <- scone(obj, scaling=list(none=identity, uq=UQ_FN),
59 60
            evaluate=TRUE, k_ruv=0, k_qc=0, 
60 61
            eval_kclust=2, bpparam = BiocParallel::SerialParam())
61 62
 select_res = select_methods(res,1:2)
... ...
@@ -11,7 +11,7 @@ test_that("all back-ends work", {
11 11
 
12 12
   negcon_ruv <- c(rep(TRUE, 100), rep(FALSE, NROW(e)-100))
13 13
 
14
-  obj <- sconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
14
+  obj <- SconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
15 15
 
16 16
   # serial
17 17
   res1 <- scone(obj, imputation=list(none=impute_null),
... ...
@@ -10,7 +10,7 @@ test_that("get_normalized works in all three modes", {
10 10
   bio <- gl(2, 5)
11 11
   batch <- as.factor(rep(1:2, 5))
12 12
 
13
-  obj <- sconeExperiment(e, qc=qc_mat,
13
+  obj <- SconeExperiment(e, qc=qc_mat,
14 14
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
15 15
                          bio = as.factor(bio), batch=as.factor(batch))
16 16
 
... ...
@@ -10,7 +10,7 @@ test_that("get_normalized works in all three modes", {
10 10
   bio <- gl(2, 5)
11 11
   batch <- as.factor(rep(1:2, 5))
12 12
 
13
-  obj <- sconeExperiment(e, qc=qc_mat,
13
+  obj <- SconeExperiment(e, qc=qc_mat,
14 14
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
15 15
                          bio = as.factor(bio), batch=as.factor(batch))
16 16
 
... ...
@@ -68,7 +68,7 @@ test_that("get_normalized works in all three modes with nested model", {
68 68
   bio <- gl(2, 5)
69 69
   batch <- as.factor(c(1,2,1,2,1,3,4,3,4,3))
70 70
 
71
-  obj <- sconeExperiment(e, qc=qc_mat,
71
+  obj <- SconeExperiment(e, qc=qc_mat,
72 72
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
73 73
                          bio = as.factor(bio), batch=as.factor(batch))
74 74
 
... ...
@@ -129,7 +129,7 @@ test_that("get_normalized works with rezero", {
129 129
   bio <- gl(2, 5)
130 130
   batch <- as.factor(rep(1:2, 5))
131 131
 
132
-  obj <- sconeExperiment(e, qc=qc_mat,
132
+  obj <- SconeExperiment(e, qc=qc_mat,
133 133
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
134 134
                          bio = as.factor(bio), batch=as.factor(batch))
135 135
 
... ...
@@ -12,7 +12,7 @@ test_that("hd5 checks", {
12 12
   batch <- as.factor(rep(1:2, 5))
13 13
   negcon_ruv <- c(rep(TRUE, 100), rep(FALSE, NROW(e)-100))
14 14
 
15
-  obj <- sconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
15
+  obj <- SconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
16 16
 
17 17
   # factorial
18 18
   expect_error(scone(obj, imputation=list(none=impute_null),
... ...
@@ -38,7 +38,7 @@ test_that("return_norm in memory", {
38 38
 
39 39
   negcon_ruv <- c(rep(TRUE, 100), rep(FALSE, NROW(e)-100))
40 40
 
41
-  obj <- sconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
41
+  obj <- SconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
42 42
 
43 43
   # factorial
44 44
   res <- scone(obj, imputation=list(none=impute_null),
... ...
@@ -59,7 +59,7 @@ test_that("do not return_norm", {
59 59
 
60 60
   negcon_ruv <- c(rep(TRUE, 100), rep(FALSE, NROW(e)-100))
61 61
 
62
-  obj <- sconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
62
+  obj <- SconeExperiment(e, bio=bio, batch=batch, qc=qc_mat, negcon_ruv=negcon_ruv)
63 63
 
64 64
   # factorial
65 65
   res <- scone(obj, imputation=list(none=impute_null),
... ...
@@ -8,7 +8,7 @@ test_that("Upper-quartile normalization works the same as in the EDASeq package"
8 8
   colnames(e) <- paste0("Sample", 1:ncol(e))
9 9
 
10 10
   negcon_ruv <- c(rep(TRUE, 100), rep(FALSE, NROW(e)-100))
11
-  obj <- sconeExperiment(e, negcon_ruv=negcon_ruv)
11
+  obj <- SconeExperiment(e, negcon_ruv=negcon_ruv)
12 12
 
13 13
   # UQ + RUV
14 14
 
... ...
@@ -26,7 +26,7 @@ test_that("Upper-quartile normalization works the same as in the EDASeq package"
26 26
 
27 27
   # UQ + QC
28 28
   qc_mat <- matrix(rnorm(20), nrow=10)
29
-  obj <- sconeExperiment(e, negcon_ruv=negcon_ruv, qc=qc_mat)
29
+  obj <- SconeExperiment(e, negcon_ruv=negcon_ruv, qc=qc_mat)
30 30
 
31 31
   res <- scone(obj, imputation=impute_null, scaling=UQ_FN, k_ruv=0, k_qc=2,
32 32
                evaluate=FALSE, run=TRUE, return_norm = "in_memory")
... ...
@@ -10,10 +10,10 @@ se <- SummarizedExperiment(assays=SimpleList(counts=counts),
10 10
                            rowData=rowdata, colData=coldata)
11 11
 
12 12
 test_that("The two constructors are equivalent", {
13
-  expect_equal(sconeExperiment(assay(se)), sconeExperiment(assay(se)))
13
+  expect_equal(SconeExperiment(assay(se)), SconeExperiment(assay(se)))
14 14
 
15
-  scone1 <- sconeExperiment(assay(se), bio=coldata$bio, poscon=rowdata$poscon)
16
-  scone2 <- sconeExperiment(se, which_bio=1L, which_poscon=1L)
15
+  scone1 <- SconeExperiment(assay(se), bio=coldata$bio, poscon=rowdata$poscon)
16
+  scone2 <- SconeExperiment(se, which_bio=1L, which_poscon=1L)
17 17
 
18 18
   expect_equal(scone1, scone2)
19 19
   }
... ...
@@ -6,7 +6,7 @@ test_that("Test with no real method (only identity)", {
6 6
   e <-  matrix(rpois(10000, lambda = 5), ncol=10)
7 7
   rownames(e) <- as.character(1:nrow(e))
8 8
   colnames(e) <- paste0("Sample", 1:ncol(e))
9
-  obj <- sconeExperiment(e)
9
+  obj <- SconeExperiment(e)
10 10
 
11 11
   # one combination
12 12
   res <- scone(obj, imputation=impute_null, scaling=identity, k_ruv=0, k_qc=0,
... ...
@@ -35,7 +35,7 @@ test_that("Test with no real method (only identity)", {
35 35
                      k_ruv=5, k_qc=0, evaluate=FALSE, run=FALSE),
36 36
                "negative controls must be specified")
37 37
 
38
-  obj <- sconeExperiment(e, negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)))
38
+  obj <- SconeExperiment(e, negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)))
39 39
   obj <- scone(obj, imputation=list(impute_null,impute_null),
40 40
                scaling=list(identity, identity, identity), k_ruv=5,
41 41
                k_qc=0, evaluate=FALSE, run=FALSE)
... ...
@@ -51,7 +51,7 @@ test_that("Test with no real method (only identity)", {
51 51
                "QC metrics must be specified")
52 52
 
53 53
   qc_mat <- matrix(rnorm(20), nrow=10)
54
-  obj <- sconeExperiment(e, qc=qc_mat, negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)))
54
+  obj <- SconeExperiment(e, qc=qc_mat, negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)))
55 55
 
56 56
   res <- scone(obj, imputation=list(impute_null,impute_null),
57 57
                scaling=list(identity, identity, identity), k_ruv=5, k_qc=2,
... ...
@@ -65,7 +65,7 @@ test_that("Test with no real method (only identity)", {
65 65
                      k_qc=2, adjust_bio="yes", evaluate=FALSE, run=FALSE),
66 66
                "if adjust_bio is 'yes' or 'force', 'bio' must be specified")
67 67
 
68
-  obj <- sconeExperiment(e, qc=qc_mat,
68
+  obj <- SconeExperiment(e, qc=qc_mat,
69 69
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
70 70
                          bio = as.factor(bio))
71 71
 
... ...
@@ -85,7 +85,7 @@ test_that("Test with no real method (only identity)", {
85 85
                      evaluate=FALSE, run=FALSE),
86 86
                "if adjust_batch is 'yes' or 'force', 'batch' must be specified")
87 87
 
88
-  obj <- sconeExperiment(e, qc=qc_mat,
88
+  obj <- SconeExperiment(e, qc=qc_mat,
89 89
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
90 90
                          bio = as.factor(bio), batch=as.factor(batch))
91 91
 
... ...
@@ -96,7 +96,7 @@ test_that("Test with no real method (only identity)", {
96 96
                "Biological conditions and batches are confounded")
97 97
 
98 98
   batch <- as.factor(rep(1:2, 5))
99
-  obj <- sconeExperiment(e, qc=qc_mat,
99
+  obj <- SconeExperiment(e, qc=qc_mat,
100 100
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
101 101
                          bio = as.factor(bio), batch=as.factor(batch))
102 102
   res <- scone(obj, imputation=list(a=impute_null, b=impute_null),
... ...
@@ -121,7 +121,7 @@ test_that("Test imputation and scaling", {
121 121
   bio <- gl(2, 5)
122 122
   batch <- as.factor(rep(1:2, 5))
123 123
 
124
-  obj <- sconeExperiment(e, qc=qc_mat,
124
+  obj <- SconeExperiment(e, qc=qc_mat,
125 125
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
126 126
                          bio = as.factor(bio), batch=as.factor(batch))
127 127
 
... ...
@@ -133,7 +133,7 @@ test_that("Test imputation and scaling", {
133 133
 
134 134
   # nested
135 135
   batch <- as.factor(c(1, 2, 1, 2, 1, 3, 4, 3, 4, 3))
136
-  obj <- sconeExperiment(e, qc=qc_mat,
136
+  obj <- SconeExperiment(e, qc=qc_mat,
137 137
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
138 138
                          bio = as.factor(bio), batch=as.factor(batch))
139 139
 
... ...
@@ -153,7 +153,7 @@ test_that("Test imputation and scaling", {
153 153
   ruv_negcon[1:10] <- TRUE
154 154
   eval_negcon[11:20] <- TRUE
155 155
   eval_poscon[21:30] <- TRUE
156
-  obj <- sconeExperiment(e, qc=qc_mat, negcon_ruv=ruv_negcon,
156
+  obj <- SconeExperiment(e, qc=qc_mat, negcon_ruv=ruv_negcon,
157 157
                          negcon_eval=eval_negcon, poscon=eval_poscon,
158 158
                          bio=as.factor(bio), batch=as.factor(batch))
159 159
 
... ...
@@ -184,7 +184,7 @@ test_that("scone works with only one normalization",{
184 184
   e <-  matrix(rpois(1000, lambda = 5), ncol=10)
185 185
   rownames(e) <- as.character(1:nrow(e))
186 186
   colnames(e) <- paste0("Sample", 1:ncol(e))
187
-  obj <- sconeExperiment(e)
187
+  obj <- SconeExperiment(e)
188 188
 
189 189
   res <- scone(obj, imputation=list(none=impute_null),
190 190
                scaling=list(none=identity),
... ...
@@ -206,7 +206,7 @@ test_that("conditional PAM",{
206 206
   eval_negcon[11:20] <- TRUE
207 207
   eval_poscon[21:30] <- TRUE
208 208
 
209
-  obj <- sconeExperiment(e, qc=qc_mat, bio=bio,
209
+  obj <- SconeExperiment(e, qc=qc_mat, bio=bio,
210 210
                          negcon_eval = eval_negcon, poscon=eval_poscon)
211 211
 
212 212
   res <- scone(obj, imputation=list(none=impute_null),
... ...
@@ -214,7 +214,7 @@ test_that("conditional PAM",{
214 214
                k_ruv=0, k_qc=0, adjust_bio="yes", run=FALSE,
215 215
                evaluate=TRUE, eval_kclust = 2, stratified_pam = TRUE)
216 216
 
217
-  obj <- sconeExperiment(e, qc=qc_mat, bio=bio, batch=batch,
217
+  obj <- SconeExperiment(e, qc=qc_mat, bio=bio, batch=batch,
218 218
                          negcon_eval = eval_negcon, poscon=eval_poscon)
219 219
 
220 220
   expect_error(res <- scone(obj, imputation=list(none=impute_null),
... ...
@@ -223,7 +223,7 @@ test_that("conditional PAM",{
223 223
                evaluate=TRUE, eval_kclust = 6, stratified_pam = TRUE),
224 224
                "For stratified_pam, max 'eval_kclust' must be smaller than bio-cross-batch stratum size")
225 225
 
226
-  obj <- sconeExperiment(e, qc=qc_mat, negcon_eval = eval_negcon, poscon=eval_poscon)
226
+  obj <- SconeExperiment(e, qc=qc_mat, negcon_eval = eval_negcon, poscon=eval_poscon)
227 227
 
228 228
   expect_error(res <- scone(obj, imputation=list(none=impute_null),
229 229
                             scaling=list(none=identity, uq=UQ_FN, deseq=DESEQ_FN),
... ...
@@ -240,8 +240,8 @@ test_that("if bio=no bio is ignored", {
240 240
   rownames(e) <- as.character(1:nrow(e))
241 241
   colnames(e) <- paste0("Sample", 1:ncol(e))
242 242
   bio <- gl(2, 5)
243
-  obj1 <- sconeExperiment(e)
244
-  obj2 <- sconeExperiment(e, bio=bio)
243
+  obj1 <- SconeExperiment(e)
244
+  obj2 <- SconeExperiment(e, bio=bio)
245 245
 
246 246
   res1 <- scone(obj1, imputation=impute_null, scaling=identity, k_ruv=0, k_qc=0,
247 247
                adjust_bio = "no",  eval_kclust = 3, return_norm = "in_memory")
... ...
@@ -257,8 +257,8 @@ test_that("if batch=no batch is ignored", {
257 257
   rownames(e) <- as.character(1:nrow(e))
258 258
   colnames(e) <- paste0("Sample", 1:ncol(e))
259 259
   batch <- gl(2, 5)
260
-  obj1 <- sconeExperiment(e)
261
-  obj2 <- sconeExperiment(e, batch=batch)
260
+  obj1 <- SconeExperiment(e)
261
+  obj2 <- SconeExperiment(e, batch=batch)
262 262
 
263 263
   res1 <- scone(obj1, imputation=impute_null, scaling=identity, k_ruv=0, k_qc=0,
264 264
                 adjust_batch = "no", eval_kclust = 3, return_norm = "in_memory")
... ...
@@ -273,7 +273,7 @@ test_that("batch and bio can be confounded if at least one of adjust_bio or adju
273 273
   e <-  matrix(rpois(10000, lambda = 5), ncol=10)
274 274
   rownames(e) <- as.character(1:nrow(e))
275 275
   colnames(e) <- paste0("Sample", 1:ncol(e))
276
-  obj <- sconeExperiment(e, batch=gl(2, 5), bio=gl(2, 5))
276
+  obj <- SconeExperiment(e, batch=gl(2, 5), bio=gl(2, 5))
277 277
 
278 278
   expect_warning(scone(obj, imputation=impute_null, scaling=identity, k_ruv=0, k_qc=0,
279 279
                 adjust_batch = "yes", eval_kclust = 3),
... ...
@@ -290,13 +290,13 @@ test_that("batch and bio can contain NA", {
290 290
   colnames(e) <- paste0("Sample", 1:ncol(e))
291 291
   batch <- gl(2, 5)
292 292
   bio <- gl(5, 2)
293
-  obj <- sconeExperiment(e, batch=batch, bio=bio)
293
+  obj <- SconeExperiment(e, batch=batch, bio=bio)
294 294
   res1 <- scone(obj, imputation=impute_null, scaling=identity, k_ruv=0, k_qc=0, evaluate = TRUE,
295 295
                adjust_batch = "no", eval_kclust = 3)
296 296
 
297 297
   batch[1] <- NA
298 298
   bio[2] <- NA
299
-  obj <- sconeExperiment(e, batch=batch, bio=bio)
299
+  obj <- SconeExperiment(e, batch=batch, bio=bio)
300 300
 
301 301
   res2 <- scone(obj, imputation=impute_null, scaling=identity, k_ruv=0, k_qc=0, evaluate = TRUE,
302 302
         adjust_batch = "no", eval_kclust = 3)
... ...
@@ -10,7 +10,7 @@ test_that("select_methods works in all three modes", {
10 10
   bio <- gl(2, 5)
11 11
   batch <- as.factor(rep(1:2, 5))
12 12
 
13
-  obj <- sconeExperiment(e, qc=qc_mat,
13
+  obj <- SconeExperiment(e, qc=qc_mat,
14 14
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
15 15
                          bio = as.factor(bio), batch=as.factor(batch))
16 16
 
... ...
@@ -45,7 +45,7 @@ test_that("get_normalized subsets score matrix", {
45 45
   bio <- gl(2, 5)
46 46
   batch <- as.factor(rep(1:2, 5))
47 47
 
48
-  obj <- sconeExperiment(e, qc=qc_mat,
48
+  obj <- SconeExperiment(e, qc=qc_mat,
49 49
                          negcon_ruv=c(rep(TRUE, 100), rep(FALSE, NROW(e)-100)),
50 50
                          bio = as.factor(bio), batch=as.factor(batch))
51 51
 
... ...
@@ -438,7 +438,7 @@ framework for evaluating the performance of normalization workflows.
438 438
 ## Creating a SconeExperiment Object
439 439
 
440 440
 Prior to running main `scone` function we will want to define a
441
-`sconeExperiment` object that contains the primary expression data,
441
+`SconeExperiment` object that contains the primary expression data,
442 442
 experimental metadata, and control gene sets.
443 443
 
444 444
 ```{r scone_init}
... ...
@@ -470,7 +470,7 @@ poscon = intersect(rownames(expr),strsplit(paste0("ALS2, CDK5R1, CYFIP1,",
470 470
 negcon = intersect(rownames(expr),hk)
471 471
 
472 472
 # Creating a SconeExperiment Object
473
-my_scone <- sconeExperiment(expr,
473
+my_scone <- SconeExperiment(expr,
474 474
                 qc=ppq, bio = bio,
475 475
                 negcon_ruv = rownames(expr) %in% negcon,
476 476
                 poscon = rownames(expr) %in% poscon
... ...
@@ -555,7 +555,7 @@ but will run scone without imputation.
555 555
 The main `scone` method arguments allow for a lot of flexibility, but a user
556 556
 may choose to run very specific combinations of modules. For this purpose,
557 557
 `scone` can be run in `run=FALSE` mode, generating a list of workflows to be
558
-performed and storing this list within a `sconeExperiment` object. After
558
+performed and storing this list within a `SconeExperiment` object. After
559 559
 running this command the list can be extracted using the `get_params` method.
560 560
 
561 561
 ```{r scone_params}
... ...
@@ -591,7 +591,7 @@ apply(get_params(my_scone),2,unique)
591 591
 Some scaling methods, such as scaling by gene detection rate (`EFF_FN()`), will
592 592
 not make sense within the context of imputed data, as imputation replaces
593 593
 zeroes with non-zero values. We can use the `select_methods` method to produce
594
-a `sconeExperiment` object initialized to run only meaningful normalization
594
+a `SconeExperiment` object initialized to run only meaningful normalization
595 595
 workflows.
596 596
 
597 597
 ```{r scone_params_filt, eval=FALSE}