WindowsIconReader.st
author Claus Gittinger <cg@exept.de>
Sun, 29 Oct 1995 20:36:22 +0100
changeset 109 9e1383121df4
parent 104 aee902af74e0
child 114 e577a2f332d0
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-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.
"
!

version
"
$Header: /cvs/stx/stx/libview2/WindowsIconReader.st,v 1.18 1995-09-18 10:35:20 claus Exp $
"
!

documentation
"
    this class provides methods for loading Windows and OS2 icon files.
    Image writing is not supported.
"
! !

!WindowsIconReader class methodsFor:'initialization'!

initialize
    Image fileFormats at:'.bmp'  put:self.
    Image fileFormats at:'.ico'  put:self.
! !

!WindowsIconReader class methodsFor:'testing'!

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 size > 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
    d == 8 ifTrue:[
	(self class loadBMP8Width:w height:h compression:c from:aStream into:data) ifFalse:[
	    'BMP: read/decompression failed' errorPrintNL.
	    ^ false
	]
    ] ifFalse:[
	d == 4 ifTrue:[
	    (self class loadBMP4to8Width:w height:h compression:c from:aStream into:data) ifFalse:[
		'BMP: read/decompression failed' errorPrintNL.
		^ false
	    ]
	] ifFalse:[
	    d == 2 ifTrue:[
		(self class loadBMP2to8Width:w height:h from:aStream into:data) ifFalse:[
		    'BMP: read failed' errorPrintNL.
		    ^ false
		]
	    ] ifFalse:[
		d == 1 ifTrue:[
		    (self class loadBMP1to8Width:w height:h from:aStream into:data) ifFalse:[
			'BMP: read failed' errorPrintNL.
			^ false
		    ]
		] ifFalse:[
		    'BMP: unsupported depth:' errorPrint. d errorPrintNL.
		    ^ false
		]
	    ]
	]
    ].
    ^ true

    "Created: 17.9.1995 / 18:48:11 / claus"
! !

!WindowsIconReader methodsFor:'reading from file'!

fromOS2File: aFilename 
    |reader stream|

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

fromWindowsBMPFile: aFilename 
    |reader stream|

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

fromWindowsICOFile: aFilename 
    |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'.
    "
!

fromWindowsICOStream:aStream
    | 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).
    "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).
    aStream 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).
    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.

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

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

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

    inStream := aStream.
    aStream binary.

    fileSize := aStream size.
    "read the header"

    header := ByteArray uninitializedNew:16r54.
    aStream 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.

	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)
	    "
	    numColor := 1 bitShift:inDepth.
	    'BMP: missing nColor in header - assume ' errorPrint. numColor errorPrintNL
	].
	rawMap := ByteArray uninitializedNew:(numColor * 4).
	aStream nextBytes:(numColor * 4) into:rawMap.
	fourBytesPerColorInfo := true.
	dataStart := header wordAt:(16r0A + 1) MSB:false
    ] 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.
	    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
	] ifFalse:[
	    'BMP: unknown format' errorPrintNL.
	    ^ 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.
"/        ^ nil
"/    ].
"/    inPlanes ~~ 1 ifTrue:[
"/        'BMP only 1 plane images supported' errorPrintNL.
"/        ^ nil
"/    ].
"/
"/    "read the data bits"
"/
"/    bytesPerRow := width * inDepth + 7 // 8.
"/    data4 := ByteArray uninitializedNew:(height * bytesPerRow).
"/
"/    aStream position:(dataStart + 1).
"/    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.
"/    data := ByteArray new:(width * height).
"/    data4 expandPixels:inDepth width:width height:height
"/                  into:data mapping:nil.
"/

    compression ~~ 0 ifTrue:[
	"/ some compression
	compression == 1 ifTrue:[
	    "/ RLE8 - must be depth-8
	    inDepth == 8 ifFalse:[
		'BMP: RLE8 compression only allowed with depth8 images' errorPrintNL.
		^ nil
	    ].
	].
	compression == 2 ifTrue:[
	    "/ RLE4 - must be depth-4
	    inDepth == 4 ifFalse:[
		'BMP: RLE4 compression only allowed with depth4 images' errorPrintNL.
		^ nil
	    ].
	].
    ].

    inPlanes ~~ 1 ifTrue:[
	'BMP: only 1 plane images supported' errorPrintNL.
	^ nil
    ].

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

    data := ByteArray uninitializedNew:(height * width "bytesPerRow").
    (self loadBMPWidth:width height:height depth:inDepth compression:compression from:aStream into:data) ifFalse:[
	^ nil
    ].
    "expand into bytes"

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

    "Modified: 17.9.1995 / 18:48:46 / claus"
!

fromStream:aStream 
    | fileSize header |

    inStream := aStream.

    aStream binary.
    fileSize := aStream size.

    fileSize < 16 ifTrue:[
	'WINREADER: short file' errorPrintNL.
	^ nil
    ].

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

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

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

    "Modified: 17.9.1995 / 18:59:07 / claus"
!

fromOS2Stream:aStream
    | 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 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:[
	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"
! !