WindowsIconReader.st
author Claus Gittinger <cg@exept.de>
Wed, 19 Nov 2003 16:28:36 +0100
changeset 1846 d29322944b05
parent 1805 93f557cbe600
child 1848 864ca2cd4e71
permissions -rw-r--r--
dimensionReport

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

"{ Package: 'stx:libview2' }"

ImageReader subclass:#WindowsIconReader
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images-Readers'
!

!WindowsIconReader class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this class provides methods for loading Windows and OS2 icon files.
    Image writing is only supported for BMP format with depth 1,4,8 and 24 bit images.

    The reader tries to figure out which version of BMP/ICO is used.
    It seems to be able to load most formats, but who knows ...

    The class name *IconReader is a bad, historic choice - it ws originally
    written to read icons only, but evolved over time and it should now be also
    capapble of reading bmp and cursor files.

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

fileFormatDescription
"
    Information from http://www.daubnet.com/formats/BMP.html - no Warranty.

          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

      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
       ColorTable        4 * NumColors bytes
                                             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

       Raster Data      Info.ImageSize bytes     The pixel data


Raster Data encoding:
       Depending on the image's BitCount and on the Compression flag there are 6 different encoding schemes. 
       All of them share the following:  

       Pixels are stored bottom-up, left-to-right. Pixel lines are padded with zeros to end on a 32bit (4byte) boundary. For
       uncompressed formats every line will have the same number of bytes. Color indices are zero based, meaning a pixel
       color of 0 represents the first color table entry, a pixel color of 255 (if there are that many) represents the 256th entry.
       For images with more than 256 colors there is no color table. 

Raster Data encoding for 1bit / black & white images:
       BitCount = 1 Compression = 0  
       Every byte holds 8 pixels, its highest order bit representing the leftmost pixel of those. There are 2 color table entries.
       Some readers will ignore them though, and assume that 0 is black and 1 is white. If you are storing black and white
       pictures you should stick to this, with any other 2 colors this is not an issue. Remember padding with zeros up to a
       32bit boundary (This can be up to 31 zeros/pixels!!)                                                                 

Raster Data encoding for 4bit / 16 color images:
       BitCount = 4 Compression = 0  
       Every byte holds 2 pixels, its high order 4 bits representing the left of those. There are 16 color table entries. These
       colors do not have to be the 16 MS-Windows standard colors. Padding each line with zeros up to a 32bit boundary
       will result in up to 28 zeros = 7 'wasted pixels'.

Raster Data encoding for 8bit / 256 color images:
       BitCount = 8 Compression = 0  
       Every byte holds 1 pixel. There are 256 color table entries. Padding each line with zeros up to a 32bit boundary will
       result in up to 3 bytes of zeros = 3 'wasted pixels'.

Raster Data encoding for 16bit / hicolor images:
       BitCount = 16 Compression = 0  
       Every 2bytes / 16bit holds 1 pixel.   
       <information missing: the 16 bit was introduced together with Video For Windows? Is it a memory-only-format?>  
       The pixels are no color table pointers. There are no color table entries. Padding each line with zeros up to a 16bit
       boundary will result in up to 2 zero bytes.

Raster Data encoding for 24bit / truecolor images:
       BitCount = 24 Compression = 0  
       Every 4bytes / 32bit holds 1 pixel. The first holds its red, the second its green, and the third its blue intensity. The
       fourth byte is reserved and should be zero. There are no color table entries. The pixels are no color table pointers. No
       zero padding necessary.


Raster Data compression for 4bit / 16 color images:
       BitCount = 4 Compression = 2  
       The pixel data is stored in 2bytes / 16bit chunks.  The first of these specifies the number of consecutive pixels with the
       same pair of color. The second byte defines two color indices. The resulting pixel pattern will be interleaved
       high-order 4bits and low order 4 bits (ABABA...). If the first byte is zero, the second defines an escape code. The
       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.


                                      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:

       BitCount = 8 Compression = 1  
       The pixel data is stored in 2bytes / 16bit chunks.  The first of these specifies the number of consecutive pixels with the
       same color. The second byte defines their color index. If the first byte is zero, the second defines an escape code. The
       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.


                                      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:

       Although BMPs were invented by Microsoft for its Windows platform, a lot of programs on other platforms are capable
       of reading and writing them. Notice the Intel order in 2byte and 4-byte integer values (Least significant byte first). The
       16bit BMPs have been introduced to Windows after the others, still puzzling many applications.


Trademarks, Patents and Royalties
       To my knowledge: None.  
"

! !

!WindowsIconReader class methodsFor:'initialization'!

initialize
    "tell Image-class, that a new fileReader is present
     for the '.bmp' and '.ico' extensions."

    MIMETypes defineImageType:'image/x-MS-bitmap' suffix:'bmp' reader:self.
    MIMETypes defineImageType:nil                 suffix:'ico' reader:self.

    "Modified: 1.2.1997 / 15:03:59 / cg"
! !

!WindowsIconReader class methodsFor:'testing'!

canRepresent:anImage
    "return true, if anImage can be represented in my file format.
     BMP supports depth 1,4,8 and 24."

    ^ (#(1 4 8 24) includes:anImage depth)

    "Created: 17.10.1997 / 20:18:23 / cg"
!

isValidImageFile:aFileName
    "return true, if aFileName contains a valid windows bitmap-file image"

    |inStream header ok|

    inStream := self streamReadingFile:aFileName.
    inStream isNil ifTrue:[^ false].

    inStream binary.
    ok := false.
    inStream fileSize > 16 ifTrue:[
        header := ByteArray uninitializedNew:4.
        inStream nextBytes:4 into:header.

        (header startsWith:#(66 77)) ifTrue:[     "BM"
            ok := true.
"/            'WINREADER: Win3.x or OS/2 vsn 2 BM format' infoPrintNL.
        ].
        (header startsWith:#(66 65)) ifTrue:[     "BA"
            ok := true.
"/            'WINREADER: OS/2 vsn 2 BA format' infoPrintNL.
        ].
        (header startsWith:#(73 67)) ifTrue:[     "IC"
            ok := true.
"/            'WINREADER: OS/2 IC format' infoPrintNL.
        ].
        (header startsWith:#(80 84)) ifTrue:[     "PT"
            ok := true.
"/            'WINREADER: OS/2 PT format' infoPrintNL.
        ].
        (header startsWith:#(0 0 1 0)) ifTrue:[
            ok := true.
"/            'WINREADER: Win3.x ICO format' infoPrintNL.
        ].
    ].
    inStream close.
    ^ ok

    "
     WindowsIconReader isValidImageFile:'/phys/clam2/LocalLibrary/Images/OS2_icons/dos.ico'
    "

    "Created: 17.9.1995 / 17:14:20 / claus"
! !

!WindowsIconReader methodsFor:'private'!

loadBMPWidth:w height:h depth:d compression:c from:aStream into:data
    "helper: load a BMP image"

    |buff idx fileBytesPerRow imgBytesPerRow|

    d == 8 ifTrue:[
        (self class loadBMP8Width:w height:h compression:c from:aStream into:data) ifFalse:[
            self fileFormatError:'read/decompression failed'.
            ^ false
        ].
        ^ true
    ].
    d == 4 ifTrue:[
        (self class loadBMP4to8Width:w height:h compression:c from:aStream into:data) ifFalse:[
            self fileFormatError:'read/decompression failed'.
            ^ false
        ].
        ^ true
    ].
    d == 2 ifTrue:[
        (self class loadBMP2to8Width:w height:h from:aStream into:data) ifFalse:[
            self fileFormatError:'read failed'.
            ^ false
        ].
        ^ true
    ].
    d == 1 ifTrue:[
        (self class loadBMP1to8Width:w height:h from:aStream into:data) ifFalse:[
            self fileFormatError:'read failed'.
            ^ false
        ].
        ^ true
    ].
    d == 24 ifTrue:[
        imgBytesPerRow := w * 3.
        fileBytesPerRow := imgBytesPerRow.
        (fileBytesPerRow bitAnd:3) ~~ 0 ifTrue:[
            fileBytesPerRow := (fileBytesPerRow bitAnd:(3 bitInvert)) + 4.
        ].
        "/
        "/ stupid - last row comes first
        "/
        idx := imgBytesPerRow * (height - 1) + 1.
        buff := ByteArray uninitializedNew:fileBytesPerRow.

        1 to:height do:[:row |
            (aStream nextBytes:fileBytesPerRow into:buff) ~~ fileBytesPerRow ifTrue:[
                self fileFormatError:'read failed'.
                ^ false
            ].
            data replaceFrom:idx to:idx+imgBytesPerRow-1 with:buff.
            idx := idx - imgBytesPerRow.
        ].
        ^ true
    ].
    self fileFormatError:('unsupported depth:' , d printString).
    ^ false

    "Created: / 17.9.1995 / 18:48:11 / claus"
    "Modified: / 3.2.1998 / 20:21:16 / cg"
! !

!WindowsIconReader methodsFor:'reading'!

fromOS2File:aFilename
    "read an image from an OS/2 BMP file"

    |reader stream|

    stream := self class streamReadingFile:aFilename.
    stream isNil ifTrue:[^ nil].
    reader := (self class new) fromOS2Stream:stream.
    stream close.
    reader notNil ifTrue:[^ reader image].
    ^ nil

    "Modified: 23.4.1996 / 13:09:28 / cg"
!

fromOS2Stream:aStream
    "read an image from an OS/2 BMP stream"

    |header inDepth inBytesPerRow mask bytesPerRow nColors nByte|

    inStream := aStream.
    aStream binary.

    "read the header"

    header := ByteArray uninitializedNew:8r110.
    aStream nextBytes:16 into:header.

    (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"
    ] 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.
        ]
    ].

    self reportDimension.

    "read the colormap; notice: its in BGR order (sigh)"

    nColors := 1 bitShift:inDepth.
    colorMap := self readColorMap:nColors numBytesPerColor:3 from:aStream.

    "read the mask"

    nByte := width * height + 7 // 8.
    mask := ByteArray uninitializedNew:nByte.
    aStream nextBytes:nByte into:mask.

    "what is this ?"

    aStream nextBytes:nByte into:mask.

"/    "read the data bits"
"/
"/    bytesPerRow := width * inDepth + 7 // 8.
"/    data4 := ByteArray uninitializedNew:(height * bytesPerRow).
"/    inDepth == 8 ifTrue:[
"/    ].
"/    aStream nextBytes:(height * bytesPerRow) into:data4.
"/
"/    "stupid: last row first"
"/
"/    tmp := ByteArray new:(height * bytesPerRow).
"/    srcIndex := 1.
"/    dstIndex := (height - 1) * bytesPerRow + 1.
"/    1 to:height do:[:row |
"/        tmp replaceFrom:dstIndex to:(dstIndex + bytesPerRow - 1)
"/                   with:data4 startingAt:srcIndex.
"/        srcIndex := srcIndex + bytesPerRow.
"/        dstIndex := dstIndex - bytesPerRow.
"/    ].
"/    data4 := tmp.
"/
"/    "expand into bytes"
"/
"/    data := ByteArray new:(width * height).
"/    data4 expandPixels:inDepth width:width height:height
"/                  into:data mapping:nil.
"/

    bytesPerRow := width * inDepth + 7 // 8.
    "/ bmp data is always 32bit aligned; if required,
    inBytesPerRow := ((bytesPerRow + 3) // 4) * 4.

    data := ByteArray uninitializedNew:(height * width "bytesPerRow").
    (self loadBMPWidth:width height:height depth:inDepth compression:0 from:aStream into:data) ifFalse:[
        ^ nil
    ].
    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).

    "
     |i f|
     i := Image fromFile:'/LocalLibrary/Images/OS2/dos3.ico'.
     f := i asFormOn:Display.
     v displayOpaqueForm:(f magnifyBy:2@2) x:5 y:5
    "

    "Modified: / 17.9.1995 / 18:49:24 / claus"
    "Modified: / 3.2.1998 / 20:17:13 / cg"
!

fromStream:aStream 
    "figure out which format the stream contains
     (there are various different bmp/ico formats around)
     and read the image."

    |fileSize header|

    inStream := aStream.

    aStream binary.
    fileSize := aStream fileSize.

    fileSize < 16 ifTrue:[
        ^ self fileFormatError:'short file'.
    ].

    header := ByteArray uninitializedNew:4.
    aStream nextBytes:4 into:header.

    (header startsWith:#(66 77)) ifTrue:[     "BM"
        aStream position1Based:1.
"/        'WinIconReader [info]: Win3.x or OS/2 vsn 2 BM format' infoPrintNL.
        ^ self fromWindowsBMPStream:aStream
    ].
    (header startsWith:#(66 65)) ifTrue:[     "BA"
        aStream position1Based:1.
"/        'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].                    
    (header startsWith:#(67 73)) ifTrue:[     "CI"
        'WinIconReader [warning]: OS/2 CI format not supported:' infoPrintCR.
        ^ nil.
        aStream position1Based:1.
"/        'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(73 67)) ifTrue:[     "IC"
        aStream position1Based:1.
"/        'WinIconReader [info]: OS/2 IC format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(80 84)) ifTrue:[     "PT"
        aStream position1Based:1.
"/        'WinIconReader [info]: OS/2 PT format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(16r53 16r5A)) ifTrue:[     "SZ"
        'WinIconReader [warning]: OS/2 SZ format not supported:' infoPrintCR.
        ^ nil.
"/        aStream position1Based:1.
"/        'WinIconReader [info]: OS/2 SZ format' infoPrintNL.
"/        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(0 0 1 0)) ifTrue:[
        aStream position1Based:1.
"/        'WinIconReader [info]: Win3.x ICO format' infoPrintNL.
        ^ self fromWindowsICOStream:aStream
    ].
    ^ self fileFormatError:('format not supported:'
                            , ((header at:1) printStringRadix:16)
                            , ' ' 
                            , ((header at:2) printStringRadix:16)).

    "
     Image fromFile:'/phys/clam//LocalLibrary/Images/OS2_icons/dos.ico'
    "

    "Modified: / 17.9.1995 / 18:59:07 / claus"
    "Modified: / 3.2.1998 / 20:18:14 / cg"
!

fromWindowsBMPFile: aFilename 
    "read an image from a windows BMP file"

    |reader stream|

    stream := self class streamReadingFile:aFilename.
    stream isNil ifTrue:[^ nil].
    reader := (self class new) fromWindowsBMPStream:stream.
    stream close.
    reader notNil ifTrue:[^ reader image].
    ^ nil

    "Modified: 23.4.1996 / 13:09:53 / cg"
!

fromWindowsBMPStream:aStream 
    "read an image from a windows BMP stream"

    | fileSize header iSize inDepth inPlanes compression
      imgSize resH resV numColor numImportantColor
      dataStart t
      bytesPerRow numBytesPerColorInColormap|

    inStream := aStream.
    aStream binary.

    fileSize := aStream fileSize.
    "read the header"

    header := ByteArray uninitializedNew:16r54.
    aStream nextBytes:18 into:header.

    iSize := header at:(16r0E + 1).
    (iSize == 40) ifTrue:[    "header-size"
        "
         its an Windows3.x BMP file
         or OS/2 vsn 2 BMP file
        "
        "/ 'WinIconReader [info]: Win3.x or OS/2 vsn 2 format' infoPrintCR.

        aStream nextBytes:(40-4) into:header startingAt:19.

        width := header wordAt:(16r12 + 1) MSB:false.  "(header at:19) + ((header at:20) * 256).   "
        height := header wordAt:(16r16 + 1) MSB:false. "(header at:23) + ((header at:24) * 256).   "
        inPlanes := header wordAt:(16r1A + 1) MSB:false.
        inDepth := header wordAt:(16r1C + 1) MSB:false.
        compression := header wordAt:(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.

        numColor == 0 ifTrue:[
            "
             some bmp-writers seem to leave this as zero (which is wrong)
            "
            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) ifTrue:[     "core-info header size"
            "
             its an OS/2 (vsn1.2) BMP file
            "
            "/ 'WinIconReader [info]: OS/2 vsn 1.2 format' infoPrintCR.
            aStream nextBytes:(12-4) into:header startingAt:19.

            width := header wordAt:(16r12 + 1) MSB:false.  "(header at:19) + ((header at:20) * 256).   "
            height := header wordAt:(16r14 + 1) MSB:false. "(header at:21) + ((header at:22) * 256).   "
            inPlanes := header wordAt:(16r16 + 1) MSB:false.
            inDepth := header wordAt:(16r18 + 1) MSB:false.
            numColor := 1 bitShift:inDepth.

            numBytesPerColorInColormap := 3.
            compression := 0.
            "/ dataStart := header wordAt:(16r0A + 1) MSB:false.
            dataStart := nil.
        ] ifFalse:[
            ^ self fileFormatError:'unknown format'.
        ].
    ].

    self reportDimension.

    numColor ~~ 0 ifTrue:[
        "read the colormap - notice: its in BGR order (sigh)"

        colorMap := self 
                        readColorMap:numColor 
                        numBytesPerColor:numBytesPerColorInColormap
                        from:aStream.

        numColor > (1 bitShift:inDepth) ifTrue:[
            'funny number of colors in image' infoPrintCR.
            numColor := 1 bitShift:inDepth.
            colorMap := colorMap copyTo:numColor.
        ].
    ].

    "/ check for valid compression

    compression ~~ 0 ifTrue:[
        "/ some compression
        compression == 1 ifTrue:[
            "/ RLE8 - must be depth-8
            inDepth ~~ 8 ifTrue:[
                ^ self fileFormatError:'RLE8 compression only supported with depth8 images'.
            ].
        ].
        compression == 2 ifTrue:[
            "/ RLE4 - must be depth-4
            inDepth ~~ 4 ifTrue:[
                ^ self fileFormatError:'RLE4 compression only supported with depth4 images'.
            ].
        ].
    ].

    inPlanes ~~ 1 ifTrue:[
        ^ self fileFormatError:'only 1 plane images supported'.
    ].

    dataStart notNil ifTrue:[
        aStream position1Based:(dataStart + 1).
    ].

    inDepth == 24 ifTrue:[
        bytesPerRow := width * 3
    ] ifFalse:[
        bytesPerRow := width
    ].
    data := ByteArray uninitializedNew:(height * bytesPerRow).

    "/ read & possibly decompress

    (self loadBMPWidth:width height:height depth:inDepth compression:compression from:aStream into:data) ifFalse:[
        ^ nil
    ].

    inDepth == 24 ifTrue:[
        photometric := #rgb.
        samplesPerPixel := 3.
        bitsPerSample := #(8 8 8).
        "/ stupid must swap red & blue bytes

        1 to:data size by:3 do:[:i |
            t := data at:i.
            data at:i put:(data at:i+2).
            data at:i+2 put:t
        ].
        ^ self
    ].
    inDepth == 1 ifTrue:[
        photometric := #blackIs0.
        samplesPerPixel := 1.
        bitsPerSample := #(1).
        ^ self
    ].
    (inDepth ~~ 8) ifTrue:[
        "/ self halt:'unsupported depth'.
    ].

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).

    "Modified: / 17.9.1995 / 18:48:46 / claus"
    "Modified: / 16.9.1998 / 01:09:08 / cg"
!

fromWindowsICOFile:aFilename 
    "read an image from a windows ICO file"

    |reader stream|

    stream := self class streamReadingFile:aFilename.
    stream isNil ifTrue:[^ nil].
    reader := (self class new) fromWindowsICOStream:stream.
    stream close.
    reader notNil ifTrue:[^ reader image].
    ^ nil

    "
     Image fromFile:'/phys/clam2//LocalLibrary/Images/WIN_icons/ibm.ico'.
    "

    "Modified: 23.4.1996 / 13:10:11 / cg"
!

fromWindowsICOStream:aStream
    "read an image from a windows ICO stream"

    |header inDepth
     srcIndex dstIndex
     rawData tmp bytesPerRow nColor cmapSize|

    inStream := aStream.
    aStream binary.

    "read the header"

    header := ByteArray uninitializedNew:(6 + 16 + 40).
    aStream nextBytes:(6 + 16 + 40) into:header.
    width := header at:(6+1).
    height := header at:(7+1).
    nColor := header at:(8+1).
    "/ reserved := header at:(9+1).
    "/ nPlanes := header wordAt:(10+1).
    "/ nBitsPerPel := header wordAt:(12+1).
    "/ nBytesInResource := header doubleWordAt:(14+1).
    "/ ordinal := header wordAt:(18+1).
    "21, 22               ?"
    "23, ... , 62         ?"

    inDepth := header at:16r25.
    "/ mhmh - some depth4 icons seem to have a 0 in the depth field ...
    inDepth == 0 ifTrue:[
        inDepth := 4
    ].
    (#(4 8) includes:inDepth) ifFalse:[
        "/ only tested for depth 4/8 images.
        ^ self fileFormatError:'only depth 4/8 ico-images supported (depth is ' , inDepth printString , ')'.
"/        self halt:'only depth 4 ico-images supported (depth is ' , inDepth printString , ')'.
    ].
    self reportDimension.

    "read the colormap"
    cmapSize := (1 bitShift:inDepth).

    colorMap := self
                readColorMap:cmapSize
                numBytesPerColor:4
                from:aStream.

    "read the data bits"

    bytesPerRow := width * inDepth + 7 // 8.
    rawData := ByteArray uninitializedNew:(height * bytesPerRow).
    aStream nextBytes:(height * bytesPerRow) into:rawData.

    "read mask"

"
    mask := ByteArray new:(width * height / 8).
    aStream nextBytes:(width * height / 8) into:mask.
"

    "stupid: last row first"

    tmp := ByteArray uninitializedNew:(height * bytesPerRow).
    srcIndex := 1.
    dstIndex := (height - 1) * bytesPerRow + 1.
    1 to:height do:[:row |
        tmp replaceFrom:dstIndex to:(dstIndex + bytesPerRow - 1)
                   with:rawData startingAt:srcIndex.
        srcIndex := srcIndex + bytesPerRow.
        dstIndex := dstIndex - bytesPerRow.
    ].
    rawData := tmp.

    photometric := #palette.
    samplesPerPixel := 1.

    false ifTrue:[
        "expand into bytes"

        data := ByteArray new:(width * height).
        rawData expandPixels:inDepth width:width height:height
                      into:data mapping:nil.
        bitsPerSample := #(8).
    ] ifFalse:[
        data := rawData.
        bitsPerSample := (Array with:inDepth).
    ].

    "
     WindowsIconReader new fromWindowsICOFile:'/phys/clam2//LocalLibrary/Images/WIN_icons/ibm.ico'.
    "

    "Modified: / 18.5.1999 / 15:40:00 / cg"
! !

!WindowsIconReader methodsFor:'reading-private'!

readColorMap:nColors numBytesPerColor:nRawBytesPerColor from:aStream
    "read the colormap; notice: its in BGR order (sigh)."

    |rawMap rMap gMap bMap 
     srcIndex  "{ Class: SmallInteger }"
     skipDelta "{ Class: SmallInteger }"|

    rawMap := ByteArray uninitializedNew:(nColors*nRawBytesPerColor).
    aStream nextBytes:(nColors*nRawBytesPerColor) into:rawMap.

    rMap := ByteArray new:nColors.
    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.
    ].

    ^ MappedPalette 
        redVector:rMap 
        greenVector:gMap 
        blueVector:bMap.
! !

!WindowsIconReader methodsFor:'writing'!

save:image onFile:aFileName
    "save image as BMP file on aFileName.
     Only depth 1,4,8 and 24 images can be represented in this format."

    aFileName asFilename suffix asLowercase = 'ico' ifTrue:[
"/        (image depth == 4
"/        and:[image width == 32
"/        and:[image height == 32]]) ifTrue:[
            ^ self saveICO:image onFile:aFileName.
"/        ]
    ].
    self saveBMP:image onFile:aFileName.

    "Modified: 17.10.1997 / 20:16:53 / cg"
!

saveBMP:image onFile:fileName 
    "save image as BMP file on aFileName.
     Only depth 1,4,8 and 24 images can be represented in this format."

    |depth bhSize biSize biClrUsed biSizeImage bfOffBits rowBytes imgBytesPerRow data srcIndex row t|

    depth := image depth.
    width := image width.
    height := image height.

    (#(1 4 8 24) includes:depth) ifFalse:[
        ^ Image cannotRepresentImageSignal 
            raiseWith:image
            errorString:('BMP format only supports depths 1,4,8 and 24').
    ].
    image mask notNil ifTrue:[
        Image informationLostQuerySignal
            raiseWith:image
            errorString:('BMP format does not support an imageMask').
    ].

    bhSize := 14.  "# bytes in file header"
    biSize := 40.  "info header size in bytes" 
    biClrUsed := (depth >= 24) ifTrue:[0] ifFalse:[1 bitShift: depth].  "No. color table entries"
    bfOffBits := biSize + bhSize + (4*biClrUsed).
    "/ bmp aligns rows on a longword boundary
    rowBytes := ((depth min:24) * width + 31 // 32) * 4.
    biSizeImage := height * rowBytes.

    outStream := fileName asFilename writeStream.
    outStream binary.
    byteOrder := #lsb.

    "Write the file header"
    self writeShort:19778.  "bfType = BM" 
    self writeLong:(bfOffBits + biSizeImage).  "Entire file size in bytes"
    self writeLong:0.  "bfReserved" 
    self writeLong:bfOffBits.  "Offset of bitmap data from start of hdr (and file)"

    "Write the bitmap info header"
    outStream position1Based: bhSize+1.
    self writeLong:biSize.  "info header size in bytes" 
    self writeLong:width.  "biWidth" 
    self writeLong:height.  "biHeight" 
    self writeShort:1.  "biPlanes" 
    self writeShort:(depth min:24).  "biBitCount" 
    self writeLong:0.  "biCompression" 
    self writeLong:biSizeImage.  "size of image section in bytes"
    self writeLong:2800.  "biXPelsPerMeter" 
    self writeLong:2800.  "biYPelsPerMeter" 
    self writeLong:biClrUsed.
    self writeLong:0.  "biClrImportant" 
    1 to:biClrUsed do:[:i |  "Color map"
        |clr r g b|

        clr := image colorFromValue:i-1.
        clr isNil ifTrue:[
            r := g := b := 0.
        ] ifFalse:[
            r := clr redByte.
            g := clr greenByte.
            b := clr blueByte.
        ].

        "/ put B,G,R
        outStream nextPut:b.
        outStream nextPut:g.
        outStream nextPut:r.
        outStream nextPut:0.
    ].

    imgBytesPerRow := image bytesPerRow.
    data := image data.


    "/ sorry, must extract rows individually
    "/ (even if alignment is correct),
    "/ since BMP saves rows bottom-to-top

    row := ByteArray new:rowBytes.

    srcIndex := 1 + (height * imgBytesPerRow).
    1 to:height do:[:i |
        srcIndex := srcIndex - imgBytesPerRow.
        row replaceFrom:1 to:imgBytesPerRow with:data startingAt:srcIndex.
        depth >= 24 ifTrue:[
            "/ stupid must swap red & blue bytes

            1 to:row size by:3 do:[:i |
                t := row at:i.
                row at:i put:(row at:i+2).
                row at:i+2 put:t
            ].
        ].
        outStream nextPutAll:row.
    ].

    outStream close.

    "
     |i|

     i := Image fromFile:'bitmaps/SBrowser.xbm'.
     WindowsIconReader save:i onFile:'test.bmp'.
    "
    "
     |i|

     i := Image fromFile:'bitmaps/gifImages/garfield.gif'.
     WindowsIconReader save:i onFile:'test.bmp'.
    "

    "Modified: 21.10.1997 / 05:02:02 / cg"
!

saveICO:image onFile:fileName 
    "save image as ICO file on aFileName.
     Only depth 4 images of size 32x32 can be represented in this format."

    |depth biSizeImage rowBytes imgBytesPerRow data srcIndex row|

    depth := image depth.
    width := image width.
    height := image height.

    depth ~~ 4 ifTrue:[
        ^ Image cannotRepresentImageSignal 
            raiseWith:image
            errorString:('ICO format only supports depths 4').
    ].
    (width ~~ 32 or:[height ~~ 32]) ifTrue:[
        ^ Image cannotRepresentImageSignal 
            raiseWith:image
            errorString:('ICO format (currently) only supports 32x32 bitmaps').
    ].

    "/ align rows on a longword boundary
    rowBytes := (depth * width + 31 // 32) * 4.
    biSizeImage := height * rowBytes.

    outStream := fileName asFilename writeStream.
    outStream binary.
    byteOrder := #lsb.

    "Write the file header"
    outStream nextPutAll:#[0 0 1 0].    "/ ICO magic
    self writeShort:1.             "/ # of images in file
    outStream nextPut:image width.      "/
    outStream nextPut:image height.     "/
    outStream nextPut:(1 bitShift:image depth). "/ # of colors
    outStream nextPutAll:#[0 0 0 0 0 ]. "/ reserved
    self writeLong:16rE802.              "/ size pixels
    self writeLong:16r26.                "/ offset in file

    "/ 40 bytes - unknown format
    outStream nextPutAll:(ByteArray new:40).

    "/ 16-entry RGB map

    1 to:16 do:[:i |  "Color map"
        |clr r g b|

        clr := image colorFromValue:i-1.
        clr isNil ifTrue:[
            r := g := b := 0.
        ] ifFalse:[
            r := clr redByte.
            g := clr greenByte.
            b := clr blueByte.
        ].

        "/ put B,G,R
        outStream nextPut:b.
        outStream nextPut:g.
        outStream nextPut:r.
        outStream nextPut:0.
    ].

    imgBytesPerRow := image bytesPerRow.
    data := image data.


    "/ sorry, must extract rows individually
    "/ (even if alignment is correct),
    "/ since ICO saves rows bottom-to-top

    row := ByteArray new:rowBytes.

    srcIndex := 1 + (height * imgBytesPerRow).
    1 to:height do:[:i |
        srcIndex := srcIndex - imgBytesPerRow.
        row replaceFrom:1 to:imgBytesPerRow with:data startingAt:srcIndex.
        outStream nextPutAll:row.
    ].

    "/ the mask ...
    image mask isNil ifTrue:[
        outStream next:128 put:16rFF
    ] ifFalse:[
        imgBytesPerRow := image mask bytesPerRow.
        data := image mask data.
        row := ByteArray new:4.

        srcIndex := 1 + (height * imgBytesPerRow).
        1 to:height do:[:i |
            srcIndex := srcIndex - imgBytesPerRow.
            row replaceFrom:1 to:imgBytesPerRow with:data startingAt:srcIndex.
            outStream nextPutAll:row.
        ].
    ].

    outStream close.

    "
     |i|

     i := Image fromFile:'bitmaps/xpmBitmaps/SmalltalkX_clr.xpm'.
     i := Depth4Image fromImage:i.
     i := i magnifiedTo:32@32.
     WindowsIconReader new saveICO:i onFile:'test.ico'.
    "

    "Modified: 21.10.1997 / 05:02:02 / cg"
! !

!WindowsIconReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/WindowsIconReader.st,v 1.57 2003-11-19 15:25:15 cg Exp $'
! !

WindowsIconReader initialize!