Depth2Image.st
author Claus Gittinger <cg@exept.de>
Thu, 07 Dec 1995 12:17:07 +0100
changeset 280 c89f1cb9e8b9
parent 219 9ff0660f447f
child 579 e381761190c4
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

Image subclass:#Depth2Image
	 instanceVariableNames:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Graphics-Images'
!

!Depth2Image class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this class represents four-color (2 bit / pixel) images 
    (as used mainly on the NeXT).
    It mainly consists of methods already implemented in Image,
    reimplemented here for more performance.
"
! !

!Depth2Image class methodsFor:'queries'!

imageDepth
    ^ 2
! !

!Depth2Image methodsFor:'accessing'!

atX: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"

    |lineIndex "{ Class: SmallInteger }"
     byte      "{ Class: SmallInteger }"
     shift     "{ Class: SmallInteger }"
     value     "{ Class: SmallInteger }" 
     p grey|

    lineIndex := (self bytesPerRow * y) + 1.

    "left pixel in high bits"
    byte := bytes at:(lineIndex + (x // 4)).

    shift := #(-6 -4 -2 0) at:((x \\ 4) + 1).
    value := (byte bitShift:shift) bitAnd:3.
    p := photometric.
    p == #whiteIs0 ifTrue:[
	value := 3 - value.
	p := #blackIs0
    ].
    p == #blackIs0 ifTrue:[
	(value == 0) ifTrue:[
	    ^ Color black
	].
	(value == 3) ifTrue:[
	    ^ Color white
	].
	(value == 1) ifTrue:[
	    grey := 33
	] ifFalse:[
	    grey := 67
	].
	^ Color grey:grey
    ].
    photometric ~~ #palette ifTrue:[
	self error:'format not supported'.
	^ nil
    ].
    ^ colorMap at:(value+1).
!

atX:x y:y putValue:aPixelValue
    "set the pixel at x/y to aPixelValue.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel"

    |lineIndex "{ Class: SmallInteger }"
     index     "{ Class: SmallInteger }"
     byte      "{ Class: SmallInteger }"
     shift     "{ Class: SmallInteger }" |

    lineIndex := (self bytesPerRow * y) + 1.

    "left pixel is in high bits"
    index := lineIndex + (x // 4).
    byte := bytes at:index.
    shift := #(6 4 2 0) at:((x \\ 4) + 1).
    byte := (byte bitAnd:(3 bitShift:shift) bitInvert) bitOr:(aPixelValue bitShift:shift).
    bytes at:index put:byte
!

valueAtX:x y:y
    "retrieve a pixel at x/y; return a pixel value.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel"

    |lineIndex "{ Class: SmallInteger }"
     byte      "{ Class: SmallInteger }"
     shift     "{ Class: SmallInteger }" |

    lineIndex := (self bytesPerRow * y) + 1.

    "left pixel in high bits"
    byte := bytes at:(lineIndex + (x // 4)).
    shift := #(-6 -4 -2 0) at:((x \\ 4) + 1).
    ^ (byte bitShift:shift) bitAnd:3.
! !

!Depth2Image methodsFor:'converting greyscale images'!

greyImageAsMonoFormOn:aDevice
    "return a (thresholded) monochrome Form from the picture."

    |bytesPerRow
     bytesPerMonoRow monoData
     left4pixel  "{Class: SmallInteger }"
     right4pixel "{Class: SmallInteger }"
     byte        "{Class: SmallInteger }"
     srcIndex    "{Class: SmallInteger }"
     dstIndex    "{Class: SmallInteger }"
     nextSrc     "{Class: SmallInteger }"
     nextDst     "{Class: SmallInteger }"
     bitNumber   "{Class: SmallInteger }"
     w           "{Class: SmallInteger }"
     h           "{Class: SmallInteger }" |

    w := width.
    h := height.

    bytesPerRow := self bytesPerRow.
    bytesPerMonoRow := w // 8.
    ((w \\ 8) ~~ 0) ifTrue:[
	bytesPerMonoRow := bytesPerMonoRow + 1
    ].
    monoData := ByteArray uninitializedNew:(bytesPerMonoRow * h).

    "2 bit -> 1 bit extract; take most significant bit"

    srcIndex := 1.
    dstIndex := 1.
    1 to:h do:[:count |
	nextSrc := srcIndex + bytesPerRow.
	nextDst := dstIndex + bytesPerMonoRow.
	bitNumber := 1.
	[bitNumber <= w] whileTrue:[
	    left4pixel := bytes at:srcIndex.
	    srcIndex := srcIndex + 1.
	    byte := 0.
	    ((left4pixel bitAnd:16r80) ~~ 0) ifTrue:[
		byte := byte bitOr:2r10000000
	    ].
	    ((left4pixel bitAnd:16r20) ~~ 0) ifTrue:[
		byte := byte bitOr:2r01000000
	    ].
	    ((left4pixel bitAnd:16r08) ~~ 0) ifTrue:[
		byte := byte bitOr:2r00100000
	    ].
	    ((left4pixel bitAnd:16r02) ~~ 0) ifTrue:[
		byte := byte bitOr:2r00010000
	    ].
	    bitNumber := bitNumber + 4.
	    (bitNumber <= w) ifTrue:[
		right4pixel := bytes at:srcIndex.
		srcIndex := srcIndex + 1.
		((right4pixel bitAnd:16r80) ~~ 0) ifTrue:[
		    byte := byte bitOr:2r00001000
		].
		((right4pixel bitAnd:16r20) ~~ 0) ifTrue:[
		    byte := byte bitOr:2r00000100
		].
		((right4pixel bitAnd:16r08) ~~ 0) ifTrue:[
		    byte := byte bitOr:2r00000010
		].
		((right4pixel bitAnd:16r02) ~~ 0) ifTrue:[
		    byte := byte bitOr:2r00000001
		].
		bitNumber := bitNumber + 4
	    ].
	    monoData at:dstIndex put:byte.
	    dstIndex := dstIndex + 1
	].
	srcIndex := nextSrc.
	dstIndex := nextDst
    ].
    ^ Form width:w height:h fromArray:monoData on:aDevice
! !

!Depth2Image methodsFor:'enumerating'!

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 }"
     byte     "{ Class: SmallInteger }"
     shift    "{ Class: SmallInteger }"
     value    "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     color0 color1 color2 color3 color|

    photometric == #whiteIs0 ifTrue:[
	color0 := Color white.
	color1 := Color grey:67.
	color2 := Color grey:33.
	color3 := Color black
    ] ifFalse:[
	photometric == #blackIs0 ifTrue:[
	    color0 := Color black.
	    color1 := Color grey:33.
	    color2 := Color grey:67.
	    color3 := Color white
	] ifFalse:[
	    photometric == #palette ifTrue:[
		color0 := colorMap at:1.
		color1 := colorMap at:2.
		color2 := colorMap at:3.
		color3 := colorMap at:4.
	    ] ifFalse:[
		self error:'format not supported'.
		^ nil
	    ]
	]
    ].

    "left pixel in high bits"

    x1 := xLow.
    x2 := xHigh.

    srcIndex := (self bytesPerRow * y) + 1.
    srcIndex := srcIndex + (x1 // 4).
    shift := #(-6 -4 -2 0) at:((x1 \\ 4) + 1).

    x1 to:x2 do:[:x |
	byte := bytes at:srcIndex.
	value := (byte bitShift:shift) bitAnd:3.

	(value == 0) ifTrue:[
	    color := color0
	] ifFalse:[
	    (value == 1) ifTrue:[
		color := color1
	    ] ifFalse:[
		(value == 2) ifTrue:[
		    color := color2
		] ifFalse:[
		    color := color3
		]
	    ]
	].
	aBlock value:x value:color.

	shift == 0 ifTrue:[
	    shift := -6.
	    srcIndex := srcIndex + 1
	] ifFalse:[
	    shift := shift + 2.
	]
    ].
!

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 x coordinate and 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."

    |srcIndex "{ Class: SmallInteger }"
     byte     "{ Class: SmallInteger }"
     shift    "{ Class: SmallInteger }"
     value    "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"|

    "left pixel in high bits"

    x1 := xLow.
    x2 := xHigh.

    srcIndex := (self bytesPerRow * y) + 1.
    srcIndex := srcIndex + (x1 // 4).
    shift := #(-6 -4 -2 0) at:((x1 \\ 4) + 1).

    x1 to:x2 do:[:x |
	byte := bytes at:srcIndex.
	value := (byte bitShift:shift) bitAnd:3.

	aBlock value:x value:value.

	shift == 0 ifTrue:[
	    shift := -6.
	    srcIndex := srcIndex + 1
	] ifFalse:[
	    shift := shift + 2.
	]
    ].
! !

!Depth2Image methodsFor:'magnification'!

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 _byte;
    int _pixels;
    REGISTER int outcnt, bits, bit, mask, incnt;
    int shift;
    OBJ w = _INST(width);

    /* helper for two-plane magnification by 2 */
    static unsigned char mag2[16] = {0x00, 0x05, 0x0a, 0x0f, 0x50, 0x55, 0x5a, 0x5f, 
				     0xa0, 0xa5, 0xaa, 0xaf, 0xf0, 0xf5, 0xfa, 0xff};

    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);

	 switch (_mag) {
	     case 1:
		break;

	     case 2:
		 /* tuned for this common case */
		 while (_pixels > 0) {
		     _byte = *srcP++;
		     *dstP++ = mag2[ _byte >> 4 ];
		     if (_pixels > 2) {
			 *dstP++ = mag2[ _byte & 0x0F ];
		     }
		     _pixels -= 4;
		 }
		 break;

	     default:
		 bits = 0, incnt = 0, outcnt = 0;
		 shift = 6;
		 _byte = *srcP++;
		 while (_pixels--) {
		     bit = (_byte >> shift) & 3;
		     incnt++;
		     if (incnt == 4) {
			 incnt = 0;
			 shift = 6;
			 _byte = *srcP++;
		     } else {
			 shift -= 2;
		     }

		     for (i=_mag; i>0; i--) {
			 bits = (bits << 2) | bit;
			 outcnt++;
			 if (outcnt == 4) {
			     *dstP++ = bits;
			     bits = 0;
			     outcnt = 0;
			 }
		     }
		 }
		 break;

	}
	RETURN (self);
    }
%}
.
    self primitiveFailed
! !

!Depth2Image methodsFor:'queries'!

bitsPerPixel
    "return the number of bits per pixel"

    ^ 2
!

bitsPerRow
    "return the number of bits in one scanline of the image"

    ^  width * 2
!

bitsPerSample
    "return the number of bits per sample.
     The return value is an array of bits-per-plane."

    ^ #(2)
!

bytesPerRow
    "return the number of bytes in one scanline of the image"

    |nbytes|

    nbytes := width // 4.
    ((width \\ 4) ~~ 0) ifTrue:[
	^ nbytes + 1
    ].
    ^ nbytes
!

samplesPerPixel
    "return the number of samples per pixel in the image."

    ^ 1
!

usedColors
    "return a collection of colors used in the receiver.
     For depth1 images, this is very easy"

    photometric ~~ #palette ifTrue:[
	^ Array with:Color black
		with:(Color grey:33)
		with:(Color grey:67)
		with:Color black.
    ].
    ^ colorMap
!

usedValues
    "return a collection of color values used in the receiver."

    "actually, this is wrong - we have to look if those are
     really used. However, assume that we dont care for 
     those extra colors here ..."

    ^ #(0 1 2 3)
! !

!Depth2Image class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Depth2Image.st,v 1.15 1995-12-07 11:16:18 cg Exp $'
! !