PCXReader.st
author Claus Gittinger <cg@exept.de>
Sat, 12 May 2018 14:23:45 +0200
changeset 4088 bbf9b58f99c8
parent 3996 9f8c87c19905
child 4149 1366a87d9e5f
permissions -rw-r--r--
#FEATURE by cg class: MIMETypes class changed: #initializeFileInfoMappings class: MIMETypes::MIMEType added: #asMimeType #isCHeaderType #isCPPSourceType #isCSourceType

"
 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.
"
"{ Package: 'stx:libview2' }"

"{ NameSpace: Smalltalk }"

ImageReader subclass:#PCXReader
	instanceVariableNames:'header sourceBytesPerRow bitsPerPixelIn depth nPlanes compression
		nPlanesUsed'
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images-Readers'
!

!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 to load PCX bitmap files.
    
    PCX used to be a popular image format in the early PC times,
    but became almost obsolete in the meantime.
    This reader is not tuned and performs slow on non-8bit images;
    if at all, use it to convert old image files to newer formats,
    such as png, tiff or jpg.
    
    Due to not having too many examples for testing, 
    this could fail to read some files. 
    (especially, I have no uncompressed files for testing).

    1,2,4,8 and 24-bit PCX images are supported, both in single and separate
    plane formats.

    Image writing is not.

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

examples
"
                                                        [exBegin]
    Image fromFile:'/usr/share/lilo/suse_640x480.pcx'
                                                        [exEnd]
                                                        [exBegin]
    Image fromFile:'../../goodies/bitmaps/pcxImages/lena_depth8_palette.pcx'
                                                        [exEnd]
"
! !

!PCXReader class methodsFor:'initialization'!

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

    MIMETypes defineImageType:'image/x-pcx'  suffix:'pcx' reader:self.

    "Modified: 27.6.1997 / 18:39:23 / 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:'obsolete'!

readCompressedData
    |rowStartIndex  endIndex byte nByte value idx2
     srcIndex dstIndex srcRowStartIndex dstRowStartIndex bytesPerPane planeData imageBytesPerRow|

    (nPlanes > 1 and:[depth == 8]) ifTrue:[
        ^ self readCompressedDepth24Data.
    ].

    imageBytesPerRow := (((width * depth) + 7) // 8).

    bytesPerPane := height * (imageBytesPerRow max:sourceBytesPerRow).
    planeData := 1 to:nPlanes collect:[:planeNr | ByteArray uninitializedNew:bytesPerPane].
    data := planeData at:1.

    rowStartIndex := 1.
    1 to:height do:[:row |
        1 to:nPlanes do:[:planeNr |
            |planeBytes|

            planeBytes := planeData at:planeNr.

            dstIndex := rowStartIndex.
            endIndex := dstIndex + sourceBytesPerRow.

            [dstIndex < endIndex] whileTrue:[
                byte := inStream nextByte.
                ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
                    planeBytes at:dstIndex put:byte.
                    dstIndex := dstIndex + 1.
                ] ifFalse:[
                    nByte := byte bitAnd:2r00111111.
                    value := inStream nextByte.
                    idx2 := ((dstIndex + nByte) min:endIndex) - 1.
                    planeBytes from:dstIndex to:idx2 put:value.
                    dstIndex := dstIndex + nByte.
                ].
            ].
        ].
        "/ rowStartIndex := endIndex.
        rowStartIndex := rowStartIndex + (imageBytesPerRow * nPlanes).
    ].

    "/ now merge the planes
    nPlanes > 1 ifTrue:[
        depth == 8 ifTrue:[
            (nPlanes >= 3) ifTrue:[
                "/ a simple rgb image
                nPlanes := nPlanes min:4.

                data := ByteArray uninitializedNew:(nPlanes*width*height).
                srcRowStartIndex := dstRowStartIndex := 1.
                1 to:height do:[:y |
                    1 to:nPlanes do:[:p |
                        |planeBytes|

                        dstIndex := dstRowStartIndex + (p - 1).
                        srcIndex := srcRowStartIndex.
                        planeBytes := planeData at:p.
                        1 to:width do:[:x |
                            data at:dstIndex put:(planeBytes at:srcIndex).
                            dstIndex := dstIndex + nPlanes.
                            srcIndex := srcIndex + 1.
                        ].    
                    ].
                    srcRowStartIndex := srcRowStartIndex + imageBytesPerRow.
                    dstRowStartIndex := dstRowStartIndex + (width * nPlanes).
                ].
            ].
            depth := nPlanes * 8.
            photometric := nPlanes==3 ifTrue:[#rgb] ifFalse:[#rgba].
        ] ifFalse:[
            (depth == 1) ifTrue:[
                |newDepth nPlanesUsed|

                nPlanesUsed := nPlanes min:4.
                newDepth := (nPlanesUsed * depth) nextPowerOf2.

                data := ByteArray new:((width*height*newDepth)+7)//8.
                srcIndex := dstIndex := 1.
                1 to:height do:[:y |
                    |inMask outBitCount outBits|

                    inMask := 16r80.
                    outBitCount := 0.
                    outBits := 0.
                    1 to:width do:[:x |
                        1 to:nPlanesUsed do:[:p |
                            outBits := (outBits bitShift:1).
                            (((planeData at:p) at:srcIndex) bitAnd:inMask) ~~ 0 ifTrue:[
                                outBits := outBits bitOr:1.
                            ].
                        ].
                        outBits := outBits bitShift:(newDepth-nPlanesUsed).
                        outBitCount := outBitCount + newDepth.

                        outBitCount >= 8 ifTrue:[
                            data at:dstIndex put:((data at:dstIndex) bitOr:outBits).
                            dstIndex := dstIndex + 1.
                            outBitCount := 0.
                            outBits := 0.
                        ].
                        inMask := inMask rightShift:1.
                        inMask == 0 ifTrue:[
                            inMask := 16r80.
                            srcIndex := srcIndex + 1.
                        ].
                    ].
                ].
                depth := newDepth.
                "/ rgbi colormap.
self halt.

            ] ifFalse:[
                self halt.
            ].
        ].    
    ].

"/    sourceBytesPerRow ~~ (((width * depth) + 7) // 8) ifTrue:[
"/        "/ have to compress - above code reads sourceBytesPerRow
"/        "/ (to keep in sync with RLE); but we want width bytesPerRow in the image data.
"/        "/ Can compress in the data-area; leftover pixels are simply ignored
"/        "/ by other image processing code
"/        "/
"/        1 to:nPlanes do:[:planeNr |
"/            |dst|
"/
"/            dst := planeData at:planeNr.
"/
"/            dstIndex := width + 1.
"/            srcIndex := sourceBytesPerRow + 1.
"/            2 to:height do:[:row |
"/                dst replaceFrom:dstIndex to:dstIndex+width-1 with:dst startingAt:srcIndex.
"/                dstIndex := dstIndex + width.
"/                srcIndex := srcIndex + sourceBytesPerRow
"/            ]
"/        ].
"/    ].

    "Created: / 29-08-2017 / 11:33:27 / cg"
!

readCompressedDepth24Data
    |rowStartIndex rowBytes endIndex byte nByte value idx2
     srcIndex dstIndex imageBytesPerRow|

    imageBytesPerRow := (((width * depth * nPlanes) + 7) // 8).
    
    data := ByteArray new:(nPlanes*width*height).
    
    rowBytes := ByteArray new:(sourceBytesPerRow * nPlanes).
    
    rowStartIndex := 1.
    1 to:height do:[:row |
        dstIndex := 1.
        endIndex := 1 + (sourceBytesPerRow * nPlanes).
        [dstIndex < endIndex] whileTrue:[
            byte := inStream nextByte.
            ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
                rowBytes at:dstIndex put:byte.
                dstIndex := dstIndex + 1.
            ] ifFalse:[
                nByte := byte bitAnd:2r00111111.
                value := inStream nextByte.
                idx2 := ((dstIndex + nByte) min:endIndex) - 1.
                rowBytes from:dstIndex to:idx2 put:value.
                dstIndex := dstIndex + nByte.
            ].
        ].

        dstIndex := rowStartIndex.
        srcIndex := 1.
        1 to:width do:[:x |
            data at:dstIndex put:(rowBytes at:x).
            data at:dstIndex+1 put:(rowBytes at:x+sourceBytesPerRow).
            data at:dstIndex+2 put:(rowBytes at:x+sourceBytesPerRow+sourceBytesPerRow).
            dstIndex := dstIndex + 3.
        ].
        rowStartIndex := rowStartIndex + imageBytesPerRow.
    ].
    depth := depth * nPlanes.

    "Created: / 29-08-2017 / 02:13:07 / cg"
    "Modified: / 29-08-2017 / 08:40:02 / cg"
!

readUncompressedData
    |dstIndex|

    "
     actually untested ...
    "
    data := ByteArray uninitializedNew:(height * width).
    sourceBytesPerRow ~~ width ifTrue:[
        dstIndex := 1.
        1 to:height do:[:row |
            inStream nextBytes:width into:data startingAt:dstIndex.
            dstIndex := dstIndex + width.
            inStream skip:(sourceBytesPerRow - width).
        ]
    ] ifFalse:[
        inStream nextBytes:(height * width) into:data.
    ].

    "Modified: / 29-08-2017 / 08:39:16 / cg"
! !

!PCXReader methodsFor:'private-reading'!

extractColorMap16
    "extract the 16-entry colormap from the header"

    |rawMap|

    rawMap := header copyFrom:17 to:(17 + (16*3) - 1).
    ^ MappedPalette rgbBytesVector:rawMap 
!

readColorMap256
    "read the 256-entry colormap at the end"

    |rawMap|

    rawMap := ByteArray uninitializedNew:(256*3).
    inStream nextBytes:(256*3) into:rawMap.
    ^ MappedPalette rgbBytesVector:rawMap

    "Modified: / 29-08-2017 / 08:38:15 / cg"
    "Modified (comment): / 29-08-2017 / 11:32:29 / cg"
!

readImageData
    |rowStartIndex imageBytesPerRow|

    imageBytesPerRow := (((width * depth) + 7) // 8).
    data := ByteArray new:(imageBytesPerRow*height).

    rowStartIndex := 1.
    1 to:height do:[:row |
        self readScanlineTo:data startingAt:rowStartIndex.
        rowStartIndex := rowStartIndex + imageBytesPerRow.
    ].

    "Created: / 29-08-2017 / 09:54:39 / cg"
    "Modified: / 29-08-2017 / 11:42:15 / cg"
!

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

    |version xmin ymin xmax ymax paletteType|

    "/ typedef struct {                         /*header for PCX bitmap files*/
    "/    unsigned char       signature;          /*1 PCX file identifier */
    "/    unsigned char       version;            /*2 version compatibility level */
    "/    unsigned char       encoding;           /*3 compression method */
    "/    unsigned char       bitsperpix;         /*4 bits per pixel, or depth */
    "/    unsigned short      Xleft;              /*5 X position of left edge */
    "/    unsigned short      Ytop;               /*7 Y position of top edge */
    "/    unsigned short      Xright;             /*9 X position of right edge */
    "/    unsigned short      Ybottom;            /*11 Y position of bottom edge */
    "/    unsigned short      Xscreensize;        /*13 X screen res of source image */
    "/    unsigned short      Yscreensize;        /*15 Y screen res of source image */
    "/    unsigned char       PCXpalette[16][3];  /*17 PCX color map */
    "/    unsigned char       reserved1;          /*17+48 should be 0, 1 if std res fax */
    "/    unsigned char       planes;             /*66 bit planes in image*/
    "/    unsigned short      linesize;           /*67 byte delta between scanlines */
    "/    unsigned char       paletteinfo;        /*69 paletteType */
    "/                                                /*0 == undef
    "/                                                  1 == color
    "/                                                  2 == grayscale*/
    "/    unsigned char reserved2[58];            /*70 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 fileFormatError:'unknown compression'.
    ].

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

    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.

    "
     although it would be easy to implement ...
     I have no test pictures for other formats.
     So its not (yet) implemented
    "
    ((#(1 2 4 8) includes:bitsPerPixelIn) "and:[nPlanes == 1]") ifFalse:[
        "/        'PCXReader: depth: ' errorPrint. depth errorPrint. 
        "/        ' planes:' errorPrint. nPlanes errorPrintNL.
        ^ self fileFormatError:'can only handle depth''s 1,2,4 or 8'.
    ].
    (nPlanes between:1 and:4) ifFalse:[
        ^ self fileFormatError:'can only handle 1 to 4 planes'.
    ].

    nPlanesUsed := nPlanes.
    depth := bitsPerPixelIn * nPlanes.
    bitsPerPixelIn ~~ 8 ifTrue:[
        "/ for 3 planes, single rgb bit, we will generate a depth4 image.
        "/ for 3 planes, two bits per rgb, we will generate a depth8 image
        "/ for 3 planes, four bits per rgb, we will generate a depth16 image
        nPlanesUsed := nPlanes min:4.
        depth := (nPlanesUsed * bitsPerPixelIn) nextPowerOf2.
    ].
    
    self reportDimension.

    "/ precompute a first guess at the photometric;
    "/ warning: might be changed by readImageData
    paletteType == 2 ifTrue:[
        photometric := #blackIs0.
    ] ifFalse:[
        depth == 1 ifTrue:[
            photometric := #blackIs0.
        ] ifFalse:[    
            photometric := #palette.
        ].
    ].

    depth == 24 ifTrue:[
        samplesPerPixel := 3.
        bitsPerSample := #( 8 8 8 ).
        photometric := #rgb.
    ] ifFalse:[    
        depth == 32 ifTrue:[
            samplesPerPixel := 4.
            bitsPerSample := #( 8 8 8 8).
            photometric := #rgba.
        ] ifFalse:[    
            samplesPerPixel := 1.
            bitsPerSample := { depth }.
        ].
    ].

    self readImageData.

    photometric == #palette ifTrue:[ 
       (version == 5) ifTrue:[
            true "depth == 8" ifTrue:[
                | nMaxPad byte "{Class: SmallInteger }" |
                
                inStream isPositionable ifTrue:[
                    "/ seek to the end, minus 3*256-1 bytes and check there
                    inStream position:(inStream fileSize - (3*256)-1).
                    byte := inStream next.
                ] ifFalse:[    
                    "/ RLE data is padded - skip over zeros for the 0C-byte                    
                    nMaxPad := 15.
                    byte := inStream next.

                    [(byte ~~ 16r0C) and:[nMaxPad > 0]] whileTrue:[
                        byte := inStream next.
                        nMaxPad := nMaxPad - 1.
                    ].
                ].
                (byte == 16r0C) ifTrue:[
                    colorMap := self readColorMap256.
                ] ifFalse:[
                    'PCXREADER: no valid 256-entry palette (got' errorPrint. 
                    byte errorPrint. '; expected ' errorPrint. 16rC0 errorPrint. ')' errorPrintCR.
                ].
            ].
        ].
        ((version == 2) or:[ colorMap isNil and:[ (depth <= 4) ] ]) ifTrue:[
            "/ take palette from header
            colorMap := self extractColorMap16.
        ].    
    ].
        
    "
     |i f|
     i := Image fromFile:'somefile.pcx'.
     i inspect.
    "

    "Modified: / 29-08-2017 / 13:00:56 / cg"
!

readScanlineTo:data startingAt:startIndex
    "read a single scanline into data starting at startIndex"
    
    |rowBytes endIndex byte nByte value idx2 dstIndex imageBytesPerRow rowOffset|

    imageBytesPerRow := (((width * bitsPerPixelIn * nPlanes) + 7) // 8).

    "/ multiband images:
    "/ need to read into a temporary buffer,
    "/ then extract the bands and merge the pixels
    "/ i.e. read as rrr...rrrggg...gggbbb...bbb
    "/ then merge bands into rgbrgb...rgbrgb
    "/ notice that each scanline is rle encoded (all bands together)

    rowBytes := ByteArray new:(sourceBytesPerRow * nPlanes).

    compression == 0 ifTrue:[
        inStream nextBytes:(sourceBytesPerRow * nPlanes) into:rowBytes startingAt:1.
    ] ifFalse:[    
        dstIndex := 1.
        endIndex := 1 + (sourceBytesPerRow * nPlanes).
        [dstIndex < endIndex] whileTrue:[
            byte := inStream nextByte.
            byte notNil ifTrue:[
                ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
                    rowBytes at:dstIndex put:byte.
                    dstIndex := dstIndex + 1.
                ] ifFalse:[
                    nByte := byte bitAnd:2r00111111.
                    value := inStream nextByte.
                    idx2 := ((dstIndex + nByte) min:endIndex) - 1.
                    rowBytes from:dstIndex to:idx2 put:value.
                    dstIndex := dstIndex + nByte.
                ].
            ] ifFalse:[
                "/ oops - short read!!
                dstIndex := endIndex + 1.
            ]    
        ].
    ].

    nPlanes > 1 ifTrue:[        
        "/ merge the bands
        bitsPerPixelIn == 8 ifTrue:[
            "/ bytewise is easy
            
            self assert:(sourceBytesPerRow >= width).

            rowOffset := 0.
            0 to:nPlanesUsed-1 do:[:planeOffs |
                dstIndex := startIndex + planeOffs.
                1 to:width do:[:x |
                    data at:dstIndex put:(rowBytes at:x+rowOffset).
                    dstIndex := dstIndex + nPlanes.
                ].
                rowOffset := rowOffset + sourceBytesPerRow.
            ].
        ] ifFalse:[
            "/ need some bit-stuffing to merge planes...
            "/ the following code is a q&d, straight forward, and
            "/ completely untuned hack.
            
            depth <= 8 ifTrue:[
                "/ merge into bytes
                |m0 srcByteIndex inShift mask outBitCount 
                 pixelBits outShift xOffs bits rowOffsets|

                m0 := #( 16r80 16rC0 nil 16rF0 ) at:bitsPerPixelIn.
                mask := #( 1 3 0 7 ) at:bitsPerPixelIn.

                dstIndex := startIndex.
                
                xOffs := 1.
                inShift := 8-bitsPerPixelIn.
                outShift := 8-(depth).

                rowOffsets := { 0 . sourceBytesPerRow . (sourceBytesPerRow*2) . (sourceBytesPerRow*3) }.
                rowOffsets := (rowOffsets copyTo:nPlanesUsed) reversed.

                1 to:width do:[:x |
                    "/ collect pixel's bits from planes
                    pixelBits := 0.
                    "/ rowOffset := 0.
                    1 to:nPlanesUsed do:[:p |
                        byte := rowBytes at:xOffs+(rowOffsets at:p).
                        bits := (byte rightShift:inShift) bitAnd:mask.
                        "/ bits now contains the plane's bits in the low bit positions
                        pixelBits := (pixelBits bitShift:bitsPerPixelIn) bitOr:bits.

                        "/ rowOffset := rowOffset + sourceBytesPerRow.
                    ].
                    inShift := inShift - bitsPerPixelIn.
                    inShift < 0 ifTrue:[
                        inShift := 8-bitsPerPixelIn.
                        xOffs := xOffs + 1.
                    ].
                    "/ pixelBits now contains the pixel's rgb bits in low bit positions.

                    "/ write output
                    byte := data at:dstIndex.
                    byte := byte bitOr:(pixelBits bitShift:outShift).
                    data at:dstIndex put:byte.

                    "/ update shift.
                    outShift := outShift - depth.
                    outShift < 0 ifTrue:[
                        outShift := 8-(depth).
                        dstIndex := dstIndex + 1.
                    ].    
                ].
            ] ifFalse:[
                depth == 16 ifTrue:[
                    "/ merge into 16bit ints
                    "/ in theory, this is possible (eg. bitsPerPixel=4; nPlanes=3), 
                    "/ but I never saw such a file in the wild...
                    self halt.
                ] ifFalse:[
                ]. 
                self fileFormatError:('unsupported: depth%1 with %2 planes' bindWith:bitsPerPixelIn with:nPlanes).
            ].    
        ].    
    ] ifFalse:[
        data replaceFrom:startIndex to:(startIndex + imageBytesPerRow - 1) with:rowBytes startingAt:1
    ].

    "Created: / 29-08-2017 / 09:49:41 / cg"
    "Modified: / 29-08-2017 / 13:08:03 / cg"
! !

!PCXReader methodsFor:'reading'!

readImage
    "read an image in pcx format from inStream"

    inStream binary.

    header := ByteArray uninitializedNew:128.
    (inStream nextBytes:128 into:header) == 128 ifFalse:[
        ^ self fileFormatError:'short file'.
    ].

    (self class isValidPCXHeader:header) ifFalse:[
        ^ self fileFormatError:'wrong header'.
    ].

    self readRestAfterHeader.
! !

!PCXReader class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !


PCXReader initialize!