GIFReader.st
changeset 757 094c6c7c4ce6
parent 755 f1135dda53b1
child 809 0d39cb7c21a9
--- a/GIFReader.st	Fri Jan 16 15:21:44 1998 +0100
+++ b/GIFReader.st	Fri Jan 16 16:20:10 1998 +0100
@@ -57,13 +57,13 @@
       CompuServe Incorporated.
 
     [See also:]
-        Image Form Icon
-        BlitImageReader FaceReader JPEGReader PBMReader PCXReader 
-        ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
-        XBMReader XPMReader XWDReader 
+	Image Form Icon
+	BlitImageReader FaceReader JPEGReader PBMReader PCXReader 
+	ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
+	XBMReader XPMReader XWDReader 
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -108,11 +108,11 @@
     inStream close.
 
     (id = 'GIF87a') ifFalse:[
-        (id startsWith:'GIF') ifFalse:[^ false].
+	(id startsWith:'GIF') ifFalse:[^ false].
 
-        id ~= 'GIF89a' ifTrue:[ 
-            'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
-        ]
+	id ~= 'GIF89a' ifTrue:[ 
+	    'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
+	]
     ].
     ^ true
 
@@ -127,38 +127,38 @@
     |cmap usedPixelValues|
 
     (cmap := image colorMap) size > 0 ifTrue:[
-        cmap size < 256 ifTrue:[
-            maskPixel := cmap size.
-            ^ self
-        ]
+	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.
+	"/ 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').
+	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]
+	    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
+	remainBitCount = 0
+		ifFalse: 
+			[self nextBytePut: bufByte.
+			remainBitCount := 0].
+	self flushBuffer
 
     "Modified: 14.10.1997 / 18:58:06 / cg"
 !
@@ -173,37 +173,37 @@
 !
 
 flushCode
-        self flushBits
+	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
+	| 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]
+	bufStream nextPut: aByte.
+	bufStream size >= 254 ifTrue: [self flushBuffer]
 
     "Modified: 15.10.1997 / 16:50:52 / cg"
 !
@@ -213,9 +213,9 @@
     ypos >= height ifTrue: [^ nil].
     (maskPixel notNil 
     and:[(mask pixelAtX:xpos y:ypos) == 0]) ifTrue:[
-        pixel := maskPixel
+	pixel := maskPixel
     ] ifFalse:[
-        pixel := bits at: ypos * rowByteSize + xpos + 1.
+	pixel := bits at: ypos * rowByteSize + xpos + 1.
     ].
     self updatePixelPosition.
     ^ pixel
@@ -235,38 +235,38 @@
 !
 
 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'
+	(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"
 !
@@ -298,9 +298,9 @@
     sz := redMap size.
 
     1 to:sz do:[:i |
-        redVal := redMap at:i.
-        redVal ~~ (greenMap at:i) ifTrue:[^ false].
-        redVal ~~ (blueMap at:i) ifTrue:[^ false].
+	redVal := redMap at:i.
+	redVal ~~ (greenMap at:i) ifTrue:[^ false].
+	redVal ~~ (blueMap at:i) ifTrue:[^ false].
     ].
     ^ true
 
@@ -334,13 +334,13 @@
 
     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.
-        ]
+	(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)"
@@ -363,11 +363,11 @@
 
     "get colorMap"
     hasColorMap ifTrue:[
-        self readColorMap:colorMapSize.
-        fileColorMap := Colormap 
-                        redVector:redMap 
-                        greenVector:greenMap 
-                        blueVector:blueMap.
+	self readColorMap:colorMapSize.
+	fileColorMap := Colormap 
+			redVector:redMap 
+			greenVector:greenMap 
+			blueVector:blueMap.
     ].
     colorMap := fileColorMap.
 
@@ -377,171 +377,48 @@
 
     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.
-"/
+	"gif89a extensions"
 
-                "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.
-
-                (aStream respondsTo:#fileSize) ifTrue:[
-                    "get hint about length of compressed data"
-                    count := aStream fileSize.
-                ] ifFalse:[
-                    count := 512.
-                ].
-                compressedData := ByteArray uninitializedNew:count.
+	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 compressed data"
-                index := 1.
-                count := aStream nextByte.
-                [count notNil and:[count ~~ 0]] whileTrue:[
-                    (compressedData size < (index+count)) ifTrue:[
-                        |c|
-                        c := ByteArray uninitializedNew:(index+count*3//2).
-                        c replaceBytesFrom:1 to:index-1 
-                          with:compressedData startingAt:1.
-                        
-                        compressedData := c.
-                    ].
-                    aStream nextBytes:count into:compressedData startingAt:index blockSize:4096.
-                    index := index + count.
-                    count := aStream nextByte
-                ].
-                compressedSize := index - 1.
-
-                h := height.
-                data := ByteArray uninitializedNew:((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 uninitializedNew:(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, ..."
+		fileColorMap notNil ifTrue:[
+		    colorMap := fileColorMap.
+		].
+		self readImage:aStream.
 
-                    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, ..."
+		imageSequence isNil ifTrue:[
+		    imageSequence := OrderedCollection new.
+		].
+		maskPixel notNil ifTrue:[
+		    "/
+		    "/ ok, there is a maskValue
+		    "/ build a Depth1Image for it.
+		    "/
+		    self buildMaskFromColor:maskPixel
+		].
 
-                    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 add:(self image).
 
-                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.
-                ]
-            ]
-        ].
+		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: / 18.12.1997 / 10:23:38 / cg"
-    "Modified: / 15.1.1998 / 15:42:19 / stefan"
+    "Modified: / 5.7.1996 / 17:32:01 / stefan"
+    "Modified: / 13.1.1998 / 10:44:26 / cg"
 !
 
 makeGreyscale
@@ -559,9 +436,9 @@
 
     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)
+	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"
@@ -578,127 +455,127 @@
 
     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
+	"/
+	"/ 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
+	[(subBlockSize := aStream nextByte) > 0] whileTrue:[
+	    aStream skip:subBlockSize
+	].
+	^ self
     ].
 
     type == 16r01 ifTrue:[
-        "/
-        "/ plaintext extension
-        "/
+	"/
+	"/ 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
+	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
-        "/
+	"/
+	"/ 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 ...
+	[(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 := aStream nextByte.
+	    animationTime := aStream nextShortMSB:false.
+	    animationMask := aStream nextByte.
+	    subBlockSize := subBlockSize - 4.
 
-           (animationType bitTest: 1) ifTrue:[
-                maskPixel := animationMask.
+	   (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
+	    subBlockSize ~~ 0 ifTrue:[
+		aStream skip:subBlockSize
+	    ].
+	].
+	^ self
     ].
 
     type == 16rFE ifTrue:[
-        "/
-        "/ comment extension
-        "/
+	"/
+	"/ comment extension
+	"/
 "/        'GIFREADER [info]: comment extension ignored' infoPrintCR.
-        [(blockSize := aStream nextByte) ~~ 0] whileTrue:[
-            aStream skip:blockSize
-        ].
-        ^ self
+	[(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.
+	"/
+	"/  application extension
+	"/
+	subBlockSize := aStream nextByte.
+	appID := (aStream nextBytes:8 ) asString.
+	appAUTH := aStream nextBytes:3.
 
-        subBlockSize := aStream nextByte.
+	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 := 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.
-        ].
+	ok ifFalse:[
+	    ('GIFREADER [info]: application extension (' , appID , ') ignored') infoPrintCR.
+	].
 
-        [subBlockSize > 0] whileTrue:[
-            aStream skip:subBlockSize.
-            subBlockSize := aStream nextByte.
-        ].
-        ^ self
+	[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
+	"/
+	"/  image descriptor extension
+	"/
+	'GIFREADER [info]: image descriptor extension ignored' infoPrintCR.
+	[(subBlockSize := aStream nextByte) > 0] whileTrue:[
+	    aStream skip:subBlockSize
+	].
+	^ self
     ].
 
     "/
@@ -706,10 +583,137 @@
     "/
     'GIFREADER [info]: unknown extension ignored' infoPrintCR.
     [(subBlockSize := aStream nextByte) > 0] whileTrue:[
-        aStream skip:subBlockSize
+	aStream skip:subBlockSize
     ]
 
     "Modified: 24.7.1997 / 18:02:49 / cg"
+!
+
+readImage:aStream
+    |leftOffs topOffs flag interlaced hasLocalColorMap bitsPerPixel colorMapSize
+     codeLen compressedData compressedSize index count h tmp srcOffset dstOffset
+     initialBuffSize|
+
+    "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.
+    ].
+
+
+    "get codelen for decompression"
+    codeLen := aStream nextByte.
+    (aStream respondsTo:#fileSize) ifTrue:[
+	initialBuffSize := aStream fileSize.
+    ] ifFalse:[
+	initialBuffSize := 512.
+    ].
+    compressedData := ByteArray uninitializedNew:initialBuffSize.
+
+    "get compressed data"
+    index := 1.
+    count := aStream nextByte.
+    [count notNil and:[count ~~ 0]] whileTrue:[
+        (compressedData size < (index+count)) ifTrue:[
+            |t|
+
+            t := ByteArray uninitializedNew:(index+count*3//2).
+            t replaceBytesFrom:1 to:index-1 with:compressedData startingAt:1.
+            compressedData := t.
+        ].
+
+	aStream nextBytes:count into:compressedData startingAt:index blockSize:4096.
+	index := index + count.
+	count := aStream nextByte
+    ].
+    compressedSize := index - 1.
+
+    h := height.
+    data := ByteArray uninitializedNew:((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 uninitializedNew:(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.
+    ].
+
+    "Modified: / 13.1.1998 / 10:41:05 / cg"
+    "Created: / 13.1.1998 / 10:44:05 / cg"
 ! !
 
 !GIFReader methodsFor:'writing to file'!
@@ -718,22 +722,22 @@
     "save image as GIF file on aFileName"
 
     image depth ~~ 8 ifTrue:[
-        ^ Image cannotRepresentImageSignal 
-            raiseWith:image
-            errorString:('GIF (currently) only supports depth8 images').
+	^ 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).
+	^ Image fileCreationErrorSignal 
+	    raiseWith:image
+	    errorString:('file creation error: ' , aFileName asString).
     ].
     outStream binary.
 
     mask := image mask.
     mask notNil ifTrue:[
-        self assignTransparentPixelIn:image
+	self assignTransparentPixelIn:image
     ].
 
     byteOrder := #lsb.
@@ -747,7 +751,7 @@
 
     self writeHeaderFor:image.
     maskPixel notNil ifTrue:[
-        self writeMaskExtensionHeaderFor:image.
+	self writeMaskExtensionHeaderFor:image.
     ].
 
     self writeBitDataFor:image.
@@ -768,94 +772,94 @@
 !
 
 writeBitDataFor: image
-        "using modified Lempel-Ziv Welch algorithm."
+	"using modified Lempel-Ziv Welch algorithm."
 
-        | bits bitsPerPixel t1
-          maxBits maxMaxCode tSize initCodeSize ent tShift fCode pixel index disp nomatch |
+	| 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.
+	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
+	interlace == true ifTrue:[
+	    t1 := 64
+	] ifFalse:[
+	    t1 := 0
+	].
+	outStream nextPut:t1.       "/ another flag
 
-        bitsPerPixel := image bitsPerPixel.
-        bits := image bits.
+	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).
+	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.
+	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.
+	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].
+	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"
+	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"
 !
@@ -878,19 +882,19 @@
     outStream nextPut:0.   "/ aspect ratio
 
     0 to:(1 bitShift:bitsPerPixel)-1 do:[:pixel |
-        |clr red green blue|
+	|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.
+	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:[
@@ -935,6 +939,6 @@
 !GIFReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.65 1998-01-15 15:38:47 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.66 1998-01-16 15:20:10 cg Exp $'
 ! !
 GIFReader initialize!