GIFReader.st
author Claus Gittinger <cg@exept.de>
Tue, 28 Oct 1997 19:38:32 +0100
changeset 718 41ade132da98
parent 714 c89f5c12538c
child 732 db51a760126a
permissions -rw-r--r--
raise an error, if depth is not supported.

"
 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.
"

ImageReader subclass:#GIFReader
	instanceVariableNames:'redMap greenMap blueMap pass xpos ypos rowByteSize remainBitCount
		bufByte bufStream prefixTable suffixTable clearCode eoiCode
		freeCode codeSize maxCode interlace'
	classVariableNames:'ImageSeparator Extension Terminator'
	poolDictionaries:''
	category:'Graphics-Images-Support'
!

!GIFReader 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.
"
!

documentation
"
    this class provides methods for loading and saving GIF pictures.
    It has been tested with some different GIF87a pictures, I dont
    know, if it works with other GIF versions.
    GIF extension blocks are not handled.

    GIF file writing is not implemented (use TIFF).

    legal stuff extracted from GIF87a documentation:

    CompuServe Incorporated hereby grants a limited, non-exclusive, royalty-free
    license for the use of the Graphics Interchange Format(sm) in computer
    software; computer software utilizing GIF(sm) must acknowledge ownership of the
    Graphics Interchange Format and its Service Mark by CompuServe Incorporated, in
    User and Technical Documentation. 

      The Graphics Interchange Format(c) is the Copyright property of
      CompuServe Incorporated. GIF(sm) is a Service Mark property of
      CompuServe Incorporated.

    [See also:]
        Image Form Icon
        BlitImageReader FaceReader JPEGReader PBMReader PCXReader 
        ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
        XBMReader XPMReader XWDReader 

    [author:]
        Claus Gittinger
"
! !

!GIFReader class methodsFor:'initialization'!

initialize
    "install myself in the Image classes fileFormat table
     for the `.gif' extensions."

    ImageSeparator := $, asciiValue.
    Extension := $!! asciiValue.
    Terminator := $; asciiValue.

    MIMETypes defineImageType:'image/gif' suffix:'gif' reader:self.

    "Modified: 14.10.1997 / 18:47:27 / cg"
! !

!GIFReader class methodsFor:'testing'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format.
     GIF supports depth 8 images only."

    ^ anImage depth == 8

    "Created: 17.10.1997 / 20:19:20 / cg"
!

isValidImageFile:aFileName
    "return true, if aFileName contains a GIF image"

    |id inStream|

    inStream := self streamReadingFile:aFileName.
    inStream isNil ifTrue:[^ false].

    inStream text.

    id := String new:6.
    inStream nextBytes:6 into:id.
    inStream close.

    (id = 'GIF87a') ifFalse:[
        (id startsWith:'GIF') ifFalse:[^ false].

        id ~= 'GIF89a' ifTrue:[ 
            'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
        ]
    ].
    ^ true

    "Modified: 10.1.1997 / 15:40:34 / cg"
! !

!GIFReader methodsFor:'private - writing'!

assignTransparentPixelIn:image
    "find an usused pixelValue in the colorMap (or image)."

    |cmap usedPixelValues|

    (cmap := image colorMap) size > 0 ifTrue:[
        cmap size < 256 ifTrue:[
            maskPixel := cmap size.
            ^ self
        ]
    ].

    usedPixelValues := image usedValues.
    usedPixelValues size < (1 bitShift:image depth) ifTrue:[
        "/ there must be an unused pixelValue
        maskPixel := ((0 to:(1 bitShift:image depth)-1) asSet removeAll:(usedPixelValues)) first.
    ] ifFalse:[
        Image informationLostQuerySignal
            raiseWith:image
            errorString:('GIF writer cannot assign a transparent pixel - all pixelValues used by image').
    ]
!

checkCodeSize
    (freeCode > maxCode and: [codeSize < 12])
            ifTrue: 
                    [codeSize := codeSize + 1.
                    maxCode := (1 bitShift: codeSize) - 1]

    "Created: 14.10.1997 / 18:42:01 / cg"
!

flushBits
        remainBitCount = 0
                ifFalse: 
                        [self nextBytePut: bufByte.
                        remainBitCount := 0].
        self flushBuffer

    "Modified: 14.10.1997 / 18:58:06 / cg"
!

flushBuffer
    bufStream isEmpty ifTrue: [^ self].
    outStream nextPut: bufStream size.
    outStream nextPutAll: bufStream contents.
    bufStream := WriteStream on: (ByteArray new: 256)

    "Modified: 14.10.1997 / 20:46:04 / cg"
!

flushCode
        self flushBits

    "Created: 14.10.1997 / 18:57:33 / cg"
!

nextBitsPut: anInteger
        | integer writeBitCount shiftCount |
        shiftCount _ 0.
        remainBitCount = 0
                ifTrue:
                        [writeBitCount _ 8.
                        integer _ anInteger]
                ifFalse:
                        [writeBitCount _ remainBitCount.
                        integer _ bufByte + (anInteger bitShift: 8 - remainBitCount)].
        [writeBitCount < codeSize]
                whileTrue:
                        [self nextBytePut: ((integer bitShift: shiftCount) bitAnd: 255).
                        shiftCount _ shiftCount - 8.
                        writeBitCount _ writeBitCount + 8].
        (remainBitCount _ writeBitCount - codeSize) = 0
                ifTrue: [self nextBytePut: (integer bitShift: shiftCount)]
                ifFalse: [bufByte _ integer bitShift: shiftCount].
        ^anInteger

    "Modified: 15.10.1997 / 16:50:30 / cg"
!

nextBytePut: aByte
        bufStream nextPut: aByte.
        bufStream size >= 254 ifTrue: [self flushBuffer]

    "Modified: 15.10.1997 / 16:50:52 / cg"
!

readPixelFrom: bits 
    | pixel |
    ypos >= height ifTrue: [^ nil].
    (maskPixel notNil 
    and:[(mask pixelAtX:xpos y:ypos) == 0]) ifTrue:[
        pixel := maskPixel
    ] ifFalse:[
        pixel := bits at: ypos * rowByteSize + xpos + 1.
    ].
    self updatePixelPosition.
    ^ pixel

    "Created: 14.10.1997 / 18:43:50 / cg"
    "Modified: 15.10.1997 / 16:46:43 / cg"
!

setParameters:bitsPerPixel 
    clearCode := 1 bitShift:bitsPerPixel.
    eoiCode := clearCode + 1.
    freeCode := clearCode + 2.
    codeSize := bitsPerPixel + 1.
    maxCode := (1 bitShift: codeSize) - 1

    "Modified: 14.10.1997 / 20:09:48 / cg"
!

updatePixelPosition
        (xpos _ xpos + 1) >= width ifFalse: [^ self].
        xpos _ 0.
        interlace == true
                ifFalse: 
                        [ypos _ ypos + 1.
                        ^ self].
        pass = 0
                ifTrue: 
                        [(ypos _ ypos + 8) >= height
                                ifTrue: 
                                        [pass _ pass + 1.
                                        ypos _ 4].
                        ^ self].
        pass = 1
                ifTrue: 
                        [(ypos _ ypos + 8) >= height
                                ifTrue: 
                                        [pass _ pass + 1.
                                        ypos _ 2].
                        ^ self].
        pass = 2
                ifTrue: 
                        [(ypos _ ypos + 4) >= height
                                ifTrue: 
                                        [pass _ pass + 1.
                                        ypos _ 1].
                        ^ self].
        pass = 3
                ifTrue: 
                        [ypos _ ypos + 2.
                        ^ self].
        ^ self error: 'can''t happen'

    "Modified: 14.10.1997 / 18:44:27 / cg"
!

writeCode: aCode 
    self nextBitsPut: aCode

    "Created: 14.10.1997 / 18:38:35 / cg"
    "Modified: 15.10.1997 / 17:01:47 / cg"
!

writeCodeAndCheckCodeSize: t1 
    self writeCode: t1.
    self checkCodeSize

    "Created: 14.10.1997 / 18:38:24 / cg"
    "Modified: 14.10.1997 / 18:40:56 / cg"
! !

!GIFReader methodsFor:'reading from file'!

checkGreyscaleColormap
    "return true, if colormap is actually a greymap.
     Could be used to convert it into a greyScale image - which is not yet done."

    |sz "{ Class: SmallInteger }"
     redVal|

    sz := redMap size.

    1 to:sz do:[:i |
        redVal := redMap at:i.
        redVal ~~ (greenMap at:i) ifTrue:[^ false].
        redVal ~~ (blueMap at:i) ifTrue:[^ false].
    ].
    ^ true

    "Modified: 2.5.1996 / 17:54:40 / cg"
!

fromStream:aStream
    "read a stream containing a GIF image.
     Leave image description in instance variables."

    |byte index flag count fileColorMap
     colorMapSize bitsPerPixel scrWidth scrHeight
     hasColorMap hasLocalColorMap interlaced id
     leftOffs topOffs codeLen
     compressedData compressedSize
     tmp srcOffset dstOffset isGif89 atEnd
     h "{ Class: SmallInteger }"|

    inStream := aStream.
    aStream binary.

    "GIF-files are always lsb (intel-world)"
    byteOrder := #lsb.

    id := ByteArray new:6.
    aStream nextBytes:6 into:id startingAt:1.
    id := id asString.

    "all I had for testing where GIF87a files;
     I hope later versions work too ..."

    isGif89 := false.
    (id ~= 'GIF87a') ifTrue:[
        (id startsWith:'GIF') ifFalse:[
            'GIFReader [info]: not a gif file' infoPrintCR.
            ^ nil
        ].
        id ~= 'GIF89a' ifTrue:[ 
            'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
        ]
    ].

    "get screen dimensions (not used)"
    scrWidth := aStream nextShortMSB:false.
    scrHeight := aStream nextShortMSB:false.

    "get flag byte"
    flag := aStream nextByte.
    hasColorMap :=      (flag bitAnd:2r10000000) ~~ 0.
    "bitsPerRGB :=     ((flag bitAnd:2r01110000) bitShift:-4) + 1. "
    "colorMapSorted := ((flag bitAnd:2r00001000) ~~ 0.             "
    bitsPerPixel :=     (flag bitAnd:2r00000111) + 1.
    colorMapSize := 1 bitShift:bitsPerPixel.

    "get background (not used)"
    aStream nextByte.

    "aspect ratio (not used)"
    aStream nextByte.

    "get colorMap"
    hasColorMap ifTrue:[
        self readColorMap:colorMapSize.
        fileColorMap := Colormap 
                        redVector:redMap 
                        greenVector:greenMap 
                        blueVector:blueMap.
    ].
    colorMap := fileColorMap.

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).

    atEnd := false.
    [atEnd] whileFalse:[
        "gif89a extensions"
        byte := aStream nextByte.

        byte == Extension ifTrue:[
            self readExtension:aStream.
        ] ifFalse:[
            (byte == Terminator) ifTrue:[
                atEnd := true
            ] ifFalse:[
                "must be image separator"
                (byte ~~ ImageSeparator) ifTrue:[
                    ('GIFReader [info]: corrupted gif file (no IMAGESEP): ' , (byte printStringRadix:16)) infoPrintCR.
                    ^ nil
                ].

                "get image data"
                leftOffs := aStream nextShortMSB:false.
                topOffs := aStream nextShortMSB:false.
                width := aStream nextShortMSB:false.
                height := aStream nextShortMSB:false.

                dimensionCallBack notNil ifTrue:[
                    dimensionCallBack value:self
                ].

"/
"/              'width ' print. width printNewline.
"/              'height ' print. height printNewline.
"/

                "another flag byte"
                flag := aStream nextByte.
                interlaced :=           (flag bitAnd:2r01000000) ~~ 0.
                hasLocalColorMap :=     (flag bitAnd:2r10000000) ~~ 0.
                "localColorMapSorted := (flag bitAnd:2r00100000) ~~ 0.      "

                "if image has a local colormap, this one is used"

                hasLocalColorMap ifTrue:[
                    "local descr. overwrites"
                    bitsPerPixel := (flag bitAnd:2r00000111) + 1.
                    colorMapSize := 1 bitShift:bitsPerPixel.
                    "overwrite colormap"
                    self readColorMap:colorMapSize.
                    colorMap := Colormap 
                                    redVector:redMap 
                                    greenVector:greenMap 
                                    blueVector:blueMap.
                ] ifFalse:[
                    colorMap := fileColorMap
                ].


                "get codelen for decompression"
                codeLen := aStream nextByte.

                compressedData := ByteArray uninitializedNew:(aStream fileSize).

                "get compressed data"
                index := 1.
                count := aStream nextByte.
                [count notNil and:[count ~~ 0]] whileTrue:[
                    aStream nextBytes:count into:compressedData startingAt:index blockSize:4096.
                    index := index + count.
                    count := aStream nextByte
                ].
                compressedSize := index - 1.

                h := height.
                data := ByteArray new:((width + 1) * (h + 1)).
"/                'GIFReader: decompressing ...' infoPrintCR.

                self class decompressGIFFrom:compressedData
                                       count:compressedSize
                                        into:data
                                  startingAt:1
                                     codeLen:(codeLen + 1).

                interlaced ifTrue:[
"/                    'GIFREADER: deinterlacing ...' infoPrintCR.
                    tmp := ByteArray new:(data size).

                    "phase 1: 0, 8, 16, 24, ..."

                    srcOffset := 1.
                    0 to:(h - 1) by:8 do:[:dstRow |
                        dstOffset := dstRow * width + 1.
                        tmp replaceFrom:dstOffset to:(dstOffset + width - 1)
                                   with:data startingAt:srcOffset.
                        srcOffset := srcOffset + width.
                    ].

                    "phase 2: 4, 12, 20, 28, ..."

                    4 to:(h - 1) by:8 do:[:dstRow |
                        dstOffset := dstRow * width + 1.
                        tmp replaceFrom:dstOffset to:(dstOffset + width - 1)
                                   with:data startingAt:srcOffset.
                        srcOffset := srcOffset + width.
                    ].

                    "phase 3: 2, 6, 10, 14, ..."

                    2 to:(h - 1) by:4 do:[:dstRow |
                        dstOffset := dstRow * width + 1.
                        tmp replaceFrom:dstOffset to:(dstOffset + width - 1)
                                   with:data startingAt:srcOffset.
                        srcOffset := srcOffset + width.
                    ].

                    "phase 4: 1, 3, 5, 7, ..."

                    1 to:(h - 1) by:2 do:[:dstRow |
                        dstOffset := dstRow * width + 1.
                        tmp replaceFrom:dstOffset to:(dstOffset + width - 1)
                                   with:data startingAt:srcOffset.
                        srcOffset := srcOffset + width.
                    ].

                    data := tmp.
                    tmp := nil.
                ].

                imageSequence isNil ifTrue:[
                    imageSequence := OrderedCollection new.
                ].
                maskPixel notNil ifTrue:[
                    "/
                    "/ ok, there is a maskValue
                    "/ build a Depth1Image for it.
                    "/
                    self buildMaskFromColor:maskPixel
                ].

                imageSequence add:(self image).

                aStream atEnd ifTrue:[
                    atEnd := true.
                ]
            ]
        ].
    ].

    "
     GIFReader fromFile:'../fileIn/bitmaps/claus.gif
     GIFReader fromFile:'../fileIn/bitmaps/garfield.gif'
     GIFReader new fromStream:('/home2/cg/.misc/circum.gif' asFilename readStream)
    "

    "Modified: 5.7.1996 / 17:32:01 / stefan"
    "Modified: 14.10.1997 / 20:45:57 / cg"
!

makeGreyscale
    "not yet implemented/needed"
!

readColorMap:colorMapSize
    "get gif colormap consisting of colorMapSize entries"

    |sz "{ Class: SmallInteger }"|

    redMap := ByteArray uninitializedNew:colorMapSize.
    greenMap := ByteArray uninitializedNew:colorMapSize.
    blueMap := ByteArray uninitializedNew:colorMapSize.

    sz := colorMapSize.
    1 to:sz do:[:i |
        redMap at:i put:(inStream nextByte).
        greenMap at:i put:(inStream nextByte).
        blueMap at:i put:(inStream nextByte)
    ].

    "Modified: 21.6.1996 / 12:32:43 / cg"
!

readExtension:aStream
    "get gif89 extension - this is currently ignored"

    |type blockSize subBlockSize
     aspNum aspDen left top width height cWidth cHeight fg bg
     animationType animationTime animationMask
     appID appAUTH
     iterationCount b ok|

    type := aStream nextByte.
    type == $R asciiValue ifTrue:[
        "/
        "/ Ratio extension
        "/
        'GIFREADER [info]: ratio extension ignored' infoPrintCR.
        blockSize := aStream nextByte.
        (blockSize == 2) ifTrue:[
            aspNum := aStream nextByte.
            aspDen := aStream nextByte
        ] ifFalse:[
            aStream skip:blockSize
        ].
        "/ eat subblocks
        
        [(subBlockSize := aStream nextByte) > 0] whileTrue:[
            aStream skip:subBlockSize
        ].
        ^ self
    ].

    type == 16r01 ifTrue:[
        "/
        "/ plaintext extension
        "/
"/        'GIFREADER [info]: plaintext extension ignored' infoPrintCR.
        subBlockSize := aStream nextByte.
        left := aStream nextShortMSB:false.
        top := aStream nextShortMSB:false.
        width := aStream nextShortMSB:false.
        height := aStream nextShortMSB:false.
        cWidth := aStream nextByte.
        cHeight := aStream nextByte.
        fg := aStream nextByte.
        bg := aStream nextByte.
        aStream skip:12.
        [(subBlockSize := aStream nextByte) > 0] whileTrue:[
            aStream skip:subBlockSize
        ].
        ^ self
    ].

    type == 16rF9 ifTrue:[
        "/
        "/ graphic control extension
        "/
"/        'GIFREADER [info]: graphic control extension ignored' infoPrintCR.

        [(subBlockSize := aStream nextByte) ~~ 0] whileTrue:[
            "/ type bitAnd:1 means: animationMask is transparent pixel
            "/ to be implemented in Image ...

            animationType := aStream nextByte.
            animationTime := aStream nextShortMSB:false.
            animationMask := aStream nextByte.
            subBlockSize := subBlockSize - 4.

           (animationType bitTest: 1) ifTrue:[
                maskPixel := animationMask.
"/                'GIFREADER [info]: mask: ' infoPrint. (maskPixel printStringRadix:16) infoPrintCR.
            ].
"/            'GIFREADER [info]: animationTime: ' infoPrint. (animationTime * (1/100)) infoPrintCR.

            subBlockSize ~~ 0 ifTrue:[
                aStream skip:subBlockSize
            ].
        ].
        ^ self
    ].

    type == 16rFE ifTrue:[
        "/
        "/ comment extension
        "/
"/        'GIFREADER [info]: comment extension ignored' infoPrintCR.
        [(blockSize := aStream nextByte) ~~ 0] whileTrue:[
            aStream skip:blockSize
        ].
        ^ self
    ].

    type == 16rFF ifTrue:[
        "/
        "/  application extension
        "/
        subBlockSize := aStream nextByte.
        appID := (aStream nextBytes:8 ) asString.
        appAUTH := aStream nextBytes:3.

        subBlockSize := aStream nextByte.

        ok := false.
        appID = 'NETSCAPE' ifTrue:[
            appAUTH asString = '2.0' ifTrue:[
                subBlockSize == 3 ifTrue:[
                    b := aStream nextByte.
                    iterationCount := aStream nextShortMSB:false.
                    subBlockSize := aStream nextByte.
                    ok := true.
                ]
            ]
        ].

        ok ifFalse:[
            ('GIFREADER [info]: application extension (' , appID , ') ignored') infoPrintCR.
        ].

        [subBlockSize > 0] whileTrue:[
            aStream skip:subBlockSize.
            subBlockSize := aStream nextByte.
        ].
        ^ self
    ].

    type == 16r2C ifTrue:[
        "/
        "/  image descriptor extension
        "/
        'GIFREADER [info]: image descriptor extension ignored' infoPrintCR.
        [(subBlockSize := aStream nextByte) > 0] whileTrue:[
            aStream skip:subBlockSize
        ].
        ^ self
    ].

    "/
    "/ unknown extension
    "/
    'GIFREADER [info]: unknown extension ignored' infoPrintCR.
    [(subBlockSize := aStream nextByte) > 0] whileTrue:[
        aStream skip:subBlockSize
    ]

    "Modified: 24.7.1997 / 18:02:49 / cg"
! !

!GIFReader methodsFor:'writing to file'!

save:image onFile:aFileName
    "save image as GIF file on aFileName"

    image depth ~~ 8 ifTrue:[
        ^ Image cannotRepresentImageSignal 
            raiseWith:image
            errorString:('GIF (currently) only supports depth8 images').
    ].

    outStream := FileStream newFileNamed:aFileName.
    outStream isNil ifTrue:[
        ^ Image fileCreationErrorSignal 
            raiseWith:image
            errorString:('file creation error: ' , aFileName asString).
    ].
    outStream binary.

    mask := image mask.
    mask notNil ifTrue:[
        self assignTransparentPixelIn:image
    ].

    byteOrder := #lsb.
    width := image width.
    height := image height.
    photometric := image photometric.
    samplesPerPixel := image samplesPerPixel.
    bitsPerSample := image bitsPerSample.
    colorMap := image colorMap.
    data := image bits.

    self writeHeaderFor:image.
    maskPixel notNil ifTrue:[
        self writeMaskExtensionHeaderFor:image.
    ].

    self writeBitDataFor:image.

    outStream nextPut: Terminator.
    outStream close.

    "
     |i|

     i := Image fromFile:'bitmaps/gifImages/garfield.gif'.
     GIFReader save:i onFile:'foo.gif'.
     (Image fromFile:'./foo.gif') inspect
    "

    "Created: / 14.10.1997 / 17:40:12 / cg"
    "Modified: / 27.10.1997 / 22:42:31 / cg"
!

writeBitDataFor: image
        "using modified Lempel-Ziv Welch algorithm."

        | bits bitsPerPixel t1
          maxBits maxMaxCode tSize initCodeSize ent tShift fCode pixel index disp nomatch |

        outStream nextPut:ImageSeparator.
        self writeShort:0.       "/
        self writeShort:0.       "/
        self writeShort:width.   "/ image size
        self writeShort:height.

        interlace == true ifTrue:[
            t1 := 64
        ] ifFalse:[
            t1 := 0
        ].
        outStream nextPut:t1.       "/ another flag

        bitsPerPixel := image bitsPerPixel.
        bits := image bits.

        pass := 0.
        xpos := 0.
        ypos := 0.
        rowByteSize := image bytesPerRow. "/ width * 8 + 31 // 32 * 4.
        remainBitCount := 0.
        bufByte := 0.
        bufStream := WriteStream on: (ByteArray new: 256).

        maxBits := 12.
        maxMaxCode := 1 bitShift: maxBits.
        tSize := 5003.
        prefixTable := Array new: tSize.
        suffixTable := Array new: tSize.

        initCodeSize := bitsPerPixel <= 1 ifTrue: [2] ifFalse: [bitsPerPixel].
        outStream nextPut: initCodeSize.
        self setParameters: initCodeSize.

        tShift := 0.
        fCode := tSize.
        [fCode < 65536] whileTrue:
                [tShift := tShift + 1.
                fCode := fCode * 2].
        tShift := 8 - tShift.
        1 to: tSize do: [:i | suffixTable at: i put: -1].

        self writeCodeAndCheckCodeSize: clearCode.
        ent := self readPixelFrom: bits.
        [(pixel := self readPixelFrom: bits) == nil] whileFalse:
                [
                fCode := (pixel bitShift: maxBits) + ent.
                index := ((pixel bitShift: tShift) bitXor: ent) + 1.
                (suffixTable at: index) = fCode
                        ifTrue: [ent := prefixTable at: index]
                        ifFalse:
                                [nomatch := true.
                                (suffixTable at: index) >= 0
                                        ifTrue:
                                                [disp := tSize - index + 1.
                                                index = 1 ifTrue: [disp := 1].
                                                "probe"
                                                [(index := index - disp) < 1 ifTrue: [index := index + tSize].
                                                (suffixTable at: index) = fCode
                                                        ifTrue:
                                                                [ent := prefixTable at: index.
                                                                nomatch := false.
                                                                "continue whileFalse:"].
                                                nomatch and: [(suffixTable at: index) > 0]]
                                                        whileTrue: ["probe"]].
                                "nomatch"
                                nomatch ifTrue:
                                        [self writeCodeAndCheckCodeSize: ent.
                                        ent := pixel.
                                        freeCode < maxMaxCode
                                                ifTrue:
                                                        [prefixTable at: index put: freeCode.
                                                        suffixTable at: index put: fCode.
                                                        freeCode := freeCode + 1]
                                                ifFalse:
                                                        [self writeCodeAndCheckCodeSize: clearCode.
                                                        1 to: tSize do: [:i | suffixTable at: i put: -1].
                                                        self setParameters: initCodeSize]]]].
        prefixTable := suffixTable := nil.
        self writeCodeAndCheckCodeSize: ent.
        self writeCodeAndCheckCodeSize: eoiCode.
        self flushCode.
        outStream nextPut: 0.        "zero-length packet"

    "Modified: 15.10.1997 / 19:56:28 / cg"
!

writeHeaderFor:image
    "write the gif header"

    |bitsPerPixel t1 n|

    bitsPerPixel := image bitsPerPixel.

    outStream nextPutAll: 'GIF87a' asByteArray.
    self writeShort:width. "/ screen size
    self writeShort:height.    
    t1 := 128.
    t1 := t1 bitOr:(bitsPerPixel - 1 bitShift:5).
    t1 := t1 bitOr:(bitsPerPixel - 1).
    outStream nextPut:t1.  "/ flag
    outStream nextPut:0.   "/ background (not used)
    outStream nextPut:0.   "/ aspect ratio

    0 to:(1 bitShift:bitsPerPixel)-1 do:[:pixel |
        |clr red green blue|

        clr := image colorFromValue:pixel.
        clr isNil ifTrue:[
            "/ unused colorMap slot
            red := green := blue := 0.
        ] ifFalse:[
            red := (clr redByte).
            green := (clr greenByte).
            blue := (clr blueByte).
        ].
        outStream
            nextPut:red; nextPut:green; nextPut:blue.
    ].    
"/    n := 0.
"/    image colorMap notNil ifTrue:[
"/        image colorMap do:[:clr |
"/            |red green blue|
"/
"/            clr isNil ifTrue:[
"/                "/ unused colorMap slot
"/                red := green := blue := 0.
"/            ] ifFalse:[
"/                red := (clr redByte).
"/                green := (clr greenByte).
"/                blue := (clr blueByte).
"/            ].
"/            outStream
"/                nextPut:red; nextPut:green; nextPut:blue.
"/            n := n + 1.
"/        ]
"/    ].
"/    n+1 to:(1 bitShift:bitsPerPixel) do:[:i |
"/        outStream nextPut:0; nextPut:0; nextPut:0
"/    ].


    "Created: 14.10.1997 / 17:41:28 / cg"
    "Modified: 21.10.1997 / 04:52:18 / cg"
!

writeMaskExtensionHeaderFor:image
    "write an extension header for the transparent pixel"

    outStream nextPut:Extension.
    outStream nextPut:16rF9.       "/ graphic control extension
    outStream nextPut:4.           "/ subBlockSize

    outStream nextPut:1.                "/ animationType
    outStream nextPutShort:1 MSB:false. "/ animationTime
    outStream nextPut:maskPixel.        "/ animationMask

    outStream nextPut:0.
! !

!GIFReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.62 1997-10-28 18:38:32 cg Exp $'
! !
GIFReader initialize!