PCXReader.st
author claus
Sat, 18 Feb 1995 16:58:20 +0100
changeset 43 e85c7d392833
parent 35 f13cdd0b44c7
child 83 97fd04d167c8
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.
"

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

ImageReader subclass:#PCXReader
	 instanceVariableNames:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Graphics-Images support'
!

PCXReader comment:'
COPYRIGHT (c) 1994 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview2/PCXReader.st,v 1.5 1995-02-18 15:57:51 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libview2/PCXReader.st,v 1.5 1995-02-18 15:57:51 claus Exp $
"
!

documentation
"
    this class provides methods for loading 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).
"
! !

!PCXReader class methodsFor:'initialization'!

initialize
    "tell Image-class, that a new fileReader is present"

    Image fileFormats at:'.pcx'  put:self.
! !

!PCXReader class methodsFor:'testing'!

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

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

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

    ^ true
!

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

!PCXReader methodsFor:'reading from file'!

fromStreamWithHeader:header 
    | 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 }"
      bytesPerRow "{Class: SmallInteger }"
      value       "{Class: SmallInteger }"
      idx2        "{Class: SmallInteger }"
      dataBytes buffer 
      bufferIndex "{Class: SmallInteger }"
      bendIndex   "{Class: SmallInteger }"
      nBuffer     "{Class: SmallInteger }"|

    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.
    bytesPerRow := header wordAt:67.
"/    'bytesPerRow=' print. bytesPerRow 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: can only handle 1-plane 256 color images' errorPrintNL.
        ^ nil
    ].

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

    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 := Array new:16.
        gMap := Array new:16.
        bMap := Array 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 new:(height * bytesPerRow).

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

        rowIndex := 1.
        h := height.
        1 to:h do:[:row |
            dstIndex := rowIndex.
            endIndex := dstIndex + bytesPerRow.
            [dstIndex < endIndex] whileTrue:[
                bufferIndex == bendIndex ifTrue:[
                    nBuffer := inStream nextBytes:4096 into:buffer.
                    bufferIndex := 1.
                    bendIndex := nBuffer + 1.
                ].
                byte := buffer at:bufferIndex.
                bufferIndex := bufferIndex + 1. "/ nBuffer := nBuffer - 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. "/ nBuffer := nBuffer - 1.
                    value notNil ifTrue:[
                        idx2 := endIndex min:(dstIndex + nByte - 1).
                        dataBytes from:dstIndex to:idx2 put:value.
                        dstIndex := dstIndex + nByte.
                    ]
                ].
            ].
            rowIndex := rowIndex + bytesPerRow
        ].
        nBuffer := endIndex - bufferIndex.

"/        rowIndex := 1.
"/        h := height.
"/        1 to:h do:[:row |
"/            dstIndex := rowIndex.
"/            endIndex := dstIndex + bytesPerRow.
"/            [dstIndex < endIndex] whileTrue:[
"/                byte := inStream next.
"/                ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
"/                    dataBytes at:dstIndex put:byte.
"/                    dstIndex := dstIndex + 1.
"/                ] ifFalse:[
"/                    nByte := byte bitAnd:2r00111111.
"/                    value := inStream next.
"/                    value notNil ifTrue:[
"/                        idx2 := endIndex min:(dstIndex + nByte - 1).
"/                        dataBytes from:dstIndex to:idx2 put:value.
"/                        dstIndex := dstIndex + nByte.
"/                    ]
"/                ].
"/            ].
"/            rowIndex := rowIndex + bytesPerRow
"/        ]
    ] ifFalse:[
        "
         actually untested ...
        "
        data := dataBytes := ByteArray uninitializedNew:(height * bytesPerRow).
        inStream nextBytes:(height * bytesPerRow) 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 == 16rC0 ifFalse:[
           'PCXREADER: no valid 256-entry palette (got' errorPrint. 
           byte errorPrint. '; expected ' errorPrint. 16rC0 errorPrint. ')' errorPrintNL.
        ].
        rawMap := ByteArray uninitializedNew:(256*3).
        nBuffer ~~ 0 ifTrue:[
            rawMap replaceFrom:1 to:(256*3) 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.
    "
!

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

PCXReader initialize!