WindowsIconReader.st
author tz
Sat, 07 Feb 1998 16:57:39 +0100
changeset 834 ac1655bd31bb
parent 819 e358c08e45ea
child 898 cdf6cc132b53
permissions -rw-r--r--
class category changed

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

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

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

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

!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 from file'!

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

    |reader stream|

    stream := self streamReadingFile:aFilename.
    stream isNil ifTrue:[^ nil].
    reader := (self 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
      rawMap rMap gMap bMap srcIndex dstIndex inBytesPerRow
      data4 mask tmp 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.
        ]
    ].

    "read the colormap"

    nColors := 1 bitShift:inDepth.

    rawMap := ByteArray uninitializedNew:(nColors*3).
    aStream nextBytes:(nColors*3) into:rawMap.
    rMap := Array new:nColors.
    gMap := Array new:nColors.
    bMap := Array new:nColors.
    srcIndex := 1.
    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.
    ].

    "read 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).
    colorMap := Colormap redVector:rMap greenVector:gMap blueVector:bMap.

    "
     |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 position:1.
"/        'WinIconReader [info]: Win3.x or OS/2 vsn 2 BM format' infoPrintNL.
        ^ self fromWindowsBMPStream:aStream
    ].
    (header startsWith:#(66 65)) ifTrue:[     "BA"
        aStream position: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:' infoPrintNL.
        ^ nil.
        aStream position:1.
"/        'WinIconReader [info]: OS/2 vsn 2 BA format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(73 67)) ifTrue:[     "IC"
        aStream position:1.
"/        'WinIconReader [info]: OS/2 IC format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(80 84)) ifTrue:[     "PT"
        aStream position: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:' infoPrintNL.
        ^ nil.
        aStream position:1.
        'WinIconReader [info]: OS/2 SZ format' infoPrintNL.
        ^ self fromOS2Stream:aStream
    ].
    (header startsWith:#(0 0 1 0)) ifTrue:[
        aStream position: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 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
      rawMap rMap gMap bMap srcIndex
      bytesPerRow fourBytesPerColorInfo|

    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' infoPrintNL.

        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 infoPrintNL
            ]
        ].

        numColor ~~ 0 ifTrue:[
            rawMap := ByteArray uninitializedNew:(numColor * 4).
            aStream nextBytes:(numColor * 4) into:rawMap.
            fourBytesPerColorInfo := true.
        ].
        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' infoPrintNL.
            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.
            rawMap := ByteArray uninitializedNew:(numColor * 3).
            aStream nextBytes:(numColor * 3) into:rawMap.
            fourBytesPerColorInfo := false.
            compression := 0.
            "/ dataStart := header wordAt:(16r0A + 1) MSB:false.
            dataStart := nil.
        ] ifFalse:[
            ^ self fileFormatError:'unknown format'.
        ].
    ].

    numColor ~~ 0 ifTrue:[
        "read the colormap"

        rMap := ByteArray new:numColor.
        gMap := ByteArray new:numColor.
        bMap := ByteArray new:numColor.
        srcIndex := 1.
        1 to:numColor 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.
            fourBytesPerColorInfo ifTrue:[
                srcIndex := srcIndex + 1.
            ]
        ].
    ].

    "/ 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 position:(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).
        ^ self
    ].

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).
    colorMap := Colormap redVector:rMap greenVector:gMap blueVector:bMap.

    "Modified: / 17.9.1995 / 18:48:46 / claus"
    "Modified: / 3.2.1998 / 20:19:41 / cg"
!

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

    |reader stream|

    stream := self class streamReadingFile:aFilename.
    stream isNil ifTrue:[^ nil].
    reader := (self 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
      rawMap rMap gMap bMap srcIndex dstIndex
      data4 mask tmp bytesPerRow nColor|

    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.

    "read the colormap"

    rawMap := ByteArray uninitializedNew:(16*4).
    aStream nextBytes:(16*4) into:rawMap.
    rMap := ByteArray new:16.
    gMap := ByteArray new:16.
    bMap := ByteArray new:16.
    srcIndex := 1.
    1 to:16 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 + 1.
    ].

    "read the data bits"

    inDepth == 0 ifTrue:[
        inDepth := 4.
    ].
    bytesPerRow := width * inDepth + 7 // 8.
    data4 := ByteArray uninitializedNew:(height * bytesPerRow).
    aStream nextBytes:(height * bytesPerRow) into:data4.

    "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:data4 startingAt:srcIndex.
        srcIndex := srcIndex + bytesPerRow.
        dstIndex := dstIndex - bytesPerRow.
    ].
    data4 := tmp.


    photometric := #palette.
    samplesPerPixel := 1.

    colorMap := Colormap redVector:rMap greenVector:gMap blueVector:bMap.

    false ifTrue:[
    "expand into bytes"

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

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

    "Modified: 24.4.1997 / 22:03:48 / cg"
! !

!WindowsIconReader methodsFor:'writing to file'!

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

    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|

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

!WindowsIconReader class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/WindowsIconReader.st,v 1.38 1998-02-03 19:22:21 cg Exp $'
! !
WindowsIconReader initialize!