git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@52821 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -620,13 +620,13 @@ summarizeXGenotypes <- function(marker.index, |
620 | 620 |
DF.PRIOR, |
621 | 621 |
gender="male", ...){ |
622 | 622 |
if(gender == "male"){ |
623 |
- sample.index <- which(gender==1) |
|
624 |
- } else sample.index <- which(gender==2) |
|
623 |
+ sample.index <- which(object$gender==1) |
|
624 |
+ } else sample.index <- which(object$gender==2) |
|
625 | 625 |
nr <- length(marker.index) |
626 | 626 |
nc <- length(batchNames(object)) |
627 | 627 |
## NN.Mlist <- imputed.medianA <- imputed.medianB <- shrink.madA <- shrink.madB <- vector("list", nc) |
628 | 628 |
NN.Mlist <- medianA <- medianB <- shrink.madA <- shrink.madB <- vector("list", nc) |
629 |
- gender <- object$gender |
|
629 |
+ ##gender <- object$gender |
|
630 | 630 |
GG <- as.matrix(calls(object)[marker.index, sample.index]) |
631 | 631 |
CP <- as.matrix(snpCallProbability(object)[marker.index, sample.index]) |
632 | 632 |
AA <- as.matrix(A(object)[marker.index, sample.index]) |
... | ... |
@@ -682,7 +682,7 @@ summarizeXGenotypes <- function(marker.index, |
682 | 682 |
madB <- cbind(statsB.AA[, 2], ##statsB.AB[, 2], |
683 | 683 |
statsB.BB[, 2]) |
684 | 684 |
NN <- cbind(N.AA, N.BB) |
685 |
- rm(statsA.AA, statsA.BB, statsB.AA, statsB.AB, statsB.BB) |
|
685 |
+ rm(statsA.AA, statsA.BB, statsB.AA, statsB.BB) |
|
686 | 686 |
} else { |
687 | 687 |
medianA[[k]] <- cbind(statsA.AA[, 1], statsA.AB[, 1], |
688 | 688 |
statsA.BB[, 1]) |
... | ... |
@@ -702,12 +702,11 @@ summarizeXGenotypes <- function(marker.index, |
702 | 702 |
## SNPs that we'll use for imputing location/scale of unobserved genotypes |
703 | 703 |
##--------------------------------------------------------------------------- |
704 | 704 |
index.complete <- indexComplete(NN, medianA[[k]], medianB[[k]], MIN.OBS) |
705 |
- |
|
706 | 705 |
##--------------------------------------------------------------------------- |
707 | 706 |
## Impute sufficient statistics for unobserved genotypes (plate-specific) |
708 | 707 |
##--------------------------------------------------------------------------- |
709 | 708 |
if(gender=="male"){ |
710 |
- res <- imputeCenterX(medianA[[k]], medianB[[k]], NN.M, index.complete, MIN.OBS) |
|
709 |
+ res <- imputeCenterX(medianA[[k]], medianB[[k]], NN, index.complete, MIN.OBS) |
|
711 | 710 |
} else { |
712 | 711 |
unobservedAA <- NN[, 1] < MIN.OBS |
713 | 712 |
unobservedAB <- NN[, 2] < MIN.OBS |