Add a message that says 'Processing sample stratum x of X'
git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/trunk/madman/Rpacks/crlmm@53851 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1181,7 +1181,8 @@ genotype.Illumina <- function(sampleSheet=NULL, |
1181 | 1181 |
mixtureParams = initializeBigMatrix("crlmmMixt-", 4, narrays, "double") |
1182 | 1182 |
SNR = initializeBigVector("crlmmSNR-", narrays, "double") |
1183 | 1183 |
SKW = initializeBigVector("crlmmSKW-", narrays, "double") |
1184 |
- ocLapply(sampleBatches, processIDAT, sampleSheet=sampleSheet, arrayNames=arrayNames, |
|
1184 |
+ ocLapply(stratum=seq_along(sampleBatches), processIDAT, sampleBatches=sampleBatches, |
|
1185 |
+ sampleSheet=sampleSheet, arrayNames=arrayNames, |
|
1185 | 1186 |
ids=ids, path=path, arrayInfoColNames=arrayInfoColNames, highDensity=highDensity, |
1186 | 1187 |
sep=sep, fileExt=fileExt, saveDate=saveDate, verbose=verbose, mixtureSampleSize=mixtureSampleSize, |
1187 | 1188 |
fitMixture=fitMixture, eps=eps, seed=seed, cdfName=cdfName, sns=sns, stripNorm=stripNorm, |
... | ... |
@@ -1314,7 +1315,7 @@ genotype.Illumina <- function(sampleSheet=NULL, |
1314 | 1315 |
|
1315 | 1316 |
|
1316 | 1317 |
|
1317 |
-processIDAT <- function(sel, sampleSheet=NULL, |
|
1318 |
+processIDAT <- function(stratum, sampleBatches, sampleSheet=NULL, |
|
1318 | 1319 |
arrayNames=NULL, |
1319 | 1320 |
ids=NULL, |
1320 | 1321 |
path=".", |
... | ... |
@@ -1333,7 +1334,8 @@ processIDAT <- function(sel, sampleSheet=NULL, |
1333 | 1334 |
stripNorm=TRUE, |
1334 | 1335 |
useTarget=TRUE, |
1335 | 1336 |
A, B, SKW, SNR, mixtureParams, is.snp) { #, outdir=".") { |
1336 |
- |
|
1337 |
+ message("Processing sample stratum ", stratum, " of ", length(sampleBatches)) |
|
1338 |
+ sel <- sampleBatches[[stratum]] |
|
1337 | 1339 |
if(length(path)>= length(sel)) path = path[sel] |
1338 | 1340 |
message("RS:... processIDAT: calling readIdatFiles") |
1339 | 1341 |
RG = readIdatFiles(sampleSheet=sampleSheet[sel,], arrayNames=arrayNames[sel], |