Browse code

v1.7.11 removed 'copyNumber' method from methods-CNSet.R.

Commented CA, CB initialization in the coercion of SnpSuperSet to CNSetLM.

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

Rob Scharp authored on 21/08/2010 02:47:41
Showing 2 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.7.9
4
+Version: 1.7.11
5 5
 Date: 2010-07-30
6 6
 Author: Rafael A Irizarry, Benilton S Carvalho <carvalho@bclab.org>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au>
7 7
 Maintainer: Benilton S Carvalho <carvalho@bclab.org>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
... ...
@@ -50,8 +50,8 @@ setAs("SnpSuperSet", "CNSetLM", function(from, to){
50 50
 		     alleleB=B(from),
51 51
 		     call=snpCall(from),
52 52
 		     callProbability=snpCallProbability(from),
53
-		     CA=initializeBigMatrix("CA", nrow(from), ncol(from)),
54
-		     CB=initializeBigMatrix("CB", nrow(from), ncol(from)),
53
+##		     CA=initializeBigMatrix("CA", nrow(from), ncol(from)),
54
+##		     CB=initializeBigMatrix("CB", nrow(from), ncol(from)),
55 55
 		     annotation=annotation(from),
56 56
 		     featureData=featureData(from),
57 57
 		     experimentData=experimentData(from),
... ...
@@ -105,24 +105,6 @@ setMethod("computeCopynumber", "CNSet",
105 105
 	object
106 106
 })
107 107
 
108
-setMethod("copyNumber", "CNSet", function(object){
109
-	I <- isSnp(object)
110
-	ffIsLoaded <- class(calls(object))[[1]]=="ff"
111
-	CA <- CA(object)
112
-	CB <- CB(object)
113
-	if(ffIsLoaded){
114
-		open(CA)
115
-		open(CB)
116
-		CA <- as.matrix(CA[,])
117
-		CB <- as.matrix(CB[,])
118
-	}
119
-	CN <- CA + CB
120
-	##For nonpolymorphic probes, CA is the total copy number
121
-	CN[!I, ] <- CA(object)[!I, ]
122
-	CN <- CN/100
123
-	CN
124
-})
125
-
126 108
 setMethod("totalCopyNumber", "CNSet", function(object, i, j){
127 109
 	if(missing(i) & missing(j)){
128 110
 		if(inherits(CA(object), "ff") | inherits(CA(object), "ffdf")) stop("Must specify i and/or j for ff objects")
... ...
@@ -150,58 +132,10 @@ setMethod("totalCopyNumber", "CNSet", function(object, i, j){
150 132
 	return(cn.total)
151 133
 })
152 134
 
153
-##setMethod("copyNumber", "CNSet", function(object){
154
-##	I <- isSnp(object)
155
-##	CA <- CA(object)
156
-##	CB <- CB(object)
157
-##	CN <- CA + CB
158
-##	##For nonpolymorphic probes, CA is the total copy number
159
-##	CN[!I, ] <- CA(object)[!I, ]
160
-##	CN
161
-##})
162
-
163
-
164 135
 setMethod("ellipse", "CNSet", function(x, copynumber, batch, ...){
165 136
 	ellipse.CNSet(x, copynumber, batch, ...)
166 137
 })
167 138
 
168
-##setMethod("ellipse", "CNSet", function(x, copynumber, ...){
169
-ellipse.CNSet <- function(x, copynumber, batch, ...){
170
-	if(nrow(x) > 1) stop("only 1 snp at a time")
171
-	##batch <- unique(x$batch)
172
-	if(missing(batch)){
173
-		stop("must specify batch")
174
-	}
175
-	if(length(batch) > 1) stop("batch variable not unique")
176
-	nuA <- getParam(x, "nuA", batch)
177
-	nuB <- getParam(x, "nuB", batch)
178
-	phiA <- getParam(x, "phiA", batch)
179
-	phiB <- getParam(x, "phiB", batch)
180
-	tau2A <- getParam(x, "tau2A", batch)
181
-	tau2B <- getParam(x, "tau2B", batch)
182
-	sig2A <- getParam(x, "sig2A", batch)
183
-	sig2B <- getParam(x, "sig2B", batch)
184
-	corrA.BB <- getParam(x, "corrA.BB", batch)
185
-	corrB.AA <- getParam(x, "corrB.AA", batch)
186
-	corr <- getParam(x, "corr", batch)
187
-	for(CN in copynumber){
188
-		for(CA in 0:CN){
189
-			CB <- CN-CA
190
-			A.scale <- sqrt(tau2A*(CA==0) + sig2A*(CA > 0))
191
-			B.scale <- sqrt(tau2B*(CB==0) + sig2B*(CB > 0))
192
-			scale <- c(A.scale, B.scale)
193
-			if(CA == 0 & CB > 0) rho <- corrA.BB
194
-			if(CA > 0 & CB == 0) rho <- corrB.AA
195
-			if(CA > 0 & CB > 0) rho <- corr
196
-			if(CA == 0 & CB == 0) rho <- 0
197
-			lines(ellipse(x=rho, centre=c(log2(nuA+CA*phiA),
198
-					     log2(nuB+CB*phiB)),
199
-				      scale=scale), ...)
200
-		}
201
-	}
202
-}
203
-
204
-
205 139
 setMethod("nu", c("CNSetLM", "character"), function(object, allele){
206 140
 	getValue <- function(allele){
207 141
 		switch(allele,