ImageReader.st
author claus
Mon, 06 Feb 1995 01:38:04 +0100
changeset 89 ea2bf46eb669
parent 81 4ba554473294
child 95 47ac85948d38
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1991 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:'ReverseBits'
	 poolDictionaries:''
	 category:'Graphics-Images support'
!

ImageReader comment:'
COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/ImageReader.st,v 1.12 1995-02-06 00:37:26 claus Exp $
'!

!ImageReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1991 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.
"
!

version
"
$Header: /cvs/stx/stx/libview/ImageReader.st,v 1.12 1995-02-06 00:37:26 claus Exp $
"
!

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

!ImageReader class methodsFor:'cleanup'!

lowSpaceCleanup
    "cleanup things we do not need"

    ReverseBits := nil
! !

!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:'constants'!

reverseBits
    "return a table filled with bit reverse information.
     To convert from msbit-first to lsbit-first bytes, use
     the value as index into the table, retrieving the reverse
     value. Since indexing must start at 1, use (value + 1) as
     index."

    |val "{ Class: SmallInteger }" |

    ReverseBits isNil ifTrue:[
	ReverseBits := ByteArray new:256.
	0 to:255 do:[:i |
	    val := 0.
	    (i bitTest:16r01) ifTrue:[val := val bitOr:16r80].
	    (i bitTest:16r02) ifTrue:[val := val bitOr:16r40].
	    (i bitTest:16r04) ifTrue:[val := val bitOr:16r20].
	    (i bitTest:16r08) ifTrue:[val := val bitOr:16r10].
	    (i bitTest:16r10) ifTrue:[val := val bitOr:16r08].
	    (i bitTest:16r20) ifTrue:[val := val bitOr:16r04].
	    (i bitTest:16r40) ifTrue:[val := val bitOr:16r02].
	    (i bitTest:16r80) ifTrue:[val := val bitOr:16r01].
	    ReverseBits at:(i + 1) put:val
	]
    ].
    ^ ReverseBits
! !

!ImageReader class methodsFor:'fileIn / fileOut'!

fromFile:aFileName
    "read an image (in my format) from aFileName"

    |reader image depth|

    reader := self new fromFile:aFileName.
    reader notNil ifTrue:[
	depth := reader bitsPerPixel.
	image := (Image implementorForDepth: depth) 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
    "save the image in my format on aFileName"

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

!ImageReader class methodsFor:'i/o support'!

streamReadingFile:aFilename
    "return a stream to read aFilename - if the filename ends with
     '.Z' or '.gz', read from a pipe to gunzip."

    |inStream|

    ((aFilename endsWith:'.Z') or:[aFilename endsWith:'.gz']) ifTrue:[
	inStream := PipeStream readingFrom:'gunzip < ' , aFilename.
	inStream isNil ifTrue:[
	    inStream := PipeStream readingFrom:'uncompress < ' , aFilename.
	]
    ] ifFalse:[
	inStream := FileStream readonlyFileNamed:aFilename.
    ].
    inStream isNil ifTrue:[
	'IMGREADER: open error on: ' errorPrint. aFilename errorPrintNL. 
    ].
    ^ inStream
! !

!ImageReader methodsFor:'accessing'!

width
    ^ width
!

height 
    ^ height
!

data 
    ^ data
!

photometric
    ^ photometric
!

colorMap
    ^ colorMap
!

samplesPerPixel
    ^ samplesPerPixel
!

bitsPerSample
    ^ bitsPerSample
!

bitsPerPixel
    "return the number of bits per pixel"

    ^ (bitsPerSample inject:0 into:[:sum :i | sum + i])
! !

!ImageReader methodsFor:'fileIn / fileOut'!

fromFile:aFileName
    ^ self subclassResponsibility
!

save:image onFile:aFileName
    ^ self subclassResponsibility
! !

!ImageReader methodsFor:'i/o support'!

readLong
    "return the next 4-byte long, honoring the byte-order"

    ^ inStream nextLongMSB:(byteOrder ~~ #lsb)
!

readShort
    "return the next 2-byte short, honoring the byte-order"

    ^ inStream nextUnsignedShortMSB:(byteOrder ~~ #lsb)
!

readShortLong
    "return the next 2-byte short, honoring the byte-order.
     There are actually 4 bytes read, but only 2 looked at."

    |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
    "write a 4-byte long, honoring the byte-order."

    outStream nextPutLong:anInteger MSB:(byteOrder ~~ #lsb)
!

writeShort:anInteger
    "write a 2-byte short, honoring the byte-order."

    outStream nextPutShort:anInteger MSB:(byteOrder ~~ #lsb)
! !

!ImageReader class methodsFor:'decompression support'!

decompressCCITT3From:srcBytes into:dstBytes startingAt:offset count:count 
    "decompress a CCITT Group 3 compressed image.
     count bytes from srcBytes are decompressed into dstBytes.
     Calls primitive c function for speed"
%{
    if (__isByteArray(srcBytes) 
     && __isByteArray(dstBytes)
     && _isSmallInteger(offset) 
     && _isSmallInteger(count)) {
	if (__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
    "decompress an LZW (tiff) compressed image.
     count bytes from srcBytes are decompressed into dstBytes.
     Calls primitive c function for speed"
%{
    if (__isByteArray(srcBytes) 
     && __isByteArray(dstBytes)
     && _isSmallInteger(offset) 
     && _isSmallInteger(count)) {
	if (__decodeLZW__(_ByteArrayInstPtr(srcBytes)->ba_element,
		      _ByteArrayInstPtr(dstBytes)->ba_element
		      + _intVal(offset) - 1,
		      _intVal(count))) {
	    RETURN ( self );
	}
    }
%}
.
    self primitiveFailed
!

decompressGIFFrom:srcBytes count:count into:dstBytes startingAt:offset codeLen:codeLen
    "decompress a GIF compressed image.
     count bytes from srcBytes are decompressed into dstBytes.
     Calls primitive c function for speed"
%{
    if (__isByteArray(srcBytes) 
     && __isByteArray(dstBytes)
     && _isSmallInteger(codeLen)
     && _isSmallInteger(offset)
     && _isSmallInteger(count)) {
	if (__decodeGIF__(_ByteArrayInstPtr(srcBytes)->ba_element,
		      _ByteArrayInstPtr(dstBytes)->ba_element
		      + _intVal(offset) - 1,
		      _intVal(count),
		      _intVal(codeLen))) {
	    RETURN ( self );
	}
    }
%}
.
    self primitiveFailed
!
decodeDelta:step in:data width:width height:height
    "perform NeXT special predictor delta decoding inplace in data.
     Calls primitive c function for speed"

    (step ~~ 3) ifTrue:[
	^ self error:'only rgb pictures supported'
    ].

%{
    if (__isByteArray(data)
     && _isSmallInteger(width)
     && _isSmallInteger(height)) {
	__decodeDelta__(_ByteArrayInstPtr(data)->ba_element,
		    _intVal(width), _intVal(height));
	RETURN ( self );
    }
%}
.
    self primitiveFailed
! !

!ImageReader primitiveFunctions!

%{

/*
 * 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);
    if (! whiteCountTable) return;
    whiteShiftTable = (char *) malloc(sizeof(char) * 8192);
    if (! whiteShiftTable) {
	free(whiteCountTable); whiteCountTable = (short *)0;
	return;
    }
    blackCountTable = (short *) malloc(sizeof(short) * 8192);
    if (! blackCountTable) {
	free(whiteShiftTable); whiteShiftTable = (char *)0;
	free(whiteCountTable); whiteCountTable = (short *)0;
	return;
    }
    blackShiftTable = (char *) malloc(sizeof(char) * 8192);
    if (! blackShiftTable) {
	free(whiteShiftTable); whiteShiftTable = (char *)0;
	free(whiteCountTable); whiteCountTable = (short *)0;
	free(blackCountTable); blackCountTable = (short *)0;
	return;
    }

    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();
    if (! whiteCountTable) return 0; /* malloc failed */

    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 1;

	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;
    short *stringLen;
    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 0;

    strings = (unsigned char **)malloc(sizeof(unsigned char *) * 4096);
    if (! strings) {
	free(scratchBuffer);
	return 0;
    }
    stringLen = (short *)malloc(sizeof(short) * 4096);
    if (! stringLen) {
	free(strings);
	free(scratchBuffer);
	return 0;
    }

    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));
		    if (! newBuffer) goto out;
		    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));
		    if (! newBuffer) goto out;
		    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;
			}
	}
    }
out: ;
    /* free stuff */
    while (scratchBuffer) {
	newBuffer = scratchBuffer;
	scratchBuffer = scratchBuffer->prev;
	free(newBuffer);
    }

    free(strings);
    free(stringLen);

    return 1;
}

/*
 * 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;
	    }
	}
}

/*
 * GIF decompression
 */
__decodeGIF__(from, to, inCount, initialCodeLen)
    unsigned char *from;
    unsigned char *to;
{
    register unsigned code;
    unsigned short *prefix;
    unsigned short *suffix;
    unsigned short *outCode;
    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 };

    prefix = (unsigned short *)malloc(sizeof(short) * 4096);
    if (! prefix) return 0;
    suffix  = (unsigned short *)malloc(sizeof(short) * 4096);
    if (! suffix) {
	free(prefix);
	return 0;
    }
    outCode = (unsigned short *)malloc(sizeof(short) * 4096);
    if (! outCode) {
	free(prefix);
	free(suffix);
	return 0;
    }
    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) {
		    goto out;
		}
		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;
		}
	    }
	}
    }
out: ;
    free(prefix);
    free(suffix);
    free(outCode);

    return 1;
}

%}
! !