git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@37667 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: crlmm |
2 | 2 |
Type: Package |
3 | 3 |
Title: Genotype Calling via CRLMM Algorithm |
4 |
-Version: 1.0.36 |
|
4 |
+Version: 1.0.37 |
|
5 | 5 |
Date: 2008-12-28 |
6 | 6 |
Author: Rafael A Irizarry |
7 | 7 |
Maintainer: Benilton S Carvalho <bcarvalh@jhsph.edu> |
... | ... |
@@ -17,5 +17,7 @@ Collate: crlmmGT.R |
17 | 17 |
zzz.R |
18 | 18 |
crlmmGTnm.R |
19 | 19 |
crlmmnm.R |
20 |
+ AllClasses.R |
|
21 |
+ Methods.R |
|
20 | 22 |
functions.R |
21 | 23 |
LazyLoad: yes |
... | ... |
@@ -1,9 +1,11 @@ |
1 | 1 |
useDynLib("crlmm", .registration=TRUE) |
2 | 2 |
export("crlmm", "list.celfiles", "computeCnBatch") |
3 |
+exportMethods("list2crlmmSet", "calls", "confs") |
|
4 |
+exportClasses("crlmmSet") |
|
3 | 5 |
importFrom(affyio, read.celfile.header, read.celfile) |
4 | 6 |
importFrom(preprocessCore, normalize.quantiles.use.target) |
5 | 7 |
importFrom(utils, data, packageDescription, setTxtProgressBar, txtProgressBar) |
6 | 8 |
importFrom(stats, coef, cov, dnorm, kmeans, lm, mad, median, quantile, sd) |
7 |
-##RS |
|
8 | 9 |
importFrom(Biobase, rowMedians) |
9 | 10 |
importFrom(genefilter, rowSds) |
11 |
+ |
0 | 3 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,27 @@ |
1 |
+## Methods for crlmm |
|
2 |
+ |
|
3 |
+setGeneric("calls", function(x) standardGeneric("calls")) |
|
4 |
+setMethod("calls", "crlmmSet", function(x) assayData(x)$calls) |
|
5 |
+ |
|
6 |
+setGeneric("confs", function(x) standardGeneric("confs")) |
|
7 |
+setMethod("confs", "crlmmSet", function(x) assayData(x)$confs) |
|
8 |
+ |
|
9 |
+setGeneric("list2crlmmSet", function(x) standardGeneric("list2crlmmSet")) |
|
10 |
+setMethod("list2crlmmSet", "list", |
|
11 |
+ function(x){ |
|
12 |
+ pd <- data.frame(SNR=x[["SNR"]], |
|
13 |
+ row.names=colnames(x[["calls"]])) |
|
14 |
+ pdv <- data.frame(labelDescription=c("Signal-to-noise Ratio"), |
|
15 |
+ row.names=c("SNR")) |
|
16 |
+ fd <- data.frame(SNPQC=x[["SNPQC"]], |
|
17 |
+ row.names=rownames(x[["calls"]])) |
|
18 |
+ fdv <- data.frame(labelDescription=c("SNP Quality Score"), |
|
19 |
+ row.names=c("SNPQC")) |
|
20 |
+ new("crlmmSet", |
|
21 |
+ assayData=assayDataNew("lockedEnvironment", |
|
22 |
+ calls=x[["calls"]], confs=x[["confs"]]), |
|
23 |
+ phenoData=new("AnnotatedDataFrame", |
|
24 |
+ data=pd, varMetadata=pdv), |
|
25 |
+ featureData=new("AnnotatedDataFrame", |
|
26 |
+ data=fd, varMetadata=fdv)) |
|
27 |
+ }) |
... | ... |
@@ -158,10 +158,14 @@ crlmmGT <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL, |
158 | 158 |
## tmp4batchQC <- DD[autosomeIndex,]/(params[["N"]][autosomeIndex,]+1) |
159 | 159 |
## tmpSnpQc <- dev[autosomeIndex] |
160 | 160 |
## SS <- cov(tmp4batchQC[tmpSnpQc < badSNP,]) |
161 |
- DD <- sweep(GG[snps2keep, ], 2, colMeans(DD[snps2keep, ])) |
|
161 |
+ tmp4batchQC <- DD[snps2keep,]/(params[["N"]][snps2keep,]+1) |
|
162 | 162 |
tmpSnpQc <- dev[snps2keep] |
163 |
- SS <- cov(DD[tmpSnpQc < badSNP, ]) |
|
164 |
- batchQC <- mean(diag(SS)) |
|
163 |
+ SS <- cov(DD[snps2keep,]) |
|
164 |
+## DD <- sweep(GG[snps2keep, ], 2, colMeans(DD[snps2keep, ])) |
|
165 |
+## tmpSnpQc <- dev[snps2keep] |
|
166 |
+## SS <- cov(DD[tmpSnpQc < badSNP, ]) |
|
167 |
+ batchQC <- sqrt(sum(diag(cov(tmp4batchQC[tmpSnpQc < badSNP,]))))*sum(params[["N"]][snps2keep[1],]) |
|
168 |
+## batchQC <- mean(diag(SS)) |
|
165 | 169 |
}else{ |
166 | 170 |
SS <- matrix(0, 3, 3) |
167 | 171 |
batchQC <- Inf |
... | ... |
@@ -169,9 +173,9 @@ crlmmGT <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL, |
169 | 173 |
|
170 | 174 |
if(verbose) message("Done.") |
171 | 175 |
if (returnParams){ |
172 |
- return(list(calls=A, confs=B, SNPQC=dev, batchQC=batchQC, params=params, DD=DD, covSS=SS)) |
|
176 |
+ return(list(calls=A, confs=B, SNPQC=dev, batchQC=batchQC, params=params, DD=DD, covDD=SS)) |
|
173 | 177 |
}else{ |
174 |
- return(list(calls=A, confs=B, SNPQC=dev, batchQC=batchQC, DD=DD, covSS=SS)) |
|
178 |
+ return(list(calls=A, confs=B, SNPQC=dev, batchQC=batchQC, DD=DD, covDD=SS)) |
|
175 | 179 |
} |
176 | 180 |
} |
177 | 181 |
|
... | ... |
@@ -225,7 +229,7 @@ gtypeCallerR2 <- function(A, B, fIndex, mIndex, theCenters, theScales, |
225 | 229 |
|
226 | 230 |
################## |
227 | 231 |
################## |
228 |
-### THIS IS TEMPORARY NOT OFFICIALLY USED |
|
232 |
+### THIS IS TEMPORARY AND NOT OFFICIALLY USED |
|
229 | 233 |
################## |
230 | 234 |
#################### |
231 | 235 |
crlmmGTTNoN <- function(A, B, SNR, mixtureParams, cdfName, |