Browse code

Merge branch 'collab'

* collab:
coercion of CNSet to oligoSnpSet uses lrr/baf instead of ca+cb/genotypes

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

Rob Scharp authored on 05/02/2012 15:20:45
Showing 3 changed files

... ...
@@ -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.13.7
4
+Version: 1.13.8
5 5
 Date: 2010-12-10
6 6
 Author: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au>, Ingo Ruczinski <iruczins@jhsph.edu>, Rafael A Irizarry
7 7
 Maintainer: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
... ...
@@ -52,9 +52,15 @@ importFrom(mvtnorm, dmvnorm)
52 52
 importFrom(ellipse, ellipse)
53 53
 ##importFrom(ff, ffdf, physical.ff, physical.ffdf, ffrowapply)
54 54
 
55
-##importClassesFrom(oligoClasses, ff_matrix, ffdf)
56
-##exportMethods(lines)
57
-exportMethods(CA, CB)
55
+##----------------------------------------------------------------------------
56
+## export
57
+##----------------------------------------------------------------------------
58
+exportClasses(PredictionRegion)
59
+exportMethods(CA, CB, coerce,
60
+	      A, B, corr, nuA, nuB, phiA, phiB,
61
+	      predictionRegion, posteriorProbability,
62
+	      tau2, Ns, medians, mads,
63
+	      xyplot, calculateRBaf)
58 64
 export(crlmm,
59 65
        crlmmIllumina,
60 66
        crlmmIlluminaV2,
... ...
@@ -69,7 +75,4 @@ export(crlmm,
69 75
        genotype.Illumina,
70 76
        crlmmCopynumber2, crlmmCopynumberLD, crlmmCopynumber)
71 77
 export(genotypes, totalCopynumber, rawCopynumber, xyplot)
72
-exportMethods(A, B, corr, nuA, nuB, phiA, phiB, predictionRegion, posteriorProbability, tau2, Ns, medians, mads,
73
-	      xyplot, calculateRBaf)
74 78
 export(ABpanel, constructInf, preprocessInf, genotypeInf, validCEL, celDates)
75
-exportClasses(PredictionRegion)
... ...
@@ -1,6 +1,62 @@
1 1
 setMethod("posteriorMean", signature(object="CNSet"), function(object) assayDataElement(object, "posteriorMean"))
2 2
 setReplaceMethod("posteriorMean", signature(object="CNSet", value="matrix"), function(object, value) assayDataElementReplace(object, "posteriorMean", value))
3 3
 
4
+setAs("CNSet", "oligoSnpSet", function(from, to){
5
+	cnSet2oligoSnpSet(from)
6
+})
7
+
8
+cnSet2oligoSnpSet <- function(object){
9
+	row.index <- seq_len(nrow(object))
10
+	col.index <- seq_len(ncol(object))
11
+	is.lds <- ifelse(is(calls(object), "ff_matrix") | is(calls(object), "ffdf"), TRUE, FALSE)
12
+	if(is.lds) stopifnot(isPackageLoaded("ff"))
13
+	b.r <- calculateRBaf(object)
14
+##	if(is.lds){
15
+##		## initialize a big matrix for raw copy number
16
+##		message("creating an ff object for storing total copy number")
17
+##		tcn <- initializeBigMatrix(name="total_cn", nrow(object), ncol(object), vmode="double")
18
+##		for(j in 1:ncol(object)){
19
+##			tcn[, j] <- totalCopynumber(object, i=row.index, j=j)
20
+##		}
21
+##	} else {
22
+##		if(ncol(object) > 5){
23
+##			##this can be memory intensive, so we try to be careful
24
+##			col.index <- splitIndicesByLength(seq(length=ncol(object)), 5)
25
+##			tcn <- matrix(NA, nrow(object), ncol(object))
26
+##			dimnames(tcn) <- list(featureNames(object), sampleNames(object))
27
+##			rows <- 1:nrow(object)
28
+##			for(i in seq_along(col.index)){
29
+##				cat(".")
30
+##				j <- col.index[[i]]
31
+##				cnSet <- object[, j]
32
+##				tcn[, j] <- totalCopynumber(cnSet, i=row.index, j=1:ncol(cnSet))
33
+##				rm(cnSet); gc()
34
+##			}
35
+##			cat("\n")
36
+##		} else {
37
+##			tcn <- totalCopynumber(object, i=row.index, j=col.index)
38
+##		}
39
+##	}
40
+##	message("Transforming copy number to log2 scale")
41
+##	tcn[tcn < 0.1] <- 0.1
42
+##	tcn[tcn > 8] <- 8
43
+##	log.tcn <- log2(tcn)
44
+	tmp <- new("oligoSnpSet",
45
+		   ##copyNumber=log.tcn,
46
+		   copyNumber=b.r[[2]],
47
+		   ##baf=b.r[[1]],
48
+		   call=calls(object),
49
+		   callProbability=snpCallProbability(object),
50
+		   annotation=annotation(object),
51
+		   featureData=featureData(object),
52
+		   phenoData=phenoData(object),
53
+		   experimentData=experimentData(object),
54
+		   protocolData=protocolData(object))
55
+	tmp <- assayDataElementReplace(tmp, "baf", b.r[[1]])
56
+	return(tmp)
57
+}
58
+
59
+
4 60
 linearParamElementReplace <- function(obj, elt, value) {
5 61
     storage.mode <- storageMode(batchStatistics(obj))
6 62
     switch(storage.mode,