Browse code

Removed export of totalCopyNumber from namespace and totalCopyNumber method from methods-CNSet

removed trace call in illumina copynumber vignette

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

Rob Scharp authored on 27/07/2010 03:01:41
Showing 4 changed files

... ...
@@ -55,8 +55,8 @@ importFrom(ellipse, ellipse)
55 55
 
56 56
 importFrom(ff, ffdf)
57 57
 
58
-exportClasses(CNSetLM, list_or_ffdf, ffdf)
59
-exportMethods(open, "[", show, lM, copyNumber, totalCopyNumber)
58
+exportClasses(CNSetLM, ffdf, list)
59
+exportMethods(open, "[", show, lM, copyNumber) ##, totalCopyNumber)
60 60
 export(crlmm, 
61 61
        crlmmCopynumber, 
62 62
        crlmmIllumina, 
... ...
@@ -236,7 +236,7 @@ readIdatFiles2 <- function(sampleSheet=NULL,
236 236
 	       stop("Cannot find .idat files")
237 237
        if(length(grnfiles)!=length(redfiles))
238 238
 	       stop("Cannot find matching .idat files")
239
-       if(path[1] != "."){
239
+       if(path[1] != "." & path[1] != ""){
240 240
 	       grnidats = file.path(path, grnfiles)
241 241
 	       redidats = file.path(path, redfiles)
242 242
        }  else {
... ...
@@ -114,34 +114,6 @@ setMethod("copyNumber", "CNSet", function(object){
114 114
 	CN
115 115
 })
116 116
 
117
-setMethod("totalCopyNumber", "CNSet", function(object, i, j){
118
-	if(missing(i) & missing(j)){
119
-		if(inherits(CA(object), "ff") | inherits(CA(object), "ffdf")) stop("Must specify i and/or j for ff objects")
120
-	}
121
-	if(missing(i) & !missing(j)){
122
-		snp.index <- which(isSnp(object))	
123
-		cn.total <- as.matrix(CA(cnSet)[, j])
124
-		cb <- as.matrix(CB(cnSet)[snp.index, j]	)
125
-		cn.total[snp.index, ] <- cn.total[snp.index, ] + cb		
126
-	}
127
-	if(!missing(i) & missing(j)){
128
-		snp.index <- intersect(which(isSnp(object)), i)
129
-		cn.total <- as.matrix(CA(cnSet)[i, ])
130
-		cb <- as.matrix(CB(cnSet)[snp.index, ])	
131
-		cn.total[snp.index, ] <- cn.total[snp.index, ] + cb				
132
-	}
133
-	if(!missing(i) & !missing(j)){
134
-		snp.index <- intersect(which(isSnp(object)), i)		
135
-		cn.total <- as.matrix(CA(cnSet)[i, j])	
136
-		cb <- as.matrix(CB(cnSet)[snp.index, j])
137
-		cn.total[snp.index, ] <- cn.total[snp.index, ] + cb
138
-	}
139
-	cn.total <- cn.total/100
140
-	dimnames(cn.total) <- NULL
141
-	return(cn.total)
142
-})
143
-
144
-
145 117
 setMethod("ellipse", "CNSet", function(x, copynumber, batch, ...){
146 118
 	ellipse.CNSet(x, copynumber, batch, ...)
147 119
 })
... ...
@@ -299,7 +299,7 @@ The following helper function can facilitate access to the total copy
299 299
 number.
300 300
 
301 301
 <<copyNumberHelper>>=
302
-trace(totalCopyNumber, browser, signature="CNSet")
302
+##trace(totalCopyNumber, browser, signature="CNSet")
303 303
 cn.total2 <- totalCopyNumber(cnSet, i=which(chromosome(cnSet)==1), j=1:20)
304 304
 @ 
305 305