git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@38580 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: crlmm |
2 | 2 |
Type: Package |
3 | 3 |
Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for SNP 5.0 and 6.0 arrays. |
4 |
-Version: 1.0.76 |
|
4 |
+Version: 1.0.77 |
|
5 | 5 |
Date: 2008-12-30 |
6 | 6 |
Author: Rafael A Irizarry, Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
7 | 7 |
Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU> |
... | ... |
@@ -128,17 +128,11 @@ celDates <- function(celfiles){ |
128 | 128 |
} |
129 | 129 |
|
130 | 130 |
cnrma <- function(filenames, cdfName="genomewidesnp6", sns, seed=1, verbose=FALSE){ |
131 |
- if(cdfName != "genomewidesnp6") stop("Only genomewidesnp6 supported at this time") |
|
132 |
- ## BC: 03/14/09 |
|
133 |
- ## getting pkgname from cdfName, in the future this might be useful |
|
134 |
- ## as the method might be implemented for other platforms |
|
135 | 131 |
pkgname <- getCrlmmAnnotationName(cdfName) |
136 | 132 |
require(pkgname, character.only=TRUE) || stop("Package ", pkgname, " not available") |
137 | 133 |
if (missing(sns)) sns <- basename(filenames) |
138 |
- ## Loading data in .crlmmPkgEnv and extracting from there |
|
139 | 134 |
loader("npProbesFid.rda", .crlmmPkgEnv, pkgname) |
140 |
-## data("npProbesFid", package=pkgname, envir=.crlmmPkgEnv) |
|
141 |
- fid <- getVarInEnv("fid") |
|
135 |
+ fid <- getVarInEnv("npProbesFid") |
|
142 | 136 |
set.seed(seed) |
143 | 137 |
idx2 <- sample(length(fid), 10^5) ##for skewness. no need to do everything |
144 | 138 |
SKW <- vector("numeric", length(filenames)) |
... | ... |
@@ -148,9 +142,7 @@ cnrma <- function(filenames, cdfName="genomewidesnp6", sns, seed=1, verbose=FALS |
148 | 142 |
message("Processing ", length(filenames), " files.") |
149 | 143 |
if (getRversion() > '2.7.0') pb <- txtProgressBar(min=0, max=length(filenames), style=3) |
150 | 144 |
} |
151 |
- ##load reference distribution obtained from hapmap |
|
152 | 145 |
loader("1m_reference_cn.rda", .crlmmPkgEnv, pkgname) |
153 |
-## data(list="1m_reference_cn", package="genomewidesnp6Crlmm", envir=.crlmmPkgEnv) |
|
154 | 146 |
reference <- getVarInEnv("reference") |
155 | 147 |
for(i in seq(along=filenames)){ |
156 | 148 |
y <- as.matrix(read.celfile(filenames[i], intensity.means.only=TRUE)[["INTENSITY"]][["MEAN"]][fid]) |