*** empty log message ***
authorclaus
Sat, 18 Feb 1995 16:57:27 +0100
changeset 105 6a4a21c17e5d
parent 104 aa39cabdc13b
child 106 6f59373d066e
*** empty log message ***
ImageRdr.st
ImageReader.st
--- a/ImageRdr.st	Sat Feb 18 16:53:17 1995 +0100
+++ b/ImageRdr.st	Sat Feb 18 16:57:27 1995 +0100
@@ -10,10 +10,11 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 2:18:34 am'!
+
 Object subclass:#ImageReader
-	 instanceVariableNames:'width height data byteOrder inStream outStream
-				photometric samplesPerPixel bitsPerSample
-				colorMap'
+	 instanceVariableNames:'width height data byteOrder inStream outStream photometric
+		samplesPerPixel bitsPerSample colorMap'
 	 classVariableNames:'ReverseBits'
 	 poolDictionaries:''
 	 category:'Graphics-Images support'
@@ -23,309 +24,10 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview/Attic/ImageRdr.st,v 1.14 1995-02-15 10:36:04 claus Exp $
+$Header: /cvs/stx/stx/libview/Attic/ImageRdr.st,v 1.15 1995-02-18 15:57:27 claus Exp $
 '!
 
-!ImageReader class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1991 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/libview/Attic/ImageRdr.st,v 1.14 1995-02-15 10:36:04 claus Exp $
-"
-!
-
-documentation
-"
-    common functions for image-readers (i.e. TIFFReader, GIFReader etc.)
-"
-! !
-
-!ImageReader class methodsFor:'cleanup'!
-
-lowSpaceCleanup
-    "cleanup things we do not need"
-
-    ReverseBits := nil
-! !
-
-!ImageReader class methodsFor:'testing'!
-
-isValidImageFile:aFileName
-    "return true, if aFileName contains an image this
-     reader understands - should be redefined in subclasses"
-
-    ^ false
-! !
-
-!ImageReader class methodsFor:'constants'!
-
-reverseBits
-    "return a table filled with bit reverse information.
-     To convert from msbit-first to lsbit-first bytes, use
-     the value as index into the table, retrieving the reverse
-     value. Since indexing must start at 1, use (value + 1) as
-     index."
-
-    |val "{ Class: SmallInteger }" |
-
-    ReverseBits isNil ifTrue:[
-	ReverseBits := ByteArray new:256.
-	0 to:255 do:[:i |
-	    val := 0.
-	    (i bitTest:16r01) ifTrue:[val := val bitOr:16r80].
-	    (i bitTest:16r02) ifTrue:[val := val bitOr:16r40].
-	    (i bitTest:16r04) ifTrue:[val := val bitOr:16r20].
-	    (i bitTest:16r08) ifTrue:[val := val bitOr:16r10].
-	    (i bitTest:16r10) ifTrue:[val := val bitOr:16r08].
-	    (i bitTest:16r20) ifTrue:[val := val bitOr:16r04].
-	    (i bitTest:16r40) ifTrue:[val := val bitOr:16r02].
-	    (i bitTest:16r80) ifTrue:[val := val bitOr:16r01].
-	    ReverseBits at:(i + 1) put:val
-	]
-    ].
-    ^ ReverseBits
-! !
-
-!ImageReader class methodsFor:'fileIn / fileOut'!
-
-fromFile:aFileName
-    "read an image (in my format) from aFileName"
-
-    |reader image depth|
-
-    reader := self new fromFile:aFileName.
-    reader notNil ifTrue:[
-	depth := reader bitsPerPixel.
-	image := (Image implementorForDepth: depth) new.
-	image width:(reader width).
-	image height:(reader height).
-	image photometric:(reader photometric).
-	image samplesPerPixel:(reader samplesPerPixel).
-	image bitsPerSample:(reader bitsPerSample).
-	image colorMap:(reader colorMap).
-	image data:(reader data).
-	^ image
-    ].
-    ^ nil
-!
-
-save:anImage onFile:aFileName
-    "save the image in my format on aFileName"
-
-    ^ (self basicNew) save:anImage onFile:aFileName
-! !
-
-!ImageReader class methodsFor:'i/o support'!
-
-streamReadingFile:aFilename
-    "return a stream to read aFilename - if the filename ends with
-     '.Z' or '.gz', read from a pipe to gunzip."
-
-    |inStream|
-
-    ((aFilename endsWith:'.Z') or:[aFilename endsWith:'.gz']) ifTrue:[
-	inStream := PipeStream readingFrom:'gunzip < ' , aFilename.
-	inStream isNil ifTrue:[
-	    inStream := PipeStream readingFrom:'uncompress < ' , aFilename.
-	]
-    ] ifFalse:[
-	inStream := FileStream readonlyFileNamed:aFilename.
-    ].
-    inStream isNil ifTrue:[
-	'IMGREADER: open error on: ' errorPrint. aFilename errorPrintNL. 
-    ].
-    ^ inStream
-! !
-
-!ImageReader methodsFor:'accessing'!
-
-width
-    ^ width
-!
-
-height 
-    ^ height
-!
-
-data 
-    ^ data
-!
-
-photometric
-    ^ photometric
-!
-
-colorMap
-    ^ colorMap
-!
-
-samplesPerPixel
-    ^ samplesPerPixel
-!
-
-bitsPerSample
-    ^ bitsPerSample
-!
-
-bitsPerPixel
-    "return the number of bits per pixel"
-
-    ^ (bitsPerSample inject:0 into:[:sum :i | sum + i])
-! !
-
-!ImageReader methodsFor:'fileIn / fileOut'!
-
-fromFile:aFileName
-    ^ self subclassResponsibility
-!
-
-save:image onFile:aFileName
-    ^ self subclassResponsibility
-! !
-
-!ImageReader methodsFor:'i/o support'!
-
-readLong
-    "return the next 4-byte long, honoring the byte-order"
-
-    ^ inStream nextLongMSB:(byteOrder ~~ #lsb)
-!
-
-readShort
-    "return the next 2-byte short, honoring the byte-order"
-
-    ^ inStream nextUnsignedShortMSB:(byteOrder ~~ #lsb)
-!
-
-readShortLong
-    "return the next 2-byte short, honoring the byte-order.
-     There are actually 4 bytes read, but only 2 looked at."
-
-    |bytes val|
-
-    bytes := ByteArray new:4.
-    inStream nextBytes:4 into:bytes.
-    (byteOrder == #lsb) ifTrue:[
-	val := bytes at:2.
-	val := val * 256 + (bytes at:1)
-    ] ifFalse:[
-	val := bytes at:3.
-	val := val * 256 + (bytes at:4)
-    ].
-    ^ val
-!
-
-writeLong:anInteger
-    "write a 4-byte long, honoring the byte-order."
-
-    outStream nextPutLong:anInteger MSB:(byteOrder ~~ #lsb)
-!
-
-writeShort:anInteger
-    "write a 2-byte short, honoring the byte-order."
-
-    outStream nextPutShort:anInteger MSB:(byteOrder ~~ #lsb)
-! !
-
-!ImageReader class methodsFor:'decompression support'!
-
-decompressCCITT3From:srcBytes into:dstBytes startingAt:offset count:count 
-    "decompress a CCITT Group 3 compressed image.
-     count bytes from srcBytes are decompressed into dstBytes.
-     Calls primitive c function for speed"
-%{
-    if (__isByteArray(srcBytes) 
-     && __isByteArray(dstBytes)
-     && __bothSmallInteger(offset, count)) {
-	if (__decodeCCITTgroup3__(_ByteArrayInstPtr(srcBytes)->ba_element,
-			      _ByteArrayInstPtr(dstBytes)->ba_element
-			      + _intVal(offset) - 1,
-			      _intVal(count))) {
-	    RETURN ( self );
-	}
-    }
-%}
-.
-    self primitiveFailed
-!
-
-decompressLZWFrom:srcBytes count:count into:dstBytes startingAt:offset
-    "decompress an LZW (tiff) compressed image.
-     count bytes from srcBytes are decompressed into dstBytes.
-     Calls primitive c function for speed"
-%{
-    if (__isByteArray(srcBytes) 
-     && __isByteArray(dstBytes)
-     && __bothSmallInteger(offset, count)) {
-	if (__decodeLZW__(_ByteArrayInstPtr(srcBytes)->ba_element,
-		      _ByteArrayInstPtr(dstBytes)->ba_element
-		      + _intVal(offset) - 1,
-		      _intVal(count))) {
-	    RETURN ( self );
-	}
-    }
-%}
-.
-    self primitiveFailed
-!
-
-decompressGIFFrom:srcBytes count:count into:dstBytes startingAt:offset codeLen:codeLen
-    "decompress a GIF compressed image.
-     count bytes from srcBytes are decompressed into dstBytes.
-     Calls primitive c function for speed"
-%{
-    if (__isByteArray(srcBytes) 
-     && __isByteArray(dstBytes)
-     && __bothSmallInteger(codeLen, offset)
-     && __isSmallInteger(count)) {
-	if (__decodeGIF__(_ByteArrayInstPtr(srcBytes)->ba_element,
-		      _ByteArrayInstPtr(dstBytes)->ba_element
-		      + _intVal(offset) - 1,
-		      _intVal(count),
-		      _intVal(codeLen))) {
-	    RETURN ( self );
-	}
-    }
-%}
-.
-    self primitiveFailed
-!
-decodeDelta:step in:data width:width height:height
-    "perform NeXT special predictor delta decoding inplace in data.
-     Calls primitive c function for speed"
-
-    (step ~~ 3) ifTrue:[
-	^ self error:'only rgb pictures supported'
-    ].
-
-%{
-    if (__isByteArray(data)
-     && __bothSmallInteger(width, height)) {
-	__decodeDelta__(_ByteArrayInstPtr(data)->ba_element,
-		    _intVal(width), _intVal(height));
-	RETURN ( self );
-    }
-%}
-.
-    self primitiveFailed
-! !
-
 !ImageReader primitiveFunctions!
-
 %{
 
 /*
@@ -1054,3 +756,353 @@
 
 %}
 ! !
+
+!ImageReader class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1991 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/libview/Attic/ImageRdr.st,v 1.15 1995-02-18 15:57:27 claus Exp $
+"
+!
+
+documentation
+"
+    Abstract class to provide common functions for image-readers 
+    (i.e. TIFFReader, GIFReader etc.)
+
+    ImageReaders are created temporary to read an image from a stream.
+    They read the stream and collect all relevant information internally.
+    Once done with reading, the image is asked for.
+
+    See implementation of fromStream: in concrete subclasses.
+    The public interfaces are:
+	 <ConcreteReaderClass> fromFile:aFilename
+    or:
+	 <ConcreteReaderClass> fromStream:aStream
+
+    However, usually this is done indirectly through
+	Image fromFile:aFileName
+"
+! !
+
+!ImageReader class methodsFor:'i/o support'!
+
+streamReadingFile:aFilename
+    "return a stream to read aFilename.
+     If the filename ends with '.Z' or '.gz', return a stream
+     to a pipe for the uncompressor. Otherwise, return a stream to read
+     the file directly."
+
+    |inStream name|
+
+    name := aFilename asString.
+    ((name endsWith:'.Z') or:[name endsWith:'.gz']) ifTrue:[
+	inStream := PipeStream readingFrom:'gunzip < ' , name.
+	inStream isNil ifTrue:[
+	    inStream := PipeStream readingFrom:'uncompress < ' , name.
+	]
+    ] ifFalse:[
+	inStream := aFilename asFilename readStream.
+    ].
+    inStream isNil ifTrue:[
+	'IMGREADER: open error on: ' errorPrint. aFilename errorPrintNL. 
+    ].
+    ^ inStream
+! !
+
+!ImageReader class methodsFor:'fileIn / fileOut'!
+
+fromStream:aStream
+    "read an image (in my format) from aStream"
+
+    |reader|
+
+    reader := self new fromStream:aStream.
+    reader notNil ifTrue:[
+	^ reader image
+    ].
+    ^ nil
+!
+
+fromFile:aFileName
+    "read an image (in my format) from aFileName. 
+     Return the image or nil on error."
+
+    |result inStream|
+
+    inStream := self streamReadingFile:aFileName.
+    inStream isNil ifTrue:[
+	'IMGREADER: file open error' errorPrintNL.
+	^ nil
+    ].
+    result := self fromStream:inStream.
+    inStream close.
+    ^ result
+
+    "
+     XPMReader fromFile:'bitmaps/ljet.xpm'
+     XBMReader fromFile:'bitmaps/SBrowser.xbm'
+    " 
+!
+
+save:anImage onFile:aFileName
+    "save the image in my format on aFileName"
+
+    ^ (self basicNew) save:anImage onFile:aFileName
+! !
+
+!ImageReader class methodsFor:'testing'!
+
+isValidImageFile:aFileName
+    "return true, if aFileName contains an image this
+     reader understands - should be redefined in subclasses"
+
+    ^ false
+! !
+
+!ImageReader class methodsFor:'constants'!
+
+reverseBits
+    "return a table filled with bit reverse information.
+     To convert from msbit-first to lsbit-first bytes, use
+     the value as index into the table, retrieving the reverse
+     value. Since indexing must start at 1, use (value + 1) as
+     index."
+
+    |val "{ Class: SmallInteger }" |
+
+    ReverseBits isNil ifTrue:[
+	ReverseBits := ByteArray new:256.
+	0 to:255 do:[:i |
+	    val := 0.
+	    (i bitTest:16r01) ifTrue:[val := val bitOr:16r80].
+	    (i bitTest:16r02) ifTrue:[val := val bitOr:16r40].
+	    (i bitTest:16r04) ifTrue:[val := val bitOr:16r20].
+	    (i bitTest:16r08) ifTrue:[val := val bitOr:16r10].
+	    (i bitTest:16r10) ifTrue:[val := val bitOr:16r08].
+	    (i bitTest:16r20) ifTrue:[val := val bitOr:16r04].
+	    (i bitTest:16r40) ifTrue:[val := val bitOr:16r02].
+	    (i bitTest:16r80) ifTrue:[val := val bitOr:16r01].
+	    ReverseBits at:(i + 1) put:val
+	]
+    ].
+    ^ ReverseBits
+! !
+
+!ImageReader class methodsFor:'cleanup'!
+
+lowSpaceCleanup
+    "cleanup things we do not need"
+
+    ReverseBits := nil
+! !
+
+!ImageReader class methodsFor:'decompression support'!
+
+decompressCCITT3From:srcBytes into:dstBytes startingAt:offset count:count 
+    "decompress CCITT Group 3 compressed image data.
+     count bytes from srcBytes are decompressed into dstBytes.
+     Calls primitive c function for speed"
+%{
+    if (__isByteArray(srcBytes) 
+     && __isByteArray(dstBytes)
+     && __bothSmallInteger(offset, count)) {
+	if (__decodeCCITTgroup3__(_ByteArrayInstPtr(srcBytes)->ba_element,
+			      _ByteArrayInstPtr(dstBytes)->ba_element
+			      + _intVal(offset) - 1,
+			      _intVal(count))) {
+	    RETURN ( self );
+	}
+    }
+%}
+.
+    self primitiveFailed
+!
+
+decompressLZWFrom:srcBytes count:count into:dstBytes startingAt:offset
+    "decompress LZW (tiff) compressed image data.
+     count bytes from srcBytes are decompressed into dstBytes.
+     Calls primitive c function for speed"
+%{
+    if (__isByteArray(srcBytes) 
+     && __isByteArray(dstBytes)
+     && __bothSmallInteger(offset, count)) {
+	if (__decodeLZW__(_ByteArrayInstPtr(srcBytes)->ba_element,
+		      _ByteArrayInstPtr(dstBytes)->ba_element
+		      + _intVal(offset) - 1,
+		      _intVal(count))) {
+	    RETURN ( self );
+	}
+    }
+%}
+.
+    self primitiveFailed
+!
+
+decompressGIFFrom:srcBytes count:count into:dstBytes startingAt:offset codeLen:codeLen
+    "decompress GIF compressed image data.
+     count bytes from srcBytes are decompressed into dstBytes.
+     Calls primitive c function for speed"
+%{
+    if (__isByteArray(srcBytes) 
+     && __isByteArray(dstBytes)
+     && __bothSmallInteger(codeLen, offset)
+     && __isSmallInteger(count)) {
+	if (__decodeGIF__(_ByteArrayInstPtr(srcBytes)->ba_element,
+		      _ByteArrayInstPtr(dstBytes)->ba_element
+		      + _intVal(offset) - 1,
+		      _intVal(count),
+		      _intVal(codeLen))) {
+	    RETURN ( self );
+	}
+    }
+%}
+.
+    self primitiveFailed
+!
+
+decodeDelta:step in:data width:width height:height
+    "perform NeXT special predictor delta decoding inplace in data.
+     Calls primitive c function for speed"
+
+    (step ~~ 3) ifTrue:[
+	^ self error:'only rgb pictures supported'
+    ].
+
+%{
+    if (__isByteArray(data)
+     && __bothSmallInteger(width, height)) {
+	__decodeDelta__(_ByteArrayInstPtr(data)->ba_element,
+		    _intVal(width), _intVal(height));
+	RETURN ( self );
+    }
+%}
+.
+    self primitiveFailed
+! !
+
+!ImageReader methodsFor:'accessing'!
+
+image
+    "return the image represented by myself"
+
+    |image depth|
+
+    depth := self bitsPerPixel.
+    image := (Image implementorForDepth:depth) new.
+    image width:width.
+    image height:height.
+    image photometric:photometric.
+    image samplesPerPixel:samplesPerPixel.
+    image bitsPerSample:bitsPerSample.
+    image colorMap:colorMap.
+    image data:data.
+    ^ image
+!
+
+height 
+    ^ height
+!
+
+photometric
+    ^ photometric
+!
+
+width
+    ^ width
+!
+
+samplesPerPixel
+    ^ samplesPerPixel
+!
+
+data 
+    ^ data
+!
+
+colorMap
+    ^ colorMap
+!
+
+bitsPerSample
+    ^ bitsPerSample
+!
+
+bitsPerPixel
+    "return the number of bits per pixel"
+
+    ^ (bitsPerSample inject:0 into:[:sum :i | sum + i])
+! !
+
+!ImageReader methodsFor:'fileIn / fileOut'!
+
+save:image onFile:aFileName
+    "save image in my format on aFile"
+
+    ^ self subclassResponsibility
+!
+
+fromStream:aStream
+    "read imagedata in my format from aStream"
+
+    ^ self subclassResponsibility
+! !
+
+!ImageReader methodsFor:'i/o support'!
+
+readLong
+    "return the next 4-byte long, honoring the byte-order"
+
+    ^ inStream nextLongMSB:(byteOrder ~~ #lsb)
+!
+
+readShort
+    "return the next 2-byte short, honoring the byte-order"
+
+    ^ inStream nextUnsignedShortMSB:(byteOrder ~~ #lsb)
+!
+
+readShortLong
+    "return the next 2-byte short, honoring the byte-order.
+     There are actually 4 bytes read, but only 2 looked at."
+
+    |bytes val|
+
+    bytes := ByteArray new:4.
+    inStream nextBytes:4 into:bytes.
+    (byteOrder == #lsb) ifTrue:[
+	val := bytes at:2.
+	val := val * 256 + (bytes at:1)
+    ] ifFalse:[
+	val := bytes at:3.
+	val := val * 256 + (bytes at:4)
+    ].
+    ^ val
+!
+
+writeLong:anInteger
+    "write a 4-byte long, honoring the byte-order."
+
+    outStream nextPutLong:anInteger MSB:(byteOrder ~~ #lsb)
+!
+
+writeShort:anInteger
+    "write a 2-byte short, honoring the byte-order."
+
+    outStream nextPutShort:anInteger MSB:(byteOrder ~~ #lsb)
+! !
+
--- a/ImageReader.st	Sat Feb 18 16:53:17 1995 +0100
+++ b/ImageReader.st	Sat Feb 18 16:57:27 1995 +0100
@@ -10,10 +10,11 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 2:18:34 am'!
+
 Object subclass:#ImageReader
-	 instanceVariableNames:'width height data byteOrder inStream outStream
-				photometric samplesPerPixel bitsPerSample
-				colorMap'
+	 instanceVariableNames:'width height data byteOrder inStream outStream photometric
+		samplesPerPixel bitsPerSample colorMap'
 	 classVariableNames:'ReverseBits'
 	 poolDictionaries:''
 	 category:'Graphics-Images support'
@@ -23,309 +24,10 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libview/ImageReader.st,v 1.14 1995-02-15 10:36:04 claus Exp $
+$Header: /cvs/stx/stx/libview/ImageReader.st,v 1.15 1995-02-18 15:57:27 claus Exp $
 '!
 
-!ImageReader class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 1991 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/libview/ImageReader.st,v 1.14 1995-02-15 10:36:04 claus Exp $
-"
-!
-
-documentation
-"
-    common functions for image-readers (i.e. TIFFReader, GIFReader etc.)
-"
-! !
-
-!ImageReader class methodsFor:'cleanup'!
-
-lowSpaceCleanup
-    "cleanup things we do not need"
-
-    ReverseBits := nil
-! !
-
-!ImageReader class methodsFor:'testing'!
-
-isValidImageFile:aFileName
-    "return true, if aFileName contains an image this
-     reader understands - should be redefined in subclasses"
-
-    ^ false
-! !
-
-!ImageReader class methodsFor:'constants'!
-
-reverseBits
-    "return a table filled with bit reverse information.
-     To convert from msbit-first to lsbit-first bytes, use
-     the value as index into the table, retrieving the reverse
-     value. Since indexing must start at 1, use (value + 1) as
-     index."
-
-    |val "{ Class: SmallInteger }" |
-
-    ReverseBits isNil ifTrue:[
-	ReverseBits := ByteArray new:256.
-	0 to:255 do:[:i |
-	    val := 0.
-	    (i bitTest:16r01) ifTrue:[val := val bitOr:16r80].
-	    (i bitTest:16r02) ifTrue:[val := val bitOr:16r40].
-	    (i bitTest:16r04) ifTrue:[val := val bitOr:16r20].
-	    (i bitTest:16r08) ifTrue:[val := val bitOr:16r10].
-	    (i bitTest:16r10) ifTrue:[val := val bitOr:16r08].
-	    (i bitTest:16r20) ifTrue:[val := val bitOr:16r04].
-	    (i bitTest:16r40) ifTrue:[val := val bitOr:16r02].
-	    (i bitTest:16r80) ifTrue:[val := val bitOr:16r01].
-	    ReverseBits at:(i + 1) put:val
-	]
-    ].
-    ^ ReverseBits
-! !
-
-!ImageReader class methodsFor:'fileIn / fileOut'!
-
-fromFile:aFileName
-    "read an image (in my format) from aFileName"
-
-    |reader image depth|
-
-    reader := self new fromFile:aFileName.
-    reader notNil ifTrue:[
-	depth := reader bitsPerPixel.
-	image := (Image implementorForDepth: depth) new.
-	image width:(reader width).
-	image height:(reader height).
-	image photometric:(reader photometric).
-	image samplesPerPixel:(reader samplesPerPixel).
-	image bitsPerSample:(reader bitsPerSample).
-	image colorMap:(reader colorMap).
-	image data:(reader data).
-	^ image
-    ].
-    ^ nil
-!
-
-save:anImage onFile:aFileName
-    "save the image in my format on aFileName"
-
-    ^ (self basicNew) save:anImage onFile:aFileName
-! !
-
-!ImageReader class methodsFor:'i/o support'!
-
-streamReadingFile:aFilename
-    "return a stream to read aFilename - if the filename ends with
-     '.Z' or '.gz', read from a pipe to gunzip."
-
-    |inStream|
-
-    ((aFilename endsWith:'.Z') or:[aFilename endsWith:'.gz']) ifTrue:[
-	inStream := PipeStream readingFrom:'gunzip < ' , aFilename.
-	inStream isNil ifTrue:[
-	    inStream := PipeStream readingFrom:'uncompress < ' , aFilename.
-	]
-    ] ifFalse:[
-	inStream := FileStream readonlyFileNamed:aFilename.
-    ].
-    inStream isNil ifTrue:[
-	'IMGREADER: open error on: ' errorPrint. aFilename errorPrintNL. 
-    ].
-    ^ inStream
-! !
-
-!ImageReader methodsFor:'accessing'!
-
-width
-    ^ width
-!
-
-height 
-    ^ height
-!
-
-data 
-    ^ data
-!
-
-photometric
-    ^ photometric
-!
-
-colorMap
-    ^ colorMap
-!
-
-samplesPerPixel
-    ^ samplesPerPixel
-!
-
-bitsPerSample
-    ^ bitsPerSample
-!
-
-bitsPerPixel
-    "return the number of bits per pixel"
-
-    ^ (bitsPerSample inject:0 into:[:sum :i | sum + i])
-! !
-
-!ImageReader methodsFor:'fileIn / fileOut'!
-
-fromFile:aFileName
-    ^ self subclassResponsibility
-!
-
-save:image onFile:aFileName
-    ^ self subclassResponsibility
-! !
-
-!ImageReader methodsFor:'i/o support'!
-
-readLong
-    "return the next 4-byte long, honoring the byte-order"
-
-    ^ inStream nextLongMSB:(byteOrder ~~ #lsb)
-!
-
-readShort
-    "return the next 2-byte short, honoring the byte-order"
-
-    ^ inStream nextUnsignedShortMSB:(byteOrder ~~ #lsb)
-!
-
-readShortLong
-    "return the next 2-byte short, honoring the byte-order.
-     There are actually 4 bytes read, but only 2 looked at."
-
-    |bytes val|
-
-    bytes := ByteArray new:4.
-    inStream nextBytes:4 into:bytes.
-    (byteOrder == #lsb) ifTrue:[
-	val := bytes at:2.
-	val := val * 256 + (bytes at:1)
-    ] ifFalse:[
-	val := bytes at:3.
-	val := val * 256 + (bytes at:4)
-    ].
-    ^ val
-!
-
-writeLong:anInteger
-    "write a 4-byte long, honoring the byte-order."
-
-    outStream nextPutLong:anInteger MSB:(byteOrder ~~ #lsb)
-!
-
-writeShort:anInteger
-    "write a 2-byte short, honoring the byte-order."
-
-    outStream nextPutShort:anInteger MSB:(byteOrder ~~ #lsb)
-! !
-
-!ImageReader class methodsFor:'decompression support'!
-
-decompressCCITT3From:srcBytes into:dstBytes startingAt:offset count:count 
-    "decompress a CCITT Group 3 compressed image.
-     count bytes from srcBytes are decompressed into dstBytes.
-     Calls primitive c function for speed"
-%{
-    if (__isByteArray(srcBytes) 
-     && __isByteArray(dstBytes)
-     && __bothSmallInteger(offset, count)) {
-	if (__decodeCCITTgroup3__(_ByteArrayInstPtr(srcBytes)->ba_element,
-			      _ByteArrayInstPtr(dstBytes)->ba_element
-			      + _intVal(offset) - 1,
-			      _intVal(count))) {
-	    RETURN ( self );
-	}
-    }
-%}
-.
-    self primitiveFailed
-!
-
-decompressLZWFrom:srcBytes count:count into:dstBytes startingAt:offset
-    "decompress an LZW (tiff) compressed image.
-     count bytes from srcBytes are decompressed into dstBytes.
-     Calls primitive c function for speed"
-%{
-    if (__isByteArray(srcBytes) 
-     && __isByteArray(dstBytes)
-     && __bothSmallInteger(offset, count)) {
-	if (__decodeLZW__(_ByteArrayInstPtr(srcBytes)->ba_element,
-		      _ByteArrayInstPtr(dstBytes)->ba_element
-		      + _intVal(offset) - 1,
-		      _intVal(count))) {
-	    RETURN ( self );
-	}
-    }
-%}
-.
-    self primitiveFailed
-!
-
-decompressGIFFrom:srcBytes count:count into:dstBytes startingAt:offset codeLen:codeLen
-    "decompress a GIF compressed image.
-     count bytes from srcBytes are decompressed into dstBytes.
-     Calls primitive c function for speed"
-%{
-    if (__isByteArray(srcBytes) 
-     && __isByteArray(dstBytes)
-     && __bothSmallInteger(codeLen, offset)
-     && __isSmallInteger(count)) {
-	if (__decodeGIF__(_ByteArrayInstPtr(srcBytes)->ba_element,
-		      _ByteArrayInstPtr(dstBytes)->ba_element
-		      + _intVal(offset) - 1,
-		      _intVal(count),
-		      _intVal(codeLen))) {
-	    RETURN ( self );
-	}
-    }
-%}
-.
-    self primitiveFailed
-!
-decodeDelta:step in:data width:width height:height
-    "perform NeXT special predictor delta decoding inplace in data.
-     Calls primitive c function for speed"
-
-    (step ~~ 3) ifTrue:[
-	^ self error:'only rgb pictures supported'
-    ].
-
-%{
-    if (__isByteArray(data)
-     && __bothSmallInteger(width, height)) {
-	__decodeDelta__(_ByteArrayInstPtr(data)->ba_element,
-		    _intVal(width), _intVal(height));
-	RETURN ( self );
-    }
-%}
-.
-    self primitiveFailed
-! !
-
 !ImageReader primitiveFunctions!
-
 %{
 
 /*
@@ -1054,3 +756,353 @@
 
 %}
 ! !
+
+!ImageReader class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1991 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/libview/ImageReader.st,v 1.15 1995-02-18 15:57:27 claus Exp $
+"
+!
+
+documentation
+"
+    Abstract class to provide common functions for image-readers 
+    (i.e. TIFFReader, GIFReader etc.)
+
+    ImageReaders are created temporary to read an image from a stream.
+    They read the stream and collect all relevant information internally.
+    Once done with reading, the image is asked for.
+
+    See implementation of fromStream: in concrete subclasses.
+    The public interfaces are:
+	 <ConcreteReaderClass> fromFile:aFilename
+    or:
+	 <ConcreteReaderClass> fromStream:aStream
+
+    However, usually this is done indirectly through
+	Image fromFile:aFileName
+"
+! !
+
+!ImageReader class methodsFor:'i/o support'!
+
+streamReadingFile:aFilename
+    "return a stream to read aFilename.
+     If the filename ends with '.Z' or '.gz', return a stream
+     to a pipe for the uncompressor. Otherwise, return a stream to read
+     the file directly."
+
+    |inStream name|
+
+    name := aFilename asString.
+    ((name endsWith:'.Z') or:[name endsWith:'.gz']) ifTrue:[
+	inStream := PipeStream readingFrom:'gunzip < ' , name.
+	inStream isNil ifTrue:[
+	    inStream := PipeStream readingFrom:'uncompress < ' , name.
+	]
+    ] ifFalse:[
+	inStream := aFilename asFilename readStream.
+    ].
+    inStream isNil ifTrue:[
+	'IMGREADER: open error on: ' errorPrint. aFilename errorPrintNL. 
+    ].
+    ^ inStream
+! !
+
+!ImageReader class methodsFor:'fileIn / fileOut'!
+
+fromStream:aStream
+    "read an image (in my format) from aStream"
+
+    |reader|
+
+    reader := self new fromStream:aStream.
+    reader notNil ifTrue:[
+	^ reader image
+    ].
+    ^ nil
+!
+
+fromFile:aFileName
+    "read an image (in my format) from aFileName. 
+     Return the image or nil on error."
+
+    |result inStream|
+
+    inStream := self streamReadingFile:aFileName.
+    inStream isNil ifTrue:[
+	'IMGREADER: file open error' errorPrintNL.
+	^ nil
+    ].
+    result := self fromStream:inStream.
+    inStream close.
+    ^ result
+
+    "
+     XPMReader fromFile:'bitmaps/ljet.xpm'
+     XBMReader fromFile:'bitmaps/SBrowser.xbm'
+    " 
+!
+
+save:anImage onFile:aFileName
+    "save the image in my format on aFileName"
+
+    ^ (self basicNew) save:anImage onFile:aFileName
+! !
+
+!ImageReader class methodsFor:'testing'!
+
+isValidImageFile:aFileName
+    "return true, if aFileName contains an image this
+     reader understands - should be redefined in subclasses"
+
+    ^ false
+! !
+
+!ImageReader class methodsFor:'constants'!
+
+reverseBits
+    "return a table filled with bit reverse information.
+     To convert from msbit-first to lsbit-first bytes, use
+     the value as index into the table, retrieving the reverse
+     value. Since indexing must start at 1, use (value + 1) as
+     index."
+
+    |val "{ Class: SmallInteger }" |
+
+    ReverseBits isNil ifTrue:[
+	ReverseBits := ByteArray new:256.
+	0 to:255 do:[:i |
+	    val := 0.
+	    (i bitTest:16r01) ifTrue:[val := val bitOr:16r80].
+	    (i bitTest:16r02) ifTrue:[val := val bitOr:16r40].
+	    (i bitTest:16r04) ifTrue:[val := val bitOr:16r20].
+	    (i bitTest:16r08) ifTrue:[val := val bitOr:16r10].
+	    (i bitTest:16r10) ifTrue:[val := val bitOr:16r08].
+	    (i bitTest:16r20) ifTrue:[val := val bitOr:16r04].
+	    (i bitTest:16r40) ifTrue:[val := val bitOr:16r02].
+	    (i bitTest:16r80) ifTrue:[val := val bitOr:16r01].
+	    ReverseBits at:(i + 1) put:val
+	]
+    ].
+    ^ ReverseBits
+! !
+
+!ImageReader class methodsFor:'cleanup'!
+
+lowSpaceCleanup
+    "cleanup things we do not need"
+
+    ReverseBits := nil
+! !
+
+!ImageReader class methodsFor:'decompression support'!
+
+decompressCCITT3From:srcBytes into:dstBytes startingAt:offset count:count 
+    "decompress CCITT Group 3 compressed image data.
+     count bytes from srcBytes are decompressed into dstBytes.
+     Calls primitive c function for speed"
+%{
+    if (__isByteArray(srcBytes) 
+     && __isByteArray(dstBytes)
+     && __bothSmallInteger(offset, count)) {
+	if (__decodeCCITTgroup3__(_ByteArrayInstPtr(srcBytes)->ba_element,
+			      _ByteArrayInstPtr(dstBytes)->ba_element
+			      + _intVal(offset) - 1,
+			      _intVal(count))) {
+	    RETURN ( self );
+	}
+    }
+%}
+.
+    self primitiveFailed
+!
+
+decompressLZWFrom:srcBytes count:count into:dstBytes startingAt:offset
+    "decompress LZW (tiff) compressed image data.
+     count bytes from srcBytes are decompressed into dstBytes.
+     Calls primitive c function for speed"
+%{
+    if (__isByteArray(srcBytes) 
+     && __isByteArray(dstBytes)
+     && __bothSmallInteger(offset, count)) {
+	if (__decodeLZW__(_ByteArrayInstPtr(srcBytes)->ba_element,
+		      _ByteArrayInstPtr(dstBytes)->ba_element
+		      + _intVal(offset) - 1,
+		      _intVal(count))) {
+	    RETURN ( self );
+	}
+    }
+%}
+.
+    self primitiveFailed
+!
+
+decompressGIFFrom:srcBytes count:count into:dstBytes startingAt:offset codeLen:codeLen
+    "decompress GIF compressed image data.
+     count bytes from srcBytes are decompressed into dstBytes.
+     Calls primitive c function for speed"
+%{
+    if (__isByteArray(srcBytes) 
+     && __isByteArray(dstBytes)
+     && __bothSmallInteger(codeLen, offset)
+     && __isSmallInteger(count)) {
+	if (__decodeGIF__(_ByteArrayInstPtr(srcBytes)->ba_element,
+		      _ByteArrayInstPtr(dstBytes)->ba_element
+		      + _intVal(offset) - 1,
+		      _intVal(count),
+		      _intVal(codeLen))) {
+	    RETURN ( self );
+	}
+    }
+%}
+.
+    self primitiveFailed
+!
+
+decodeDelta:step in:data width:width height:height
+    "perform NeXT special predictor delta decoding inplace in data.
+     Calls primitive c function for speed"
+
+    (step ~~ 3) ifTrue:[
+	^ self error:'only rgb pictures supported'
+    ].
+
+%{
+    if (__isByteArray(data)
+     && __bothSmallInteger(width, height)) {
+	__decodeDelta__(_ByteArrayInstPtr(data)->ba_element,
+		    _intVal(width), _intVal(height));
+	RETURN ( self );
+    }
+%}
+.
+    self primitiveFailed
+! !
+
+!ImageReader methodsFor:'accessing'!
+
+image
+    "return the image represented by myself"
+
+    |image depth|
+
+    depth := self bitsPerPixel.
+    image := (Image implementorForDepth:depth) new.
+    image width:width.
+    image height:height.
+    image photometric:photometric.
+    image samplesPerPixel:samplesPerPixel.
+    image bitsPerSample:bitsPerSample.
+    image colorMap:colorMap.
+    image data:data.
+    ^ image
+!
+
+height 
+    ^ height
+!
+
+photometric
+    ^ photometric
+!
+
+width
+    ^ width
+!
+
+samplesPerPixel
+    ^ samplesPerPixel
+!
+
+data 
+    ^ data
+!
+
+colorMap
+    ^ colorMap
+!
+
+bitsPerSample
+    ^ bitsPerSample
+!
+
+bitsPerPixel
+    "return the number of bits per pixel"
+
+    ^ (bitsPerSample inject:0 into:[:sum :i | sum + i])
+! !
+
+!ImageReader methodsFor:'fileIn / fileOut'!
+
+save:image onFile:aFileName
+    "save image in my format on aFile"
+
+    ^ self subclassResponsibility
+!
+
+fromStream:aStream
+    "read imagedata in my format from aStream"
+
+    ^ self subclassResponsibility
+! !
+
+!ImageReader methodsFor:'i/o support'!
+
+readLong
+    "return the next 4-byte long, honoring the byte-order"
+
+    ^ inStream nextLongMSB:(byteOrder ~~ #lsb)
+!
+
+readShort
+    "return the next 2-byte short, honoring the byte-order"
+
+    ^ inStream nextUnsignedShortMSB:(byteOrder ~~ #lsb)
+!
+
+readShortLong
+    "return the next 2-byte short, honoring the byte-order.
+     There are actually 4 bytes read, but only 2 looked at."
+
+    |bytes val|
+
+    bytes := ByteArray new:4.
+    inStream nextBytes:4 into:bytes.
+    (byteOrder == #lsb) ifTrue:[
+	val := bytes at:2.
+	val := val * 256 + (bytes at:1)
+    ] ifFalse:[
+	val := bytes at:3.
+	val := val * 256 + (bytes at:4)
+    ].
+    ^ val
+!
+
+writeLong:anInteger
+    "write a 4-byte long, honoring the byte-order."
+
+    outStream nextPutLong:anInteger MSB:(byteOrder ~~ #lsb)
+!
+
+writeShort:anInteger
+    "write a 2-byte short, honoring the byte-order."
+
+    outStream nextPutShort:anInteger MSB:(byteOrder ~~ #lsb)
+! !
+