Browse code

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

unknown authored on 26/08/2010 04:08:38
Showing 1 changed files

... ...
@@ -615,11 +615,19 @@ preprocessInfinium2 <- function(XY, mixtureSampleSize=10^5,
615 615
     npIndex = getVarInEnv("npProbesFid")
616 616
     nprobes = length(npIndex)
617 617
     if(length(nprobes)>0) {
618
+      open(XY@assayData$X)
619
+      open(XY@assayData$Y)
620
+      open(XY@assayData$zero)
621
+      
618 622
       A <- matrix(as.integer(exprs(channel(XY, "X"))[npIndex,]), nprobes, narrays)
619 623
       B <- matrix(as.integer(exprs(channel(XY, "Y"))[npIndex,]), nprobes, narrays)
620 624
 
621 625
       # new lines below - useful to keep track of zeroed out probes
622
-      zero <- matrix(as.integer(exprs(channel(XY, "zero"))[npIndex,]), nprobes, narrays) 
626
+      zero <- matrix(as.integer(exprs(channel(XY, "zero"))[npIndex,]), nprobes, narrays)
627
+
628
+      close(XY@assayData$X)
629
+      close(XY@assayData$Y)
630
+      close(XY@assayData$zero)
623 631
 
624 632
       colnames(A) <- colnames(B) <- colnames(zero) <- sns
625 633
       rownames(A) <- rownames(B) <- rownames(zero) <- names(npIndex)
... ...
@@ -665,6 +673,10 @@ preprocessInfinium2 <- function(XY, mixtureSampleSize=10^5,
665 673
      if (getRversion() > '2.7.0') pb <- txtProgressBar(min=0, max=narrays, style=3)
666 674
   }
667 675
 
676
+  open(XY@assayData$X)
677
+  open(XY@assayData$Y)
678
+  open(XY@assayData$zero)
679
+  
668 680
   for(i in 1:narrays){
669 681
      A[,i] = exprs(channel(XY, "X"))[snpIndex,i]
670 682
      B[,i] = exprs(channel(XY, "Y"))[snpIndex,i]
... ...
@@ -693,6 +705,10 @@ preprocessInfinium2 <- function(XY, mixtureSampleSize=10^5,
693 705
   if (!fitMixture) SNR <- mixtureParams <- NA
694 706
   ## gns comes from preprocStuff.rda
695 707
 
708
+  close(XY@assayData$X)
709
+  close(XY@assayData$Y)
710
+  close(XY@assayData$zero)  
711
+  
696 712
 #  if(class(A)[1]=="ff_matrix") {
697 713
     close(A)
698 714
     close(B)
... ...
@@ -892,7 +908,7 @@ crlmmIlluminaV2 = function(sampleSheet=NULL,
892 908
     if (missing(sns)) { sns = sampleNames(XY) #subsns = sampleNames(XY)
893 909
     } # else subsns = sns[j]
894 910
     res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose,
895
-                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget, #) # sns=subsns
911
+                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget,
896 912
                                save.it=save.it, snpFile=snpFile, cnFile=cnFile)
897 913
     open(res[["A"]])
898 914
     open(res[["B"]])