Browse code

create a valid ExpressionSet()

- exprs(obj) <- value does not sync dimnames(value) with dimnames(obj)


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

Martin Morgan authored on 31/08/2016 22:08:32
Showing 2 changed files

... ...
@@ -2,7 +2,7 @@ Package: edge
2 2
 Type: Package
3 3
 Title: Extraction of Differential Gene Expression
4 4
 Date: 2015-04-15
5
-Version: 2.5.2
5
+Version: 2.5.3
6 6
 Author: John D. Storey, Jeffrey T. Leek and Andrew J. Bass
7 7
 Maintainer: John D. Storey <jstorey@princeton.edu>, Andrew J. Bass
8 8
     <ajbass@princeton.edu>
... ...
@@ -145,10 +145,8 @@ build_study = function(data, grp = NULL, adj.var = NULL, bio.var = NULL,
145 145
         fmod <- paste(paste("~", paste(names(pdat)[-1], collapse=" + ")),"+",time.basis,"+", paste( "(", paste(names(pdat)[ncol(pdat)], collapse=" + ", sep=""), ")", ":", time.basis))  }
146 146
     }
147 147
   }
148
-  exp_set <- new("ExpressionSet")
149 148
   rownames(pdat) <- colnames(data)
150
-  pData(exp_set) <- data.frame(pdat)
151
-  exprs(exp_set) <- as.matrix(data)
149
+  exp_set <- ExpressionSet(as.matrix(data), AnnotatedDataFrame(pdat))
152 150
   edgeObj <- deSet(exp_set, full.model=as.formula(fmod),
153 151
                      null.model=as.formula(nmod), individual=ind)
154 152
   return(edgeObj)
... ...
@@ -206,10 +204,7 @@ build_models <- function(data, cov, full.model = NULL, null.model = NULL,
206 204
     stop("alternative and null models must be formatted as a formula")
207 205
   }
208 206
 
209
-  exp_set <- new("ExpressionSet")
210
-  exprs(exp_set) <- data
211
-  pData(exp_set) <- cov
212
-
207
+  exp_set <- ExpressionSet(data, AnnotatedDataFrame(cov))
213 208
   edgeObj <- deSet(exp_set, full.model = full.model, null.model = null.model,
214 209
                    individual = ind)
215 210
   return(edgeObj)