#FEATURE
authorClaus Gittinger <cg@exept.de>
Sat, 05 Mar 2016 15:16:12 +0100
changeset 3583 ccf4b1d2548a
parent 3581 cbd1af2f743b
child 3584 141dd71ce83f
#FEATURE class: WindowsIconReader class definition comment/format in: #fileFormatDescription #fromOS2Stream:alreadyRead: changed:6 methods
WindowsIconReader.st
--- a/WindowsIconReader.st	Fri Mar 04 19:53:34 2016 +0100
+++ b/WindowsIconReader.st	Sat Mar 05 15:16:12 2016 +0100
@@ -14,7 +14,7 @@
 "{ NameSpace: Smalltalk }"
 
 ImageReader subclass:#WindowsIconReader
-	instanceVariableNames:'compression inDepth'
+	instanceVariableNames:'compression inDepth topDown'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Graphics-Images-Readers'
@@ -60,47 +60,55 @@
 "
     Information from http://www.daubnet.com/formats/BMP.html - no Warranty.
 
-	  Name           Size                Description
+          Name           Size                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             'BM'
+          FileSize       4 bytes             File size in bytes
+          reserved       4 bytes             unused (=0)
+          DataOffset     4 bytes             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
-					     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
-					     0 = BI_RGB   no compression
-					     1 = BI_RLE8 8bit RLE encoding
-					     2 = BI_RLE4 4bit RLE encoding
-	  ImageSize      4 bytes             (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
-	  ColorsImportant
-			 4 bytes             Number of important colors
-					     0 = all
+          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
+                                             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
+                                             0 = RGB            no compression
+                                             1 = RLE8           8bit RLE encoding
+                                             2 = RLE4           4bit RLE encoding
+                                             3 = BITFIELDS      Windows V3+ only
+                                             4 = JPEG           Windows V3+ only
+                                             5 = PNG            Windows V3+ only
+        
+                                             3 = HUFFMAN1D      OS/2 2.x-only
+                                             4 = RLE24          OS/2 2.x-only
+
+
+          ImageSize      4 bytes             (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
+          ColorsImportant
+                         4 bytes             Number of important colors
+                                             0 = all
        ColorTable        4 * NumColors bytes
-					     present only if Info.BitsPerPixel <= 8
-					     colors should be ordered by importance
+                                             present only if Info.BitsPerPixel <= 8
+                                             colors should be ordered by importance
 
-	    Red           1 byte              Red intensity
-	    Green         1 byte              Green intensity
-	    Blue          1 byte              Blue intensity
-	    reserved      1 byte             unused (=0)
-	  repeated NumColors times
+            Red           1 byte              Red intensity
+            Green         1 byte              Green intensity
+            Blue          1 byte              Blue intensity
+            reserved      1 byte             unused (=0)
+          repeated NumColors times
 
        Raster Data      Info.ImageSize bytes     The pixel data
 
@@ -154,29 +162,29 @@
        End-of-Bitmap is zero padded to end on a 32bit boundary. Due to the 16bit-ness of this structure this will always be
        either two zero bytes or none.
 
-	n (byte 1) c (Byte 2)                                       Description
-	>0        any      n pixels are to be drawn. The 1st, 3rd, 5th, ... pixels' color is in c's high-order 4 bits, the even
-			    pixels' color is in c's low-order 4 bits. If both color indices are the same, it results in just n
-			    pixels of color c
-	0         0        End-of-line
-	0         1        End-of-Bitmap
-	0         2        Delta. The following 2 bytes define an unsigned offset in x and y direction (y being up) The
-			    skipped pixels should get a color zero.
-	0         >=3      The following c bytes will be read as single pixel colors just as in uncompressed files. up to 12
-			    bits of zeros follow, to put the file/memory pointer on a 16bit boundary again.
+        n (byte 1) c (Byte 2)                                       Description
+        >0        any      n pixels are to be drawn. The 1st, 3rd, 5th, ... pixels' color is in c's high-order 4 bits, the even
+                            pixels' color is in c's low-order 4 bits. If both color indices are the same, it results in just n
+                            pixels of color c
+        0         0        End-of-line
+        0         1        End-of-Bitmap
+        0         2        Delta. The following 2 bytes define an unsigned offset in x and y direction (y being up) The
+                            skipped pixels should get a color zero.
+        0         >=3      The following c bytes will be read as single pixel colors just as in uncompressed files. up to 12
+                            bits of zeros follow, to put the file/memory pointer on a 16bit boundary again.
 
 
-				      Example for 4bit RLE
-	Compressed Data                           Expanded data
-	03 04              0 4 0
-	05 06              0 6 0 6 0
-	00 06 45 56 67 00  4 5 5 6 6 7
-	04 78              7 8 7 8
-	00 02 05 01        Move 5 right and 1 up. (Windows docs say down, which is wrong)
-	00 00              End-of-line
-	09 1E              1 E 1 E 1 E 1 E 1
-	00 01              EndofBitmap
-	00 00              Zero padding for 32bit boundary
+                                      Example for 4bit RLE
+        Compressed Data                           Expanded data
+        03 04              0 4 0
+        05 06              0 6 0 6 0
+        00 06 45 56 67 00  4 5 5 6 6 7
+        04 78              7 8 7 8
+        00 02 05 01        Move 5 right and 1 up. (Windows docs say down, which is wrong)
+        00 00              End-of-line
+        09 1E              1 E 1 E 1 E 1 E 1
+        00 01              EndofBitmap
+        00 00              Zero padding for 32bit boundary
 
 
 Raster Data compression for 8bit / 256 color images:
@@ -187,30 +195,27 @@
        End-of-Bitmap is zero padded to end on a 32bit boundary. Due to the 16bit-ness of this structure this will always be
        either two zero bytes or none.
 
-	n (byte 1)   c (Byte 2)                                    Description
-	>0       any        n pixels of color number c
-	0        0          End-of-line
-	0        1          End Of Bitmap
-	0        2          Delta. The following 2 bytes define an unsigned offset in x and y direction (y being up) The
-			    skipped pixels should get a color zero.
-	0        >=3        The following c bytes will be read as single pixel colors just as in uncompressed files. A zero
-			    follows, if c is odd, putting the file/memory pointer on a 16bit boundary again.
+        n (byte 1)   c (Byte 2)                                    Description
+        >0       any        n pixels of color number c
+        0        0          End-of-line
+        0        1          End Of Bitmap
+        0        2          Delta. The following 2 bytes define an unsigned offset in x and y direction (y being up) The
+                            skipped pixels should get a color zero.
+        0        >=3        The following c bytes will be read as single pixel colors just as in uncompressed files. A zero
+                            follows, if c is odd, putting the file/memory pointer on a 16bit boundary again.
 
 
-				      Example for 8bit RLE
-	Compressed Data                           Expanded data
-	03 04              04 04 04
-	05 06              06 06 06 06 06
-	00 03 45 56 67 00  45 56 67
-	02 78              78 78
-	00 02 05 01        Move 5 right and 1 up. (Windows docs say down, which is wrong)
-	00 00              End-of-line
-	09 1E              1E 1E 1E 1E 1E 1E 1E 1E 1E
-	00 01              End-of-bitmap
-	00 00              Zero padding for 32bit boundary
-
-
-
+                                      Example for 8bit RLE
+        Compressed Data                           Expanded data
+        03 04              04 04 04
+        05 06              06 06 06 06 06
+        00 03 45 56 67 00  45 56 67
+        02 78              78 78
+        00 02 05 01        Move 5 right and 1 up. (Windows docs say down, which is wrong)
+        00 00              End-of-line
+        09 1E              1E 1E 1E 1E 1E 1E 1E 1E 1E
+        00 01              End-of-bitmap
+        00 00              Zero padding for 32bit boundary
 
 Portability:
 
@@ -222,7 +227,6 @@
 Trademarks, Patents and Royalties
        To my knowledge: None.
 "
-
 ! !
 
 !WindowsIconReader class methodsFor:'initialization'!
@@ -346,7 +350,9 @@
 !
 
 loadBMPWidth:w height:h bytesPerPixel:bpp from:aStream into:data
-    |buff idx fileBytesPerRow imgBytesPerRow align|
+    "load bmp-16/24/32 bit per pixel imagedata."
+
+    |buff dstIdx fileBytesPerRow imgBytesPerRow align lineDelta|
 
     align := 4.
 
@@ -359,19 +365,23 @@
         "/
         "/ stupid - last row comes first
         "/
-        idx := imgBytesPerRow * (h - 1) + 1.
         buff := ByteArray uninitializedNew:fileBytesPerRow.
 
+        topDown ifTrue:[
+            dstIdx := 1.
+            lineDelta := imgBytesPerRow
+        ] ifFalse:[
+            dstIdx := imgBytesPerRow * (h - 1) + 1.
+            lineDelta := imgBytesPerRow negated
+        ].
+        
         1 to:h do:[:row |
             (aStream nextBytes:fileBytesPerRow into:buff) == fileBytesPerRow ifFalse:[
                 ^ false
             ].
-            data replaceFrom:idx to:idx+imgBytesPerRow-1 with:buff.
-            idx := idx - imgBytesPerRow.
+            data replaceFrom:dstIdx to:(dstIdx+imgBytesPerRow-1) with:buff.
+            dstIdx := dstIdx + lineDelta.
         ].
-        compression == 3 ifTrue:[
-            self breakPoint:#cg. "/ TODO: check what we have to do here...
-        ].    
         ^ true
     ].
     "/ 'BMPReader: unsupported compression: ' infoPrint. compression infoPrintCR. 
@@ -429,43 +439,78 @@
 loadRLECompressedBMP4From:aStream into:aByteArray
     "load bmp-rle-4 pixel imagedata"
 
-    |bytesPerRowInData x y dstIndex lineStartIndex cnt pair clr1 clr2 code n nbyte|
+    |bytesPerRowInData x y dstIndex lineStartIndex cnt pair clr1 clr2 code nbyte byte bytes byteIdx|
 
     bytesPerRowInData := self bytesPerRow.
     x := 0.
-    y := height - 1.
-    lineStartIndex := (y * bytesPerRowInData) + 1.
+    
+    topDown ifTrue:[
+        y := 0.
+        lineStartIndex := 1.
+    ] ifFalse:[
+        y := height - 1.
+        lineStartIndex := (y * bytesPerRowInData) + 1.
+    ].
     dstIndex := lineStartIndex.
-
-    [ y < height ] whileTrue:[
+    
+    [ y between:0 and:height-1 ] whileTrue:[
         cnt := aStream nextByte.
         pair := aStream nextByte.
         cnt ~~ 0 ifTrue:[
+            ((x between:0 and:width-1) and:[y between:0 and:height-1]) ifFalse:[
+                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.
-            [cnt > 1] whileTrue:[
-                aByteArray at:dstIndex put:((clr2 << 4) bitOr:clr1).
+            x even ifTrue:[
+                byte := ((clr2 << 4) bitOr:clr1).
+                (cnt >= 2) ifTrue:[
+                    nbyte := cnt // 2.
+                    aByteArray from:dstIndex to:(dstIndex+nbyte-1) put:byte.
+                    dstIndex := dstIndex + nbyte.
+                ].
+                cnt odd ifTrue:[
+                    "/ got odd count
+                    aByteArray at:dstIndex put:clr1.
+                    "/ self halt.
+                ].    
+            ] ifFalse:[
+                "/ the first halfbyte
+                byte := aByteArray at:dstIndex.
+                aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(pair bitAnd:16rF0)).
                 dstIndex := dstIndex + 1.
-                cnt := cnt - 2.
-                x := x + 2.
+                nbyte := (cnt-1) // 2.
+                nbyte > 0 ifTrue:[
+                    aByteArray from:dstIndex to:(dstIndex+nbyte-1) put:pair.
+                    dstIndex := dstIndex + nbyte.
+                ].
+                cnt even ifTrue:[
+                    "/ the final halfbyte
+                    byte := aByteArray at:dstIndex.
+                    aByteArray at:dstIndex put:((byte bitAnd:16rF0) bitOr:(pair bitAnd:16r0F)).
+                ].    
             ].
-            (cnt > 0) ifTrue:[
-                "/ got odd count
-                aByteArray at:dstIndex put:clr1.
-                x := x + 1.
-                "/ self halt.
-            ].    
+            x := x + cnt.
         ] ifFalse:[
             "/ cnt == 0: escape codes */
             code := pair.
             code == 0 ifTrue:[
                 "/ end of line
+Transcript printf:'EOL\n'.
                 x := 0.
-                y := y - 1.
-                lineStartIndex := lineStartIndex - bytesPerRowInData.
+                topDown ifTrue:[
+                    y := y + 1.
+                    lineStartIndex := lineStartIndex + bytesPerRowInData.
+                ] ifFalse:[    
+                    y := y - 1.
+                    lineStartIndex := lineStartIndex - bytesPerRowInData.
+                ].    
                 dstIndex := lineStartIndex.
             ] ifFalse:[
                 code == 1 ifTrue:[
+Transcript printf:'END\n'.
                     "/ end of pic
                     ^ true
                 ].
@@ -473,28 +518,57 @@
                     "/ 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.
                 ] ifFalse:[
                     "/ absolute; cnt pixels coming
+                    ((x between:0 and:width-1) and:[y between:0 and:height-1]) ifFalse:[
+                        self breakPoint:#cg.
+                        self fileFormatError:('invalid delta').
+                    ].    
                     cnt := code.
-                    nbyte := cnt // 2.
-                    n := aStream nextBytes:nbyte into:aByteArray startingAt:dstIndex.
-                    n ~~ nbyte ifTrue:[^ false].
-                    dstIndex := dstIndex + nbyte.
-                    x := x + cnt.
-                    
-                    cnt odd ifTrue:[
-                        clr1 := aStream nextByte.
-                        aByteArray at:dstIndex put:clr1.
-                        x := x + 1.
-                        "/ self halt.
-                    ].
-                    
-                    "/ odd count - padd
+                    nbyte := (cnt+1) // 2.
+                    bytes := aStream nextBytes:nbyte.
+                    "/ odd byte count - padd
                     nbyte odd ifTrue:[
                         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.
+                    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.
+                        ].                        
+                        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.
+                            byte := aByteArray at:dstIndex.
+                            aByteArray at:dstIndex put:((byte bitAnd:16r0F) bitOr:(pair bitAnd:16rF0)).
+                            "/ self halt.
+                        ].
+                    ].    
+                    x := x + cnt. 
                 ].
             ].
         ].
@@ -509,11 +583,17 @@
 
     bytesPerRowInData := self bytesPerRow.
     x := 0.
-    y := height - 1.
-    lineStartIndex := (y * bytesPerRowInData) + 1.
+
+    topDown ifTrue:[
+        y := 0.
+        lineStartIndex := 1.
+    ] ifFalse:[
+        y := height - 1.
+        lineStartIndex := (y * bytesPerRowInData) + 1.
+    ].    
     dstIndex := lineStartIndex.
-
-    [ y < height ] whileTrue:[
+    
+    [ y between:0 and:height-1 ] whileTrue:[
         cnt := aStream nextByte.
         clr := aStream nextByte.
         cnt ~~ 0 ifTrue:[
@@ -526,8 +606,13 @@
             code == 0 ifTrue:[
                 "/ end of line
                 x := 0.
-                y := y - 1.
-                lineStartIndex := lineStartIndex - bytesPerRowInData.
+                topDown ifTrue:[
+                    y := y + 1.
+                    lineStartIndex := lineStartIndex + bytesPerRowInData.
+                ] ifFalse:[    
+                    y := y - 1.
+                    lineStartIndex := lineStartIndex - bytesPerRowInData.
+                ].
                 dstIndex := lineStartIndex.
             ] ifFalse:[
                 code == 1 ifTrue:[
@@ -561,27 +646,38 @@
 loadUncompressedFrom:aStream into:aByteArray
     "load bmp-1,2,4 and 8 bit per pixel imagedata."
 
-    |bytesPerRowInStream bytesPerRowInData skip dstIndex n|
+    |bytesPerRowInStream bytesPerRowInData skip n
+     dstIndex  "{ Class: SmallInteger }" 
+     lineDelta "{ Class: SmallInteger }" 
+     nRows     "{ Class: SmallInteger }" |
 
     compression == 0 ifFalse:[
-	^ false
+        ^ false
     ].
 
     bytesPerRowInStream := Image bytesPerRowForWidth:width depth:inDepth padding:32.
     bytesPerRowInData := self bytesPerRow.
     skip := bytesPerRowInStream - bytesPerRowInData.
 
-    "/ bottom row first...
-    dstIndex := (height - 1) * bytesPerRowInData + 1.
-    height to:1 by:-1 do:[:y |
-	n := aStream nextBytes:bytesPerRowInData into:aByteArray startingAt:dstIndex.
-	n ~~ bytesPerRowInData ifTrue:[
-	    ^ false.
-	].
-	skip ~~ 0 ifTrue:[
-	    aStream skip:skip.
-	].
-	dstIndex := dstIndex - bytesPerRowInData.
+    topDown ifTrue:[
+        dstIndex := 1.
+        lineDelta := bytesPerRowInData.
+    ] ifFalse:[    
+        "/ bottom row first...
+        dstIndex := (height - 1) * bytesPerRowInData + 1.
+        lineDelta := bytesPerRowInData negated.
+    ].
+    nRows := height.
+    
+    1 to:nRows do:[:row |
+        n := aStream nextBytes:bytesPerRowInData into:aByteArray startingAt:dstIndex.
+        n ~~ bytesPerRowInData ifTrue:[
+            ^ false.
+        ].
+        skip ~~ 0 ifTrue:[
+            aStream skip:skip.
+        ].
+        dstIndex := dstIndex + lineDelta.
     ].
     ^ true.
 !
@@ -656,25 +752,25 @@
 
     header := ByteArray uninitializedNew:8r110.
     bytesAlreadyRead size > 0 ifTrue:[
-	header replaceFrom:1 with:bytesAlreadyRead
+        header replaceFrom:1 with:bytesAlreadyRead
     ].
     aStream nextBytes:(16-bytesAlreadyRead size) into:header startingAt:(1+bytesAlreadyRead size).
 
     (header startsWith:#(73 67)) ifTrue:[         "IC"
-	"IC format"
-	aStream nextBytes:10 into:header startingAt:17.
-	width := header at:7.
-	height := header at:9.
-	inDepth := 2 "header at:11". "where is it"
+        "IC format"
+        aStream nextBytes:10 into:header startingAt:17.
+        width := header at:7.
+        height := header at:9.
+        inDepth := 2 "header at:11". "where is it"
     ] ifFalse:[
-	(header startsWith:#(67 73)) ifTrue:[     "CI"
-	    ^ self fileFormatError:'unsupported format: CI'.
-	] ifFalse:[
-	    aStream nextBytes:(8r110-16) into:header startingAt:17.
-	    width := header at:8r101.
-	    height := header at:8r103.
-	    inDepth := header at:8r107.
-	]
+        (header startsWith:#(67 73)) ifTrue:[     "CI"
+            ^ self fileFormatError:'unsupported format: CI'.
+        ] ifFalse:[
+            aStream nextBytes:(8r110-16) into:header startingAt:17.
+            width := header at:8r101.
+            height := header at:8r103.
+            inDepth := header at:8r107.
+        ]
     ].
 
     self reportDimension.
@@ -729,7 +825,7 @@
     data := ByteArray uninitializedNew:(height * width "bytesPerRow").
     compression := 0.
     (self loadBMPWidth:width height:height depth:inDepth from:aStream into:data) ifFalse:[
-	^ nil
+        ^ nil
     ].
     photometric := #palette.
     samplesPerPixel := 1.
@@ -758,50 +854,53 @@
     byteOrder := #lsb.
 
     aStream binary.
+    aStream signalAtEnd:true.
     aStream isFileStream ifTrue:[
-	fileSize := aStream fileSize.
-	fileSize < 16 ifTrue:[
-	    ^ self fileFormatError:'short file'.
-	].
+        fileSize := aStream fileSize.
+        fileSize < 16 ifTrue:[
+            ^ self fileFormatError:'short/corrupted file'.
+        ].
     ].
 
-    header := ByteArray uninitializedNew:4.
-    aStream nextBytes:4 into:header.
+    EndOfStreamError handle:[:ex |
+        ^ self fileFormatError:'unexpected EOF while reading (short/corrupted file)'.
+    ] do:[    
+        header := ByteArray uninitializedNew:4.
+        aStream nextBytes:4 into:header.
 
-    (header startsWith:#(66 77)) ifTrue:[     "BM"
-"/        'WinIconReader [info]: Win3.x or OS/2 vsn 2 BM format' infoPrintNL.
-	^ self fromWindowsBMPStream:aStream alreadyRead:header
-    ].
-    (header startsWith:#(66 65)) ifTrue:[     "BA"
-"/        'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
-	^ self fromOS2Stream:aStream alreadyRead:header
-    ].
-    (header startsWith:#(67 73)) ifTrue:[     "CI"
-"/        'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
-"/        ^ self fromOS2Stream:aStream
-	^ self fileFormatError:'OS/2 CI format not supported'.
+        (header startsWith:#(66 77)) ifTrue:[     "BM"
+            "/ 'WinIconReader [info]: Win3.x or OS/2 vsn 2 BM format' infoPrintNL.
+            ^ self fromWindowsBMPStream:aStream alreadyRead:header
+        ].
+        (header startsWith:#(66 65)) ifTrue:[     "BA"
+            "/ 'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
+            ^ self fromOS2Stream:aStream alreadyRead:header
+        ].
+        (header startsWith:#(67 73)) ifTrue:[     "CI"
+            "/ 'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
+            "/ ^ self fromOS2Stream:aStream
+            ^ self fileFormatError:'OS/2 CI format not supported'.
+        ].
+        (header startsWith:#(73 67)) ifTrue:[     "IC"
+            "/ 'WinIconReader [info]: OS/2 IC format' infoPrintNL.
+            ^ self fromOS2Stream:aStream alreadyRead:header
+        ].
+        (header startsWith:#(80 84)) ifTrue:[     "PT"
+            "/ 'WinIconReader [info]: OS/2 PT format' infoPrintNL.
+            ^ self fromOS2Stream:aStream alreadyRead:header
+        ].
+        (header startsWith:#(16r53 16r5A)) ifTrue:[     "SZ"
+            "/ 'WinIconReader [info]: OS/2 SZ format' infoPrintNL.
+            "/ ^ self fromOS2Stream:aStream
+            ^ self fileFormatError:'OS/2 SZ format not supported'.
+        ].
+        (header startsWith:#(0 0 1 0)) ifTrue:[
+            "/ 'WinIconReader [info]: Win3.x ICO format' infoPrintNL.
+            ^ self fromWindowsICOStream:aStream alreadyRead:header
+        ].
     ].
-    (header startsWith:#(73 67)) ifTrue:[     "IC"
-"/        'WinIconReader [info]: OS/2 IC format' infoPrintNL.
-	^ self fromOS2Stream:aStream alreadyRead:header
-    ].
-    (header startsWith:#(80 84)) ifTrue:[     "PT"
-"/        'WinIconReader [info]: OS/2 PT format' infoPrintNL.
-	^ self fromOS2Stream:aStream alreadyRead:header
-    ].
-    (header startsWith:#(16r53 16r5A)) ifTrue:[     "SZ"
-"/        'WinIconReader [info]: OS/2 SZ format' infoPrintNL.
-"/        ^ self fromOS2Stream:aStream
-	^ self fileFormatError:'OS/2 SZ format not supported'.
-    ].
-    (header startsWith:#(0 0 1 0)) ifTrue:[
-"/        'WinIconReader [info]: Win3.x ICO format' infoPrintNL.
-	^ self fromWindowsICOStream:aStream alreadyRead:header
-    ].
-    ^ self fileFormatError:('format not supported:'
-			    , ((header at:1) printStringRadix:16)
-			    , ' '
-			    , ((header at:2) printStringRadix:16)).
+    
+    ^ self fileFormatError:('format not supported: %02x %02x' printfWith:(header at:1) with:(header at:2))
 
     "
      Image fromFile:'/phys/clam//LocalLibrary/Images/OS2_icons/dos.ico'
@@ -843,57 +942,63 @@
     inStream := aStream.
     aStream binary.
     byteOrder := #lsb.
+    topDown := false.
 
     "read the header"
 
-    header := ByteArray uninitializedNew:16r54.
+    header := ByteArray uninitializedNew:200.
     bytesAlreadyRead size > 0 ifTrue:[
         header replaceFrom:1 with:bytesAlreadyRead
     ].
     aStream nextBytes:(18-bytesAlreadyRead size) into:header startingAt:(1+bytesAlreadyRead size).
 
     iSize := header at:(16r0E + 1).
-    (iSize == 40) ifTrue:[    "header-size"
+    ((iSize == 40) or:[iSize == 108 or:[iSize == 124]]) ifTrue:[    "header-size"
         "/
-        "/ a Windows3.x BMP file
+        "/ a Windows3.x BMP file (40)
+        "/ a Windows4.x BMP file (108)
+        "/ a Windows5.x BMP file (124)
         "/
-        "/ 'WinIconReader [info]: Win3.x format' infoPrintCR.
+        "/ 'WinIconReader [info]: Win3.x/Win4.x/Win5.x format' infoPrintCR.
 
-        aStream nextBytes:(40-4) into:header startingAt:19.
+        aStream nextBytes:(iSize-4) into:header startingAt:19.
 
-        width := header wordAt:(16r12 + 1) MSB:false.
-        height := header wordAt:(16r16 + 1) MSB:false.
+        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 wordAt:(16r1E + 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.
-        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.
-
+        
+        (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.
+        ].
+        
         numColor == 0 ifTrue:[
-            "
-             some bmp-writers seem to leave this as zero (which is wrong)
-            "
+            "if 0 and depth is 8 or smaller, then the colormap has the size for the depth"
             inDepth <= 8 ifTrue:[
                 numColor := 1 bitShift:inDepth.
-                "/ 'WinIconReader [warning]: missing nColor in header - assume ' infoPrint. numColor infoPrintCR
             ]
         ].
 
         numBytesPerColorInColormap := 4.
         dataStart := header wordAt:(16r0A + 1) MSB:false
     ] ifFalse:[
-        ((iSize == 12) or:[iSize >= 64]) ifTrue:[
+        ((iSize == 12) or:[iSize == 64]) ifTrue:[
             "/
-            "/ its an OS/2 BMP file
+            "/ its a Win2.x or OS/2 BMP file
             "/
-            "/ 'WinIconReader [info]: OS/2 format' infoPrintCR.
+            "/ 'WinIconReader [info]: Win2.x or OS/2 format' infoPrintCR.
             aStream nextBytes:(iSize-4) into:header startingAt:19.
 
             numBytesPerColorInColormap := 3.
@@ -901,35 +1006,48 @@
 
             iSize == 12 ifTrue:[
                 width := header wordAt:(16r12 + 1) MSB:false.
-                height := header wordAt:(16r14 + 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.
                 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'.
+                    ].    
+                ].
             ].
-            iSize >= 64 ifTrue:[
-                "/
-                "/ its an OS/2 (vsn2) BMP file
-                "/
-                width := header doubleWordAt:(16r12 + 1) MSB:false.
-                height := header doubleWordAt:(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.
-            ].
-            numColor := 1 bitShift:inDepth.
+            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'.
         ].
     ].
-    width > 10000 ifTrue:[
-        ^ self fileFormatError:'unreasonable width'.
-    ].
-    height > 10000 ifTrue:[
-        ^ self fileFormatError:'unreasonable height'.
+    topDown := false.
+    height < 0 ifTrue:[
+        height := height negated.
+        topDown := true.
+    ].    
+    ((width > 10000) or:[height > 10000]) ifTrue:[
+        ^ self fileFormatError:'unreasonable width or height'.
     ].
     
     self reportDimension.
@@ -1052,8 +1170,13 @@
             ].
         ].
     ].
+
     data := ByteArray uninitializedNew:(height * bytesPerRow).
-
+    "/ when compressed, there may be holes, which need to be filled with zeros
+    compression ~~ 0 ifTrue:[
+        data atAllPut:0
+    ].
+    
     "/ read & possibly decompress
 
     (self loadBMPWidth:width height:height depth:inDepth from:aStream into:data) ifFalse:[