checkin from browser
authorClaus Gittinger <cg@exept.de>
Thu, 07 Dec 1995 12:39:00 +0100
changeset 135 ff507d9a242b
parent 134 f83c245371c2
child 136 69c9d2368352
checkin from browser
GIFReader.st
TIFFRdr.st
TIFFReader.st
XBMReader.st
--- a/GIFReader.st	Thu Dec 07 11:34:06 1995 +0100
+++ b/GIFReader.st	Thu Dec 07 12:39:00 1995 +0100
@@ -10,8 +10,6 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 2:18:24 am'!
-
 ImageReader subclass:#GIFReader
 	 instanceVariableNames:'redMap greenMap blueMap'
 	 classVariableNames:''
@@ -35,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.19 1995-11-11 16:04:30 cg Exp $'
-!
-
 documentation
 "
     this class provides methods for loading and saving GIF pictures.
@@ -93,25 +87,6 @@
 
 !GIFReader methodsFor:'reading from file'!
 
-readColorMap:colorMapSize
-    "get gif colormap consisting of colorMapSize entries"
-
-    |sz "{ Class: SmallInteger }"|
-
-"/    redMap := Array new:colorMapSize.
-"/    greenMap := Array new:colorMapSize.
-"/    blueMap := Array new:colorMapSize.
-    redMap := ByteArray uninitializedNew:colorMapSize.
-    greenMap := ByteArray uninitializedNew:colorMapSize.
-    blueMap := ByteArray uninitializedNew:colorMapSize.
-    sz := colorMapSize.
-    1 to:sz do:[:i |
-	redMap at:i put:(inStream nextByte).
-	greenMap at:i put:(inStream nextByte).
-	blueMap at:i put:(inStream nextByte)
-    ]
-!
-
 checkGreyscaleColormap
     "return true, if colormap is really a greymap"
 
@@ -128,10 +103,6 @@
     ^ true
 !
 
-makeGreyscale
-    "not yet implemented/needed"
-!
-
 fromStream:aStream
     "read a GIF file"
 
@@ -309,6 +280,34 @@
      GIFReader fromFile:'../fileIn/bitmaps/claus.gif
      GIFReader fromFile:'../fileIn/bitmaps/garfield.gif'
     "
+!
+
+makeGreyscale
+    "not yet implemented/needed"
+!
+
+readColorMap:colorMapSize
+    "get gif colormap consisting of colorMapSize entries"
+
+    |sz "{ Class: SmallInteger }"|
+
+"/    redMap := Array new:colorMapSize.
+"/    greenMap := Array new:colorMapSize.
+"/    blueMap := Array new:colorMapSize.
+    redMap := ByteArray uninitializedNew:colorMapSize.
+    greenMap := ByteArray uninitializedNew:colorMapSize.
+    blueMap := ByteArray uninitializedNew:colorMapSize.
+    sz := colorMapSize.
+    1 to:sz do:[:i |
+	redMap at:i put:(inStream nextByte).
+	greenMap at:i put:(inStream nextByte).
+	blueMap at:i put:(inStream nextByte)
+    ]
 ! !
 
+!GIFReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/GIFReader.st,v 1.20 1995-12-07 11:38:12 cg Exp $'
+! !
 GIFReader initialize!
--- a/TIFFRdr.st	Thu Dec 07 11:34:06 1995 +0100
+++ b/TIFFRdr.st	Thu Dec 07 12:39:00 1995 +0100
@@ -11,13 +11,10 @@
 "
 
 ImageReader subclass:#TIFFReader
-	 instanceVariableNames:'planarConfiguration
-				subFileType stripOffsets rowsPerStrip
-				fillOrder compression group3options predictor
-				stripByteCounts
-				currentOffset 
-				stripOffsetsPos stripByteCountsPos bitsPerSamplePos
-				colorMapPos'
+	 instanceVariableNames:'planarConfiguration subFileType stripOffsets rowsPerStrip
+                fillOrder compression group3options predictor stripByteCounts
+                currentOffset stripOffsetsPos stripByteCountsPos bitsPerSamplePos
+                colorMapPos'
 	 classVariableNames:''
 	 poolDictionaries:''
 	 category:'Graphics-Images support'
@@ -39,10 +36,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/Attic/TIFFRdr.st,v 1.26 1995-11-22 12:06:32 cg Exp $'
-!
-
 documentation
 "
     This class knows how to read TIFF files and how to
@@ -74,6 +67,13 @@
 
 !TIFFReader class methodsFor:'testing'!
 
+canRepresent:anImage
+    "return true, if anImage can be represented in my file format.
+     Any image is supported."
+
+    ^ true
+!
+
 isValidImageFile:aFileName
     "return true, if aFileName contains a GIF image"
 
@@ -96,364 +96,10 @@
 
     (version ~~ 42) ifTrue:[^ false].
     ^ true
-!
-
-canRepresent:anImage
-    "return true, if anImage can be represented in my file format.
-     Any image is supported."
-
-    ^ true
-! !
-
-!TIFFReader methodsFor:'reading from file'!
-
-fromStream:aStream
-    "read an image from aStream"
-
-    |char1 char2 version 
-     numberOfTags "{ Class: SmallInteger }"
-     tagType      "{ Class: SmallInteger }"
-     numberType   "{ Class: SmallInteger }"
-     length       "{ Class: SmallInteger }"
-     result offset ok msb|
-
-    inStream := aStream.
-
-    char1 := aStream next.
-    char2 := aStream next.
-    (char1 ~~ char2) ifTrue:[
-	'TIFFReader: not a tiff file' errorPrintNL.
-	^ nil
-    ].
-    (char1 == $I) ifTrue:[
-	byteOrder := #lsb.
-	msb := false.
-    ] ifFalse:[
-	(char1 == $M) ifTrue:[
-	    byteOrder := #msb.
-	    msb := true.
-	] ifFalse:[
-	    'TIFFReader: not a tiff file' errorPrintNL.
-	    ^ nil
-	]
-    ].
-
-    aStream binary.
-
-    version := self readShort.
-    (version ~~ 42) ifTrue:[
-	'TIFFReader: version of tiff-file not supported' errorPrintNL.
-	^ nil
-    ].
-
-    "setup default values"
-
-    compression := 1. "none"
-    fillOrder := #msb.
-    planarConfiguration := 1.
-    photometric := nil.
-    bitsPerSample := 1.
-    samplesPerPixel := 1.
-    width := nil.
-    height := nil.
-    stripOffsets := nil.
-    rowsPerStrip := nil.
-    "resolutionUnit := 2."
-    predictor := 1.
-
-    offset := aStream nextLongMSB:msb.
-    aStream position:offset + 1.
-
-    numberOfTags := self readShort.
-    1 to:numberOfTags do:[:index |
-	tagType := self readShort.
-	numberType := self readShort.
-	length := aStream nextLongMSB:msb.
-	self decodeTiffTag:tagType numberType:numberType length:length
-    ].
-
-    offset := aStream nextLongMSB:msb.
-    (offset ~~ 0) ifTrue:[
-	'TIFFReader: more tags ignored' errorPrintNL
-    ].
-
-    "check for required tags"
-    ok := true.
-    width isNil ifTrue:[
-	'TIFFReader: missing width tag' errorPrintNL.
-	ok := false
-    ].
-
-    height isNil ifTrue:[
-	'TIFFReader: missing length tag' errorPrintNL.
-	ok := false
-    ].
-
-    photometric isNil ifTrue:[
-	'TIFFReader: missing photometric tag' errorPrintNL.
-	ok := false
-    ].
-
-    stripOffsets isNil ifTrue:[
-	'TIFFReader: missing stripOffsets tag' errorPrintNL.
-	ok := false
-    ].
-
-    stripByteCounts isNil ifTrue:[
-	stripOffsets size == 1 ifTrue:[
-	    stripByteCounts := Array with:(self bitsPerPixel // 8) * width * height
-	]
-    ].
-
-    stripByteCounts isNil ifTrue:[
-	'TIFFReader: missing stripByteCounts tag' errorPrintNL.
-	ok := false
-    ].
-
-    ok ifFalse:[
-	^ nil
-    ].
-
-    "given all the information, read the bits"
-
-    rowsPerStrip isNil ifTrue:[
-	rowsPerStrip := height
-    ].
-
-    ok := false.
-    (compression == 1) ifTrue:[
-	result := self readUncompressedTiffImageData.
-	ok := true
-    ].
-    (compression == 2) ifTrue:[
-	result := self readCCITT3RLETiffImageData.
-	ok := true
-    ].
-    (compression == 3) ifTrue:[
-	result := self readCCITTGroup3TiffImageData.
-	ok := true
-    ]. 
-    (compression == 4) ifTrue:[
-	result := self readCCITTGroup4TiffImageData.
-	ok := true
-    ]. 
-    (compression == 5) ifTrue:[
-	result := self readLZWTiffImageData.
-	ok := true
-    ].
-    (compression == 6) ifTrue:[
-	result := self readJPEGTiffImageData.
-	ok := true
-    ].
-    (compression == 32766) ifTrue:[
-	result := self readNeXTRLE2TiffImageData.
-	ok := true
-    ].
-    (compression == 32771) ifTrue:[
-	result := self readCCITTRLEWTiffImageData.
-	ok := true
-    ].
-    (compression == 32773) ifTrue:[
-	result := self readPackbitsTiffImageData.
-	ok := true
-    ].
-    (compression == 32865) ifTrue:[
-	result := self readNeXTJPEGTiffImageData.
-	ok := true
-    ].
-    ok ifFalse:[
-	'TIFFReader: compression type ' errorPrint. compression errorPrint.
-	' not known' errorPrintNL
-    ].
-    ^ result
-! !
-
-!TIFFReader methodsFor:'writing to file'!
-
-save:image onFile:aFileName
-    "save image as (uncompressed) TIFF file on aFileName"
-
-    |pos1 pos|
-
-    outStream := FileStream newFileNamed:aFileName.
-    outStream isNil ifTrue:[
-	'TIFFReader: create error' errorPrintNL. 
-	^ nil
-    ].
-
-    "save as msb"
-
-    byteOrder := #msb.
-"
-    byteOrder := #lsb.
-"
-    fillOrder := #msb.
-    width := image width.
-    height := image height.
-    photometric := image photometric.
-    samplesPerPixel := image samplesPerPixel.
-    bitsPerSample := image bitsPerSample.
-    colorMap := image colorMap.
-    planarConfiguration := 1.
-    compression := 1.   "none"
-    data := image bits.
-
-    currentOffset := 0.
-
-    (byteOrder == #msb) ifTrue:[
-	outStream nextPut:$M.
-	outStream nextPut:$M.
-    ] ifFalse:[
-	outStream nextPut:$I.
-	outStream nextPut:$I.
-    ].
-    currentOffset := currentOffset + 2.
-
-    outStream binary.
-
-    self writeShort:42.
-    currentOffset := currentOffset + 2.
-
-    pos1 := outStream position.
-    self writeLong:0.           "start of tags - filled in later"
-    currentOffset := currentOffset + 4.
-
-    "output strips"
-
-    self writeUncompressedBits. "this outputs bits as strips, sets stripOffsets and stripByteCounts"
-    self writeStripOffsets.     "this outputs strip offsets, sets stripOffsetsPos"
-    self writeStripByteCounts.  "this outputs strip bytecounts, sets stripByteCountPos"
-    self writeBitsPerSample.    "this outputs bitsPerSample, sets bitsPerSamplePos"
-    photometric == #palette ifTrue:[
-	self writeColorMap      "this outputs colorMap, sets colorMapPos"
-    ].
-
-    pos := outStream position.                  "backpatch tag offset"
-    outStream position:pos1.
-    self writeLong:(pos - 1).                   "fill in tag offset"
-    outStream position:pos.
-"
-('patch tag offset at: ', (pos1 printStringRadix:16) , ' to ',
-			 (pos printStringRadix:16)) printNewline.
-"
-    "output tag data"
-
-    photometric == #palette ifTrue:[
-	self writeShort:10.  "10 tags"
-    ] ifFalse:[
-	self writeShort:9.   "9 tags"
-    ].
-    self writeTag:256.               "image width"
-    self writeTag:257.               "image height"
-    self writeTag:258.               "bits per sample"
-    self writeTag:259.               "compression"
-    self writeTag:262.               "photometric"
-    self writeTag:273.               "strip offsets"
-    self writeTag:278.               "rowsPerStrip"
-    self writeTag:279.               "strip byte counts"
-    self writeTag:284.               "planarconfig"
-    photometric == #palette ifTrue:[
-	self writeTag:320            "colorMap"
-    ].
-    self writeLong:0.                "end of tags mark"
-    outStream close
 ! !
 
 !TIFFReader methodsFor:'private'!
 
-readLongs:nLongs
-    "read nLongs long numbers (32bit) and return them in an array"
-
-    |oldPos offset values msb 
-     n "{ Class: SmallInteger }" |
-
-    n := nLongs.
-
-    msb := byteOrder ~~ #lsb.
-    values := Array basicNew:n.
-    (n == 1) ifTrue:[
-	values at:1 put:(inStream nextLongMSB:msb).
-    ] ifFalse:[
-	offset := inStream nextLongMSB:msb.
-	oldPos := inStream position.
-	inStream position:(offset + 1).
-	1 to:n do:[:index |
-	    values at:index put:(inStream nextLongMSB:msb)
-	].
-	inStream position:oldPos
-    ].
-    ^ values
-!
-
-readShorts:nShorts
-    "read nShorts short numbers (16bit) and return them in an array"
-
-    |oldPos offset values msb val2
-     n "{ Class: SmallInteger }" |
-
-    n := nShorts.
-
-    msb := (byteOrder ~~ #lsb).
-    values := Array basicNew:n.
-    (n <= 2) ifTrue:[
-	values at:1 put:(inStream nextUnsignedShortMSB:msb).
-	val2 := inStream nextUnsignedShortMSB:msb.
-
-	(n == 2) ifTrue:[
-	    values at:2 put:val2
-	]
-    ] ifFalse:[
-	offset := inStream nextLongMSB:msb.
-	oldPos := inStream position.
-	inStream position:(offset + 1).
-	1 to:n do:[:index |
-	    values at:index put:(inStream nextUnsignedShortMSB:msb)
-	].
-	inStream position:oldPos
-    ].
-    ^ values
-!
-
-readChars:n
-    "read n characters and return them in a string"
-
-    |oldPos offset string|
-
-    string := String new:(n - 1).
-    (n <= 4) ifTrue:[
-	inStream nextBytes:(n - 1) into:string
-    ] ifFalse:[
-	offset := inStream nextLongMSB:(byteOrder ~~ #lsb).
-	oldPos := inStream position.
-	inStream position:(offset + 1).
-	inStream nextBytes:(n - 1) into:string.
-	inStream position:oldPos
-    ].
-    ^ string
-!
-
-readFracts:nFracts
-    "read nFracts fractions (2 32bit words) and return them in an array"
-
-    |oldPos offset values numerator denominator msb
-     n "{ Class: SmallInteger }" |
-
-    n := nFracts.
-
-    msb := byteOrder ~~ #lsb.
-    values := Array basicNew:n.
-    offset := inStream nextLongMSB:msb.
-    oldPos := inStream position.
-    inStream position:(offset + 1).
-    1 to:n do:[:index |
-	numerator := inStream nextLongMSB:msb.
-	denominator := inStream nextLongMSB:msb.
-	values at:index put:(Fraction numerator:numerator denominator:denominator)
-    ].
-    inStream position:oldPos.
-    ^ values
-!
-
 decodeTiffTag:tagType numberType:numberType length:length
     |offset value valueArray 
      val scaleFactor rV gV bV
@@ -1018,36 +664,351 @@
     'TIFFReader: unknown tag type ' errorPrint. tagType errorPrintNL
 !
 
-writeUncompressedBits
-    "write bits as one or multiple strips"
+readCCITT3RLETiffImageData
+     'TIFFReader: ccitt mod Huffman (rle) compression not implemented' errorPrintNL.
+!
+
+readCCITT3RLEWTiffImageData
+     'TIFFReader: ccitt mod Huffman (rlew) compression not implemented' errorPrintNL.
+!
+
+readCCITTGroup3TiffImageData
+    "not really tested - all I got is a single
+     fax from NeXT step"
+
+    |bytesPerRow bitsPerRow compressedStrip nPlanes 
+     stripNr       "{ Class: SmallInteger }"
+     offset        "{ Class: SmallInteger }"
+     row           "{ Class: SmallInteger }"
+     bytesPerStrip "{ Class: SmallInteger }" |
+
+    nPlanes := samplesPerPixel.
+    (nPlanes == 2) ifTrue:[
+	'TIFFReader: ignoring alpha plane' errorPrintNL.
+	nPlanes := 1
+    ].
+
+    (nPlanes ~~ 1) ifTrue:[
+	self error:'only monochrome/greyscale supported'.
+	^ nil
+    ].
 
-    |offs bytesPerRow nBytes
-     h "{ Class: SmallInteger }"|
+    stripByteCounts isNil ifTrue:[
+	self error:'currently require stripByteCounts'.
+	^ nil
+    ].
+    (rowsPerStrip ~~ 1) isNil ifTrue:[
+	self error:'currently require rowsPerStrip to be 1'.
+	^ nil
+    ].
+
+    'TIFFReader: decompressing CCITT-3 ...' infoPrintNL.
+
+    bitsPerRow := width * (bitsPerSample at:1).
+    bytesPerRow := bitsPerRow // 8.
+    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
+	bytesPerRow := bytesPerRow + 1
+    ].
+
+    data := ByteArray new:(bytesPerRow * height).
+    compressedStrip := ByteArray uninitializedNew:bytesPerRow.
+
+    offset := 1.
+    stripNr := 0.
+
+    row := 1.
+    bytesPerStrip := bytesPerRow * rowsPerStrip.
+    [row <= height] whileTrue:[
+	stripNr := stripNr + 1.
+	inStream position:((stripOffsets at:stripNr) + 1).
+	inStream nextBytes:(stripByteCounts at:stripNr) into:compressedStrip.
+	self class decompressCCITT3From:compressedStrip
+				   into:data
+			     startingAt:offset
+				  count:width.
+	offset := offset + bytesPerStrip.
+	row := row + rowsPerStrip
+    ]
+!
+
+readCCITTGroup4TiffImageData
+    'TIFFReader: ccitt group4 fax compression not implemented' errorPrintNL.
+!
 
-    nBytes := data size.
-    nBytes < 16rFFFF ifTrue:[
-	stripOffsets := Array with:(outStream position - 1).
-	stripByteCounts := Array with:nBytes.
-	outStream nextPutBytes:nBytes from:data.
-	rowsPerStrip := height
+readChars:n
+    "read n characters and return them in a string"
+
+    |oldPos offset string|
+
+    string := String new:(n - 1).
+    (n <= 4) ifTrue:[
+	inStream nextBytes:(n - 1) into:string
+    ] ifFalse:[
+	offset := inStream nextLongMSB:(byteOrder ~~ #lsb).
+	oldPos := inStream position.
+	inStream position:(offset + 1).
+	inStream nextBytes:(n - 1) into:string.
+	inStream position:oldPos
+    ].
+    ^ string
+!
+
+readFracts:nFracts
+    "read nFracts fractions (2 32bit words) and return them in an array"
+
+    |oldPos offset values numerator denominator msb
+     n "{ Class: SmallInteger }" |
+
+    n := nFracts.
+
+    msb := byteOrder ~~ #lsb.
+    values := Array basicNew:n.
+    offset := inStream nextLongMSB:msb.
+    oldPos := inStream position.
+    inStream position:(offset + 1).
+    1 to:n do:[:index |
+	numerator := inStream nextLongMSB:msb.
+	denominator := inStream nextLongMSB:msb.
+	values at:index put:(Fraction numerator:numerator denominator:denominator)
+    ].
+    inStream position:oldPos.
+    ^ values
+!
+
+readJPEGTiffImageData
+    'TIFFReader: jpeg compression not implemented' errorPrintNL
+!
+
+readLZWTiffImageData
+    "read LZW compressed tiff data; this method only
+     handles 3x8 rgb and 1x2 or 2x2 greyscale images.
+     For 2x2 greyscale images, the alpha plane is ignored.
+     (maybe other formats work also - its simply not
+      tested)"
+
+    |bytesPerRow compressedStrip nPlanes 
+     bytesPerStrip "{ Class: SmallInteger }"
+     nBytes        "{ Class: SmallInteger }"
+     prevSize      "{ Class: SmallInteger }"
+     stripNr       "{ Class: SmallInteger }"
+     offset        "{ Class: SmallInteger }"
+     row           "{ Class: SmallInteger }" |
+
+    nPlanes := samplesPerPixel.
+
+    (nPlanes == 3) ifTrue:[
+	((bitsPerSample at:1) ~~ 8) ifTrue:[
+	    self error:'only 8 bit/sample supported'.
+	    ^ nil
+	].
+	((bitsPerSample at:2) ~~ 8) ifTrue:[
+	    self error:'only 8 bit/sample supported'.
+	    ^ nil
+	].
+	((bitsPerSample at:3) ~~ 8) ifTrue:[
+	    self error:'only 8 bit/sample supported'.
+	    ^ nil
+	].
+	bytesPerRow := width * samplesPerPixel.
     ] ifFalse:[
-	stripOffsets := Array basicNew:height.
-	bytesPerRow := nBytes // height.
-	stripByteCounts := (Array basicNew:height) atAllPut:bytesPerRow.
+	(nPlanes == 2) ifTrue:[
+	    (planarConfiguration ~~ 2) ifTrue:[
+		self error:'only separate planes supported'.
+		^ nil
+	    ].
+	    'TIFFReader: ignoring alpha plane' errorPrintNL.
+	    nPlanes := 1
+	].
+	(nPlanes == 1) ifFalse:[
+	    self error:'only 3-sample rgb / monochrome supported'.
+	    ^ nil
+	].
+	bytesPerRow := (width * (bitsPerSample at:1) + 7) // 8.
+    ].
+
+    stripByteCounts isNil ifTrue:[
+	self error:'currently require stripByteCounts'.
+	^ nil
+    ].
+
+    'TIFFReader: decompressing LZW ...' infoPrintNL.
+
+    data := ByteArray uninitializedNew:(bytesPerRow * height).
+
+    offset := 1.
+    stripNr := 0.
+
+    row := 1.
+    bytesPerStrip := bytesPerRow * rowsPerStrip.
+    prevSize := 0.
+    [row <= height] whileTrue:[
+	stripNr := stripNr + 1.
+	inStream position:((stripOffsets at:stripNr) + 1).
+	nBytes := stripByteCounts at:stripNr.
+	(nBytes > prevSize) ifTrue:[
+	    compressedStrip := ByteArray uninitializedNew:nBytes.
+	    prevSize := nBytes
+	].
+	inStream nextBytes:nBytes
+		      into:compressedStrip.
+	self class decompressLZWFrom:compressedStrip
+			       count:nBytes
+				into:data
+			  startingAt:offset.
+	offset := offset + bytesPerStrip.
+	row := row + rowsPerStrip
+    ].
+
+    (predictor == 2) ifTrue:[
+	self class decodeDelta:3 in:data width:width height:height
+    ]
+!
+
+readLongs:nLongs
+    "read nLongs long numbers (32bit) and return them in an array"
+
+    |oldPos offset values msb 
+     n "{ Class: SmallInteger }" |
+
+    n := nLongs.
+
+    msb := byteOrder ~~ #lsb.
+    values := Array basicNew:n.
+    (n == 1) ifTrue:[
+	values at:1 put:(inStream nextLongMSB:msb).
+    ] ifFalse:[
+	offset := inStream nextLongMSB:msb.
+	oldPos := inStream position.
+	inStream position:(offset + 1).
+	1 to:n do:[:index |
+	    values at:index put:(inStream nextLongMSB:msb)
+	].
+	inStream position:oldPos
+    ].
+    ^ values
+!
+
+readNeXTJPEGTiffImageData
+    'TIFFReader: jpeg compression not implemented' errorPrintNL
+!
+
+readNeXTRLE2TiffImageData
+    'TIFFReader: next 2bit rle compression not implemented' errorPrintNL.
+!
+
+readPackbitsTiffImageData
+    "had no samples yet - however, packbits decompression
+     is rather trivial to add ..."
+
+    'TIFFReader: packbits compression not implemented' errorPrintNL
+!
+
+readShorts:nShorts
+    "read nShorts short numbers (16bit) and return them in an array"
+
+    |oldPos offset values msb val2
+     n "{ Class: SmallInteger }" |
 
-	offs := 1.
-	h := height.
-	1 to:h do:[:row |
-	    stripOffsets at:row put:(outStream position - 1).
-	    outStream nextPutBytes:bytesPerRow from:data startingAt:offs.
-	    offs := offs + bytesPerRow
+    n := nShorts.
+
+    msb := (byteOrder ~~ #lsb).
+    values := Array basicNew:n.
+    (n <= 2) ifTrue:[
+	values at:1 put:(inStream nextUnsignedShortMSB:msb).
+	val2 := inStream nextUnsignedShortMSB:msb.
+
+	(n == 2) ifTrue:[
+	    values at:2 put:val2
+	]
+    ] ifFalse:[
+	offset := inStream nextLongMSB:msb.
+	oldPos := inStream position.
+	inStream position:(offset + 1).
+	1 to:n do:[:index |
+	    values at:index put:(inStream nextUnsignedShortMSB:msb)
+	].
+	inStream position:oldPos
+    ].
+    ^ values
+!
+
+readUncompressedTiffImageData
+    |bytesPerRow bitsPerRow nPlanes 
+     stripNr       "{ Class: SmallInteger }"
+     offset        "{ Class: SmallInteger }"
+     row           "{ Class: SmallInteger }" 
+     nBytes        "{ Class: SmallInteger }"
+     bitsPerPixel overAllBytes|
+
+    nPlanes := samplesPerPixel.
+
+    "only support 1-sample/pixel,
+     with alpha - if separate planes,
+     or rgb - if non separate planes and no alpha"
+
+    (nPlanes == 2) ifTrue:[
+	(planarConfiguration ~~ 2) ifTrue:[
+	    self error:'with alpha, only separate planes supported'.
+	    ^ nil
 	].
-	rowsPerStrip := 1
+	'TIFFReader: ignoring alpha plane' errorPrintNL.
+	nPlanes := 1.
+	bitsPerPixel := bitsPerSample at:1.
+	bitsPerSample := Array with:bitsPerPixel.
+	samplesPerPixel := 1.
+    ] ifFalse:[
+	(nPlanes == 3) ifTrue:[
+	    (planarConfiguration ~~ 1) ifTrue:[
+		self error:'only non separate planes supported'.
+		^ nil
+	    ].
+	    bitsPerSample ~= #(8 8 8) ifTrue:[
+		self error:'only 8/8/8 rgb images supported'.
+		^ nil
+	    ].
+	    bitsPerPixel := 24
+	] ifFalse:[
+	    (nPlanes ~~ 1) ifTrue:[
+		self error:'format not supported'.
+		^ nil
+	    ].
+	    bitsPerPixel := bitsPerSample at:1.
+	]
     ].
+
+    bitsPerRow := width * bitsPerPixel.
+    bytesPerRow := bitsPerRow // 8.
+    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
+	bytesPerRow := bytesPerRow + 1
+    ].
+
+    overAllBytes := bytesPerRow * height.
+    data := ByteArray uninitializedNew:overAllBytes.
+
+    offset := 1.
+    stripNr := 0.
+
+    row := 1.
+    [row <= height] whileTrue:[
+	stripNr := stripNr + 1.
+	nBytes := stripByteCounts at:stripNr.
+	inStream position:((stripOffsets at:stripNr) + 1).
+
+	inStream nextBytes:nBytes into:data startingAt:offset.
+	offset := offset + nBytes.
+	row := row + rowsPerStrip
+    ]
+!
+
+writeBitsPerSample
 "
-    'stripOffsets: ' print. stripOffsets printNewline.
-    'stripByteCounts: ' print. stripByteCounts printNewline.
+'bitsPerSample: ' print. bitsPerSample printNewline.
+'store bitspersample at: ' print. outStream position printNewline.
 "
+    bitsPerSamplePos := outStream position.
+    bitsPerSample do:[:n |
+	self writeShort:n
+    ]
 !
 
 writeColorMap
@@ -1081,17 +1042,6 @@
     ]
 !
 
-writeStripOffsets
-"
-'stripOffsets: ' print. stripOffsets printNewline.
-'store stripoffsets at: ' print. outStream position printNewline.
-"
-    stripOffsetsPos := outStream position.
-    stripOffsets do:[:o |
-	self writeLong:o
-    ]
-!
-
 writeStripByteCounts
 "
 'stripByteCounts: ' print. stripByteCounts printNewline.
@@ -1103,14 +1053,14 @@
     ]
 !
 
-writeBitsPerSample
+writeStripOffsets
 "
-'bitsPerSample: ' print. bitsPerSample printNewline.
-'store bitspersample at: ' print. outStream position printNewline.
+'stripOffsets: ' print. stripOffsets printNewline.
+'store stripoffsets at: ' print. outStream position printNewline.
 "
-    bitsPerSamplePos := outStream position.
-    bitsPerSample do:[:n |
-	self writeShort:n
+    stripOffsetsPos := outStream position.
+    stripOffsets do:[:o |
+	self writeLong:o
     ]
 !
 
@@ -1391,245 +1341,295 @@
     ].
 !
 
-readUncompressedTiffImageData
-    |bytesPerRow bitsPerRow nPlanes 
-     stripNr       "{ Class: SmallInteger }"
-     offset        "{ Class: SmallInteger }"
-     row           "{ Class: SmallInteger }" 
-     nBytes        "{ Class: SmallInteger }"
-     bitsPerPixel overAllBytes|
+writeUncompressedBits
+    "write bits as one or multiple strips"
+
+    |offs bytesPerRow nBytes
+     h "{ Class: SmallInteger }"|
 
-    nPlanes := samplesPerPixel.
+    nBytes := data size.
+    nBytes < 16rFFFF ifTrue:[
+	stripOffsets := Array with:(outStream position - 1).
+	stripByteCounts := Array with:nBytes.
+	outStream nextPutBytes:nBytes from:data.
+	rowsPerStrip := height
+    ] ifFalse:[
+	stripOffsets := Array basicNew:height.
+	bytesPerRow := nBytes // height.
+	stripByteCounts := (Array basicNew:height) atAllPut:bytesPerRow.
 
-    "only support 1-sample/pixel,
-     with alpha - if separate planes,
-     or rgb - if non separate planes and no alpha"
-
-    (nPlanes == 2) ifTrue:[
-	(planarConfiguration ~~ 2) ifTrue:[
-	    self error:'with alpha, only separate planes supported'.
-	    ^ nil
+	offs := 1.
+	h := height.
+	1 to:h do:[:row |
+	    stripOffsets at:row put:(outStream position - 1).
+	    outStream nextPutBytes:bytesPerRow from:data startingAt:offs.
+	    offs := offs + bytesPerRow
 	].
-	'TIFFReader: ignoring alpha plane' errorPrintNL.
-	nPlanes := 1.
-	bitsPerPixel := bitsPerSample at:1.
-	bitsPerSample := Array with:bitsPerPixel.
-	samplesPerPixel := 1.
+	rowsPerStrip := 1
+    ].
+"
+    'stripOffsets: ' print. stripOffsets printNewline.
+    'stripByteCounts: ' print. stripByteCounts printNewline.
+"
+! !
+
+!TIFFReader methodsFor:'reading from file'!
+
+fromStream:aStream
+    "read an image from aStream"
+
+    |char1 char2 version 
+     numberOfTags "{ Class: SmallInteger }"
+     tagType      "{ Class: SmallInteger }"
+     numberType   "{ Class: SmallInteger }"
+     length       "{ Class: SmallInteger }"
+     result offset ok msb|
+
+    inStream := aStream.
+
+    char1 := aStream next.
+    char2 := aStream next.
+    (char1 ~~ char2) ifTrue:[
+	'TIFFReader: not a tiff file' errorPrintNL.
+	^ nil
+    ].
+    (char1 == $I) ifTrue:[
+	byteOrder := #lsb.
+	msb := false.
     ] ifFalse:[
-	(nPlanes == 3) ifTrue:[
-	    (planarConfiguration ~~ 1) ifTrue:[
-		self error:'only non separate planes supported'.
-		^ nil
-	    ].
-	    bitsPerSample ~= #(8 8 8) ifTrue:[
-		self error:'only 8/8/8 rgb images supported'.
-		^ nil
-	    ].
-	    bitsPerPixel := 24
+	(char1 == $M) ifTrue:[
+	    byteOrder := #msb.
+	    msb := true.
 	] ifFalse:[
-	    (nPlanes ~~ 1) ifTrue:[
-		self error:'format not supported'.
-		^ nil
-	    ].
-	    bitsPerPixel := bitsPerSample at:1.
+	    'TIFFReader: not a tiff file' errorPrintNL.
+	    ^ nil
 	]
     ].
 
-    bitsPerRow := width * bitsPerPixel.
-    bytesPerRow := bitsPerRow // 8.
-    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
-	bytesPerRow := bytesPerRow + 1
+    aStream binary.
+
+    version := self readShort.
+    (version ~~ 42) ifTrue:[
+	'TIFFReader: version of tiff-file not supported' errorPrintNL.
+	^ nil
     ].
 
-    overAllBytes := bytesPerRow * height.
-    data := ByteArray uninitializedNew:overAllBytes.
-
-    offset := 1.
-    stripNr := 0.
-
-    row := 1.
-    [row <= height] whileTrue:[
-	stripNr := stripNr + 1.
-	nBytes := stripByteCounts at:stripNr.
-	inStream position:((stripOffsets at:stripNr) + 1).
+    "setup default values"
 
-	inStream nextBytes:nBytes into:data startingAt:offset.
-	offset := offset + nBytes.
-	row := row + rowsPerStrip
-    ]
-!
+    compression := 1. "none"
+    fillOrder := #msb.
+    planarConfiguration := 1.
+    photometric := nil.
+    bitsPerSample := 1.
+    samplesPerPixel := 1.
+    width := nil.
+    height := nil.
+    stripOffsets := nil.
+    rowsPerStrip := nil.
+    "resolutionUnit := 2."
+    predictor := 1.
 
-readLZWTiffImageData
-    "read LZW compressed tiff data; this method only
-     handles 3x8 rgb and 1x2 or 2x2 greyscale images.
-     For 2x2 greyscale images, the alpha plane is ignored.
-     (maybe other formats work also - its simply not
-      tested)"
+    offset := aStream nextLongMSB:msb.
+    aStream position:offset + 1.
+
+    numberOfTags := self readShort.
+    1 to:numberOfTags do:[:index |
+	tagType := self readShort.
+	numberType := self readShort.
+	length := aStream nextLongMSB:msb.
+	self decodeTiffTag:tagType numberType:numberType length:length
+    ].
 
-    |bytesPerRow compressedStrip nPlanes 
-     bytesPerStrip "{ Class: SmallInteger }"
-     nBytes        "{ Class: SmallInteger }"
-     prevSize      "{ Class: SmallInteger }"
-     stripNr       "{ Class: SmallInteger }"
-     offset        "{ Class: SmallInteger }"
-     row           "{ Class: SmallInteger }" |
+    offset := aStream nextLongMSB:msb.
+    (offset ~~ 0) ifTrue:[
+	'TIFFReader: more tags ignored' errorPrintNL
+    ].
 
-    nPlanes := samplesPerPixel.
+    "check for required tags"
+    ok := true.
+    width isNil ifTrue:[
+	'TIFFReader: missing width tag' errorPrintNL.
+	ok := false
+    ].
 
-    (nPlanes == 3) ifTrue:[
-	((bitsPerSample at:1) ~~ 8) ifTrue:[
-	    self error:'only 8 bit/sample supported'.
-	    ^ nil
-	].
-	((bitsPerSample at:2) ~~ 8) ifTrue:[
-	    self error:'only 8 bit/sample supported'.
-	    ^ nil
-	].
-	((bitsPerSample at:3) ~~ 8) ifTrue:[
-	    self error:'only 8 bit/sample supported'.
-	    ^ nil
-	].
-	bytesPerRow := width * samplesPerPixel.
-    ] ifFalse:[
-	(nPlanes == 2) ifTrue:[
-	    (planarConfiguration ~~ 2) ifTrue:[
-		self error:'only separate planes supported'.
-		^ nil
-	    ].
-	    'TIFFReader: ignoring alpha plane' errorPrintNL.
-	    nPlanes := 1
-	].
-	(nPlanes == 1) ifFalse:[
-	    self error:'only 3-sample rgb / monochrome supported'.
-	    ^ nil
-	].
-	bytesPerRow := (width * (bitsPerSample at:1) + 7) // 8.
+    height isNil ifTrue:[
+	'TIFFReader: missing length tag' errorPrintNL.
+	ok := false
+    ].
+
+    photometric isNil ifTrue:[
+	'TIFFReader: missing photometric tag' errorPrintNL.
+	ok := false
+    ].
+
+    stripOffsets isNil ifTrue:[
+	'TIFFReader: missing stripOffsets tag' errorPrintNL.
+	ok := false
     ].
 
     stripByteCounts isNil ifTrue:[
-	self error:'currently require stripByteCounts'.
+	stripOffsets size == 1 ifTrue:[
+	    stripByteCounts := Array with:(self bitsPerPixel // 8) * width * height
+	]
+    ].
+
+    stripByteCounts isNil ifTrue:[
+	'TIFFReader: missing stripByteCounts tag' errorPrintNL.
+	ok := false
+    ].
+
+    ok ifFalse:[
 	^ nil
     ].
 
-    'TIFFReader: decompressing LZW ...' infoPrintNL.
-
-    data := ByteArray uninitializedNew:(bytesPerRow * height).
-
-    offset := 1.
-    stripNr := 0.
+    "given all the information, read the bits"
 
-    row := 1.
-    bytesPerStrip := bytesPerRow * rowsPerStrip.
-    prevSize := 0.
-    [row <= height] whileTrue:[
-	stripNr := stripNr + 1.
-	inStream position:((stripOffsets at:stripNr) + 1).
-	nBytes := stripByteCounts at:stripNr.
-	(nBytes > prevSize) ifTrue:[
-	    compressedStrip := ByteArray uninitializedNew:nBytes.
-	    prevSize := nBytes
-	].
-	inStream nextBytes:nBytes
-		      into:compressedStrip.
-	self class decompressLZWFrom:compressedStrip
-			       count:nBytes
-				into:data
-			  startingAt:offset.
-	offset := offset + bytesPerStrip.
-	row := row + rowsPerStrip
+    rowsPerStrip isNil ifTrue:[
+	rowsPerStrip := height
     ].
 
-    (predictor == 2) ifTrue:[
-	self class decodeDelta:3 in:data width:width height:height
-    ]
-!
-
-readCCITTGroup3TiffImageData
-    "not really tested - all I got is a single
-     fax from NeXT step"
+    ok := false.
+    (compression == 1) ifTrue:[
+	result := self readUncompressedTiffImageData.
+	ok := true
+    ].
+    (compression == 2) ifTrue:[
+	result := self readCCITT3RLETiffImageData.
+	ok := true
+    ].
+    (compression == 3) ifTrue:[
+	result := self readCCITTGroup3TiffImageData.
+	ok := true
+    ]. 
+    (compression == 4) ifTrue:[
+	result := self readCCITTGroup4TiffImageData.
+	ok := true
+    ]. 
+    (compression == 5) ifTrue:[
+	result := self readLZWTiffImageData.
+	ok := true
+    ].
+    (compression == 6) ifTrue:[
+	result := self readJPEGTiffImageData.
+	ok := true
+    ].
+    (compression == 32766) ifTrue:[
+	result := self readNeXTRLE2TiffImageData.
+	ok := true
+    ].
+    (compression == 32771) ifTrue:[
+	result := self readCCITTRLEWTiffImageData.
+	ok := true
+    ].
+    (compression == 32773) ifTrue:[
+	result := self readPackbitsTiffImageData.
+	ok := true
+    ].
+    (compression == 32865) ifTrue:[
+	result := self readNeXTJPEGTiffImageData.
+	ok := true
+    ].
+    ok ifFalse:[
+	'TIFFReader: compression type ' errorPrint. compression errorPrint.
+	' not known' errorPrintNL
+    ].
+    ^ result
+! !
 
-    |bytesPerRow bitsPerRow compressedStrip nPlanes 
-     stripNr       "{ Class: SmallInteger }"
-     offset        "{ Class: SmallInteger }"
-     row           "{ Class: SmallInteger }"
-     bytesPerStrip "{ Class: SmallInteger }" |
+!TIFFReader methodsFor:'writing to file'!
+
+save:image onFile:aFileName
+    "save image as (uncompressed) TIFF file on aFileName"
 
-    nPlanes := samplesPerPixel.
-    (nPlanes == 2) ifTrue:[
-	'TIFFReader: ignoring alpha plane' errorPrintNL.
-	nPlanes := 1
-    ].
+    |pos1 pos|
 
-    (nPlanes ~~ 1) ifTrue:[
-	self error:'only monochrome/greyscale supported'.
+    outStream := FileStream newFileNamed:aFileName.
+    outStream isNil ifTrue:[
+	'TIFFReader: create error' errorPrintNL. 
 	^ nil
     ].
 
-    stripByteCounts isNil ifTrue:[
-	self error:'currently require stripByteCounts'.
-	^ nil
-    ].
-    (rowsPerStrip ~~ 1) isNil ifTrue:[
-	self error:'currently require rowsPerStrip to be 1'.
-	^ nil
+    "save as msb"
+
+    byteOrder := #msb.
+"
+    byteOrder := #lsb.
+"
+    fillOrder := #msb.
+    width := image width.
+    height := image height.
+    photometric := image photometric.
+    samplesPerPixel := image samplesPerPixel.
+    bitsPerSample := image bitsPerSample.
+    colorMap := image colorMap.
+    planarConfiguration := 1.
+    compression := 1.   "none"
+    data := image bits.
+
+    currentOffset := 0.
+
+    (byteOrder == #msb) ifTrue:[
+	outStream nextPut:$M.
+	outStream nextPut:$M.
+    ] ifFalse:[
+	outStream nextPut:$I.
+	outStream nextPut:$I.
     ].
+    currentOffset := currentOffset + 2.
 
-    'TIFFReader: decompressing CCITT-3 ...' infoPrintNL.
+    outStream binary.
+
+    self writeShort:42.
+    currentOffset := currentOffset + 2.
 
-    bitsPerRow := width * (bitsPerSample at:1).
-    bytesPerRow := bitsPerRow // 8.
-    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
-	bytesPerRow := bytesPerRow + 1
+    pos1 := outStream position.
+    self writeLong:0.           "start of tags - filled in later"
+    currentOffset := currentOffset + 4.
+
+    "output strips"
+
+    self writeUncompressedBits. "this outputs bits as strips, sets stripOffsets and stripByteCounts"
+    self writeStripOffsets.     "this outputs strip offsets, sets stripOffsetsPos"
+    self writeStripByteCounts.  "this outputs strip bytecounts, sets stripByteCountPos"
+    self writeBitsPerSample.    "this outputs bitsPerSample, sets bitsPerSamplePos"
+    photometric == #palette ifTrue:[
+	self writeColorMap      "this outputs colorMap, sets colorMapPos"
     ].
 
-    data := ByteArray new:(bytesPerRow * height).
-    compressedStrip := ByteArray uninitializedNew:bytesPerRow.
-
-    offset := 1.
-    stripNr := 0.
-
-    row := 1.
-    bytesPerStrip := bytesPerRow * rowsPerStrip.
-    [row <= height] whileTrue:[
-	stripNr := stripNr + 1.
-	inStream position:((stripOffsets at:stripNr) + 1).
-	inStream nextBytes:(stripByteCounts at:stripNr) into:compressedStrip.
-	self class decompressCCITT3From:compressedStrip
-				   into:data
-			     startingAt:offset
-				  count:width.
-	offset := offset + bytesPerStrip.
-	row := row + rowsPerStrip
-    ]
-!
-
-readJPEGTiffImageData
-    'TIFFReader: jpeg compression not implemented' errorPrintNL
-!
+    pos := outStream position.                  "backpatch tag offset"
+    outStream position:pos1.
+    self writeLong:(pos - 1).                   "fill in tag offset"
+    outStream position:pos.
+"
+('patch tag offset at: ', (pos1 printStringRadix:16) , ' to ',
+			 (pos printStringRadix:16)) printNewline.
+"
+    "output tag data"
 
-readNeXTJPEGTiffImageData
-    'TIFFReader: jpeg compression not implemented' errorPrintNL
-!
-
-readCCITT3RLETiffImageData
-     'TIFFReader: ccitt mod Huffman (rle) compression not implemented' errorPrintNL.
-!
-
-readCCITT3RLEWTiffImageData
-     'TIFFReader: ccitt mod Huffman (rlew) compression not implemented' errorPrintNL.
-!
+    photometric == #palette ifTrue:[
+	self writeShort:10.  "10 tags"
+    ] ifFalse:[
+	self writeShort:9.   "9 tags"
+    ].
+    self writeTag:256.               "image width"
+    self writeTag:257.               "image height"
+    self writeTag:258.               "bits per sample"
+    self writeTag:259.               "compression"
+    self writeTag:262.               "photometric"
+    self writeTag:273.               "strip offsets"
+    self writeTag:278.               "rowsPerStrip"
+    self writeTag:279.               "strip byte counts"
+    self writeTag:284.               "planarconfig"
+    photometric == #palette ifTrue:[
+	self writeTag:320            "colorMap"
+    ].
+    self writeLong:0.                "end of tags mark"
+    outStream close
+! !
 
-readCCITTGroup4TiffImageData
-    'TIFFReader: ccitt group4 fax compression not implemented' errorPrintNL.
-!
+!TIFFReader class methodsFor:'documentation'!
 
-readNeXTRLE2TiffImageData
-    'TIFFReader: next 2bit rle compression not implemented' errorPrintNL.
-!
-
-readPackbitsTiffImageData
-    "had no samples yet - however, packbits decompression
-     is rather trivial to add ..."
-
-    'TIFFReader: packbits compression not implemented' errorPrintNL
+version
+    ^ '$Header: /cvs/stx/stx/libview2/Attic/TIFFRdr.st,v 1.27 1995-12-07 11:38:46 cg Exp $'
 ! !
+TIFFReader initialize!
--- a/TIFFReader.st	Thu Dec 07 11:34:06 1995 +0100
+++ b/TIFFReader.st	Thu Dec 07 12:39:00 1995 +0100
@@ -11,13 +11,10 @@
 "
 
 ImageReader subclass:#TIFFReader
-	 instanceVariableNames:'planarConfiguration
-				subFileType stripOffsets rowsPerStrip
-				fillOrder compression group3options predictor
-				stripByteCounts
-				currentOffset 
-				stripOffsetsPos stripByteCountsPos bitsPerSamplePos
-				colorMapPos'
+	 instanceVariableNames:'planarConfiguration subFileType stripOffsets rowsPerStrip
+                fillOrder compression group3options predictor stripByteCounts
+                currentOffset stripOffsetsPos stripByteCountsPos bitsPerSamplePos
+                colorMapPos'
 	 classVariableNames:''
 	 poolDictionaries:''
 	 category:'Graphics-Images support'
@@ -39,10 +36,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/TIFFReader.st,v 1.26 1995-11-22 12:06:32 cg Exp $'
-!
-
 documentation
 "
     This class knows how to read TIFF files and how to
@@ -74,6 +67,13 @@
 
 !TIFFReader class methodsFor:'testing'!
 
+canRepresent:anImage
+    "return true, if anImage can be represented in my file format.
+     Any image is supported."
+
+    ^ true
+!
+
 isValidImageFile:aFileName
     "return true, if aFileName contains a GIF image"
 
@@ -96,364 +96,10 @@
 
     (version ~~ 42) ifTrue:[^ false].
     ^ true
-!
-
-canRepresent:anImage
-    "return true, if anImage can be represented in my file format.
-     Any image is supported."
-
-    ^ true
-! !
-
-!TIFFReader methodsFor:'reading from file'!
-
-fromStream:aStream
-    "read an image from aStream"
-
-    |char1 char2 version 
-     numberOfTags "{ Class: SmallInteger }"
-     tagType      "{ Class: SmallInteger }"
-     numberType   "{ Class: SmallInteger }"
-     length       "{ Class: SmallInteger }"
-     result offset ok msb|
-
-    inStream := aStream.
-
-    char1 := aStream next.
-    char2 := aStream next.
-    (char1 ~~ char2) ifTrue:[
-	'TIFFReader: not a tiff file' errorPrintNL.
-	^ nil
-    ].
-    (char1 == $I) ifTrue:[
-	byteOrder := #lsb.
-	msb := false.
-    ] ifFalse:[
-	(char1 == $M) ifTrue:[
-	    byteOrder := #msb.
-	    msb := true.
-	] ifFalse:[
-	    'TIFFReader: not a tiff file' errorPrintNL.
-	    ^ nil
-	]
-    ].
-
-    aStream binary.
-
-    version := self readShort.
-    (version ~~ 42) ifTrue:[
-	'TIFFReader: version of tiff-file not supported' errorPrintNL.
-	^ nil
-    ].
-
-    "setup default values"
-
-    compression := 1. "none"
-    fillOrder := #msb.
-    planarConfiguration := 1.
-    photometric := nil.
-    bitsPerSample := 1.
-    samplesPerPixel := 1.
-    width := nil.
-    height := nil.
-    stripOffsets := nil.
-    rowsPerStrip := nil.
-    "resolutionUnit := 2."
-    predictor := 1.
-
-    offset := aStream nextLongMSB:msb.
-    aStream position:offset + 1.
-
-    numberOfTags := self readShort.
-    1 to:numberOfTags do:[:index |
-	tagType := self readShort.
-	numberType := self readShort.
-	length := aStream nextLongMSB:msb.
-	self decodeTiffTag:tagType numberType:numberType length:length
-    ].
-
-    offset := aStream nextLongMSB:msb.
-    (offset ~~ 0) ifTrue:[
-	'TIFFReader: more tags ignored' errorPrintNL
-    ].
-
-    "check for required tags"
-    ok := true.
-    width isNil ifTrue:[
-	'TIFFReader: missing width tag' errorPrintNL.
-	ok := false
-    ].
-
-    height isNil ifTrue:[
-	'TIFFReader: missing length tag' errorPrintNL.
-	ok := false
-    ].
-
-    photometric isNil ifTrue:[
-	'TIFFReader: missing photometric tag' errorPrintNL.
-	ok := false
-    ].
-
-    stripOffsets isNil ifTrue:[
-	'TIFFReader: missing stripOffsets tag' errorPrintNL.
-	ok := false
-    ].
-
-    stripByteCounts isNil ifTrue:[
-	stripOffsets size == 1 ifTrue:[
-	    stripByteCounts := Array with:(self bitsPerPixel // 8) * width * height
-	]
-    ].
-
-    stripByteCounts isNil ifTrue:[
-	'TIFFReader: missing stripByteCounts tag' errorPrintNL.
-	ok := false
-    ].
-
-    ok ifFalse:[
-	^ nil
-    ].
-
-    "given all the information, read the bits"
-
-    rowsPerStrip isNil ifTrue:[
-	rowsPerStrip := height
-    ].
-
-    ok := false.
-    (compression == 1) ifTrue:[
-	result := self readUncompressedTiffImageData.
-	ok := true
-    ].
-    (compression == 2) ifTrue:[
-	result := self readCCITT3RLETiffImageData.
-	ok := true
-    ].
-    (compression == 3) ifTrue:[
-	result := self readCCITTGroup3TiffImageData.
-	ok := true
-    ]. 
-    (compression == 4) ifTrue:[
-	result := self readCCITTGroup4TiffImageData.
-	ok := true
-    ]. 
-    (compression == 5) ifTrue:[
-	result := self readLZWTiffImageData.
-	ok := true
-    ].
-    (compression == 6) ifTrue:[
-	result := self readJPEGTiffImageData.
-	ok := true
-    ].
-    (compression == 32766) ifTrue:[
-	result := self readNeXTRLE2TiffImageData.
-	ok := true
-    ].
-    (compression == 32771) ifTrue:[
-	result := self readCCITTRLEWTiffImageData.
-	ok := true
-    ].
-    (compression == 32773) ifTrue:[
-	result := self readPackbitsTiffImageData.
-	ok := true
-    ].
-    (compression == 32865) ifTrue:[
-	result := self readNeXTJPEGTiffImageData.
-	ok := true
-    ].
-    ok ifFalse:[
-	'TIFFReader: compression type ' errorPrint. compression errorPrint.
-	' not known' errorPrintNL
-    ].
-    ^ result
-! !
-
-!TIFFReader methodsFor:'writing to file'!
-
-save:image onFile:aFileName
-    "save image as (uncompressed) TIFF file on aFileName"
-
-    |pos1 pos|
-
-    outStream := FileStream newFileNamed:aFileName.
-    outStream isNil ifTrue:[
-	'TIFFReader: create error' errorPrintNL. 
-	^ nil
-    ].
-
-    "save as msb"
-
-    byteOrder := #msb.
-"
-    byteOrder := #lsb.
-"
-    fillOrder := #msb.
-    width := image width.
-    height := image height.
-    photometric := image photometric.
-    samplesPerPixel := image samplesPerPixel.
-    bitsPerSample := image bitsPerSample.
-    colorMap := image colorMap.
-    planarConfiguration := 1.
-    compression := 1.   "none"
-    data := image bits.
-
-    currentOffset := 0.
-
-    (byteOrder == #msb) ifTrue:[
-	outStream nextPut:$M.
-	outStream nextPut:$M.
-    ] ifFalse:[
-	outStream nextPut:$I.
-	outStream nextPut:$I.
-    ].
-    currentOffset := currentOffset + 2.
-
-    outStream binary.
-
-    self writeShort:42.
-    currentOffset := currentOffset + 2.
-
-    pos1 := outStream position.
-    self writeLong:0.           "start of tags - filled in later"
-    currentOffset := currentOffset + 4.
-
-    "output strips"
-
-    self writeUncompressedBits. "this outputs bits as strips, sets stripOffsets and stripByteCounts"
-    self writeStripOffsets.     "this outputs strip offsets, sets stripOffsetsPos"
-    self writeStripByteCounts.  "this outputs strip bytecounts, sets stripByteCountPos"
-    self writeBitsPerSample.    "this outputs bitsPerSample, sets bitsPerSamplePos"
-    photometric == #palette ifTrue:[
-	self writeColorMap      "this outputs colorMap, sets colorMapPos"
-    ].
-
-    pos := outStream position.                  "backpatch tag offset"
-    outStream position:pos1.
-    self writeLong:(pos - 1).                   "fill in tag offset"
-    outStream position:pos.
-"
-('patch tag offset at: ', (pos1 printStringRadix:16) , ' to ',
-			 (pos printStringRadix:16)) printNewline.
-"
-    "output tag data"
-
-    photometric == #palette ifTrue:[
-	self writeShort:10.  "10 tags"
-    ] ifFalse:[
-	self writeShort:9.   "9 tags"
-    ].
-    self writeTag:256.               "image width"
-    self writeTag:257.               "image height"
-    self writeTag:258.               "bits per sample"
-    self writeTag:259.               "compression"
-    self writeTag:262.               "photometric"
-    self writeTag:273.               "strip offsets"
-    self writeTag:278.               "rowsPerStrip"
-    self writeTag:279.               "strip byte counts"
-    self writeTag:284.               "planarconfig"
-    photometric == #palette ifTrue:[
-	self writeTag:320            "colorMap"
-    ].
-    self writeLong:0.                "end of tags mark"
-    outStream close
 ! !
 
 !TIFFReader methodsFor:'private'!
 
-readLongs:nLongs
-    "read nLongs long numbers (32bit) and return them in an array"
-
-    |oldPos offset values msb 
-     n "{ Class: SmallInteger }" |
-
-    n := nLongs.
-
-    msb := byteOrder ~~ #lsb.
-    values := Array basicNew:n.
-    (n == 1) ifTrue:[
-	values at:1 put:(inStream nextLongMSB:msb).
-    ] ifFalse:[
-	offset := inStream nextLongMSB:msb.
-	oldPos := inStream position.
-	inStream position:(offset + 1).
-	1 to:n do:[:index |
-	    values at:index put:(inStream nextLongMSB:msb)
-	].
-	inStream position:oldPos
-    ].
-    ^ values
-!
-
-readShorts:nShorts
-    "read nShorts short numbers (16bit) and return them in an array"
-
-    |oldPos offset values msb val2
-     n "{ Class: SmallInteger }" |
-
-    n := nShorts.
-
-    msb := (byteOrder ~~ #lsb).
-    values := Array basicNew:n.
-    (n <= 2) ifTrue:[
-	values at:1 put:(inStream nextUnsignedShortMSB:msb).
-	val2 := inStream nextUnsignedShortMSB:msb.
-
-	(n == 2) ifTrue:[
-	    values at:2 put:val2
-	]
-    ] ifFalse:[
-	offset := inStream nextLongMSB:msb.
-	oldPos := inStream position.
-	inStream position:(offset + 1).
-	1 to:n do:[:index |
-	    values at:index put:(inStream nextUnsignedShortMSB:msb)
-	].
-	inStream position:oldPos
-    ].
-    ^ values
-!
-
-readChars:n
-    "read n characters and return them in a string"
-
-    |oldPos offset string|
-
-    string := String new:(n - 1).
-    (n <= 4) ifTrue:[
-	inStream nextBytes:(n - 1) into:string
-    ] ifFalse:[
-	offset := inStream nextLongMSB:(byteOrder ~~ #lsb).
-	oldPos := inStream position.
-	inStream position:(offset + 1).
-	inStream nextBytes:(n - 1) into:string.
-	inStream position:oldPos
-    ].
-    ^ string
-!
-
-readFracts:nFracts
-    "read nFracts fractions (2 32bit words) and return them in an array"
-
-    |oldPos offset values numerator denominator msb
-     n "{ Class: SmallInteger }" |
-
-    n := nFracts.
-
-    msb := byteOrder ~~ #lsb.
-    values := Array basicNew:n.
-    offset := inStream nextLongMSB:msb.
-    oldPos := inStream position.
-    inStream position:(offset + 1).
-    1 to:n do:[:index |
-	numerator := inStream nextLongMSB:msb.
-	denominator := inStream nextLongMSB:msb.
-	values at:index put:(Fraction numerator:numerator denominator:denominator)
-    ].
-    inStream position:oldPos.
-    ^ values
-!
-
 decodeTiffTag:tagType numberType:numberType length:length
     |offset value valueArray 
      val scaleFactor rV gV bV
@@ -1018,36 +664,351 @@
     'TIFFReader: unknown tag type ' errorPrint. tagType errorPrintNL
 !
 
-writeUncompressedBits
-    "write bits as one or multiple strips"
+readCCITT3RLETiffImageData
+     'TIFFReader: ccitt mod Huffman (rle) compression not implemented' errorPrintNL.
+!
+
+readCCITT3RLEWTiffImageData
+     'TIFFReader: ccitt mod Huffman (rlew) compression not implemented' errorPrintNL.
+!
+
+readCCITTGroup3TiffImageData
+    "not really tested - all I got is a single
+     fax from NeXT step"
+
+    |bytesPerRow bitsPerRow compressedStrip nPlanes 
+     stripNr       "{ Class: SmallInteger }"
+     offset        "{ Class: SmallInteger }"
+     row           "{ Class: SmallInteger }"
+     bytesPerStrip "{ Class: SmallInteger }" |
+
+    nPlanes := samplesPerPixel.
+    (nPlanes == 2) ifTrue:[
+	'TIFFReader: ignoring alpha plane' errorPrintNL.
+	nPlanes := 1
+    ].
+
+    (nPlanes ~~ 1) ifTrue:[
+	self error:'only monochrome/greyscale supported'.
+	^ nil
+    ].
 
-    |offs bytesPerRow nBytes
-     h "{ Class: SmallInteger }"|
+    stripByteCounts isNil ifTrue:[
+	self error:'currently require stripByteCounts'.
+	^ nil
+    ].
+    (rowsPerStrip ~~ 1) isNil ifTrue:[
+	self error:'currently require rowsPerStrip to be 1'.
+	^ nil
+    ].
+
+    'TIFFReader: decompressing CCITT-3 ...' infoPrintNL.
+
+    bitsPerRow := width * (bitsPerSample at:1).
+    bytesPerRow := bitsPerRow // 8.
+    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
+	bytesPerRow := bytesPerRow + 1
+    ].
+
+    data := ByteArray new:(bytesPerRow * height).
+    compressedStrip := ByteArray uninitializedNew:bytesPerRow.
+
+    offset := 1.
+    stripNr := 0.
+
+    row := 1.
+    bytesPerStrip := bytesPerRow * rowsPerStrip.
+    [row <= height] whileTrue:[
+	stripNr := stripNr + 1.
+	inStream position:((stripOffsets at:stripNr) + 1).
+	inStream nextBytes:(stripByteCounts at:stripNr) into:compressedStrip.
+	self class decompressCCITT3From:compressedStrip
+				   into:data
+			     startingAt:offset
+				  count:width.
+	offset := offset + bytesPerStrip.
+	row := row + rowsPerStrip
+    ]
+!
+
+readCCITTGroup4TiffImageData
+    'TIFFReader: ccitt group4 fax compression not implemented' errorPrintNL.
+!
 
-    nBytes := data size.
-    nBytes < 16rFFFF ifTrue:[
-	stripOffsets := Array with:(outStream position - 1).
-	stripByteCounts := Array with:nBytes.
-	outStream nextPutBytes:nBytes from:data.
-	rowsPerStrip := height
+readChars:n
+    "read n characters and return them in a string"
+
+    |oldPos offset string|
+
+    string := String new:(n - 1).
+    (n <= 4) ifTrue:[
+	inStream nextBytes:(n - 1) into:string
+    ] ifFalse:[
+	offset := inStream nextLongMSB:(byteOrder ~~ #lsb).
+	oldPos := inStream position.
+	inStream position:(offset + 1).
+	inStream nextBytes:(n - 1) into:string.
+	inStream position:oldPos
+    ].
+    ^ string
+!
+
+readFracts:nFracts
+    "read nFracts fractions (2 32bit words) and return them in an array"
+
+    |oldPos offset values numerator denominator msb
+     n "{ Class: SmallInteger }" |
+
+    n := nFracts.
+
+    msb := byteOrder ~~ #lsb.
+    values := Array basicNew:n.
+    offset := inStream nextLongMSB:msb.
+    oldPos := inStream position.
+    inStream position:(offset + 1).
+    1 to:n do:[:index |
+	numerator := inStream nextLongMSB:msb.
+	denominator := inStream nextLongMSB:msb.
+	values at:index put:(Fraction numerator:numerator denominator:denominator)
+    ].
+    inStream position:oldPos.
+    ^ values
+!
+
+readJPEGTiffImageData
+    'TIFFReader: jpeg compression not implemented' errorPrintNL
+!
+
+readLZWTiffImageData
+    "read LZW compressed tiff data; this method only
+     handles 3x8 rgb and 1x2 or 2x2 greyscale images.
+     For 2x2 greyscale images, the alpha plane is ignored.
+     (maybe other formats work also - its simply not
+      tested)"
+
+    |bytesPerRow compressedStrip nPlanes 
+     bytesPerStrip "{ Class: SmallInteger }"
+     nBytes        "{ Class: SmallInteger }"
+     prevSize      "{ Class: SmallInteger }"
+     stripNr       "{ Class: SmallInteger }"
+     offset        "{ Class: SmallInteger }"
+     row           "{ Class: SmallInteger }" |
+
+    nPlanes := samplesPerPixel.
+
+    (nPlanes == 3) ifTrue:[
+	((bitsPerSample at:1) ~~ 8) ifTrue:[
+	    self error:'only 8 bit/sample supported'.
+	    ^ nil
+	].
+	((bitsPerSample at:2) ~~ 8) ifTrue:[
+	    self error:'only 8 bit/sample supported'.
+	    ^ nil
+	].
+	((bitsPerSample at:3) ~~ 8) ifTrue:[
+	    self error:'only 8 bit/sample supported'.
+	    ^ nil
+	].
+	bytesPerRow := width * samplesPerPixel.
     ] ifFalse:[
-	stripOffsets := Array basicNew:height.
-	bytesPerRow := nBytes // height.
-	stripByteCounts := (Array basicNew:height) atAllPut:bytesPerRow.
+	(nPlanes == 2) ifTrue:[
+	    (planarConfiguration ~~ 2) ifTrue:[
+		self error:'only separate planes supported'.
+		^ nil
+	    ].
+	    'TIFFReader: ignoring alpha plane' errorPrintNL.
+	    nPlanes := 1
+	].
+	(nPlanes == 1) ifFalse:[
+	    self error:'only 3-sample rgb / monochrome supported'.
+	    ^ nil
+	].
+	bytesPerRow := (width * (bitsPerSample at:1) + 7) // 8.
+    ].
+
+    stripByteCounts isNil ifTrue:[
+	self error:'currently require stripByteCounts'.
+	^ nil
+    ].
+
+    'TIFFReader: decompressing LZW ...' infoPrintNL.
+
+    data := ByteArray uninitializedNew:(bytesPerRow * height).
+
+    offset := 1.
+    stripNr := 0.
+
+    row := 1.
+    bytesPerStrip := bytesPerRow * rowsPerStrip.
+    prevSize := 0.
+    [row <= height] whileTrue:[
+	stripNr := stripNr + 1.
+	inStream position:((stripOffsets at:stripNr) + 1).
+	nBytes := stripByteCounts at:stripNr.
+	(nBytes > prevSize) ifTrue:[
+	    compressedStrip := ByteArray uninitializedNew:nBytes.
+	    prevSize := nBytes
+	].
+	inStream nextBytes:nBytes
+		      into:compressedStrip.
+	self class decompressLZWFrom:compressedStrip
+			       count:nBytes
+				into:data
+			  startingAt:offset.
+	offset := offset + bytesPerStrip.
+	row := row + rowsPerStrip
+    ].
+
+    (predictor == 2) ifTrue:[
+	self class decodeDelta:3 in:data width:width height:height
+    ]
+!
+
+readLongs:nLongs
+    "read nLongs long numbers (32bit) and return them in an array"
+
+    |oldPos offset values msb 
+     n "{ Class: SmallInteger }" |
+
+    n := nLongs.
+
+    msb := byteOrder ~~ #lsb.
+    values := Array basicNew:n.
+    (n == 1) ifTrue:[
+	values at:1 put:(inStream nextLongMSB:msb).
+    ] ifFalse:[
+	offset := inStream nextLongMSB:msb.
+	oldPos := inStream position.
+	inStream position:(offset + 1).
+	1 to:n do:[:index |
+	    values at:index put:(inStream nextLongMSB:msb)
+	].
+	inStream position:oldPos
+    ].
+    ^ values
+!
+
+readNeXTJPEGTiffImageData
+    'TIFFReader: jpeg compression not implemented' errorPrintNL
+!
+
+readNeXTRLE2TiffImageData
+    'TIFFReader: next 2bit rle compression not implemented' errorPrintNL.
+!
+
+readPackbitsTiffImageData
+    "had no samples yet - however, packbits decompression
+     is rather trivial to add ..."
+
+    'TIFFReader: packbits compression not implemented' errorPrintNL
+!
+
+readShorts:nShorts
+    "read nShorts short numbers (16bit) and return them in an array"
+
+    |oldPos offset values msb val2
+     n "{ Class: SmallInteger }" |
 
-	offs := 1.
-	h := height.
-	1 to:h do:[:row |
-	    stripOffsets at:row put:(outStream position - 1).
-	    outStream nextPutBytes:bytesPerRow from:data startingAt:offs.
-	    offs := offs + bytesPerRow
+    n := nShorts.
+
+    msb := (byteOrder ~~ #lsb).
+    values := Array basicNew:n.
+    (n <= 2) ifTrue:[
+	values at:1 put:(inStream nextUnsignedShortMSB:msb).
+	val2 := inStream nextUnsignedShortMSB:msb.
+
+	(n == 2) ifTrue:[
+	    values at:2 put:val2
+	]
+    ] ifFalse:[
+	offset := inStream nextLongMSB:msb.
+	oldPos := inStream position.
+	inStream position:(offset + 1).
+	1 to:n do:[:index |
+	    values at:index put:(inStream nextUnsignedShortMSB:msb)
+	].
+	inStream position:oldPos
+    ].
+    ^ values
+!
+
+readUncompressedTiffImageData
+    |bytesPerRow bitsPerRow nPlanes 
+     stripNr       "{ Class: SmallInteger }"
+     offset        "{ Class: SmallInteger }"
+     row           "{ Class: SmallInteger }" 
+     nBytes        "{ Class: SmallInteger }"
+     bitsPerPixel overAllBytes|
+
+    nPlanes := samplesPerPixel.
+
+    "only support 1-sample/pixel,
+     with alpha - if separate planes,
+     or rgb - if non separate planes and no alpha"
+
+    (nPlanes == 2) ifTrue:[
+	(planarConfiguration ~~ 2) ifTrue:[
+	    self error:'with alpha, only separate planes supported'.
+	    ^ nil
 	].
-	rowsPerStrip := 1
+	'TIFFReader: ignoring alpha plane' errorPrintNL.
+	nPlanes := 1.
+	bitsPerPixel := bitsPerSample at:1.
+	bitsPerSample := Array with:bitsPerPixel.
+	samplesPerPixel := 1.
+    ] ifFalse:[
+	(nPlanes == 3) ifTrue:[
+	    (planarConfiguration ~~ 1) ifTrue:[
+		self error:'only non separate planes supported'.
+		^ nil
+	    ].
+	    bitsPerSample ~= #(8 8 8) ifTrue:[
+		self error:'only 8/8/8 rgb images supported'.
+		^ nil
+	    ].
+	    bitsPerPixel := 24
+	] ifFalse:[
+	    (nPlanes ~~ 1) ifTrue:[
+		self error:'format not supported'.
+		^ nil
+	    ].
+	    bitsPerPixel := bitsPerSample at:1.
+	]
     ].
+
+    bitsPerRow := width * bitsPerPixel.
+    bytesPerRow := bitsPerRow // 8.
+    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
+	bytesPerRow := bytesPerRow + 1
+    ].
+
+    overAllBytes := bytesPerRow * height.
+    data := ByteArray uninitializedNew:overAllBytes.
+
+    offset := 1.
+    stripNr := 0.
+
+    row := 1.
+    [row <= height] whileTrue:[
+	stripNr := stripNr + 1.
+	nBytes := stripByteCounts at:stripNr.
+	inStream position:((stripOffsets at:stripNr) + 1).
+
+	inStream nextBytes:nBytes into:data startingAt:offset.
+	offset := offset + nBytes.
+	row := row + rowsPerStrip
+    ]
+!
+
+writeBitsPerSample
 "
-    'stripOffsets: ' print. stripOffsets printNewline.
-    'stripByteCounts: ' print. stripByteCounts printNewline.
+'bitsPerSample: ' print. bitsPerSample printNewline.
+'store bitspersample at: ' print. outStream position printNewline.
 "
+    bitsPerSamplePos := outStream position.
+    bitsPerSample do:[:n |
+	self writeShort:n
+    ]
 !
 
 writeColorMap
@@ -1081,17 +1042,6 @@
     ]
 !
 
-writeStripOffsets
-"
-'stripOffsets: ' print. stripOffsets printNewline.
-'store stripoffsets at: ' print. outStream position printNewline.
-"
-    stripOffsetsPos := outStream position.
-    stripOffsets do:[:o |
-	self writeLong:o
-    ]
-!
-
 writeStripByteCounts
 "
 'stripByteCounts: ' print. stripByteCounts printNewline.
@@ -1103,14 +1053,14 @@
     ]
 !
 
-writeBitsPerSample
+writeStripOffsets
 "
-'bitsPerSample: ' print. bitsPerSample printNewline.
-'store bitspersample at: ' print. outStream position printNewline.
+'stripOffsets: ' print. stripOffsets printNewline.
+'store stripoffsets at: ' print. outStream position printNewline.
 "
-    bitsPerSamplePos := outStream position.
-    bitsPerSample do:[:n |
-	self writeShort:n
+    stripOffsetsPos := outStream position.
+    stripOffsets do:[:o |
+	self writeLong:o
     ]
 !
 
@@ -1391,245 +1341,295 @@
     ].
 !
 
-readUncompressedTiffImageData
-    |bytesPerRow bitsPerRow nPlanes 
-     stripNr       "{ Class: SmallInteger }"
-     offset        "{ Class: SmallInteger }"
-     row           "{ Class: SmallInteger }" 
-     nBytes        "{ Class: SmallInteger }"
-     bitsPerPixel overAllBytes|
+writeUncompressedBits
+    "write bits as one or multiple strips"
+
+    |offs bytesPerRow nBytes
+     h "{ Class: SmallInteger }"|
 
-    nPlanes := samplesPerPixel.
+    nBytes := data size.
+    nBytes < 16rFFFF ifTrue:[
+	stripOffsets := Array with:(outStream position - 1).
+	stripByteCounts := Array with:nBytes.
+	outStream nextPutBytes:nBytes from:data.
+	rowsPerStrip := height
+    ] ifFalse:[
+	stripOffsets := Array basicNew:height.
+	bytesPerRow := nBytes // height.
+	stripByteCounts := (Array basicNew:height) atAllPut:bytesPerRow.
 
-    "only support 1-sample/pixel,
-     with alpha - if separate planes,
-     or rgb - if non separate planes and no alpha"
-
-    (nPlanes == 2) ifTrue:[
-	(planarConfiguration ~~ 2) ifTrue:[
-	    self error:'with alpha, only separate planes supported'.
-	    ^ nil
+	offs := 1.
+	h := height.
+	1 to:h do:[:row |
+	    stripOffsets at:row put:(outStream position - 1).
+	    outStream nextPutBytes:bytesPerRow from:data startingAt:offs.
+	    offs := offs + bytesPerRow
 	].
-	'TIFFReader: ignoring alpha plane' errorPrintNL.
-	nPlanes := 1.
-	bitsPerPixel := bitsPerSample at:1.
-	bitsPerSample := Array with:bitsPerPixel.
-	samplesPerPixel := 1.
+	rowsPerStrip := 1
+    ].
+"
+    'stripOffsets: ' print. stripOffsets printNewline.
+    'stripByteCounts: ' print. stripByteCounts printNewline.
+"
+! !
+
+!TIFFReader methodsFor:'reading from file'!
+
+fromStream:aStream
+    "read an image from aStream"
+
+    |char1 char2 version 
+     numberOfTags "{ Class: SmallInteger }"
+     tagType      "{ Class: SmallInteger }"
+     numberType   "{ Class: SmallInteger }"
+     length       "{ Class: SmallInteger }"
+     result offset ok msb|
+
+    inStream := aStream.
+
+    char1 := aStream next.
+    char2 := aStream next.
+    (char1 ~~ char2) ifTrue:[
+	'TIFFReader: not a tiff file' errorPrintNL.
+	^ nil
+    ].
+    (char1 == $I) ifTrue:[
+	byteOrder := #lsb.
+	msb := false.
     ] ifFalse:[
-	(nPlanes == 3) ifTrue:[
-	    (planarConfiguration ~~ 1) ifTrue:[
-		self error:'only non separate planes supported'.
-		^ nil
-	    ].
-	    bitsPerSample ~= #(8 8 8) ifTrue:[
-		self error:'only 8/8/8 rgb images supported'.
-		^ nil
-	    ].
-	    bitsPerPixel := 24
+	(char1 == $M) ifTrue:[
+	    byteOrder := #msb.
+	    msb := true.
 	] ifFalse:[
-	    (nPlanes ~~ 1) ifTrue:[
-		self error:'format not supported'.
-		^ nil
-	    ].
-	    bitsPerPixel := bitsPerSample at:1.
+	    'TIFFReader: not a tiff file' errorPrintNL.
+	    ^ nil
 	]
     ].
 
-    bitsPerRow := width * bitsPerPixel.
-    bytesPerRow := bitsPerRow // 8.
-    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
-	bytesPerRow := bytesPerRow + 1
+    aStream binary.
+
+    version := self readShort.
+    (version ~~ 42) ifTrue:[
+	'TIFFReader: version of tiff-file not supported' errorPrintNL.
+	^ nil
     ].
 
-    overAllBytes := bytesPerRow * height.
-    data := ByteArray uninitializedNew:overAllBytes.
-
-    offset := 1.
-    stripNr := 0.
-
-    row := 1.
-    [row <= height] whileTrue:[
-	stripNr := stripNr + 1.
-	nBytes := stripByteCounts at:stripNr.
-	inStream position:((stripOffsets at:stripNr) + 1).
+    "setup default values"
 
-	inStream nextBytes:nBytes into:data startingAt:offset.
-	offset := offset + nBytes.
-	row := row + rowsPerStrip
-    ]
-!
+    compression := 1. "none"
+    fillOrder := #msb.
+    planarConfiguration := 1.
+    photometric := nil.
+    bitsPerSample := 1.
+    samplesPerPixel := 1.
+    width := nil.
+    height := nil.
+    stripOffsets := nil.
+    rowsPerStrip := nil.
+    "resolutionUnit := 2."
+    predictor := 1.
 
-readLZWTiffImageData
-    "read LZW compressed tiff data; this method only
-     handles 3x8 rgb and 1x2 or 2x2 greyscale images.
-     For 2x2 greyscale images, the alpha plane is ignored.
-     (maybe other formats work also - its simply not
-      tested)"
+    offset := aStream nextLongMSB:msb.
+    aStream position:offset + 1.
+
+    numberOfTags := self readShort.
+    1 to:numberOfTags do:[:index |
+	tagType := self readShort.
+	numberType := self readShort.
+	length := aStream nextLongMSB:msb.
+	self decodeTiffTag:tagType numberType:numberType length:length
+    ].
 
-    |bytesPerRow compressedStrip nPlanes 
-     bytesPerStrip "{ Class: SmallInteger }"
-     nBytes        "{ Class: SmallInteger }"
-     prevSize      "{ Class: SmallInteger }"
-     stripNr       "{ Class: SmallInteger }"
-     offset        "{ Class: SmallInteger }"
-     row           "{ Class: SmallInteger }" |
+    offset := aStream nextLongMSB:msb.
+    (offset ~~ 0) ifTrue:[
+	'TIFFReader: more tags ignored' errorPrintNL
+    ].
 
-    nPlanes := samplesPerPixel.
+    "check for required tags"
+    ok := true.
+    width isNil ifTrue:[
+	'TIFFReader: missing width tag' errorPrintNL.
+	ok := false
+    ].
 
-    (nPlanes == 3) ifTrue:[
-	((bitsPerSample at:1) ~~ 8) ifTrue:[
-	    self error:'only 8 bit/sample supported'.
-	    ^ nil
-	].
-	((bitsPerSample at:2) ~~ 8) ifTrue:[
-	    self error:'only 8 bit/sample supported'.
-	    ^ nil
-	].
-	((bitsPerSample at:3) ~~ 8) ifTrue:[
-	    self error:'only 8 bit/sample supported'.
-	    ^ nil
-	].
-	bytesPerRow := width * samplesPerPixel.
-    ] ifFalse:[
-	(nPlanes == 2) ifTrue:[
-	    (planarConfiguration ~~ 2) ifTrue:[
-		self error:'only separate planes supported'.
-		^ nil
-	    ].
-	    'TIFFReader: ignoring alpha plane' errorPrintNL.
-	    nPlanes := 1
-	].
-	(nPlanes == 1) ifFalse:[
-	    self error:'only 3-sample rgb / monochrome supported'.
-	    ^ nil
-	].
-	bytesPerRow := (width * (bitsPerSample at:1) + 7) // 8.
+    height isNil ifTrue:[
+	'TIFFReader: missing length tag' errorPrintNL.
+	ok := false
+    ].
+
+    photometric isNil ifTrue:[
+	'TIFFReader: missing photometric tag' errorPrintNL.
+	ok := false
+    ].
+
+    stripOffsets isNil ifTrue:[
+	'TIFFReader: missing stripOffsets tag' errorPrintNL.
+	ok := false
     ].
 
     stripByteCounts isNil ifTrue:[
-	self error:'currently require stripByteCounts'.
+	stripOffsets size == 1 ifTrue:[
+	    stripByteCounts := Array with:(self bitsPerPixel // 8) * width * height
+	]
+    ].
+
+    stripByteCounts isNil ifTrue:[
+	'TIFFReader: missing stripByteCounts tag' errorPrintNL.
+	ok := false
+    ].
+
+    ok ifFalse:[
 	^ nil
     ].
 
-    'TIFFReader: decompressing LZW ...' infoPrintNL.
-
-    data := ByteArray uninitializedNew:(bytesPerRow * height).
-
-    offset := 1.
-    stripNr := 0.
+    "given all the information, read the bits"
 
-    row := 1.
-    bytesPerStrip := bytesPerRow * rowsPerStrip.
-    prevSize := 0.
-    [row <= height] whileTrue:[
-	stripNr := stripNr + 1.
-	inStream position:((stripOffsets at:stripNr) + 1).
-	nBytes := stripByteCounts at:stripNr.
-	(nBytes > prevSize) ifTrue:[
-	    compressedStrip := ByteArray uninitializedNew:nBytes.
-	    prevSize := nBytes
-	].
-	inStream nextBytes:nBytes
-		      into:compressedStrip.
-	self class decompressLZWFrom:compressedStrip
-			       count:nBytes
-				into:data
-			  startingAt:offset.
-	offset := offset + bytesPerStrip.
-	row := row + rowsPerStrip
+    rowsPerStrip isNil ifTrue:[
+	rowsPerStrip := height
     ].
 
-    (predictor == 2) ifTrue:[
-	self class decodeDelta:3 in:data width:width height:height
-    ]
-!
-
-readCCITTGroup3TiffImageData
-    "not really tested - all I got is a single
-     fax from NeXT step"
+    ok := false.
+    (compression == 1) ifTrue:[
+	result := self readUncompressedTiffImageData.
+	ok := true
+    ].
+    (compression == 2) ifTrue:[
+	result := self readCCITT3RLETiffImageData.
+	ok := true
+    ].
+    (compression == 3) ifTrue:[
+	result := self readCCITTGroup3TiffImageData.
+	ok := true
+    ]. 
+    (compression == 4) ifTrue:[
+	result := self readCCITTGroup4TiffImageData.
+	ok := true
+    ]. 
+    (compression == 5) ifTrue:[
+	result := self readLZWTiffImageData.
+	ok := true
+    ].
+    (compression == 6) ifTrue:[
+	result := self readJPEGTiffImageData.
+	ok := true
+    ].
+    (compression == 32766) ifTrue:[
+	result := self readNeXTRLE2TiffImageData.
+	ok := true
+    ].
+    (compression == 32771) ifTrue:[
+	result := self readCCITTRLEWTiffImageData.
+	ok := true
+    ].
+    (compression == 32773) ifTrue:[
+	result := self readPackbitsTiffImageData.
+	ok := true
+    ].
+    (compression == 32865) ifTrue:[
+	result := self readNeXTJPEGTiffImageData.
+	ok := true
+    ].
+    ok ifFalse:[
+	'TIFFReader: compression type ' errorPrint. compression errorPrint.
+	' not known' errorPrintNL
+    ].
+    ^ result
+! !
 
-    |bytesPerRow bitsPerRow compressedStrip nPlanes 
-     stripNr       "{ Class: SmallInteger }"
-     offset        "{ Class: SmallInteger }"
-     row           "{ Class: SmallInteger }"
-     bytesPerStrip "{ Class: SmallInteger }" |
+!TIFFReader methodsFor:'writing to file'!
+
+save:image onFile:aFileName
+    "save image as (uncompressed) TIFF file on aFileName"
 
-    nPlanes := samplesPerPixel.
-    (nPlanes == 2) ifTrue:[
-	'TIFFReader: ignoring alpha plane' errorPrintNL.
-	nPlanes := 1
-    ].
+    |pos1 pos|
 
-    (nPlanes ~~ 1) ifTrue:[
-	self error:'only monochrome/greyscale supported'.
+    outStream := FileStream newFileNamed:aFileName.
+    outStream isNil ifTrue:[
+	'TIFFReader: create error' errorPrintNL. 
 	^ nil
     ].
 
-    stripByteCounts isNil ifTrue:[
-	self error:'currently require stripByteCounts'.
-	^ nil
-    ].
-    (rowsPerStrip ~~ 1) isNil ifTrue:[
-	self error:'currently require rowsPerStrip to be 1'.
-	^ nil
+    "save as msb"
+
+    byteOrder := #msb.
+"
+    byteOrder := #lsb.
+"
+    fillOrder := #msb.
+    width := image width.
+    height := image height.
+    photometric := image photometric.
+    samplesPerPixel := image samplesPerPixel.
+    bitsPerSample := image bitsPerSample.
+    colorMap := image colorMap.
+    planarConfiguration := 1.
+    compression := 1.   "none"
+    data := image bits.
+
+    currentOffset := 0.
+
+    (byteOrder == #msb) ifTrue:[
+	outStream nextPut:$M.
+	outStream nextPut:$M.
+    ] ifFalse:[
+	outStream nextPut:$I.
+	outStream nextPut:$I.
     ].
+    currentOffset := currentOffset + 2.
 
-    'TIFFReader: decompressing CCITT-3 ...' infoPrintNL.
+    outStream binary.
+
+    self writeShort:42.
+    currentOffset := currentOffset + 2.
 
-    bitsPerRow := width * (bitsPerSample at:1).
-    bytesPerRow := bitsPerRow // 8.
-    ((bitsPerRow \\ 8) ~~ 0) ifTrue:[
-	bytesPerRow := bytesPerRow + 1
+    pos1 := outStream position.
+    self writeLong:0.           "start of tags - filled in later"
+    currentOffset := currentOffset + 4.
+
+    "output strips"
+
+    self writeUncompressedBits. "this outputs bits as strips, sets stripOffsets and stripByteCounts"
+    self writeStripOffsets.     "this outputs strip offsets, sets stripOffsetsPos"
+    self writeStripByteCounts.  "this outputs strip bytecounts, sets stripByteCountPos"
+    self writeBitsPerSample.    "this outputs bitsPerSample, sets bitsPerSamplePos"
+    photometric == #palette ifTrue:[
+	self writeColorMap      "this outputs colorMap, sets colorMapPos"
     ].
 
-    data := ByteArray new:(bytesPerRow * height).
-    compressedStrip := ByteArray uninitializedNew:bytesPerRow.
-
-    offset := 1.
-    stripNr := 0.
-
-    row := 1.
-    bytesPerStrip := bytesPerRow * rowsPerStrip.
-    [row <= height] whileTrue:[
-	stripNr := stripNr + 1.
-	inStream position:((stripOffsets at:stripNr) + 1).
-	inStream nextBytes:(stripByteCounts at:stripNr) into:compressedStrip.
-	self class decompressCCITT3From:compressedStrip
-				   into:data
-			     startingAt:offset
-				  count:width.
-	offset := offset + bytesPerStrip.
-	row := row + rowsPerStrip
-    ]
-!
-
-readJPEGTiffImageData
-    'TIFFReader: jpeg compression not implemented' errorPrintNL
-!
+    pos := outStream position.                  "backpatch tag offset"
+    outStream position:pos1.
+    self writeLong:(pos - 1).                   "fill in tag offset"
+    outStream position:pos.
+"
+('patch tag offset at: ', (pos1 printStringRadix:16) , ' to ',
+			 (pos printStringRadix:16)) printNewline.
+"
+    "output tag data"
 
-readNeXTJPEGTiffImageData
-    'TIFFReader: jpeg compression not implemented' errorPrintNL
-!
-
-readCCITT3RLETiffImageData
-     'TIFFReader: ccitt mod Huffman (rle) compression not implemented' errorPrintNL.
-!
-
-readCCITT3RLEWTiffImageData
-     'TIFFReader: ccitt mod Huffman (rlew) compression not implemented' errorPrintNL.
-!
+    photometric == #palette ifTrue:[
+	self writeShort:10.  "10 tags"
+    ] ifFalse:[
+	self writeShort:9.   "9 tags"
+    ].
+    self writeTag:256.               "image width"
+    self writeTag:257.               "image height"
+    self writeTag:258.               "bits per sample"
+    self writeTag:259.               "compression"
+    self writeTag:262.               "photometric"
+    self writeTag:273.               "strip offsets"
+    self writeTag:278.               "rowsPerStrip"
+    self writeTag:279.               "strip byte counts"
+    self writeTag:284.               "planarconfig"
+    photometric == #palette ifTrue:[
+	self writeTag:320            "colorMap"
+    ].
+    self writeLong:0.                "end of tags mark"
+    outStream close
+! !
 
-readCCITTGroup4TiffImageData
-    'TIFFReader: ccitt group4 fax compression not implemented' errorPrintNL.
-!
+!TIFFReader class methodsFor:'documentation'!
 
-readNeXTRLE2TiffImageData
-    'TIFFReader: next 2bit rle compression not implemented' errorPrintNL.
-!
-
-readPackbitsTiffImageData
-    "had no samples yet - however, packbits decompression
-     is rather trivial to add ..."
-
-    'TIFFReader: packbits compression not implemented' errorPrintNL
+version
+    ^ '$Header: /cvs/stx/stx/libview2/TIFFReader.st,v 1.27 1995-12-07 11:38:46 cg Exp $'
 ! !
+TIFFReader initialize!
--- a/XBMReader.st	Thu Dec 07 11:34:06 1995 +0100
+++ b/XBMReader.st	Thu Dec 07 12:39:00 1995 +0100
@@ -10,8 +10,6 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.4 on 18-feb-1995 at 2:23:58 am'!
-
 ImageReader subclass:#XBMReader
 	 instanceVariableNames:''
 	 classVariableNames:''
@@ -35,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.17 1995-11-11 16:05:42 cg Exp $'
-!
-
 documentation
 "
     this class provides methods for loading and saving x-bitmap-file images.
@@ -57,6 +51,16 @@
 
 !XBMReader class methodsFor:'testing'!
 
+canRepresent:anImage
+    "return true, if anImage can be represented in my file format"
+
+    |photometric|
+
+    (anImage depth ~~ 1) ifTrue:[^ false.].
+    (((photometric := anImage photometric) ~~ #blackIs0) and:[photometric ~~ #whiteIs0]) ifTrue:[^ false.].
+    ^ true
+!
+
 isValidImageFile:aFileName
     "return true, if aFileName contains an x-bitmap-file image"
 
@@ -90,16 +94,6 @@
     ].
     inStream close.
     ^ true
-!
-
-canRepresent:anImage
-    "return true, if anImage can be represented in my file format"
-
-    |photometric|
-
-    (anImage depth ~~ 1) ifTrue:[^ false.].
-    (((photometric := anImage photometric) ~~ #blackIs0) and:[photometric ~~ #whiteIs0]) ifTrue:[^ false.].
-    ^ true
 ! !
 
 !XBMReader methodsFor:'reading from file'!
@@ -275,4 +269,9 @@
     "
 ! !
 
+!XBMReader class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview2/XBMReader.st,v 1.18 1995-12-07 11:39:00 cg Exp $'
+! !
 XBMReader initialize!