git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@48943 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -2633,7 +2633,7 @@ thresholdModelParams <- function(object, cnOptions){ |
2633 | 2633 |
return(object) |
2634 | 2634 |
} |
2635 | 2635 |
|
2636 |
-computeCopynumber.CNSet <- function(object, cnOptions){ |
|
2636 |
+cnCNSet <- function(object, cnOptions){ |
|
2637 | 2637 |
PLATE <- unique(batch(object)) |
2638 | 2638 |
verbose <- cnOptions$verbose |
2639 | 2639 |
tmp.objects <- instantiateObjects(object, cnOptions) |
... | ... |
@@ -2695,9 +2695,9 @@ computeCopynumber.CNSet <- function(object, cnOptions){ |
2695 | 2695 |
object <- pr(object, "corrA.BB", PLATE, getParam(object, "corrA.BB", PLATE)) |
2696 | 2696 |
object <- pr(object, "corrB.AA", PLATE, getParam(object, "corrB.AA", PLATE)) |
2697 | 2697 |
##object <- object[order(chromosome(object), position(object)), ] |
2698 |
- if(cnOptions[["thresholdCopynumber"]]){ |
|
2699 |
- object <- thresholdCopynumber(object) |
|
2700 |
- } |
|
2698 |
+## if(cnOptions[["thresholdCopynumber"]]){ |
|
2699 |
+## object <- thresholdCopynumber(object) |
|
2700 |
+## } |
|
2701 | 2701 |
return(object) |
2702 | 2702 |
} |
2703 | 2703 |
|
... | ... |
@@ -96,11 +96,11 @@ setMethod("computeCopynumber", "CNSet", |
96 | 96 |
if(bias.adj & all(is.na(fData(object)$nuA_1))){ |
97 | 97 |
cnOptions[["bias.adj"]] <- FALSE |
98 | 98 |
} |
99 |
- object <- computeCopynumber.CNSet(object, cnOptions) |
|
99 |
+ object <- cnCNSet(object, cnOptions) |
|
100 | 100 |
if(bias.adj & !cnOptions[["bias.adj"]]){ |
101 | 101 |
## Do a second iteration with bias adjustment |
102 | 102 |
cnOptions[["bias.adj"]] <- TRUE |
103 |
- object <- computeCopynumber.CNSet(object, cnOptions) |
|
103 |
+ object <- cnCNSet(object, cnOptions) |
|
104 | 104 |
} |
105 | 105 |
object |
106 | 106 |
}) |
... | ... |
@@ -212,9 +212,9 @@ getParam.SnpSuperSet <- function(object, name, batch){ |
212 | 212 |
## saved.objects |
213 | 213 |
##}) |
214 | 214 |
|
215 |
-setMethod("computeCopynumber", "SnpSuperSet", |
|
216 |
- function(object, cnOptions){ |
|
217 |
- computeCopynumber.SnpSuperSet(object, cnOptions) |
|
218 |
- }) |
|
215 |
+##setMethod("computeCopynumber", "SnpSuperSet", |
|
216 |
+## function(object, cnOptions){ |
|
217 |
+## computeCopynumber.SnpSuperSet(object, cnOptions) |
|
218 |
+## }) |
|
219 | 219 |
|
220 | 220 |
|
... | ... |
@@ -147,7 +147,7 @@ cnSet.assayData_matrix <- checkExists("cnSet.assayData_matrix", |
147 | 147 |
object=gtSet.assayData_matrix, |
148 | 148 |
chromosome=22) |
149 | 149 |
##Rprof(interval=0.1) |
150 |
-##obj <- crlmmCopynumber(gtSet.assayData_matrix, chromosome=22) |
|
150 |
+obj <- crlmmCopynumber(gtSet.assayData_matrix, chromosome=23) |
|
151 | 151 |
##Rprof(NULL) |
152 | 152 |
if(file.exists(file.path(outdir, "gtSet.assayData_matrix.rda"))) |
153 | 153 |
unlink(file.path(outdir, "gtSet.assayData_matrix.rda")) |
... | ... |
@@ -376,20 +376,23 @@ genotypeConf <- integerScoreToProbability(snpCallProbability(x)[snp.index[1:10], |
376 | 376 |
Allele-specific copy number at polymorphic loci: |
377 | 377 |
<<ca>>= |
378 | 378 |
##ca <- CA(x[snp.index, ])/100 |
379 |
-snp.index <- which(isSnp(obj)) |
|
380 |
-ca <- CA(obj, i=snp.index) |
|
379 |
+snp.index <- which(isSnp(x)) |
|
380 |
+ca <- CA(x, i=snp.index) |
|
381 | 381 |
##or |
382 |
-ca <- ACN(obj, "A", i=snp.index) |
|
382 |
+ca <- ACN(x, "A", i=snp.index) |
|
383 |
+cb <- CB(x, i=snp.index) |
|
384 |
+ct <- ca+cb |
|
383 | 385 |
@ |
384 | 386 |
|
385 | 387 |
Total copy number at nonpolymorphic loci: |
386 | 388 |
<<ca>>= |
387 |
-cn.nonpolymorphic <- CA(x[np.index, ])/100 |
|
389 |
+cn.nonpolymorphic <- CA(obj, i=which(!isSnp(obj))) |
|
388 | 390 |
@ |
389 | 391 |
|
390 | 392 |
Total copy number at both polymorphic and nonpolymorphic loci: |
391 | 393 |
<<totalCopynumber>>= |
392 |
-cn <- copyNumber(x) |
|
394 |
+##cn <- copyNumber(x) |
|
395 |
+cn <- totalCopyNumber(x, sample(1:nrow(x), 1e4), 1:5) |
|
393 | 396 |
apply(cn, 2, median, na.rm=TRUE) |
394 | 397 |
@ |
395 | 398 |
|