#FEATURE by cg
authorClaus Gittinger <cg@exept.de>
Tue, 29 Aug 2017 12:38:15 +0200
changeset 3995 ab4741a8e8f5
parent 3994 8ab8729d5dec
child 3996 9f8c87c19905
#FEATURE by cg class: PCXReader class definition added: #readCompressedData #readImageData #readScanlineTo:startingAt: removed: #nextByteFromBufferOrStream comment/format in: #readColorMap256 changed: #readCompressedDepth24Data #readRestAfterHeader #readScanline #readUncompressedData category of: #readCompressedDepth24Data #readUncompressedData
PCXReader.st
--- a/PCXReader.st	Tue Aug 29 02:19:30 2017 +0200
+++ b/PCXReader.st	Tue Aug 29 12:38:15 2017 +0200
@@ -14,7 +14,8 @@
 "{ NameSpace: Smalltalk }"
 
 ImageReader subclass:#PCXReader
-	instanceVariableNames:'header buffer nBuffer bufferIndex sourceBytesPerRow depth nPlanes'
+	instanceVariableNames:'header sourceBytesPerRow bitsPerPixelIn depth nPlanes compression
+		nPlanesUsed'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Graphics-Images-Readers'
@@ -123,64 +124,21 @@
     "Modified: 16.4.1997 / 22:24:32 / 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 
-!
-
-nextByteFromBufferOrStream
-    |byte|
-
-    nBuffer ~~ 0 ifTrue:[
-        byte := buffer at:bufferIndex.
-        bufferIndex := bufferIndex + 1. nBuffer := nBuffer - 1.
-    ] ifFalse:[
-        byte := inStream next
-    ].
-    ^ byte
-!
-
-readColorMap256
-    |rawMap mapSize|
-
-    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.
-    ].
-
-    ^ MappedPalette rgbBytesVector:rawMap 
-!
+!PCXReader methodsFor:'obsolete'!
 
 readCompressedData
-    |bendIndex rowStartIndex  endIndex byte nByte value idx2
+    |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.
-    
-    buffer := ByteArray uninitializedNew:4096.
-    bufferIndex := 1.
-    bendIndex := 1.
 
     rowStartIndex := 1.
     1 to:height do:[:row |
@@ -188,30 +146,18 @@
             |planeBytes|
 
             planeBytes := planeData at:planeNr.
-            
+
             dstIndex := rowStartIndex.
             endIndex := dstIndex + sourceBytesPerRow.
-            
+
             [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 := inStream nextByte.
                 ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
                     planeBytes 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.
+                    value := inStream nextByte.
                     idx2 := ((dstIndex + nByte) min:endIndex) - 1.
                     planeBytes from:dstIndex to:idx2 put:value.
                     dstIndex := dstIndex + nByte.
@@ -221,7 +167,6 @@
         "/ rowStartIndex := endIndex.
         rowStartIndex := rowStartIndex + (imageBytesPerRow * nPlanes).
     ].
-    nBuffer := endIndex - bufferIndex.
 
     "/ now merge the planes
     nPlanes > 1 ifTrue:[
@@ -235,7 +180,7 @@
                 1 to:height do:[:y |
                     1 to:nPlanes do:[:p |
                         |planeBytes|
-                        
+
                         dstIndex := dstRowStartIndex + (p - 1).
                         srcIndex := srcRowStartIndex.
                         planeBytes := planeData at:p.
@@ -257,12 +202,12 @@
 
                 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.
@@ -275,7 +220,7 @@
                         ].
                         outBits := outBits bitShift:(newDepth-nPlanesUsed).
                         outBitCount := outBitCount + newDepth.
-                        
+
                         outBitCount >= 8 ifTrue:[
                             data at:dstIndex put:((data at:dstIndex) bitOr:outBits).
                             dstIndex := dstIndex + 1.
@@ -320,21 +265,17 @@
 "/        ].
 "/    ].
 
-    "Modified: / 29-08-2017 / 02:13:12 / cg"
+    "Created: / 29-08-2017 / 11:33:27 / cg"
 !
 
 readCompressedDepth24Data
-    |bEndIndex rowStartIndex rowBytes endIndex byte nByte value idx2
+    |rowStartIndex rowBytes endIndex byte nByte value idx2
      srcIndex dstIndex imageBytesPerRow|
 
     imageBytesPerRow := (((width * depth * nPlanes) + 7) // 8).
     
     data := ByteArray new:(nPlanes*width*height).
     
-    buffer := ByteArray uninitializedNew:4096.
-    bufferIndex := 1.
-    bEndIndex := 1.
-
     rowBytes := ByteArray new:(sourceBytesPerRow * nPlanes).
     
     rowStartIndex := 1.
@@ -342,25 +283,13 @@
         dstIndex := 1.
         endIndex := 1 + (sourceBytesPerRow * nPlanes).
         [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 := inStream nextByte.
             ((byte bitAnd:2r11000000) ~~ 2r11000000) ifTrue:[
                 rowBytes 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.
+                value := inStream nextByte.
                 idx2 := ((dstIndex + nByte) min:endIndex) - 1.
                 rowBytes from:dstIndex to:idx2 put:value.
                 dstIndex := dstIndex + nByte.
@@ -375,25 +304,80 @@
             data at:dstIndex+2 put:(rowBytes at:x+sourceBytesPerRow+sourceBytesPerRow).
             dstIndex := dstIndex + 3.
         ].
-        "/ data replaceFrom:rowStartIndex to:rowStartIndex+(sourceBytesPerRow*nPlanes)-1 with:rowBytes startingAt:1.
-        
-        "/ rowStartIndex := endIndex.
         rowStartIndex := rowStartIndex + imageBytesPerRow.
     ].
-    nBuffer := endIndex - bufferIndex.
     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 compression xmin ymin xmax ymax
-      paletteType 
-      byte        "{Class: SmallInteger }" 
-      nMaxPad|
+    |version xmin ymin xmax ymax paletteType|
 
     "/ typedef struct {                         /*header for PCX bitmap files*/
     "/    unsigned char       signature;          /*1 PCX file identifier */
@@ -425,7 +409,7 @@
         ^ self fileFormatError:'unknown compression'.
     ].
 
-    depth := header at:4.
+    bitsPerPixelIn := header at:4.
     "/    'depth=' print. depth printNL.
     nPlanes := header at:66.
     "/    'planes=' print. nPlanes printNL.
@@ -448,7 +432,7 @@
      I have no test pictures for other formats.
      So its not (yet) implemented
     "
-    ((#(1 2 4 8) includes:depth) "and:[nPlanes == 1]") ifFalse:[
+    ((#(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'.
@@ -457,10 +441,20 @@
         ^ 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 readCompressedData
+    "/ warning: might be changed by readImageData
     paletteType == 2 ifTrue:[
         photometric := #blackIs0.
     ] ifFalse:[
@@ -470,14 +464,8 @@
             photometric := #palette.
         ].
     ].
+    self readImageData.
 
-    compression == 1 ifTrue:[
-        self readCompressedData
-    ] ifFalse:[
-        self readUncompressedData
-    ].
-
-    "/ warning: depth might be changed by readCompressedData
     depth == 24 ifTrue:[
         samplesPerPixel := 3.
         bitsPerSample := #( 8 8 8 ).
@@ -496,18 +484,19 @@
     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).
-                    nBuffer := 0.
                     byte := inStream next.
                 ] ifFalse:[    
                     "/ RLE data is padded - skip over zeros for the 0C-byte                    
                     nMaxPad := 15.
-                    byte := self nextByteFromBufferOrStream.
+                    byte := inStream next.
 
                     [(byte ~~ 16r0C) and:[nMaxPad > 0]] whileTrue:[
-                        byte := self nextByteFromBufferOrStream.
+                        byte := inStream next.
                         nMaxPad := nMaxPad - 1.
                     ].
                 ].
@@ -531,27 +520,127 @@
      i inspect.
     "
 
-    "Modified: / 28-08-2017 / 15:53:11 / cg"
+    "Modified: / 29-08-2017 / 12:24:11 / cg"
 !
 
-readUncompressedData
-    |dstIndex|
+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).
 
-    "
-     actually untested ...
-    "
-    data := ByteArray uninitializedNew:(height * width).
-    sourceBytesPerRow ~~ width ifTrue:[
+    "/ 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.
-        1 to:height do:[:row |
-            inStream nextBytes:width into:data startingAt:dstIndex.
-            dstIndex := dstIndex + width.
-            inStream skip:(sourceBytesPerRow - width).
-        ]
+        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...
+            depth <= 8 ifTrue:[
+                "/ merge into bytes
+                |m0 srcByteIndex inShift mask outBitCount pixelBits outShift xOffs bits|
+
+                m0 := #( 16r80 16rC0 nil 16rF0 ) at:bitsPerPixelIn.
+                mask := #( 1 3 0 7 ) at:bitsPerPixelIn.
+
+                dstIndex := startIndex.
+                
+                xOffs := 1.
+                inShift := 8-bitsPerPixelIn.
+                outShift := 8-(depth).
+
+                1 to:width do:[:x |
+                    "/ collect pixel's bits from planes
+                    pixelBits := 0.
+                    rowOffset := 0.
+                    1 to:nPlanesUsed do:[:p |
+                        byte := rowBytes at:xOffs+rowOffset.
+                        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
+                    self halt.
+                ] ifFalse:[
+                    self error.
+                ]. 
+            ].    
+        ].    
     ] ifFalse:[
-        inStream nextBytes:(height * width) into:data.
+        data replaceFrom:startIndex to:(startIndex + imageBytesPerRow - 1) with:rowBytes startingAt:1
     ].
-    nBuffer := 0.
+
+    "Created: / 29-08-2017 / 09:49:41 / cg"
+    "Modified: / 29-08-2017 / 12:27:12 / cg"
 ! !
 
 !PCXReader methodsFor:'reading'!