Browse code

Make API for crlmmGT2 the same as crlmmGT. Define snpNames method for 'character'.

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

Rob Scharp authored on 01/10/2011 04:50:07
Showing 4 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.11.37
4
+Version: 1.11.38
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>
... ...
@@ -29,7 +29,7 @@ importMethodsFrom(oligoClasses, allele, calls, "calls<-", confs,
29 29
 		  "A<-", "B<-", open, close, flags,
30 30
 		  openff, closeff,
31 31
 		  batchStatistics, "batchStatistics<-", updateObject,
32
-		  order, checkOrder)
32
+		  order, checkOrder, snpNames)
33 33
 importFrom(oligoClasses, chromosome2integer, celfileDate, list.celfiles,
34 34
            copyNumber, initializeBigMatrix, initializeBigVector, isPackageLoaded)
35 35
 
... ...
@@ -9,6 +9,18 @@ getProtocolData.Affy <- function(filenames){
9 9
 			                           row.names=colnames(scanDates)))
10 10
 	return(protocoldata)
11 11
 }
12
+
13
+setMethod("snpNames", signature(object="character"),
14
+	  function(object){
15
+		  nm <- grep("Crlmm", object)
16
+		  if(length(nm)==0){
17
+			  pkgname <- paste(object, "Crlmm", sep="")
18
+		  } else pkgname <- object
19
+		  loader("preprocStuff.rda", .crlmmPkgEnv, object)
20
+		  gns <- getVarInEnv("gns")
21
+		  return(gns)
22
+	  })
23
+
12 24
 getFeatureData <- function(cdfName, copynumber=FALSE){
13 25
 	pkgname <- getCrlmmAnnotationName(cdfName)
14 26
 	if(!require(pkgname, character.only=TRUE)){
... ...
@@ -2,7 +2,7 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
2 2
                      col.names=NULL, probs=c(1/3, 1/3, 1/3), DF=6,
3 3
                      SNRMin=5, recallMin=10, recallRegMin=1000,
4 4
                      gender=NULL, desctrucitve=FALSE, verbose=TRUE,
5
-                     returnParams=FALSE, badSNP=.7, snp.names){
5
+                     returnParams=FALSE, badSNP=.7){
6 6
 	pkgname <- getCrlmmAnnotationName(cdfName)
7 7
 	stopifnot(require(pkgname, character.only=TRUE, quietly=!verbose))
8 8
 	open(SNR)
... ...
@@ -18,11 +18,14 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
18 18
 		stopifnot(nrow(A) == length(gns))
19 19
 		index <- seq(length=nrow(A))
20 20
 	}
21
-	if(!missing(snp.names)){
22
-		stopifnot(!is.null(rownames(A)))
23
-		##verify that A has only snps.  otherwise, calling function must pass rownames
24
-		index <- match(snp.names, rownames(A))
25
-	}
21
+	snp.names <- snpNames(pkgname)
22
+	stopifnot(!is.null(rownames(A)))
23
+	index <- match(snp.names, rownames(A))
24
+##	if(!missing(snp.names)){
25
+##
26
+##		##verify that A has only snps.  otherwise, calling function must pass rownames
27
+##		index <- match(snp.names, rownames(A))
28
+##	}
26 29
 	snpBatches <- splitIndicesByLength(index, ocProbesets())
27 30
 	NR <- length(unlist(snpBatches))
28 31
 	if(verbose) message("Calling ", NR, " SNPs for recalibration... ")