Browse code

Merge branch 'collab'

* collab:
remove getCluster() calls and replace with parStatus()
update man pages for crlmm and genotype.Illumina with respect to the setup for parallelization
add neededPkgs argument to ocLapply calls in crlmmGT2
bump dependency on oligoClasses
Update R/crlmm-illumina.R
contructInf, preprocessInf and genotypeInf no longer exported

git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@64211 bc3139a8-67e5-0310-9ffc-ced21a209358

Rob Scharp authored on 21/03/2012 02:52:50
Showing 8 changed files

... ...
@@ -1,7 +1,7 @@
1 1
 Package: crlmm
2 2
 Type: Package
3 3
 Title: Genotype Calling (CRLMM) and Copy Number Analysis tool for Affymetrix SNP 5.0 and 6.0 and Illumina arrays.
4
-Version: 1.13.11
4
+Version: 1.13.12
5 5
 Date: 2010-12-10
6 6
 Author: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.edu.au>, Ingo Ruczinski <iruczins@jhsph.edu>, Rafael A Irizarry
7 7
 Maintainer: Benilton S Carvalho <Benilton.Carvalho@cancer.org.uk>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
... ...
@@ -10,7 +10,7 @@ License: Artistic-2.0
10 10
 Depends: R (>= 2.13.0),
11 11
          methods,
12 12
          Biobase (>= 2.15.0),
13
-         oligoClasses (>= 1.17.29)
13
+         oligoClasses (>= 1.17.34)
14 14
 Imports: affyio (>= 1.19.2),
15 15
          ellipse,
16 16
          genefilter (>= 1.33.0),
... ...
@@ -75,4 +75,4 @@ export(crlmm,
75 75
        genotype.Illumina,
76 76
        crlmmCopynumber2, crlmmCopynumberLD, crlmmCopynumber)
77 77
 export(genotypes, totalCopynumber, rawCopynumber, xyplot)
78
-export(ABpanel, constructInf, preprocessInf, genotypeInf, validCEL, celDates)
78
+export(ABpanel, validCEL, celDates)
... ...
@@ -1541,7 +1541,7 @@ shrinkSummary <- function(object,
1541 1541
 	}
1542 1542
 	if(is.lds){
1543 1543
 		##index.list <- splitIndicesByLength(marker.index, ocProbesets())
1544
-		if(!is.null(getCluster()) & isPackageLoaded("snow")){
1544
+		if(parStatus()){
1545 1545
 			index.list <- splitIndicesByNode(marker.index)
1546 1546
 		} else index.list <- splitIndicesByLength(marker.index, ocProbesets())
1547 1547
 		ocLapply(seq(along=index.list),
... ...
@@ -1595,7 +1595,7 @@ genotypeSummary <- function(object,
1595 1595
 	FUN <- get(myf)
1596 1596
 	if(is.lds){
1597 1597
 		##index.list <- splitIndicesByLength(marker.index, ocProbesets())
1598
-		if(!is.null(getCluster()) & isPackageLoaded("snow")){
1598
+		if(parStatus()){
1599 1599
 			index.list <- splitIndicesByNode(marker.index)
1600 1600
 		} else index.list <- splitIndicesByLength(marker.index, ocProbesets())
1601 1601
 		ocLapply(seq(along=index.list),
... ...
@@ -2116,7 +2116,7 @@ estimateCnParameters <- function(object,
2116 2116
 	myfun <- lmFxn(type[[1]])
2117 2117
 	FUN <- get(myfun)
2118 2118
 	if(is.lds){
2119
-		if(!is.null(getCluster()) & isPackageLoaded("snow")){
2119
+		if(parStatus()){
2120 2120
 			index.list <- splitIndicesByNode(marker.index)
2121 2121
 		} else index.list <- splitIndicesByLength(marker.index, ocProbesets())
2122 2122
 		ocLapply(seq(along=index.list),
... ...
@@ -1267,7 +1267,7 @@ preprocessInf <- function(cnSet,
1267 1267
 	sampleBatches <- splitIndicesByNode(seq(length=ncol(cnSet)))
1268 1268
 	mixtureParams = initializeBigMatrix("crlmmMixt-", 4, narrays, "double")
1269 1269
 	ocLapply(seq_along(sampleBatches),
1270
-		 processIDAT,
1270
+		 crlmm:::processIDAT,
1271 1271
 		 sampleBatches=sampleBatches,
1272 1272
 		 sampleSheet=sampleSheet,
1273 1273
 		 arrayNames=arrayNames,
... ...
@@ -99,7 +99,8 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
99 99
 				   mIndex=mIndex, params=params,
100 100
 				   cIndexes=cIndexes, SMEDIAN=SMEDIAN,
101 101
 				   theKnots=theKnots, DF=DF, probs=probs,
102
-				   batchSize=ocProbesets())
102
+				   batchSize=ocProbesets(),
103
+				   neededPkgs="crlmm")
103 104
 	newparams <- vector("list", 3)
104 105
 	names(newparams) <- c("centers", "scales", "N")
105 106
 	newparams[["centers"]] <- do.call("rbind", lapply(newparamsBatch, "[[", 1))
... ...
@@ -227,7 +228,8 @@ crlmmGT2 <- function(A, B, SNR, mixtureParams, cdfName, row.names=NULL,
227 228
 		 A=A, B=B, mixtureParams=mixtureParams, fIndex=fIndex,
228 229
 		 mIndex=mIndex, params=params, cIndexes=cIndexes,
229 230
 		 SMEDIAN=SMEDIAN, theKnots=theKnots, DF=DF, probs=probs,
230
-		 regionInfo=regionInfo, batchSize=ocProbesets())
231
+		 regionInfo=regionInfo, batchSize=ocProbesets(),
232
+		 neededPkgs="crlmm")
231 233
 	##  END MOVE TO C#######
232 234
 	## ##################
233 235
 	##
... ...
@@ -60,6 +60,7 @@ calls.
60 60
 
61 61
 <<ldpath,results=hide>>=
62 62
 library(ff)
63
+options(ffcaching="ffeachflush")
63 64
 outdir <- paste("/local_data/r00/crlmm/", getRversion(), "/illumina_vignette", sep="")
64 65
 ldPath(outdir)
65 66
 dir.create(outdir, recursive=TRUE, showWarnings=FALSE)
... ...
@@ -102,7 +102,10 @@ library(crlmm)
102 102
 ## genotype 50K SNPs at a time
103 103
 ocProbesets(50000)
104 104
 ## setup cluster - 8 cores on the machine
105
-setCluster(8, "SOCK")
105
+library(doSNOW)
106
+cl <- makeCluster(8, "SOCK")
107
+registerDoSNOW(cl)
108
+##setCluster(8, "SOCK")
106 109
 
107 110
 path <- system.file("celFiles", package="hapmapsnp6")
108 111
 cels <- list.celfiles(path, full.names=TRUE)
... ...
@@ -129,8 +129,10 @@ example below indicates.}
129 129
 	## to enable paralellization, set to TRUE
130 130
 	if(FALSE){
131 131
 		library(snow)
132
-		## 10 workers
133
-		setCluster(10, "SOCK")
132
+		library(doSNOW)
133
+		## with 10 workers
134
+		cl <- makeCluster(10, type="SOCK")
135
+		registerDoSNOW(cl)
134 136
 	}
135 137
 	## path to idat files
136 138
 	datadir <- "/thumper/ctsa/snpmicroarray/illumina/IDATS/370k"