Browse code

added "ihw" as pvalue adjustment method in MRcoefs

also created fitFeatureModelResults and fitZigResults classes

Domenick Braccia authored on 19/04/2019 23:54:14
Showing 14 changed files

... ...
@@ -14,8 +14,14 @@
14 14
 #' @param taxa Taxa list.
15 15
 #' @param uniqueNames Number the various taxa.
16 16
 #' @param adjustMethod Method to adjust p-values by. Default is "FDR". Options
17
-#' include "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr",
17
+#' include "IHW", "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr",
18 18
 #' "none". See \code{\link{p.adjust}} for more details.
19
+#' @param IHWcov Character value specifying which covariate to use when adjusting pvalues
20
+#' using IHW. Options include: "nnz" (number of non-zero elements per feature), 
21
+#' "median" (median abundance value per feature), "Amean" (adjusted mean, used for a 
22
+#' fitZigResults obj)
23
+#' @param alpha Value for p-value significance threshold when running IHW. 
24
+#' The default is set to 0.1 
19 25
 #' @param group One of five choices, 0,1,2,3,4. 0: the sort is ordered by a
20 26
 #' decreasing absolute value coefficient fit. 1: the sort is ordered by the raw
21 27
 #' coefficient fit in decreasing order. 2: the sort is ordered by the raw
... ...
@@ -43,21 +49,22 @@
43 49
 #' fit = fitFeatureModel(obj = lungTrim,mod=mod)
44 50
 #' head(MRcoefs(fit))
45 51
 #'
46
-MRcoefs<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,
47
-    uniqueNames=FALSE,adjustMethod="fdr",group=0,eff=0,numberEff=FALSE,counts=0,file=NULL){
52
+MRcoefs<-function(obj,by=2,coef=NULL,number=10,taxa=obj@taxa,
53
+    uniqueNames=FALSE,adjustMethod="fdr",alpha=0.1,
54
+    group=0,eff=0,numberEff=FALSE,counts=0,file=NULL){
48 55
 
49
-    if(length(grep("fitFeatureModel",obj$call))){
50
-        groups = factor(obj$design[,by])
56
+    if(length(grep("fitFeatureModel",obj@call))){
57
+        groups = factor(obj@design[,by])
51 58
         by = "logFC"; coef = 1:2;
52
-        tb = data.frame(logFC=obj$fitZeroLogNormal$logFC,se=obj$fitZeroLogNormal$se)
53
-        p  = obj$pvalues
59
+        tb = data.frame(logFC=obj@fitZeroLogNormal$logFC,se=obj@fitZeroLogNormal$se)
60
+        p  = obj@pvalues
54 61
     } else {
55
-        tb = obj$fit$coefficients
62
+        tb = obj@fit$coefficients
56 63
         if(is.null(coef)){
57 64
             coef = 1:ncol(tb)
58 65
         }
59
-        p=obj$eb$p.value[,by]
60
-        groups = factor(obj$fit$design[,by])
66
+        p=obj@eb$p.value[,by]
67
+        groups = factor(obj@fit$design[,by])
61 68
         if(eff>0){
62 69
             effectiveSamples = calculateEffectiveSamples(obj)
63 70
             if(numberEff == FALSE){
... ...
@@ -75,8 +82,24 @@ MRcoefs<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,
75 82
             tx[ii]=paste(tx[ii],seq_along(ii),sep=":")
76 83
         }
77 84
     }
78
-    padj = p.adjust(p,method=adjustMethod)
79
-
85
+    
86
+    # # adding IHW as pvalue adjustment method
87
+    # if(adjustMethod == "ihw") {
88
+    #   # run MRihw
89
+    #   padj = MRihw(obj, p, IHWcov, alpha)
90
+    # } else {
91
+    #   padj = p.adjust(p, method = adjustMethod) # use classic pvalue adjusment methods
92
+    # }
93
+    
94
+    # adding 'ihw' as pvalue adjustment method
95
+    if (adjustMethod == "ihw-ubiquity" | adjustMethod == "ihw-abundance") {
96
+      # use IHW to adjust pvalues
97
+      padj = MRihw(obj, p, adjustMethod, alpha)
98
+    } else {
99
+      # use classic pvalue adjusment method
100
+      padj = p.adjust(p, method = adjustMethod)
101
+    }
102
+    
80 103
     if(group==0){
81 104
         srt = order(abs(tb[,by]),decreasing=TRUE)
82 105
     } else if(group==1){
... ...
@@ -91,7 +114,7 @@ MRcoefs<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,
91 114
     
92 115
     valid = 1:length(padj);
93 116
     if(counts>0){
94
-        np=rowSums(obj$counts);
117
+        np=rowSums(obj@counts);
95 118
         valid = intersect(valid,which(np>=counts));
96 119
     }
97 120
     srt = srt[which(srt%in%valid)][1:min(number,nrow(tb))];
98 121
new file mode 100644
... ...
@@ -0,0 +1,66 @@
1
+#' MRihw runs IHW within a MRcoefs() call
2
+#' 
3
+#' Function used in MRcoefs() when "IHW" is set as the p value adjustment method
4
+#' 
5
+#' @rdname MRihw
6
+#' @param obj Either a fitFeatureModelResults or fitZigResults object
7
+#' @param ... other parameters
8
+#' 
9
+setGeneric("MRihw", function(obj, ...){standardGeneric("MRihw")})
10
+
11
+#' MRihw runs IHW within a MRcoefs() call
12
+#' 
13
+#' Function used in MRcoefs() when "IHW" is set as the p value adjustment method
14
+#' 
15
+#' @rdname MRihw-fitFeatureModelResults
16
+#' @param obj Either a fitFeatureModelResults or fitZigResults object
17
+#' @param p a vector of pvalues extracted from obj
18
+#' @param IHWcov Value specifying which covariate to use in IHW pvalue adjustment. For obj
19
+#' of class \code{\link{fitFeatureModelResults}}, options are "median" and "nnz" (number of non-zero 
20
+#' features per row). For obj of class \code{\link{fitZigResults}}, options are "Amean" and "nnz".
21
+#' @param alpha pvalue significance level specified for IHW call. Default is 0.1
22
+#' 
23
+setMethod("MRihw", signature = "fitFeatureModelResults", function(obj, p, adjustMethod, alpha){
24
+  if (adjustMethod == "ihw-ubiquity") {
25
+    # set covariate to be num of non-zero elements per row
26
+    p <- obj@pvalues
27
+    covariate <- rowSums(obj@counts != 0)
28
+    ihwRes <- ihw(p, covariate, alpha)
29
+    padj <- ihwRes@df$adj_pvalue 
30
+  }
31
+  if (adjustMethod == "ihw-abundance"){
32
+    # use feature median count as covariate
33
+    covariate <- rowMedians(obj@counts)
34
+    ihwRes <- ihw(p, covariate, alpha)
35
+    padj <- ihwRes@df$adj_pvalue
36
+  }
37
+  padj
38
+})
39
+
40
+#' MRihw runs IHW within a MRcoefs() call
41
+#' 
42
+#' Function used in MRcoefs() when "IHW" is set as the p value adjustment method
43
+#' 
44
+#' @rdname MRihw-fitZigResults
45
+#' @param obj Either a fitFeatureModelResults or fitZigResults object
46
+#' @param p a vector of pvalues extracted from obj
47
+#' @param IHWcov Value specifying which covariate to use in IHW pvalue adjustment. For obj
48
+#' of class \code{\link{fitFeatureModelResults}}, options are "median" and "nnz" (number of non-zero 
49
+#' features per row). For obj of class \code{\link{fitZigResults}}, options are "Amean" and "nnz".
50
+#' @param alpha pvalue significance level specified for IHW call. Default is 0.1
51
+#' 
52
+setMethod("MRihw", signature = "fitZigResults", function(obj, p, adjustMethod, alpha){
53
+  if (adjustMethod == "ihw-ubiquity"){
54
+    #use number of non-zero features per row as the covariate in ihw() call
55
+    covariate <- rowSums(obj@counts != 0)
56
+    ihwRes <- ihw(p, covariate, alpha)
57
+    padj <- ihwRes@df$adj_pvalue
58
+  }
59
+  if (adjustMethod == "ihw-abundance"){
60
+    # use Amean as covariate
61
+    covariate <- obj@eb$Amean
62
+    ihwRes <- ihw(p, covariate, alpha)
63
+    padj <- ihwRes@df$adj_pvalue
64
+  }
65
+  padj
66
+})
0 67
\ No newline at end of file
... ...
@@ -46,21 +46,21 @@
46 46
 #' fit = fitFeatureModel(obj = lungTrim,mod=mod)
47 47
 #' head(MRtable(fit))
48 48
 #'
49
-MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,
49
+MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj@taxa,
50 50
     uniqueNames=FALSE,adjustMethod="fdr",group=0,eff=0,numberEff=FALSE,ncounts=0,file=NULL){
51 51
 
52
-    if(length(grep("fitFeatureModel",obj$call))){
53
-        groups = factor(obj$design[,by])
52
+    if(length(grep("fitFeatureModel",obj@call))){
53
+        groups = factor(obj@design[,by])
54 54
         by = "logFC"; coef = 1:2;
55
-        tb = data.frame(logFC=obj$fitZeroLogNormal$logFC,se=obj$fitZeroLogNormal$se)
56
-        p  = obj$pvalues
55
+        tb = data.frame(logFC=obj@fitZeroLogNormal$logFC,se=obj@fitZeroLogNormal$se)
56
+        p  = obj@pvalues
57 57
     } else {
58
-        tb = obj$fit$coefficients
58
+        tb = obj@fit$coefficients
59 59
         if(is.null(coef)){
60 60
             coef = 1:ncol(tb)
61 61
         }
62
-        p=obj$eb$p.value[,by]
63
-        groups = factor(obj$fit$design[,by])
62
+        p=obj@eb$p.value[,by]
63
+        groups = factor(obj@fit$design[,by])
64 64
         if(eff>0){
65 65
             effectiveSamples = calculateEffectiveSamples(obj)
66 66
             if(numberEff == FALSE){
... ...
@@ -79,7 +79,7 @@ MRtable<-function(obj,by=2,coef=NULL,number=10,taxa=obj$taxa,
79 79
         }
80 80
     }
81 81
     padj = p.adjust(p,method=adjustMethod)
82
-    cnts = obj$counts
82
+    cnts = obj@counts
83 83
     posIndices = cnts>0
84 84
     
85 85
     np0 = rowSums(posIndices[,groups==0])
... ...
@@ -1,32 +1,32 @@
1 1
 setClass("MRexperiment", contains=c("eSet"), representation=representation(expSummary = "list"),prototype = prototype( new( "VersionedBiobase",versions = c(classVersion("eSet"),MRexperiment = "1.0.0" ))))
2 2
 
3 3
 setMethod("[", "MRexperiment", function (x, i, j, ..., drop = FALSE) {
4
-        obj= callNextMethod()
5
-        if(!missing(j)){
6
-            obj@expSummary = new("list",expSummary=as(expSummary(x)[j,1:2,...,drop=drop],"AnnotatedDataFrame"),cumNormStat=x@expSummary$cumNormStat)
7
-            if(length(pData(obj))>0){
8
-              for(i in 1:length(pData(obj))){
9
-                if(is.factor(pData(obj)[,i])){
10
-                  pData(obj)[,i] = factor(pData(obj)[,i])
11
-                } else {
12
-                  pData(obj)[,i] = pData(obj)[,i]
13
-                }
14
-              }
15
-            }
4
+  obj= callNextMethod()
5
+  if(!missing(j)){
6
+    obj@expSummary = new("list",expSummary=as(expSummary(x)[j,1:2,...,drop=drop],"AnnotatedDataFrame"),cumNormStat=x@expSummary$cumNormStat)
7
+    if(length(pData(obj))>0){
8
+      for(i in 1:length(pData(obj))){
9
+        if(is.factor(pData(obj)[,i])){
10
+          pData(obj)[,i] = factor(pData(obj)[,i])
11
+        } else {
12
+          pData(obj)[,i] = pData(obj)[,i]
16 13
         }
17
-        obj
14
+      }
15
+    }
16
+  }
17
+  obj
18 18
 })
19 19
 setMethod("colSums", signature ="MRexperiment", function (x, ...) {
20
-    callNextMethod(MRcounts(x),...)
20
+  callNextMethod(MRcounts(x),...)
21 21
 })
22 22
 setMethod("rowSums", signature="MRexperiment", function (x, ...) {
23
-    callNextMethod(MRcounts(x),...)
23
+  callNextMethod(MRcounts(x),...)
24 24
 })
25 25
 setMethod("rowMeans", signature="MRexperiment", function (x, ...) {
26
-    callNextMethod(MRcounts(x),...)
26
+  callNextMethod(MRcounts(x),...)
27 27
 })
28 28
 setMethod("colMeans", signature="MRexperiment", function (x, ...) {
29
-    callNextMethod(MRcounts(x),...)
29
+  callNextMethod(MRcounts(x),...)
30 30
 })
31 31
 
32 32
 #' Access the normalization factors in a MRexperiment object
... ...
@@ -48,11 +48,11 @@ setGeneric("normFactors",function(object){standardGeneric("normFactors")})
48 48
 setGeneric("normFactors<-",function(object,value){standardGeneric("normFactors<-")})
49 49
 
50 50
 setMethod("normFactors", signature="MRexperiment",function(object) {
51
-   nf <- expSummary(object)$normFactors
52
-   nf <- unlist(nf)
53
-   names(nf) <- sampleNames(object)
54
-   nf
55
- })
51
+  nf <- expSummary(object)$normFactors
52
+  nf <- unlist(nf)
53
+  names(nf) <- sampleNames(object)
54
+  nf
55
+})
56 56
 
57 57
 #' Replace the normalization factors in a MRexperiment object
58 58
 #'
... ...
@@ -72,11 +72,11 @@ setMethod("normFactors", signature="MRexperiment",function(object) {
72 72
 #' head(normFactors(lungData)<- rnorm(1))
73 73
 #'
74 74
 setReplaceMethod("normFactors", signature=c(object="MRexperiment", value="numeric"),
75
-  function( object, value ) {
76
-   pData(object@expSummary$expSummary)$normFactors <- value
77
-   validObject( object )
78
-   object
79
-})
75
+                 function( object, value ) {
76
+                   pData(object@expSummary$expSummary)$normFactors <- value
77
+                   validObject( object )
78
+                   object
79
+                 })
80 80
 
81 81
 #' Access sample depth of coverage from MRexperiment object
82 82
 #'
... ...
@@ -98,11 +98,11 @@ setGeneric("libSize",function(object){standardGeneric("libSize")})
98 98
 setGeneric("libSize<-",function(object,value){standardGeneric("libSize<-")})
99 99
 
100 100
 setMethod("libSize", signature="MRexperiment",function(object) {
101
-   ls <- expSummary(object)$libSize
102
-   ls <- unlist(ls)
103
-   names(ls) <- sampleNames(object)
104
-   ls
105
- })
101
+  ls <- expSummary(object)$libSize
102
+  ls <- unlist(ls)
103
+  names(ls) <- sampleNames(object)
104
+  ls
105
+})
106 106
 
107 107
 #' Replace the library sizes in a MRexperiment object
108 108
 #'
... ...
@@ -122,11 +122,54 @@ setMethod("libSize", signature="MRexperiment",function(object) {
122 122
 #' head(libSize(lungData)<- rnorm(1))
123 123
 #'
124 124
 setReplaceMethod("libSize", signature=c(object="MRexperiment", value="numeric"),
125
-  function( object, value ) {
126
-   pData(object@expSummary$expSummary)$libSize <- value
127
-   validObject( object )
128
-   object
129
-})
125
+                 function( object, value ) {
126
+                   pData(object@expSummary$expSummary)$libSize <- value
127
+                   validObject( object )
128
+                   object
129
+                 })
130
+
131
+#' Class "fitZigResults" -- a formal class for storing results from a fitZig call
132
+#' 
133
+#' This class contains all of the same information expected from a fitZig call, 
134
+#' but it is defined in the S4 style as opposed to being stored as a list.
135
+#' 
136
+#' @slot call the call made to fitZig
137
+#' @slot fit 'MLArrayLM' Limma object of the weighted fit
138
+#' @slot countResiduals standardized residuals of the fit
139
+#' @slot z matrix of the posterior probabilities. It is defined as $z_ij = pr(delta_ij=1 | data)$
140
+#' @slot zUsed used in \code{\link{getZ}}
141
+#' @slot eb output of eBayes, moderated t-statistics, moderated F-statistics, etc
142
+#' @slot taxa vector of the taxa names
143
+#' @slot counts the original count matrix input
144
+#' @slot zeroMod the zero model matrix
145
+#' @slot zeroCoef the zero model fitted results
146
+#' @slot stillActive convergence
147
+#' @slot stillActiveNLL nll at convergence
148
+#' @slot dupcor correlation of duplicates
149
+#' @exportClass
150
+#' 
151
+setClass("fitZigResults", 
152
+         slots = c(fit = "list", countResiduals = "matrix", z = "matrix", zUsed = "ANY", 
153
+                   eb = "MArrayLM", zeroMod = "matrix", stillActive = "logical", stillActiveNLL = "numeric", 
154
+                   zeroCoef = "list", dupcor = "ANY", call = "call", taxa = "character", counts = "matrix"))
155
+
156
+#' Class "fitFeatureModelResults" -- a formal class for storing results from a fitFeatureModel call
157
+#' 
158
+#' This class contains all of the same information expected from a fitFeatureModel call, 
159
+#' but it is defined in the S4 style as opposed to being stored as a list.
160
+#' 
161
+#' @slot call  the call made to fitFeatureModel
162
+#' @slot fitZeroLogNormal  list of parameter estimates for the zero-inflated log normal model
163
+#' @slot design  model matrix
164
+#' @slot taxa  taxa names
165
+#' @slot counts  count matrix
166
+#' @slot pvalues  calculated p-values
167
+#' @slot permuttedFits  permutted z-score estimates under the null
168
+#' @exportClass
169
+#' 
170
+setClass("fitFeatureModelResults",
171
+         slots = c(call = "call", fitZeroLogNormal = "list", design = "matrix", taxa = "character",
172
+                   counts = "matrix", pvalues = "numeric", permuttedFits = "ANY"))
130 173
 
131 174
 #' Create a MRexperiment object
132 175
 #' 
... ...
@@ -147,6 +190,7 @@ setReplaceMethod("libSize", signature=c(object="MRexperiment", value="numeric"),
147 190
 #' @param normFactors normFactors, the normalization factors used in either the
148 191
 #' model or as scaling factors of sample counts for each particular sample.
149 192
 #' @return an object of class MRexperiment
193
+#' @export
150 194
 #' @author Joseph N Paulson
151 195
 #' @examples
152 196
 #' 
... ...
@@ -154,37 +198,37 @@ setReplaceMethod("libSize", signature=c(object="MRexperiment", value="numeric"),
154 198
 #' obj <- newMRexperiment(cnts)
155 199
 #' 
156 200
 newMRexperiment <- function(counts, phenoData=NULL, featureData=NULL,libSize=NULL, normFactors=NULL) {
157
-    counts= as.matrix(counts)
158
-
159
-    if( is.null( featureData ) ){
160
-      featureData <- annotatedDataFrameFrom(counts, byrow=TRUE)
161
-    }
162
-    if( is.null( phenoData ) ){
163
-      phenoData   <- annotatedDataFrameFrom(counts, byrow=FALSE)
164
-    }
165
-    if( is.null( libSize ) ){
166
-      libSize <- as.matrix(colSums(counts))
167
-      rownames(libSize) = colnames(counts)
168
-    }
169
-    if( is.null( normFactors ) ){
170
-      normFactors <- as.matrix(rep( NA_real_, length(libSize) ))
171
-      rownames(normFactors) = rownames(libSize)
172
-    }
173
-
174
-    obj <-new("MRexperiment", assayData = assayDataNew("environment",counts=counts),phenoData = phenoData,featureData = featureData ,expSummary = new("list",expSummary=annotatedDataFrameFrom(counts,byrow=FALSE),cumNormStat=NULL))
175
-    obj@expSummary$expSummary$libSize = libSize;
176
-    obj@expSummary$expSummary$normFactors=normFactors;
177
-    validObject(obj)
178
-    obj
201
+  counts= as.matrix(counts)
202
+  
203
+  if( is.null( featureData ) ){
204
+    featureData <- annotatedDataFrameFrom(counts, byrow=TRUE)
205
+  }
206
+  if( is.null( phenoData ) ){
207
+    phenoData   <- annotatedDataFrameFrom(counts, byrow=FALSE)
208
+  }
209
+  if( is.null( libSize ) ){
210
+    libSize <- as.matrix(colSums(counts))
211
+    rownames(libSize) = colnames(counts)
212
+  }
213
+  if( is.null( normFactors ) ){
214
+    normFactors <- as.matrix(rep( NA_real_, length(libSize) ))
215
+    rownames(normFactors) = rownames(libSize)
216
+  }
217
+  
218
+  obj <-new("MRexperiment", assayData = assayDataNew("environment",counts=counts),phenoData = phenoData,featureData = featureData ,expSummary = new("list",expSummary=annotatedDataFrameFrom(counts,byrow=FALSE),cumNormStat=NULL))
219
+  obj@expSummary$expSummary$libSize = libSize;
220
+  obj@expSummary$expSummary$normFactors=normFactors;
221
+  validObject(obj)
222
+  obj
179 223
 }
180 224
 setValidity( "MRexperiment", function( object ) {
181
-    if( is.null(assayData(object)$counts))
182
-        return( "There are no counts!" )
183
-#    if( ncol(MRcounts(object)) != length(normFactors(object)))
184
-#        return( "Experiment summary got hacked!" )
185
-#    if( ncol(MRcounts(object)) != length(libSize(object)))
186
-#        return( "Experiment summary got hacked!" )
187
-    TRUE
225
+  if( is.null(assayData(object)$counts))
226
+    return( "There are no counts!" )
227
+  #    if( ncol(MRcounts(object)) != length(normFactors(object)))
228
+  #        return( "Experiment summary got hacked!" )
229
+  #    if( ncol(MRcounts(object)) != length(libSize(object)))
230
+  #        return( "Experiment summary got hacked!" )
231
+  TRUE
188 232
 } )
189 233
 #' Accessor for the counts slot of a MRexperiment object
190 234
 #' 
... ...
@@ -208,22 +252,22 @@ setValidity( "MRexperiment", function( object ) {
208 252
 #' head(MRcounts(lungData))
209 253
 #' 
210 254
 MRcounts <- function(obj,norm=FALSE,log=FALSE,sl=1000) {
211
-   stopifnot( is( obj, "MRexperiment" ) )
212
-   if(!norm){
255
+  stopifnot( is( obj, "MRexperiment" ) )
256
+  if(!norm){
213 257
     x=assayData(obj)[["counts"]]
214
-   }
215
-   else{
258
+  }
259
+  else{
216 260
     if(any(is.na(normFactors(obj)))){
217 261
       x=cumNormMat(obj,sl=sl)
218 262
     } else{
219 263
       x=sweep(assayData(obj)[["counts"]],2,as.vector(unlist(normFactors(obj)))/sl,"/")
220 264
     }
221
-   }
222
-   if(!log){
265
+  }
266
+  if(!log){
223 267
     return(x)
224
-   } else{
268
+  } else{
225 269
     return(log2(x+1))
226
-   }
270
+  }
227 271
 }
228 272
 #' Access the posterior probabilities that results from analysis
229 273
 #' 
... ...
@@ -248,14 +292,14 @@ MRcounts <- function(obj,norm=FALSE,log=FALSE,sl=1000) {
248 292
 #' lungTrim = lungTrim[-k,]
249 293
 #' smokingStatus = pData(lungTrim)$SmokingStatus
250 294
 #' mod = model.matrix(~smokingStatus)
251
-#' # The maxit is not meant to be 1 - this is for demonstration/speed
295
+#' # The maxit is not meant to be 1 -- this is for demonstration/speed
252 296
 #' settings = zigControl(maxit=1,verbose=FALSE)
253 297
 #' fit = fitZig(obj = lungTrim,mod=mod,control=settings)
254 298
 #' head(posteriorProbs(lungTrim))
255 299
 #' 
256 300
 posteriorProbs <- function( obj ) {
257
-   stopifnot( is( obj, "MRexperiment" ) )
258
-   assayData(obj)[["z"]]
301
+  stopifnot( is( obj, "MRexperiment" ) )
302
+  assayData(obj)[["z"]]
259 303
 }
260 304
 
261 305
 #' Access MRexperiment object experiment data
... ...
@@ -76,7 +76,13 @@ fitFeatureModel<-function(obj,mod,coef=2,B=1,szero=FALSE,spos=TRUE){
76 76
   } else {
77 77
     pvals = 2*(1-pnorm(abs(zscore)))
78 78
   }
79
-  res = list(call=match.call(),fitZeroLogNormal=fitzeroln,design=mmCount,
80
-    taxa=rownames(obj),counts=MRcounts(obj),pvalues=pvals,permuttedFits=permuttedFits)
79
+  # old way of creating results object
80
+  # res = list(call=match.call(),fitZeroLogNormal=fitzeroln,design=mmCount,
81
+  #   taxa=rownames(obj),counts=MRcounts(obj),pvalues=pvals,permuttedFits=permuttedFits)
82
+  
83
+  # new way with defined results class
84
+  res = new("fitFeatureModelResults", call = match.call(), fitZeroLogNormal=fitzeroln, 
85
+            design = mmCount, taxa = rownames(obj), counts = MRcounts(obj), 
86
+            pvalues = pvals, permuttedFits = permuttedFits)
81 87
   res
82 88
 }
83 89
\ No newline at end of file
... ...
@@ -100,7 +100,16 @@ fitZig <- function(obj,
100 100
 	dat$zUsed <- NULL
101 101
 	
102 102
 	dat <- c(dat, list(call=match.call(),taxa=rownames(obj),counts=y))
103
-	dat
103
+	
104
+	# old way of outputting results with list
105
+	# dat <- c(dat, list(call=match.call(),taxa=rownames(obj),counts=y))
106
+	
107
+	# new output with defined results class
108
+	dat <- new("fitZigResults", fit=dat$fit, countResiduals=dat$countResiduals,
109
+	           z=dat$z, zUsed=dat$zUsed, eb=dat$eb, zeroMod=dat$zeroMod, stillActive=dat$stillActive,
110
+	           stillActiveNLL=dat$stillActiveNLL, zeroCoef=dat$zeroCoef, dupcor=dat$dupcor, call = dat$call,
111
+	           taxa = rownames(obj), counts = dat$counts)
112
+ 	dat
104 113
 }
105 114
 
106 115
 .do_fitZig <- function(y, 
... ...
@@ -181,7 +190,7 @@ fitZig <- function(obj,
181 190
   
182 191
   eb <- limma::eBayes(fit$fit)
183 192
   dat <- list(fit=fit$fit, countResiduals=fit$residuals,
184
-              z=z, zUsed=zUsed, eb=eb, zeroMod=zero_model_matrix, stillActive=stillActive, 
193
+              z=z, zUsed=zUsed, eb=eb, zeroMod=zero_model_matrix, stillActive=stillActive,
185 194
               stillActiveNLL=stillActiveNLL, zeroCoef=zeroCoef, dupcor=dupcor)
186 195
   dat
187 196
 }
... ...
@@ -4,9 +4,9 @@
4 4
 \alias{MRcoefs}
5 5
 \title{Table of top-ranked features from fitZig or fitFeatureModel}
6 6
 \usage{
7
-MRcoefs(obj, by = 2, coef = NULL, number = 10, taxa = obj$taxa,
8
-  uniqueNames = FALSE, adjustMethod = "fdr", group = 0, eff = 0,
9
-  numberEff = FALSE, counts = 0, file = NULL)
7
+MRcoefs(obj, by = 2, coef = NULL, number = 10, taxa = obj@taxa,
8
+  uniqueNames = FALSE, adjustMethod = "fdr", alpha = 0.1,
9
+  group = 0, eff = 0, numberEff = FALSE, counts = 0, file = NULL)
10 10
 }
11 11
 \arguments{
12 12
 \item{obj}{Output of fitFeatureModel or fitZig.}
... ...
@@ -24,9 +24,12 @@ or contrast of the linear model to display.}
24 24
 \item{uniqueNames}{Number the various taxa.}
25 25
 
26 26
 \item{adjustMethod}{Method to adjust p-values by. Default is "FDR". Options
27
-include "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr",
27
+include "IHW", "holm", "hochberg", "hommel", "bonferroni", "BH", "BY", "fdr",
28 28
 "none". See \code{\link{p.adjust}} for more details.}
29 29
 
30
+\item{alpha}{Value for p-value significance threshold when running IHW. 
31
+The default is set to 0.1}
32
+
30 33
 \item{group}{One of five choices, 0,1,2,3,4. 0: the sort is ordered by a
31 34
 decreasing absolute value coefficient fit. 1: the sort is ordered by the raw
32 35
 coefficient fit in decreasing order. 2: the sort is ordered by the raw
... ...
@@ -40,6 +43,11 @@ of the coefficient fit in increasing order. 4: no sorting.}
40 43
 \item{counts}{Filter features to have at least 'counts' counts.}
41 44
 
42 45
 \item{file}{Name of output file, including location, to save the table.}
46
+
47
+\item{IHWcov}{Character value specifying which covariate to use when adjusting pvalues
48
+using IHW. Options include: "nnz" (number of non-zero elements per feature), 
49
+"median" (median abundance value per feature), "Amean" (adjusted mean, used for a 
50
+fitZigResults obj)}
43 51
 }
44 52
 \value{
45 53
 Table of the top-ranked features determined by the linear fit's
46 54
new file mode 100644
... ...
@@ -0,0 +1,23 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/MRihw.R
3
+\docType{methods}
4
+\name{MRihw,fitFeatureModelResults-method}
5
+\alias{MRihw,fitFeatureModelResults-method}
6
+\title{MRihw runs IHW within a MRcoefs() call}
7
+\usage{
8
+\S4method{MRihw}{fitFeatureModelResults}(obj, p, adjustMethod, alpha)
9
+}
10
+\arguments{
11
+\item{obj}{Either a fitFeatureModelResults or fitZigResults object}
12
+
13
+\item{p}{a vector of pvalues extracted from obj}
14
+
15
+\item{alpha}{pvalue significance level specified for IHW call. Default is 0.1}
16
+
17
+\item{IHWcov}{Value specifying which covariate to use in IHW pvalue adjustment. For obj
18
+of class \code{\link{fitFeatureModelResults}}, options are "median" and "nnz" (number of non-zero 
19
+features per row). For obj of class \code{\link{fitZigResults}}, options are "Amean" and "nnz".}
20
+}
21
+\description{
22
+Function used in MRcoefs() when "IHW" is set as the p value adjustment method
23
+}
0 24
new file mode 100644
... ...
@@ -0,0 +1,23 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/MRihw.R
3
+\docType{methods}
4
+\name{MRihw,fitZigResults-method}
5
+\alias{MRihw,fitZigResults-method}
6
+\title{MRihw runs IHW within a MRcoefs() call}
7
+\usage{
8
+\S4method{MRihw}{fitZigResults}(obj, p, adjustMethod, alpha)
9
+}
10
+\arguments{
11
+\item{obj}{Either a fitFeatureModelResults or fitZigResults object}
12
+
13
+\item{p}{a vector of pvalues extracted from obj}
14
+
15
+\item{alpha}{pvalue significance level specified for IHW call. Default is 0.1}
16
+
17
+\item{IHWcov}{Value specifying which covariate to use in IHW pvalue adjustment. For obj
18
+of class \code{\link{fitFeatureModelResults}}, options are "median" and "nnz" (number of non-zero 
19
+features per row). For obj of class \code{\link{fitZigResults}}, options are "Amean" and "nnz".}
20
+}
21
+\description{
22
+Function used in MRcoefs() when "IHW" is set as the p value adjustment method
23
+}
0 24
new file mode 100644
... ...
@@ -0,0 +1,16 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/MRihw.R
3
+\name{MRihw}
4
+\alias{MRihw}
5
+\title{MRihw runs IHW within a MRcoefs() call}
6
+\usage{
7
+MRihw(obj, ...)
8
+}
9
+\arguments{
10
+\item{obj}{Either a fitFeatureModelResults or fitZigResults object}
11
+
12
+\item{...}{other parameters}
13
+}
14
+\description{
15
+Function used in MRcoefs() when "IHW" is set as the p value adjustment method
16
+}
... ...
@@ -5,7 +5,7 @@
5 5
 \title{Table of top microbial marker gene from linear model fit including sequence
6 6
 information}
7 7
 \usage{
8
-MRtable(obj, by = 2, coef = NULL, number = 10, taxa = obj$taxa,
8
+MRtable(obj, by = 2, coef = NULL, number = 10, taxa = obj@taxa,
9 9
   uniqueNames = FALSE, adjustMethod = "fdr", group = 0, eff = 0,
10 10
   numberEff = FALSE, ncounts = 0, file = NULL)
11 11
 }
12 12
new file mode 100644
... ...
@@ -0,0 +1,28 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/allClasses.R
3
+\docType{class}
4
+\name{fitFeatureModelResults-class}
5
+\alias{fitFeatureModelResults-class}
6
+\title{Class "fitFeatureModelResults" -- a formal class for storing results from a fitFeatureModel call}
7
+\description{
8
+This class contains all of the same information expected from a fitFeatureModel call, 
9
+but it is defined in the S4 style as opposed to being stored as a list.
10
+}
11
+\section{Slots}{
12
+
13
+\describe{
14
+\item{\code{call}}{the call made to fitFeatureModel}
15
+
16
+\item{\code{fitZeroLogNormal}}{list of parameter estimates for the zero-inflated log normal model}
17
+
18
+\item{\code{design}}{model matrix}
19
+
20
+\item{\code{taxa}}{taxa names}
21
+
22
+\item{\code{counts}}{count matrix}
23
+
24
+\item{\code{pvalues}}{calculated p-values}
25
+
26
+\item{\code{permuttedFits}}{permutted z-score estimates under the null}
27
+}}
28
+
0 29
new file mode 100644
... ...
@@ -0,0 +1,40 @@
1
+% Generated by roxygen2: do not edit by hand
2
+% Please edit documentation in R/allClasses.R
3
+\docType{class}
4
+\name{fitZigResults-class}
5
+\alias{fitZigResults-class}
6
+\title{Class "fitZigResults" -- a formal class for storing results from a fitZig call}
7
+\description{
8
+This class contains all of the same information expected from a fitZig call, 
9
+but it is defined in the S4 style as opposed to being stored as a list.
10
+}
11
+\section{Slots}{
12
+
13
+\describe{
14
+\item{\code{call}}{the call made to fitZig}
15
+
16
+\item{\code{fit}}{'MLArrayLM' Limma object of the weighted fit}
17
+
18
+\item{\code{countResiduals}}{standardized residuals of the fit}
19
+
20
+\item{\code{z}}{matrix of the posterior probabilities. It is defined as $z_ij = pr(delta_ij=1 | data)$}
21
+
22
+\item{\code{zUsed}}{used in \code{\link{getZ}}}
23
+
24
+\item{\code{eb}}{output of eBayes, moderated t-statistics, moderated F-statistics, etc}
25
+
26
+\item{\code{taxa}}{vector of the taxa names}
27
+
28
+\item{\code{counts}}{the original count matrix input}
29
+
30
+\item{\code{zeroMod}}{the zero model matrix}
31
+
32
+\item{\code{zeroCoef}}{the zero model fitted results}
33
+
34
+\item{\code{stillActive}}{convergence}
35
+
36
+\item{\code{stillActiveNLL}}{nll at convergence}
37
+
38
+\item{\code{dupcor}}{correlation of duplicates}
39
+}}
40
+
... ...
@@ -29,7 +29,7 @@ lungTrim = cumNorm(lungTrim)
29 29
 lungTrim = lungTrim[-k,]
30 30
 smokingStatus = pData(lungTrim)$SmokingStatus
31 31
 mod = model.matrix(~smokingStatus)
32
-# The maxit is not meant to be 1 - this is for demonstration/speed
32
+# The maxit is not meant to be 1 -- this is for demonstration/speed
33 33
 settings = zigControl(maxit=1,verbose=FALSE)
34 34
 fit = fitZig(obj = lungTrim,mod=mod,control=settings)
35 35
 head(posteriorProbs(lungTrim))