R/readCelUnits.R
ad4b2701
 #########################################################################/**
 # @RdocFunction readCelUnits
 #
 # @title "Reads probe-level data ordered as units (probesets) from one or several Affymetrix CEL files"
 #
95092fca
 # @synopsis
 #
ad4b2701
 # \description{
95092fca
 #   @get "title" by using the unit and group definitions in the
ad4b2701
 #   corresponding Affymetrix CDF file.
 # }
95092fca
 #
ad4b2701
 # \arguments{
 #   \item{filenames}{The filenames of the CEL files.}
ddd48129
 #   \item{units}{An @integer @vector of unit indices specifying which
 #     units to be read.  If @NULL, all units are read.}
95092fca
 #   \item{stratifyBy}{Argument passed to low-level method
7ba4cea3
 #     @see "affxparser::readCdfCellIndices".}
ad4b2701
 #   \item{cdf}{A @character filename of a CDF file, or a CDF @list
 #     structure.  If @NULL, the CDF file is searched for by
 #     @see "findCdf" first starting from the current directory and
 #     then from the directory where the first CEL file is.}
95092fca
 #   \item{...}{Arguments passed to low-level method
f1d6fcf0
 #     @see "affxparser::readCel", e.g. \code{readXY} and \code{readStdvs}.}
ad4b2701
 #   \item{addDimnames}{If @TRUE, dimension names are added to arrays,
95092fca
 #     otherwise not.  The size of the returned CEL structure in bytes
ad4b2701
 #     increases by 30-40\% with dimension names.}
f1d6fcf0
 #   \item{dropArrayDim}{If @TRUE and only one array is read, the elements of
 #     the group field do \emph{not} have an array dimension.}
 #   \item{transforms}{A @list of exactly \code{length(filenames)}
 #     @functions.  If @NULL, no transformation is performed.
 #     Intensities read are passed through the corresponding transform
 #     function before being returned.}
95092fca
 #   \item{readMap}{A @vector remapping cell indices to file indices.
f1d6fcf0
 #     If @NULL, no mapping is used.}
ad4b2701
 #   \item{verbose}{Either a @logical, a @numeric, or a @see "R.utils::Verbose"
 #     object specifying how much verbose/debug information is written to
 #     standard output. If a Verbose object, how detailed the information is
 #     is specified by the threshold level of the object. If a numeric, the
95092fca
 #     value is used to set the threshold of a new Verbose object. If @TRUE,
ad4b2701
 #     the threshold is set to -1 (minimal). If @FALSE, no output is written
 #     (and neither is the \pkg{R.utils} package required).
 #   }
 # }
95092fca
 #
ad4b2701
 # \value{
ddd48129
 #   A named @list with one element for each unit read.  The names
95092fca
 #   corresponds to the names of the units read.
ddd48129
 #   Each unit element is in
95092fca
 #   turn a @list structure with groups (aka blocks).
 #   Each group contains requested fields, e.g. \code{intensities},
ddd48129
 #   \code{stdvs}, and \code{pixels}.
 #   If more than one CEL file is read, an extra dimension is added
 #   to each of the fields corresponding, which can be used to subset
 #   by CEL file.
 #
 #   Note that neither CEL headers nor information about outliers and
 #   masked cells are returned.  To access these, use @see "readCelHeader"
 #   and @see "readCel".
ad4b2701
 # }
 #
76cf4b26
 # @author "HB"
95092fca
 #
ad4b2701
 # @examples "../incl/readCelUnits.Rex"
95092fca
 #
ad4b2701
 # \seealso{
95092fca
 #   Internally, @see "readCelHeader", @see "readCdfUnits" and
ddd48129
 #   @see "readCel" are used.
ad4b2701
 # }
95092fca
 #
ad4b2701
 # \references{
 #   [1] Affymetrix Inc, Affymetrix GCOS 1.x compatible file formats,
 #       June 14, 2005.
 #       \url{http://www.affymetrix.com/support/developer/}
 # }
 #
 # @keyword "file"
 # @keyword "IO"
95092fca
 #*/#########################################################################
7e675541
 readCelUnits <- function(filenames, units=NULL, stratifyBy=c("nothing", "pmmm", "pm", "mm"), cdf=NULL, ..., addDimnames=FALSE, dropArrayDim=TRUE, transforms=NULL, readMap=NULL, verbose=FALSE) {
0b615a31
   # To please R CMD check
   Arguments <- enter <- exit <- NULL;
   rm(list=c("Arguments", "enter", "exit"));
 
00472b76
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Local functions
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   qsort <- function(x) {
 ##    o0 <- .Internal(qsort(x, TRUE));
 ##    o <- sort.int(x, index.return=TRUE, method="quick");
 ##    stopifnot(identical(o, o0));
     sort.int(x, index.return=TRUE, method="quick");
   } # qsort()
 
 
95092fca
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
ad4b2701
   # Validate arguments
95092fca
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
ad4b2701
   # Argument 'filenames':
   filenames <- file.path(dirname(filenames), basename(filenames));
   missing <- filenames[!file.exists(filenames)];
   if (length(missing)) {
     stop("File(s) not found: ", paste(missing, collapse=", "));
   }
 
   # Argument 'units' and 'cdf':
   if (is.list(cdf) && !is.null(units)) {
     stop("Arguments 'units' must not be specified if argument 'cdf' is a CDF list structure.");
   }
 
   # Argument 'units':
   if (is.null(units)) {
   } else if (is.numeric(units)) {
     units <- as.integer(units);
ddd48129
     # Unit indices are one-based in R
0257f391
     if (any(units < 1L))
ddd48129
       stop("Argument 'units' contains non-positive indices.");
ad4b2701
   } else {
     stop("Argument 'units' must be numeric or NULL: ", class(units)[1]);
   }
 
   # Argument 'cdf':
   searchForCdf <- FALSE;
   if (is.null(cdf)) {
     searchForCdf <- TRUE;
   } else if (is.character(cdf)) {
     cdfFile <- file.path(dirname(cdf), basename(cdf));
     if (!file.exists(cdfFile))
       stop("File not found: ", cdfFile);
     cdf <- NULL;
   } else if (is.list(cdf)) {
0257f391
     aUnit <- cdf[[1L]];
ad4b2701
     if (!is.list(aUnit))
       stop("Argument 'cdf' is of unknown format: First unit is not a list.");
 
     groups <- aUnit$groups;
     if (!is.list(groups))
       stop("Argument 'cdf' is of unknown format: Units Does not contain the list 'groups'.");
 
0257f391
     extractGroups <- (length(names(aUnit)) > 1L);
349caa9b
 
ddd48129
     # Check for group fields 'indices' or 'x' & 'y' in one of the groups.
ad4b2701
     aGroup <- groups[[1]];
 
349caa9b
     extractFields <- TRUE;
ad4b2701
     fields <- names(aGroup);
ddd48129
     if ("indices" %in% fields) {
       cdfType <- "indices";
0257f391
       extractFields <- (length(fields) > 1L);
ad4b2701
     } else if (all(c("x", "y") %in% fields)) {
c7cc55c7
       # The CDF is needed in order to know the (x,y) dimensions of the
       # chip so that one can calculate (x,y) -> cell index.
ad4b2701
       cdfType <- "x";
       searchForCdf <- TRUE;
     } else {
ddd48129
       stop("Argument 'cdf' is of unknown format: The groups contains neither the fields 'indices' nor ('x' and 'y').");
ad4b2701
     }
95092fca
     aUnit <- groups <- aGroup <- NULL; # Not needed anymore
ad4b2701
   } else {
     stop("Argument 'cdf' must be a filename, a CDF list structure or NULL: ", mode(cdf));
   }
 
ddd48129
   # Argument 'readMap':
   if (!is.null(readMap)) {
95092fca
     # Cannot check map indices without knowing the array.  Is it worth
ad4b2701
     # reading such details already here?
   }
 
ddd48129
   # Argument 'dropArrayDim':
   dropArrayDim <- as.logical(dropArrayDim);
ad4b2701
 
   # Argument 'addDimnames':
   addDimnames <- as.logical(addDimnames);
 
   nbrOfArrays <- length(filenames);
 
   # Argument 'transforms':
   if (is.null(transforms)) {
     hasTransforms <- FALSE;
   } else if (is.list(transforms)) {
     if (length(transforms) != nbrOfArrays) {
95092fca
       stop("Length of argument 'transforms' does not match the number of arrays: ",
ad4b2701
                                    length(transforms), " != ", nbrOfArrays);
     }
     for (transform in transforms) {
       if (!is.function(transform))
         stop("Argument 'transforms' must be a list of functions.");
     }
     hasTransforms <- TRUE;
   } else {
     stop("Argument 'transforms' must be a list of functions or NULL.");
   }
 
   # Argument 'stratifyBy':
   stratifyBy <- match.arg(stratifyBy);
 
 
   # Argument 'verbose': (Utilized the Verbose class in R.utils if available)
   if (!identical(verbose, FALSE)) {
0e455230
     requireNamespace("R.utils") || stop("Package not loaded: R.utils");
     Arguments <- R.utils::Arguments
     enter <- R.utils::enter
     exit <- R.utils::exit
ad4b2701
     verbose <- Arguments$getVerbose(verbose);
   }
ddd48129
   cVerbose <- -(as.numeric(verbose) + 2);
ad4b2701
 
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # 0. Search for CDF file?
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   if (searchForCdf) {
     verbose && enter(verbose, "Searching for CDF file");
 
     verbose && enter(verbose, "Reading chip type from first CEL file");
0257f391
     celHeader <- readCelHeader(filenames[1L]);
ad4b2701
     chipType <- celHeader$chiptype;
     verbose && exit(verbose);
 
     verbose && enter(verbose, "Searching for chip type '", chipType, "'");
     cdfFile <- findCdf(chipType=chipType);
0257f391
     if (length(cdfFile) == 0L) {
ad4b2701
       # If not found, try also where the first CEL file is
       opwd <- getwd();
       on.exit(setwd(opwd));
0257f391
       setwd(dirname(filenames[1L]));
ad4b2701
       cdfFile <- findCdf(chipType=chipType);
       setwd(opwd);
     }
     verbose && exit(verbose);
0257f391
     if (length(cdfFile) == 0L)
ad4b2701
       stop("No CDF file for chip type found: ", chipType);
 
     verbose && exit(verbose);
   }
 
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # 1. Read cell indices for units of interest from the CDF file?
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   if (is.null(cdf)) {
349caa9b
 #    verbose && enter(verbose, "Reading cell indices from CDF file");
90cb1239
     cdf <- readCdfCellIndices(cdfFile, units=units, stratifyBy=stratifyBy, verbose=FALSE);
349caa9b
 #    verbose && exit(verbose);
ad4b2701
 
ddd48129
     # Assume 'cdf' contains only "indices" fields.
     indices <- unlist(cdf, use.names=FALSE);
ad4b2701
   } else {
ddd48129
     if (cdfType == "indices") {
349caa9b
       # Clean up CDF list structure from other elements than groups?
       if (extractGroups) {
 #        verbose && enter(verbose, "Extracting groups...");
         cdf <- lapply(cdf, FUN=function(unit) list(groups=unit$groups));
 #        verbose && exit(verbose);
       }
 
       # Clean up CDF list structure from other group fields than "indices"?
       if (extractFields) {
 #        verbose && enter(verbose, "Extracting fields...");
         cdf <- applyCdfGroups(cdf, cdfGetFields, fields="indices");
 #        verbose && exit(verbose);
       }
ddd48129
       indices <- unlist(cdf, use.names=FALSE);
ad4b2701
     } else {
       verbose && enter(verbose, "Calculating cell indices from (x,y) positions");
       verbose && enter(verbose, "Reading chip layout from CDF file");
       cdfHeader <- readCdfHeader(cdfFile);
       ncol <- cdfHeader$cols;
       verbose && exit(verbose);
f1d6fcf0
       # Clean up CDF list structure from other elements than groups
       cdf <- lapply(cdf, FUN=function(unit) list(groups=unit$groups));
ddd48129
       x <- unlist(applyCdfGroups(cdf, cdfGetFields, "x"), use.names=FALSE);
       y <- unlist(applyCdfGroups(cdf, cdfGetFields, "y"), use.names=FALSE);
       # Cell indices are one-based in R
       indices <- as.integer(y * ncol + x + 1);
95092fca
       x <- y <- NULL; # Not needed anymore
ad4b2701
       verbose && exit(verbose);
     }
   }
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # 2. Remapping cell indices?
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
ddd48129
   if (!is.null(readMap)) {
ad4b2701
     verbose && enter(verbose, "Remapping cell indices");
ddd48129
     indices <- readMap[indices];
ad4b2701
     verbose && exit(verbose);
   }
 
 
ddd48129
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # 2b. Order cell indices for optimal speed when reading, i.e. minimal
   #     jumping around in the file.
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
7e675541
   reorder <- TRUE;  # Hardwired from now on.
886f672a
   if (reorder) {
     verbose && enter(verbose, "Reordering cell indices to optimize speed");
00472b76
     # qsort() is about 10-15 times faster than using order()!
     # WAS: o <- .Internal(qsort(indices, TRUE));  # From base::sort.int()
     o <- qsort(indices);
886f672a
     indices <- o$x;
00472b76
     # WAS: o <- .Internal(qsort(o$ix, TRUE))$ix;  # From base::sort.int()
     o <- qsort(o$ix)$ix;
886f672a
     verbose && exit(verbose);
   }
 
ddd48129
 
ad4b2701
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # 3. Read signals of the cells of interest from the CEL file(s)
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
ddd48129
 
95092fca
   # Comment: We assign elements of CEL list structure to local environment,
ddd48129
   # because calling cel[[field]][idxs,] multiple (=nbrOfUnits) times is very
   # slow whereas get(field) is much faster (about 4-6 times actually!)
   # /HB 2006-03-24
 
   nbrOfCells <- length(indices);
ad4b2701
   nbrOfUnits <- length(cdf);
 
0257f391
   # Because integer 'nbrOfCells*nbrOfArrays' may overflow to NA, we corce to double
   # here.  See aroma.affymetrix thread 'Speeding up RmaBackgroundCorrection' on
   # 2014-02-27 for background/details.
   # FIXME: Ideally, this function should be rewritten to read signals and group them
   # into CEL units in chunks. /HB 2014-02-27
   nbrOfEntries <- as.double(nbrOfCells) * as.double(nbrOfArrays);
   stopifnot(is.finite(nbrOfEntries));
 
ad4b2701
   verbose && enter(verbose, "Reading ", nbrOfUnits, "*", nbrOfCells/nbrOfUnits, "=", nbrOfCells, " cells from ", nbrOfArrays, " CEL files");
 
ddd48129
   # Cell-value elements
   cellValueFields <- c("x", "y", "intensities", "stdvs", "pixels");
ad4b2701
   integerFields <- "pixels";
ddd48129
   doubleFields <- setdiff(cellValueFields, integerFields);
ad4b2701
 
0257f391
   # Local environment where to store the temporary variables
   env <- environment();
 
24277d85
   for (kk in seq_len(nbrOfArrays)) {
ad4b2701
     filename <- filenames[kk];
 
     verbose && enter(verbose, "Reading CEL data for array #", kk);
7e675541
     celTmp <- readCel(filename, indices=indices, readHeader=FALSE, readOutliers=FALSE, readMasked=FALSE, ..., readMap=NULL, verbose=cVerbose, .checkArgs=FALSE);
ad4b2701
     verbose && exit(verbose);
 
0257f391
     if (kk == 1L) {
ad4b2701
       verbose && enter(verbose, "Allocating return structure");
       # Allocate the return list structure
ddd48129
 #      celTmp$header <- NULL;
       celFields <- names(celTmp);
ad4b2701
 
       # Update list of special fields
ddd48129
       cellValueFields <- intersect(celFields, cellValueFields);
       doubleFields <- intersect(cellValueFields, doubleFields);
       integerFields <- intersect(cellValueFields, integerFields);
ad4b2701
 
ddd48129
       # Allocate all field variables
886f672a
       dim <- c(nbrOfCells, nbrOfArrays);
0257f391
       value <- vector("double", length=nbrOfEntries);
886f672a
       dim(value) <- dim;
ad4b2701
       for (name in doubleFields)
0257f391
         assign(name, value, envir=env, inherits=FALSE);
       value <- NULL; # Not needed anymore
ad4b2701
 
0257f391
       value <- vector("integer", length=nbrOfEntries);
886f672a
       dim(value) <- dim;
ad4b2701
       for (name in integerFields)
0257f391
         assign(name, value, envir=env, inherits=FALSE);
       value <- NULL; # Not needed anymore
ddd48129
 
ad4b2701
       verbose && exit(verbose);
ddd48129
     }
ad4b2701
 
ddd48129
     for (name in cellValueFields) {
       # Extract field values and re-order them again
ad4b2701
       value <- celTmp[[name]];
ddd48129
       if (is.null(value))
         next;
 
886f672a
       # "Re-reorder" cells read
       if (reorder)
         value <- value[o];
ddd48129
 
ad4b2701
       # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
       # Transform signals?
       # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
       if (hasTransforms && name == "intensities") {
         verbose && enter(verbose, "Transform signals for array #", kk);
         value <- transforms[[kk]](value);
         verbose && exit(verbose);
       }
 
f06bec15
       eval(substitute(name[,kk] <- value, list(name=as.name(name))));
0257f391
       value <- NULL; # Not needed anymore
     } # for (name ...)
ad4b2701
 
95092fca
     celTmp <- NULL; # Not needed anymore
ad4b2701
   }
   verbose && exit(verbose);
 
95092fca
   indices <- NULL; # Not needed anymore
ad4b2701
 
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # 3. Structure CEL data in units and groups according to the CDF file
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   verbose && enter(verbose, "Structuring data by units and groups");
 
0257f391
   fields <- vector("list", length=length(cellValueFields));
ddd48129
   names(fields) <- cellValueFields;
ad4b2701
 
37a9aff7
   # Keep a copy for groups with empty fields
   emptyFields <- fields;
 
ddd48129
   # Add a dimension for the arrays, unless only one array is read
   # and the array dimension is not wanted.
0257f391
   addArrayDim <- (nbrOfArrays >= 2L || !dropArrayDim);
ad4b2701
 
17cb3b6e
   seqOfArrays <- list(seq_len(nbrOfArrays));
0257f391
   offset <- 0L;
95092fca
 
ddd48129
   res <- lapply(cdf, FUN=function(u) {
37a9aff7
     lapply(.subset2(u, "groups"), FUN=function(g) {
ad4b2701
       # Same dimensions of all fields
0257f391
       field <- .subset2(g, 1L);  # Faster than g[[1L]]
ad4b2701
       ncells <- length(field);
37a9aff7
 
       # Empty unit group?
0257f391
       if (ncells == 0L)
23dafa60
         return(emptyFields);
37a9aff7
 
ad4b2701
       idxs <- offset + 1:ncells;
       offset <<- offset + ncells;
 
       # Get the target dimension
       dim <- dim(field);
       if (is.null(dim))
         dim <- ncells;
ddd48129
 
       if (addDimnames) {
ad4b2701
         dimnames <- dimnames(field);
ddd48129
         if (is.null(dimnames))
24277d85
           dimnames <- list(seq_len(dim));
ad4b2701
 
ddd48129
         # Add an extra dimension for arrays?
         if (addArrayDim) {
           dim <- c(dim, nbrOfArrays);
ad4b2701
           dimnames <- c(dimnames, seqOfArrays);
ddd48129
         }
 
         # Update all fields with dimensions
0257f391
         setDim <- (length(dim) > 1L);
ddd48129
         for (name in cellValueFields) {
           # Faster to drop dimensions.
0257f391
           values <- get(name, envir=env, inherits=FALSE)[idxs,,drop=TRUE];
ddd48129
           if (setDim) {
             dim(values) <- dim;
             dimnames(values) <- dimnames;
           } else {
             names(values) <- dimnames;
           }
ad4b2701
           fields[[name]] <- values;
0257f391
           values <- NULL; # Not needed anymore
ddd48129
         }
       } else {
        # Add an extra dimension for arrays?
         if (addArrayDim)
           dim <- c(dim, nbrOfArrays);
 
         # Update all fields with dimensions
0257f391
         setDim <- (length(dim) > 1L);
ddd48129
         for (name in cellValueFields) {
           # Faster to drop dimensions.
0257f391
           values <- get(name, envir=env, inherits=FALSE)[idxs,,drop=TRUE];
ddd48129
           if (setDim)
             dim(values) <- dim;
           fields[[name]] <- values;
0257f391
           values <- NULL; # Not needed anymore
ddd48129
         }
       } # if (addDimnames)
ad4b2701
 
       fields;
0257f391
     }) # lapply(.subset2(u, "groups"), ...);
   }) # lapply(cdf, ...)
ad4b2701
 
   verbose && exit(verbose);
 
ddd48129
   res;
ad4b2701
 }
 
 
 ############################################################################
 # HISTORY:
0257f391
 # 2014-02-27 [HB]
 # o ROBUSTNESS: Using integer constants (e.g. 1L) where applicable.
 # o ROBUSTNESS: Using explicitly named arguments in more places.
00472b76
 # 2012-05-22 [HB]
 # o CRAN POLICY: readCel() and readCelUnits() are no longer calling
 #   .Internal(qsort(...)).
7e675541
 # 2007-12-01 [HB]
 # o Removed argument 'reorder' from readCelUnits(). Reordering is now always
 #   done.
f06bec15
 # 2007-06-28 [HB]
 # o Removed the name of the second argument in a substitute() call.
37a9aff7
 # 2007-02-01 [KS]
 # o Now readCelUnits() can handle unit groups for which there are no probes,
 #   e.g. when stratifying on PM in a unit containing only MMs.
349caa9b
 # 2006-10-04 [HB]
 # o Made readCelUnits() a bit more clever if a 'cdf' structure with only
 #   cell indices is passed. Then all fields are just indices and one can
 #   call unlist immediately.  This speeds things up a bit.
f1d6fcf0
 # 2006-05-12 [HB]
 # o Rearranged order of arguments such that the most often used/most user-
 #   friendly arguments come first.  This was done as a first step after
 #   our developers meeting yesterday.
 # 2006-04-18 [HB]
 # o BUG FIX: When argument 'cdf' was a CDF list structure with elements
 #   'type' or 'direction', readCelUnits() would not read the correct cells
 #   because the values of 'type' and 'direction' would be included in the
 #   extracted list of cell indices.
90cb1239
 # 2006-04-15 [HB]
 # o BUG FIX: Passed '...' to both readCdfCellIndices() and readCel(), but
 #   should only be passed to the latter.
886f672a
 # 2006-04-01 [HB]
 # o Using readCdfCellIndices() instead of readCdfUnits().  Faster!
95092fca
 # o Added argument 'reorder'.  If TRUE, all cells are read in order to
886f672a
 #   minimize the jumping around in the file.  This speeds things up a lot!
 #   I tried this last week, but for some reason I did not see a difference.
ddd48129
 # 2006-03-29 [HB]
 # o Renamed argument 'map' to 'readMap'.
 # 2006-03-28 [HB]
 # o Unit and cell indices are now one-based.
 # o Renamed argument 'readCells' to 'readIndices' and same with the name of
 #   the returned group field.
 # 2006-03-26 [HB]
 # o Now only "x", "y", "intensities", "pixels", and "stdvs" values are
 #   returned.
 # 2006-03-24 [HB]
 # o Made the creation of the final CEL structure according to the CDF much
 #   faster.  Now it is about 4-6 times faster utilizing get(field) instead
 #   of cel[[field]].
 # o Tried to reorder cell indices in order to minimize jumping around in the
 #   file, but there seems to be no speed up at all doing this. Strange!
ad4b2701
 # 2006-03-14
 # o Updated code to make use of package R.utils only if it is available.
 # 2006-03-08
 # o Removed the usage of Arguments of R.utils.  This is because we might
 #   move this function to the affxparser package.  Still to be removed is
 #   the use of the Verbose class.
 # 2006-03-04
 # o Added argument 'map'.
 # o Removed all gc(). They slow down quite a bit.
 # 2006-02-27 [HB]
 # o BUG FIX: It was only stratifyBy="pmmm" that worked if more than one
 #   array was read.
 # 2006-02-23 [HB]
 # o The restructuring code is now more generic, e.g. it does not require
95092fca
 #   the 'stratifyBy' argument and can append multiple arrays of any
ad4b2701
 #   dimensions.
 # o Now the CDF file is search for where the CEL files lives too.
 # 2006-02-22 [HB]
 # o First test where argument 'cdf' is a CDF structure.  Fixed some bugs,
 #   but it works now.
 # o Simple redundancy test: The new code and the updated affxparser package
 #   works with the new aroma.affymetrix/rsp/ GUI.
 # o Now argument 'cdf' is checked to contain either 'cells' or 'x' & 'y'
95092fca
 #   group fields.  If 'x' and 'y', the cell indices are calculated from
 #   (x,y) and the chip layout obtained from the header of CDF file, which
ad4b2701
 #   has been searched for.
 # 2006-02-21 [HB]
 # o TO DO: Re implement all of this in a C function to speed things up
 #   further; it is better to put values in the right position from the
 #   beginning.
 # o Added arguments 'transforms' to be able to transform all probe signals
 #   at once.  This improves the speed further.
 # o Removed annotation of PM/MM dimension when 'stratifyBy="pmmm", because
 #   the resulting object increases ~33% in size.
 # o Improved speed for restructuring cell data about 20-25%.
 # o Now it is possible to read multiple CEL files.
 # o Making use of new 'readCells' in readCdfUnits(), which is much faster.
95092fca
 # o Replaced argument 'splitPmMm' with 'stratifyBy'.  This speeds up if
ad4b2701
 #   reading PM (or MM) only.
 # o BUG FIX: 'splitPmMm=TRUE' allocated PMs and MMs incorrectly.  The reason
 #   was that the indices are already in the correct PM/MM order from the
 #   splitPmMm in readCdfUnits() from which the (x,y) to cell indices are
 #   calculated.
 # o Updated to make use of the latest affxparser.
 # 2006-01-24 [HB]
 # o BUG FIX: Made some modifications a few days ago that introduced missing
 #   variables etc.
 # 2006-01-21 [HB]
 # o Added Rdoc comments.
 # 2006-01-16 [HB]
 # o Created by HB.
95092fca
 ############################################################################