#REFACTORING
authorClaus Gittinger <cg@exept.de>
Sun, 14 Feb 2016 00:16:12 +0100
changeset 3553 2e3f003c3848
parent 3552 ef88cdf452d1
child 3554 f1820748e4a9
#REFACTORING class: GIFReader changed:5 methods removed remaining references to obsolete inhomogenous writers and readers.
GIFReader.st
--- a/GIFReader.st	Sun Feb 14 00:14:45 2016 +0100
+++ b/GIFReader.st	Sun Feb 14 00:16:12 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
@@ -227,7 +225,7 @@
 
     id := ByteArray new:6.
     (aStream nextBytes:6 into:id startingAt:1) ~~ 6 ifTrue:[
-	^ self fileFormatError:'not a gif file (short read)'.
+        ^ self fileFormatError:'not a gif file (short read)'.
     ].
     id := id asString.
 
@@ -236,17 +234,17 @@
 
     isGif89 := false.
     (id ~= 'GIF87a') ifTrue:[
-	(id startsWith:'GIF') ifFalse:[
-	    ^ self fileFormatError:('not a gif file (id=''' , id , ''')').
-	].
-	id ~= 'GIF89a' ifTrue:[
-	    'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
-	]
+        (id startsWith:'GIF') ifFalse:[
+            ^ self fileFormatError:('not a gif file (id=''' , id , ''')').
+        ].
+        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.
+    scrWidth := aStream nextInt16MSB:false.
+    scrHeight := aStream nextInt16MSB:false.
 
     "get flag byte"
     flag := aStream nextByte.
@@ -264,7 +262,7 @@
 
     "get colorMap"
     hasColorMap ifTrue:[
-	fileColorMap := self readColorMap:colorMapSize.
+        fileColorMap := self readColorMap:colorMapSize.
     ].
     colorMap := fileColorMap.
 
@@ -275,91 +273,91 @@
     imageCount := 0.
     atEnd := false.
     [atEnd] whileFalse:[
-	"gif89a extensions"
+        "gif89a extensions"
 
-	byte := aStream nextByte.
-	byte isNil ifTrue:[
-	    "/ atEnd-Terminator missing
-	    atEnd := true
-	] ifFalse:[
-	    byte == Extension ifTrue:[
+        byte := aStream nextByte.
+        byte isNil ifTrue:[
+            "/ atEnd-Terminator missing
+            atEnd := true
+        ] ifFalse:[
+            byte == Extension ifTrue:[
 "/ 'Ext' infoPrintCR.
-		self readExtension:aStream.
-	    ] ifFalse:[
-		(byte == Terminator) ifTrue:[
-		    atEnd := true
-		] ifFalse:[
-		    "must be image separator"
-		    (byte ~~ ImageSeparator) ifTrue:[
-			^ self fileFormatError:('corrupted gif file (no IMAGESEP): ' , (byte printStringRadix:16)).
-		    ].
+                self readExtension:aStream.
+            ] ifFalse:[
+                (byte == Terminator) ifTrue:[
+                    atEnd := true
+                ] ifFalse:[
+                    "must be image separator"
+                    (byte ~~ ImageSeparator) ifTrue:[
+                        ^ self fileFormatError:('corrupted gif file (no IMAGESEP): ' , (byte printStringRadix:16)).
+                    ].
 "/ 'Img' infoPrintCR.
 
-		    fileColorMap notNil ifTrue:[
-			colorMap := fileColorMap.
-		    ].
-		    Object primitiveFailureSignal handle:[:ex |
-			^ self fileFormatError:('corrupted gif file').
-		    ] do:[
-			self readImage:aStream.
-		    ].
+                    fileColorMap notNil ifTrue:[
+                        colorMap := fileColorMap.
+                    ].
+                    Object primitiveFailureSignal handle:[:ex |
+                        ^ self fileFormatError:('corrupted gif file').
+                    ] do:[
+                        self readImage:aStream.
+                    ].
 
-		    maskPixel notNil ifTrue:[
-			"/
-			"/ ok, there is a maskValue
-			"/ build a Depth1Image for it.
-			"/
-			self buildMaskFromColor:maskPixel
-		    ].
+                    maskPixel notNil ifTrue:[
+                        "/
+                        "/ ok, there is a maskValue
+                        "/ build a Depth1Image for it.
+                        "/
+                        self buildMaskFromColor:maskPixel
+                    ].
 
-		    imageCount == 0 ifTrue:[
-			img := self makeImage.
-			"/ remember first image in case more come later.
-			firstImage := img.
-			firstFrameDelay := frameDelay.
-			firstOffset := (leftOffs @ topOffs).
-		    ] ifFalse:[
-			imageCount == 1 ifTrue:[
-			    imageSequence := ImageSequence new.
-			    img imageSequence:imageSequence.
+                    imageCount == 0 ifTrue:[
+                        img := self makeImage.
+                        "/ remember first image in case more come later.
+                        firstImage := img.
+                        firstFrameDelay := frameDelay.
+                        firstOffset := (leftOffs @ topOffs).
+                    ] ifFalse:[
+                        imageCount == 1 ifTrue:[
+                            imageSequence := ImageSequence new.
+                            img imageSequence:imageSequence.
 
-			    "/ add frame for first image.
-			    frame := ImageFrame new image:firstImage.
-			    frame delay:firstFrameDelay.
-			    frame offset:firstOffset.
-			    imageSequence add:frame.
-			].
-			img := self makeImage.
-			img imageSequence:imageSequence.
+                            "/ add frame for first image.
+                            frame := ImageFrame new image:firstImage.
+                            frame delay:firstFrameDelay.
+                            frame offset:firstOffset.
+                            imageSequence add:frame.
+                        ].
+                        img := self makeImage.
+                        img imageSequence:imageSequence.
 
-			"/ add frame for this image.
-			frame := ImageFrame new image:img.
-			frame delay:frameDelay.
-			frame offset:(leftOffs @ topOffs).
-			imageSequence add:frame.
-		    ].
+                        "/ add frame for this image.
+                        frame := ImageFrame new image:img.
+                        frame delay:frameDelay.
+                        frame offset:(leftOffs @ topOffs).
+                        imageSequence add:frame.
+                    ].
 
-		    imageCount := imageCount + 1.
+                    imageCount := imageCount + 1.
 
-		    frameDelay := nil.
+                    frameDelay := nil.
 
-		    aStream atEnd ifTrue:[
-			atEnd := true.
-		    ]
-		]
-	    ].
-	].
+                    aStream atEnd ifTrue:[
+                        atEnd := true.
+                    ]
+                ]
+            ].
+        ].
     ].
 
     imageSequence notNil ifTrue:[
-	iterationCount notNil ifTrue:[
-	    iterationCount == 0 ifTrue:[
-		imageSequence loop:true.
-	    ] ifFalse:[
-		imageSequence loop:false.
-		imageSequence iterationCount:iterationCount.
-	    ]
-	]
+        iterationCount notNil ifTrue:[
+            iterationCount == 0 ifTrue:[
+                imageSequence loop:true.
+            ] ifFalse:[
+                imageSequence loop:false.
+                imageSequence iterationCount:iterationCount.
+            ]
+        ]
     ].
 
     "
@@ -397,136 +395,136 @@
 
     type := aStream nextByte.
     type == $R codePoint 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
-	].
+        "/
+        "/ 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
+        "/ 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.
-	"/ eat subblocks
-	[(subBlockSize := aStream nextByte) > 0] whileTrue:[
-	    aStream skip:subBlockSize
-	].
-	^ self
+        "/
+        "/ plaintext extension
+        "/
+        "/ 'GIFREADER [info]: plaintext extension ignored' infoPrintCR.
+        subBlockSize := aStream nextByte.
+        left := aStream nextInt16MSB:false.
+        top := aStream nextInt16MSB:false.
+        width := aStream nextInt16MSB:false.
+        height := aStream nextInt16MSB:false.
+        cWidth := aStream nextByte.
+        cHeight := aStream nextByte.
+        fg := aStream nextByte.
+        bg := aStream nextByte.
+        aStream skip:12.
+        "/ eat subblocks
+        [(subBlockSize := aStream nextByte) > 0] whileTrue:[
+            aStream skip:subBlockSize
+        ].
+        ^ self
     ].
 
     type == 16rF9 ifTrue:[
-	"/
-	"/ graphic control extension
-	"/
-	"/ 'GIFREADER [info]: graphic control extension' infoPrintCR.
+        "/
+        "/ graphic control extension
+        "/
+        "/ 'GIFREADER [info]: graphic control extension' infoPrintCR.
 
-	[(subBlockSize := aStream nextByte) ~~ 0 and:[subBlockSize notNil]] whileTrue:[
-	    "/ type bitAnd:1 means: animationMask is transparent pixel
-	    "/ to be implemented in Image ...
+        [(subBlockSize := aStream nextByte) ~~ 0 and:[subBlockSize notNil]] whileTrue:[
+            "/ type bitAnd:1 means: animationMask is transparent pixel
+            "/ to be implemented in Image ...
 
-	    animationType := aStream nextByte.
-	    animationTime := aStream nextShortMSB:false.
-	    animationMask := aStream nextByte.
+            animationType := aStream nextByte.
+            animationTime := aStream nextInt16MSB:false.
+            animationMask := aStream nextByte.
 
-	    subBlockSize := subBlockSize - 4.
+            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.
 "/            'GIFREADER [info]: animationType: ' infoPrint. (animationType) infoPrintCR.
 "/            'GIFREADER [info]: animationMask: ' infoPrint. (animationMask) infoPrintCR.
 
-	    frameDelay := (animationTime * (1/100)) * 1000.
+            frameDelay := (animationTime * (1/100)) * 1000.
 
-	    subBlockSize ~~ 0 ifTrue:[
-		aStream skip:subBlockSize
-	    ].
-	].
-	^ self
+            subBlockSize ~~ 0 ifTrue:[
+                aStream skip:subBlockSize
+            ].
+        ].
+        ^ self
     ].
 
     type == 16rFE ifTrue:[
-	"/
-	"/ comment extension
-	"/
-	"/ 'GIFREADER [info]: comment extension' infoPrintCR.
-	[(blockSize := aStream nextByte) ~~ 0] whileTrue:[
-	    aStream skip:blockSize
-	].
-	^ self
+        "/
+        "/ comment extension
+        "/
+        "/ 'GIFREADER [info]: comment extension' infoPrintCR.
+        [(blockSize := aStream nextByte) ~~ 0] whileTrue:[
+            aStream skip:blockSize
+        ].
+        ^ self
     ].
 
     type == 16rFF ifTrue:[
-	"/
-	"/  application extension
-	"/
-	"/ 'GIFREADER [info]: application extension' infoPrintCR.
-	subBlockSize := aStream nextByte.
-	appID := (aStream nextBytes:8 ) asString.
-	appAUTH := aStream nextBytes:3.
+        "/
+        "/  application extension
+        "/
+        "/ 'GIFREADER [info]: application extension' infoPrintCR.
+        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 nextInt16MSB:false.
+                    subBlockSize := aStream nextByte.
+                    ok := true.
 "/                    ('GIFREADER [info]: NETSCAPE application extension - iterationCount = ') infoPrint.
 "/                    iterationCount infoPrintCR.
-		]
-	    ]
-	].
+                ]
+            ]
+        ].
 
-	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
     ].
 
     "/
@@ -534,7 +532,7 @@
     "/
     'GIFREADER [info]: unknown extension ignored' infoPrintCR.
     [(subBlockSize := aStream nextByte) > 0] whileTrue:[
-	aStream skip:subBlockSize
+        aStream skip:subBlockSize
     ]
 
     "Modified: / 02-06-2010 / 12:21:53 / cg"
@@ -548,12 +546,12 @@
      initialBuffSize|
 
     "get image data"
-    leftOffs := aStream nextShortMSB:false.
-    topOffs := aStream nextShortMSB:false.
+    leftOffs := aStream nextInt16MSB:false.
+    topOffs := aStream nextInt16MSB:false.
 "/    'GIFReader: leftOffs ' infoPrint. leftOffs infoPrintCR.
 "/    'GIFReader: topOffs ' infoPrint. topOffs infoPrintCR.
-    width := aStream nextShortMSB:false.
-    height := aStream nextShortMSB:false.
+    width := aStream nextInt16MSB:false.
+    height := aStream nextInt16MSB:false.
 
     self reportDimension.
 
@@ -571,20 +569,20 @@
     "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"
-	colorMap := self readColorMap:colorMapSize.
+        "local descr. overwrites"
+        bitsPerPixel := (flag bitAnd:2r00000111) + 1.
+        colorMapSize := 1 bitShift:bitsPerPixel.
+        "overwrite colormap"
+        colorMap := self readColorMap:colorMapSize.
     ].
 
 
     "get codelen for decompression"
     codeLen := aStream nextByte.
     (aStream respondsTo:#fileSize) ifTrue:[
-	initialBuffSize := aStream fileSize.
+        initialBuffSize := aStream fileSize.
     ] ifFalse:[
-	initialBuffSize := 512.
+        initialBuffSize := 512.
     ].
     compressedData := ByteArray uninitializedNew:initialBuffSize.
 
@@ -592,17 +590,17 @@
     index := 1.
     count := aStream nextByte.
     [count notNil and:[count ~~ 0]] whileTrue:[
-	(compressedData size < (index+count)) ifTrue:[
-	    |t|
+        (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.
-	].
+            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
+        aStream nextBytes:count into:compressedData startingAt:index blockSize:4096.
+        index := index + count.
+        count := aStream nextByte
     ].
     compressedSize := index - 1.
 
@@ -611,54 +609,54 @@
 "/    'GIFReader: decompressing ...' infoPrintCR.
 
     self class decompressGIFFrom:compressedData
-			   count:compressedSize
-			    into:data
-		      startingAt:1
-			 codeLen:(codeLen + 1).
+                           count:compressedSize
+                            into:data
+                      startingAt:1
+                         codeLen:(codeLen + 1).
 
     interlaced ifTrue:[
 "/    'GIFREADER: deinterlacing ...' infoPrintCR.
-	tmp := ByteArray new:(data size).
+        tmp := ByteArray new:(data size).
 
-	"phase 1: 0, 8, 16, 24, ..."
+        "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.
-	].
+        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, ..."
+        "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.
-	].
+        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, ..."
+        "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.
-	].
+        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, ..."
+        "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.
-	].
+        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.
+        data := tmp.
+        tmp := nil.
     ].
 
     "Created: / 13.1.1998 / 10:44:05 / cg"
@@ -977,7 +975,7 @@
     outStream nextPut:4.           "/ subBlockSize
 
     outStream nextPut:1.                "/ animationType
-    outStream nextPutShort:1 MSB:false. "/ animationTime
+    outStream nextPutInt16:1 MSB:false. "/ animationTime
     outStream nextPut:maskPixel.        "/ animationMask
 
     outStream nextPut:0.
@@ -1026,9 +1024,9 @@
     "save image in GIF-file-format onto aStream"
 
     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 := aStream.
@@ -1036,7 +1034,7 @@
 
     mask := image mask.
     mask notNil ifTrue:[
-	self assignTransparentPixelIn:image
+        self assignTransparentPixelIn:image
     ].
 
     byteOrder := #lsb.
@@ -1050,24 +1048,24 @@
 
     self writeHeaderFor:image.
     maskPixel notNil ifTrue:[
-	self writeMaskExtensionHeaderFor:image.
+        self writeMaskExtensionHeaderFor:image.
     ].
 
     self writeBitDataFor:image.
 
     image imageSequence notEmptyOrNil ifTrue:[
-	image imageSequence do:[:eachFrame |
-	    outStream nextPut:Extension.
-	    outStream nextPut:16rF9.    "/ graphic control extension
-	    outStream nextPut:4.        "/ sub block size
-	    outStream nextPut:0.        "/ animation type 0
-	    outStream nextPutShort:(eachFrame delay / 10) rounded asInteger MSB:false.
-	    outStream nextPut:0.        "/ animation mask
-	    outStream nextPut:0.        "/ subblock size
+        image imageSequence do:[:eachFrame |
+            outStream nextPut:Extension.
+            outStream nextPut:16rF9.    "/ graphic control extension
+            outStream nextPut:4.        "/ sub block size
+            outStream nextPut:0.        "/ animation type 0
+            outStream nextPutInt16:(eachFrame delay / 10) rounded asInteger MSB:false.
+            outStream nextPut:0.        "/ animation mask
+            outStream nextPut:0.        "/ subblock size
 
-	    self writeBitDataFor:eachFrame image.
+            self writeBitDataFor:eachFrame image.
 
-	].
+        ].
     ].
 
     outStream nextPut: Terminator.
@@ -1087,11 +1085,11 @@
 !GIFReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.108 2015-05-07 20:42:35 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.108 2015-05-07 20:42:35 cg Exp $'
+    ^ '$Header$'
 ! !