git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@52824 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1302,22 +1302,15 @@ ellipseCenters <- function(object, index, allele, batch, log.it=TRUE){ |
1302 | 1302 |
|
1303 | 1303 |
|
1304 | 1304 |
shrinkSummary <- function(object, |
1305 |
- type=c("SNP", "X.SNP"), ##"X.snps", "X.nps"), |
|
1305 |
+ type="SNP", |
|
1306 | 1306 |
MIN.OBS=1, |
1307 | 1307 |
MIN.SAMPLES=10, |
1308 | 1308 |
DF.PRIOR=50, |
1309 | 1309 |
verbose=TRUE, |
1310 | 1310 |
marker.index, |
1311 | 1311 |
is.lds){ |
1312 |
- stopifnot(type[[1]] %in% c("SNP", "X.SNP")) |
|
1313 |
- if(type[[1]] == "X.SNP"){ |
|
1314 |
- gender <- object$gender |
|
1315 |
- if(sum(gender == 2) < 3) { |
|
1316 |
- message("too few females to estimate within genotype summary statistics on CHR X") |
|
1317 |
- return(object) |
|
1318 |
- } |
|
1319 |
- CHR.X <- TRUE |
|
1320 |
- } else CHR.X <- FALSE |
|
1312 |
+ stopifnot(type[[1]] != "SNP") |
|
1313 |
+ CHR.X <- FALSE ## this is no longer needed |
|
1321 | 1314 |
if(missing(marker.index)){ |
1322 | 1315 |
batch <- batch(object) |
1323 | 1316 |
is.snp <- isSnp(object) |
... | ... |
@@ -1641,7 +1634,6 @@ crlmmCopynumber <- function(object, |
1641 | 1634 |
X.NP="chromosome X nonpolymorphic markers") |
1642 | 1635 |
} |
1643 | 1636 |
if(verbose) message("Computing summary statistics of the genotype clusters for each batch") |
1644 |
-## for(i in seq_along(type)){ |
|
1645 | 1637 |
for(i in c(1, 2, 4)){ ## do not do X.SNP. Do this during fit.lm3 |
1646 | 1638 |
marker.type <- type[i] |
1647 | 1639 |
if(verbose) message(paste("...", mylabel(marker.type))) |
... | ... |
@@ -1659,17 +1651,13 @@ crlmmCopynumber <- function(object, |
1659 | 1651 |
is.lds=is.lds) |
1660 | 1652 |
} |
1661 | 1653 |
if(verbose) message("Imputing unobserved genotype medians and shrinking the variances (within-batch, across loci) ")##SNPs only |
1662 |
-## for(i in c(1, 2, 4)){ |
|
1663 |
-## marker.type <- type[i] |
|
1664 |
-## if(!marker.type %in% c("SNP", "X.SNP")) next() |
|
1665 |
-## message(paste("...", mylabel(marker.type))) |
|
1666 | 1654 |
marker.index <- whichMarkers("SNP", is.snp, |
1667 | 1655 |
is.autosome, is.annotated, is.X) |
1668 | 1656 |
object <- shrinkSummary(object=object, |
1669 | 1657 |
MIN.OBS=MIN.OBS, |
1670 | 1658 |
MIN.SAMPLES=MIN.SAMPLES, |
1671 | 1659 |
DF.PRIOR=DF.PRIOR, |
1672 |
- type=marker.type, |
|
1660 |
+ type="SNP", |
|
1673 | 1661 |
verbose=verbose, |
1674 | 1662 |
marker.index=marker.index, |
1675 | 1663 |
is.lds=is.lds) |