git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@45324 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -473,3 +473,7 @@ then readIDAT() should work. Thanks to Pierre Cherel who reported this error. |
473 | 473 |
(currently saving intermediate steps in crlmmIlluminaRS) |
474 | 474 |
removed cnOptions function and changed arguments to crlmmCopynumber |
475 | 475 |
|
476 |
+2010-03-18 R.Scharpf committed version 1.5.38 |
|
477 |
+ |
|
478 |
+** a few updates to initializeBigMatrix |
|
479 |
+** show, [ defined for CNSetLM |
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: crlmm |
2 | 2 |
Type: Package |
3 | 3 |
Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for Affymetrix SNP 5.0 and 6.0 and Illumina arrays. |
4 |
-Version: 1.5.37 |
|
4 |
+Version: 1.5.38 |
|
5 | 5 |
Date: 2010-02-05 |
6 | 6 |
Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au> |
7 | 7 |
Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
... | ... |
@@ -67,6 +67,9 @@ construct <- function(filenames, cdfName, copynumber=FALSE, sns, verbose=TRUE){ |
67 | 67 |
callProbability=initializeBigMatrix(name="callPr", nr,nc), |
68 | 68 |
featureData=featureData, |
69 | 69 |
annotation=cdfName) |
70 |
+ pd <- data.frame(matrix(NA, nc, 3), row.names=sns) |
|
71 |
+ colnames(pd)=c("SKW", "SNR", "gender") |
|
72 |
+ phenoData(callSet) <- new("AnnotatedDataFrame", data=pd) |
|
70 | 73 |
protocolData(callSet) <- protocolData |
71 | 74 |
sampleNames(callSet) <- sns |
72 | 75 |
return(callSet) |
... | ... |
@@ -1,9 +1,9 @@ |
1 |
-setMethod("show", "CNSet", function(object){ |
|
1 |
+setMethod("show", "CNSetLM", function(object){ |
|
2 | 2 |
callNextMethod(object) |
3 | 3 |
cat("lM: ", length(lM(object)), " elements \n") |
4 | 4 |
print(names(lM(object))) |
5 | 5 |
}) |
6 |
-setMethod("[", "CNSet", function(x, i, j, ..., drop=FALSE){ |
|
6 |
+setMethod("[", "CNSetLM", function(x, i, j, ..., drop=FALSE){ |
|
7 | 7 |
x <- callNextMethod(x, i, j, ..., drop=drop) |
8 | 8 |
if(!missing(i)){ |
9 | 9 |
if(class(lM(x)) == "ffdf"){ |
... | ... |
@@ -16,9 +16,9 @@ setMethod("[", "CNSet", function(x, i, j, ..., drop=FALSE){ |
16 | 16 |
}) |
17 | 17 |
setGeneric("lM", function(object) standardGeneric("lM")) |
18 | 18 |
setGeneric("lM<-", function(object, value) standardGeneric("lM<-")) |
19 |
-setMethod("lM", "CNSet", function(object) object@lM) |
|
19 |
+setMethod("lM", "CNSetLM", function(object) object@lM) |
|
20 | 20 |
##setMethod("linearModelParam", "AffymetrixCNSet", function(object) object@linearModelParam) |
21 |
-setReplaceMethod("lM", c("CNSet", "list_or_ffdf"), function(object, value){ |
|
21 |
+setReplaceMethod("lM", c("CNSetLM", "list_or_ffdf"), function(object, value){ |
|
22 | 22 |
object@lM <- value |
23 | 23 |
object |
24 | 24 |
}) |
... | ... |
@@ -211,36 +211,34 @@ initializeBigMatrix <- function(name, nr, nc, vmode="integer"){ |
211 | 211 |
if(prod(nr, nc) > 2^31){ |
212 | 212 |
##Need multiple matrices |
213 | 213 |
## -- use ffdf |
214 |
- |
|
215 | 214 |
## How many samples per ff object |
216 | 215 |
S <- floor(2^31/nr - 1) |
217 |
- |
|
218 | 216 |
## How many ff objects |
219 | 217 |
L <- ceiling(nc/S) |
220 | 218 |
name <- paste(name, 1:L, sep="_") |
221 |
- |
|
222 |
- results <- vector("list", L) |
|
219 |
+ resultsff <- vector("list", L) |
|
223 | 220 |
##resultsB <- vector("list", L) |
224 | 221 |
for(i in 1:(L-1)){ ## the Lth object may have fewer than nc columns |
225 |
- results[[i]] <- createFF(name=name[i], |
|
226 |
- dim=c(nr, S), |
|
227 |
- vmode=vmode) |
|
222 |
+ resultsff[[i]] <- createFF(name=name[i], |
|
223 |
+ dim=c(nr, S), |
|
224 |
+ vmode=vmode) |
|
228 | 225 |
} |
229 | 226 |
##the Lth element |
230 | 227 |
leftOver <- nc - ((L-1)*S) |
231 |
- results[[L]] <- createFF(name=name[L], |
|
232 |
- dim=c(nr, leftOver), |
|
233 |
- vmode=vmode) |
|
234 |
- resultsff <- do.call(ffdf, results) |
|
228 |
+ resultsff[[L]] <- createFF(name=name[L], |
|
229 |
+ dim=c(nr, leftOver), |
|
230 |
+ vmode=vmode) |
|
231 |
+ resultsff[[L]][,] <- NA |
|
232 |
+ results <- do.call(ffdf, resultsff) |
|
233 |
+ rm(resultsff); gc() |
|
235 | 234 |
##dimnames(resultsff) <- dns |
236 | 235 |
} else { |
237 |
- resultsff <- createFF(name=name, |
|
238 |
- dim=c(nr, nc), |
|
239 |
- vmode=vmode) |
|
236 |
+ results <- createFF(name=name, |
|
237 |
+ dim=c(nr, nc), |
|
238 |
+ vmode=vmode) |
|
240 | 239 |
} |
241 |
- resultsff[,] <- NA |
|
242 |
- } else resultsff <- matrix(NA, nr, nc) |
|
243 |
- return(resultsff) |
|
240 |
+ } else results <- matrix(NA, nr, nc) |
|
241 |
+ return(results) |
|
244 | 242 |
} |
245 | 243 |
setMethod("annotatedDataFrameFrom", "ff_matrix", Biobase:::annotatedDataFrameFromMatrix) |
246 | 244 |
setMethod("annotatedDataFrameFrom", "ffdf", Biobase:::annotatedDataFrameFromMatrix) |