GIFReader.st
author Claus Gittinger <cg@exept.de>
Sat, 11 Nov 1995 17:05:49 +0100
changeset 114 e577a2f332d0
parent 99 a656b0c9dd21
child 135 ff507d9a242b
permissions -rw-r--r--
uff - version methods changed to return stings

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

'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 2:18:24 am'!

ImageReader subclass:#GIFReader
	 instanceVariableNames:'redMap greenMap blueMap'
	 classVariableNames:''
	 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.
"
!

version
    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.19 1995-11-11 16:04:30 cg Exp $'
!

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

!GIFReader class methodsFor:'initialization'!

initialize
    Image fileFormats at:'.gif'  put:self.
    Image fileFormats at:'.GIF'  put:self.
! !

!GIFReader class methodsFor:'testing'!

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

    |id inStream|

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

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

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

	'GIFReader: not GIF87a - untested' errorPrintNL.
    ].
    ^ true
! !

!GIFReader methodsFor:'reading from file'!

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

    |sz "{ Class: SmallInteger }"|

"/    redMap := Array new:colorMapSize.
"/    greenMap := Array new:colorMapSize.
"/    blueMap := Array new:colorMapSize.
    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)
    ]
!

checkGreyscaleColormap
    "return true, if colormap is really a greymap"

    |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
!

makeGreyscale
    "not yet implemented/needed"
!

fromStream:aStream
    "read a GIF file"

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

    inStream := aStream.
    aStream binary.

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

    id := String new:6.
    aStream nextBytes:6 into:id.

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

    (id ~= 'GIF87a') ifTrue:[
	(id startsWith:'GIF') ifFalse:[
	    'GIFReader: not a gif file' errorPrintNL.
	    ^ nil
	].
	'GIFReader: not a GIF87a file - hope that works' errorPrintNL.
    ].

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

    "image separator"
    byte := aStream nextByte.
    (byte ~~ 16r2C) ifTrue:[
	'GIFReader: corrupted gif file (no imgSep)' errorPrintNL.
	^ nil
    ].

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

"
'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.
" 'local colormap' printNewline. "
	"overwrite colormap"
	self readColorMap:colorMapSize
    ].

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

    compressedData := ByteArray uninitializedNew:(aStream size).

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

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

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

    interlaced ifTrue:[
	Transcript showCr:'deinterlacing'.
	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
    ].

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

    "check if only grey values are used,
     could make it a greyscale image if so (currently not done)"

"/    self checkGreyscaleColormap ifTrue:[
"/        self makeGreyscale
"/    ].

    colorMap := Colormap redVector:redMap greenVector:greenMap blueVector:blueMap.

    "
     GIFReader fromFile:'../fileIn/bitmaps/claus.gif
     GIFReader fromFile:'../fileIn/bitmaps/garfield.gif'
    "
! !

GIFReader initialize!