WinIconRdr.st
author claus
Fri, 05 Aug 1994 03:16:30 +0200
changeset 24 6bc436eb4c4a
parent 21 66b31c91177f
child 28 8daff0234d2e
permissions -rw-r--r--
*** empty log message ***

"
 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-Support'
!

WindowsIconReader comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libview2/Attic/WinIconRdr.st,v 1.7 1994-08-05 01:16:24 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libview2/Attic/WinIconRdr.st,v 1.7 1994-08-05 01:16:24 claus Exp $
"
!

documentation
"
    this class provides methods for loading Windows and OS2 icon files..
"
! !

!WindowsIconReader methodsFor:'reading from file'!

fromOS2File: aFilename 
    inStream := self class streamReadingFile:aFilename.
    inStream isNil ifTrue:[^ nil].
    inStream binary.
    ^ self fromOS2Stream.
!

fromWindowsBMPFile: aFilename 
    inStream := self class streamReadingFile:aFilename.
    inStream isNil ifTrue:[^ nil].
    inStream binary.
    ^ self fromWindowsBMPStream.
!

fromWindowsICOFile: aFilename 
    inStream := self class streamReadingFile:aFilename.
    inStream isNil ifTrue:[^ nil].
    ^ self fromWindowsICOStream.

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

fromWindowsICOStream
    | header inDepth
      rawMap rMap gMap bMap srcIndex dstIndex
      data4 mask tmp bytesPerRow nColor|

    inStream binary.

    "read the header"

    header := ByteArray uninitializedNew:(6 + 16 + 40).
    inStream nextBytes:(6 + 16 + 40) into:header.
    width := header at:(6+1).
    height := header at:(7+1).
    nColor := header at:(8+1).
    "10, 11, 12, 13, 14 ? (reserve)"
    "15, 16, 17, 18       pixel array size"
    "19, 20, 21, 22       offset        "
    "23, ... , 62         ?"

    inDepth := header at:16r25.

    "read the colormap"

    rawMap := ByteArray uninitializedNew:(16*4).
    inStream nextBytes:(16*4) into:rawMap.
    rMap := Array new:16.
    gMap := Array new:16.
    bMap := Array 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"

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

    "read mask"

"
    mask := ByteArray new:(width * height / 8).
    inStream 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.

    "expand into bytes"

    data := ByteArray new:(width * height).
    data4 expandPixels:inDepth width:width height:height
                  into:data mapping:nil.

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).
    colorMap := Array with:rMap with:gMap with:bMap.
    inStream close.

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

fromWindowsBMPStream 
    | fileSize header inDepth inPlanes compression
      imgSize resH resV numColor numImportantColor
      dataStart
      rawMap rMap gMap bMap srcIndex dstIndex
      data4 mask tmp bytesPerRow fourBytesPerColorInfo|

    fileSize := inStream size.
    "read the header"

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

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

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

        width := header wordAt:(16r12 + 1).  "(header at:19) + ((header at:20) * 256).   "
        height := header wordAt:(16r16 + 1). "(header at:23) + ((header at:24) * 256).   "
        inPlanes := header wordAt:(16r1A + 1).
        inDepth := header wordAt:(16r1C + 1).
        compression := header wordAt:(16r1E + 1).
        imgSize := header doubleWordAt:(16r22 + 1).
        resH := header doubleWordAt:(16r26 + 1).
        resV := header doubleWordAt:(16r2A + 1).
        numColor := header doubleWordAt:(16r2E + 1).
        numImportantColor := header doubleWordAt:(16r32 + 1).

        numColor == 0 ifTrue:[
            "
             some bmp-writers seem to leave this as zero (which is wrong)
            "
            numColor := 1 bitShift:inDepth.
            'BMP: missing nColor in header - assume ' errorPrint. numColor errorPrintNL
        ].
        rawMap := ByteArray uninitializedNew:(numColor * 4).
        inStream nextBytes:(numColor * 4) into:rawMap.
        fourBytesPerColorInfo := true.
        dataStart := header wordAt:(16r0A + 1)
    ] ifFalse:[
        ((header at:(16r0E + 1)) == 12) ifTrue:[     "core-info header size"
            "
             its an OS/2 (vsn1.2) BMP file
            "
           'BMP: OS/2 vsn 1.2 format' errorPrintNL.
            inStream nextBytes:(12-4) into:header startingAt:19.

            width := header wordAt:(16r12 + 1).  "(header at:19) + ((header at:20) * 256).   "
            height := header wordAt:(16r14 + 1). "(header at:21) + ((header at:22) * 256).   "
            inPlanes := header wordAt:(16r16 + 1).
            inDepth := header wordAt:(16r18 + 1).
            numColor := 1 bitShift:inDepth.
            rawMap := ByteArray uninitializedNew:(numColor * 3).
            inStream nextBytes:(numColor * 3) into:rawMap.
            fourBytesPerColorInfo := false.
            compression := 0.
            dataStart := header wordAt:(16r0A + 1)
        ] ifFalse:[
            'BMP: unknown format' errorPrintNL.
            inStream close.
            ^ nil
        ].
    ].

    "read the colormap"

    rMap := Array new:numColor.
    gMap := Array new:numColor.
    bMap := Array 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.
        ]
    ].

    "
     currently only normal (non-rle) bitmaps
     supported
    "
    compression ~~ 0 ifTrue:[
        'BMP compression type ' errorPrint. compression errorPrint.
        'not supported' errorPrintNL.
        inStream close.
        ^ nil
    ].
    inPlanes ~~ 1 ifTrue:[
        'BMP only 1 plane images supported' errorPrintNL.
        inStream close.
        ^ nil
    ].

    "read the data bits"

    bytesPerRow := width * inDepth + 7 // 8.
    data4 := ByteArray uninitializedNew:(height * bytesPerRow).

    inStream position:(dataStart + 1).
    inStream nextBytes:(height * bytesPerRow) into:data4.

    "read mask"

"
    mask := ByteArray new:(width * height / 8).
    inStream 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.

    "expand into bytes"

    data := ByteArray new:(width * height).
    data4 expandPixels:inDepth width:width height:height
                  into:data mapping:nil.

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).
    colorMap := Array with:rMap with:gMap with:bMap.
    inStream close.
!

fromFile: aFilename 
    | fileSize header |

    inStream := self class streamReadingFile:aFilename.
    inStream isNil ifTrue:[^ nil].

    inStream binary.
    fileSize := inStream size.

    fileSize < 16 ifTrue:[
        inStream close.
        self error:'WINREADER: short file'.
        ^ nil
    ].

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

    (header startsWith:#(66 77)) ifTrue:[     "BM"
        inStream position:1.
        'WINREADER: Win3.x or OS/2 vsn 2 BM format' errorPrintNL.
        ^ self fromWindowsBMPStream
    ].
    (header startsWith:#(66 65)) ifTrue:[     "BA"
        inStream position:1.
        'WINREADER: OS/2 vsn 2 BA format' errorPrintNL.
        ^ self fromOS2Stream
    ].
    (header startsWith:#(73 67)) ifTrue:[     "IC"
        inStream position:1.
        'WINREADER: OS/2 IC format' errorPrintNL.
        ^ self fromOS2Stream
    ].
    (header startsWith:#(80 84)) ifTrue:[     "PT"
        inStream position:1.
        'WINREADER: OS/2 PT format' errorPrintNL.
        ^ self fromOS2Stream
    ].
    (header startsWith:#(0 0 1 0)) ifTrue:[
        inStream position:1.
        'WINREADER: Win3.x ICO format' errorPrintNL.
        ^ self fromWindowsICOStream
    ].
    self error:'WINREADER: format not supported'.
    inStream close.
    ^ nil

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

fromOS2Stream 
    | header inDepth
      rawMap rMap gMap bMap srcIndex dstIndex
      data4 mask tmp bytesPerRow nColors nByte|

    inStream binary.

    "read the header"

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

    (header startsWith:#(73 67)) ifTrue:[
        "IC format"
        inStream nextBytes:10 into:header startingAt:17.
        width := header at:7.
        height := header at:9.
        inDepth := 2 "header at:11". "where is it"
    ] ifFalse:[
        inStream 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).
    inStream 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.
    inStream nextBytes:nByte into:mask.

    "what is this"

    inStream nextBytes:nByte into:mask.

    "read the data bits"

    bytesPerRow := width * inDepth + 7 // 8.
    data4 := ByteArray uninitializedNew:(height * bytesPerRow).
    inStream 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.

    photometric := #palette.
    samplesPerPixel := 1.
    bitsPerSample := #(8).
    colorMap := Array with:rMap with:gMap with:bMap.
    inStream close.

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