Browse code

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

unknown authored on 25/08/2010 23:53:32
Showing 2 changed files

... ...
@@ -546,5 +546,5 @@ function (which expects ff objects and supports parallel processing)
546 546
 2010-08-25 M. Ritchie 1.7.12
547 547
 ** Renamed functions readIdatFiles2() -> readIdatFiles(), RGtoXY2() -> RGtoXY(), preprocessInfinium2v2() -> preprocessInfinium2(), crlmmIllumina2() -> crlmmIllumina().  These make use of ff objects to store data.
548 548
 ** Exported crlmmIlluminaV2(), which combines reading in of idats and genotyping in one.  Also added a man page for this function
549
-** Added close() statements to readIdatFiles(), RGtoXY() and stripNormalize().  Added open() statement to stripNormalize().
549
+** Added close() statements to readIdatFiles(), RGtoXY() and stripNormalize().  Added open() statement to stripNormalize(). Moved close() statement in preprocessInfinium2()
550 550
 ** tidied up crlmm-illumina.R, removing commented out code.
... ...
@@ -684,6 +684,16 @@ preprocessInfinium2 <- function(XY, mixtureSampleSize=10^5,
684 684
   }
685 685
   if (!fitMixture) SNR <- mixtureParams <- NA
686 686
   ## gns comes from preprocStuff.rda
687
+
688
+#  if(class(A)[1]=="ff_matrix") {
689
+    close(A)
690
+    close(B)
691
+    close(zero)
692
+    close(SKW)
693
+    close(mixtureParams)
694
+    close(SNR)
695
+#  }  
696
+  
687 697
   res = list(A=A, B=B,
688 698
              zero=zero, sns=sns, gns=names(snpIndex), SNR=SNR, SKW=SKW,
689 699
              mixtureParams=mixtureParams, cdfName=cdfName)
... ...
@@ -694,14 +704,7 @@ preprocessInfinium2 <- function(XY, mixtureSampleSize=10^5,
694 704
     t0 <- proc.time()-t0
695 705
     if(verbose) message("Used ", round(t0[3],1), " seconds to save ", snpFile, ".")
696 706
   }
697
-#  if(class(A)[1]=="ff_matrix") {
698
-    close(A)
699
-    close(B)
700
-    close(zero)
701
-    close(SKW)
702
-    close(mixtureParams)
703
-    close(SNR)
704
-#  }
707
+
705 708
   return(res)
706 709
 }
707 710
 
... ...
@@ -735,6 +738,10 @@ crlmmIllumina <- function(RG, XY, stripNorm=TRUE, useTarget=TRUE,
735 738
     res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose,
736 739
                         seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget,
737 740
                         save.it=save.it, snpFile=snpFile, cnFile=cnFile)
741
+    open(res[["A"]])  # this should perhaps go below }else{ below
742
+    open(res[["B"]])
743
+    open(res[["SNR"]])
744
+    open(res[["mixtureParams"]])    
738 745
 
739 746
 #    fD = featureData(XY)
740 747
 #    phenD = XY@phenoData
... ...
@@ -762,7 +769,7 @@ crlmmIllumina <- function(RG, XY, stripNorm=TRUE, useTarget=TRUE,
762 769
           stop("Object in ", snpFile, " seems to be invalid.")
763 770
   }
764 771
 
765
- #   rm(phenD, protD , fD)
772
+#    rm(phenD, protD , fD)
766 773
 	
767 774
 #    snp.index <- res$snpIndex #match(res$gns, featureNames(callSet))                
768 775
 #    suppressWarnings(A(callSet) <- res[["A"]])