Browse code

Version: 1.23.1 [2009-12-16] o ROBUSTNESS: Now matrix(...) is used instead of .Interal(matrix(...)).

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

Henrik Bengtsson authored on 16/12/2010 09:05:39
Showing 7 changed files

... ...
@@ -1,6 +1,6 @@
1 1
 Package: affxparser
2
-Version: 1.23.0
3
-Date: 2010-10-05
2
+Version: 1.23.1
3
+Date: 2010-12-16
4 4
 Title: Affymetrix File Parsing SDK
5 5
 Author: Henrik Bengtsson, James Bullard, Robert Gentleman, Kasper Daniel Hansen, Martin Morgan
6 6
 Maintainer: Kasper Daniel Hansen <[email protected]>
... ...
@@ -82,7 +82,7 @@ readCdf <- function(filename, units=NULL, readXY=TRUE, readBases=TRUE,
82 82
                     stop("Number of PM and MM probes differ in probeset #", uu,
83 83
                          ": ", length(pm), " != ", length(mm));
84 84
                 }
85
-                pmmm <- .Internal(matrix(c(pm, mm), 2, npm, TRUE));
85
+                pmmm <- matrix(c(pm, mm), nrow=2L, ncol=npm, byrow=TRUE);
86 86
 
87 87
                 ## Re-order cell elements according to PM/MM.
88 88
                 ngroup <- length(group);
... ...
@@ -175,3 +175,10 @@ readCdf <- function(filename, units=NULL, readXY=TRUE, readBases=TRUE,
175 175
     cdf;
176 176
 } # readCdfUnits()
177 177
 
178
+
179
+############################################################################
180
+# HISTORY:
181
+# 2010-12-12
182
+# o ROBUSTNESS: Replaces .Internal(matrix(...)) with matrix().
183
+#   In the upcoming R 2.13.0 matrix() has less overhead.
184
+############################################################################
... ...
@@ -134,7 +134,7 @@ readCdfCellIndices <- function(filename, units=NULL, stratifyBy=c("nothing", "pm
134 134
           stop("Number of PM and MM probes differ in probeset #", uu,
135 135
                                      ": ", length(pm), " != ", length(mm));
136 136
         }
137
-        pmmm <- .Internal(matrix(c(pm, mm), 2, npm, TRUE));
137
+        pmmm <- matrix(c(pm, mm), nrow=2L, ncol=npm, byrow=TRUE);
138 138
 #        dimnames(pmmm) <- dimnames;
139 139
 
140 140
         # Re-order cell elements according to PM/MM.
... ...
@@ -206,6 +206,9 @@ readCdfCellIndices <- function(filename, units=NULL, stratifyBy=c("nothing", "pm
206 206
 
207 207
 ############################################################################
208 208
 # HISTORY:
209
+# 2010-12-12
210
+# o ROBUSTNESS: Replaces .Internal(matrix(...)) with matrix().
211
+#   In the upcoming R 2.13.0 matrix() has less overhead.
209 212
 # 2006-12-10
210 213
 # o BUG FIX: Same stratifyBy="mm" bug here as in readCdfUnits().
211 214
 # 2006-07-22
... ...
@@ -177,7 +177,7 @@ readCdfUnits <- function(filename, units=NULL, readXY=TRUE, readBases=TRUE, read
177 177
           stop("Number of PM and MM probes differ in probeset #", uu,
178 178
                                      ": ", length(pm), " != ", length(mm));
179 179
         }
180
-        pmmm <- .Internal(matrix(c(pm, mm), 2, npm, TRUE));
180
+        pmmm <- matrix(c(pm, mm), nrow=2L, ncol=npm, byrow=TRUE);
181 181
 #        dimnames(pmmm) <- dimnames;
182 182
 
183 183
         # Re-order cell elements according to PM/MM.
... ...
@@ -250,6 +250,9 @@ readCdfUnits <- function(filename, units=NULL, readXY=TRUE, readBases=TRUE, read
250 250
 
251 251
 ############################################################################
252 252
 # HISTORY:
253
+# 2010-12-12
254
+# o ROBUSTNESS: Replaces .Internal(matrix(...)) with matrix().
255
+#   In the upcoming R 2.13.0 matrix() has less overhead.
253 256
 # 2006-12-30
254 257
 # o Now 'readDirection=TRUE' also return group directions.
255 258
 # 2006-03-28
... ...
@@ -78,9 +78,9 @@ readCel <- function(filename,
78 78
     # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
79 79
     if (reorder) {
80 80
       # About 10-15 times faster than using order()!
81
-      o <- .Internal(qsort(indices, TRUE));
81
+      o <- .Internal(qsort(indices, TRUE));  # From base::sort.int()
82 82
       indices <- o$x;
83
-      o <- .Internal(qsort(o$ix, TRUE))$ix;
83
+      o <- .Internal(qsort(o$ix, TRUE))$ix;  # From base::sort.int()
84 84
     }
85 85
 
86 86
     # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
... ...
@@ -276,9 +276,9 @@ readCelUnits <- function(filenames, units=NULL, stratifyBy=c("nothing", "pmmm",
276 276
   if (reorder) {
277 277
     verbose && enter(verbose, "Reordering cell indices to optimize speed");
278 278
     # About 10-15 times faster than using order()!
279
-    o <- .Internal(qsort(indices, TRUE));
279
+    o <- .Internal(qsort(indices, TRUE));  # From base::sort.int()
280 280
     indices <- o$x;
281
-    o <- .Internal(qsort(o$ix, TRUE))$ix;
281
+    o <- .Internal(qsort(o$ix, TRUE))$ix;  # From base::sort.int()
282 282
     verbose && exit(verbose);
283 283
   }
284 284
 
... ...
@@ -1,6 +1,18 @@
1 1
 Package: affxparser
2 2
 ===================
3 3
 
4
+Version: 1.23.1 [2009-12-16]
5
+o ROBUSTNESS: Now matrix(...) is used instead of .Interal(matrix(...)).
6
+
7
+
8
+Version: 1.23.0 [2009-10-17]
9
+o The version number was bumped for the Bioconductor devel version.
10
+
11
+
12
+Version: 1.22.0 [2009-10-17]
13
+o The version number was bumped for the Bioconductor release version.
14
+
15
+
4 16
 Version: 1.21.1 [2010-10-05]
5 17
 o Now readCdfDataFrame() also returns the cell field 'expos'.
6 18