R/readCcg.R
ede2c2f5
 #########################################################################/**
 # @RdocFunction readCcg
95092fca
 #
ede2c2f5
 # @title "Reads an Affymetrix Command Console Generic (CCG) Data file"
95092fca
 #
ede2c2f5
 # @synopsis
95092fca
 #
ede2c2f5
 # \description{
95092fca
 #   @get "title".  The CCG data file format is also known as the
ede2c2f5
 #   Calvin file format.
 # }
95092fca
 #
ede2c2f5
 # \arguments{
 #   \item{pathname}{The pathname of the CCG file.}
 #   \item{verbose}{An @integer specifying the verbose level. If 0, the
 #     file is parsed quietly.  The higher numbers, the more details.}
 #   \item{.filter}{A @list.}
 #   \item{...}{Not used.}
 # }
95092fca
 #
ede2c2f5
 # \value{
 #   A named @list structure consisting of ...
 # }
95092fca
 #
ede2c2f5
 #  \details{
 #    Note, the current implementation of this methods does not utilize the
 #    Affymetrix Fusion SDK library.  Instead, it is implemented in R from the
 #    file format definition [1].
 #  }
 #
 # \section{About the CCG file format}{
 #  A CCG file, consists of a "file header", a "generic data header",
 #  and "data" section, as outlined here:
 #  \itemize{
 #   \item File Header
 #   \item Generic Data Header (for the file)
 #    \enumerate{
 #     \item Generic Data Header (for the files 1st parent)
95092fca
 #      \enumerate{
ede2c2f5
 #       \item Generic Data Header (for the files 1st parents 1st parent)
 #       \item Generic Data Header (for the files 1st parents 2nd parent)
 #       \item ...
 #       \item Generic Data Header (for the files 1st parents Mth parent)
 #      }
 #    \item Generic Data Header (for the files 2nd parent)
 #    \item ...
 #    \item Generic Data Header (for the files Nth parent)
 #   }
 #   \item Data
 #    \enumerate{
71f54ad1
 #     \item Data Group #1
ede2c2f5
 #      \enumerate{
71f54ad1
 #       \item Data Set #1
6f7db567
 #        \itemize{
ede2c2f5
 #         \item Parameters
 #         \item Column definitions
 #         \item Matrix of data
 #        }
71f54ad1
 #       \item Data Set #2
ede2c2f5
 #       \item ...
71f54ad1
 #       \item Data Set #L
ede2c2f5
 #      }
71f54ad1
 #     \item Data Group #2
ede2c2f5
 #     \item ...
71f54ad1
 #     \item Data Group #K
ede2c2f5
 #    }
 #  }
 # }
 #
76cf4b26
 # @author "HB"
95092fca
 #
ede2c2f5
 #  \seealso{
 #    @see "readCcgHeader".
 #    @see "readCdfUnits".
 #  }
95092fca
 #
ede2c2f5
 # \references{
 #  [1] Affymetrix Inc, Affymetrix GCOS 1.x compatible file formats,
 #      April, 2006.
 #      \url{http://www.affymetrix.com/support/developer/}\cr
 # }
 #
 # @keyword "file"
 # @keyword "IO"
 #*/#########################################################################
 readCcg <- function(pathname, verbose=0, .filter=NULL, ...) {
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Validate arguments
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Argument '.filter':
   hasFilter <- FALSE;
   if (!is.null(.filter)) {
     if (!is.list(.filter)) {
b5de40e6
       stop("Argument '.filter' must be a list: ", mode(.filter));
ede2c2f5
     }
     hasFilter <- TRUE;
   }
 
a3b26d44
 
ede2c2f5
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Open file
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   con <- file(pathname, open="rb");
   on.exit(close(con));
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Allocate return structure
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   ccg <- list();
95092fca
 
ede2c2f5
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Read file header
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   fhdr <- .readCcgFileHeader(con);
   if (hasFilter) {
     if (!identical(.filter$header, FALSE))
       ccg$fileHeader <- fhdr;
   } else {
     ccg$fileHeader <- fhdr;
   }
 
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Read the data header
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   ccg$genericDataHeader <- .readCcgDataHeader(con, .filter=.filter$dataHeader);
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Read the data
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   dataGroups <- .readCcgDataGroups(con, .filter=.filter$data, .fileHeader=fhdr);
   if (hasFilter) {
     if (!identical(.filter$dataGroups, FALSE))
       ccg$dataGroups <- dataGroups;
   } else {
     ccg$dataGroups <- dataGroups;
   }
95092fca
 
ede2c2f5
   ccg;
 } # readCcg()
 
 
 
 .readCcgDataGroups <- function(pathname, .filter=NULL, .fileHeader=NULL, ...) {
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Validate arguments
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Argument 'pathname':
   if (inherits(pathname, "connection")) {
     con <- pathname;
   } else {
     if (!file.exists(pathname))
       stop("File not found: ", pathname);
     con <- file(pathname, open="rb");
     on.exit(close(con));
   }
 
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Read file header?
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   if (is.null(.fileHeader)) {
     .fileHeader <- .readCcgFileHeader(con);
   }
 
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Read data groups
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   currFilter <- .filter;
   nextDataGroupStart <- .fileHeader$dataGroupStart;
   dataGroups <- list();
24277d85
   for (gg in seq_len(.fileHeader$nbrOfDataGroups)) {
95092fca
     dataGroupHeader <- .readCcgDataGroupHeader(con,
ede2c2f5
                                           fileOffset=nextDataGroupStart);
     # Next data group
     nextDataGroupStart <- dataGroupHeader$nextGroupStart;
 
     # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     # Apply filter
     # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
 #     if (!is.null(.filter)) {
 #       currFilter <- NULL;
 #       if (is.null(names(.filter))) {
 #         currFilter <- .filter[[gg]];
 #       } else {
 #         pos <- match(dataGroupHeader$name, names(.filter));
 #         if (length(pos) > 0)
 #           currFilter <- .filter[[pos]];
 #       }
 #     }
 #     str(currFilter);
 
     # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     # Read data sets
     # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
95092fca
     offset <- dataGroupHeader$dataSetStart;
ede2c2f5
     dss <- vector("list", dataGroupHeader$nbrOfDataSets);
     names <- character(dataGroupHeader$nbrOfDataSets);
24277d85
     for (kk in seq_along(dss)) {
95092fca
       ds <- .readCcgDataSet(con, fileOffset=offset);
a3b26d44
 
95092fca
       offset <- ds$nextDataSetStart;
ede2c2f5
       dss[[kk]] <- ds;
       names[kk] <- ds$name;
     };
     names(dss) <- names;
95092fca
 
ede2c2f5
     dataGroup <- list(
       header = dataGroupHeader,
       dataSets = dss
     );
     dataGroups <- c(dataGroups, list(dataGroup));
   } # while (nextDataGroupStart != 0)
   names(dataGroups) <- unlist(lapply(dataGroups, FUN=function(dg) {
     dg$header$name
   }), use.names=FALSE);
 
   dataGroups;
 } # .readCcgDataGroups()
 
 
 
 .readCcgDataGroupHeader <- function(con, fileOffset=NULL, ...) {
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Local functions
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
6f7db567
   rawToString <- function(raw, ...) {
     # This approach drops all '\0', in order to avoid warnings
     # in rawToChar().  Note, it does not truncate the string after
     # the first '\0'.  However, such strings should never occur in
     # the first place.
     raw <- raw[raw != as.raw(0)];
     rawToChar(raw);
   }
 
ede2c2f5
   readInt <- function(con, n=1, ...) {
     readBin(con, what=integer(), size=4, signed=TRUE, endian="big", n=n);
   }
 
   readUInt <- function(con, n=1, ...) {
7d16a177
     # NOTE: Ideally we would use signed=FALSE here, but there is no
     # integer data type in R that can hold 4-byte unsigned integers.
     # Because of this limitation, readBin() will give a warning that
     # signed=FALSE only works for size=1 or 2.
     # WORKAROUND: Use signed=TRUE and assume there are no values
     # greater that .Machine$integer.max == 2^31-1. /HB 2015-04-15
b3f97f6d
     readBin(con, what=integer(), size=4, signed=TRUE, endian="big", n=n);
ede2c2f5
   }
 
   readWString <- function(con, ...) {
     nchars <- readInt(con);
     if (nchars == 0)
       return("");
     bfr <- readBin(con, what=raw(), n=2*nchars);
     bfr <- bfr[seq(from=2, to=length(bfr), by=2)];
6f7db567
     rawToString(bfr);
ede2c2f5
   }
 
   readRaw <- function(con, ...) {
     n <- readInt(con);
     if (n == 0)
       return(raw(0));
     readBin(con, what=raw(0), n=n);
   }
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
95092fca
   #
ede2c2f5
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   if (!is.null(fileOffset)) {
     seek(con=con, where=fileOffset, offset="start", rw="read");
   }
 
   # Data Group
95092fca
   # This section describes the data group. A data group is a group
ede2c2f5
   # of data sets. The file supports one or more data groups in a file.
95092fca
   #
ede2c2f5
   # Item 	Description 	Type
   # 1 	File position of the next data group. When this is the last
   #     data group in the file, the value should be 0. 	UINT
   # 2 	File position of the first data set within the data group. 	UINT
   # 3 	The number of data sets within the data group. 	INT
   # 4 	The data group name. 	WSTRING
     nextGroupStart=readUInt(con)
     dataSetStart=readUInt(con)
     nbrOfDataSets=readInt(con)
     name=readWString(con)
 
   dataGroupHeader <- list(
     nextGroupStart=nextGroupStart,
     dataSetStart=dataSetStart,
     nbrOfDataSets=nbrOfDataSets,
     name=name
   )
 
   dataGroupHeader;
 } # .readCcgDataGroupHeader()
 
 
 
 
 .readCcgDataSet <- function(con, fileOffset=NULL, ...) {
   # Value Types
   # The following table defines the numeric values for the value types.
95092fca
   # The value type is used to representing the type of value stored in
ede2c2f5
   # the file.
   #
   # Value 	Type
   # 0 	BYTE
   # 1 	UBYTE
   # 2 	SHORT
   # 3 	USHORT
   # 4 	INT
   # 5 	UINT
   # 6 	FLOAT
a3b26d44
   # 7 	STRING
   # 8 	WSTRING
95092fca
   whats <- c("integer", "integer", "integer", "integer", "integer",
a3b26d44
             "integer", "double", "character", "character");
   names(whats) <- c("BYTE", "UBYTE", "SHORT", "USHORT", "INT", "UINT", "FLOAT", "STRING", "WSTRING");
   signeds <- c(TRUE, FALSE, TRUE, FALSE, TRUE, FALSE, TRUE, TRUE, TRUE);
   sizes <- c(1, 1, 2, 2, 4, 4, 4, 1, 2);
ede2c2f5
 
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
   # Local functions
   # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
6f7db567
   rawToString <- function(raw, ...) {
     # This approach drops all '\0', in order to avoid warnings
     # in rawToChar().  Note, it does not truncate the string after
     # the first '\0'.  However, such strings should never occur in
     # the first place.
     raw <- raw[raw != as.raw(0)];
     rawToChar(raw);
   }
 
ede2c2f5
   readByte <- function(con, n=1, ...) {
     readBin(con, what=integer(), size=1, signed=TRUE, endian="big", n=n);
   }
 
   readInt <- function(con, n=1, ...) {
     readBin(con, what=integer(), size=4, signed=TRUE, endian="big", n=n);
   }
 
   readUInt <- function(con, n=1, ...) {
7d16a177
     # NOTE: Ideally we would use signed=FALSE here, but there is no
     # integer data type in R that can hold 4-byte unsigned integers.
     # Because of this limitation, readBin() will give a warning that
     # signed=FALSE only works for size=1 or 2.
     # WORKAROUND: Use signed=TRUE and assume there are no values
     # greater that .Machine$integer.max == 2^31-1. /HB 2015-04-15
b3f97f6d
     readBin(con, what=integer(), size=4, signed=TRUE, endian="big", n=n);
ede2c2f5
   }
 
   readString <- function(con, ...) {
     nchars <- readInt(con);
     if (nchars == 0)
       return("");
     readChar(con, nchars=nchars);
   }
 
   readWString <- function(con, ...) {
     nchars <- readInt(con);
     if (nchars == 0)
       return("");
     bfr <- readBin(con, what=raw(), n=2*nchars);
     bfr <- bfr[seq(from=2, to=length(bfr), by=2)];
6f7db567
     rawToString(bfr);
ede2c2f5
   }
 
   readRaw <- function(con, ...) {
     n <- readInt(con);
     if (n == 0)
       return(raw(0));
     readBin(con, what=raw(0), n=n);
   }
 
   readWVT <- function(con, ...) {
     name <- readWString(con);
a3b26d44
     raw <- readRaw(con);
ede2c2f5
     type <- readWString(con);
 
     # Update data types
     # * text/x-calvin-integer-8
     # * text/x-calvin-unsigned-integer-8
     # * text/x-calvin-integer-16
     # * text/x-calvin-unsigned-integer-16
     # * text/x-calvin-integer-32
     # * text/x-calvin-unsigned-integer-32
     # * text/x-calvin-float
     # * text/plain
a3b26d44
 
ede2c2f5
     n <- length(raw);
a3b26d44
 
 #    cat(sprintf("Reading n=%d records of type '%s' named '%s'.\n", n, type, name));
 
95092fca
     value <- switch(type,
ede2c2f5
       "text/ascii" = {
6f7db567
         rawToString(raw);
ede2c2f5
       },
 
       "text/plain" = {
         # Unicode/UTF-16?!?
         raw <- matrix(raw, ncol=2, byrow=TRUE);
         raw <- raw[,2];
6f7db567
         rawToString(raw);
ede2c2f5
       },
 
       "text/x-calvin-integer-8" = {
         readBin(raw, what=integer(0), endian="big", size=1, signed=TRUE, n=n);
       },
 
       "text/x-calvin-unsigned-integer-8" = {
         readBin(raw, what=integer(0), endian="big", size=1, signed=FALSE, n=n);
       },
 
       "text/x-calvin-integer-16" = {
a3b26d44
         readBin(raw, what=integer(0), endian="big", size=2, signed=TRUE, n=n);
ede2c2f5
       },
 
       "text/x-calvin-unsigned-integer-16" = {
a3b26d44
         readBin(raw, what=integer(0), endian="big", size=2, signed=FALSE, n=n);
ede2c2f5
       },
 
       "text/x-calvin-integer-32" = {
a3b26d44
         readBin(raw, what=integer(0), endian="big", size=4, signed=TRUE, n=n);
ede2c2f5
       },
 
       "text/x-calvin-unsigned-integer-32" = {
7d16a177
         # NOTE: Ideally we would use signed=FALSE here, but there is no
         # integer data type in R that can hold 4-byte unsigned integers.
         # Because of this limitation, readBin() will give a warning that
         # signed=FALSE only works for size=1 or 2.
         # WORKAROUND: Use signed=TRUE and assume there are no values
         # greater that .Machine$integer.max == 2^31-1. /HB 2015-04-15
b3f97f6d
         readBin(raw, what=integer(0), endian="big", size=4, signed=TRUE, n=n);
ede2c2f5
       },
 
       "text/x-calvin-float" = {
a3b26d44
         readBin(raw, what=double(0), endian="big", size=4, n=n);
ede2c2f5
       },
 
       {
         raw;
       }
     ) # switch()
 
     list(name=name, value=value, raw=raw, type=type);
   } # readWVT()
 
   readWBI <- function(con, ...) {
     list(name=readWString(con), type=readByte(con), size=readInt(con));
   }
 
 
   if (!is.null(fileOffset)) {
     seek(con=con, where=fileOffset, offset="start", rw="read");
   }
 
 #  Data Set
 #  This section describes the data for a single data set item
 #  (probe set, sequence, allele, etc.). The file supports one
 #  or more data sets within a data group.
95092fca
 #
ede2c2f5
 #  Item 	Description 	Type
 #  1 	The file position of the first data element in the data set.
 #     This is the first byte after the data set header. 	UINT
 #  2 	The file position of the next data set within the data group.
95092fca
 #     When this is the last data set in the data group the value
ede2c2f5
 #     shall be 1 byte past the end of the data set. This way the size
 #     of the data set may be determined. 	UINT
 #  3 	The data set name. 	WSTRING
 #  4 	The number of name/value/type parameters. 	INT
 #  5 	Array of name/value/type parameters. 	(WSTRING / VALUE / TYPE) [ ]
 #  6 	Number of columns in the data set.
 #     Example: For expression arrays, columns may include signal, p-value,
 #     detection call and for genotyping arrays columns may include allele
95092fca
 #     call, and confidence value. For universal arrays, columns may
ede2c2f5
 #     include probe set intensities and background. 	UINT
 #  7 	An array of column names, column value types and column type sizes
 #     (one per column).
 #     The value type shall be represented by the value from the value type
 #     table. The size shall be the size of the type in bytes. For strings,
 #     this value shall be the size of the string in bytes plus 4 bytes for
95092fca
 #     the string length written before the string in the file.
ede2c2f5
 #     (WSTRING / BYTE / INT) [ ]
 #  8 	The number of rows in the data set. 	UINT
95092fca
 #  9 	The data set table, consisting of rows of columns (data values).
ede2c2f5
 #     The specific type and size of each column is described by the data
 #     and size types above. 	ROW [ ]
   dataSet <- list(
     elementsStart=readUInt(con),
     nextDataSetStart=readUInt(con),
     name=readWString(con)
   )
   # Reading parameters
   nbrOfParams <- readInt(con);
   params <- vector("list", nbrOfParams);
   names <- character(nbrOfParams);
24277d85
   for (kk in seq_len(nbrOfParams)) {
ede2c2f5
     wvt <- readWVT(con);
     names[kk] <- wvt$name;
     value <- wvt$value;
     attr(value, "mimeType") <- wvt$type;
     params[[kk]] <- value;
   }
   names(params) <- names;
   dataSet$parameters <- params;
 
   # Reading columns
   nbrOfColumns <- readUInt(con);
   columns <- vector("list", nbrOfColumns);
   names <- character(nbrOfColumns);
   colWhats <- vector("list", nbrOfColumns);
   bytesPerRow <- 0;
24277d85
   for (cc in seq_len(nbrOfColumns)) {
ede2c2f5
     wbi <- readWBI(con);
     names[cc] <- wbi$name;
     what <- whats[wbi$type+1];
     signed <- signeds[wbi$type+1];
     size <- wbi$size;
     bytesPerRow <- bytesPerRow + size;
     attr(what, "name") <- names(whats)[wbi$type+1];
     attr(what, "signed") <- signed;
     attr(what, "size") <- size;
     colWhats[[cc]] <- what;
   }
a3b26d44
   names(colWhats) <- names;
ede2c2f5
   bytesPerRow <- as.integer(bytesPerRow);
 
   nbrOfRows <- readUInt(con);
   totalNbrOfBytes <- nbrOfRows * bytesPerRow;
 
   # Skip to the first element
   seek(con, which=dataSet$elementsStart, offset="start", rw="read");
   # Read all data row by row
   raw <- readBin(con, what=raw(), n=totalNbrOfBytes);
   dim(raw) <- c(bytesPerRow, nbrOfRows);
 
   table <- vector("list", nbrOfColumns);
   colsOffset <- 0;
24277d85
   for (cc in seq_len(nbrOfColumns)) {
ede2c2f5
     what <- colWhats[[cc]];
     signed <- attr(what, "signed");
     size <- attr(what, "size");
 
     if (what == "character") {
a3b26d44
       value <- matrix(raw[1:4,], nrow=nbrOfRows, ncol=4);
       raw <- raw[-c(1:4),,drop=FALSE];
 
       # Get the number of characters per string (all equal)
 ##      nchars <- readInt(con=value, n=nbrOfRows);
 ##      nchars <- nchars[1];
       nchars <- readInt(con=value, n=1);
95092fca
       value <- NULL; # Not needed anymore
a3b26d44
 
       ccs <- 1:(size-4);
       value <- raw[ccs,];
       raw <- raw[-ccs,,drop=FALSE];
       value <- rawToChar(value, multiple=TRUE);
ede2c2f5
       dim(value) <- c(nchars, nbrOfRows);
a3b26d44
 
       # Build strings using vectorization (not apply()!)
       strs <- NULL;
24277d85
       for (pp in seq_len(nrow(value))) {
a3b26d44
         valuePP <- value[1,,drop=FALSE];
         value <- value[-1,,drop=FALSE];
         if (pp == 1) {
           strs <- valuePP;
         } else {
           strs <- paste(strs, valuePP, sep="");
         }
95092fca
         valuePP <- NULL; # Not needed anymore
a3b26d44
       }
       value <- strs;
95092fca
       strs <- NULL; # Not needed anymore
ede2c2f5
     } else {
a3b26d44
       ccs <- 1:size;
       value <- raw[ccs,,drop=FALSE];
       raw <- raw[-ccs,,drop=FALSE];
       value <- readBin(con=value, what=what, size=size, signed=signed, endian="big", n=nbrOfRows);
ede2c2f5
     }
a3b26d44
 
ede2c2f5
     table[[cc]] <- value;
     colsOffset <- colsOffset + size;
3f8dfde2
   } # for (cc ...)
a3b26d44
 
   # Turn into a data frame
   attr(table, "row.names") <- .set_row_names(length(table[[1]]));
   attr(table, "names") <- names;
   class(table) <- "data.frame";
 
ede2c2f5
   dataSet$table <- table;
 
   dataSet;
 } # .readCcgDataSet()
 
 
 ############################################################################
 # HISTORY:
b5de40e6
 # 2012-05-18
 # o Now using stop() instead of throw().
b3f97f6d
 # 2011-11-01
 # o CLEANUP: Changed signed=FALSE to signed=TRUE for readBin() calls
 #   reading 4-byte integers in internal .readCcgDataGroupHeader() and
 #   .readCcgDataSet().
6f7db567
 # 2009-02-10
 # o Added internal rawToString() replacing rawToChar() to avoid warnings
 #   on "truncating string with embedded nul".
3f8dfde2
 # 2008-08-23
 # o SPEED UP: Removed all gc() calls.
a3b26d44
 # 2008-01-13
 # o Removed dependency on intToChar() in R.utils.
 # o BUG FIX/UPDATE: The file format was updated between April 2006 and
 #   November 2007.  More specifically, the so called "Value Types" were
 #   changed/corrected.  Before values 7:9 were 'DOUBLE', 'STRING', and
 #   'WSTRING'.  Now 7:8 are 'STRING' and 'WSTRING' and there is no longer
 #   a 'DOUBLE'.
 #   This was detected while trying to read a CNCHP file outputted by the
 #   new Affymetrix Genotyping Console 2.0.  We can now read these files.
ede2c2f5
 # 2007-08-16
 # o Now it is only readCcg() and readCcgHeader() that are public.  The
 #   other readCcgNnn() functions are renamed to .readCcgNnn().
 # o Now the read data is converted according to the mime type.  See internal
 #   readWVT() function.  The code is still ad hoc, so it is not generic.
 #   For instance, it basically assumes that Unicode strings only contain
 #   ASCII/ASCII-8 characters.
 # 2006-11-06
 # o Tested on Test3-1-121502.calvin.CEL and Test3-1-121502.calvin.CDF.
95092fca
 # o Created.
 ############################################################################