SunRasterReader.st
changeset 28 8daff0234d2e
parent 23 11c422f6d825
child 32 6bdcb6da4d4f
--- a/SunRasterReader.st	Mon Oct 10 03:32:51 1994 +0100
+++ b/SunRasterReader.st	Mon Oct 10 03:34:22 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -11,17 +11,17 @@
 "
 
 ImageReader subclass:#SunRasterReader
-         instanceVariableNames:''
-         classVariableNames:''
-         poolDictionaries:''
-         category:'Graphics-Support'
+	 instanceVariableNames:''
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Graphics-Support'
 !
 
 SunRasterReader comment:'
 COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.7 1994-08-05 01:15:11 claus Exp $
+$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.8 1994-10-10 02:33:19 claus Exp $
 '!
 
 !SunRasterReader class methodsFor:'documentation'!
@@ -29,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -42,7 +42,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.7 1994-08-05 01:15:11 claus Exp $
+$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.8 1994-10-10 02:33:19 claus Exp $
 "
 !
 
@@ -52,6 +52,12 @@
 "
 ! !
 
+!SunRasterReader class methodsFor:'initialization'!
+
+initialize
+    Image fileFormats at:'.icon'  put:self.
+! !
+
 !SunRasterReader class methodsFor:'testing'!
 
 isValidImageFile:aFileName
@@ -66,33 +72,33 @@
     inStream binary.
     ((inStream nextWord == 16r59A6) 
     and:[inStream nextWord == 16r6A95]) ifTrue: [
-        inStream close.
-        ^ true
+	inStream close.
+	^ true
     ].
 
     "try sun bitmap image format"
     inStream text.
     inStream reset.
     (inStream skipThroughAll: 'idth') isNil ifTrue: [
-        inStream close.
-        ^ false
+	inStream close.
+	^ false
     ].
     inStream next; skipSeparators.
     nr := Integer readFrom: inStream.
     (nr isNil or:[nr <= 0]) ifTrue: [
-        inStream close.
-        ^ false
+	inStream close.
+	^ false
     ].
 
     (inStream skipThroughAll: 'eight') isNil ifTrue: [
-        inStream close.
-        ^ false
+	inStream close.
+	^ false
     ].
     inStream next; skipSeparators.
     nr := Integer readFrom: inStream.
     (nr isNil or:[nr <= 0]) ifTrue: [
-        inStream close.
-        ^ false
+	inStream close.
+	^ false
     ].
 
     inStream close.
@@ -113,8 +119,8 @@
 
     ((inStream nextWord == 16r59A6) 
     and:[inStream nextWord == 16r6A95]) ifFalse: [
-        inStream close.
-        ^ self fromSunIconFile:aFilename
+	inStream close.
+	^ self fromSunIconFile:aFilename
     ].
 
     width := inStream nextLong.
@@ -127,27 +133,27 @@
     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.
+	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.
+	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
+	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'
+	inStream close.
+	self error: 'Raster file is not monochrome'
     ].
 
     form := nil.
@@ -157,39 +163,39 @@
     data := ByteArray uninitializedNew:(imageWords * 2).
 
     (rasterType between: 0 and: 2) ifFalse: [
-        inStream close.
-        self error: 'Unknown raster file rasterType'
+	inStream close.
+	self error: 'Unknown raster file rasterType'
     ].
 
     (rasterType = 2)  ifFalse: [
-        "no compression of bytes"
-        inStream nextBytes:(imageWords * 2) into:data
+	"no compression of bytes"
+	inStream nextBytes:(imageWords * 2) into:data
     ] ifTrue: [ 
-        "run length compression of bytes"
+	"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)]
+	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.
@@ -208,30 +214,30 @@
     inStream isNil ifTrue:[^ nil].
 
     (inStream skipThroughAll:'idth') isNil ifTrue: [
-        'Not a Sun Raster/Icon File' errorPrintNewline.
-        inStream close.
-        ^nil
+	'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
+	'format error (expected number)' errorPrintNewline.
+	inStream close. 
+	^ nil
     ].
     w := width.
 
     (inStream skipThroughAll:'eight') isNil ifTrue: [
-        'format error (expected height)' errorPrintNewline.
-        inStream close. 
-        ^ nil
+	'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
+	'format error (expected number)' errorPrintNewline.
+	inStream close. 
+	^nil
     ].
     h := height.
 
@@ -242,18 +248,18 @@
 
     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).
-        ]
+	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.
 ! !