git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@38302 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -631,7 +631,7 @@ preprocessInfinium2 = function(XY, mixtureSampleSize=10^5, fitMixture=TRUE, eps= |
631 | 631 |
crlmmIllumina <- function(RG, XY, stripNorm=TRUE, useTarget=TRUE, |
632 | 632 |
row.names=TRUE, col.names=TRUE, |
633 | 633 |
probs=c(1/3, 1/3, 1/3), DF=6, SNRMin=5, gender=NULL, |
634 |
- seed=1, # save.it=FALSE, load.it=FALSE, intensityFile, |
|
634 |
+ seed=1, save.it=FALSE, load.it=FALSE, intensityFile, |
|
635 | 635 |
mixtureSampleSize=10^5, eps=0.1, verbose=TRUE, |
636 | 636 |
cdfName, sns, recallMin=10, recallRegMin=1000, |
637 | 637 |
returnParams=FALSE, badSNP=.7) { |
... | ... |
@@ -641,34 +641,34 @@ crlmmIllumina <- function(RG, XY, stripNorm=TRUE, useTarget=TRUE, |
641 | 641 |
else |
642 | 642 |
stop("Both RG and XY specified - please use one or the other") |
643 | 643 |
} |
644 |
-# if ((load.it | save.it) & missing(intensityFile)) |
|
645 |
-# stop("'intensityFile' is missing, and you chose either load.it or save.it") |
|
644 |
+ if ((load.it | save.it) & missing(intensityFile)) |
|
645 |
+ stop("'intensityFile' is missing, and you chose either load.it or save.it") |
|
646 | 646 |
if (missing(sns)) sns <- sampleNames(XY) #basename(filenames) |
647 |
-# if (!missing(intensityFile)) |
|
648 |
-# if (load.it & !file.exists(intensityFile)){ |
|
649 |
-# load.it <- FALSE |
|
650 |
-# message("File ", intensityFile, " does not exist.") |
|
651 |
-# message("Not loading it, but running SNPRMA from scratch.") |
|
652 |
-# } |
|
653 |
-# if (!load.it){ |
|
647 |
+ if (!missing(intensityFile)) |
|
648 |
+ if (load.it & !file.exists(intensityFile)){ |
|
649 |
+ load.it <- FALSE |
|
650 |
+ message("File ", intensityFile, " does not exist.") |
|
651 |
+ message("Not loading it, but running SNPRMA from scratch.") |
|
652 |
+ } |
|
653 |
+ if (!load.it){ |
|
654 | 654 |
# res <- snprma(filenames, fitMixture=TRUE, |
655 | 655 |
# mixtureSampleSize=mixtureSampleSize, verbose=verbose, |
656 | 656 |
# eps=eps, cdfName=cdfName, sns=sns) |
657 |
- res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose, |
|
657 |
+ res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose, |
|
658 | 658 |
seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget) |
659 |
-# if(save.it){ |
|
660 |
-# t0 <- proc.time() |
|
661 |
-# save(res, file=intensityFile) |
|
662 |
-# t0 <- proc.time()-t0 |
|
663 |
-# if (verbose) message("Used ", t0[3], " seconds to save ", intensityFile, ".") |
|
664 |
-# } |
|
665 |
-# }else{ |
|
666 |
-# if (verbose) message("Loading ", intensityFile, ".") |
|
667 |
-# obj <- load(intensityFile) |
|
668 |
-# if (verbose) message("Done.") |
|
669 |
-# if (obj != "res") |
|
670 |
-# stop("Object in ", intensityFile, " seems to be invalid.") |
|
671 |
-# } |
|
659 |
+ if(save.it){ |
|
660 |
+ t0 <- proc.time() |
|
661 |
+ save(res, file=intensityFile) |
|
662 |
+ t0 <- proc.time()-t0 |
|
663 |
+ if(verbose) message("Used ", t0[3], " seconds to save ", intensityFile, ".") |
|
664 |
+ } |
|
665 |
+ }else{ |
|
666 |
+ if(verbose) message("Loading ", intensityFile, ".") |
|
667 |
+ obj <- load(intensityFile) |
|
668 |
+ if(verbose) message("Done.") |
|
669 |
+ if(obj != "res") |
|
670 |
+ stop("Object in ", intensityFile, " seems to be invalid.") |
|
671 |
+ } |
|
672 | 672 |
if(row.names) row.names=res$gns else row.names=NULL |
673 | 673 |
if(col.names) col.names=res$sns else col.names=NULL |
674 | 674 |
|
... | ... |
@@ -680,13 +680,7 @@ crlmmIllumina <- function(RG, XY, stripNorm=TRUE, useTarget=TRUE, |
680 | 680 |
returnParams=returnParams, badSNP=badSNP, |
681 | 681 |
verbose=verbose) |
682 | 682 |
|
683 |
- res2[["A"]] <- res[["A"]] # added for copy number analysis |
|
684 |
- res2[["B"]] <- res[["B"]] # added for copy number analysis |
|
685 | 683 |
res2[["SNR"]] <- res[["SNR"]] |
686 | 684 |
res2[["SKW"]] <- res[["SKW"]] |
687 |
- res2[["zero"]] <- res[["zero"]] |
|
688 |
- rm(res) |
|
689 |
- gc() |
|
690 |
- # MR: FIXME - for consistency with crlmm, need to save results in a 'SnpSet' object |
|
691 |
- return(res2) |
|
685 |
+ return(res2) # return(list2SnpSet(res2, returnParams=returnParams)) |
|
692 | 686 |
} |
... | ... |
@@ -10,7 +10,8 @@ |
10 | 10 |
crlmmIllumina(RG, XY, stripNorm=TRUE, useTarget=TRUE, |
11 | 11 |
row.names=TRUE, col.names=TRUE, |
12 | 12 |
probs=c(1/3, 1/3, 1/3), DF=6, SNRMin=5, |
13 |
- gender=NULL, seed=1, mixtureSampleSize=10^5, |
|
13 |
+ gender=NULL, seed=1, save.it=FALSE, load.it=FALSE, |
|
14 |
+ intensityFile, mixtureSampleSize=10^5, |
|
14 | 15 |
eps=0.1, verbose=TRUE, cdfName, sns, recallMin=10, |
15 | 16 |
recallRegMin=1000, returnParams=FALSE, badSNP=0.7) |
16 | 17 |
} |
... | ... |
@@ -31,6 +32,10 @@ crlmmIllumina(RG, XY, stripNorm=TRUE, useTarget=TRUE, |
31 | 32 |
defining sex. (1 - male; 2 - female)} |
32 | 33 |
\item{seed}{'integer' scalar for random number generator (used to |
33 | 34 |
sample \code{mixtureSampleSize} SNPs for mixture model.} |
35 |
+ \item{save.it}{'logical'. Save preprocessed data?} |
|
36 |
+ \item{load.it}{'logical'. Load preprocessed data to speed up analysis?} |
|
37 |
+ \item{intensityFile}{'character' with filename of preprocessed data to |
|
38 |
+ be saved/loaded.} |
|
34 | 39 |
\item{mixtureSampleSize}{'integer'. The number of SNP's to be used |
35 | 40 |
when fitting the mixture model.} |
36 | 41 |
\item{eps}{Minimum change for mixture model.} |