SunRasterReader.st
changeset 208 bd41881b2a0d
parent 114 e577a2f332d0
child 209 840ddcf12904
--- a/SunRasterReader.st	Tue Apr 23 12:57:34 1996 +0200
+++ b/SunRasterReader.st	Tue Apr 23 12:59:53 1996 +0200
@@ -10,13 +10,11 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 2:18:51 am'!
-
 ImageReader subclass:#SunRasterReader
-	 instanceVariableNames:''
-	 classVariableNames:''
-	 poolDictionaries:''
-	 category:'Graphics-Images support'
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Graphics-Images support'
 !
 
 !SunRasterReader class methodsFor:'documentation'!
@@ -35,20 +33,26 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.16 1995-11-11 16:05:02 cg Exp $'
-!
-
 documentation
 "
-    this class provides methods for loading Sun Raster file images.
+    this class provides methods for loading Sun Raster and
+    Sun Icon file images.
+
     No image writing is implemented.
+
+    [See also:]
+        BlitImageReader FaceReader JPEGReader GIFReader PBMReader PCXReader 
+        ST80FormReader TIFFReader WindowsIconReader 
+        XBMreader XPMReader XWDReader 
 "
 ! !
 
 !SunRasterReader class methodsFor:'initialization'!
 
 initialize
+    "install myself in the Image classes fileFormat table
+     for the `.icon' extension."
+
     Image fileFormats at:'.icon'  put:self.
 ! !
 
@@ -110,6 +114,9 @@
 !SunRasterReader methodsFor:'reading from file'!
 
 fromStream: aStream 
+    "read an image in my format from aStream.
+     Dtermine if its a raster or icon file."
+
     | rasterType mapType mapBytes imageWords form depth 
       rMap gMap bMap mapLen
       bits a b c index pos|
@@ -122,8 +129,8 @@
     ((aStream nextWord == 16r59A6) 
     and:[aStream nextWord == 16r6A95]) ifFalse: [
 "/        'SUNReader: not a SunRaster file' errorPrintNL.
-	aStream position:pos.
-	^ self fromSunIconStream:aStream
+        aStream position:pos.
+        ^ self fromSunIconStream:aStream
     ].
 
     width := aStream nextLong.
@@ -136,26 +143,26 @@
     mapBytes := aStream nextLong.  
 
     depth = 8 ifTrue: [
-	mapLen := (mapBytes // 3).
-	rMap := ByteArray uninitializedNew:mapLen.
-	gMap := ByteArray uninitializedNew:mapLen.
-	bMap := ByteArray uninitializedNew:mapLen.
-	aStream nextBytes:mapLen into:rMap.
-	aStream nextBytes:mapLen into:gMap.
-	aStream nextBytes:mapLen into:bMap.
+        mapLen := (mapBytes // 3).
+        rMap := ByteArray uninitializedNew:mapLen.
+        gMap := ByteArray uninitializedNew:mapLen.
+        bMap := ByteArray uninitializedNew:mapLen.
+        aStream nextBytes:mapLen into:rMap.
+        aStream nextBytes:mapLen into:gMap.
+        aStream nextBytes:mapLen into:bMap.
 
-	data := ByteArray uninitializedNew:(width * height).
-	aStream nextBytes:(width * height) into:data.
+        data := ByteArray uninitializedNew:(width * height).
+        aStream nextBytes:(width * height) into:data.
 
-	photometric := #palette.
-	samplesPerPixel := 1.
-	bitsPerSample := #(8).
-	colorMap := Colormap redVector:rMap greenVector:gMap blueVector:bMap.
-	^ self
+        photometric := #palette.
+        samplesPerPixel := 1.
+        bitsPerSample := #(8).
+        colorMap := Colormap redVector:rMap greenVector:gMap blueVector:bMap.
+        ^ self
     ].
     depth ~~ 1 ifTrue: [
-	'SUNReader: only depth 1 and 8 supported' errorPrintNL.
-	^ nil
+        'SUNReader: only depth 1 and 8 supported' errorPrintNL.
+        ^ nil
     ].
 
     form := nil.
@@ -165,37 +172,37 @@
     data := ByteArray uninitializedNew:(imageWords * 2).
 
     (rasterType between: 0 and: 2) ifFalse: [
-	'SUNReader: Unknown raster file rasterType' errorPrintNL.
-	^ nil
+        'SUNReader: Unknown raster file rasterType' errorPrintNL.
+        ^ nil
     ].
 
     (rasterType = 2)  ifFalse: [
-	"no compression of bytes"
-	aStream nextBytes:(imageWords * 2) into:data
+        "no compression of bytes"
+        aStream nextBytes:(imageWords * 2) into:data
     ] ifTrue: [ 
-	"run length compression of bytes"
+        "run length compression of bytes"
 
-	index := 1.
-	a := aStream next.
-	[a notNil] whileTrue: [
-	    (a = 128) ifFalse: [
-		data at:index put: a.
-		index := index + 1
-	    ] ifTrue: [
-		b := aStream next.
-		b = 0 ifTrue: [
-		    data at:index put:128 .
-		    index := index + 1
-		] ifFalse: [
-		    c := aStream next.
-		    1 to:(b+1) do:[:i |
-			data at:index put:c.
-			index := index + 1
-		    ]
-		]
-	    ].
-	    a := aStream next
-	].
+        index := 1.
+        a := aStream next.
+        [a notNil] whileTrue: [
+            (a = 128) ifFalse: [
+                data at:index put: a.
+                index := index + 1
+            ] ifTrue: [
+                b := aStream next.
+                b = 0 ifTrue: [
+                    data at:index put:128 .
+                    index := index + 1
+                ] ifFalse: [
+                    c := aStream next.
+                    1 to:(b+1) do:[:i |
+                        data at:index put:c.
+                        index := index + 1
+                    ]
+                ]
+            ].
+            a := aStream next
+        ].
     ].
     photometric := #whiteIs0.
     samplesPerPixel := 1.
@@ -207,9 +214,13 @@
      SunRasterReader fromStream:'bitmaps/founders.im8' asFilename readStream
      SunRasterReader fromStream:'bitmaps/bf.im8' asFilename readStream
     "
+
+    "Modified: 23.4.1996 / 12:59:31 / cg"
 !
 
-fromSunIconStream: aStream 
+fromSunIconStream:aStream 
+    "helper: read an image in icon format from aStream"
+
     |index word 
      w "{ Class: SmallInteger }"
      h "{ Class: SmallInteger }"|
@@ -218,26 +229,26 @@
     aStream text.
 
     (aStream skipThroughAll:'idth') isNil ifTrue: [
-	'SUNReader: Not a Sun Raster/Icon File' errorPrintNL.
-	^nil
+        'SUNReader: Not a Sun Raster/Icon File' errorPrintNL.
+        ^nil
     ].
     aStream next; skipSeparators. "skip $="
     width := Integer readFrom: aStream.
     (width isNil or:[width <= 0]) ifTrue: [
-	'SUNReader: format error (expected number)' errorPrintNL.
-	^ nil
+        'SUNReader: format error (expected number)' errorPrintNL.
+        ^ nil
     ].
     w := width.
 
     (aStream skipThroughAll:'eight') isNil ifTrue: [
-	'SUNReader: format error (expected height)' errorPrintNL.
-	^ nil
+        'SUNReader: format error (expected height)' errorPrintNL.
+        ^ nil
     ].
     aStream next; skipSeparators. "skip $="
     height := Integer readFrom: aStream.
     (height isNil or:[height <= 0]) ifTrue: [
-	'SUNReader: format error (expected number)' errorPrintNL.
-	^nil
+        'SUNReader: format error (expected number)' errorPrintNL.
+        ^nil
     ].
     h := height.
 
@@ -248,18 +259,25 @@
 
     index := 0.
     1 to:h do: [:row |
-	1 to: (w + 15 // 16) do: [:col |
-	    "rows are rounded up to next multiple of 16 bits"
-	    (aStream skipThroughAll:'0x') isNil ifTrue: [^ nil]. 
-	    word := Integer readFrom:aStream radix:16.
-	    word isNil ifTrue:[
-		'SUNReader: format error' errorPrintNL.
-		^ 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"
+            (aStream skipThroughAll:'0x') isNil ifTrue: [^ nil]. 
+            word := Integer readFrom:aStream radix:16.
+            word isNil ifTrue:[
+                'SUNReader: format error' errorPrintNL.
+                ^ nil
+            ].
+            data at: (index := index + 1) put: (word bitShift:-8).
+            data at: (index := index + 1) put: (word bitAnd:16rFF).
+        ]
     ].
+
+    "Modified: 23.4.1996 / 12:59:07 / cg"
 ! !
 
+!SunRasterReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.17 1996-04-23 10:59:53 cg Exp $'
+! !
 SunRasterReader initialize!