checkin from browser
authorClaus Gittinger <cg@exept.de>
Thu, 07 Dec 1995 12:23:25 +0100
changeset 282 fe2d82f516f1
parent 281 4f04a56b1641
child 283 c4ff5f26ff44
checkin from browser
Depth24Image.st
--- a/Depth24Image.st	Thu Dec 07 12:18:40 1995 +0100
+++ b/Depth24Image.st	Thu Dec 07 12:23:25 1995 +0100
@@ -33,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libview/Depth24Image.st,v 1.18 1995-11-22 14:33:08 cg Exp $'
-!
-
 documentation
 "
     this class represents true-color (24 bit / pixel) images.
@@ -51,39 +47,6 @@
     ^ 24
 ! !
 
-!Depth24Image methodsFor:'queries'!
-
-bitsPerPixel
-    "return the number of bits per pixel"
-
-    ^ 24
-!
-
-bitsPerRow
-    "return the number of bits in one scanline of the image"
-
-    ^  width * 24
-!
-
-bitsPerSample
-    "return the number of bits per sample.
-     The return value is an array of bits-per-plane."
-
-    ^ #(8 8 8)
-!
-
-bytesPerRow
-    "return the number of bytes in one scanline of the image"
-
-    ^ width * 3
-!
-
-samplesPerPixel
-    "return the number of samples per pixel in the image."
-
-    ^ 3
-! !
-
 !Depth24Image methodsFor:'accessing'!
 
 atX:x y:y
@@ -125,23 +88,6 @@
     bytes at:(index + 2) put:val.
 !
 
-valueAtX:x y:y
-    "retrieve a pixel at x/y; return a color.
-     Pixels start at x=0 , y=0 for upper left pixel, end at
-     x = width-1, y=height-1 for lower right pixel"
-
-    |index "{ Class: SmallInteger }"
-     rVal  "{ Class: SmallInteger }"
-     gVal  "{ Class: SmallInteger }"
-     bVal  "{ Class: SmallInteger }"|
-
-    index := 1 + (((width * y) + x) * 3).
-    rVal := bytes at:(index).
-    gVal := bytes at:(index + 1).
-    bVal := bytes at:(index + 2).
-    ^ (((rVal bitShift:8) bitOr:gVal) bitShift:8) bitOr:bVal
-!
-
 atX:x y:y putValue:aPixelValue
     "set a pixel at x/y to aPixelValue, which is 24 bits RGB.
      Pixels start at x=0 , y=0 for upper left pixel, end at
@@ -157,248 +103,27 @@
     bytes at:(index + 1) put:(val bitAnd:16rFF).
     val := val bitShift:-8.
     bytes at:(index) put:val.
-! !
-
-!Depth24Image methodsFor:'enumerating'!
-
-valueAtY:y from:xLow to:xHigh do:aBlock
-    "perform aBlock for each pixelValue from x1 to x2 in row y.
-     The block is passed the pixelValue at each pixel.
-     This method allows slighly faster processing of an
-     image than using valueAtX:y:, since some processing can be
-     avoided when going from pixel to pixel. However, for
-     real image processing, specialized methods should be written.
-     Notice that the pixelValue is the r/g/b value packed into an integer
-     (r bitShift:16) bitOr:(g bitSHift:8) bitOr:b"
-
-    |srcIndex "{ Class: SmallInteger }"
-     x1       "{ Class: SmallInteger }"
-     x2       "{ Class: SmallInteger }"
-     r        "{ Class: SmallInteger }"
-     g        "{ Class: SmallInteger }"
-     b        "{ Class: SmallInteger }"|
-
-    x1 := xLow.
-    x2 := xHigh.
-
-    srcIndex := 1 + (((width * y) + x1) * 3).
-
-    x1 to:x2 do:[:x |
-	r := bytes at:(srcIndex).
-	g := bytes at:(srcIndex + 1).
-	b := bytes at:(srcIndex + 2).
-	srcIndex := srcIndex + 3.
-	aBlock value:x value:(((r bitShift:16) bitOr:(g bitShift:8)) bitOr:b)
-    ]
 !
 
-atY:y from:xLow to:xHigh do:aBlock
-    "perform aBlock for each pixel from x1 to x2 in row y.
-     The block is passed the color at each pixel.
-     This method allows slighly faster processing of an
-     image than using atX:y:, since some processing can be
-     avoided when going from pixel to pixel. However, for
-     real image processing, specialized methods should be written."
-
-    |srcIndex "{ Class: SmallInteger }"
-     x1       "{ Class: SmallInteger }"
-     x2       "{ Class: SmallInteger }"
-     rVal     "{ Class: SmallInteger }"
-     gVal     "{ Class: SmallInteger }"
-     bVal     "{ Class: SmallInteger }"
-     lastR lastG lastB lastColor|
-
-    photometric ~~ #rgb ifTrue:[
-	self error:'format not supported'.
-	^ nil
-    ].
+valueAtX:x y:y
+    "retrieve a pixel at x/y; return a color.
+     Pixels start at x=0 , y=0 for upper left pixel, end at
+     x = width-1, y=height-1 for lower right pixel"
 
-    x1 := xLow.
-    x2 := xHigh.
-
-    srcIndex := 1 + (((width * y) + x1) * 3).
+    |index "{ Class: SmallInteger }"
+     rVal  "{ Class: SmallInteger }"
+     gVal  "{ Class: SmallInteger }"
+     bVal  "{ Class: SmallInteger }"|
 
-    x1 to:x2 do:[:x |
-	rVal := bytes at:(srcIndex).
-	gVal := bytes at:(srcIndex + 1).
-	bVal := bytes at:(srcIndex + 2).
-	srcIndex := srcIndex + 3.
-	(rVal == lastR and:[gVal == lastG and:[bVal == lastB]]) ifFalse:[
-	    lastColor := Color red:rVal * 100 / 255
-			     green:gVal * 100 / 255
-			      blue:bVal * 100 / 255.
-	    lastR := rVal.
-	    lastG := gVal.
-	    lastB := bVal.
-	].
-	aBlock value:x value:lastColor
-    ]
+    index := 1 + (((width * y) + x) * 3).
+    rVal := bytes at:(index).
+    gVal := bytes at:(index + 1).
+    bVal := bytes at:(index + 2).
+    ^ (((rVal bitShift:8) bitOr:gVal) bitShift:8) bitOr:bVal
 ! !
 
 !Depth24Image methodsFor:'converting rgb images'!
 
-rgbImageAsGreyFormOn:aDevice
-    "convert an rgb image to a grey image for greyscale displays"
-
-    |deviceDepth|
-
-    deviceDepth := aDevice depth.
-
-    "I have specially tuned methods for monochrome"
-    (deviceDepth == 1) ifTrue:[
-	DitherAlgorithm == #error ifTrue:[
-	    ^ self rgbImageAsErrorDitheredGreyFormOn:aDevice
-	].
-	DitherAlgorithm == #pattern ifTrue:[
-	    ^ self rgbImageAsPatternDitheredGreyFormOn:aDevice
-	].
-	^ self rgbImageAsMonoFormOn:aDevice
-    ].
-
-    "and for 2plane greyscale (i.e. NeXTs)"
-    (deviceDepth == 2) ifTrue:[
-	DitherAlgorithm == #error  ifTrue:[
-	    ^ self rgbImageAsErrorDitheredGreyFormOn:aDevice
-	].
-	DitherAlgorithm == #pattern  ifTrue:[
-	    ^ self rgbImageAsPatternDitheredGreyFormOn:aDevice
-	].
-	^ self rgbImageAs2PlaneFormOn:aDevice
-    ].
-
-    (deviceDepth == 8) ifTrue:[
-	^ self rgbImageAs8BitGreyFormOn:aDevice
-    ].
-
-    "mhmh need another converter ...
-     till then we do:"
-    DitherAlgorithm == #error  ifTrue:[
-	^ self rgbImageAsErrorDitheredGreyFormOn:aDevice
-    ].
-    DitherAlgorithm == #pattern  ifTrue:[
-	^ self rgbImageAsPatternDitheredGreyFormOn:aDevice
-    ].
-    ^ self rgbImageAsMonoFormOn:aDevice
-!
-
-rgbImageAsMonoFormOn:aDevice
-    "return a 1-bit monochrome form for aDevice from the rgb picture,
-     using a threshold algorithm. 
-     (i.e. grey value < 0.5 -> black, grey value >= 0.5 -> white)."
-
-    |monoBits f
-     w        "{ Class: SmallInteger }"
-     h        "{ Class: SmallInteger }"
-     r        "{ Class: SmallInteger }"
-     g        "{ Class: SmallInteger }"
-     b        "{ Class: SmallInteger }"
-     v        "{ Class: SmallInteger }"
-     map rMap gMap bMap
-     srcIndex "{ Class: SmallInteger }"
-     dstIndex "{ Class: SmallInteger }"
-     bits     "{ Class: SmallInteger }"
-     bitCount "{ Class: SmallInteger }"
-     failed |
-
-    w := width.
-    h := height.
-    monoBits := ByteArray uninitializedNew:(((w + 7) // 8) * h).
-    failed := true.
-%{
-    register unsigned char *srcPtr, *dstPtr;
-    register _v, _bits, _bitCount;
-    register j;
-    register i;
-    extern OBJ ByteArray;
-
-    if (__isByteArray(_INST(bytes))
-     && __isByteArray(monoBits)) {
-	failed = false;
-	srcPtr = _ByteArrayInstPtr(_INST(bytes))->ba_element;
-	dstPtr = _ByteArrayInstPtr(monoBits)->ba_element;
-	for (i=_intVal(h); i>0; i--) {
-	    _bitCount = 0;
-	    _bits = 0;
-	    for (j=_intVal(w); j>0; j--) {
-		_bits <<= 1; 
-
-		_v = (*srcPtr++ * 3);   /* 0.3*r + 0.6*g + b */
-		_v += (*srcPtr++ * 6);
-		_v += *srcPtr++;
-		_v /= 10;
-		if (_v & 0x80)
-		    _bits |= 1;
-
-		_bitCount++;
-		if (_bitCount == 8) {
-		    *dstPtr++ = _bits;
-		    _bits = 0;
-		    _bitCount = 0;
-		}
-	    }
-	    if (_bitCount != 0) {
-		while (_bitCount++ != 8) _bits <<= 1;
-		*dstPtr++ = _bits;
-	    }
-	}
-    }
-%}.
-
-    failed ifTrue:[
-"/ the above is equivalent to:
-"/
-"/        srcIndex := 1.
-"/        dstIndex := 1.
-"/        1 to:h do:[:row |
-"/            bitCount := 0.
-"/            bits := 0.
-"/            1 to:w do:[:col |
-"/                bits := bits bitShift:1.
-"/
-"/                r := bytes at:srcIndex.
-"/                srcIndex := srcIndex + 1.
-"/                g := bytes at:srcIndex.
-"/                srcIndex := srcIndex + 1.
-"/                b := bytes at:srcIndex.
-"/                srcIndex := srcIndex + 1.
-"/                v := ((3 * r) + (6 * g) + (1 * b)) // 10.
-"/                ((v bitAnd:16r80) == 0) ifFalse:[
-"/                    bits := bits bitOr:1
-"/                ].
-"/                bitCount := bitCount + 1.
-"/                (bitCount == 8) ifTrue:[
-"/                    monoBits at:dstIndex put:bits.
-"/                    dstIndex := dstIndex + 1.
-"/                    bits := 0.
-"/                    bitCount := 0
-"/                ]
-"/            ].
-"/            (bitCount ~~ 0) ifTrue:[
-"/                [bitCount == 8] whileFalse:[
-"/                    bitCount := bitCount + 1.
-"/                    bits := bits bitShift:1.
-"/                ].
-"/                monoBits at:dstIndex put:bits.
-"/                dstIndex := dstIndex + 1
-"/            ]
-"/        ]
-	self primitiveFailed.
-	^ nil
-    ].
-
-    f := Form width:w height:h depth:1 on:aDevice.
-    f isNil ifTrue:[^ nil].
-    f initGC.
-    (aDevice blackpixel == 0) ifFalse:[
-	"have to invert bits"
-	f function:#copyInverted
-    ].
-    aDevice drawBits:monoBits depth:1 width:w height:h
-		   x:0 y:0
-		into:(f id) x:0 y:0 width:w height:h with:(f gcId).
-    ^ f
-!
-
 rgbImageAs2PlaneFormOn:aDevice
     "return a 2-bit device form for aDevice from the rgb picture,
      using a threshold algorithm. 
@@ -586,6 +311,380 @@
     ^ f
 !
 
+rgbImageAsDitheredPseudoFormOn:aDevice
+    "return a dithered pseudocolor form from the rgb-picture.
+     This method depends on fixColors being allocated (see Color>>getColors*)"
+
+    ^ self rgbImageAsDitheredPseudoFormOn:aDevice
+				   colors:Color fixColors
+				     nRed:Color numFixRed
+				     nGreen:Color numFixGreen
+				     nBlue:Color numFixBlue
+!
+
+rgbImageAsDitheredPseudoFormOn:aDevice colors:fixColors nRed:nRed nGreen:nGreen nBlue:nBlue
+    "return a dithered pseudocolor form from the rgb-picture"
+
+    |pseudoBits f
+     h        "{ Class: SmallInteger }"
+     w        "{ Class: SmallInteger }"
+"/     eR    "{Class: SmallInteger }"
+"/     eG    "{Class: SmallInteger }"
+"/     eB    "{Class: SmallInteger }"
+"/     wantR "{Class: SmallInteger }"
+"/     wantG "{Class: SmallInteger }"
+"/     wantB "{Class: SmallInteger }"
+     fixR  "{Class: SmallInteger }"
+     fixG  "{Class: SmallInteger }"
+     fixB  "{Class: SmallInteger }"
+     srcIndex "{ Class: SmallInteger }"
+     dstIndex "{ Class: SmallInteger }"
+     deviceDepth has8BitImage 
+     fixIds failed|
+
+    aDevice ~~ Display ifTrue:[^ nil].
+
+    fixR := nRed.
+    fixR == 0 ifTrue:[ ^ nil].
+    fixG := nGreen.
+    fixG == 0 ifTrue:[ ^ nil].
+    fixB := nBlue.
+    fixB == 0 ifTrue:[ ^ nil].
+    "/ simple check
+    (fixR * fixG * fixB) ~~ fixColors size ifTrue:[
+	self error:'invalid color array passed'.
+	^ nil
+    ].
+    fixIds := (fixColors asArray collect:[:clr | clr colorId]) asByteArray.
+
+    deviceDepth := aDevice depth.
+    deviceDepth == 8 ifTrue:[
+	has8BitImage := true.
+    ] ifFalse:[
+	has8BitImage := false.
+	aDevice supportedImageFormats do:[:fmt |
+	    (fmt at:#bitsPerPixel) == 8 ifTrue:[
+		has8BitImage := true.
+	    ]
+	]
+    ].
+    has8BitImage ifFalse:[^ nil].
+
+    'D24IMAGE: dithering ...' infoPrintNL.
+
+    pseudoBits := ByteArray uninitializedNew:(width * height).
+
+    h := height.
+    w := width.
+
+%{
+    int __x, __y;
+    int __eR, __eG, __eB;
+    int __wantR, __wantG, __wantB;
+    unsigned char *srcP, *dstP;
+    unsigned char *redP, *greenP, *blueP;
+    int pix;
+    unsigned char *idP;
+    int __fR, __fG, __fB;
+    int iR, iG, iB;
+    int idx;
+
+    if (__isByteArray(_INST(bytes))
+     && __isByteArray(pseudoBits)
+     && __isByteArray(fixIds)
+     && __bothSmallInteger(fixR, fixG)
+     && __isSmallInteger(fixB)) {
+	failed = false;
+
+	srcP = _ByteArrayInstPtr(_INST(bytes))->ba_element;
+	dstP = _ByteArrayInstPtr(pseudoBits)->ba_element;
+	idP = _ByteArrayInstPtr(fixIds)->ba_element;
+	__fR = _intVal(fixR)-1;
+	__fG = _intVal(fixG)-1;
+	__fB = _intVal(fixB)-1;
+
+	for (__y=_intVal(h); __y>0; __y--) {
+	    __eR = __eG = __eB = 0;
+	    for (__x=_intVal(w); __x>0; __x--) {
+		int t;
+		int __want;
+
+		/*
+		 * wR, wG and wB is the wanted r/g/b value;
+		 * compute the index into the dId table ..
+		 * values: 0..255; scale to 0..fR-1, 0..fG-1, 0..fB-1
+		 *
+		 * bad kludge: knows how to index into FixColor table
+		 */
+		__wantR = srcP[0] + __eR;
+		__wantG = srcP[1] + __eG;
+		__wantB = srcP[2] + __eB;
+		srcP += 3;
+
+		if (__wantR > 255) __want = 255;
+		else if (__wantR < 0) __want = 0;
+		else __want = __wantR;
+
+		iR = __want * __fR / 128;
+		iR = (iR / 2) + (iR & 1);
+		idx = iR * (__fG+1);
+
+		if (__wantG > 255) __want = 255;
+		else if (__wantG < 0) __want = 0;
+		else __want = __wantG;
+
+		iG = __want * __fG / 128;
+		iG = (iG / 2) + (iG & 1);
+		idx = (idx + iG) * (__fB+1);
+
+		if (__wantB > 255) __want = 255;
+		else if (__wantB < 0) __want = 0;
+		else __want = __wantB;
+
+		iB = __want * __fB / 128;
+		iB = (iB / 2) + (iB & 1);
+		idx = idx + iB;
+
+		/*
+		 * store the corresponding dither colorId
+		 */
+		*dstP++ = idP[idx];
+
+		/*
+		 * the new error:
+		 */
+		__eR = __wantR - (iR * 256 / __fR); 
+		__eG = __wantG - (iG * 256 / __fG); 
+		__eB = __wantB - (iB * 256 / __fB); 
+	    }
+	}
+    }
+%}.
+    failed ifTrue:[
+	self primitiveFailed.
+	^ nil
+
+"/ for non-C programmers:
+"/   the above code is (roughly) equivalent to:
+"/    srcIndex := 1.
+"/    dstIndex := 1.
+"/    1 to:h do:[:y |
+"/        eR := eG := eB := 0.
+"/        1 to:w do:[:x |
+"/            |pixel "{ Class: SmallInteger }"
+"/             clr 
+"/             idx   "{ Class: SmallInteger }"
+"/             iR    "{ Class: SmallInteger }"
+"/             iG    "{ Class: SmallInteger }"
+"/             iB    "{ Class: SmallInteger }"
+"/             wR    "{ Class: SmallInteger }"
+"/             wG    "{ Class: SmallInteger }"
+"/             wB    "{ Class: SmallInteger }" |
+"/
+"/            wantR := ((bytes at:srcIndex) + eR). srcIndex := srcIndex + 1.
+"/            wantG := ((bytes at:srcIndex) + eG). srcIndex := srcIndex + 1.
+"/            wantB := ((bytes at:srcIndex) + eB). srcIndex := srcIndex + 1.
+"/            wR := wantR.
+"/            wR > 255 ifTrue:[wR := 255] ifFalse:[wR < 0 ifTrue:[wR := 0]].
+"/            wG := wantG.
+"/            wG > 255 ifTrue:[wG := 255] ifFalse:[wG < 0 ifTrue:[wG := 0]].
+"/            wB := wantB.
+"/            wB > 255 ifTrue:[wB := 255] ifFalse:[wB < 0 ifTrue:[wB := 0]].
+"/
+"/            iR := wR * (fixR-1) // 128.
+"/            iR := (iR // 2) + (iR bitAnd:1).
+"/            iG := wG * (fixG-1) // 128.
+"/            iG := (iG // 2) + (iG bitAnd:1).
+"/            iB := wB * (fixB-1) // 128.
+"/            iB := (iB // 2) + (iB bitAnd:1).
+"/            idx := (iR * fixR + iG) * fixB + iB + 1.
+"/
+"/            clr := fixColors at:idx.
+"/
+"/            eR := wantR - (clr red * 2) asInteger.
+"/            eG := wantG - (clr green * 2) asInteger.
+"/            eB := wantB - (clr blue * 2) asInteger.
+"/
+"/            pixel := clr colorId.
+"/            pseudoBits at:dstIndex put:pixel.
+"/
+"/            dstIndex := dstIndex + 1
+"/        ].
+    ].
+
+    f := Form width:width height:height depth:aDevice depth on:aDevice.
+    f isNil ifTrue:[^ nil].
+    f colorMap:fixColors.
+    f initGC.
+    aDevice drawBits:pseudoBits bitsPerPixel:8 depth:aDevice depth
+	       width:width height:height
+		   x:0 y:0
+		into:(f id) x:0 y:0 width:width height:height with:(f gcId).
+    ^ f
+!
+
+rgbImageAsGreyFormOn:aDevice
+    "convert an rgb image to a grey image for greyscale displays"
+
+    |deviceDepth|
+
+    deviceDepth := aDevice depth.
+
+    "I have specially tuned methods for monochrome"
+    (deviceDepth == 1) ifTrue:[
+	DitherAlgorithm == #error ifTrue:[
+	    ^ self rgbImageAsErrorDitheredGreyFormOn:aDevice
+	].
+	DitherAlgorithm == #pattern ifTrue:[
+	    ^ self rgbImageAsPatternDitheredGreyFormOn:aDevice
+	].
+	^ self rgbImageAsMonoFormOn:aDevice
+    ].
+
+    "and for 2plane greyscale (i.e. NeXTs)"
+    (deviceDepth == 2) ifTrue:[
+	DitherAlgorithm == #error  ifTrue:[
+	    ^ self rgbImageAsErrorDitheredGreyFormOn:aDevice
+	].
+	DitherAlgorithm == #pattern  ifTrue:[
+	    ^ self rgbImageAsPatternDitheredGreyFormOn:aDevice
+	].
+	^ self rgbImageAs2PlaneFormOn:aDevice
+    ].
+
+    (deviceDepth == 8) ifTrue:[
+	^ self rgbImageAs8BitGreyFormOn:aDevice
+    ].
+
+    "mhmh need another converter ...
+     till then we do:"
+    DitherAlgorithm == #error  ifTrue:[
+	^ self rgbImageAsErrorDitheredGreyFormOn:aDevice
+    ].
+    DitherAlgorithm == #pattern  ifTrue:[
+	^ self rgbImageAsPatternDitheredGreyFormOn:aDevice
+    ].
+    ^ self rgbImageAsMonoFormOn:aDevice
+!
+
+rgbImageAsMonoFormOn:aDevice
+    "return a 1-bit monochrome form for aDevice from the rgb picture,
+     using a threshold algorithm. 
+     (i.e. grey value < 0.5 -> black, grey value >= 0.5 -> white)."
+
+    |monoBits f
+     w        "{ Class: SmallInteger }"
+     h        "{ Class: SmallInteger }"
+     r        "{ Class: SmallInteger }"
+     g        "{ Class: SmallInteger }"
+     b        "{ Class: SmallInteger }"
+     v        "{ Class: SmallInteger }"
+     map rMap gMap bMap
+     srcIndex "{ Class: SmallInteger }"
+     dstIndex "{ Class: SmallInteger }"
+     bits     "{ Class: SmallInteger }"
+     bitCount "{ Class: SmallInteger }"
+     failed |
+
+    w := width.
+    h := height.
+    monoBits := ByteArray uninitializedNew:(((w + 7) // 8) * h).
+    failed := true.
+%{
+    register unsigned char *srcPtr, *dstPtr;
+    register _v, _bits, _bitCount;
+    register j;
+    register i;
+    extern OBJ ByteArray;
+
+    if (__isByteArray(_INST(bytes))
+     && __isByteArray(monoBits)) {
+	failed = false;
+	srcPtr = _ByteArrayInstPtr(_INST(bytes))->ba_element;
+	dstPtr = _ByteArrayInstPtr(monoBits)->ba_element;
+	for (i=_intVal(h); i>0; i--) {
+	    _bitCount = 0;
+	    _bits = 0;
+	    for (j=_intVal(w); j>0; j--) {
+		_bits <<= 1; 
+
+		_v = (*srcPtr++ * 3);   /* 0.3*r + 0.6*g + b */
+		_v += (*srcPtr++ * 6);
+		_v += *srcPtr++;
+		_v /= 10;
+		if (_v & 0x80)
+		    _bits |= 1;
+
+		_bitCount++;
+		if (_bitCount == 8) {
+		    *dstPtr++ = _bits;
+		    _bits = 0;
+		    _bitCount = 0;
+		}
+	    }
+	    if (_bitCount != 0) {
+		while (_bitCount++ != 8) _bits <<= 1;
+		*dstPtr++ = _bits;
+	    }
+	}
+    }
+%}.
+
+    failed ifTrue:[
+"/ the above is equivalent to:
+"/
+"/        srcIndex := 1.
+"/        dstIndex := 1.
+"/        1 to:h do:[:row |
+"/            bitCount := 0.
+"/            bits := 0.
+"/            1 to:w do:[:col |
+"/                bits := bits bitShift:1.
+"/
+"/                r := bytes at:srcIndex.
+"/                srcIndex := srcIndex + 1.
+"/                g := bytes at:srcIndex.
+"/                srcIndex := srcIndex + 1.
+"/                b := bytes at:srcIndex.
+"/                srcIndex := srcIndex + 1.
+"/                v := ((3 * r) + (6 * g) + (1 * b)) // 10.
+"/                ((v bitAnd:16r80) == 0) ifFalse:[
+"/                    bits := bits bitOr:1
+"/                ].
+"/                bitCount := bitCount + 1.
+"/                (bitCount == 8) ifTrue:[
+"/                    monoBits at:dstIndex put:bits.
+"/                    dstIndex := dstIndex + 1.
+"/                    bits := 0.
+"/                    bitCount := 0
+"/                ]
+"/            ].
+"/            (bitCount ~~ 0) ifTrue:[
+"/                [bitCount == 8] whileFalse:[
+"/                    bitCount := bitCount + 1.
+"/                    bits := bits bitShift:1.
+"/                ].
+"/                monoBits at:dstIndex put:bits.
+"/                dstIndex := dstIndex + 1
+"/            ]
+"/        ]
+	self primitiveFailed.
+	^ nil
+    ].
+
+    f := Form width:w height:h depth:1 on:aDevice.
+    f isNil ifTrue:[^ nil].
+    f initGC.
+    (aDevice blackpixel == 0) ifFalse:[
+	"have to invert bits"
+	f function:#copyInverted
+    ].
+    aDevice drawBits:monoBits depth:1 width:w height:h
+		   x:0 y:0
+		into:(f id) x:0 y:0 width:w height:h with:(f gcId).
+    ^ f
+!
+
 rgbImageAsPatternDitheredGreyFormOn:aDevice
     "return a dithered greyForm for aDevice from the palette picture.
      works for any destination depth.
@@ -876,218 +975,6 @@
     ^ f
 !
 
-rgbImageAsDitheredPseudoFormOn:aDevice
-    "return a dithered pseudocolor form from the rgb-picture.
-     This method depends on fixColors being allocated (see Color>>getColors*)"
-
-    ^ self rgbImageAsDitheredPseudoFormOn:aDevice
-				   colors:Color fixColors
-				     nRed:Color numFixRed
-				     nGreen:Color numFixGreen
-				     nBlue:Color numFixBlue
-!
-
-rgbImageAsDitheredPseudoFormOn:aDevice colors:fixColors nRed:nRed nGreen:nGreen nBlue:nBlue
-    "return a dithered pseudocolor form from the rgb-picture"
-
-    |pseudoBits f
-     h        "{ Class: SmallInteger }"
-     w        "{ Class: SmallInteger }"
-"/     eR    "{Class: SmallInteger }"
-"/     eG    "{Class: SmallInteger }"
-"/     eB    "{Class: SmallInteger }"
-"/     wantR "{Class: SmallInteger }"
-"/     wantG "{Class: SmallInteger }"
-"/     wantB "{Class: SmallInteger }"
-     fixR  "{Class: SmallInteger }"
-     fixG  "{Class: SmallInteger }"
-     fixB  "{Class: SmallInteger }"
-     srcIndex "{ Class: SmallInteger }"
-     dstIndex "{ Class: SmallInteger }"
-     deviceDepth has8BitImage 
-     fixIds failed|
-
-    aDevice ~~ Display ifTrue:[^ nil].
-
-    fixR := nRed.
-    fixR == 0 ifTrue:[ ^ nil].
-    fixG := nGreen.
-    fixG == 0 ifTrue:[ ^ nil].
-    fixB := nBlue.
-    fixB == 0 ifTrue:[ ^ nil].
-    "/ simple check
-    (fixR * fixG * fixB) ~~ fixColors size ifTrue:[
-	self error:'invalid color array passed'.
-	^ nil
-    ].
-    fixIds := (fixColors asArray collect:[:clr | clr colorId]) asByteArray.
-
-    deviceDepth := aDevice depth.
-    deviceDepth == 8 ifTrue:[
-	has8BitImage := true.
-    ] ifFalse:[
-	has8BitImage := false.
-	aDevice supportedImageFormats do:[:fmt |
-	    (fmt at:#bitsPerPixel) == 8 ifTrue:[
-		has8BitImage := true.
-	    ]
-	]
-    ].
-    has8BitImage ifFalse:[^ nil].
-
-    'D24IMAGE: dithering ...' infoPrintNL.
-
-    pseudoBits := ByteArray uninitializedNew:(width * height).
-
-    h := height.
-    w := width.
-
-%{
-    int __x, __y;
-    int __eR, __eG, __eB;
-    int __wantR, __wantG, __wantB;
-    unsigned char *srcP, *dstP;
-    unsigned char *redP, *greenP, *blueP;
-    int pix;
-    unsigned char *idP;
-    int __fR, __fG, __fB;
-    int iR, iG, iB;
-    int idx;
-
-    if (__isByteArray(_INST(bytes))
-     && __isByteArray(pseudoBits)
-     && __isByteArray(fixIds)
-     && __bothSmallInteger(fixR, fixG)
-     && __isSmallInteger(fixB)) {
-	failed = false;
-
-	srcP = _ByteArrayInstPtr(_INST(bytes))->ba_element;
-	dstP = _ByteArrayInstPtr(pseudoBits)->ba_element;
-	idP = _ByteArrayInstPtr(fixIds)->ba_element;
-	__fR = _intVal(fixR)-1;
-	__fG = _intVal(fixG)-1;
-	__fB = _intVal(fixB)-1;
-
-	for (__y=_intVal(h); __y>0; __y--) {
-	    __eR = __eG = __eB = 0;
-	    for (__x=_intVal(w); __x>0; __x--) {
-		int t;
-		int __want;
-
-		/*
-		 * wR, wG and wB is the wanted r/g/b value;
-		 * compute the index into the dId table ..
-		 * values: 0..255; scale to 0..fR-1, 0..fG-1, 0..fB-1
-		 *
-		 * bad kludge: knows how to index into FixColor table
-		 */
-		__wantR = srcP[0] + __eR;
-		__wantG = srcP[1] + __eG;
-		__wantB = srcP[2] + __eB;
-		srcP += 3;
-
-		if (__wantR > 255) __want = 255;
-		else if (__wantR < 0) __want = 0;
-		else __want = __wantR;
-
-		iR = __want * __fR / 128;
-		iR = (iR / 2) + (iR & 1);
-		idx = iR * (__fG+1);
-
-		if (__wantG > 255) __want = 255;
-		else if (__wantG < 0) __want = 0;
-		else __want = __wantG;
-
-		iG = __want * __fG / 128;
-		iG = (iG / 2) + (iG & 1);
-		idx = (idx + iG) * (__fB+1);
-
-		if (__wantB > 255) __want = 255;
-		else if (__wantB < 0) __want = 0;
-		else __want = __wantB;
-
-		iB = __want * __fB / 128;
-		iB = (iB / 2) + (iB & 1);
-		idx = idx + iB;
-
-		/*
-		 * store the corresponding dither colorId
-		 */
-		*dstP++ = idP[idx];
-
-		/*
-		 * the new error:
-		 */
-		__eR = __wantR - (iR * 256 / __fR); 
-		__eG = __wantG - (iG * 256 / __fG); 
-		__eB = __wantB - (iB * 256 / __fB); 
-	    }
-	}
-    }
-%}.
-    failed ifTrue:[
-	self primitiveFailed.
-	^ nil
-
-"/ for non-C programmers:
-"/   the above code is (roughly) equivalent to:
-"/    srcIndex := 1.
-"/    dstIndex := 1.
-"/    1 to:h do:[:y |
-"/        eR := eG := eB := 0.
-"/        1 to:w do:[:x |
-"/            |pixel "{ Class: SmallInteger }"
-"/             clr 
-"/             idx   "{ Class: SmallInteger }"
-"/             iR    "{ Class: SmallInteger }"
-"/             iG    "{ Class: SmallInteger }"
-"/             iB    "{ Class: SmallInteger }"
-"/             wR    "{ Class: SmallInteger }"
-"/             wG    "{ Class: SmallInteger }"
-"/             wB    "{ Class: SmallInteger }" |
-"/
-"/            wantR := ((bytes at:srcIndex) + eR). srcIndex := srcIndex + 1.
-"/            wantG := ((bytes at:srcIndex) + eG). srcIndex := srcIndex + 1.
-"/            wantB := ((bytes at:srcIndex) + eB). srcIndex := srcIndex + 1.
-"/            wR := wantR.
-"/            wR > 255 ifTrue:[wR := 255] ifFalse:[wR < 0 ifTrue:[wR := 0]].
-"/            wG := wantG.
-"/            wG > 255 ifTrue:[wG := 255] ifFalse:[wG < 0 ifTrue:[wG := 0]].
-"/            wB := wantB.
-"/            wB > 255 ifTrue:[wB := 255] ifFalse:[wB < 0 ifTrue:[wB := 0]].
-"/
-"/            iR := wR * (fixR-1) // 128.
-"/            iR := (iR // 2) + (iR bitAnd:1).
-"/            iG := wG * (fixG-1) // 128.
-"/            iG := (iG // 2) + (iG bitAnd:1).
-"/            iB := wB * (fixB-1) // 128.
-"/            iB := (iB // 2) + (iB bitAnd:1).
-"/            idx := (iR * fixR + iG) * fixB + iB + 1.
-"/
-"/            clr := fixColors at:idx.
-"/
-"/            eR := wantR - (clr red * 2) asInteger.
-"/            eG := wantG - (clr green * 2) asInteger.
-"/            eB := wantB - (clr blue * 2) asInteger.
-"/
-"/            pixel := clr colorId.
-"/            pseudoBits at:dstIndex put:pixel.
-"/
-"/            dstIndex := dstIndex + 1
-"/        ].
-    ].
-
-    f := Form width:width height:height depth:aDevice depth on:aDevice.
-    f isNil ifTrue:[^ nil].
-    f colorMap:fixColors.
-    f initGC.
-    aDevice drawBits:pseudoBits bitsPerPixel:8 depth:aDevice depth
-	       width:width height:height
-		   x:0 y:0
-		into:(f id) x:0 y:0 width:width height:height with:(f gcId).
-    ^ f
-!
-
 rgbImageAsPseudoFormOn:aDevice
     "return a pseudocolor form from the rgb-picture"
 
@@ -1611,47 +1498,83 @@
     "Modified: 21.10.1995 / 19:30:11 / cg"
 ! !
 
-!Depth24Image methodsFor:'magnification'!
+!Depth24Image methodsFor:'enumerating'!
 
-magnifyRowFrom:srcBytes offset:srcStart
-	  into:dstBytes offset:dstStart factor:mX
-
-    "magnify a single pixel row - can only magnify by integer factors"
+atY:y from:xLow to:xHigh do:aBlock
+    "perform aBlock for each pixel from x1 to x2 in row y.
+     The block is passed the color at each pixel.
+     This method allows slighly faster processing of an
+     image than using atX:y:, since some processing can be
+     avoided when going from pixel to pixel. However, for
+     real image processing, specialized methods should be written."
 
-%{
-    unsigned char *srcP, *dstP;
-    int _mag;
-    REGISTER int i;
-    REGISTER unsigned char byte1, byte2, byte3;
-    int _pixels;
-    OBJ w = _INST(width);
+    |srcIndex "{ Class: SmallInteger }"
+     x1       "{ Class: SmallInteger }"
+     x2       "{ Class: SmallInteger }"
+     rVal     "{ Class: SmallInteger }"
+     gVal     "{ Class: SmallInteger }"
+     bVal     "{ Class: SmallInteger }"
+     lastR lastG lastB lastColor|
+
+    photometric ~~ #rgb ifTrue:[
+	self error:'format not supported'.
+	^ nil
+    ].
+
+    x1 := xLow.
+    x2 := xHigh.
+
+    srcIndex := 1 + (((width * y) + x1) * 3).
 
-    if (__bothSmallInteger(srcStart, dstStart)
-     && __bothSmallInteger(w, mX)
-     && __isByteArray(srcBytes) && __isByteArray(dstBytes)) {
-	_mag = _intVal(mX);
-	srcP = _ByteArrayInstPtr(srcBytes)->ba_element - 1 + _intVal(srcStart);
-	dstP = _ByteArrayInstPtr(dstBytes)->ba_element - 1 + _intVal(dstStart);
-	_pixels = _intVal(w);
+    x1 to:x2 do:[:x |
+	rVal := bytes at:(srcIndex).
+	gVal := bytes at:(srcIndex + 1).
+	bVal := bytes at:(srcIndex + 2).
+	srcIndex := srcIndex + 3.
+	(rVal == lastR and:[gVal == lastG and:[bVal == lastB]]) ifFalse:[
+	    lastColor := Color red:rVal * 100 / 255
+			     green:gVal * 100 / 255
+			      blue:bVal * 100 / 255.
+	    lastR := rVal.
+	    lastG := gVal.
+	    lastB := bVal.
+	].
+	aBlock value:x value:lastColor
+    ]
+!
 
-	while (_pixels--) {
-	    byte1 = *srcP;
-	    byte2 = *(srcP+1);
-	    byte3 = *(srcP+2);
-	    srcP += 3;
-	    for (i=_mag; i>0; i--) {
-		*dstP = byte1;
-		*(dstP+1) = byte2;
-		*(dstP+2) = byte3;
-		dstP += 3;
-	    }
-	}
-	RETURN (self);
-    }
-%}
-.
-    self primitiveFailed
-!
+valueAtY:y from:xLow to:xHigh do:aBlock
+    "perform aBlock for each pixelValue from x1 to x2 in row y.
+     The block is passed the pixelValue at each pixel.
+     This method allows slighly faster processing of an
+     image than using valueAtX:y:, since some processing can be
+     avoided when going from pixel to pixel. However, for
+     real image processing, specialized methods should be written.
+     Notice that the pixelValue is the r/g/b value packed into an integer
+     (r bitShift:16) bitOr:(g bitSHift:8) bitOr:b"
+
+    |srcIndex "{ Class: SmallInteger }"
+     x1       "{ Class: SmallInteger }"
+     x2       "{ Class: SmallInteger }"
+     r        "{ Class: SmallInteger }"
+     g        "{ Class: SmallInteger }"
+     b        "{ Class: SmallInteger }"|
+
+    x1 := xLow.
+    x2 := xHigh.
+
+    srcIndex := 1 + (((width * y) + x1) * 3).
+
+    x1 to:x2 do:[:x |
+	r := bytes at:(srcIndex).
+	g := bytes at:(srcIndex + 1).
+	b := bytes at:(srcIndex + 2).
+	srcIndex := srcIndex + 3.
+	aBlock value:x value:(((r bitShift:16) bitOr:(g bitShift:8)) bitOr:b)
+    ]
+! !
+
+!Depth24Image methodsFor:'magnification'!
 
 hardMagnifiedBy:extent
     "return a new image magnified by extent, aPoint.
@@ -1732,4 +1655,83 @@
     ].
 "
     ^ newImage
+!
+
+magnifyRowFrom:srcBytes offset:srcStart
+	  into:dstBytes offset:dstStart factor:mX
+
+    "magnify a single pixel row - can only magnify by integer factors"
+
+%{
+    unsigned char *srcP, *dstP;
+    int _mag;
+    REGISTER int i;
+    REGISTER unsigned char byte1, byte2, byte3;
+    int _pixels;
+    OBJ w = _INST(width);
+
+    if (__bothSmallInteger(srcStart, dstStart)
+     && __bothSmallInteger(w, mX)
+     && __isByteArray(srcBytes) && __isByteArray(dstBytes)) {
+	_mag = _intVal(mX);
+	srcP = _ByteArrayInstPtr(srcBytes)->ba_element - 1 + _intVal(srcStart);
+	dstP = _ByteArrayInstPtr(dstBytes)->ba_element - 1 + _intVal(dstStart);
+	_pixels = _intVal(w);
+
+	while (_pixels--) {
+	    byte1 = *srcP;
+	    byte2 = *(srcP+1);
+	    byte3 = *(srcP+2);
+	    srcP += 3;
+	    for (i=_mag; i>0; i--) {
+		*dstP = byte1;
+		*(dstP+1) = byte2;
+		*(dstP+2) = byte3;
+		dstP += 3;
+	    }
+	}
+	RETURN (self);
+    }
+%}
+.
+    self primitiveFailed
 ! !
+
+!Depth24Image methodsFor:'queries'!
+
+bitsPerPixel
+    "return the number of bits per pixel"
+
+    ^ 24
+!
+
+bitsPerRow
+    "return the number of bits in one scanline of the image"
+
+    ^  width * 24
+!
+
+bitsPerSample
+    "return the number of bits per sample.
+     The return value is an array of bits-per-plane."
+
+    ^ #(8 8 8)
+!
+
+bytesPerRow
+    "return the number of bytes in one scanline of the image"
+
+    ^ width * 3
+!
+
+samplesPerPixel
+    "return the number of samples per pixel in the image."
+
+    ^ 3
+! !
+
+!Depth24Image class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview/Depth24Image.st,v 1.19 1995-12-07 11:23:25 cg Exp $'
+! !