*** empty log message ***
authorclaus
Sat, 18 Feb 1995 18:56:08 +0100
changeset 44 c6cf7d0d6337
parent 43 e85c7d392833
child 45 f94fc6118d0a
*** empty log message ***
SunRasterReader.st
SunReader.st
XWDReader.st
--- a/SunRasterReader.st	Sat Feb 18 16:58:20 1995 +0100
+++ b/SunRasterReader.st	Sat Feb 18 18:56:08 1995 +0100
@@ -23,7 +23,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.11 1995-02-18 15:58:11 claus Exp $
+$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.12 1995-02-18 17:55:37 claus Exp $
 '!
 
 !SunRasterReader class methodsFor:'documentation'!
@@ -44,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.11 1995-02-18 15:58:11 claus Exp $
+$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.12 1995-02-18 17:55:37 claus Exp $
 "
 !
 
@@ -128,9 +128,9 @@
     pos := aStream position.
     ((aStream nextWord == 16r59A6) 
     and:[aStream nextWord == 16r6A95]) ifFalse: [
-        'SUNReader: not a SunRaster file' errorPrintNL.
-        aStream position:pos.
-        ^ self fromSunIconStream:aStream
+"/        'SUNReader: not a SunRaster file' errorPrintNL.
+	aStream position:pos.
+	^ self fromSunIconStream:aStream
     ].
 
     width := aStream nextLong.
@@ -143,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: Raster file is not monochrome' errorPrintNL.
-        ^ nil
+	'SUNReader: only depth 1 and 8 supported' errorPrintNL.
+	^ nil
     ].
 
     form := nil.
@@ -172,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.
@@ -214,7 +214,6 @@
      SunRasterReader fromStream:'bitmaps/founders.im8' asFilename readStream
      SunRasterReader fromStream:'bitmaps/bf.im8' asFilename readStream
     "
-
 !
 
 fromSunIconStream: aStream 
@@ -223,28 +222,29 @@
      h "{ Class: SmallInteger }"|
 
     inStream := aStream.
+    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.
 
@@ -255,17 +255,17 @@
 
     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).
+	]
     ].
 ! !
 
--- a/SunReader.st	Sat Feb 18 16:58:20 1995 +0100
+++ b/SunReader.st	Sat Feb 18 18:56:08 1995 +0100
@@ -23,7 +23,7 @@
 COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview2/Attic/SunReader.st,v 1.11 1995-02-18 15:58:11 claus Exp $
+$Header: /cvs/stx/stx/libview2/Attic/SunReader.st,v 1.12 1995-02-18 17:55:37 claus Exp $
 '!
 
 !SunRasterReader class methodsFor:'documentation'!
@@ -44,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libview2/Attic/SunReader.st,v 1.11 1995-02-18 15:58:11 claus Exp $
+$Header: /cvs/stx/stx/libview2/Attic/SunReader.st,v 1.12 1995-02-18 17:55:37 claus Exp $
 "
 !
 
@@ -128,9 +128,9 @@
     pos := aStream position.
     ((aStream nextWord == 16r59A6) 
     and:[aStream nextWord == 16r6A95]) ifFalse: [
-        'SUNReader: not a SunRaster file' errorPrintNL.
-        aStream position:pos.
-        ^ self fromSunIconStream:aStream
+"/        'SUNReader: not a SunRaster file' errorPrintNL.
+	aStream position:pos.
+	^ self fromSunIconStream:aStream
     ].
 
     width := aStream nextLong.
@@ -143,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: Raster file is not monochrome' errorPrintNL.
-        ^ nil
+	'SUNReader: only depth 1 and 8 supported' errorPrintNL.
+	^ nil
     ].
 
     form := nil.
@@ -172,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.
@@ -214,7 +214,6 @@
      SunRasterReader fromStream:'bitmaps/founders.im8' asFilename readStream
      SunRasterReader fromStream:'bitmaps/bf.im8' asFilename readStream
     "
-
 !
 
 fromSunIconStream: aStream 
@@ -223,28 +222,29 @@
      h "{ Class: SmallInteger }"|
 
     inStream := aStream.
+    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.
 
@@ -255,17 +255,17 @@
 
     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).
+	]
     ].
 ! !
 
--- a/XWDReader.st	Sat Feb 18 16:58:20 1995 +0100
+++ b/XWDReader.st	Sat Feb 18 18:56:08 1995 +0100
@@ -1,4 +1,14 @@
-'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 3:27:03 am'!
+"
+ COPYRIGHT (c) 1995 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:#XWDReader
 	 instanceVariableNames:''
@@ -7,12 +17,49 @@
 	 category:'Graphics-Images support'
 !
 
+XWDReader comment:'
+COPYRIGHT (c) 1995 by Claus Gittinger
+	      All Rights Reserved
+
+$Header: /cvs/stx/stx/libview2/XWDReader.st,v 1.2 1995-02-18 17:56:08 claus Exp $
+'!
+
+!XWDReader class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1995 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/XWDReader.st,v 1.2 1995-02-18 17:56:08 claus Exp $
+"
+!
+
+documentation
+"
+    this class provides methods for loading x-window dump (xwd) images.
+"
+! !
+
 !XWDReader methodsFor:'image reading'!
 
 fromStream: aStream 
-        "read an image in XWD (X Window Dump) format."
+	"read an image in XWD (X Window Dump) format."
 
-    |header nColors palette res colors pad srcRowByteSize bitsPerPixel mask colormapSize depth |
+    |header nColors palette res colors pad 
+     srcRowByteSize bytesPerRow bitsPerPixel mask colormapSize depth 
+     dstIndex|
 
     aStream binary.
 
@@ -27,39 +74,53 @@
     pad := header at: 11.
     bitsPerPixel := header at: 12.
     bitsPerPixel == 24 ifTrue:[
-        bitsPerSample := #(8 8 8).
-        samplesPerPixel := 3.
-        photometric := #rgb
+	bitsPerSample := #(8 8 8).
+	samplesPerPixel := 3.
+	photometric := #rgb
     ] ifFalse:[
-        bitsPerSample := Array with:bitsPerPixel.
-        samplesPerPixel := 1.
-        photometric := #palette
+	bitsPerSample := Array with:bitsPerPixel.
+	samplesPerPixel := 1.
+	photometric := #palette
     ].
 
     colormapSize := header at: 19.
     nColors := header at: 20.
 
-    colorMap := Array new:depth * depth.
+    colorMap := Array new:colormapSize.
 
     1 to:nColors do:[:i |
-        |clr|
+	|clr|
+
+	aStream nextLong.
+	clr := ColorValue scaledRed: (aStream nextWord bitShift: -3)
+			scaledGreen: (aStream nextWord bitShift: -3)
+			 scaledBlue: (aStream nextWord bitShift: -3).
+	colorMap at:i put:clr.
+	aStream nextWord.
+    ].
+
+    nColors+1 to:colormapSize do: [:i | colorMap at:i put:Color black].
 
-        aStream nextLong.
-        clr := Color scaledRed: (aStream nextWord bitShift: -3)
-                     scaledGreen: (aStream nextWord bitShift: -3)
-                     scaledBlue: (aStream nextWord bitShift: -3).
-        colorMap at:i put:clr.
-        aStream nextWord.
-   ].
+    bytesPerRow := width * bitsPerPixel // 8.
+    ((width * bitsPerPixel \\ 8) ~~ 0) ifTrue:[
+	bytesPerRow := bytesPerRow + 1
+    ].
+    srcRowByteSize := width * bitsPerPixel + pad - 1 // pad * (pad / 8).
 
-    nColors+1 to:(depth * depth) do: [:i | colorMap at:i put:Color black].
-
-    srcRowByteSize := width * bitsPerPixel + pad - 1 // pad * (pad / 8).
     data := ByteArray uninitializedNew: srcRowByteSize * height.
-    aStream nextBytes:srcRowByteSize * height into:data.
-
+    srcRowByteSize == bytesPerRow ifTrue:[
+	aStream nextBytes:srcRowByteSize * height into:data.
+    ] ifFalse:[
+	dstIndex := 1.
+	1 to:height do:[:y |
+	    aStream nextBytes:bytesPerRow into:data startingAt:dstIndex.
+	    aStream next:(srcRowByteSize - bytesPerRow).
+	    dstIndex := dstIndex + bytesPerRow.
+	].
+	self halt.
+    ]
     "
-     XWDReader fromFile:'/phys/clam/claus/smalltalk/private_classes/hpdst/pixmaps/bike.xwd'
+     XWDReader fromFile:'testfile.xwd'
     "
 ! !