Browse code

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

unknown authored on 09/12/2010 17:33:21
Showing 6 changed files

... ...
@@ -582,5 +582,9 @@ be used to specify where you want to store the large data objects.  ldPath(outdi
582 582
 inside preprocessInfinium2()
583 583
 ** the 'batch' variable is now left empty and must be specified by the user
584 584
 ** X and Y are now initialized with zeroes by initializeBigMatrix( ,initdata=0) in RGtoXY().
585
-** open(A(callSet); open(B(callSet) replaces open(callSet) in genotyp.Illumina()
585
+** open(A(callSet); open(B(callSet) replaces open(callSet) in genotype.Illumina()
586 586
 
587
+2010-12-10 M. Ritchie 1.9.9
588
+** ffcolapply() now used instead of ffrowapply()
589
+** ff storage only used to initialize callSet - no longer used in storage of RG, XY, res data created along the way (matrices now used here) etc.
590
+** removed 'outdir' argument and ldPath() added in 1.9.8
... ...
@@ -1,8 +1,8 @@
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.9.8
5
-Date: 2010-11-18
4
+Version: 1.9.9
5
+Date: 2010-12-10
6 6
 Author: Benilton S Carvalho <carvalho@bclab.org>, 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 <carvalho@bclab.org>, Robert Scharpf <rscharpf@jhsph.edu>, Matt Ritchie <mritchie@wehi.EDU.AU>
8 8
 Description: Faster implementation of CRLMM specific to SNP 5.0 and 6.0 arrays, as well as a copy number tool specific to 5.0, 6.0, and Illumina platforms
... ...
@@ -11,7 +11,7 @@ readIdatFiles = function(sampleSheet=NULL,
11 11
 			  highDensity=FALSE,
12 12
 			  sep="_",
13 13
 			  fileExt=list(green="Grn.idat", red="Red.idat"),
14
-			  saveDate=FALSE) {
14
+			  saveDate=FALSE, verbose=FALSE) {
15 15
        if(!is.null(arrayNames)) {
16 16
                pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames))
17 17
        }
... ...
@@ -72,9 +72,11 @@ readIdatFiles = function(sampleSheet=NULL,
72 72
                     scan=rep(NA, narrays))
73 73
        ## read in the data
74 74
        for(i in seq_along(arrayNames)) {
75
-	       cat("reading", arrayNames[i], "\t")
75
+	       if(verbose) {
76
+	         cat("reading", arrayNames[i], "\t")
77
+   	         cat(paste(sep, fileExt$green, sep=""), "\t")
78
+	       }
76 79
 	       idsG = idsR = G = R = NULL
77
-	       cat(paste(sep, fileExt$green, sep=""), "\t")
78 80
 	       G = readIDAT(grnidats[i])
79 81
 	       idsG = rownames(G$Quants)
80 82
 	       headerInfo$nProbes[i] = G$nSNPsRead
... ...
@@ -95,12 +97,12 @@ readIdatFiles = function(sampleSheet=NULL,
95 97
 		       nprobes = length(ids)
96 98
 		       narrays = length(arrayNames)
97 99
 		       RG = new("NChannelSet",
98
-		                 R=initializeBigMatrix(name="R", nr=nprobes, nc=narrays, vmode="integer"),
99
-		                 G=initializeBigMatrix(name="G", nr=nprobes, nc=narrays, vmode="integer"),
100
-		                 zero=initializeBigMatrix(name="zero", nr=nprobes, nc=narrays, vmode="integer"),
101
-				         annotation=headerInfo$Manifest[1],
102
-				         phenoData=pd, storage.mode="environment")
103
-			   featureNames(RG) = ids
100
+		                 R=matrix(NA, nprobes, narrays),
101
+		                 G=matrix(NA, nprobes, narrays),
102
+		                 zero=matrix(NA, nprobes, narrays),
103
+				 annotation=headerInfo$Manifest[1],
104
+				 phenoData=pd, storage.mode="environment")
105
+		       featureNames(RG) = ids
104 106
 		       if(!is.null(sampleSheet) && !is.null(sampleSheet$Sample_ID)){
105 107
 		            sampleNames(RG) = sampleSheet$Sample_ID
106 108
 		       } else  sampleNames(RG) = arrayNames
... ...
@@ -118,15 +120,16 @@ readIdatFiles = function(sampleSheet=NULL,
118 120
 	       }
119 121
 	       rm(G)
120 122
 	       gc()
121
-
122
-	       cat(paste(sep, fileExt$red, sep=""), "\n")
123
+	       if(verbose) { 
124
+                      cat(paste(sep, fileExt$red, sep=""), "\n")
125
+	       }
123 126
 	       R = readIDAT(redidats[i])
124 127
 	       idsR = rownames(R$Quants)
125 128
 
126 129
 	       if(length(ids)==length(idsG)) {
127 130
 		       if(sum(ids==idsR)==nprobes) {
128 131
 			       RG@assayData$R[,i] = R$Quants[ ,"Mean"]
129
-		           zeroR = R$Quants[ ,"NBeads"]==0
132
+		               zeroR = R$Quants[ ,"NBeads"]==0
130 133
 		       }
131 134
 	       } else {
132 135
 		       indR = match(ids, idsR)
... ...
@@ -141,12 +144,6 @@ readIdatFiles = function(sampleSheet=NULL,
141 144
 	       protocolData(RG)[["ScanDate"]] = dates$scan
142 145
        }
143 146
        storageMode(RG) = "lockedEnvironment"
144
-       is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
145
-       if(is.lds) {
146
-         close(RG@assayData$R)
147
-         close(RG@assayData$G)
148
-         close(RG@assayData$zero)
149
-       }
150 147
        RG
151 148
 }
152 149
 
... ...
@@ -421,7 +418,7 @@ RGtoXY = function(RG, chipType, verbose=TRUE) {
421 418
                "human1mduov3b",          # 1M Duo
422 419
                "humanomni1quadv1b",      # Omni1 quad
423 420
                "humanomni25quadv1b",     # Omni2.5 quad
424
-	       "humanomniexpress12v1b",  # Omni express 12
421
+	           "humanomniexpress12v1b",  # Omni express 12
425 422
                "humanimmuno12v1b")       # Immuno chip 12
426 423
   if(missing(chipType)){
427 424
 	  chipType = match.arg(annotation(RG), chipList)
... ...
@@ -462,9 +459,9 @@ RGtoXY = function(RG, chipType, verbose=TRUE) {
462 459
 #  brgrg = bids[rrgg]
463 460
 
464 461
   XY = new("NChannelSet",
465
-	     X=initializeBigMatrix(name="X", nr=nsnps, nc=narrays, vmode="integer", initdata=0),
466
-	     Y=initializeBigMatrix(name="Y", nr=nsnps, nc=narrays, vmode="integer", initdata=0),
467
-	     zero=initializeBigMatrix(name="zero", nr=nsnps, nc=narrays, vmode="integer", initdata=0),
462
+	     X=matrix(0, nsnps, narrays),
463
+	     Y=matrix(0, nsnps, narrays),
464
+	     zero=matrix(0, nsnps, narrays),
468 465
 	     annotation=chipType, phenoData=RG@phenoData,
469 466
 	     protocolData=RG@protocolData, storage.mode="environment")
470 467
   featureNames(XY) = ids
... ...
@@ -475,14 +472,6 @@ RGtoXY = function(RG, chipType, verbose=TRUE) {
475 472
 #  XY@assayData$Y[1:nsnps,] = 0
476 473
 #  XY@assayData$zero[1:nsnps,] = 0
477 474
 
478
-  is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
479
-
480
-  if(is.lds) {
481
-    open(RG@assayData$G)
482
-    open(RG@assayData$R)
483
-    open(RG@assayData$zero)
484
-  }
485
-
486 475
   # First sort out Infinium II SNPs, X -> R (allele A)  and Y -> G (allele B) from the same probe
487 476
   XY@assayData$X[!is.na(aord),] = exprs(channel(RG, "R"))[aord[!is.na(aord)],] # mostly red
488 477
   XY@assayData$Y[!is.na(aord),] = exprs(channel(RG, "G"))[aord[!is.na(aord)],] # mostly green
... ...
@@ -504,20 +493,10 @@ RGtoXY = function(RG, chipType, verbose=TRUE) {
504 493
 #  Y[infIGG,] = exprs(channel(RG, "G"))[bord[infIGG],] # mostly green
505 494
 
506 495
   #  For now zero out Infinium I probes
507
-  XY@assayData$X[infI,] = 0
508
-  XY@assayData$Y[infI,] = 0
509
-  XY@assayData$zero[infI,] = 0
510
-  gc()
511
-
512
-  is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
513
-  if(is.lds) {
514
-    close(RG@assayData$G)
515
-    close(RG@assayData$R)
516
-    close(RG@assayData$zero)
517
-    close(XY@assayData$X)
518
-    close(XY@assayData$Y)
519
-    close(XY@assayData$zero)
520
-  }
496
+#  XY@assayData$X[infI,] = 0
497
+#  XY@assayData$Y[infI,] = 0
498
+#  XY@assayData$zero[infI,] = 0
499
+#  gc()
521 500
   XY
522 501
 }
523 502
 
... ...
@@ -543,12 +522,7 @@ stripNormalize = function(XY, useTarget=TRUE, verbose=TRUE) {
543 522
     message("Quantile normalizing ", ncol(XY), " arrays by ", max(stripnum), " strips.")
544 523
     if (getRversion() > '2.7.0') pb = txtProgressBar(min=0, max=max(stripnum), style=3)
545 524
   }
546
-  is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
547 525
 
548
-  if(is.lds) {
549
-    open(XY@assayData$X)
550
-    open(XY@assayData$Y)
551
-  }
552 526
   for(s in 1:max(stripnum)) {
553 527
     if(verbose) {
554 528
       if (getRversion() > '2.7.0') setTxtProgressBar(pb, s)
... ...
@@ -566,10 +540,6 @@ stripNormalize = function(XY, useTarget=TRUE, verbose=TRUE) {
566 540
     rm(subX, subY, tmp, sel)
567 541
     gc()
568 542
   }
569
-  if(is.lds) {
570
-    close(XY@assayData$X)
571
-    close(XY@assayData$Y)
572
-  }
573 543
 
574 544
   if(verbose)
575 545
     cat("\n")
... ...
@@ -585,8 +555,8 @@ preprocessInfinium2 = function(XY, mixtureSampleSize=10^5,
585 555
 				cdfName,
586 556
 				sns,
587 557
 				stripNorm=TRUE,
588
-				useTarget=TRUE,
589
-                                outdir=".") {
558
+				useTarget=TRUE) { #,
559
+#               outdir=".") {
590 560
 #				save.it=FALSE,
591 561
 #				snpFile,
592 562
 #				cnFile) {
... ...
@@ -615,42 +585,30 @@ preprocessInfinium2 = function(XY, mixtureSampleSize=10^5,
615 585
   theKnots = getVarInEnv("theKnots")
616 586
   narrays = ncol(XY)
617 587
 
618
-  is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
619
-  if(is.lds)
620
-    ldPath(outdir)
621 588
 #  if(save.it & !missing(cnFile)) {
622 589
     # separate out copy number probes
623
-    npIndex = getVarInEnv("npProbesFid")
624
-    nprobes = length(npIndex)
625
-    if(length(nprobes)>0) {
626
-      if(is.lds) {
627
-        open(XY@assayData$X)
628
-        open(XY@assayData$Y)
629
-        open(XY@assayData$zero)
630
-      }
631
-      A = matrix(as.integer(exprs(channel(XY, "X"))[npIndex,]), nprobes, narrays)
632
-      B = matrix(as.integer(exprs(channel(XY, "Y"))[npIndex,]), nprobes, narrays)
590
+  npIndex = getVarInEnv("npProbesFid")
591
+  if(length(nprobes)>0) {
592
+     nprobes = length(npIndex)
593
+
594
+     A = matrix(as.integer(exprs(channel(XY, "X"))[npIndex,]), nprobes, narrays)
595
+     B = matrix(as.integer(exprs(channel(XY, "Y"))[npIndex,]), nprobes, narrays)
633 596
 
634
-      # new lines below - useful to keep track of zeroed out probes
635
-      zero = matrix(as.integer(exprs(channel(XY, "zero"))[npIndex,]), nprobes, narrays)
597
+     # new lines below - useful to keep track of zeroed out probes
598
+     zero = matrix(as.integer(exprs(channel(XY, "zero"))[npIndex,]), nprobes, narrays)
636 599
 
637
-      colnames(A) = colnames(B) = colnames(zero) = sns
638
-      rownames(A) = rownames(B) = rownames(zero) = names(npIndex)
600
+     colnames(A) = colnames(B) = colnames(zero) = sns
601
+     rownames(A) = rownames(B) = rownames(zero) = names(npIndex)
639 602
 
640
-      cnAB = list(A=A, B=B, zero=zero, sns=sns, gns=names(npIndex), cdfName=cdfName)
603
+     cnAB = list(A=A, B=B, zero=zero, sns=sns, gns=names(npIndex), cdfName=cdfName)
641 604
 
642 605
 #      t0 <- proc.time()
643 606
 #      save(cnAB, file=cnFile)
644 607
 #      t0 <- proc.time()-t0
645 608
 #      if(verbose) message("Used ", round(t0[3],1), " seconds to save ", cnFile, ".")
646
-       rm(A, B, zero)
647
-      if(is.lds) {
648
-        close(XY@assayData$X)
649
-        close(XY@assayData$Y)
650
-        close(XY@assayData$zero)
651
-      }
652
-    }
653
-#  }
609
+     rm(A, B, zero)
610
+#    }
611
+  }
654 612
 
655 613
   # next process snp probes
656 614
   snpIndex = getVarInEnv("snpProbesFid")
... ...
@@ -658,9 +616,9 @@ preprocessInfinium2 = function(XY, mixtureSampleSize=10^5,
658 616
 
659 617
   ##We will read each cel file, summarize, and run EM one by one
660 618
   ##We will save parameters of EM to use later
661
-  mixtureParams = initializeBigMatrix("crlmmMixt-", 4, narrays, "double")
662
-  SNR = initializeBigVector("crlmmSNR-", narrays, "double")
663
-  SKW = initializeBigVector("crlmmSKW-", narrays, "double")
619
+  mixtureParams = matrix(NA, 4, narrays)
620
+  SNR = rep(NA, narrays)
621
+  SKW = rep(NA, narrays)
664 622
 
665 623
   ## This is the sample for the fitting of splines
666 624
   ## BC: I like better the idea of the user passing the seed,
... ...
@@ -674,21 +632,15 @@ preprocessInfinium2 = function(XY, mixtureSampleSize=10^5,
674 632
   ##NOTE: We actually dont need to save S. Only for pics etc...
675 633
   ##f is the correction. we save to avoid recomputing
676 634
 
677
-  A = initializeBigMatrix("crlmmA-", nprobes, narrays, "integer")
678
-  B = initializeBigMatrix("crlmmB-", nprobes, narrays, "integer")
679
-  zero = initializeBigMatrix("crlmmZero-", nprobes, narrays, "integer")
635
+  A = matrix(NA, nprobes, narrays)
636
+  B = matrix(NA, nprobes, narrays)
637
+  zero = matrix(NA, nprobes, narrays)
680 638
 
681 639
   if(verbose){
682 640
      message("Calibrating ", narrays, " arrays.")
683 641
      if (getRversion() > '2.7.0') pb = txtProgressBar(min=0, max=narrays, style=3)
684 642
   }
685 643
 
686
-  if(is.lds) {
687
-    open(XY@assayData$X)
688
-    open(XY@assayData$Y)
689
-    open(XY@assayData$zero)
690
-  }
691
-
692 644
   for(i in 1:narrays){
693 645
      A[,i] = as.integer(exprs(channel(XY, "X"))[snpIndex,i])
694 646
      B[,i] = as.integer(exprs(channel(XY, "Y"))[snpIndex,i])
... ...
@@ -722,17 +674,6 @@ preprocessInfinium2 = function(XY, mixtureSampleSize=10^5,
722 674
 #    t0 <- proc.time()-t0
723 675
 #    if(verbose) message("Used ", round(t0[3],1), " seconds to save ", snpFile, ".")
724 676
 #  }
725
-  if(is.lds) {
726
-    close(XY@assayData$X)
727
-    close(XY@assayData$Y)
728
-    close(XY@assayData$zero)
729
-    close(A)
730
-    close(B)
731
-    close(zero)
732
-    close(SKW)
733
-    close(mixtureParams)
734
-    close(SNR)
735
-  }
736 677
 
737 678
   res = list(A=A, B=B,
738 679
              zero=zero, sns=sns, gns=names(snpIndex), SNR=SNR, SKW=SKW,
... ...
@@ -790,14 +731,15 @@ crlmmIllumina = function(RG, XY, stripNorm=TRUE, useTarget=TRUE,
790 731
                         seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget) #,
791 732
 #                        save.it=save.it, snpFile=snpFile, cnFile=cnFile)
792 733
 
793
-    is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
734
+#    is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
735
+     is.lds=FALSE
794 736
 
795
-    if(is.lds) {
796
-      open(res[["A"]])
797
-      open(res[["B"]])
798
-      open(res[["SNR"]])
799
-      open(res[["mixtureParams"]])
800
-    }
737
+#    if(is.lds) {
738
+#      open(res[["A"]])
739
+#      open(res[["B"]])
740
+#      open(res[["SNR"]])
741
+#      open(res[["mixtureParams"]])
742
+#    }
801 743
 
802 744
 #    fD = featureData(XY)
803 745
 #    phenD = XY@phenoData
... ...
@@ -915,7 +857,7 @@ crlmmIlluminaV2 = function(sampleSheet=NULL,
915 857
 			  saveDate=FALSE,
916 858
 			  stripNorm=TRUE,
917 859
 			  useTarget=TRUE,
918
-                          outdir=".",
860
+ #                         outdir=".",
919 861
 			  row.names=TRUE,
920 862
 			  col.names=TRUE,
921 863
 			  probs=c(1/3, 1/3, 1/3), DF=6, SNRMin=5, gender=NULL,
... ...
@@ -927,30 +869,30 @@ crlmmIlluminaV2 = function(sampleSheet=NULL,
927 869
     if(missing(cdfName)) stop("must specify cdfName")
928 870
     if(!isValidCdfName(cdfName)) stop("cdfName not valid.  see validCdfNames")
929 871
 
930
-    is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
931
-
872
+#    is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
873
+    is.lds=FALSE
932 874
     RG = readIdatFiles(sampleSheet=sampleSheet, arrayNames=arrayNames,
933 875
                        ids=ids, path=path, arrayInfoColNames=arrayInfoColNames,
934 876
                        highDensity=highDensity, sep=sep, fileExt=fileExt, saveDate=saveDate)
935 877
 
936 878
 
937 879
     XY = RGtoXY(RG, chipType=cdfName)
938
-    if(is.lds) {
939
-      open(RG@assayData$R); open(RG@assayData$G); open(RG@assayData$zero)
940
-      delete(RG@assayData$R); delete(RG@assayData$G); delete(RG@assayData$zero)
941
-    }
880
+#    if(is.lds) {
881
+#      open(RG@assayData$R); open(RG@assayData$G); open(RG@assayData$zero)
882
+#      delete(RG@assayData$R); delete(RG@assayData$G); delete(RG@assayData$zero)
883
+#    }
942 884
     rm(RG); gc()
943 885
 
944 886
     if (missing(sns)) { sns = sampleNames(XY)
945 887
     }
946 888
     res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose,
947
-                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget, outdir=outdir) #,
889
+                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget) #, outdir=outdir) #,
948 890
 #                               save.it=save.it, snpFile=snpFile, cnFile=cnFile)
949 891
 
950
-    if(is.lds) {
951
-      open(XY@assayData$X); open(XY@assayData$Y); open(XY@assayData$zero)
952
-      delete(XY@assayData$X); delete(XY@assayData$Y); delete(XY@assayData$zero)
953
-    }
892
+#    if(is.lds) {
893
+#      open(XY@assayData$X); open(XY@assayData$Y); open(XY@assayData$zero)
894
+#      delete(XY@assayData$X); delete(XY@assayData$Y); delete(XY@assayData$zero)
895
+#    }
954 896
     rm(XY); gc()
955 897
 
956 898
     if(row.names) row.names=res$gns else row.names=NULL
... ...
@@ -981,9 +923,9 @@ crlmmIlluminaV2 = function(sampleSheet=NULL,
981 923
                      returnParams=returnParams,
982 924
                      badSNP=badSNP)
983 925
 
984
-    if(is.lds) {
985
-      open(res[["SNR"]]); open(res[["SKW"]])
986
-    }
926
+#    if(is.lds) {
927
+#      open(res[["SNR"]]); open(res[["SKW"]])
928
+#    }
987 929
     res2[["SNR"]] = res[["SNR"]]
988 930
     res2[["SKW"]] = res[["SKW"]]
989 931
  #  if(is.lds) {
... ...
@@ -995,7 +937,7 @@ crlmmIlluminaV2 = function(sampleSheet=NULL,
995 937
 }
996 938
 
997 939
 # Functions analogous to Rob's Affy functions to set up container
998
-getProtocolData.Illumina = function(filenames, sep="_", fileExt="Grn.idat") {
940
+getProtocolData.Illumina = function(filenames, sep="_", fileExt="Grn.idat", verbose=FALSE) {
999 941
        narrays = length(filenames)
1000 942
 
1001 943
        headerInfo = list(nProbes = rep(NA, narrays),
... ...
@@ -1008,7 +950,8 @@ getProtocolData.Illumina = function(filenames, sep="_", fileExt="Grn.idat") {
1008 950
        rownames(scanDates) = gsub(paste(sep, fileExt, sep=""), "", filenames)
1009 951
        ## read in the data
1010 952
        for(i in seq_along(filenames)) {
1011
-	       cat("reading", filenames[i], "\n")
953
+               if(verbose)
954
+	               cat("reading", filenames[i], "\n")
1012 955
 	       idsG = G = NULL
1013 956
 	       G = readIDAT(filenames[i])
1014 957
 	       idsG = rownames(G$Quants)
... ...
@@ -1043,10 +986,10 @@ construct.Illumina = function(sampleSheet=NULL,
1043 986
 			  sep="_",
1044 987
 			  fileExt=list(green="Grn.idat",
1045 988
 			  red="Red.idat"),
1046
-		      	  cdfName,
1047
-		      	  copynumber=TRUE,
1048
-		      	  verbose=TRUE, batch, #fns,
1049
-                          saveDate=TRUE, outdir="."){
989
+		      cdfName,
990
+			  copynumber=TRUE,
991
+			  verbose=FALSE, batch, #fns,
992
+			  saveDate=TRUE) { #, outdir="."){
1050 993
        if(!is.null(arrayNames)) {
1051 994
                pd = new("AnnotatedDataFrame", data = data.frame(Sample_ID=arrayNames))
1052 995
        }
... ...
@@ -1115,7 +1058,7 @@ construct.Illumina = function(sampleSheet=NULL,
1115 1058
 #		featureData = featureData[index, ]
1116 1059
 #	}
1117 1060
 	nr = nrow(featureData); nc = narrays
1118
-        ldPath(outdir)
1061
+#        ldPath(outdir)
1119 1062
 	cnSet = new("CNSet",
1120 1063
 		     alleleA=initializeBigMatrix(name="A", nr, nc),
1121 1064
 		     alleleB=initializeBigMatrix(name="B", nr, nc),
... ...
@@ -1129,7 +1072,7 @@ construct.Illumina = function(sampleSheet=NULL,
1129 1072
         else sampleNames(cnSet) = arrayNames
1130 1073
 
1131 1074
 	if(saveDate){
1132
-		protocolData = getProtocolData.Illumina(grnidats, sep=sep, fileExt=fileExt$green)
1075
+		protocolData = getProtocolData.Illumina(grnidats, sep=sep, fileExt=fileExt$green, verbose=verbose)
1133 1076
 	} else{
1134 1077
 		protocolData = annotatedDataFrameFrom(A(cnSet), byrow=FALSE)
1135 1078
 	}
... ...
@@ -1151,51 +1094,52 @@ genotype.Illumina = function(sampleSheet=NULL,
1151 1094
 			  arrayInfoColNames=list(barcode="SentrixBarcode_A", position="SentrixPosition_A"),
1152 1095
 			  highDensity=FALSE,
1153 1096
 			  sep="_",
1154
-			  fileExt=list(green="Grn.idat",
1155
-			  red="Red.idat"),
1156
-		      	  cdfName,
1157
-		      	  copynumber=TRUE,
1158
-                          batch,
1159
-                          outdir=".",
1097
+			  fileExt=list(green="Grn.idat", red="Red.idat"),
1098
+			  cdfName,
1099
+			  copynumber=TRUE,
1100
+			  batch,
1101
+#                          outdir=".",
1160 1102
 #                          fns,
1161
-                          saveDate=TRUE,
1162
-       			  stripNorm=TRUE,
1103
+              saveDate=TRUE,
1104
+			  stripNorm=TRUE,
1163 1105
 			  useTarget=TRUE,
1164
-		          mixtureSampleSize=10^5,
1165
-                          fitMixture=TRUE,
1166
-		          eps=0.1,
1167
-		          verbose=TRUE,
1168
-		          seed=1,
1169
-		          sns,
1170
-		          probs=rep(1/3, 3),
1171
-		          DF=6,
1172
-		          SNRMin=5,
1173
-		          recallMin=10,
1174
-		          recallRegMin=1000,
1175
-		          gender=NULL,
1176
-		          returnParams=TRUE,
1177
-		          badSNP=0.7) {
1106
+		      mixtureSampleSize=10^5,
1107
+              fitMixture=TRUE,
1108
+		      eps=0.1,
1109
+		      verbose=TRUE,
1110
+		      seed=1,
1111
+		      sns,
1112
+		      probs=rep(1/3, 3),
1113
+		      DF=6,
1114
+		      SNRMin=5,
1115
+		      recallMin=10,
1116
+		      recallRegMin=1000,
1117
+		      gender=NULL,
1118
+		      returnParams=TRUE,
1119
+		      badSNP=0.7) {
1178 1120
 	is.lds = ifelse(isPackageLoaded("ff"), TRUE, FALSE)
1179 1121
 	if(missing(cdfName)) stop("must specify cdfName")
1180 1122
 	if(!isValidCdfName(cdfName)) stop("cdfName not valid.  see validCdfNames")
1181 1123
         pkgname = getCrlmmAnnotationName(cdfName)
1182
-        if(missing(outdir))
1183
-          stop("Must specify a directory to store large data objects")
1124
+#        if(missing(outdir))
1125
+#          stop("Must specify a directory to store large data objects")
1184 1126
 	callSet = construct.Illumina(sampleSheet=sampleSheet, arrayNames=arrayNames,
1185
-			     ids=ids, path=path, arrayInfoColNames=arrayInfoColNames,
1127
+			                 ids=ids, path=path, arrayInfoColNames=arrayInfoColNames,
1186 1128
                              highDensity=highDensity, sep=sep, fileExt=fileExt,
1187
-			     cdfName=cdfName, copynumber=copynumber, verbose=verbose, batch=batch, # fns=fns, 
1188
-                             saveDate=saveDate, outdir=outdir)
1189
-        if(missing(sns)) sns = sampleNames(callSet)
1190
-        
1191
-        open(A(callSet))
1192
-        open(B(callSet))
1193
-        # open(callSet)
1129
+			                 cdfName=cdfName, copynumber=copynumber, verbose=verbose, batch=batch, # fns=fns, 
1130
+                             saveDate=saveDate) #, outdir=outdir)
1131
+	if(missing(sns)) sns = sampleNames(callSet)
1132
+    
1133
+    if(is.lds) {
1134
+		open(A(callSet))
1135
+		open(B(callSet))
1136
+	# open(callSet)
1137
+	}
1194 1138
  	is.snp = isSnp(callSet)
1195 1139
 	snp.index = which(is.snp)
1196
-        narrays = ncol(callSet)
1197
-        if(is.lds) {
1198
-          sampleBatches = splitIndicesByNode(seq(along=sampleNames(callSet)))
1140
+	narrays = ncol(callSet)
1141
+	if(is.lds) {
1142
+          sampleBatches = splitIndicesByLength(seq(along=sampleNames(callSet)), ocSamples())
1199 1143
 
1200 1144
           mixtureParams = initializeBigMatrix("crlmmMixt-", 4, narrays, "double")
1201 1145
           SNR = initializeBigVector("crlmmSNR-", narrays, "double")
... ...
@@ -1206,7 +1150,7 @@ genotype.Illumina = function(sampleSheet=NULL,
1206 1150
                  sep=sep, fileExt=fileExt, saveDate=saveDate, verbose=verbose, mixtureSampleSize=mixtureSampleSize,
1207 1151
                  fitMixture=fitMixture, eps=eps, seed=seed, cdfName=cdfName, sns=sns, stripNorm=stripNorm,
1208 1152
                  useTarget=useTarget, A=A(callSet), B=B(callSet), SKW=SKW, SNR=SNR,
1209
-                 mixtureParams=mixtureParams, is.snp=is.snp, outdir=outdir, neededPkgs=c("crlmm", pkgname))
1153
+                 mixtureParams=mixtureParams, is.snp=is.snp, neededPkgs=c("crlmm", pkgname)) # outdir=outdir, 
1210 1154
 
1211 1155
           open(SKW)
1212 1156
           open(SNR)
... ...
@@ -1214,7 +1158,7 @@ genotype.Illumina = function(sampleSheet=NULL,
1214 1158
           pData(callSet)$SNR = SNR
1215 1159
           close(SNR)
1216 1160
           close(SKW)
1217
-        } else {
1161
+	} else {
1218 1162
           mixtureParams = matrix(NA, 4, nrow(callSet))
1219 1163
 
1220 1164
           RG = readIdatFiles(sampleSheet=sampleSheet, arrayNames=arrayNames,
... ...
@@ -1225,23 +1169,21 @@ genotype.Illumina = function(sampleSheet=NULL,
1225 1169
           rm(RG); gc()
1226 1170
 
1227 1171
           res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose,
1228
-                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget, outdir=outdir)
1172
+                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget) # , outdir=outdir)
1229 1173
           rm(XY); gc()
1230 1174
           if(verbose) message("Finished preprocessing.")
1231 1175
           np.index = which(!is.snp)
1232 1176
           A(callSet)[snp.index, ] = res[["A"]]
1233 1177
           B(callSet)[snp.index, ] = res[["B"]]
1234 1178
           if(length(np.index)>0) {
1235
-            for (j in 1:ncol(callSet)) {
1236 1179
         	A(callSet)[np.index, ] = res[["cnAB"]]$A
1237 1180
         	B(callSet)[np.index, ] = res[["cnAB"]]$B
1238
-        	}
1239 1181
           }
1240
-	  SKW = pData(callSet)$SKW = res[["SKW"]]
1241
-	  SNR = pData(callSet)$SNR = res[["SNR"]]
1242
-	  mixtureParams = res[["mixtureParams"]]
1243
-          rm(res)
1244
-        }
1182
+		  SKW = pData(callSet)$SKW = res[["SKW"]]
1183
+		  SNR = pData(callSet)$SNR = res[["SNR"]]
1184
+		  mixtureParams = res[["mixtureParams"]]
1185
+		  rm(res)
1186
+	}
1245 1187
 
1246 1188
 	FUN = ifelse(is.lds, "crlmmGT2", "crlmmGT")
1247 1189
 	## genotyping
... ...
@@ -1251,22 +1193,23 @@ genotype.Illumina = function(sampleSheet=NULL,
1251 1193
 		       crlmmGT=crlmmGT(...))
1252 1194
 	}
1253 1195
 
1254
-        if(is.lds) {
1196
+	if(is.lds) {
1255 1197
           open(A(callSet))
1256 1198
           open(B(callSet))
1257 1199
           tmpA = initializeBigMatrix(name="A", length(snp.index), narrays)
1258
-          tmpB = initializeBigMatrix(name="B", length(snp.index), narrays)
1259
-          bb = ocProbesets()*length(sns)*8
1260
-	  ffrowapply(tmpA[i1:i2, ] <- A(callSet)[snp.index,][i1:i2, ], X=A(callSet)[snp.index,], BATCHBYTES=bb)
1261
-	  ffrowapply(tmpB[i1:i2, ] <- B(callSet)[snp.index,][i1:i2, ], X=B(callSet)[snp.index,], BATCHBYTES=bb)
1200
+          tmpB = initializeBigMatrix(name="B", length(snp.index), narrays) 
1201
+#          bb = getOption("ffbatchbytes")          
1202
+#          bb = ocProbesets()*length(sns)*8
1203
+		  ffcolapply(tmpA[,i1:i2] <- A(callSet)[snp.index,i1:i2], X=A(callSet)) #, BATCHBYTES=bb) # X=A(callSet)[snp.index,]
1204
+		  ffcolapply(tmpB[,i1:i2] <- B(callSet)[snp.index,i1:i2], X=B(callSet)) #, BATCHBYTES=bb) # X=B(callSet)[snp.index,]
1262 1205
           close(A(callSet))
1263 1206
           close(B(callSet))
1264 1207
           close(tmpA)
1265 1208
           close(tmpB)
1266
-        } else {
1209
+	} else {
1267 1210
           tmpA = A(callSet)[snp.index,]
1268 1211
           tmpB = B(callSet)[snp.index,]
1269
-        }
1212
+	}
1270 1213
 
1271 1214
 	tmp = crlmmGTfxn(FUN,
1272 1215
 			  A=tmpA,
... ...
@@ -1287,24 +1230,24 @@ genotype.Illumina = function(sampleSheet=NULL,
1287 1230
 			  badSNP=badSNP)
1288 1231
 	if(verbose) message("Genotyping finished.  Updating container with genotype calls and confidence scores.")
1289 1232
 	if(is.lds){
1290
-		bb = ocProbesets()*ncol(callSet)*8
1233
+#       bb = getOption("ffbatchbytes") # ocProbesets()*ncol(callSet)*8
1291 1234
 		open(tmp[["calls"]])
1292 1235
 		open(tmp[["confs"]])
1293
-		ffrowapply(snpCall(callSet)[snp.index,][i1:i2, ] <- tmp[["calls"]][i1:i2, ], X=tmp[["calls"]], BATCHBYTES=bb)
1294
-		ffrowapply(snpCallProbability(callSet)[snp.index,][i1:i2, ] <- tmp[["confs"]][i1:i2, ], X=tmp[["confs"]], BATCHBYTES=bb)
1236
+		ffcolapply(snpCall(callSet)[snp.index,i1:i2] <- tmp[["calls"]][,i1:i2], X=tmp[["calls"]]) #, BATCHBYTES=bb)
1237
+		ffcolapply(snpCallProbability(callSet)[snp.index,i1:i2] <- tmp[["confs"]][,i1:i2], X=tmp[["confs"]]) #, BATCHBYTES=bb)
1295 1238
 #		close(tmp[["calls"]])
1296 1239
 #		close(tmp[["confs"]])
1297
-#                open(tmpA); open(tmpB)
1298
-#                delete(tmpA); delete(tmpB);
1299
-                delete(tmp[["calls"]]); delete(tmp[["confs"]])
1300
-                rm(tmpA, tmpB)
1240
+		open(tmpA); open(tmpB)
1241
+		delete(tmpA); delete(tmpB);
1242
+	    delete(tmp[["calls"]]); delete(tmp[["confs"]])
1243
+		rm(tmpA, tmpB)
1301 1244
 	} else {
1302 1245
 		calls(callSet)[snp.index, ] = tmp[["calls"]]
1303 1246
 		snpCallProbability(callSet)[snp.index, ] = tmp[["confs"]]
1304
-                rm(tmpA, tmpB)
1247
+		rm(tmpA, tmpB)
1305 1248
 	}
1306 1249
 	callSet$gender = tmp$gender
1307
-        rm(tmp)
1250
+	rm(tmp)
1308 1251
 	close(callSet)
1309 1252
 	return(callSet)
1310 1253
 }
... ...
@@ -1319,8 +1262,8 @@ processIDAT =  function(sel, sampleSheet=NULL,
1319 1262
 			  sep="_",
1320 1263
 			  fileExt=list(green="Grn.idat", red="Red.idat"),
1321 1264
 			  saveDate=FALSE,
1322
-                          verbose=TRUE,
1323
-                          mixtureSampleSize=10^5,
1265
+			  verbose=TRUE,
1266
+              mixtureSampleSize=10^5,
1324 1267
 			  fitMixture=TRUE,
1325 1268
 			  eps=0.1,
1326 1269
 			  seed=1,
... ...
@@ -1328,53 +1271,61 @@ processIDAT =  function(sel, sampleSheet=NULL,
1328 1271
 			  sns,
1329 1272
 			  stripNorm=TRUE,
1330 1273
 			  useTarget=TRUE,
1331
-                          A, B, SKW, SNR, mixtureParams, is.snp, outdir=".") {
1274
+              A, B, SKW, SNR, mixtureParams, is.snp) { #, outdir=".") {
1332 1275
 
1333 1276
         if(length(path)>= length(sel)) path = path[sel]
1334 1277
         RG = readIdatFiles(sampleSheet=sampleSheet[sel,], arrayNames=arrayNames[sel],
1335 1278
                        ids=ids, path=path, arrayInfoColNames=arrayInfoColNames,
1336
-                       highDensity=highDensity, sep=sep, fileExt=fileExt, saveDate=saveDate)
1279
+                       highDensity=highDensity, sep=sep, fileExt=fileExt, saveDate=saveDate, verbose=verbose)
1337 1280
 
1338 1281
         XY = RGtoXY(RG, chipType=cdfName)
1339
-        open(RG@assayData$R); open(RG@assayData$G); open(RG@assayData$zero)
1340
-        delete(RG@assayData$R); delete(RG@assayData$G); delete(RG@assayData$zero); rm(RG)
1282
+#        open(RG@assayData$R); open(RG@assayData$G); open(RG@assayData$zero)
1283
+#        delete(RG@assayData$R); delete(RG@assayData$G); delete(RG@assayData$zero);
1284
+        rm(RG)
1341 1285
         gc()
1342 1286
         if (missing(sns) || length(sns)!=ncol(XY)) sns = sampleNames(XY)
1343 1287
 
1344 1288
         res = preprocessInfinium2(XY, mixtureSampleSize=mixtureSampleSize, fitMixture=TRUE, verbose=verbose,
1345
-                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget, outdir=outdir)
1346
-        #                       save.it=save.it, snpFile=snpFile, cnFile=cnFile)
1347
-        open(XY@assayData$X); open(XY@assayData$Y); open(XY@assayData$zero)
1348
-        delete(XY@assayData$X); delete(XY@assayData$Y); delete(XY@assayData$zero); rm(XY)
1289
+                               seed=seed, eps=eps, cdfName=cdfName, sns=sns, stripNorm=stripNorm, useTarget=useTarget) #, outdir=outdir)
1290
+#							    save.it=save.it, snpFile=snpFile, cnFile=cnFile)
1291
+#        open(XY@assayData$X); open(XY@assayData$Y); open(XY@assayData$zero)
1292
+#        delete(XY@assayData$X); delete(XY@assayData$Y); delete(XY@assayData$zero);
1293
+        rm(XY)
1349 1294
         gc()
1350
-	if(verbose) message("Finished preprocessing.")
1295
+	    if(verbose) message("Finished preprocessing.")
1351 1296
         snp.index = which(is.snp)
1352
-	np.index = which(!is.snp)
1353
-
1354
-        open(res[["A"]])
1355
-        open(res[["B"]])
1356
-        open(res[["SKW"]])
1357
-        open(res[["SNR"]])
1358
-        open(res[["mixtureParams"]])
1359
-	bb = ocProbesets()*length(sns)*8
1360
-        ffrowapply(A[snp.index,][i1:i2, sel] <- res[["A"]][i1:i2, ], X=res[["A"]], BATCHBYTES=bb)
1361
-	ffrowapply(B[snp.index,][i1:i2, sel] <- res[["B"]][i1:i2, ], X=res[["B"]], BATCHBYTES=bb)
1362
-	if(length(np.index)>0) {
1363
-          for (j in 1:length(sel)) {
1364
-            A[np.index, sel[j]] = res[["cnAB"]]$A[,j]
1365
-            B[np.index, sel[j]] = res[["cnAB"]]$B[,j]
1366
-          }
1297
+	    np.index = which(!is.snp)
1298
+
1299
+#        open(res[["A"]])
1300
+#        open(res[["B"]])
1301
+#        open(res[["SKW"]])
1302
+#        open(res[["SNR"]])
1303
+#        open(res[["mixtureParams"]])
1304
+# remove this line: bb = ocProbesets()*length(sns)*8
1305
+# Add these
1306
+        ffcolapply(A[snp.index,sel][,i1:i2] <- res[["A"]][,i1:i2], X=res[["A"]])
1307
+        ffcolapply(B[snp.index,sel][,i1:i2] <- res[["B"]][,i1:i2], X=res[["B"]])
1308
+#   ffrowapply(A[snp.index,][i1:i2, sel] <- res[["A"]][i1:i2, ], X=res[["A"]], BATCHBYTES=bb)
1309
+#	ffrowapply(B[snp.index,][i1:i2, sel] <- res[["B"]][i1:i2, ], X=res[["B"]], BATCHBYTES=bb)
1310
+	    if(length(np.index)>0) {
1311
+#			for (j in 1:length(sel)) {
1312
+			ffcolapply(A[np.index,sel][,i1:i2] <- res[["cnAB"]]$A[,i1:i2], X=res[["cnAB"]]$A)
1313
+			ffcolapply(B[np.index,sel][,i1:i2] <- res[["cnAB"]]$B[,i1:i2], X=res[["cnAB"]]$B)		  
1314
+#            A[np.index, sel[j]] = res[["cnAB"]]$A[,j]
1315
+#            B[np.index, sel[j]] = res[["cnAB"]]$B[,j]
1316
+#          }
1367 1317
         }
1368
-        delete(res[["A"]]); delete(res[["B"]])
1369
-	SKW[sel] = res[["SKW"]][]
1370
-	SNR[sel] = res[["SNR"]][]
1371
-	mixtureParams[,sel] = res[["mixtureParams"]][]
1318
+#        delete(res[["A"]]); delete(res[["B"]])
1319
+	    SKW[sel] = res[["SKW"]][]
1320
+	    SNR[sel] = res[["SNR"]][]
1321
+	    mixtureParams[,sel] = res[["mixtureParams"]][]
1372 1322
         close(A)
1373 1323
         close(B)
1374 1324
         close(SNR)
1375 1325
         close(SKW)
1376 1326
         close(mixtureParams)
1377
-        delete(res[["SKW"]]); delete(res[["SNR"]]); delete(res[["mixtureParams"]])
1327
+#        delete(res[["SKW"]]); delete(res[["SNR"]]); delete(res[["mixtureParams"]])
1378 1328
         rm(res)
1329
+		gc()
1379 1330
         TRUE
1380
-      }
1331
+      }
1381 1332
\ No newline at end of file
... ...
@@ -10,7 +10,7 @@
10 10
 crlmmIlluminaV2(sampleSheet=NULL, arrayNames=NULL, ids=NULL, path=".",
11 11
       arrayInfoColNames=list(barcode="SentrixBarcode_A", position="SentrixPosition_A"),
12 12
       highDensity=FALSE, sep="_", fileExt=list(green="Grn.idat", red="Red.idat"),
13
-      saveDate=FALSE, stripNorm=TRUE, useTarget=TRUE, outdir=".", 
13
+      saveDate=FALSE, stripNorm=TRUE, useTarget=TRUE,  
14 14
       row.names=TRUE, col.names=TRUE, probs=c(1/3, 1/3, 1/3), 
15 15
       DF=6, SNRMin=5, gender=NULL, seed=1, mixtureSampleSize=10^5, 
16 16
       eps=0.1, verbose=TRUE, cdfName, sns, recallMin=10, 
... ...
@@ -47,8 +47,6 @@ crlmmIlluminaV2(sampleSheet=NULL, arrayNames=NULL, ids=NULL, path=".",
47 47
   \item{stripNorm}{'logical'.  Should the data be strip-level normalized?}
48 48
   \item{useTarget}{'logical' (only used when \code{stripNorm=TRUE}).
49 49
     Should the reference HapMap intensities be used in strip-level normalization?}
50
-  \item{outdir}{character string specifying the location to store large data objects 
51
-    (used when \code{ff} package is loaded)}
52 50
   \item{row.names}{'logical'. Use rownames - SNP names?}
53 51
   \item{col.names}{'logical'. Use colnames - Sample names?}
54 52
   \item{probs}{'numeric' vector with priors for AA, AB and BB.}
... ...
@@ -11,7 +11,7 @@
11 11
 genotype.Illumina(sampleSheet=NULL, arrayNames=NULL, ids=NULL, path=".",
12 12
       arrayInfoColNames=list(barcode="SentrixBarcode_A", position="SentrixPosition_A"),
13 13
       highDensity=FALSE, sep="_", fileExt=list(green="Grn.idat", red="Red.idat"),
14
-      cdfName, copynumber=TRUE, batch, outdir=".", saveDate=TRUE, stripNorm=TRUE, useTarget=TRUE, 
14
+      cdfName, copynumber=TRUE, batch, saveDate=TRUE, stripNorm=TRUE, useTarget=TRUE, 
15 15
       mixtureSampleSize=10^5, fitMixture=TRUE, eps =0.1, verbose = TRUE, seed = 1, 
16 16
       sns, probs = rep(1/3, 3), DF = 6, SNRMin = 5, recallMin = 10, recallRegMin = 1000,
17 17
       gender = NULL, returnParams = TRUE, badSNP = 0.7)
... ...
@@ -43,8 +43,7 @@ genotype.Illumina(sampleSheet=NULL, arrayNames=NULL, ids=NULL, path=".",
43 43
     specify the .idat file extension for the Cy3 and Cy5 channels.}
44 44
   \item{cdfName}{ annotation package  (see also \code{validCdfNames})}
45 45
   \item{copynumber}{ 'logical.' Whether to store copy number intensities with SNP output.} 
46
-  \item{batch}{ batch variable. See details. }
47
-  \item{outdir}{character string specifying the location to store large data objects.}
46
+  \item{batch}{ batch variable. See details.}
48 47
   \item{saveDate}{'logical'.  Should the dates from each .idat be saved
49 48
     with sample information?}
50 49
   \item{stripNorm}{'logical'.  Should the data be strip-level normalized?}
... ...
@@ -14,7 +14,7 @@ readIdatFiles(sampleSheet=NULL, arrayNames=NULL, ids=NULL, path="",
14 14
                                      position="SentrixPosition_A"),
15 15
               highDensity=FALSE, sep="_",
16 16
               fileExt=list(green="Grn.idat", red="Red.idat"),
17
-              saveDate=FALSE)
17
+              saveDate=FALSE, verbose=FALSE)
18 18
 }
19 19
 
20 20
 \arguments{
... ...
@@ -44,6 +44,7 @@ readIdatFiles(sampleSheet=NULL, arrayNames=NULL, ids=NULL, path="",
44 44
     specify the .idat file extension for the Cy3 and Cy5 channels.}
45 45
   \item{saveDate}{logical.  Should the dates from each .idat be saved
46 46
     with sample information?}
47
+  \item{verbose}{logical.  Should processing information be displayed as data is read in?}
47 48
 }
48 49
 
49 50
 \details{