GIFReader.st
author Claus Gittinger <cg@exept.de>
Fri, 11 Apr 1997 00:55:22 +0200
changeset 519 1ee56341ef50
parent 398 aef700d15416
child 563 38cbee875bfa
permissions -rw-r--r--
*** empty log message ***

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

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

    Image addReader:self suffix:'gif'.

    "Modified: 1.2.1997 / 14:59:37 / cg"
! !

!GIFReader class methodsFor:'testing'!

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:'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
     colorMapSize bitsPerPixel scrWidth scrHeight
     hasColorMap hasLocalColorMap interlaced id
     leftOffs topOffs codeLen
     compressedData compressedSize
     tmp srcOffset dstOffset isGif89 
     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
    ].

    "skip gif89a extensions "
    byte := aStream nextByte.
    [byte == 16r21] whileTrue:[
        "/ extension
        self readExtension:aStream.
        byte := aStream nextByte.
    ].

    "must now be image separator"
    (byte ~~ 16r2C) 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.
" '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 ...' 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
    ].

    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.

    maskPixelValue notNil ifTrue:[
        "/
        "/ ok, there is a maskValue
        "/ build a Depth1Image for it.
        "/
        self buildMaskFromColor:maskPixelValue
    ].

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

    "Modified: 5.7.1996 / 17:32:01 / stefan"
    "Modified: 10.1.1997 / 15:40:58 / 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|

    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.

        "/ type=1 means: animationMask is transparent pixel
        "/ to be implemented in Image ...

        animationType := aStream nextByte.
        animationTime := aStream nextShortMSB:false.
        animationMask := aStream nextByte.

        animationType == 1 ifTrue:[
            maskPixelValue := animationMask.
"/            'GIFREADER [info]: mask: ' infoPrint. (maskPixelValue printStringRadix:16) infoPrintCR.
        ].

        [(subBlockSize := aStream nextByte) > 0] whileTrue:[
            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
        "/
        'GIFREADER [info]: application 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: 11.4.1997 / 00:55:15 / cg"
! !

!GIFReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.47 1997-04-10 22:55:22 cg Exp $'
! !
GIFReader initialize!