#FEATURE
authorClaus Gittinger <cg@exept.de>
Mon, 07 Mar 2016 00:45:45 +0100
changeset 3589 ef1e5b12715f
parent 3588 b1560f509caa
child 3590 104bc11d3845
#FEATURE class: WindowsIconReader mony more formats supported class definition added: #bitsPerPixel #convertPixels comment/format in: #fileFormatDescription #loadUncompressedFrom:into: changed:6 methods category of:9 methods
WindowsIconReader.st
--- a/WindowsIconReader.st	Mon Mar 07 00:39:29 2016 +0100
+++ b/WindowsIconReader.st	Mon Mar 07 00:45:45 2016 +0100
@@ -14,7 +14,7 @@
 "{ NameSpace: Smalltalk }"
 
 ImageReader subclass:#WindowsIconReader
-	instanceVariableNames:'compression inDepth topDown'
+	instanceVariableNames:'compression inDepth topDown redMask greenMask blueMask alphaMask'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Graphics-Images-Readers'
@@ -61,27 +61,27 @@
 "
     Information from http://www.daubnet.com/formats/BMP.html - no Warranty.
 
-          Name           Size                Description
+          Name           Size      Offset   Description
 
       Header            14 bytes            Windows Structure: BITMAPFILEHEADER
-          Signature      2 bytes             'BM'
-          FileSize       4 bytes             File size in bytes
-          reserved       4 bytes             unused (=0)
-          DataOffset     4 bytes             File offset to Raster Data
+          Signature      2 bytes      0      'BM'
+          FileSize       4 bytes      2      File size in bytes
+          reserved       4 bytes      6      unused (=0)
+          DataOffset     4 bytes     10      File offset to Raster Data
 
       InfoHeader        40 bytes            Windows Structure: BITMAPINFOHEADER
 
-          Size           4 bytes             Size of InfoHeader =40
-          Width          4 bytes             Bitmap Width
-          Height         4 bytes             Bitmap Height
-          Planes         2 bytes             Number of Planes (=1)
-          BitCount       2 bytes             Bits per Pixel
+          Size           4 bytes     14      Size of InfoHeader =40
+          Width          4 bytes     18      Bitmap Width
+          Height         4 bytes     22      Bitmap Height
+          Planes         2 bytes     26      Number of Planes (=1)
+          BitCount       2 bytes     28      Bits per Pixel
                                              1 = monochrome palette. NumColors = 1
                                              4 = 4bit palletized. NumColors = 16
                                              8 = 8bit palletized. NumColors = 256
                                              16 = 16bit RGB. NumColors = 65536 (?)
                                              24 = 24bit RGB. NumColors = 16M
-          Compression    4 bytes             Type of Compression
+          Compression    4 bytes     30      Type of Compression
                                              0 = RGB            no compression
                                              1 = RLE8           8bit RLE encoding
                                              2 = RLE4           4bit RLE encoding
@@ -93,13 +93,13 @@
                                              4 = RLE24          OS/2 2.x-only
 
 
-          ImageSize      4 bytes             (compressed) Size of Image
+          ImageSize      4 bytes     34      (compressed) Size of Image
                                              It is valid to set this =0 if Compression = 0
-          XpixelsPerM    4 bytes             horizontal resolution: Pixels/meter
-          YpixelsPerM    4 bytes             vertical resolution: Pixels/meter
-          ColorsUsed     4 bytes             Number of actually used colors
+          XpixelsPerM    4 bytes     38      horizontal resolution: Pixels/meter
+          YpixelsPerM    4 bytes     42      vertical resolution: Pixels/meter
+          ColorsUsed     4 bytes     46      Number of actually used colors
           ColorsImportant
-                         4 bytes             Number of important colors
+                         4 bytes     50      Number of important colors
                                              0 = all
        ColorTable        4 * NumColors bytes
                                              present only if Info.BitsPerPixel <= 8
@@ -237,6 +237,7 @@
      for the '.bmp' and '.ico' extensions."
 
     MIMETypes defineImageType:'image/x-MS-bitmap' suffix:'bmp' reader:self.
+    MIMETypes defineImageType:'image/x-ms-bitmap' suffix:'bmp' reader:self.
     MIMETypes defineImageType:'image/bmp'         suffix:'bmp' reader:self.
     MIMETypes defineImageType:nil                 suffix:'ico' reader:self.
 
@@ -303,31 +304,280 @@
 
 !WindowsIconReader methodsFor:'private'!
 
-swapBytesFromRGBA_to_BGRA
-    |idx bytesPerRow|
-
-    "/ Depth32Image keeps its data r/g/b/a; BMP has it b/g/r/a (sigh)
-    idx := 1.
-    bytesPerRow := self bytesPerRow.
-    1 to:height do:[:y |
-        self class swap:width pixelsFromRGB_to_BGR_in:data startingAt:idx bytesPerPixel:4.
-        idx := idx + bytesPerRow.
-    ].
+bitsPerPixel
+    ^ inDepth
 !
 
-swapBytesFromRGB_to_BGR
-    |idx bytesPerRow|
+convertPixels
+    "/ figure out, how pixels should be processed,
+    "/ according to the order of r/g/b components and masks
+    "/ bring the pixels to a standard format:
+    "/  rgb888/rgba8888 if possible and useful
+    "/ 
+    |swapAction redShift greenShift blueShift alphaShift pixelAction
+     numRedBits numGreenBits numBlueBits numAlphaBits needPixelProcessing|
+
+    inDepth == 1 ifTrue:[
+        colorMap isNil ifTrue:[
+            photometric := #blackIs0
+        ] ifFalse:[
+            photometric := #palette.
+            colorMap size == 2 ifTrue:[
+                ((colorMap at:1) = (Color white)
+                and:[(colorMap at:2) = (Color black)]) ifTrue:[
+                    photometric := #whiteIs0.
+                    colorMap := nil.
+                ] ifFalse:[
+                    ((colorMap at:1) = (Color black)
+                    and:[(colorMap at:2) = (Color white)]) ifTrue:[
+                        photometric := #blackIs0.
+                        colorMap := nil.
+                    ]
+                ].                    
+            ].
+        ].
+        samplesPerPixel := 1.
+        bitsPerSample := Array with:inDepth.
+        ^ self.
+    ].
+
+    ((inDepth > 8) and:[redMask notNil]) ifTrue:[
+        numRedBits   := redMask bitCount.
+        numGreenBits := greenMask bitCount.
+        numBlueBits  := blueMask bitCount.
+        numAlphaBits := alphaMask bitCount.
+        redShift := redMask lowBit - 1.
+        greenShift  := greenMask lowBit - 1.
+        blueShift  := blueMask lowBit - 1.
+        alphaShift := alphaMask lowBit - 1.
 
-    "/ Depth24Image keeps its data r/g/b; BMP has it b/g/r (sigh)
-    idx := 1.
-    bytesPerRow := self bytesPerRow.
-    1 to:height do:[:y |
-        self class swap:width pixelsFromRGB_to_BGR_in:data startingAt:idx bytesPerPixel:3.
-        idx := idx + bytesPerRow.
+        alphaMask == 0 ifTrue:[
+            photometric := #rgb.
+            samplesPerPixel := 3
+        ] ifFalse:[    
+            photometric := #rgba.
+            samplesPerPixel := 4
+        ].
+        needPixelProcessing := false.
+        
+        inDepth == 16 ifTrue:[
+            (redShift ~~ 0
+                or:[ greenShift ~~ 5
+                or:[ blueShift ~~ 10
+                or:[ numRedBits ~~ 5
+                or:[ numGreenBits ~~ 5
+                or:[ numBlueBits ~~ 5
+                or:[ alphaMask ~~ 0]]]]]]
+            ) ifTrue:[
+                needPixelProcessing := true.
+                alphaMask == 0 ifTrue:[
+                    bitsPerSample := {numRedBits. numGreenBits. numBlueBits}.
+                    photometric := #rgb
+                ] ifFalse:[
+                    bitsPerSample := {numRedBits. numGreenBits. numBlueBits. numAlphaBits }.
+                    photometric := #rgba
+                ].
+            ] ifFalse:[
+                swapAction := [:bytes | data swapBytes].                
+                colorMap := FixedPalette
+                                redShift:10 redMask:16r1f
+                                greenShift:5 greenMask:16r1f
+                                blueShift:0 blueMask:16r1F.
+                bitsPerSample := #(5 5 5).
+                photometric := #palette
+            ].    
+        ].    
+        inDepth == 24 ifTrue:[
+            (redShift ~~ 0
+                or:[ greenShift ~~ 8
+                or:[ blueShift ~~ 16
+                or:[ numRedBits ~~ 8
+                or:[ numGreenBits ~~ 8
+                or:[ numBlueBits ~~ 8
+                or:[ alphaMask ~~ 0]]]]]]
+            ) ifTrue:[ 
+                (redShift == 16 
+                    and:[greenShift == 8
+                    and:[blueShift == 0
+                    and:[numRedBits == 8
+                    and:[numGreenBits == 8
+                    and:[numBlueBits == 8
+                    and:[alphaMask == 0]]]]]]
+                ) ifTrue:[
+                    "/ common case: swap r and b
+                    swapAction := [:data | self swapBytesFromRGB_to_BGR].
+                ] ifFalse:[    
+                    needPixelProcessing := true
+                ].    
+            ].    
+            bitsPerSample := #(8 8 8).
+            photometric := #rgb.
+        ].    
+        inDepth == 32 ifTrue:[
+            (redShift ~~ 0
+                or:[ greenShift ~~ 8
+                or:[ redShift ~~ 16
+                or:[ numRedBits ~~ 8
+                or:[ numGreenBits ~~ 8
+                or:[ numBlueBits ~~ 8
+                or:[ alphaMask ~~ 0 and:[ alphaShift ~~ 24]]]]]]]
+            ) ifTrue:[ 
+                (redShift == 16 
+                    and:[greenShift == 8
+                    and:[blueShift == 0
+                    and:[alphaShift == 24
+                    and:[numRedBits == 8
+                    and:[numGreenBits == 8
+                    and:[numBlueBits == 8
+                    and:[numAlphaBits == 8]]]]]]]
+                ) ifTrue:[
+                    "/ common case: swap r and b
+                    swapAction := [:data | self swapBytesFromRGBA_to_BGRA].
+                ] ifFalse:[    
+                    needPixelProcessing := true
+                ].    
+            ].    
+            bitsPerSample := #(8 8 8 8).
+            photometric := #rgba.
+        ].
+        
+        needPixelProcessing ifTrue:[ 
+            alphaMask == 0 ifTrue:[
+                inDepth == 16 ifTrue:[
+                    colorMap := FixedPalette
+                                    redShift:redShift redMask:(redMask >> redShift)
+                                    greenShift:greenShift greenMask:(greenMask >> greenShift)
+                                    blueShift:blueShift blueMask:(blueMask >> blueShift).
+                    photometric := #palette.
+                    swapAction := [:bytes | data swapBytes].                
+"/                    pixelAction := [:v |
+"/                                    |r g b|
+"/                                    r := (v bitAnd:redMask) >> redShift.
+"/                                    g := (v bitAnd:greenMask) >> greenShift.
+"/                                    b := (v bitAnd:blueMask) >> blueShift.
+"/                                    (((b bitShift:5) bitOr:g) bitShift:5) bitOr:r
+"/                                   ].
+                ] ifFalse:[
+                    pixelAction := [:v |
+                                    |r g b|
+                                    r := (v bitAnd:redMask) >> redShift.
+                                    g := (v bitAnd:greenMask) >> greenShift.
+                                    b := (v bitAnd:blueMask) >> blueShift.
+                                    (((b bitShift:8) bitOr:g) bitShift:8) bitOr:r
+                                   ].
+                ]
+            ] ifFalse:[    
+                inDepth == 16 ifTrue:[
+                    pixelAction := [:v |
+                                    |r g b a|
+                                    r := (v bitAnd:redMask) >> redShift.
+                                    g := (v bitAnd:greenMask) >> greenShift.
+                                    b := (v bitAnd:blueMask) >> blueShift.
+                                    a := (v bitAnd:alphaMask) >> alphaShift.
+                                    (((((a bitShift:5) bitOr:b) bitShift:5) bitOr:g) bitShift:5) bitOr:r
+                                   ].
+                ] ifFalse:[
+                    pixelAction := [:v |
+                                    |r g b a|
+                                    r := (v bitAnd:redMask) >> redShift.
+                                    g := (v bitAnd:greenMask) >> greenShift.
+                                    b := (v bitAnd:blueMask) >> blueShift.
+                                    a := (v bitAnd:alphaMask) >> alphaShift.
+                                    (((((a bitShift:8) bitOr:b) bitShift:8) bitOr:g) bitShift:8) bitOr:r
+                                   ].
+                ].
+            ].
+        ].    
+    ] ifFalse:[
+        inDepth <= 8 ifTrue:[
+            photometric := #palette.
+        ] ifFalse:[    
+            inDepth == 16 ifTrue:[
+                bitsPerSample := #(5 5 5).
+                colorMap := FixedPalette
+                                redShift:10 redMask:16r1f
+                                greenShift:5 greenMask:16r1f
+                                blueShift:0 blueMask:16r1F.
+                photometric := #palette.
+                swapAction := [:bytes | data swapBytes].                
+            ].    
+            inDepth == 24 ifTrue:[
+                bitsPerSample := #(8 8 8).
+                photometric := #rgb.
+                swapAction := [:data | self swapBytesFromRGB_to_BGR].
+            ].    
+            inDepth == 32 ifTrue:[
+                bitsPerSample := #(8 8 8 8).
+                photometric := #rgba.
+                swapAction := [:data | self swapBytesFromRGBA_to_BGRA].
+            ].    
+        ].    
+    ].    
+
+    "/ Depth32Image keeps its data r/g/b/a; BMP has it b/g/r/a (sigh)
+    pixelAction notNil ifTrue:[
+        inDepth == 16 ifTrue:[
+            swapAction := 
+                [:byteArray | 
+                    |idx rowIdx oldValue newValue bpr|
+                    rowIdx := 1.
+                    bpr := self bytesPerRow.
+
+                    1 to:height do:[:y |
+                        idx := rowIdx.
+                        1 to:width do:[:x |
+                            oldValue := data wordAt:idx MSB:false.
+                            newValue := pixelAction value:oldValue.
+                            data wordAt:idx put:newValue MSB:true.
+                            idx := idx + 2.
+                        ].    
+                        rowIdx := rowIdx + bpr.
+                    ]
+               ].                 
+        ].    
+        inDepth == 24 ifTrue:[
+            swapAction := 
+                [:byteArray | 
+                    |idx rowIdx oldValue newValue bpr|
+                    rowIdx := 1.
+                    bpr := self bytesPerRow.
+
+                    1 to:height do:[:y |
+                        idx := rowIdx.
+                        1 to:width do:[:x |
+                            oldValue := data unsignedIntegerAt:idx length:3 bigEndian:false.
+                            newValue := pixelAction value:oldValue.
+                            data unsignedIntegerAt:idx put:newValue length:3 bigEndian:true.
+                            idx := idx + 3.
+                        ].    
+                        rowIdx := rowIdx + bpr.
+                    ]
+               ].                 
+        ].    
+        inDepth == 32 ifTrue:[
+            swapAction := 
+                [:byteArray | 
+                    |idx rowIdx oldValue newValue bpr|
+                    rowIdx := 1.
+                    bpr := self bytesPerRow.
+                    
+                    1 to:height do:[:y |
+                        idx := rowIdx.
+                        1 to:width do:[:x |
+                            oldValue := data doubleWordAt:idx MSB:false.
+                            newValue := pixelAction value:oldValue.
+                            data doubleWordAt:idx put:newValue MSB:false.
+                            idx := idx + 4.
+                        ].    
+                        rowIdx := rowIdx + bpr.
+                    ]
+               ].                 
+        ].
     ].
-! !
-
-!WindowsIconReader methodsFor:'private-reading'!
+    swapAction notNil ifTrue:[
+        swapAction value:data
+    ].
+!
 
 loadBMP1From:aStream into:aByteArray
     "load bmp-1 bit per pixel imagedata."
@@ -362,88 +612,79 @@
     ^ false
 !
 
-loadBMPWidth:w height:h bytesPerPixel:bpp from:aStream into:data
+loadBMPWidth:w height:h bytesPerPixel:bpp from:aStream into:aByteArray
     "load bmp-16/24/32 bit per pixel imagedata."
 
-    |buff dstIdx fileBytesPerRow imgBytesPerRow align lineDelta|
+    |dstIdx fileBytesPerRow imgBytesPerRow skip align lineDelta|
 
     align := 4.
 
-    ((compression == 0) or:[compression == 3]) ifTrue:[
-        imgBytesPerRow := w * bpp.
-        fileBytesPerRow := imgBytesPerRow.
-        (fileBytesPerRow bitAnd:(align-1)) ~~ 0 ifTrue:[
-            fileBytesPerRow := (fileBytesPerRow bitAnd:((align-1) bitInvert)) + align.
-        ].
-        "/
-        "/ stupid - last row comes first
-        "/
-        buff := ByteArray uninitializedNew:fileBytesPerRow.
+    ((compression == 0) or:[compression == 3]) ifFalse:[
+        "/ 'BMPReader: unsupported compression: ' infoPrint. compression infoPrintCR. 
+        self fileFormatError:('unsupported compression:', compression printString).
+        ^ false.
+    ].
 
-        topDown ifTrue:[
-            dstIdx := 1.
-            lineDelta := imgBytesPerRow
-        ] ifFalse:[
-            dstIdx := imgBytesPerRow * (h - 1) + 1.
-            lineDelta := imgBytesPerRow negated
+    imgBytesPerRow := w * bpp.
+    fileBytesPerRow := imgBytesPerRow.
+    (fileBytesPerRow bitAnd:(align-1)) ~~ 0 ifTrue:[
+        fileBytesPerRow := (fileBytesPerRow bitAnd:((align-1) bitInvert)) + align.
+    ].
+    
+    topDown ifTrue:[
+        dstIdx := 1.
+        lineDelta := imgBytesPerRow
+    ] ifFalse:[
+        dstIdx := imgBytesPerRow * (h - 1) + 1.
+        lineDelta := imgBytesPerRow negated
+    ].
+    
+    (lineDelta == fileBytesPerRow) ifTrue:[
+        (aStream nextBytes:(fileBytesPerRow*h) into:aByteArray startingAt:dstIdx) == (fileBytesPerRow*h) ifFalse:[
+            ^ false
         ].
-        
+    ] ifFalse:[    
+        skip := fileBytesPerRow - imgBytesPerRow.
         1 to:h do:[:row |
-            (aStream nextBytes:fileBytesPerRow into:buff) == fileBytesPerRow ifFalse:[
+            (aStream nextBytes:imgBytesPerRow into:aByteArray startingAt:dstIdx) == imgBytesPerRow ifFalse:[
                 ^ false
             ].
-            data replaceFrom:dstIdx to:(dstIdx+imgBytesPerRow-1) with:buff.
+            skip ~~ 0 ifTrue:[ aStream skip:skip ].
             dstIdx := dstIdx + lineDelta.
         ].
-        ^ true
     ].
-    "/ 'BMPReader: unsupported compression: ' infoPrint. compression infoPrintCR. 
-    self fileFormatError:('unsupported compression:', compression printString).
-    ^ false.
+    ^ true
 !
 
-loadBMPWidth:w height:h depth:d from:aStream into:data
+loadBMPWidth:w height:h depth:d from:aStream into:aByteArray
     "helper: load a BMP image"
 
     d == 8 ifTrue:[
         compression == 0 ifTrue:[
-            ^ self loadUncompressedFrom:aStream into:data.
+            ^ self loadUncompressedFrom:aStream into:aByteArray.
         ].
         compression == 1 ifTrue:[
-            ^ self loadRLECompressedBMP8From:aStream into:data.
+            ^ self loadRLECompressedBMP8From:aStream into:aByteArray.
         ].
         "/ self breakPoint:#cg info:'unhandled compression'.
         self fileFormatError:('unsupported compression:', compression printString).
         ^ false
     ].
     d == 4 ifTrue:[
-        ^ self loadBMP4From:aStream into:data
+        ^ self loadBMP4From:aStream into:aByteArray
     ].
     d == 2 ifTrue:[
-        ^ self loadBMP2From:aStream into:data
+        ^ self loadBMP2From:aStream into:aByteArray
     ].
     d == 1 ifTrue:[
-        ^ self loadBMP1From:aStream into:data
+        ^ self loadBMP1From:aStream into:aByteArray
     ].
     ((d == 16)
     or:[ (d == 24)
     or:[ (d == 32) ]]) ifTrue:[
-        (self loadBMPWidth:w height:h bytesPerPixel:(d // 8) from:aStream into:data) ifFalse:[
+        (self loadBMPWidth:w height:h bytesPerPixel:(d // 8) from:aStream into:aByteArray) ifFalse:[
             ^ false
         ].
-        inDepth == 16 ifTrue:[
-            "/ Depth16Image keeps its data MSB (sigh); here they come LSB.
-            data swapBytes.
-        ].
-        inDepth == 24 ifTrue:[
-            "/ Depth24Image keeps its data r/g/b; BMP has it b/g/r (sigh)
-            self swapBytesFromRGB_to_BGR.
-        ].
-        inDepth == 32 ifTrue:[
-            "/ Depth32Image keeps its data r/g/b/a; BMP has it b/g/r/a (sigh)
-            self swapBytesFromRGBA_to_BGRA.
-        ].
-
         ^ true
     ].
     self fileFormatError:('unsupported depth:', d printString).
@@ -456,9 +697,9 @@
 loadRLECompressedBMP4From:aStream into:aByteArray
     "load bmp-rle-4 pixel imagedata"
 
-    |bytesPerRowInData x y dstIndex lineStartIndex cnt pair clr1 clr2 code nbyte byte bytes byteIdx|
+    |bytesPerRow x y dstIndex lineStartIndex cnt pair clr1 clr2 code nbyte byte bytes byteIdx rev|
 
-    bytesPerRowInData := self bytesPerRow.
+    bytesPerRow := self bytesPerRow.
     x := 0.
     
     topDown ifTrue:[
@@ -466,10 +707,11 @@
         lineStartIndex := 1.
     ] ifFalse:[
         y := height - 1.
-        lineStartIndex := (y * bytesPerRowInData) + 1.
+        lineStartIndex := (y * bytesPerRow) + 1.
     ].
     dstIndex := lineStartIndex.
-    
+    "/ data atAllPut:16rBB.
+
     [ y between:0 and:height-1 ] whileTrue:[
         cnt := aStream nextByte.
         pair := aStream nextByte.
@@ -478,35 +720,38 @@
                 self breakPoint:#cg.
                 self fileFormatError:('invalid delta').
             ].    
-Transcript printf:'RUN y: %d x: %d cnt: %d pair: %02x\n' with:y with:x with:cnt with:pair.
-            clr1 := pair bitShift:-4.
-            clr2 := pair bitAnd:16rF.
+            "/ Transcript printf:'RUN y: %d x: %d cnt: %d pair: %02x\n' with:y with:x with:cnt with:pair.
             x even ifTrue:[
-                byte := ((clr2 << 4) bitOr:clr1).
                 (cnt >= 2) ifTrue:[
                     nbyte := cnt // 2.
-                    aByteArray from:dstIndex to:(dstIndex+nbyte-1) put:byte.
+                    aByteArray from:dstIndex to:(dstIndex+nbyte-1) put:pair.
                     dstIndex := dstIndex + nbyte.
                 ].
                 cnt odd ifTrue:[
                     "/ got odd count
-                    aByteArray at:dstIndex put:clr1.
+                    byte := aByteArray at:dstIndex.
+                    aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(pair bitAnd:16rF0)).
                     "/ self halt.
                 ].    
             ] ifFalse:[
-                "/ the first halfbyte
+                clr1 := pair bitShift:-4. "/ left bit
+                clr2 := pair bitAnd:16rF. "/ right bit
+
+                "/ the first odd-x halfbyte
                 byte := aByteArray at:dstIndex.
-                aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(pair bitAnd:16rF0)).
+                aByteArray at:dstIndex put:((byte bitAnd:16rF0) bitOr:clr1).
                 dstIndex := dstIndex + 1.
+
                 nbyte := (cnt-1) // 2.
                 nbyte > 0 ifTrue:[
-                    aByteArray from:dstIndex to:(dstIndex+nbyte-1) put:pair.
+                    rev := (clr2 << 4) bitOr:clr1.
+                    aByteArray from:dstIndex to:(dstIndex+nbyte-1) put:rev.
                     dstIndex := dstIndex + nbyte.
                 ].
                 cnt even ifTrue:[
-                    "/ the final halfbyte
+                    "/ the final odd-x halfbyte
                     byte := aByteArray at:dstIndex.
-                    aByteArray at:dstIndex put:((byte bitAnd:16rF0) bitOr:(pair bitAnd:16r0F)).
+                    aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(clr2 bitShift:4)).
                 ].    
             ].
             x := x + cnt.
@@ -515,19 +760,19 @@
             code := pair.
             code == 0 ifTrue:[
                 "/ end of line
-Transcript printf:'EOL\n'.
+                "/ Transcript printf:'EOL\n'.
                 x := 0.
                 topDown ifTrue:[
                     y := y + 1.
-                    lineStartIndex := lineStartIndex + bytesPerRowInData.
+                    lineStartIndex := lineStartIndex + bytesPerRow.
                 ] ifFalse:[    
                     y := y - 1.
-                    lineStartIndex := lineStartIndex - bytesPerRowInData.
+                    lineStartIndex := lineStartIndex - bytesPerRow.
                 ].    
                 dstIndex := lineStartIndex.
             ] ifFalse:[
                 code == 1 ifTrue:[
-Transcript printf:'END\n'.
+                    "/ Transcript printf:'END\n'.
                     "/ end of pic
                     ^ true
                 ].
@@ -535,9 +780,9 @@
                     "/ delta
                     x := x + aStream nextSignedByte.
                     y := y - aStream nextSignedByte.
-Transcript printf:'MOVE y: %d x: %d\n' with:y with:x with:code.
-                    lineStartIndex := (y * bytesPerRowInData) + 1.
-                    dstIndex := lineStartIndex + x.
+                    "/ Transcript printf:'MOVE y: %d x: %d\n' with:y with:x with:code.
+                    lineStartIndex := (y * bytesPerRow) + 1.
+                    dstIndex := lineStartIndex + (x//2).
                 ] ifFalse:[
                     "/ absolute; cnt pixels coming
                     ((x between:0 and:width-1) and:[y between:0 and:height-1]) ifFalse:[
@@ -552,38 +797,37 @@
                         aStream skip:1.
                     ].
                     x + cnt > width ifTrue:[self halt].
-                    nbyte := cnt // 2.
                     byteIdx := 1.
-Transcript printf:'PIXELS: %d x: %d count: %d nbyte: %d\n' with:y with:x with:cnt with:nbyte.
+                    "/ Transcript printf:'PIXELS: %d x: %d count: %d nbyte: %d\n' with:y with:x with:cnt with:nbyte.
                     x even ifTrue:[
-                        nbyte timesRepeat:[
-                            pair := bytes at:byteIdx. byteIdx := byteIdx + 1.
-                            clr1 := pair bitShift:-4.
-                            clr2 := pair bitAnd:16rF.
-                            byte := ((clr2 << 4) bitOr:clr1).
-                            aByteArray at:dstIndex put:byte.
-                            dstIndex := dstIndex + 1.
-                        ].                        
+                        nbyte := cnt // 2.
+                        aByteArray replaceFrom:dstIndex to:(dstIndex+nbyte-1) with:bytes startingAt:byteIdx.
+                        byteIdx := byteIdx + nbyte.
+                        dstIndex := dstIndex + nbyte.
                         cnt odd ifTrue:[
-                            pair := bytes at:byteIdx. byteIdx := byteIdx + 1.
-                            aByteArray at:dstIndex put:(pair bitShift:-4).
-                            "/ self halt.
-                        ].
-                    ] ifFalse:[
-                        nbyte timesRepeat:[
-                            pair := bytes at:byteIdx. byteIdx := byteIdx + 1.
-                            byte := aByteArray at:dstIndex.
-                            aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(pair bitAnd:16rF0)).
-                            byte := aByteArray at:dstIndex+1.
-                            aByteArray at:dstIndex+1 put:((byte bitAnd:16rF0) bitOr:(pair bitAnd:16r0F)).
-                            dstIndex := dstIndex + 1.
-                        ].    
-                        cnt odd ifTrue:[
-                            pair := bytes at:byteIdx. byteIdx := byteIdx + 1.
+                            "/ the last half-byte
+                            pair := bytes at:byteIdx.
                             byte := aByteArray at:dstIndex.
                             aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(pair bitAnd:16rF0)).
                             "/ self halt.
                         ].
+                    ] ifFalse:[
+                        nbyte := (cnt // 2).
+                        [nbyte > 0] whileTrue:[
+                            pair := bytes at:byteIdx. byteIdx := byteIdx + 1.
+                            byte := aByteArray at:dstIndex.
+                            aByteArray at:dstIndex put:((byte bitAnd:16rF0) bitOr:((pair bitShift:-4) bitAnd:16r0F)).
+                            dstIndex := dstIndex + 1.
+                            byte := aByteArray at:dstIndex.
+                            aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:((pair bitShift:4) bitAnd:16rF0)).
+                            nbyte := nbyte - 1.
+                        ].
+                        cnt odd ifTrue:[
+                            pair := bytes at:byteIdx. byteIdx := byteIdx + 1.
+                            byte := aByteArray at:dstIndex.
+                            aByteArray at:dstIndex put:((byte bitAnd:16rF0) bitOr:((pair bitShift:-4) bitAnd:16r0F)).
+                            dstIndex := dstIndex + 1.
+                        ].    
                     ].    
                     x := x + cnt. 
                 ].
@@ -688,12 +932,8 @@
     
     1 to:nRows do:[:row |
         n := aStream nextBytes:bytesPerRowInData into:aByteArray startingAt:dstIndex.
-        n ~~ bytesPerRowInData ifTrue:[
-            ^ false.
-        ].
-        skip ~~ 0 ifTrue:[
-            aStream skip:skip.
-        ].
+        n ~~ bytesPerRowInData ifTrue:[^ false].
+        skip ~~ 0 ifTrue:[aStream skip:skip].
         dstIndex := dstIndex + lineDelta.
     ].
     ^ true.
@@ -703,8 +943,7 @@
     "read the colormap; notice: its in BGR order (sigh)."
 
     |rawMap rMap gMap bMap
-     srcIndex  "{ Class: SmallInteger }"
-     skipDelta "{ Class: SmallInteger }"|
+     srcIndex  "{ Class: SmallInteger }"|
 
     rawMap := ByteArray uninitializedNew:(nColors*nRawBytesPerColor).
     aStream nextBytes:(nColors*nRawBytesPerColor) into:rawMap.
@@ -713,24 +952,44 @@
     gMap := ByteArray new:nColors.
     bMap := ByteArray new:nColors.
     srcIndex := 1.
-    skipDelta := nRawBytesPerColor - 3.
 
     "/ stupid: this is a BGR-ordered map (otherwise, could use #rgbBytesVector:-message)
     "/ also, there might be a fourth byte (alpha ?) which is (currently) skipped.
     1 to:nColors do:[:i |
-	bMap at:i put:(rawMap at:srcIndex).
-	srcIndex := srcIndex + 1.
-	gMap at:i put:(rawMap at:srcIndex).
-	srcIndex := srcIndex + 1.
-	rMap at:i put:(rawMap at:srcIndex).
-	srcIndex := srcIndex + 1.
-	srcIndex := srcIndex + skipDelta.
+        bMap at:i put:(rawMap at:srcIndex).
+        gMap at:i put:(rawMap at:srcIndex+1).
+        rMap at:i put:(rawMap at:srcIndex+2).
+        srcIndex := srcIndex + nRawBytesPerColor.
     ].
 
     ^ MappedPalette
-	redVector:rMap
-	greenVector:gMap
-	blueVector:bMap.
+        redVector:rMap
+        greenVector:gMap
+        blueVector:bMap.
+!
+
+swapBytesFromRGBA_to_BGRA
+    |idx bytesPerRow|
+
+    "/ Depth32Image keeps its data r/g/b/a; BMP has it b/g/r/a (sigh)
+    idx := 1.
+    bytesPerRow := self bytesPerRow.
+    1 to:height do:[:y |
+        self class swap:width pixelsFromRGB_to_BGR_in:data startingAt:idx bytesPerPixel:4.
+        idx := idx + bytesPerRow.
+    ].
+!
+
+swapBytesFromRGB_to_BGR
+    |idx bytesPerRow|
+
+    "/ Depth24Image keeps its data r/g/b; BMP has it b/g/r (sigh)
+    idx := 1.
+    bytesPerRow := self bytesPerRow.
+    1 to:height do:[:y |
+        self class swap:width pixelsFromRGB_to_BGR_in:data startingAt:idx bytesPerPixel:3.
+        idx := idx + bytesPerRow.
+    ].
 ! !
 
 !WindowsIconReader methodsFor:'reading'!
@@ -951,9 +1210,9 @@
 fromWindowsBMPStream:aStream alreadyRead:bytesAlreadyRead
     "read an image from a windows BMP stream"
 
-    | header iSize inPlanes
+    | fileHeader bitmapHeader iSize inPlanes
       imgSize resH resV numColor numImportantColor
-      dataStart redMask greenMask blueMask alphaMask
+      dataStart 
       bytesPerRow numBytesPerColorInColormap|
 
     inStream := aStream.
@@ -963,13 +1222,22 @@
 
     "read the header"
 
-    header := ByteArray uninitializedNew:200.
+    fileHeader := ByteArray new:14.
     bytesAlreadyRead size > 0 ifTrue:[
-        header replaceFrom:1 with:bytesAlreadyRead
+        fileHeader replaceFrom:1 with:bytesAlreadyRead
     ].
-    aStream nextBytes:(18-bytesAlreadyRead size) into:header startingAt:(1+bytesAlreadyRead size).
+    aStream nextBytes:(14-bytesAlreadyRead size) into:fileHeader startingAt:(1+bytesAlreadyRead size).
 
-    iSize := header at:(16r0E + 1).
+    iSize := aStream nextUnsignedLongMSB:false.
+    iSize > 124 ifTrue:[
+        ^ self fileFormatError:'unknown format'.
+    ].
+
+    bitmapHeader := ByteArray new:iSize+16. "/ reserve to allow masks to be read with iSize=40 
+    aStream nextBytes:(iSize-4) into:bitmapHeader startingAt:(1+4).
+
+    dataStart := fileHeader doubleWordAt:(10 + 1) MSB:false.
+self halt.
     ((iSize == 40) or:[iSize == 108 or:[iSize == 124]]) ifTrue:[    "header-size"
         "/
         "/ a Windows3.x BMP file (40)
@@ -978,27 +1246,37 @@
         "/
         "/ 'WinIconReader [info]: Win3.x/Win4.x/Win5.x format' infoPrintCR.
 
-        aStream nextBytes:(iSize-4) into:header startingAt:19.
-
-        width := header doubleWordAt:(16r12 + 1) MSB:false.
-        height := header signedDoubleWordAt:(16r16 + 1) MSB:false.
-        inPlanes := header wordAt:(16r1A + 1) MSB:false.
-        inDepth := header wordAt:(16r1C + 1) MSB:false.
-        compression := header doubleWordAt:(16r1E + 1) MSB:false.
-        imgSize := header doubleWordAt:(16r22 + 1) MSB:false.
-        resH := header doubleWordAt:(16r26 + 1) MSB:false.
-        resV := header doubleWordAt:(16r2A + 1) MSB:false.
-        numColor := header doubleWordAt:(16r2E + 1) MSB:false.
-        numImportantColor := header doubleWordAt:(16r32 + 1) MSB:false.
+        width := bitmapHeader doubleWordAt:(4 + 1) MSB:false.
+        height := bitmapHeader signedDoubleWordAt:(8 + 1) MSB:false.
+        inPlanes := bitmapHeader wordAt:(12 + 1) MSB:false.
+        inDepth := bitmapHeader wordAt:(14 + 1) MSB:false.
+        compression := bitmapHeader doubleWordAt:(16 + 1) MSB:false.
+        imgSize := bitmapHeader doubleWordAt:(20 + 1) MSB:false.
+        resH := bitmapHeader doubleWordAt:(24 + 1) MSB:false.
+        resV := bitmapHeader doubleWordAt:(28 + 1) MSB:false.
+        numColor := bitmapHeader doubleWordAt:(32 + 1) MSB:false.
+        numImportantColor := bitmapHeader doubleWordAt:(36 + 1) MSB:false.
         
         (compression > 3) ifTrue:[
             ^ self fileFormatError:'unhandled compression'.
-        ].    
-        ((compression == 3) or:[iSize == 108]) ifTrue:[
-            redMask := header doubleWordAt:(16r36 + 1) MSB:false.
-            greenMask := header doubleWordAt:(16r3A + 1) MSB:false.
-            blueMask := header doubleWordAt:(16r3E + 1) MSB:false.
-            alphaMask := header doubleWordAt:(16r42 + 1) MSB:false.
+        ].
+        
+        (iSize == 40 and:[compression == 3]) ifTrue:[
+            "/ masks are not counted in header (sigh)
+            aStream next:4*3 into:bitmapHeader startingAt:iSize+1.
+            redMask := bitmapHeader doubleWordAt:(40 + 1) MSB:false.
+            greenMask := bitmapHeader doubleWordAt:(44 + 1) MSB:false.
+            blueMask := bitmapHeader doubleWordAt:(48 + 1) MSB:false.
+            alphaMask := 0.
+        ] ifFalse:[        
+            iSize > 40 ifTrue:[
+                ((compression == 3) or:[iSize == 108]) ifTrue:[
+                    redMask := bitmapHeader doubleWordAt:(40 + 1) MSB:false.
+                    greenMask := bitmapHeader doubleWordAt:(44 + 1) MSB:false.
+                    blueMask := bitmapHeader doubleWordAt:(48 + 1) MSB:false.
+                    alphaMask := bitmapHeader doubleWordAt:(52 + 1) MSB:false.
+                ].
+            ].
         ].
         
         numColor == 0 ifTrue:[
@@ -1009,55 +1287,63 @@
         ].
 
         numBytesPerColorInColormap := 4.
-        dataStart := header wordAt:(16r0A + 1) MSB:false
     ] ifFalse:[
-        ((iSize == 12) or:[iSize == 64]) ifTrue:[
+        ((iSize == 12) or:[ (iSize == 16) or:[iSize == 64]]) ifTrue:[
             "/
             "/ its a Win2.x or OS/2 BMP file
             "/
             "/ 'WinIconReader [info]: Win2.x or OS/2 format' infoPrintCR.
-            aStream nextBytes:(iSize-4) into:header startingAt:19.
 
             numBytesPerColorInColormap := 3.
-            dataStart := nil.
 
-            iSize == 12 ifTrue:[
-                width := header wordAt:(16r12 + 1) MSB:false.
-                height := header signedWordAt:(16r14 + 1) MSB:false.
-                inPlanes := header wordAt:(16r16 + 1) MSB:false.
-                inDepth := header wordAt:(16r18 + 1) MSB:false.
-                "/ dataStart := header wordAt:(16r0A + 1) MSB:false.
+            iSize >= 64 ifTrue:[
+                "/
+                "/ its an OS/2 (vsn2) BMP file
+                "/
+                width := bitmapHeader doubleWordAt:(4 + 1) MSB:false.
+                height := bitmapHeader signedDoubleWordAt:(8 + 1) MSB:false.
+                inPlanes := bitmapHeader wordAt:(12 + 1) MSB:false.
+                inDepth := bitmapHeader wordAt:(14 + 1) MSB:false.
+                compression := bitmapHeader doubleWordAt:(16 + 1) MSB:false.
+                numColor := bitmapHeader doubleWordAt:(32 + 1) MSB:false.
+                numImportantColor := bitmapHeader doubleWordAt:(36 + 1) MSB:false.
+                (compression > 2) ifTrue:[
+                    ^ self fileFormatError:'unhandled OS2 compression'.
+                ].
+                numColor == 0 ifTrue:[
+                    self halt.
+                    "if 0 and depth is 8 or smaller, then the colormap has the size for the depth"
+                    inDepth <= 8 ifTrue:[
+                        numColor := 1 bitShift:inDepth.
+                    ].    
+                ].    
+                numBytesPerColorInColormap := 4.
+            ] ifFalse:[    
+                iSize == 16 ifTrue:[
+                    "/ an OS2 bitmap with large dimensions
+                    width := bitmapHeader doubleWordAt:(4 + 1) MSB:false.
+                    height := bitmapHeader signedDoubleWordAt:(8 + 1) MSB:false.
+                    inPlanes := bitmapHeader wordAt:(12 + 1) MSB:false.
+                    inDepth := bitmapHeader wordAt:(14 + 1) MSB:false.
+                    numBytesPerColorInColormap := 4.
+                ] ifFalse:[
+                    "/ size == 12:
+                    "/ a Win2.x bitmap
+                    width := bitmapHeader wordAt:(4 + 1) MSB:false.
+                    height := bitmapHeader signedWordAt:(6 + 1) MSB:false.
+                    inPlanes := bitmapHeader wordAt:(8 + 1) MSB:false.
+                    inDepth := bitmapHeader wordAt:(10 + 1) MSB:false.
+                ].
                 compression := 0.
-                numColor := 1 bitShift:inDepth.
-            ] ifFalse:[
-                iSize == 64 ifTrue:[
-                    "/
-                    "/ its an OS/2 (vsn2) BMP file
-                    "/
-                    width := header doubleWordAt:(16r12 + 1) MSB:false.
-                    height := header signedDoubleWordAt:(16r16 + 1) MSB:false.
-                    inPlanes := header wordAt:(16r1A + 1) MSB:false.
-                    inDepth := header wordAt:(16r1c + 1) MSB:false.
-                    compression := header doubleWordAt:(16r1e + 1) MSB:false.
-                    numColor := header doubleWordAt:(16r2E + 1) MSB:false.
-                    numImportantColor := header doubleWordAt:(16r32 + 1) MSB:false.
-                    dataStart := header wordAt:(16r0A + 1) MSB:false.
-                    (compression > 2) ifTrue:[
-                        ^ self fileFormatError:'unhandled OS2 compression'.
-                    ].    
-                ].
-            ].
-            numColor == 0 ifTrue:[
-                self halt.
-                "if 0 and depth is 8 or smaller, then the colormap has the size for the depth"
                 inDepth <= 8 ifTrue:[
                     numColor := 1 bitShift:inDepth.
                 ].    
-            ].    
+            ].
         ] ifFalse:[
             ^ self fileFormatError:'unknown format'.
         ].
     ].
+
     topDown := false.
     height < 0 ifTrue:[
         height := height negated.
@@ -1075,7 +1361,15 @@
         numColor > 4096 ifTrue:[
             "/ colormap only allowed up to 12bit
             ^ self fileFormatError:'unreasonable colormap size'.
+        ]. 
+        (dataStart - inStream position) < (numBytesPerColorInColormap*numColor) ifTrue:[
+            self halt
+        ] ifFalse:[
+            (dataStart - inStream position) > (numBytesPerColorInColormap*numColor) ifTrue:[
+                self halt
+            ].    
         ].    
+        
         colorMap := self
                         readColorMap:numColor
                         numBytesPerColor:numBytesPerColorInColormap
@@ -1105,7 +1399,7 @@
         ].
         compression == 3 ifTrue:[
             "/ BITFIELDS - must be depth-16 or 32
-            ((inDepth ~~ 16) and:[inDepth ~~ 32]) ifTrue:[
+            (inDepth < 16) ifTrue:[
                 ^ self fileFormatError:'BITFIELDS compression only supported with depth16/32 images'.
             ].
         ].
@@ -1119,61 +1413,11 @@
     ].
 
     dataStart notNil ifTrue:[
+        (dataStart - inStream position) ~~ 0 ifTrue:[self halt].
+        
         aStream position:dataStart.
     ].
     
-    inDepth <= 8 ifTrue:[
-        photometric := #palette.
-
-        inDepth == 1 ifTrue:[
-            colorMap isNil ifTrue:[
-                photometric := #blackIs0
-            ] ifFalse:[
-                colorMap size == 2 ifTrue:[
-                    ((colorMap at:1) = (Color white)
-                    and:[(colorMap at:2) = (Color black)]) ifTrue:[
-                        photometric := #whiteIs0.
-                        colorMap := nil.
-                    ] ifFalse:[
-                        ((colorMap at:1) = (Color black)
-                        and:[(colorMap at:2) = (Color white)]) ifTrue:[
-                            photometric := #blackIs0.
-                            colorMap := nil.
-                        ].                    
-                    ].                    
-                ].
-            ].
-        ].
-
-        samplesPerPixel := 1.
-        bitsPerSample := Array with:inDepth.
-    ] ifFalse:[
-        inDepth == 16 ifTrue:[
-            photometric := #palette.
-            samplesPerPixel := 3.
-            bitsPerSample := #(5 5 5).
-            colorMap := FixedPalette
-                            redShift:10 redMask:16r1f
-                            greenShift:5 greenMask:16r1f
-                            blueShift:0 blueMask:16r1F.
-
-        ] ifFalse:[
-            inDepth == 24 ifTrue:[
-                photometric := #rgb.
-                samplesPerPixel := 3.
-                bitsPerSample := #(8 8 8).
-            ] ifFalse:[
-                inDepth == 32 ifTrue:[
-                    photometric := #rgb.
-                    samplesPerPixel := 4.
-                    bitsPerSample := #(8 8 8 8).
-                ] ifFalse:[
-                    ^ self fileFormatError:'unsupported depth'.
-                ]
-            ]
-        ]
-    ].
-
     inDepth == 24 ifTrue:[
         bytesPerRow := width * 3
     ] ifFalse:[
@@ -1183,6 +1427,7 @@
             inDepth == 32 ifTrue:[
                 bytesPerRow := width * 4
             ] ifFalse:[
+                bitsPerSample := Array with:inDepth.
                 bytesPerRow := self bytesPerRow
             ].
         ].
@@ -1201,6 +1446,8 @@
         ^ nil
     ].
 
+    self convertPixels.
+    
     ^ self image
 
     "Modified: / 17-09-1995 / 18:48:46 / claus"