Hello all,

Please excuse the length of this email.

A week or two ago I discovered that the GIF implementation in Pharo (and
possibly Squeak?) is incomplete. This has two side effects:
1) Not all GIF data will load correctly;
2) There is for now no way to display animated GIFs.

It looks like the corresponding classes have not been updated since the 90s.

But fear not! I've been working on a solution, and need the community's
feedback and advice.

# The Problem with GIFs #
One of the issues here is that GIF files can (and do) contain multiple
images inside of them. The root header will supply things like a "screen
size" in which these nested images should be displayed. That also means
that each nested image does not have to have the same dimensions as the
parent object -- in fact, most are offset somewhere inside of the "screen."

Additionally, each nested image will contain information about how it
should be handled when animating. This is a crucial point. In many cases
images are just updates of a small area that should be applied to the
previous image in the set. GIFs call this attribute the "disposal," and
this information is contained in a packed byte.

Both GIFReadWriter and AnimatedGIFReadWriter have intentionally
skipped/ignored the bits/bytes that store and keep track of these things.
GIFReadWriter on its own will only read the first Form and does not store
information about disposal, offsets, etc. These classes are not reading all
the information we need to display GIFs!

# My Solution #
The attached changes file includes some preliminary updates to the
GIFReadWriter class. Now when each nested image is read, it will be loaded
into a collection called "frames" as a (new -- see attached package file)
AnimatedImageFrame. Instances of this new class will store the disposal
symbol, offset, and form for each nested image in the file.

I have also created an AnimatedImageMorph which reads AnimatedImageFrame
objects and cycles them based on the disposal re-drawing rules.

# Trying This Out #
To try this out, first load the attached changes file and the ST file.

You'll need a FileReference to a gif file, so when you have one execute the
following:

```smalltalk
file := "your gif filereference here"
img := AnimatedImageMorph fromGIFReader: (AnimatedGIFReadWriter
formsFromStream: file readStream).
img openInWorld.
```

# Issues #
Not all GIF images work. This has to do with my implementation of the
disposal (redrawing) rules for each frame. I'm still experimenting.

I believe AnimatedGIFReadWriter should be deprecated and all appropriate
functionality should be put into GIFReadWriter. If you all agree, I will
make several changes to GIFReadWriter that I think will be helpful /
necessary.

AnimatedImageMorph is also incomplete. I'm not sure if I should subclass
ImageMorph for this or not.

# Your Feedback #
If you disagree with any point of this architecture, please let me know.
Also if you come across GIFs that do not animate or display properly, send
them my way please!

-- 
Eric

Attachment: Images-Animated.st
Description: Binary data

'From Pharo6.0 of 13 May 2016 [Latest update: #60540] on 23 May 2018 at 11:28:36.06927 am'!
ImageReadWriter subclass: #GIFReadWriter
	instanceVariableNames: 'width height bitsPerPixel colorPalette rowByteSize xpos ypos pass interlace codeSize clearCode eoiCode freeCode maxCode prefixTable suffixTable remainBitCount bufByte bufStream transparentIndex mapOf32 localColorTable delay loopCount offset frames canvasWidth canvasHeight backgroundColorIndex'
	classVariableNames: 'Extension ImageSeparator Terminator'
	poolDictionaries: ''
	category: 'Graphics-Files'!

!GIFReadWriter methodsFor: 'private-decoding' stamp: 'EricGade 5/18/2018 17:36'!
readHeader
	| is89 byte hasColorMap |
	frames := OrderedCollection new. "For storing AnimatedImageFrames"
	(self hasMagicNumber: 'GIF87a' asByteArray) 
		ifTrue: [ is89 := false ]
		ifFalse: 
			[ (self hasMagicNumber: 'GIF89a' asByteArray) 
				ifTrue: [ is89 := true ]
				ifFalse: [ ^ self error: 'This does not appear to be a GIF file' ] ].
	"Width and Height for whole canvas, not
	just an invididual frame/form"
	canvasWidth := self readWord.
	canvasHeight := self readWord.
	byte := self next.
	hasColorMap := (byte bitAnd: 128) ~= 0.
	bitsPerPixel := (byte bitAnd: 7) + 1.
	backgroundColorIndex := self next.
	self next ~= 0 ifTrue: 
		[ is89 ifFalse: [ ^ self error: 'corrupt GIF file (screen descriptor)' ] ].
	hasColorMap 
		ifTrue: [ colorPalette := self readColorTable: (1 bitShift: bitsPerPixel) ]
		ifFalse: 
			[ "Transcript cr; show: 'GIF file does not have a color map.'."
			colorPalette := nil	"Palette monochromeDefault" ]! !

!GIFReadWriter methodsFor: 'private-decoding' stamp: 'EricGade 5/18/2018 16:04'!
readBody
	"Read the GIF blocks. Modified to return a form.  "
	| form extype block blocksize packedFields delay1 disposal frame |
	form := nil.
	frame := AnimatedImageFrame new.
	[ stream atEnd ] whileFalse: 
		[ block := self next.
		block = Terminator ifTrue: [ ^ form ].
		block = ImageSeparator 
			ifTrue: 
				[ form
					ifNil: [ 
						form := self readBitData.
						frame 
							form: form;
							offset: form offset ]
					ifNotNil: [ self skipBitData ] ]
			ifFalse: 
				[ block = Extension ifFalse: [ ^ form	"^ self error: 'Unknown block type'" ].
				"Extension block"
				extype := self next.	"extension type"
				extype = 249 
					ifTrue: 
						[ "graphics control"
						self next = 4 ifFalse: [ ^ form	"^ self error: 'corrupt GIF file'" ].
						"====
				Reserved                      3 Bits
				Disposal Method               3 Bits
				User Input Flag               1 Bit
				Transparent Color Flag        1 Bit
				==="
						packedFields := self next.
						disposal := self readDisposal: packedFields.
						delay1 := self next.	"delay time 1"
						delay := (self next * 256 + delay1) * 10.	"delay time 2"
						transparentIndex := self next.
						(packedFields bitAnd: 1) = 0 
							ifTrue: [ transparentIndex := nil ]
							ifFalse: [ 
								Transcript show: ('transparentBitSet for ',transparentIndex asString); cr].
						self next = 0 ifFalse: [ ^ form	"^ self error: 'corrupt GIF file'" ]. 
						frame
							form: form;
							delay: delay1 * 10; "We might need to use the other?"
							disposal: disposal.
						frames add: frame ]
					ifFalse: 
						[ "Skip blocks"
						[ (blocksize := self next) > 0 ] whileTrue: 
							[ "Read the block and ignore it and eat the block terminator"
							self next: blocksize ] ] ] ].
			frame form: form.
			frames add: frame.! !

!GIFReadWriter methodsFor: 'accessing' stamp: 'EricGade 5/18/2018 12:41'!
frames
	^ frames! !

!GIFReadWriter methodsFor: 'accessing' stamp: 'EricGade 5/18/2018 14:37'!
canvasHeight
	^ canvasHeight! !

!GIFReadWriter methodsFor: 'accessing' stamp: 'EricGade 5/18/2018 17:54'!
backgroundColor
	backgroundColorIndex ifNotNil: [ 
		colorPalette ifNotNil: [ 
			^ colorPalette at: backgroundColorIndex + 1]].
	^ Color transparent.! !

!GIFReadWriter methodsFor: 'accessing' stamp: 'EricGade 5/18/2018 14:37'!
canvasWidth
	^ canvasWidth! !

!GIFReadWriter methodsFor: 'as yet unclassified' stamp: 'EricGade 5/18/2018 16:01'!
readDisposal: aPackedByte
	"Read the three-bit disposal flag from
	the packed byte in the Graphic Control Extension block.
	Disposal is three-bits with the following codes:
	 |0 0 0 [0 0 0] 0 0|
	1 => leave current frame and draw on top of it (#leaveCurrent)
	2 => Restore to background color (#restoreBackground)
	3 => Restore to state before current frame was drawn (#restorePrevState)"
	| least middle both str |
	
	"This means both the least significant and middle
	bits are set, giving us 3"
	str := ''.
	((aPackedByte bitAnd: 16) = 16)
		ifTrue: [ str := str,'1' ]
		ifFalse: [ str := str,'0' ].
	((aPackedByte bitAnd: 8) = 8)
		ifTrue: [ str := str,'1' ]
		ifFalse: [ str := str,'0' ].
	((aPackedByte bitAnd: 4) = 4)
		ifTrue: [ str := str,'1' ]
		ifFalse: [ str := str,'0' ].
	Transcript show: str; cr.
	(both := (aPackedByte bitAnd: 12) = 12).
	both ifTrue: [ ^ #restorePrevState ].
	
	least := (aPackedByte bitAnd: 4) = 4.
	least ifTrue: [ ^ #leaveCurrent ].
	
	middle := (aPackedByte bitAnd: 8) = 8.
	middle ifTrue: [ ^ #restoreToBackground ].
	
	^ nil
	! !


!GIFReadWriter reorganize!
(#private updatePixelPosition checkCodeSize setParameters:)
(#'stream access' close)
(#'private-bits access' nextBitsPut: nextBits flushBits)
(#'private-decoding' readBitData readHeader readCode readWord readColorTable: skipBitData readBody)
(#'private-encoding' writeBitData: writeCode: readPixelFrom: flushCode writeWord: writeHeader writeCodeAndCheckCodeSize:)
(#'private-packing' fillBuffer peekByte nextBytePut: flushBuffer nextByte)
(#accessing nextImage understandsImageFormat frames canvasHeight delay: setStream: backgroundColor nextPutImage: canvasWidth loopCount:)
(#'as yet unclassified' readDisposal:)
!

Reply via email to