Browse code

Cleaning up... importing isPackageLoaded() from oligoClasses

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

Benilton Carvalho authored on 20/01/2011 18:33:39
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.9.10
4
+Version: 1.9.2
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>
... ...
@@ -32,7 +32,7 @@ importMethodsFrom(oligoClasses, allele, calls, "calls<-", confs,
32 32
 		  "A<-", "B<-", open, close, flags,
33 33
 		  batchStatistics, "batchStatistics<-", updateObject)
34 34
 importFrom(oligoClasses, chromosome2integer, celfileDate, list.celfiles,
35
-           copyNumber, initializeBigMatrix, initializeBigVector)
35
+           copyNumber, initializeBigMatrix, initializeBigVector, isPackageLoaded)
36 36
 
37 37
 
38 38
 importFrom(graphics, abline, axis, layout, legend, mtext, par, plot,
... ...
@@ -94,9 +94,6 @@ list2SnpSet <- function(x, returnParams=FALSE){
94 94
                           "Center AA", "Center AB", "Center BB",
95 95
                           "Scale AA", "Scale AB", "Scale BB",
96 96
                           "N AA", "N AB", "N BB"),
97
-#                          "Shift in parameters AA",
98
-#                          "Shift in parameters AB",
99
-#                          "Shift in parameters BB"),
100 97
                         row.names=c(
101 98
                           "SNPQC",
102 99
                           "cAA", "cAB", "cBB",
... ...
@@ -142,8 +139,7 @@ loader <- function(theFile, envir, pkgname){
142 139
 
143 140
 celDates <- function(celfiles){
144 141
 	if(!all(file.exists(celfiles))) stop("1 or more cel file does not exist")
145
-	celdates <- vector("character", length(celfiles))
146
-	celtimes <- vector("character", length(celfiles))
142
+	celdates <- celtimes <- vector("character", length(celfiles))
147 143
 	for(i in seq(along=celfiles)){
148 144
 		if(i %% 100 == 0) cat(".")
149 145
 		tmp <- read.celfile.header(celfiles[i], info="full")$DatHeader
... ...
@@ -172,19 +168,12 @@ validCdfNames <- function(){
172 168
           "humanimmuno12v1b")
173 169
 }
174 170
 isValidCdfName <- function(cdfName){
175
-	chipList <- validCdfNames()
176
-	result <- cdfName %in% chipList	
177
-	if(!(result)){
178
-		warning("cdfName must be one of the following: ",
179
-			chipList)
180
-	}
181
-	return(result)
182
-}
183
-
184
-isPackageLoaded <- function(pkg){
185
-	stopifnot(is.character(pkg))
186
-	pkg <- paste("package:", pkg, sep="")
187
-	pkg %in% search()
171
+    stopifnot(is.character(cdfName))
172
+    result <- cdfName %in% validCdfNames()
173
+    if (!result)
174
+        warning("cdfName must be one of the following: ",
175
+                chipList)
176
+    return(result)
188 177
 }
189 178
 
190 179
 paramNames <- function(){