ImageReader.st
author claus
Fri, 16 Jul 1993 11:42:20 +0200
changeset 0 48194c26a46c
child 2 b35336ab0de3
permissions -rw-r--r--
Initial revision

"
 COPYRIGHT (c) 1991-93 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Object subclass:#ImageReader
         instanceVariableNames:'width height data byteOrder inStream outStream
                                photometric samplesPerPixel bitsPerSample
                                colorMap'
         classVariableNames:''
         poolDictionaries:''
         category:'Graphics-Support'
!

ImageReader comment:'

COPYRIGHT (c) 1991-93 by Claus Gittinger
              All Rights Reserved

common functions for image-readers (i.e. TIFFReader, GIFReader etc.)

%W% %E%
written Summer 91 by claus
'!

!ImageReader class methodsFor:'testing'!

isValidImageFile:aFileName
    "return true, if aFileName contains an image this
     reader understands - should be redefined in subclasses"

    ^ false
! !

!ImageReader class methodsFor:'fileIn / fileOut'!

fromFile:aFileName
    |reader image|

    reader := self new.
    (reader fromFile:aFileName) notNil ifTrue:[
        image := Image new.
        image width:(reader width).
        image height:(reader height).
        image photometric:(reader photometric).
        image samplesPerPixel:(reader samplesPerPixel).
        image bitsPerSample:(reader bitsPerSample).
        image colorMap:(reader colorMap).
        image data:(reader data).
        ^ image
    ].
    ^ nil
!

save:anImage onFile:aFileName
    ^ (self basicNew) save:anImage onFile:aFileName
! !

!ImageReader methodsFor:'accessing'!

width
    ^ width
!

height 
    ^ height
!

data 
    ^ data
!

photometric
    ^ photometric
!

colorMap
    ^ colorMap
!

samplesPerPixel
    ^ samplesPerPixel
!

bitsPerSample
    ^ bitsPerSample
! !

!ImageReader methodsFor:'fileIn / fileOut'!

fromFile:aFileName
    ^ self subclassResponsibility
!

save:image onFile:aFileName
    ^ self subclassResponsibility
! !

!ImageReader methodsFor:'i/o support'!

readLong
    |bytes val|

    bytes := ByteArray new:4.
    inStream nextBytes:4 into:bytes.
    (byteOrder == #lsb) ifTrue:[
        val := bytes at:4.
        val := val * 256 + (bytes at:3).
        val := val * 256 + (bytes at:2).
        val := val * 256 + (bytes at:1)
    ] ifFalse:[
        val := bytes at:1.
        val := val * 256 + (bytes at:2).
        val := val * 256 + (bytes at:3).
        val := val * 256 + (bytes at:4)
    ].
    ^ val
!

readShort
    |bytes val|

    bytes := ByteArray new:2.
    inStream nextBytes:2 into:bytes.
    (byteOrder == #lsb) ifTrue:[
        val := bytes at:2.
        val := val * 256 + (bytes at:1)
    ] ifFalse:[
        val := bytes at:1.
        val := val * 256 + (bytes at:2)
    ].
    ^ val
!

readShortLong
    |bytes val|

    bytes := ByteArray new:4.
    inStream nextBytes:4 into:bytes.
    (byteOrder == #lsb) ifTrue:[
        val := bytes at:2.
        val := val * 256 + (bytes at:1)
    ] ifFalse:[
        val := bytes at:3.
        val := val * 256 + (bytes at:4)
    ].
    ^ val
!

writeLong:anInteger
    |bytes i|

    i := anInteger.
    bytes := ByteArray new:4.
    (byteOrder == #lsb) ifTrue:[
        bytes at:1 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:2 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:3 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:4 put:(i bitAnd:16rFF).
    ] ifFalse:[
        bytes at:4 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:3 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:2 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:1 put:(i bitAnd:16rFF).
    ].
    outStream nextPutBytes:4 from:bytes
!

writeShort:anInteger
    |bytes i|

    i := anInteger.
    bytes := ByteArray new:2.
    (byteOrder == #lsb) ifTrue:[
        bytes at:1 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:2 put:(i bitAnd:16rFF).
    ] ifFalse:[
        bytes at:2 put:(i bitAnd:16rFF).
        i := i // 256.
        bytes at:1 put:(i bitAnd:16rFF).
    ].
    outStream nextPutBytes:2 from:bytes
! !

!ImageReader class methodsFor:'decompression support'!

decompressCCITT3From:srcBytes into:dstBytes startingAt:offset count:count 
    "same as above but using primitive for speed"
%{
    if ((_Class(srcBytes) == ByteArray)
     && (_Class(dstBytes) == ByteArray)
     && _isSmallInteger(offset)
     && _isSmallInteger(count)) {
        decodeCCITTgroup3(_ByteArrayInstPtr(srcBytes)->ba_element,
                          _ByteArrayInstPtr(dstBytes)->ba_element
                          + _intVal(offset) - 1,
                          _intVal(count));
        RETURN ( self );
    }
%}
.
    self primitiveFailed
!

decompressLZWFrom:srcBytes count:count into:dstBytes startingAt:offset
%{
    if ((_Class(srcBytes) == ByteArray)
     && (_Class(dstBytes) == ByteArray)
     && _isSmallInteger(offset)
     && _isSmallInteger(count)) {
        decodeLZW(_ByteArrayInstPtr(srcBytes)->ba_element,
                  _ByteArrayInstPtr(dstBytes)->ba_element
                  + _intVal(offset) - 1,
                  _intVal(count));
        RETURN ( self );
    }
%}
.
    self primitiveFailed
!

decodeDelta:step in:data width:width height:height
    (step ~~ 3) ifTrue:[
        ^ self error:'only rgb pictures supported'
    ].

%{
    if ((_Class(data) == ByteArray)
     && _isSmallInteger(width)
     && _isSmallInteger(height)) {
        decodeDelta(_ByteArrayInstPtr(data)->ba_element,
                    _intVal(width), _intVal(height));
        RETURN ( self );
    }
%}
.
    self primitiveFailed
!

decompressGIFFrom:srcBytes count:count into:dstBytes startingAt:offset codeLen:codeLen
%{
    if ((_Class(srcBytes) == ByteArray)
     && (_Class(dstBytes) == ByteArray)
     && _isSmallInteger(codeLen)
     && _isSmallInteger(offset)
     && _isSmallInteger(count)) {
        decodeGIF(_ByteArrayInstPtr(srcBytes)->ba_element,
                  _ByteArrayInstPtr(dstBytes)->ba_element
                  + _intVal(offset) - 1,
                  _intVal(count),
                  _intVal(codeLen));
        RETURN ( self );
    }
%}
.
    self primitiveFailed
! !

%{

/*
 * ccitt decompression
 */
static short *whiteCountTable;
static char  *whiteShiftTable;
static short *blackCountTable;
static char  *blackShiftTable;

struct ccitt_def {
    unsigned short bits;
    short nBits;
};

static struct ccitt_def 
whiteDef[] = {
    { 0x3500, 8 }, /* 0 */
    { 0x1c00, 6 },
    { 0x7000, 4 },
    { 0x8000, 4 },
    { 0xb000, 4 },
    { 0xc000, 4 },
    { 0xe000, 4 },
    { 0xf000, 4 },
    { 0x9800, 5 },
    { 0xA000, 5 },
    { 0x3800, 5 }, /* 10 */
    { 0x4000, 5 },
    { 0x2000, 6 },
    { 0x0c00, 6 },
    { 0xd000, 6 },
    { 0xd400, 6 },
    { 0xa800, 6 },
    { 0xac00, 6 },
    { 0x4e00, 7 },
    { 0x1800, 7 },
    { 0x1000, 7 }, /* 20 */
    { 0x2e00, 7 },
    { 0x0600, 7 },
    { 0x0800, 7 },
    { 0x5000, 7 },
    { 0x5600, 7 },
    { 0x2600, 7 },
    { 0x4800, 7 },
    { 0x3000, 7 },
    { 0x0200, 8 },
    { 0x0300, 8 }, /* 30 */ 
    { 0x1a00, 8 }, 
    { 0x1b00, 8 }, 
    { 0x1200, 8 }, 
    { 0x1300, 8 }, 
    { 0x1400, 8 }, 
    { 0x1500, 8 }, 
    { 0x1600, 8 }, 
    { 0x1700, 8 }, 
    { 0x2800, 8 }, 
    { 0x2900, 8 }, /* 40 */
    { 0x2a00, 8 }, 
    { 0x2b00, 8 }, 
    { 0x2c00, 8 }, 
    { 0x2d00, 8 }, 
    { 0x0400, 8 }, 
    { 0x0500, 8 }, 
    { 0x0a00, 8 }, 
    { 0x0b00, 8 }, 
    { 0x5200, 8 }, 
    { 0x5300, 8 }, /* 50 */
    { 0x5400, 8 }, 
    { 0x5500, 8 }, 
    { 0x2400, 8 }, 
    { 0x2500, 8 }, 
    { 0x5800, 8 }, 
    { 0x5900, 8 }, 
    { 0x5a00, 8 }, 
    { 0x5b00, 8 }, 
    { 0x4a00, 8 }, 
    { 0x4b00, 8 }, /* 60 */
    { 0x3200, 8 }, 
    { 0x3300, 8 }, 
    { 0x3400, 8 }, 
/* ---------------- */
    { 0xd800, 5 }, /* 64 */
    { 0x9000, 5 }, /* 128 */
    { 0x5c00, 6 }, /* 192 */
    { 0x6e00, 7 }, /* 256 */
    { 0x3600, 8 }, /* 320 */
    { 0x3700, 8 },
    { 0x6400, 8 },
    { 0x6500, 8 },
    { 0x6800, 8 },
    { 0x6700, 8 }, /* 640 */
    { 0x6600, 9 }, /* 704 */
    { 0x6680, 9 },
    { 0x6900, 9 },
    { 0x6980, 9 },
    { 0x6a00, 9 },
    { 0x6a80, 9 },
    { 0x6b00, 9 },
    { 0x6b80, 9 },
    { 0x6c00, 9 },
    { 0x6c80, 9 },
    { 0x6d00, 9 },
    { 0x6d80, 9 },
    { 0x4c00, 9 },
    { 0x4c80, 9 },
    { 0x4d00, 9 }, /* 1600 */
    { 0x6000, 6 }, /* 1664 */
    { 0x4d80, 9 }, /* 1728 */
/* -------------------------------- */
    { 0x0100, 11 }, /* 1792 */
    { 0x0180, 11 },
    { 0x01a0, 11 }, /* 1920 */
    { 0x0120, 12 }, /* 1984 */
    { 0x0130, 12 },
    { 0x0140, 12 },
    { 0x0150, 12 },
    { 0x0160, 12 },
    { 0x0170, 12 },
    { 0x01c0, 12 },
    { 0x01d0, 12 },
    { 0x01e0, 12 },
    { 0x01f0, 12 }, /* 2560 */
/* -------------------------------- */
    { 0x0010, 12 }, /* EOL */
};

static struct ccitt_def 
blackDef[] = {
    { 0x0dc0, 10 }, /* 0 */
    { 0x4000, 3 },
    { 0xc000, 2 },
    { 0x8000, 2 },
    { 0x6000, 3 },
    { 0x3000, 4 },
    { 0x2000, 4 },
    { 0x1800, 5 },
    { 0x1400, 6 },
    { 0x1000, 6 },
    { 0x0800, 7 }, /* 10 */
    { 0x0a00, 7 },
    { 0x0e00, 7 },
    { 0x0400, 8 },
    { 0x0700, 8 },
    { 0x0c00, 9 },
    { 0x05c0, 10 },
    { 0x0600, 10 },
    { 0x0200, 10 },
    { 0x0ce0, 11 },
    { 0x0d00, 11 }, /* 20 */
    { 0x0d80, 11 },
    { 0x06e0, 11 },
    { 0x0500, 11 },
    { 0x02e0, 11 },
    { 0x0300, 11 },
    { 0x0ca0, 12 },
    { 0x0cb0, 12 },
    { 0x0cc0, 12 },
    { 0x0cd0, 12 }, 
    { 0x0680, 12 }, /* 30 */
    { 0x0690, 12 }, 
    { 0x06a0, 12 }, 
    { 0x06b0, 12 }, 
    { 0x0d20, 12 }, 
    { 0x0d30, 12 }, 
    { 0x0d40, 12 }, 
    { 0x0d50, 12 }, 
    { 0x0d60, 12 }, 
    { 0x0d70, 12 },
    { 0x06c0, 12 }, /* 40 */ 
    { 0x06d0, 12 }, 
    { 0x0da0, 12 }, 
    { 0x0db0, 12 }, 
    { 0x0540, 12 }, 
    { 0x0550, 12 }, 
    { 0x0560, 12 }, 
    { 0x0570, 12 }, 
    { 0x0640, 12 }, 
    { 0x0650, 12 },
    { 0x0520, 12 }, /* 50 */ 
    { 0x0530, 12 }, 
    { 0x0240, 12 }, 
    { 0x0370, 12 }, 
    { 0x0380, 12 }, 
    { 0x0270, 12 }, 
    { 0x0280, 12 }, 
    { 0x0580, 12 }, 
    { 0x0590, 12 }, 
    { 0x02b0, 12 },
    { 0x02c0, 12 }, /* 60 */ 
    { 0x05a0, 12 }, 
    { 0x0660, 12 }, 
    { 0x0670, 12 }, 
/* ---------------- */
    { 0x03c0, 10 }, /* 64 */
    { 0x0c80, 12 }, /* 128 */
    { 0x0c90, 12 }, /* 192 */
    { 0x05b0, 12 }, /* 256 */
    { 0x0330, 12 }, /* 320 */
    { 0x0340, 12 },
    { 0x0350, 12 }, /* 448 */
    { 0x0360, 13 }, /* 512 */
    { 0x0368, 13 },
    { 0x0250, 13 }, /* 640 */
    { 0x0258, 13 }, /* 704 */
    { 0x0260, 13 },
    { 0x0268, 13 },
    { 0x0390, 13 },
    { 0x0398, 13 },
    { 0x03a0, 13 },
    { 0x03a8, 13 },
    { 0x03b0, 13 },
    { 0x03b8, 13 },
    { 0x0290, 13 },
    { 0x0298, 13 },
    { 0x02a0, 13 },
    { 0x02a8, 13 },
    { 0x02d0, 13 },
    { 0x02d8, 13 }, /* 1600 */
    { 0x0320, 13 }, /* 1664 */
    { 0x0328, 13 }, /* 1728 */
/* -------------------------------- */
};

static
initCCITTTables() {
    register cnt, bits, value;
    int nBits, index;

    if (whiteCountTable != (short *)0) return;

    whiteCountTable = (short *) malloc(sizeof(short) * 8192);
    whiteShiftTable = (char *) malloc(sizeof(char) * 8192);
    blackCountTable = (short *) malloc(sizeof(short) * 8192);
    blackShiftTable = (char *) malloc(sizeof(char) * 8192);

    for (index = 0; index < 8192; index++) {
        whiteCountTable[index] = -1;
        blackCountTable[index] = -1;
    }

    for (value = 0; value <= 63; value++) {
        nBits = whiteDef[value].nBits;
        bits = whiteDef[value].bits >> 3;
        for (cnt = 1 << (13 - nBits); cnt; cnt--, bits++) {
            whiteCountTable[bits] = value;
            whiteShiftTable[bits] = nBits;
        }
        nBits = blackDef[value].nBits;
        bits = blackDef[value].bits >> 3;
        for (cnt = 1 << (13 - nBits); cnt; cnt--, bits++) {
            blackCountTable[bits] = value;
            blackShiftTable[bits] = nBits;
        }
    }
    index = value;

    for (; value <= 1728; value += 64) {
        nBits = whiteDef[index].nBits;
        bits = whiteDef[index].bits >> 3;
        for (cnt = 1 << (13 - nBits); cnt; cnt--, bits++) {
            whiteCountTable[bits] = value;
            whiteShiftTable[bits] = nBits;
        }
        nBits = blackDef[index].nBits;
        bits = blackDef[index].bits >> 3;
        for (cnt = 1 << (13 - nBits); cnt; cnt--, bits++) {
            blackCountTable[bits] = value;
            blackShiftTable[bits] = nBits;
        }
        index++;
    }

    for (; value <= 2560; value += 64) {
        nBits = whiteDef[index].nBits;
        bits = whiteDef[index].bits >> 3;
        for (cnt = 1 << (13 - nBits); cnt; cnt--, bits++) {
            whiteCountTable[bits] = value;
            whiteShiftTable[bits] = nBits;
            blackCountTable[bits] = value;
            blackShiftTable[bits] = nBits;
        }
        index++;
    }
}

static short 
leftBits[] = {
     0, 0x80, 0xC0, 0xE0, 0xF0, 0xF8, 0xFC, 0xFE, 0xFF
};

decodeCCITTgroup3(from, to, len)
    unsigned char *from;
    register unsigned char *to;
{
    register cnt;
    register short *countPtr;
    register char *shiftPtr;
    unsigned bits, bits13;
    int shift, outCount, nBitsLess13;
    int outBitOffset;
    int nLeft, t;

    if (! whiteCountTable) initCCITTTables();

    countPtr = whiteCountTable;
    shiftPtr = whiteShiftTable;
    outCount = 0;
    outBitOffset = 0;
    bits = *from++;
    bits = (bits << 8) | *from++;
    nBitsLess13 = 3;
    for (;;) {
        bits13 = (bits >> nBitsLess13) & 0x1FFF;
        cnt = countPtr[bits13];
        if (cnt < 0) return;
        shift = shiftPtr[bits13];
        outCount += cnt;
        if (countPtr == blackCountTable) {
            /* toggle if it was a terminating code */
            if (cnt < 64) {
                countPtr = whiteCountTable;
                shiftPtr = whiteShiftTable;
            }

            /* draw cnt black bits */
            if (cnt) {
                if (outBitOffset) {
                    nLeft = 8 - outBitOffset;
                    if (cnt < nLeft) nLeft = cnt;
                    t = leftBits[nLeft] >> outBitOffset;
                    *to |= t;
                    cnt -= nLeft;
                    outBitOffset += nLeft;
                    if (outBitOffset >= 8) {
                        to++;
                        outBitOffset -= 8;
                    }
                }
                if (cnt > 256) {
                    while ((int)to & 3) {
                        *to++ = 0xFF;
                        cnt -= 8;
                    }
                    while (cnt >= 32) {
                        (*(long *)to) = 0xFFFFFFFF;
                        to += 4;
                        cnt -= 32;
                    }
                }
                while (cnt >= 8) {
                    *to++ = 0xFF;
                    cnt -= 8;
                }
                *to |= leftBits[cnt];
                outBitOffset += cnt;
            }
        } else {
            /* toggle if it was a terminating code */
            if (cnt < 64) {
                countPtr = blackCountTable;
                shiftPtr = blackShiftTable;
            }

            /* skip cnt bits */
            to += cnt >> 3;
            outBitOffset += cnt & 7;
            if (outBitOffset >= 8) {
                to++;
                outBitOffset -= 8;
            }
        }
        if (outCount >= len) return;

        nBitsLess13 -= shift;
        while (nBitsLess13 < 0) {
            bits = (bits << 8) | *from++;
            nBitsLess13 += 8;
        }
    }
}

/*
 * LZW decompression
 */
struct buffer {
        struct buffer *prev;
        unsigned char chars[8192 - 4];
};
        
decodeLZW(from, to, inCount)
    unsigned char *from;
    unsigned char *to;
{
    register unsigned code;
    unsigned char *strings[4096];
    short stringLen[4096];
    struct buffer *scratchBuffer;
    struct buffer *newBuffer;
    unsigned char *scratchPtr;
    int nScratch;
    unsigned nextCode, oldCode;
    register unsigned bits;
    int nBits, mask, shift;
    int i;
    int len;
    int codeLen = 9;

    scratchBuffer = (struct buffer *)malloc(sizeof(struct buffer));
    if (! scratchBuffer) return;
    scratchBuffer->prev = (struct buffer *)0;
    scratchPtr = scratchBuffer->chars;
    nScratch = sizeof(scratchBuffer->chars);

    for (i = 0; i < 256; i++) {
        *scratchPtr = i;
        strings[i] = scratchPtr++;
        stringLen[i] = 1;
    }

    nextCode = 258;
    nScratch -= 256;
    mask = 0x1FF;
    nBits = 0;
    bits = 0;
    while (inCount) {
        /* fetch code */
        while (nBits < codeLen) {
            bits = (bits<<8) | *from++;
            inCount--;
            nBits += 8;
        }
        shift = nBits - codeLen;
        code = (bits >> shift) & mask;
        bits &= ~(mask << shift);
        nBits -= codeLen;
        if (code == 257) break;
        if (code == 256) {
            if (! inCount)
                break;

            /* free stuff */
            while (scratchBuffer->prev) {
                newBuffer = scratchBuffer;
                scratchBuffer = scratchBuffer->prev;
                free(newBuffer);
            }
            /* reset everything */
            scratchPtr = scratchBuffer->chars + 256;
            nScratch = sizeof(scratchBuffer->chars) - 256;
            codeLen = 9;
            nextCode = 258;
            mask = 0x1FF;
            /* fetch code */
            while (nBits < codeLen) {
                bits = (bits<<8) | *from++;
                inCount--;
                nBits += 8;
            }
            shift = nBits - codeLen;
            code = (bits >> shift) & mask;
            bits &= ~(mask << shift);
            nBits -= codeLen;
            if (code == 257) break;
            /* add to output */
            *to++ = code;
            oldCode = code;
        } else {
            if (code < nextCode) {
                /* writeString(string[code]) */
                len = stringLen[code];
                bcopy(strings[code], to, len);
                to += len;

                /* add( string[oldcode] + first(string[code]) ) */
                len = stringLen[oldCode] + 1;
                if (nScratch < len) {
                    newBuffer = (struct buffer *)malloc(sizeof(struct buffer));
                    newBuffer->prev = scratchBuffer;
                    scratchBuffer = newBuffer;
                    scratchPtr = scratchBuffer->chars;
                    nScratch = sizeof(scratchBuffer->chars);
                }
                stringLen[nextCode] = len;
                strings[nextCode] = scratchPtr;
                bcopy(strings[oldCode], scratchPtr, len-1);
                scratchPtr += len-1;
                *scratchPtr++ = strings[code][0];
                nScratch -= len;
            } else {
                /* writeString(string[oldCode] + first(string[oldCode]) ) */
                len = stringLen[oldCode];
                bcopy(strings[oldCode], to, len);
                to += len;
                *to++ = strings[oldCode][0];

                /* add( string[oldcode] + first(string[oldCode]) ) */
                len++;
                if (nScratch < len) {
                    newBuffer = (struct buffer *)malloc(sizeof(struct buffer));
                    newBuffer->prev = scratchBuffer;
                    scratchBuffer = newBuffer;
                    scratchPtr = scratchBuffer->chars;
                    nScratch = sizeof(scratchBuffer->chars);
                }
                stringLen[nextCode] = len;
                strings[nextCode] = scratchPtr;
                bcopy(strings[oldCode], scratchPtr, len-1);
                scratchPtr += len-1;
                *scratchPtr++ = strings[oldCode][0];
                nScratch -= len;
            }
            oldCode = code;
            nextCode++;
            if (nextCode >= 511)
                if (nextCode == 511) {
                    codeLen = 10;
                    mask = 0x3FF;
                } else if (nextCode >= 1023)
                    if (nextCode == 1023) {
                        codeLen = 11;
                        mask = 0x7FF;
                    } else 
                        if (nextCode == 2047) {
                            codeLen = 12;
                            mask = 0xFFF;
                        }
        }
    }
    /* free stuff */
    while (scratchBuffer) {
        newBuffer = scratchBuffer;
        scratchBuffer = scratchBuffer->prev;
        free(newBuffer);
    }
}

/*
 * delta decoding (TIFF predictor = 2)
 */
decodeDelta(bytes, width, height)
    register unsigned char *bytes;
{
        register w;
        unsigned char r, g, b;

        while (height--) {
            r = g = b = 0;
            for (w = width; w; w--) {
                r += *bytes;
                *bytes++ = r;
                g += *bytes;
                *bytes++ = g;
                b += *bytes;
                *bytes++ = b;
            }
        }
}

decodeGIF(from, to, inCount, initialCodeLen)
    unsigned char *from;
    unsigned char *to;
{
    register unsigned code;
    unsigned short prefix[4096];
    unsigned short suffix[4096];
    unsigned short outCode[4096];
    int outCount;
    unsigned maxCode, oldCode, fin, inCode, curCode;
    register unsigned bits;
    register int nBits, mask, shift;
    int i;
    int len;
    int endCode, clearCode, freeCode;
    int codeLen = initialCodeLen;
    static int ranges[] = {0, 1, 2, 4,
                           8, 16, 32, 64,
                           128, 256, 512, 1024,
                           2048 };

    clearCode = ranges[codeLen]; /* 256 */
    endCode = clearCode + 1;     /* 257 */
    freeCode = clearCode + 2;    /* 258 */
    maxCode = clearCode << 1;    /* 512 */
    outCount = 0;

    mask = maxCode - 1;          /* 1FF */
    nBits = 0;
    bits = 0;
    while (inCount) {
        /* fetch code */
        while (nBits < codeLen) {
            bits = bits | (*from++ << nBits);
            inCount--;
            nBits += 8;
        }
        code = bits & mask;
        bits >>= codeLen;
        nBits -= codeLen;
        if (code == endCode) break;
        if (code == clearCode) {
            if (! inCount)
                break;

            codeLen = initialCodeLen;
            maxCode = clearCode<<1;
            mask = maxCode - 1;
            freeCode = clearCode + 2;  

            /* fetch code */
            while (nBits < codeLen) {
                bits = bits | (*from++ << nBits);
                inCount--;
                nBits += 8;
            }
            code = bits & mask;
            bits >>= codeLen;
            nBits -= codeLen;
            if (code == endCode) break;
            /* add to output */
            *to++ = code;
            oldCode = fin = curCode = code;
        } else {
            curCode = inCode = code;
            if (curCode >= freeCode) {
                curCode = oldCode;
                outCode[outCount++] = fin;
            }

            while (curCode >= clearCode) {
                if (outCount > 1024) {
                    return;
                }
                outCode[outCount++] = suffix[curCode];
                curCode = prefix[curCode];
            }

            fin = curCode;
            outCode[outCount++] = fin;

            for (i = outCount - 1; i >= 0; i--)
                *to++ = outCode[i];
            outCount = 0;

            prefix[freeCode] = oldCode;
            suffix[freeCode] = fin;
            oldCode = inCode;

            freeCode++;
            if (freeCode >= maxCode) {
                if (codeLen < 12) {
                    codeLen++;
                    maxCode *= 2;
                    mask = (1 << codeLen) - 1;
                }
            }
        }
    }
}

%}