PCXReader.st
author Claus Gittinger <cg@exept.de>
Thu, 24 Apr 1997 19:47:57 +0200
changeset 561 bb8103acb292
parent 531 19c16bd5e0bf
child 566 f3cbbba715d9
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1994 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:#PCXReader
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images-Support'
!

!PCXReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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 8-plane PCX bitmap files.

    Due to not having too many examples for testing, this could fail
    to read some files. 
    (especially, I have no uncompressed files for testing).

    Only 8-bit (i.e. 256 color) PCX images are supported.
    Image writing is not supported.

    [See also:]
	Image Form Icon
	BlitImageReader FaceReader GIFReader JPEGReader PBMReader 
	ST80FormReader SunRasterReader TargaReader TIFFReader WindowsIconReader 
	XBMReader XPMReader XWDReader 
"
! !

!PCXReader class methodsFor:'initialization'!

initialize
    "tell Image-class, that a new fileReader is present
     for the '.pcx' extension."

    Image addReader:self suffix:'pcx'.

    "Modified: 1.2.1997 / 15:02:32 / cg"
! !

!PCXReader class methodsFor:'testing'!

isValidImageFile:aFilename
    "return true, if aFilename contains a PCX image"

    |count header inStream|

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

    header := ByteArray uninitializedNew:128.
    count := inStream nextBytes:128 into:header.
    inStream close.

    ((count == 128) and:[self isValidPCXHeader:header]) ifFalse:[
	^ false
    ].
    ^ true

    "Modified: 17.9.1995 / 17:32:07 / claus"
!

isValidPCXHeader:aHeader
    "return true, if aHeader looks like a PCX image header"

    "check magic number"
    ((aHeader at:1) ~~ 16r0A) ifTrue:[
	^ false
    ].

    "check version"
    (#(0 2 3 5) includes:(aHeader at:2)) ifFalse:[
	^ false
    ].

    ^ true

    "Modified: 16.4.1997 / 22:24:32 / cg"
! !

!PCXReader methodsFor:'reading from file'!

fromStream:aStream
    "read an image in pcx format from aStream"

    |fileSize header img|

    inStream := aStream.

    inStream binary.
    fileSize := aStream size.

    fileSize < 128 ifTrue:[
	self error:'PCXREADER: short file'.
	^ nil
    ].

    header := ByteArray uninitializedNew:128.
    aStream nextBytes:128 into:header.

    (self class isValidPCXHeader:header) ifFalse:[
	self error:'PCXREADER: wrong header'.
	^ nil
    ].

    img := self fromStreamWithHeader:header.
    ^ img
!

fromStreamWithHeader:header 
    "read an raw image in pcx format from aStream.
     The header has already been read into the header argument."

    | inDepth version compression nPlanes xmin ymin xmax ymax
      paletteType rawMap rMap gMap bMap 
      endIndex    "{Class: SmallInteger }"
      srcIndex    "{Class: SmallInteger }"
      dstIndex    "{Class: SmallInteger }"
      rowIndex    "{Class: SmallInteger }"
      h           "{Class: SmallInteger }"
      byte        "{Class: SmallInteger }"
      nByte       "{Class: SmallInteger }"
      srcBytesPerRow "{Class: SmallInteger }"
      value       "{Class: SmallInteger }"
      idx2        "{Class: SmallInteger }"
      dataBytes buffer 
      bufferIndex "{Class: SmallInteger }"
      bendIndex   "{Class: SmallInteger }"
      nBuffer     "{Class: SmallInteger }"
      mapSize|

    "/ typedef struct {                         /*header for PCX bitmap files*/
    "/    unsigned char       signature;          /*PCX file identifier*/
    "/    unsigned char       version;            /*version compatibility level*/
    "/    unsigned char       encoding;           /*encoding method*/
    "/    unsigned char       bitsperpix;         /*bits per pixel, or depth*/
    "/    unsigned short      Xleft;              /*X position of left edge*/
    "/    unsigned short      Ytop;               /*Y position of top edge*/
    "/    unsigned short      Xright;             /*X position of right edge*/
    "/    unsigned short      Ybottom;            /*Y position of bottom edge*/
    "/    unsigned short      Xscreensize;        /*X screen res of source image*/
    "/    unsigned short      Yscreensize;        /*Y screen res of source image*/
    "/    unsigned char       PCXpalette[16][3];  /*PCX color map*/
    "/    unsigned char       reserved1;          /*should be 0, 1 if std res fax*/
    "/    unsigned char       planes;             /*bit planes in image*/
    "/    unsigned short      linesize;           /*byte delta between scanlines */
    "/    unsigned short      paletteinfo;            /*0 == undef
    "/                                                  1 == color
    "/                                                  2 == grayscale*/
    "/    unsigned char reserved2[58];            /*fill to struct size of 128*/
    "/ } PCX_HEADER;

    version := header at:2.
"/    'version=' print. version printNL.
    compression := header at:3.
"/    'compression=' print. compression printNL.
    (#(0 1) includes:compression) ifFalse:[
        self error:'PCXREADER: unknown compression'.
        ^ nil
    ].

    inDepth := header at:4.
"/    'depth=' print. inDepth printNL.
    nPlanes := header at:66.
"/    'planes=' print. nPlanes printNL.
    srcBytesPerRow := header wordAt:67 MSB:false.
"/    'srcBytesPerRow=' print. srcBytesPerRow printNL.
    paletteType := header at:69.

    "
     although it would be easy to implement ...
     I have no test pictures for other formats.
     So its not (yet) implemented
    "
    ((inDepth ~~ 8) or:[nPlanes ~~ 1]) ifTrue:[
        'PCXReader: depth: ' errorPrint. inDepth errorPrint. 
        ' planes:' errorPrint. nPlanes errorPrintNL.
        'PCXReader: can only handle 1-plane 256 color images' errorPrintNL.
        ^ nil
    ].

    xmin := header wordAt:5 MSB:false. 
    ymin := header wordAt:7 MSB:false.
    xmax := header wordAt:9 MSB:false. 
    ymax := header wordAt:11 MSB:false.

    width := (xmax - xmin + 1).
    height := (ymax - ymin + 1).
"/    'width=' print. width printNL.
"/    'height=' print. width printNL.

    (version == 2) ifTrue:[
        "read the 16-entry colormap"

        rawMap := ByteArray uninitializedNew:(16*3).
        rawMap replaceFrom:1 to:(16*3) with:header startingAt:17.
        rMap := ByteArray new:16.
        gMap := ByteArray new:16.
        bMap := ByteArray new:16.
        srcIndex := 1.
        1 to:16 do:[:i |
            rMap at:i put:(rawMap at:srcIndex).
            srcIndex := srcIndex + 1.
            gMap at:i put:(rawMap at:srcIndex).
            srcIndex := srcIndex + 1.
            bMap at:i put:(rawMap at:srcIndex).
            srcIndex := srcIndex + 1.
        ].
    ].

    compression == 1 ifTrue:[
        data := dataBytes := ByteArray uninitializedNew:(height * srcBytesPerRow).

        buffer := ByteArray uninitializedNew:4096.
        bufferIndex := 1.
        bendIndex := 1.

        rowIndex := 1.
        h := height.
        1 to:h do:[:row |
            dstIndex := rowIndex.
            endIndex := dstIndex + srcBytesPerRow.
            [dstIndex < endIndex] whileTrue:[
                bufferIndex == bendIndex ifTrue:[
                    nBuffer := inStream nextBytes:4096 into:buffer.
                    bufferIndex := 1.
                    bendIndex := nBuffer + 1.
                ].
                byte := buffer at:bufferIndex.
                bufferIndex := bufferIndex + 1.
                ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
                    dataBytes at:dstIndex put:byte.
                    dstIndex := dstIndex + 1.
                ] ifFalse:[
                    nByte := byte bitAnd:2r00111111.
                    bufferIndex == bendIndex ifTrue:[
                        nBuffer := inStream nextBytes:4096 into:buffer.
                        bufferIndex := 1.
                        bendIndex := nBuffer + 1.
                    ].
                    value := buffer at:bufferIndex.
                    bufferIndex := bufferIndex + 1.
                    idx2 := ((dstIndex + nByte) min:endIndex) - 1.
                    dataBytes from:dstIndex to:idx2 put:value.
                    dstIndex := dstIndex + nByte.
                ].
            ].
            rowIndex := endIndex.
        ].

        "/ have to compress - above code reads srcBytesPerRow
        "/ (to keep in sync with RLE); but we want width bytesPerRow
        "/ Can compress in the data-area; leftover pixels are simply ignored
        "/ by other image processing code
        "/
        srcBytesPerRow ~~ width ifTrue:[
            dstIndex := width + 1.
            srcIndex := srcBytesPerRow + 1.
            2 to:h do:[:row |
                dataBytes replaceFrom:dstIndex to:dstIndex+width-1 with:dataBytes startingAt:srcIndex.
                dstIndex := dstIndex + width.
                srcIndex := srcIndex + srcBytesPerRow
            ]
        ].
        nBuffer := endIndex - bufferIndex.
    ] ifFalse:[
        "
         uncompressed; actually untested ...
        "
        data := dataBytes := ByteArray uninitializedNew:(height * width).
        srcBytesPerRow ~~ width ifTrue:[
            dstIndex := 1.
            1 to:h do:[:row |
                inStream nextBytes:width into:data startingAt:dstIndex.
                dstIndex := dstIndex + width.
                inStream skip:(srcBytesPerRow - width).
            ]
        ] ifFalse:[
            inStream nextBytes:(height * width) into:data.
        ].
        nBuffer := 0.
    ].

    (version == 5) ifTrue:[
        "read the 256-entry colormap"

        nBuffer ~~ 0 ifTrue:[
            byte := buffer at:bufferIndex.
            bufferIndex := bufferIndex + 1. nBuffer := nBuffer - 1.
        ] ifFalse:[
            byte := inStream next
        ].

        byte == 16r0C ifFalse:[
           'PCXREADER: no valid 256-entry palette (got' errorPrint. 
           byte errorPrint. '; expected ' errorPrint. 16rC0 errorPrint. ')' errorPrintNL.
        ].
        rawMap := ByteArray uninitializedNew:(256*3).
        nBuffer ~~ 0 ifTrue:[
            mapSize := buffer size - bufferIndex + 1.
            mapSize := mapSize min:(256*3).
            rawMap replaceFrom:1 to:mapSize with:buffer startingAt:bufferIndex.
            nBuffer < (256*3) ifTrue:[
                inStream nextBytes:((256*3)-nBuffer) into:rawMap startingAt:nBuffer+1
            ]
        ] ifFalse:[
            inStream nextBytes:(256*3) into:rawMap.
        ].
        rMap := Array new:256.
        gMap := Array new:256.
        bMap := Array new:256.
        srcIndex := 1.
        1 to:256 do:[:i |
            rMap at:i put:(rawMap at:srcIndex).
            srcIndex := srcIndex + 1.
            gMap at:i put:(rawMap at:srcIndex).
            srcIndex := srcIndex + 1.
            bMap at:i put:(rawMap at:srcIndex).
            srcIndex := srcIndex + 1.
        ].
    ].

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).
    colorMap := Colormap redVector:rMap greenVector:gMap blueVector:bMap.

    "
     |i f|
     i := Image fromFile:'somefile.pcx'.
     i inspect.
    "

    "Modified: 24.4.1997 / 19:38:52 / cg"
! !

!PCXReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/PCXReader.st,v 1.21 1997-04-24 17:47:57 cg Exp $'
! !
PCXReader initialize!