SunRasterReader.st
author claus
Mon, 10 Oct 1994 03:34:22 +0100
changeset 28 8daff0234d2e
parent 23 11c422f6d825
child 32 6bdcb6da4d4f
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:#SunRasterReader
	 instanceVariableNames:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Graphics-Support'
!

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

$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.8 1994-10-10 02:33:19 claus Exp $
'!

!SunRasterReader 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/SunRasterReader.st,v 1.8 1994-10-10 02:33:19 claus Exp $
"
!

documentation
"
    this class provides methods for loading Sun Raster file images
"
! !

!SunRasterReader class methodsFor:'initialization'!

initialize
    Image fileFormats at:'.icon'  put:self.
! !

!SunRasterReader class methodsFor:'testing'!

isValidImageFile:aFileName
    "return true, if aFileName contains a sunraster image"

    |inStream nr|

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

    "try sun raster"
    inStream binary.
    ((inStream nextWord == 16r59A6) 
    and:[inStream nextWord == 16r6A95]) ifTrue: [
	inStream close.
	^ true
    ].

    "try sun bitmap image format"
    inStream text.
    inStream reset.
    (inStream skipThroughAll: 'idth') isNil ifTrue: [
	inStream close.
	^ false
    ].
    inStream next; skipSeparators.
    nr := Integer readFrom: inStream.
    (nr isNil or:[nr <= 0]) ifTrue: [
	inStream close.
	^ false
    ].

    (inStream skipThroughAll: 'eight') isNil ifTrue: [
	inStream close.
	^ false
    ].
    inStream next; skipSeparators.
    nr := Integer readFrom: inStream.
    (nr isNil or:[nr <= 0]) ifTrue: [
	inStream close.
	^ false
    ].

    inStream close.
    ^ true
! !

!SunRasterReader methodsFor:'reading from file'!

fromFile: aFilename 
    | rasterType mapType mapBytes imageWords form depth 
      rMap gMap bMap mapLen
      bits a b c index|

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

    inStream binary.

    ((inStream nextWord == 16r59A6) 
    and:[inStream nextWord == 16r6A95]) ifFalse: [
	inStream close.
	^ self fromSunIconFile:aFilename
    ].

    width := inStream nextLong.
    height := inStream nextLong.

    depth := inStream nextLong.
    inStream nextLong.   "Ignore the image length since I can't rely on it anyway."
    rasterType _ inStream nextLong.
    mapType := inStream nextLong.  "Ignore the raster maptype."
    mapBytes := inStream nextLong.  

    depth = 8 ifTrue: [
	mapLen := (mapBytes // 3).
	rMap := ByteArray uninitializedNew:mapLen.
	gMap := ByteArray uninitializedNew:mapLen.
	bMap := ByteArray uninitializedNew:mapLen.
	inStream nextBytes:mapLen into:rMap.
	inStream nextBytes:mapLen into:gMap.
	inStream nextBytes:mapLen into:bMap.

	data := ByteArray uninitializedNew:(width * height).
	inStream nextBytes:(width * height) into:data.

	photometric := #palette.
	samplesPerPixel := 1.
	bitsPerSample := #(8).
	colorMap := Array with:rMap with:gMap with:bMap.
	inStream close.
	^ self
    ].
    depth ~~ 1 ifTrue: [
	inStream close.
	self error: 'Raster file is not monochrome'
    ].

    form := nil.

    inStream skip: mapBytes.  "Skip the color map."
    imageWords _ (width / 16) ceiling * height.
    data := ByteArray uninitializedNew:(imageWords * 2).

    (rasterType between: 0 and: 2) ifFalse: [
	inStream close.
	self error: 'Unknown raster file rasterType'
    ].

    (rasterType = 2)  ifFalse: [
	"no compression of bytes"
	inStream nextBytes:(imageWords * 2) into:data
    ] ifTrue: [ 
	"run length compression of bytes"

	bits _ ByteArray uninitializedNew: imageWords * 2.
	index := 1.
	a _ inStream next.
	[a notNil] whileTrue: [
	    (a = 128) ifFalse: [
		bits at:index put: a.
		index := index + 1
	    ] ifTrue: [
		b _ inStream next.
		b = 0 ifTrue: [
		    bits at:index put:128 .
		    index := index + 1
		] ifFalse: [
		    c := inStream next.
		    1 to:(b+1) do:[:i |
			bits at:index put:c.
			index := index + 1
		    ]
		]
	    ].
	    a _ inStream next
	].
	1 to: imageWords do: [:i | form bitsWordAt: i put: (bits wordAt: i)]
    ].
    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).
    inStream close

    "Image fromFile:'../fileIn/bitmaps/founders.im8'"
!

fromSunIconFile: aFilename 
    |index word 
     w "{ Class: SmallInteger }"
     h "{ Class: SmallInteger }"|

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

    (inStream skipThroughAll:'idth') isNil ifTrue: [
	'Not a Sun Raster/Icon File' errorPrintNewline.
	inStream close.
	^nil
    ].
    inStream next; skipSeparators. "skip $="
    width := Integer readFrom: inStream.
    (width isNil or:[width <= 0]) ifTrue: [
	'format error (expected number)' errorPrintNewline.
	inStream close. 
	^ nil
    ].
    w := width.

    (inStream skipThroughAll:'eight') isNil ifTrue: [
	'format error (expected height)' errorPrintNewline.
	inStream close. 
	^ nil
    ].
    inStream next; skipSeparators. "skip $="
    height := Integer readFrom: inStream.
    (height isNil or:[height <= 0]) ifTrue: [
	'format error (expected number)' errorPrintNewline.
	inStream close. 
	^nil
    ].
    h := height.

    data := ByteArray uninitializedNew:((width + 7 // 8) * height).
    photometric := #whiteIs0.
    samplesPerPixel := 1.
    bitsPerSample := #(1).

    index := 0.
    1 to:h do: [:row |
	1 to: (w + 15 // 16) do: [:col |
	    "rows are rounded up to next multiple of 16 bits"
	    (inStream skipThroughAll:'0x') isNil ifTrue: [^ nil]. 
	    word := Integer readFrom:inStream radix:16.
	    word isNil ifTrue:[
		'format error' errorPrintNewline.
		inStream close.
		^ nil
	    ].
	    data at: (index _ index + 1) put: (word bitShift:-8).
	    data at: (index _ index + 1) put: (word bitAnd:16rFF).
	]
    ].
    inStream close.
! !