category changes
authorClaus Gittinger <cg@exept.de>
Mon, 01 Sep 2003 16:47:57 +0200
changeset 1805 93f557cbe600
parent 1804 f84ff77deaea
child 1806 69e71e3497c0
category changes
FLIReader.st
FaceReader.st
GIFReader.st
IrisRGBReader.st
JPEGReader.st
PBMReader.st
PCXReader.st
PNGReader.st
ST80FormReader.st
SunRasterReader.st
TIFFReader.st
TargaReader.st
WindowsIconReader.st
XBMReader.st
XPMReader.st
XWDReader.st
--- a/FLIReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/FLIReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -227,6 +227,105 @@
     "Modified: 24.6.1997 / 15:57:22 / cg"
 ! !
 
+!FLIReader methodsFor:'private-reading'!
+
+getFrame
+    "get a single frame"
+
+    |header n len type dataLen nchunks|
+
+    header := ByteArray new:FRAME_HEAD_SIZE.
+    n := inStream nextBytes:FRAME_HEAD_SIZE into:header.
+    n ~~ FRAME_HEAD_SIZE ifTrue:[^ false].
+
+    len := header doubleWordAt:(1+0).
+    type := header wordAt:(1+4).
+
+    type ~~ FLI_FRAME_MAGIC ifTrue:[^ false].
+
+    dataLen := len - FRAME_HEAD_SIZE.
+    dataLen > frameBufferSize ifTrue:[
+        frameBuffer := ByteArray uninitializedNew:dataLen.
+        frameBufferSize := dataLen.
+    ].
+
+    n := inStream nextBytes:dataLen into:frameBuffer.
+    n ~~ dataLen ifTrue:[^ false].
+
+    nchunks := header wordAt:(1+6).
+    nchunks == 0 ifTrue:[
+        "/ mhmh - a timing frame; should add a dummy frame
+        ^ self.
+    ].     
+    ^ self processChunks:nchunks size:dataLen.
+
+    "
+     FLIReader fromFile:'bitmaps/magtape.xpm'    
+     FLIReader fromFile:'/usr/local/FLI/jeffmild.fli'      
+    "
+
+    "Created: 3.4.1997 / 22:15:19 / cg"
+    "Modified: 4.4.1997 / 22:18:21 / cg"
+!
+
+getHeader
+    "read the header; return true, if its valid"
+
+    |header n len type speed|
+
+    header := ByteArray new:FILE_HEAD_SIZE.
+    n := inStream nextBytes:FILE_HEAD_SIZE into:header.
+    n ~~ FILE_HEAD_SIZE ifTrue:[^ false].
+
+    len := header doubleWordAt:(1+0).
+    type := header wordAt:(1+4).
+
+    type ~~ FLI_FILE_MAGIC ifTrue:[
+        type ~~ FLC_FILE_MAGIC ifTrue:[
+            ^ false
+        ]
+    ].
+
+    nframes := header wordAt:(1+6).
+    width := header wordAt:(1+8).
+    height := header wordAt:(1+10).
+
+    dimensionCallBack notNil ifTrue:[
+        dimensionCallBack value
+    ].
+    flags := header wordAt:(1+14).
+    speed := header wordAt:(1+16).
+    speed <= 0 ifTrue:[
+        speed := 1
+    ].
+    "/ FLI uses 1/70th of a second;
+    "/ FLC measures the frameDelay in milliseconds
+    type == FLI_FILE_MAGIC ifTrue:[
+        frameDelay := 1000 * speed // 70
+    ] ifFalse:[
+        frameDelay := speed
+    ].
+
+    frameBufferSize := width * height.
+    frameBuffer := ByteArray uninitializedNew:frameBufferSize.
+
+    redPalette := ByteArray new:256.
+    greenPalette := ByteArray new:256.
+    bluePalette := ByteArray new:256.
+
+    imageSequence := OrderedCollection new:nframes.
+
+    ^ true
+
+    "
+     FLIReader fromFile:'bitmaps/magtape.xpm'    
+     FLIReader fromFile:'/usr/local/FLI/jeffmild.fli'      
+    "
+
+    "Created: 3.4.1997 / 22:09:12 / cg"
+    "Modified: 24.6.1997 / 15:31:39 / cg"
+! !
+
 !FLIReader methodsFor:'processing chunks'!
 
 brunChunkAt:chunkOffs
@@ -427,7 +526,7 @@
     "Modified: 3.4.1997 / 22:52:38 / cg"
 ! !
 
-!FLIReader methodsFor:'reading from stream'!
+!FLIReader methodsFor:'reading'!
 
 fromStream:aStream
     "read a FLI-movie from aStream."
@@ -460,109 +559,12 @@
     "
 
     "Modified: 24.6.1997 / 15:58:18 / cg"
-!
-
-getFrame
-    "get a single frame"
-
-    |header n len type dataLen nchunks|
-
-    header := ByteArray new:FRAME_HEAD_SIZE.
-    n := inStream nextBytes:FRAME_HEAD_SIZE into:header.
-    n ~~ FRAME_HEAD_SIZE ifTrue:[^ false].
-
-    len := header doubleWordAt:(1+0).
-    type := header wordAt:(1+4).
-
-    type ~~ FLI_FRAME_MAGIC ifTrue:[^ false].
-
-    dataLen := len - FRAME_HEAD_SIZE.
-    dataLen > frameBufferSize ifTrue:[
-        frameBuffer := ByteArray uninitializedNew:dataLen.
-        frameBufferSize := dataLen.
-    ].
-
-    n := inStream nextBytes:dataLen into:frameBuffer.
-    n ~~ dataLen ifTrue:[^ false].
-
-    nchunks := header wordAt:(1+6).
-    nchunks == 0 ifTrue:[
-        "/ mhmh - a timing frame; should add a dummy frame
-        ^ self.
-    ].     
-    ^ self processChunks:nchunks size:dataLen.
-
-    "
-     FLIReader fromFile:'bitmaps/magtape.xpm'    
-     FLIReader fromFile:'/usr/local/FLI/jeffmild.fli'      
-    "
-
-    "Created: 3.4.1997 / 22:15:19 / cg"
-    "Modified: 4.4.1997 / 22:18:21 / cg"
-!
-
-getHeader
-    "read the header; return true, if its valid"
-
-    |header n len type speed|
-
-    header := ByteArray new:FILE_HEAD_SIZE.
-    n := inStream nextBytes:FILE_HEAD_SIZE into:header.
-    n ~~ FILE_HEAD_SIZE ifTrue:[^ false].
-
-    len := header doubleWordAt:(1+0).
-    type := header wordAt:(1+4).
-
-    type ~~ FLI_FILE_MAGIC ifTrue:[
-        type ~~ FLC_FILE_MAGIC ifTrue:[
-            ^ false
-        ]
-    ].
-
-    nframes := header wordAt:(1+6).
-    width := header wordAt:(1+8).
-    height := header wordAt:(1+10).
-
-    dimensionCallBack notNil ifTrue:[
-        dimensionCallBack value
-    ].
-    flags := header wordAt:(1+14).
-    speed := header wordAt:(1+16).
-    speed <= 0 ifTrue:[
-        speed := 1
-    ].
-    "/ FLI uses 1/70th of a second;
-    "/ FLC measures the frameDelay in milliseconds
-    type == FLI_FILE_MAGIC ifTrue:[
-        frameDelay := 1000 * speed // 70
-    ] ifFalse:[
-        frameDelay := speed
-    ].
-
-    frameBufferSize := width * height.
-    frameBuffer := ByteArray uninitializedNew:frameBufferSize.
-
-    redPalette := ByteArray new:256.
-    greenPalette := ByteArray new:256.
-    bluePalette := ByteArray new:256.
-
-    imageSequence := OrderedCollection new:nframes.
-
-    ^ true
-
-    "
-     FLIReader fromFile:'bitmaps/magtape.xpm'    
-     FLIReader fromFile:'/usr/local/FLI/jeffmild.fli'      
-    "
-
-    "Created: 3.4.1997 / 22:09:12 / cg"
-    "Modified: 24.6.1997 / 15:31:39 / cg"
 ! !
 
 !FLIReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/FLIReader.st,v 1.12 2003-05-05 16:51:01 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/FLIReader.st,v 1.13 2003-09-01 14:47:45 cg Exp $'
 ! !
 
 FLIReader initialize!
--- a/FaceReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/FaceReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -83,7 +83,7 @@
     "Modified: 1.2.1997 / 15:01:25 / cg"
 ! !
 
-!FaceReader methodsFor:'reading from file'!
+!FaceReader methodsFor:'reading'!
 
 readImage
     "read an image in my format from my inStream"
@@ -155,7 +155,7 @@
 !FaceReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/FaceReader.st,v 1.28 2003-04-27 15:41:09 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/FaceReader.st,v 1.29 2003-09-01 14:47:36 cg Exp $'
 ! !
 
 FaceReader initialize!
--- a/GIFReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/GIFReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -123,336 +123,7 @@
     "Modified: 10.1.1997 / 15:40:34 / cg"
 ! !
 
-!GIFReader methodsFor:'private-writing'!
-
-assignTransparentPixelIn:image
-    "find an usused pixelValue in the colorMap (or image)."
-
-    |cmap usedPixelValues|
-
-    (cmap := image colorMap) size > 0 ifTrue:[
-	cmap size < 256 ifTrue:[
-	    maskPixel := cmap size.
-	    ^ self
-	]
-    ].
-
-    usedPixelValues := image usedValues.
-    usedPixelValues size < (1 bitShift:image depth) ifTrue:[
-	"/ there must be an unused pixelValue
-	maskPixel := ((0 to:(1 bitShift:image depth)-1) asSet removeAll:(usedPixelValues)) first.
-    ] ifFalse:[
-	Image informationLostQuerySignal
-	    raiseWith:image
-	    errorString:('GIF writer cannot assign a transparent pixel - all pixelValues used by image').
-    ]
-!
-
-checkCodeSize
-    (freeCode > maxCode and: [codeSize < 12])
-	    ifTrue: 
-		    [codeSize := codeSize + 1.
-		    maxCode := (1 bitShift: codeSize) - 1]
-
-    "Created: 14.10.1997 / 18:42:01 / cg"
-!
-
-flushBits
-	remainBitCount = 0
-		ifFalse: 
-			[self nextBytePut: bufByte.
-			remainBitCount := 0].
-	self flushBuffer
-
-    "Modified: 14.10.1997 / 18:58:06 / cg"
-!
-
-flushBuffer
-    bufStream isEmpty ifTrue: [^ self].
-    outStream nextPut: bufStream size.
-    outStream nextPutAll: bufStream contents.
-    bufStream := WriteStream on: (ByteArray new: 256)
-
-    "Modified: 14.10.1997 / 20:46:04 / cg"
-!
-
-flushCode
-	self flushBits
-
-    "Created: 14.10.1997 / 18:57:33 / cg"
-!
-
-nextBitsPut: anInteger
-        | integer writeBitCount shiftCount |
-        shiftCount := 0.
-        remainBitCount = 0
-                ifTrue:
-                        [writeBitCount := 8.
-                        integer := anInteger]
-                ifFalse:
-                        [writeBitCount := remainBitCount.
-                        integer := bufByte + (anInteger bitShift: 8 - remainBitCount)].
-        [writeBitCount < codeSize]
-                whileTrue:
-                        [self nextBytePut: ((integer bitShift: shiftCount) bitAnd: 255).
-                        shiftCount := shiftCount - 8.
-                        writeBitCount := writeBitCount + 8].
-        (remainBitCount := writeBitCount - codeSize) = 0
-                ifTrue: [self nextBytePut: (integer bitShift: shiftCount)]
-                ifFalse: [bufByte := integer bitShift: shiftCount].
-        ^anInteger
-
-    "Modified: 15.10.1997 / 16:50:30 / cg"
-!
-
-nextBytePut: aByte
-	bufStream nextPut: aByte.
-	bufStream size >= 254 ifTrue: [self flushBuffer]
-
-    "Modified: 15.10.1997 / 16:50:52 / cg"
-!
-
-readPixelFrom: bits 
-    | pixel |
-    ypos >= height ifTrue: [^ nil].
-    (maskPixel notNil 
-    and:[(mask pixelAtX:xpos y:ypos) == 0]) ifTrue:[
-	pixel := maskPixel
-    ] ifFalse:[
-	pixel := bits at: ypos * rowByteSize + xpos + 1.
-    ].
-    self updatePixelPosition.
-    ^ pixel
-
-    "Created: 14.10.1997 / 18:43:50 / cg"
-    "Modified: 15.10.1997 / 16:46:43 / cg"
-!
-
-setParameters:bitsPerPixel 
-    clearCode := 1 bitShift:bitsPerPixel.
-    eoiCode := clearCode + 1.
-    freeCode := clearCode + 2.
-    codeSize := bitsPerPixel + 1.
-    maxCode := (1 bitShift: codeSize) - 1
-
-    "Modified: 14.10.1997 / 20:09:48 / cg"
-!
-
-updatePixelPosition
-    (xpos := xpos + 1) >= width ifFalse: [^ self].
-
-    xpos := 0.
-    interlace == true ifFalse:[
-        ypos := ypos + 1.
-        ^ self
-    ].
-
-    pass == 0 ifTrue:[
-        (ypos := ypos + 8) >= height ifTrue:[
-            pass := pass + 1.
-            ypos := 4
-        ].
-        ^ self
-    ].
-    pass == 1 ifTrue:[
-        (ypos := ypos + 8) >= height ifTrue:[
-            pass := pass + 1.
-            ypos := 2
-        ].
-        ^ self
-    ].
-    pass == 2 ifTrue:[
-        (ypos := ypos + 4) >= height ifTrue:[
-            pass := pass + 1.
-            ypos := 1
-        ].
-        ^ self
-    ].
-    pass == 3 ifTrue:[
-        ypos := ypos + 2.
-        ^ self
-    ].
-    ^ self error: 'can''t happen'
-
-    "Modified: 14.10.1997 / 18:44:27 / cg"
-!
-
-writeCode: aCode 
-    self nextBitsPut: aCode
-
-    "Created: 14.10.1997 / 18:38:35 / cg"
-    "Modified: 15.10.1997 / 17:01:47 / cg"
-!
-
-writeCodeAndCheckCodeSize: t1 
-    self writeCode: t1.
-    self checkCodeSize
-
-    "Created: 14.10.1997 / 18:38:24 / cg"
-    "Modified: 14.10.1997 / 18:40:56 / cg"
-! !
-
-!GIFReader methodsFor:'reading from file'!
-
-fromStream:aStream
-    "read a stream containing a GIF image (or an image sequence).
-     Leave image description in instance variables."
-
-    |byte index flag count fileColorMap
-     colorMapSize bitsPerPixel scrWidth scrHeight
-     hasColorMap hasLocalColorMap interlaced id
-     codeLen
-     compressedData compressedSize
-     tmp srcOffset dstOffset isGif89 atEnd
-     h "{ Class: SmallInteger }" 
-     img firstImage firstOffset firstFrameDelay frame imageCount|
-
-    inStream := aStream.
-    aStream binary.
-
-    "GIF-files are always lsb (intel-world)"
-    byteOrder := #lsb.
-
-    id := ByteArray new:6.
-    (aStream nextBytes:6 into:id startingAt:1) ~~ 6 ifTrue:[
-        ^ self fileFormatError:'not a gif file (short read)'.
-    ].
-    id := id asString.
-
-    "all I had for testing where GIF87a files;
-     I hope later versions work too ..."
-
-    isGif89 := false.
-    (id ~= 'GIF87a') ifTrue:[
-        (id startsWith:'GIF') ifFalse:[
-            ^ self fileFormatError:('not a gif file (id=''' , id , ''')').
-        ].
-        id ~= 'GIF89a' ifTrue:[ 
-            'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
-        ]
-    ].
-
-    "get screen dimensions (not used)"
-    scrWidth := aStream nextShortMSB:false.
-    scrHeight := aStream nextShortMSB:false.
-
-    "get flag byte"
-    flag := aStream nextByte.
-    hasColorMap :=      (flag bitAnd:2r10000000) ~~ 0.
-    "bitsPerRGB :=     ((flag bitAnd:2r01110000) bitShift:-4) + 1. "
-    "colorMapSorted := ((flag bitAnd:2r00001000) ~~ 0.             "
-    bitsPerPixel :=     (flag bitAnd:2r00000111) + 1.
-    colorMapSize := 1 bitShift:bitsPerPixel.
-
-    "get background (not used)"
-    aStream nextByte.
-
-    "aspect ratio (not used)"
-    aStream nextByte.
-
-    "get colorMap"
-    hasColorMap ifTrue:[
-        fileColorMap := self readColorMap:colorMapSize.
-    ].
-    colorMap := fileColorMap.
-
-    photometric := #palette.
-    samplesPerPixel := 1.
-    bitsPerSample := #(8).
-
-    imageCount := 0.
-    atEnd := false.
-    [atEnd] whileFalse:[
-        "gif89a extensions"
-
-        byte := aStream nextByte.
-        byte == Extension ifTrue:[
-"/ 'Ext' infoPrintCR.
-            self readExtension:aStream.
-        ] ifFalse:[
-            (byte == Terminator) ifTrue:[
-                atEnd := true
-            ] ifFalse:[
-                "must be image separator"
-                (byte ~~ ImageSeparator) ifTrue:[
-                    ^ self fileFormatError:('corrupted gif file (no IMAGESEP): ' , (byte printStringRadix:16)).
-                ].
-"/ 'Img' infoPrintCR.
-
-                fileColorMap notNil ifTrue:[
-                    colorMap := fileColorMap.
-                ].
-                Object primitiveFailureSignal handle:[:ex |
-                    ^ self fileFormatError:('corrupted gif file').
-                ] do:[
-                    self readImage:aStream.
-                ].
-
-                maskPixel notNil ifTrue:[
-                    "/
-                    "/ ok, there is a maskValue
-                    "/ build a Depth1Image for it.
-                    "/
-                    self buildMaskFromColor:maskPixel
-                ].
-
-                imageCount == 0 ifTrue:[
-                    img := self makeImage.
-                    "/ remember first image in case more come later.
-                    firstImage := img.
-                    firstFrameDelay := frameDelay.
-                    firstOffset := (leftOffs @ topOffs).
-                ] ifFalse:[
-                    imageCount == 1 ifTrue:[
-                        imageSequence := ImageSequence new.
-                        img imageSequence:imageSequence.
-
-                        "/ add frame for first image.
-                        frame := ImageFrame new image:firstImage.
-                        frame delay:firstFrameDelay.
-                        frame offset:firstOffset.
-                        imageSequence add:frame.
-                    ].  
-                    img := self makeImage.
-                    img imageSequence:imageSequence.
-
-                    "/ add frame for this image.
-                    frame := ImageFrame new image:img.
-                    frame delay:frameDelay.
-                    frame offset:(leftOffs @ topOffs).
-                    imageSequence add:frame.
-                ].
-
-                imageCount := imageCount + 1.
-
-                frameDelay := nil.
-
-                aStream atEnd ifTrue:[
-                    atEnd := true.
-                ]
-            ]
-        ].
-    ].
-
-    imageSequence notNil ifTrue:[
-        iterationCount notNil ifTrue:[
-            iterationCount == 0 ifTrue:[
-                imageSequence loop:true.
-            ] ifFalse:[
-                imageSequence loop:false.
-                imageSequence iterationCount:iterationCount.
-            ]
-        ]
-    ].
-
-    "
-     Image fromFile:'/home/cg/work/stx/goodies/bitmaps/gifImages/animated/vrml.gif'
-     Image fromFile:'/home/cg/work/stx/goodies/bitmaps/gifImages/animated/arrow.gif'
-    "
-
-    "Modified: / 5.7.1996 / 17:32:01 / stefan"
-    "Modified: / 21.8.1998 / 22:20:00 / cg"
-!
+!GIFReader methodsFor:'private-reading'!
 
 makeGreyscale
     "not yet implemented/needed"
@@ -745,6 +416,337 @@
     "Modified: / 12.8.1998 / 13:55:32 / cg"
 ! !
 
+!GIFReader methodsFor:'private-writing'!
+
+assignTransparentPixelIn:image
+    "find an usused pixelValue in the colorMap (or image)."
+
+    |cmap usedPixelValues|
+
+    (cmap := image colorMap) size > 0 ifTrue:[
+	cmap size < 256 ifTrue:[
+	    maskPixel := cmap size.
+	    ^ self
+	]
+    ].
+
+    usedPixelValues := image usedValues.
+    usedPixelValues size < (1 bitShift:image depth) ifTrue:[
+	"/ there must be an unused pixelValue
+	maskPixel := ((0 to:(1 bitShift:image depth)-1) asSet removeAll:(usedPixelValues)) first.
+    ] ifFalse:[
+	Image informationLostQuerySignal
+	    raiseWith:image
+	    errorString:('GIF writer cannot assign a transparent pixel - all pixelValues used by image').
+    ]
+!
+
+checkCodeSize
+    (freeCode > maxCode and: [codeSize < 12])
+	    ifTrue: 
+		    [codeSize := codeSize + 1.
+		    maxCode := (1 bitShift: codeSize) - 1]
+
+    "Created: 14.10.1997 / 18:42:01 / cg"
+!
+
+flushBits
+	remainBitCount = 0
+		ifFalse: 
+			[self nextBytePut: bufByte.
+			remainBitCount := 0].
+	self flushBuffer
+
+    "Modified: 14.10.1997 / 18:58:06 / cg"
+!
+
+flushBuffer
+    bufStream isEmpty ifTrue: [^ self].
+    outStream nextPut: bufStream size.
+    outStream nextPutAll: bufStream contents.
+    bufStream := WriteStream on: (ByteArray new: 256)
+
+    "Modified: 14.10.1997 / 20:46:04 / cg"
+!
+
+flushCode
+	self flushBits
+
+    "Created: 14.10.1997 / 18:57:33 / cg"
+!
+
+nextBitsPut: anInteger
+        | integer writeBitCount shiftCount |
+        shiftCount := 0.
+        remainBitCount = 0
+                ifTrue:
+                        [writeBitCount := 8.
+                        integer := anInteger]
+                ifFalse:
+                        [writeBitCount := remainBitCount.
+                        integer := bufByte + (anInteger bitShift: 8 - remainBitCount)].
+        [writeBitCount < codeSize]
+                whileTrue:
+                        [self nextBytePut: ((integer bitShift: shiftCount) bitAnd: 255).
+                        shiftCount := shiftCount - 8.
+                        writeBitCount := writeBitCount + 8].
+        (remainBitCount := writeBitCount - codeSize) = 0
+                ifTrue: [self nextBytePut: (integer bitShift: shiftCount)]
+                ifFalse: [bufByte := integer bitShift: shiftCount].
+        ^anInteger
+
+    "Modified: 15.10.1997 / 16:50:30 / cg"
+!
+
+nextBytePut: aByte
+	bufStream nextPut: aByte.
+	bufStream size >= 254 ifTrue: [self flushBuffer]
+
+    "Modified: 15.10.1997 / 16:50:52 / cg"
+!
+
+readPixelFrom: bits 
+    | pixel |
+    ypos >= height ifTrue: [^ nil].
+    (maskPixel notNil 
+    and:[(mask pixelAtX:xpos y:ypos) == 0]) ifTrue:[
+	pixel := maskPixel
+    ] ifFalse:[
+	pixel := bits at: ypos * rowByteSize + xpos + 1.
+    ].
+    self updatePixelPosition.
+    ^ pixel
+
+    "Created: 14.10.1997 / 18:43:50 / cg"
+    "Modified: 15.10.1997 / 16:46:43 / cg"
+!
+
+setParameters:bitsPerPixel 
+    clearCode := 1 bitShift:bitsPerPixel.
+    eoiCode := clearCode + 1.
+    freeCode := clearCode + 2.
+    codeSize := bitsPerPixel + 1.
+    maxCode := (1 bitShift: codeSize) - 1
+
+    "Modified: 14.10.1997 / 20:09:48 / cg"
+!
+
+updatePixelPosition
+    (xpos := xpos + 1) >= width ifFalse: [^ self].
+
+    xpos := 0.
+    interlace == true ifFalse:[
+        ypos := ypos + 1.
+        ^ self
+    ].
+
+    pass == 0 ifTrue:[
+        (ypos := ypos + 8) >= height ifTrue:[
+            pass := pass + 1.
+            ypos := 4
+        ].
+        ^ self
+    ].
+    pass == 1 ifTrue:[
+        (ypos := ypos + 8) >= height ifTrue:[
+            pass := pass + 1.
+            ypos := 2
+        ].
+        ^ self
+    ].
+    pass == 2 ifTrue:[
+        (ypos := ypos + 4) >= height ifTrue:[
+            pass := pass + 1.
+            ypos := 1
+        ].
+        ^ self
+    ].
+    pass == 3 ifTrue:[
+        ypos := ypos + 2.
+        ^ self
+    ].
+    ^ self error: 'can''t happen'
+
+    "Modified: 14.10.1997 / 18:44:27 / cg"
+!
+
+writeCode: aCode 
+    self nextBitsPut: aCode
+
+    "Created: 14.10.1997 / 18:38:35 / cg"
+    "Modified: 15.10.1997 / 17:01:47 / cg"
+!
+
+writeCodeAndCheckCodeSize: t1 
+    self writeCode: t1.
+    self checkCodeSize
+
+    "Created: 14.10.1997 / 18:38:24 / cg"
+    "Modified: 14.10.1997 / 18:40:56 / cg"
+! !
+
+!GIFReader methodsFor:'reading'!
+
+fromStream:aStream
+    "read a stream containing a GIF image (or an image sequence).
+     Leave image description in instance variables."
+
+    |byte index flag count fileColorMap
+     colorMapSize bitsPerPixel scrWidth scrHeight
+     hasColorMap hasLocalColorMap interlaced id
+     codeLen
+     compressedData compressedSize
+     tmp srcOffset dstOffset isGif89 atEnd
+     h "{ Class: SmallInteger }" 
+     img firstImage firstOffset firstFrameDelay frame imageCount|
+
+    inStream := aStream.
+    aStream binary.
+
+    "GIF-files are always lsb (intel-world)"
+    byteOrder := #lsb.
+
+    id := ByteArray new:6.
+    (aStream nextBytes:6 into:id startingAt:1) ~~ 6 ifTrue:[
+        ^ self fileFormatError:'not a gif file (short read)'.
+    ].
+    id := id asString.
+
+    "all I had for testing where GIF87a files;
+     I hope later versions work too ..."
+
+    isGif89 := false.
+    (id ~= 'GIF87a') ifTrue:[
+        (id startsWith:'GIF') ifFalse:[
+            ^ self fileFormatError:('not a gif file (id=''' , id , ''')').
+        ].
+        id ~= 'GIF89a' ifTrue:[ 
+            'GIFReader [info]: not a GIF87a/GIF89a file - hope that works' infoPrintCR.
+        ]
+    ].
+
+    "get screen dimensions (not used)"
+    scrWidth := aStream nextShortMSB:false.
+    scrHeight := aStream nextShortMSB:false.
+
+    "get flag byte"
+    flag := aStream nextByte.
+    hasColorMap :=      (flag bitAnd:2r10000000) ~~ 0.
+    "bitsPerRGB :=     ((flag bitAnd:2r01110000) bitShift:-4) + 1. "
+    "colorMapSorted := ((flag bitAnd:2r00001000) ~~ 0.             "
+    bitsPerPixel :=     (flag bitAnd:2r00000111) + 1.
+    colorMapSize := 1 bitShift:bitsPerPixel.
+
+    "get background (not used)"
+    aStream nextByte.
+
+    "aspect ratio (not used)"
+    aStream nextByte.
+
+    "get colorMap"
+    hasColorMap ifTrue:[
+        fileColorMap := self readColorMap:colorMapSize.
+    ].
+    colorMap := fileColorMap.
+
+    photometric := #palette.
+    samplesPerPixel := 1.
+    bitsPerSample := #(8).
+
+    imageCount := 0.
+    atEnd := false.
+    [atEnd] whileFalse:[
+        "gif89a extensions"
+
+        byte := aStream nextByte.
+        byte == Extension ifTrue:[
+"/ 'Ext' infoPrintCR.
+            self readExtension:aStream.
+        ] ifFalse:[
+            (byte == Terminator) ifTrue:[
+                atEnd := true
+            ] ifFalse:[
+                "must be image separator"
+                (byte ~~ ImageSeparator) ifTrue:[
+                    ^ self fileFormatError:('corrupted gif file (no IMAGESEP): ' , (byte printStringRadix:16)).
+                ].
+"/ 'Img' infoPrintCR.
+
+                fileColorMap notNil ifTrue:[
+                    colorMap := fileColorMap.
+                ].
+                Object primitiveFailureSignal handle:[:ex |
+                    ^ self fileFormatError:('corrupted gif file').
+                ] do:[
+                    self readImage:aStream.
+                ].
+
+                maskPixel notNil ifTrue:[
+                    "/
+                    "/ ok, there is a maskValue
+                    "/ build a Depth1Image for it.
+                    "/
+                    self buildMaskFromColor:maskPixel
+                ].
+
+                imageCount == 0 ifTrue:[
+                    img := self makeImage.
+                    "/ remember first image in case more come later.
+                    firstImage := img.
+                    firstFrameDelay := frameDelay.
+                    firstOffset := (leftOffs @ topOffs).
+                ] ifFalse:[
+                    imageCount == 1 ifTrue:[
+                        imageSequence := ImageSequence new.
+                        img imageSequence:imageSequence.
+
+                        "/ add frame for first image.
+                        frame := ImageFrame new image:firstImage.
+                        frame delay:firstFrameDelay.
+                        frame offset:firstOffset.
+                        imageSequence add:frame.
+                    ].  
+                    img := self makeImage.
+                    img imageSequence:imageSequence.
+
+                    "/ add frame for this image.
+                    frame := ImageFrame new image:img.
+                    frame delay:frameDelay.
+                    frame offset:(leftOffs @ topOffs).
+                    imageSequence add:frame.
+                ].
+
+                imageCount := imageCount + 1.
+
+                frameDelay := nil.
+
+                aStream atEnd ifTrue:[
+                    atEnd := true.
+                ]
+            ]
+        ].
+    ].
+
+    imageSequence notNil ifTrue:[
+        iterationCount notNil ifTrue:[
+            iterationCount == 0 ifTrue:[
+                imageSequence loop:true.
+            ] ifFalse:[
+                imageSequence loop:false.
+                imageSequence iterationCount:iterationCount.
+            ]
+        ]
+    ].
+
+    "
+     Image fromFile:'/home/cg/work/stx/goodies/bitmaps/gifImages/animated/vrml.gif'
+     Image fromFile:'/home/cg/work/stx/goodies/bitmaps/gifImages/animated/arrow.gif'
+    "
+
+    "Modified: / 5.7.1996 / 17:32:01 / stefan"
+    "Modified: / 21.8.1998 / 22:20:00 / cg"
+! !
+
 !GIFReader methodsFor:'writing to file'!
 
 save:image onFile:aFileName
@@ -983,7 +985,7 @@
 !GIFReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.85 2003-05-07 14:10:10 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.86 2003-09-01 14:47:30 cg Exp $'
 ! !
 
 GIFReader initialize!
--- a/IrisRGBReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/IrisRGBReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -97,7 +97,7 @@
     "Modified: 14.4.1997 / 16:51:58 / cg"
 ! !
 
-!IrisRGBReader methodsFor:'reading from file'!
+!IrisRGBReader methodsFor:'reading'!
 
 fromStream:aStream
     "read a Portable bitmap file format as of Jeff Poskanzers Portable Bitmap Package.
@@ -145,7 +145,9 @@
 
     "Created: / 14.4.1997 / 15:38:51 / cg"
     "Modified: / 1.4.1998 / 14:28:51 / cg"
-!
+! !
+
+!IrisRGBReader methodsFor:'reading-private'!
 
 readRLEData 
     "read RLE compressed data"
@@ -229,7 +231,7 @@
 !IrisRGBReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/IrisRGBReader.st,v 1.9 2003-04-27 15:41:47 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/IrisRGBReader.st,v 1.10 2003-09-01 14:47:57 cg Exp $'
 ! !
 
 IrisRGBReader initialize!
--- a/JPEGReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/JPEGReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -475,7 +475,7 @@
 %}
 ! !
 
-!JPEGReader methodsFor:'reading from stream'!
+!JPEGReader methodsFor:'reading'!
 
 fromStream:aStream
     "read a JPG image from a stream"
@@ -578,7 +578,7 @@
 !JPEGReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/JPEGReader.st,v 1.43 2003-04-10 23:42:19 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/JPEGReader.st,v 1.44 2003-09-01 14:47:42 cg Exp $'
 ! !
 
 JPEGReader initialize!
--- a/PBMReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/PBMReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -171,7 +171,7 @@
     "Created: / 3.2.1998 / 17:20:54 / cg"
 ! !
 
-!PBMReader methodsFor:'reading from file'!
+!PBMReader methodsFor:'reading'!
 
 fromStream:aStream
     "read a Portable bitmap file format as of Jeff Poskanzers Portable Bitmap Package.
@@ -475,7 +475,7 @@
     "Modified: / 7.9.1998 / 15:50:36 / cg"
 ! !
 
-!PBMReader methodsFor:'writing to file'!
+!PBMReader methodsFor:'writing'!
 
 save:image onFile:aFileName
     "save image as PBM/PGM/PNM file on aFileName"
@@ -545,20 +545,6 @@
     "Modified: / 30.9.1998 / 23:30:43 / cg"
 !
 
-writeCommonHeader:format on:aStream
-    "common header for P4, P5 and P5 formats"
-
-    aStream nextPutAll:format; cr.
-    aStream nextPutAll:'# From Smalltalk/X on '.
-    aStream nextPutAll:(Date today printString).
-    aStream nextPutAll:' at '; nextPutAll:(Time now printString).
-    aStream cr.
-    aStream nextPutAll:(width printString); space; nextPutAll:(height printString).
-
-    "Created: / 14.10.1997 / 20:01:05 / cg"
-    "Modified: / 1.4.1998 / 14:30:47 / cg"
-!
-
 writePBMFileOn:aStream
     "Saves the receivers image on the file fileName in Portable Bitmap format."
 
@@ -650,10 +636,26 @@
     "Modified: 14.10.1997 / 20:07:08 / cg"
 ! !
 
+!PBMReader methodsFor:'writing-private'!
+
+writeCommonHeader:format on:aStream
+    "common header for P4, P5 and P5 formats"
+
+    aStream nextPutAll:format; cr.
+    aStream nextPutAll:'# From Smalltalk/X on '.
+    aStream nextPutAll:(Date today printString).
+    aStream nextPutAll:' at '; nextPutAll:(Time now printString).
+    aStream cr.
+    aStream nextPutAll:(width printString); space; nextPutAll:(height printString).
+
+    "Created: / 14.10.1997 / 20:01:05 / cg"
+    "Modified: / 1.4.1998 / 14:30:47 / cg"
+! !
+
 !PBMReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.38 2003-04-10 14:26:08 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/PBMReader.st,v 1.39 2003-09-01 14:47:44 cg Exp $'
 ! !
 
 PBMReader initialize!
--- a/PCXReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/PCXReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -112,7 +112,26 @@
     "Modified: 16.4.1997 / 22:24:32 / cg"
 ! !
 
-!PCXReader methodsFor:'reading from file'!
+!PCXReader methodsFor:'reading'!
+
+readImage
+    "read an image in pcx format from inStream"
+
+    inStream binary.
+
+    header := ByteArray uninitializedNew:128.
+    (inStream nextBytes:128 into:header) == 128 ifFalse:[
+        ^ self fileFormatError:'short file'.
+    ].
+
+    (self class isValidPCXHeader:header) ifFalse:[
+        ^ self fileFormatError:'wrong header'.
+    ].
+
+    self readRestAfterHeader.
+! !
+
+!PCXReader methodsFor:'reading-private'!
 
 extractColorMap16
     "extract the 16-entry colormap from the header"
@@ -212,23 +231,6 @@
     nBuffer := endIndex - bufferIndex.
 !
 
-readImage
-    "read an image in pcx format from inStream"
-
-    inStream binary.
-
-    header := ByteArray uninitializedNew:128.
-    (inStream nextBytes:128 into:header) == 128 ifFalse:[
-        ^ self fileFormatError:'short file'.
-    ].
-
-    (self class isValidPCXHeader:header) ifFalse:[
-        ^ self fileFormatError:'wrong header'.
-    ].
-
-    self readRestAfterHeader.
-!
-
 readRestAfterHeader
     "read an raw image in pcx format from aStream.
      The header has already been read into the header argument."
@@ -358,7 +360,7 @@
 !PCXReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/PCXReader.st,v 1.30 2003-05-05 16:50:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/PCXReader.st,v 1.31 2003-09-01 14:47:48 cg Exp $'
 ! !
 
 PCXReader initialize!
--- a/PNGReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/PNGReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -318,7 +318,7 @@
     "Created: 21.6.1996 / 21:15:58 / cg"
 ! !
 
-!PNGReader methodsFor:'reading from file'!
+!PNGReader methodsFor:'reading'!
 
 fromStream:aStream
     "read a stream containing a PNG image.
@@ -380,7 +380,9 @@
     "
 
     "Modified: 21.6.1996 / 21:44:34 / cg"
-!
+! !
+
+!PNGReader methodsFor:'reading-private'!
 
 setColorType:colorType
     colorType == 0 ifTrue:[
@@ -441,7 +443,7 @@
 !PNGReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/PNGReader.st,v 1.7 2003-05-05 16:51:08 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/PNGReader.st,v 1.8 2003-09-01 14:47:50 cg Exp $'
 ! !
 
 PNGReader initialize!
--- a/ST80FormReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/ST80FormReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -101,7 +101,7 @@
     "Modified: 21.4.1997 / 19:48:56 / cg"
 ! !
 
-!ST80FormReader methodsFor:'reading from file'!
+!ST80FormReader methodsFor:'reading'!
 
 fromStream:aStream
     "read an image in my format from aStream"
@@ -140,7 +140,7 @@
     "Modified: / 4.4.1998 / 18:24:40 / cg"
 ! !
 
-!ST80FormReader methodsFor:'writing to file'!
+!ST80FormReader methodsFor:'writing'!
 
 save:image onFile:aFileName
     "save image as XBM file on aFileName.
@@ -190,7 +190,7 @@
 !ST80FormReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/ST80FormReader.st,v 1.22 2003-04-10 14:25:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/ST80FormReader.st,v 1.23 2003-09-01 14:47:32 cg Exp $'
 ! !
 
 ST80FormReader initialize!
--- a/SunRasterReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/SunRasterReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -117,7 +117,7 @@
     ^ true
 ! !
 
-!SunRasterReader methodsFor:'reading from file'!
+!SunRasterReader methodsFor:'reading'!
 
 fromStream: aStream 
     "read an image in my format from aStream.
@@ -276,7 +276,7 @@
 !SunRasterReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.29 2003-05-05 16:51:04 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/SunRasterReader.st,v 1.30 2003-09-01 14:47:29 cg Exp $'
 ! !
 
 SunRasterReader initialize!
--- a/TIFFReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/TIFFReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -1968,7 +1968,7 @@
 "
 ! !
 
-!TIFFReader methodsFor:'reading from file'!
+!TIFFReader methodsFor:'reading'!
 
 fromStream:aStream
     "read a stream containing a TIFF image.
@@ -2109,7 +2109,7 @@
     "Modified: / 3.2.1998 / 18:02:29 / cg"
 ! !
 
-!TIFFReader methodsFor:'writing to file'!
+!TIFFReader methodsFor:'writing'!
 
 save:image onFile:aFileName
     "save image as (uncompressed) TIFF file on aFileName"
@@ -2221,7 +2221,7 @@
 !TIFFReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/TIFFReader.st,v 1.74 2003-06-21 09:56:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/TIFFReader.st,v 1.75 2003-09-01 14:47:53 cg Exp $'
 ! !
 
 TIFFReader initialize!
--- a/TargaReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/TargaReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -159,7 +159,144 @@
     "Modified: 21.4.1997 / 20:46:52 / cg"
 ! !
 
-!TargaReader methodsFor:'reading from file'!
+!TargaReader methodsFor:'reading'!
+
+readImage
+    "read a targa-image from aFileName. return the receiver (with all
+     relevant instance variables set for the image) or nil on error"
+
+    |depth flags lenID hasColorMap imageType 
+     cmapOffset cmapLength cmapEntrySize xOrg yOrg rle|
+
+    inStream binary.
+
+    lenID := inStream next.
+    hasColorMap := inStream next.
+    imageType := inStream next.
+    cmapOffset := inStream nextShortMSB:false.
+    cmapLength := inStream nextShortMSB:false.
+    cmapEntrySize := inStream next.
+    xOrg := inStream nextShortMSB:false.
+    yOrg := inStream nextShortMSB:false.
+
+    width := inStream nextShortMSB:false.
+    height := inStream nextShortMSB:false.
+    depth := inStream next.
+    (#(8 "16" 24 32) includes:depth) ifFalse:[
+        ^ self fileFormatError:('unsupported depth: ', depth printString).
+    ].
+    depth == 32 ifTrue:[
+        'TargaReader [info]: alpha channel ignored' infoPrintCR.
+    ] ifFalse:[
+        'TargaReader [info]: depth: ' infoPrint. depth infoPrintCR.
+    ].
+
+    "/ MapRGB == 1
+    "/ RawRGB == 2
+    "/ RawMono == 3
+    "/ MapEnCode == 9
+    "/ RawEnCode == 10
+
+    (#(1 2 9 10) includes:imageType) ifFalse:[
+        "/ 'TargaReader [warning]: unsupported imageType: ' errorPrint. imageType errorPrintCR.
+        ^ self fileFormatError:('unsupported imageType: ', imageType printString).
+    ].
+    'TargaReader [info]: imageType: ' infoPrint. imageType infoPrintCR.
+
+    "/ flags:
+    "/    0000 xxxx  attribute-bits-per-pixel
+    "/    0000 0001  greysc
+    "/    0000 0010  colour
+    "/    0000 0011  mapped
+    "/    0000 0100  rleEncoded
+    "/    0000 1000  interlaced
+    "/    00xx 0000  origin (0 -> lower-left / 1 -> l-r / 2 -> u-l / 3 -> u-r)
+    "/    xx00 0000  interleave (0 -> none / 1 -> odd/even / 2 ->4-fould / 3 reserved)
+    "/
+    flags := inStream next.
+
+    (flags bitAnd:2r11000000) ~~ 0 ifTrue:[
+        ^ self fileFormatError:('unsupported interlace: ' , flags printString).
+    ].
+
+    rle := flags bitTest:2r000001000.
+    flags := flags bitAnd:2r111110111.
+
+    (flags bitAnd:2r00001111) ~~ 0 ifTrue:[
+        ^ self fileFormatError:('unsupported flags: ' , flags printString).
+    ].
+
+    (flags bitAnd:2r00110000) == 16r20 ifTrue:[
+        orientation := #topLeft
+    ] ifFalse:[
+        (flags bitAnd:2r00110000) == 16r30 ifTrue:[
+            orientation := #topRight
+        ] ifFalse:[
+            (flags bitAnd:2r00110000) == 16r10 ifTrue:[
+                orientation := #bottomRight
+            ] ifFalse:[
+                (flags bitAnd:2r00110000) == 0 ifTrue:[
+                    orientation := #bottomLeft
+                ]
+            ]
+        ]
+    ].
+
+    lenID ~~ 0 ifTrue:[
+        inStream skip:lenID
+    ].
+
+    hasColorMap ~~ 0 ifTrue:[
+        "/ read the colorMap
+        colorMap := self readColorMap:cmapLength.
+        'TargaReader [info]: has colorMap' infoPrintCR.
+    ].
+
+    depth == 32 ifTrue:[
+        imageType == 2 ifTrue:[
+"/            rle ifTrue:[self halt:'oops - should not happen'].
+            self read32.
+        ] ifFalse:[
+"/            rle ifFalse:[self halt:'oops - should not happen'].
+            self read32RLE.
+        ].
+        bytesPerRow := width*3.
+        bytesPerPixel := 3.
+    ].
+    depth == 24 ifTrue:[
+        imageType == 2 ifTrue:[
+"/            rle ifTrue:[self halt:'oops - should not happen'].
+            self read24.
+        ] ifFalse:[
+"/            rle ifFalse:[self halt:'oops - should not happen'].
+            self read24RLE.
+        ].
+        bytesPerRow := width*3.
+        bytesPerPixel := 3.
+    ].
+    depth == 8 ifTrue:[
+        imageType == 1 ifTrue:[
+"/            rle ifTrue:[self halt:'oops - should not happen'].
+            self read8.
+        ] ifFalse:[
+"/            rle ifFalse:[self halt:'oops - should not happen'].
+            self read8RLE
+        ].
+        bytesPerRow := width.
+        bytesPerPixel := 1.
+    ].
+
+    self handleImageOrientation.
+
+    "
+     TargaReader fromFile:'bitmaps/test.tga' 
+    "
+
+    "Modified: / 7.9.1998 / 21:12:12 / cg"
+    "Modified: / 13.10.1998 / 19:50:48 / ps"
+! !
+
+!TargaReader methodsFor:'reading-private'!
 
 handleImageOrientation
     |rowIdx startIdx endIdx t|
@@ -408,147 +545,12 @@
         colorMap at:index put:(Color redByte:r greenByte:g blueByte:b).
     ].
     ^ colorMap
-!
-
-readImage
-    "read a targa-image from aFileName. return the receiver (with all
-     relevant instance variables set for the image) or nil on error"
-
-    |depth flags lenID hasColorMap imageType 
-     cmapOffset cmapLength cmapEntrySize xOrg yOrg rle|
-
-    inStream binary.
-
-    lenID := inStream next.
-    hasColorMap := inStream next.
-    imageType := inStream next.
-    cmapOffset := inStream nextShortMSB:false.
-    cmapLength := inStream nextShortMSB:false.
-    cmapEntrySize := inStream next.
-    xOrg := inStream nextShortMSB:false.
-    yOrg := inStream nextShortMSB:false.
-
-    width := inStream nextShortMSB:false.
-    height := inStream nextShortMSB:false.
-    depth := inStream next.
-    (#(8 "16" 24 32) includes:depth) ifFalse:[
-        ^ self fileFormatError:('unsupported depth: ', depth printString).
-    ].
-    depth == 32 ifTrue:[
-        'TargaReader [info]: alpha channel ignored' infoPrintCR.
-    ] ifFalse:[
-        'TargaReader [info]: depth: ' infoPrint. depth infoPrintCR.
-    ].
-
-    "/ MapRGB == 1
-    "/ RawRGB == 2
-    "/ RawMono == 3
-    "/ MapEnCode == 9
-    "/ RawEnCode == 10
-
-    (#(1 2 9 10) includes:imageType) ifFalse:[
-        "/ 'TargaReader [warning]: unsupported imageType: ' errorPrint. imageType errorPrintCR.
-        ^ self fileFormatError:('unsupported imageType: ', imageType printString).
-    ].
-    'TargaReader [info]: imageType: ' infoPrint. imageType infoPrintCR.
-
-    "/ flags:
-    "/    0000 xxxx  attribute-bits-per-pixel
-    "/    0000 0001  greysc
-    "/    0000 0010  colour
-    "/    0000 0011  mapped
-    "/    0000 0100  rleEncoded
-    "/    0000 1000  interlaced
-    "/    00xx 0000  origin (0 -> lower-left / 1 -> l-r / 2 -> u-l / 3 -> u-r)
-    "/    xx00 0000  interleave (0 -> none / 1 -> odd/even / 2 ->4-fould / 3 reserved)
-    "/
-    flags := inStream next.
-
-    (flags bitAnd:2r11000000) ~~ 0 ifTrue:[
-        ^ self fileFormatError:('unsupported interlace: ' , flags printString).
-    ].
-
-    rle := flags bitTest:2r000001000.
-    flags := flags bitAnd:2r111110111.
-
-    (flags bitAnd:2r00001111) ~~ 0 ifTrue:[
-        ^ self fileFormatError:('unsupported flags: ' , flags printString).
-    ].
-
-    (flags bitAnd:2r00110000) == 16r20 ifTrue:[
-        orientation := #topLeft
-    ] ifFalse:[
-        (flags bitAnd:2r00110000) == 16r30 ifTrue:[
-            orientation := #topRight
-        ] ifFalse:[
-            (flags bitAnd:2r00110000) == 16r10 ifTrue:[
-                orientation := #bottomRight
-            ] ifFalse:[
-                (flags bitAnd:2r00110000) == 0 ifTrue:[
-                    orientation := #bottomLeft
-                ]
-            ]
-        ]
-    ].
-
-    lenID ~~ 0 ifTrue:[
-        inStream skip:lenID
-    ].
-
-    hasColorMap ~~ 0 ifTrue:[
-        "/ read the colorMap
-        colorMap := self readColorMap:cmapLength.
-        'TargaReader [info]: has colorMap' infoPrintCR.
-    ].
-
-    depth == 32 ifTrue:[
-        imageType == 2 ifTrue:[
-"/            rle ifTrue:[self halt:'oops - should not happen'].
-            self read32.
-        ] ifFalse:[
-"/            rle ifFalse:[self halt:'oops - should not happen'].
-            self read32RLE.
-        ].
-        bytesPerRow := width*3.
-        bytesPerPixel := 3.
-    ].
-    depth == 24 ifTrue:[
-        imageType == 2 ifTrue:[
-"/            rle ifTrue:[self halt:'oops - should not happen'].
-            self read24.
-        ] ifFalse:[
-"/            rle ifFalse:[self halt:'oops - should not happen'].
-            self read24RLE.
-        ].
-        bytesPerRow := width*3.
-        bytesPerPixel := 3.
-    ].
-    depth == 8 ifTrue:[
-        imageType == 1 ifTrue:[
-"/            rle ifTrue:[self halt:'oops - should not happen'].
-            self read8.
-        ] ifFalse:[
-"/            rle ifFalse:[self halt:'oops - should not happen'].
-            self read8RLE
-        ].
-        bytesPerRow := width.
-        bytesPerPixel := 1.
-    ].
-
-    self handleImageOrientation.
-
-    "
-     TargaReader fromFile:'bitmaps/test.tga' 
-    "
-
-    "Modified: / 7.9.1998 / 21:12:12 / cg"
-    "Modified: / 13.10.1998 / 19:50:48 / ps"
 ! !
 
 !TargaReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/TargaReader.st,v 1.22 2003-04-10 14:25:18 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/TargaReader.st,v 1.23 2003-09-01 14:47:27 cg Exp $'
 ! !
 
 TargaReader initialize!
--- a/WindowsIconReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/WindowsIconReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -356,7 +356,7 @@
     "Modified: / 3.2.1998 / 20:21:16 / cg"
 ! !
 
-!WindowsIconReader methodsFor:'reading from file'!
+!WindowsIconReader methodsFor:'reading'!
 
 fromOS2File:aFilename
     "read an image from an OS/2 BMP file"
@@ -822,7 +822,9 @@
     "
 
     "Modified: / 18.5.1999 / 15:40:00 / cg"
-!
+! !
+
+!WindowsIconReader methodsFor:'reading-private'!
 
 readColorMap:nColors numBytesPerColor:nRawBytesPerColor from:aStream
     "read the colormap; notice: its in BGR order (sigh)."
@@ -858,7 +860,7 @@
         blueVector:bMap.
 ! !
 
-!WindowsIconReader methodsFor:'writing to file'!
+!WindowsIconReader methodsFor:'writing'!
 
 save:image onFile:aFileName
     "save image as BMP file on aFileName.
@@ -1104,7 +1106,7 @@
 !WindowsIconReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/WindowsIconReader.st,v 1.55 2003-08-18 22:33:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/WindowsIconReader.st,v 1.56 2003-09-01 14:47:47 cg Exp $'
 ! !
 
 WindowsIconReader initialize!
--- a/XBMReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/XBMReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -153,7 +153,7 @@
     "Modified: / 18.3.1999 / 11:33:39 / cg"
 ! !
 
-!XBMReader methodsFor:'reading from file'!
+!XBMReader methodsFor:'reading'!
 
 fromStream:aStream
     "read an image in xbm format from aStream"
@@ -278,7 +278,7 @@
     "Modified: / 18.3.1999 / 11:32:46 / cg"
 ! !
 
-!XBMReader methodsFor:'writing to file'!
+!XBMReader methodsFor:'writing'!
 
 save:image onFile:aFileName
     "save image as XBM file on aFileName.
@@ -365,7 +365,7 @@
 !XBMReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.47 2003-04-10 14:25:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.48 2003-09-01 14:47:52 cg Exp $'
 ! !
 
 XBMReader initialize!
--- a/XPMReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/XPMReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -131,7 +131,166 @@
     "Modified: 24.4.1997 / 20:29:40 / cg"
 ! !
 
-!XPMReader methodsFor:'reading from file'!
+!XPMReader methodsFor:'reading'!
+
+readImage
+    "read an XPM-image from my inStream. Return the receiver 
+     (with all relevant instance variables set for the image) 
+     or nil on error"
+
+    |line 
+     srcIndex "{ Class: SmallInteger }"
+     dstIndex "{ Class: SmallInteger }"
+     colorMapSize   
+     s bitsPerPixel key lastKey lastChar1 lastChar2 c1 c2 lastXLation|
+
+    line := inStream nextLine.
+    (line notNil and:[line startsWith:'/* XPM']) ifFalse:[
+        ^ self fileFormatError:'format error (expected XPM)'.
+    ].
+
+    line := inStream nextLine.
+    [line notNil and:[(line startsWith:'/*') or:[line isBlank or:[(line startsWith:' *')]]]] whileTrue:[
+        line := inStream nextLine.
+    ].
+    (line notNil and:[line startsWith:'static char']) ifFalse:[
+        ^ self fileFormatError:'format error (expected static char)'.
+    ].
+    line := inStream nextLine.
+    (line notNil and:[line startsWith:'/*']) ifTrue:[
+        [line notNil 
+         and:[(line startsWith:'/*') or:[line startsWith:' *']]] whileTrue:[
+            line := inStream nextLine.
+        ].
+    ].
+    line notNil ifTrue:[
+        line := line withoutSeparators
+    ].
+    (line notNil and:[line startsWith:'"']) ifFalse:[
+        ^ self fileFormatError:'format error (expected "ww hh nn mm)'.
+    ].
+    s := ReadStream on:line.
+    s next.  "skip quote"
+    width := Integer readFrom:s.
+    height := Integer readFrom:s.
+    colorMapSize := Integer readFrom:s.
+    charsPerPixel := Integer readFrom:s.
+
+    charsPerPixel ~~ 1 ifTrue:[
+        characterTranslation := Dictionary new:colorMapSize.
+    ] ifFalse:[
+        characterTranslation := Array new:256.
+    ].
+
+    self readColorMap:colorMapSize.
+
+    "actually, could make it an image with less depth most of the time ..."
+
+"
+    bitsPerPixel := ((colorMapSize - 1) log:2) truncated + 1.
+"
+    colorMapSize > 256 ifTrue:[
+        bitsPerPixel := 24.
+        data := ByteArray new:(width * height * 3).
+    ] ifFalse:[
+        bitsPerPixel := 8.
+        data := ByteArray new:(width * height).
+    ].
+
+    dstIndex := 1.
+    1 to:height do:[:row |
+        line := inStream nextLine withoutSpaces.
+        [line notNil and:[line startsWith:'/*']] whileTrue:[
+            line := inStream nextLine withoutSpaces.
+        ].
+        line notNil ifTrue:[
+            line := line withoutSeparators
+        ].
+        (line notNil and:[line startsWith:'"']) ifFalse:[
+            ^ self fileFormatError:'format error (expected pixels)'.
+        ].
+        charsPerPixel == 1 ifTrue:[
+            srcIndex := 2. "skip dquote"
+            1 to:width do:[:col |
+                key := line at:srcIndex.
+                key ~~ lastKey ifTrue:[
+                    lastXLation := characterTranslation at:key asciiValue.
+                    lastKey := key
+                ].
+                data at:dstIndex put:lastXLation.
+                srcIndex := srcIndex + 1.
+                dstIndex := dstIndex + 1
+            ]
+        ] ifFalse:[
+            charsPerPixel == 2 ifTrue:[
+                "/ sorry, but this ugly code does a lot for speed,
+                "/ when reading big Xpm files (factor=5 for banner8.xpm)  ...
+                srcIndex := 2."skip dquote"
+                lastChar1 := lastChar2 := nil.
+                key := String new:2.
+                1 to:width do:[:col |
+                    c1 := line at:srcIndex.
+                    c2 := line at:srcIndex+1.
+                    (c1 ~~ lastChar1 or:[c2 ~~ lastChar2]) ifTrue:[
+                        key at:1 put:c1.
+                        key at:2 put:c2.
+                        lastXLation := characterTranslation at:key.
+                        lastChar1 := c1.
+                        lastChar2 := c2.
+                    ].
+                    bitsPerPixel == 24 ifTrue:[
+                        data at:dstIndex   put:(colorMap at:lastXLation+1) redByte.
+                        data at:dstIndex+1 put:(colorMap at:lastXLation+1) greenByte.
+                        data at:dstIndex+2 put:(colorMap at:lastXLation+1) blueByte.
+                        dstIndex := dstIndex + 3.
+                    ] ifFalse:[
+                        data at:dstIndex put:lastXLation.
+                        dstIndex := dstIndex + 1.
+                    ].
+                    srcIndex := srcIndex + 2.
+                ]
+            ] ifFalse:[
+                s := line readStream.
+                s next. "/ skip dquote
+                1 to:width do:[:col |
+                    key := s next:charsPerPixel.
+"/                data at:dstIndex put:(characterTranslation at:key).
+                    key ~= lastKey ifTrue:[
+                        lastXLation := characterTranslation at:key.
+                        lastKey := key
+                    ].
+                    data at:dstIndex put:lastXLation.
+                    dstIndex := dstIndex + 1
+                ]
+            ]
+        ]
+    ].
+
+    bitsPerPixel == 24 ifTrue:[
+        photometric := #rgb.
+        samplesPerPixel := 3.
+        bitsPerSample := #(8 8 8).
+    ] ifFalse:[
+        photometric := #palette.
+        samplesPerPixel := 1.
+        bitsPerSample := Array with:bitsPerPixel.
+    ].
+
+    maskPixelValue notNil ifTrue:[
+        self buildMaskFromColor:maskPixelValue
+    ].
+
+    "
+     XPMReader fromStream:('../../goodies/bitmaps/xpmBitmaps/FATAL.xpm' asFilename readStream)
+    "
+
+    "Created: / 24.9.1995 / 06:20:06 / claus"
+    "Modified: / 24.9.1995 / 07:07:33 / claus"
+    "Modified: / 5.7.1996 / 17:27:59 / stefan"
+    "Modified: / 27.7.1998 / 20:01:56 / cg"
+! !
+
+!XPMReader methodsFor:'reading-private'!
 
 colorNameFrom:aStream
     "read either a color-name or value specified in X-notation
@@ -294,185 +453,9 @@
     ].
 
     colorMap := MappedPalette redVector:redMap greenVector:greenMap blueVector:blueMap.
-!
-
-readImage
-    "read an XPM-image from my inStream. Return the receiver 
-     (with all relevant instance variables set for the image) 
-     or nil on error"
-
-    |line 
-     srcIndex "{ Class: SmallInteger }"
-     dstIndex "{ Class: SmallInteger }"
-     colorMapSize   
-     s bitsPerPixel key lastKey lastChar1 lastChar2 c1 c2 lastXLation|
-
-    line := inStream nextLine.
-    (line notNil and:[line startsWith:'/* XPM']) ifFalse:[
-        ^ self fileFormatError:'format error (expected XPM)'.
-    ].
-
-    line := inStream nextLine.
-    [line notNil and:[(line startsWith:'/*') or:[line isBlank or:[(line startsWith:' *')]]]] whileTrue:[
-        line := inStream nextLine.
-    ].
-    (line notNil and:[line startsWith:'static char']) ifFalse:[
-        ^ self fileFormatError:'format error (expected static char)'.
-    ].
-    line := inStream nextLine.
-    (line notNil and:[line startsWith:'/*']) ifTrue:[
-        [line notNil 
-         and:[(line startsWith:'/*') or:[line startsWith:' *']]] whileTrue:[
-            line := inStream nextLine.
-        ].
-    ].
-    line notNil ifTrue:[
-        line := line withoutSeparators
-    ].
-    (line notNil and:[line startsWith:'"']) ifFalse:[
-        ^ self fileFormatError:'format error (expected "ww hh nn mm)'.
-    ].
-    s := ReadStream on:line.
-    s next.  "skip quote"
-    width := Integer readFrom:s.
-    height := Integer readFrom:s.
-    colorMapSize := Integer readFrom:s.
-    charsPerPixel := Integer readFrom:s.
-
-    charsPerPixel ~~ 1 ifTrue:[
-        characterTranslation := Dictionary new:colorMapSize.
-    ] ifFalse:[
-        characterTranslation := Array new:256.
-    ].
-
-    self readColorMap:colorMapSize.
-
-    "actually, could make it an image with less depth most of the time ..."
-
-"
-    bitsPerPixel := ((colorMapSize - 1) log:2) truncated + 1.
-"
-    colorMapSize > 256 ifTrue:[
-        bitsPerPixel := 24.
-        data := ByteArray new:(width * height * 3).
-    ] ifFalse:[
-        bitsPerPixel := 8.
-        data := ByteArray new:(width * height).
-    ].
-
-    dstIndex := 1.
-    1 to:height do:[:row |
-        line := inStream nextLine withoutSpaces.
-        [line notNil and:[line startsWith:'/*']] whileTrue:[
-            line := inStream nextLine withoutSpaces.
-        ].
-        line notNil ifTrue:[
-            line := line withoutSeparators
-        ].
-        (line notNil and:[line startsWith:'"']) ifFalse:[
-            ^ self fileFormatError:'format error (expected pixels)'.
-        ].
-        charsPerPixel == 1 ifTrue:[
-            srcIndex := 2. "skip dquote"
-            1 to:width do:[:col |
-                key := line at:srcIndex.
-                key ~~ lastKey ifTrue:[
-                    lastXLation := characterTranslation at:key asciiValue.
-                    lastKey := key
-                ].
-                data at:dstIndex put:lastXLation.
-                srcIndex := srcIndex + 1.
-                dstIndex := dstIndex + 1
-            ]
-        ] ifFalse:[
-            charsPerPixel == 2 ifTrue:[
-                "/ sorry, but this ugly code does a lot for speed,
-                "/ when reading big Xpm files (factor=5 for banner8.xpm)  ...
-                srcIndex := 2."skip dquote"
-                lastChar1 := lastChar2 := nil.
-                key := String new:2.
-                1 to:width do:[:col |
-                    c1 := line at:srcIndex.
-                    c2 := line at:srcIndex+1.
-                    (c1 ~~ lastChar1 or:[c2 ~~ lastChar2]) ifTrue:[
-                        key at:1 put:c1.
-                        key at:2 put:c2.
-                        lastXLation := characterTranslation at:key.
-                        lastChar1 := c1.
-                        lastChar2 := c2.
-                    ].
-                    bitsPerPixel == 24 ifTrue:[
-                        data at:dstIndex   put:(colorMap at:lastXLation+1) redByte.
-                        data at:dstIndex+1 put:(colorMap at:lastXLation+1) greenByte.
-                        data at:dstIndex+2 put:(colorMap at:lastXLation+1) blueByte.
-                        dstIndex := dstIndex + 3.
-                    ] ifFalse:[
-                        data at:dstIndex put:lastXLation.
-                        dstIndex := dstIndex + 1.
-                    ].
-                    srcIndex := srcIndex + 2.
-                ]
-            ] ifFalse:[
-                s := line readStream.
-                s next. "/ skip dquote
-                1 to:width do:[:col |
-                    key := s next:charsPerPixel.
-"/                data at:dstIndex put:(characterTranslation at:key).
-                    key ~= lastKey ifTrue:[
-                        lastXLation := characterTranslation at:key.
-                        lastKey := key
-                    ].
-                    data at:dstIndex put:lastXLation.
-                    dstIndex := dstIndex + 1
-                ]
-            ]
-        ]
-    ].
-
-    bitsPerPixel == 24 ifTrue:[
-        photometric := #rgb.
-        samplesPerPixel := 3.
-        bitsPerSample := #(8 8 8).
-    ] ifFalse:[
-        photometric := #palette.
-        samplesPerPixel := 1.
-        bitsPerSample := Array with:bitsPerPixel.
-    ].
-
-    maskPixelValue notNil ifTrue:[
-        self buildMaskFromColor:maskPixelValue
-    ].
-
-    "
-     XPMReader fromStream:('../../goodies/bitmaps/xpmBitmaps/FATAL.xpm' asFilename readStream)
-    "
-
-    "Created: / 24.9.1995 / 06:20:06 / claus"
-    "Modified: / 24.9.1995 / 07:07:33 / claus"
-    "Modified: / 5.7.1996 / 17:27:59 / stefan"
-    "Modified: / 27.7.1998 / 20:01:56 / cg"
 ! !
 
-!XPMReader methodsFor:'writing to file'!
-
-colorNameOf:aColor
-    "generate a name for a color. If its a standard color,
-     return its name; otherwise return the hex representation."
-
-    #(white black red green blue
-      yellow magenta cyan orange) do:[:aStandardColorName |
-        aColor = (Color name:aStandardColorName) ifTrue:[
-            ^ aStandardColorName.
-        ]
-    ].
-    ^ '#' 
-     , (aColor redByte hexPrintString:2)
-     , (aColor greenByte hexPrintString:2)
-     , (aColor blueByte hexPrintString:2)
-
-    "Created: / 27.2.1997 / 11:48:40 / cg"
-    "Modified: / 6.6.1998 / 20:58:49 / cg"
-!
+!XPMReader methodsFor:'writing'!
 
 save:image onFile:aFileName
     "save image as XPM file on aFileName.
@@ -575,10 +558,31 @@
     "Modified: / 28.7.1998 / 21:52:13 / cg"
 ! !
 
+!XPMReader methodsFor:'writing-private'!
+
+colorNameOf:aColor
+    "generate a name for a color. If its a standard color,
+     return its name; otherwise return the hex representation."
+
+    #(white black red green blue
+      yellow magenta cyan orange) do:[:aStandardColorName |
+        aColor = (Color name:aStandardColorName) ifTrue:[
+            ^ aStandardColorName.
+        ]
+    ].
+    ^ '#' 
+     , (aColor redByte hexPrintString:2)
+     , (aColor greenByte hexPrintString:2)
+     , (aColor blueByte hexPrintString:2)
+
+    "Created: / 27.2.1997 / 11:48:40 / cg"
+    "Modified: / 6.6.1998 / 20:58:49 / cg"
+! !
+
 !XPMReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.53 2003-05-05 16:50:53 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/XPMReader.st,v 1.54 2003-09-01 14:47:55 cg Exp $'
 ! !
 
 XPMReader initialize!
--- a/XWDReader.st	Mon Sep 01 11:52:06 2003 +0200
+++ b/XWDReader.st	Mon Sep 01 16:47:57 2003 +0200
@@ -82,7 +82,7 @@
     ^ true
 ! !
 
-!XWDReader methodsFor:'image reading'!
+!XWDReader methodsFor:'reading'!
 
 readImage
     "read an image in XWD (X Window Dump) format from my inStream."
@@ -163,7 +163,7 @@
     "
 ! !
 
-!XWDReader methodsFor:'image writing'!
+!XWDReader methodsFor:'writing'!
 
 save:image onFile:fileName
     "Save as a version 7 color X11 window dump file (xwd) to the file fileName.
@@ -299,7 +299,7 @@
 !XWDReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/XWDReader.st,v 1.24 2003-04-27 15:44:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/XWDReader.st,v 1.25 2003-09-01 14:47:38 cg Exp $'
 ! !
 
 XWDReader initialize!