Depth1Image.st
author Claus Gittinger <cg@exept.de>
Mon, 23 Oct 1995 18:00:19 +0100
changeset 193 3abcc2ee1641
parent 118 25e775072a89
child 219 9ff0660f447f
permissions -rw-r--r--
.

"
 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:#Depth1Image
	 instanceVariableNames:''
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Graphics-Images'
!

Depth1Image comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/Depth1Image.st,v 1.13 1995-10-23 16:58:41 cg Exp $
'!

!Depth1Image 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.
"
!

version
"
$Header: /cvs/stx/stx/libview/Depth1Image.st,v 1.13 1995-10-23 16:58:41 cg Exp $
"
!

documentation
"
    this class represents bilevel (1 bit / pixel) images.
    It mainly consists of methods which are already implemented in Image,
    but reimplemented here for more performance. If you plan to do heavy
    image processing on bilevel images, you may want to add more
    specialized methods here.
"
! !

!Depth1Image class methodsFor:'queries'!

imageDepth
    ^ 1
! !

!Depth1Image methodsFor:'queries'!

bitsPerPixel
    "return the number of bits per pixel"

    ^ 1
!

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

    ^  width
!

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

    ^ #(1)
!

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

    |nbytes|

    nbytes := width // 8.
    ((width \\ 8) ~~ 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 white with:Color black.
    ].
    ^ colorMap

    "
     (Image fromFile:'bitmaps/garfield.gif') usedColors
     (Image fromFile:'bitmaps/SBrowser.xbm') usedColors
    "
!

usedValues
    "return a collection of color values used in the receiver.
     For depth1 images, this is very easy"

    ^ #(0 1)
! !

!Depth1Image methodsFor:'accessing'!

valueAtX:x y:y
    "retrieve a pixelValue at x/y; return a number.
     The interpretation of the returned value depends on the photometric
     and the colormap. See also Image>>atX:y:)
     Pixels start at 0@0 for upper left pixel, end at
     (width-1)@(height-1) for lower right pixel"

    |bytesPerRow "{Class: SmallInteger}"
     index       "{Class: SmallInteger}"
     byte        "{Class: SmallInteger}"
     mask        "{Class: SmallInteger}"|

%{  /* NOCONTEXT */

    OBJ b = _INST(bytes);
    OBJ w = _INST(width);

    if (__isByteArray(b) && __bothSmallInteger(x, y) && __isSmallInteger(w) ) {
	int _w = _intVal(w);
	int _y = _intVal(y);
	int _x = _intVal(x);
	unsigned _byte;

	_byte = _ByteArrayInstPtr(b)->ba_element[(_w + 7) / 8 * _y + (_x / 8)];
	RETURN( (_byte & (0x80 >> (_x % 8))) ? _MKSMALLINT(1) : _MKSMALLINT(0) );
    }
%}.

"/ the above is equivalent to:
"/   (notice that the code below is evaluated if the bytes-collection is
"/   not a byteArray, or the arguments are not integers)

"/    bytesPerRow := width // 8.
"/    ((width \\ 8) ~~ 0) ifTrue:[
"/        bytesPerRow := bytesPerRow + 1
"/    ].
"/    index := (bytesPerRow * y) + 1 + (x // 8).
"/
"/    "left pixel is in high bit"
"/    byte := bytes at:index.
"/    mask := #(16r80 16r40 16r20 16r10 16r08 16r04 16r02 16r01) at:((x \\ 8) + 1).
"/    (byte bitAnd:mask) == 0 ifTrue:[^ 0].
"/    ^ 1

"/ since that cannot happen, we faile here
    self primitiveFailed.
    ^ 0
!

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|

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

    "left pixel is in high bit"
    byte := bytes at:(lineIndex + (x // 8)).
    shift := #(-7 -6 -5 -4 -3 -2 -1 0) at:((x \\ 8) + 1).
    value := (byte bitShift:shift) bitAnd:1.
    (p := photometric) == #whiteIs0 ifTrue:[
	value := 1-value.
	p := #blackIs0
    ].
    p == #blackIs0 ifTrue:[
	(value == 0) ifTrue:[
	    ^ Color black
	].
	^ Color white
    ].
    p ~~ #palette ifTrue:[
	self error:'format not supported'.
	^ nil
    ].
    value := value + 1.
    ^ colorMap at:value
!

atX:x y:y putValue:aPixelValue
    "set a pixels value 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"

    |bytesPerRow "{Class: SmallInteger}"
     index       "{Class: SmallInteger}"
     byte        "{Class: SmallInteger}"
     mask        "{Class: SmallInteger}"|

%{  /* NOCONTEXT */

    OBJ b = _INST(bytes);
    OBJ w = _INST(width);

    if (__isByteArray(b) && __bothSmallInteger(x, y) && __isSmallInteger(w) ) {
	int _w = _intVal(w);
	int _y = _intVal(y);
	int _x = _intVal(x);
	int _idx;

	_idx = (_w + 7) / 8 * _y + (_x / 8);
	if (aPixelValue == _MKSMALLINT(0)) {
	    _ByteArrayInstPtr(b)->ba_element[_idx] &= ~(0x80 >> (_x % 8));
	} else {
	    _ByteArrayInstPtr(b)->ba_element[_idx] |= (0x80 >> (_x % 8));
	}
	RETURN( self );
    }
%}.
    "fall back code for nonByteArray or nonInteger arguments"

    bytesPerRow := width // 8.
    ((width \\ 8) ~~ 0) ifTrue:[
	bytesPerRow := bytesPerRow + 1
    ].
    index := (bytesPerRow * y) + 1 + (x // 8).

    "left pixel is in high bit"
    byte := bytes at:index.
    mask := #(16r80 16r40 16r20 16r10 16r08 16r04 16r02 16r01) at:((x \\ 8) + 1).
    aPixelValue == 0 ifTrue:[
	byte := byte bitAnd:(mask bitInvert)
    ] ifFalse:[
	byte := byte bitOr:mask
    ].
    bytes at:index put:byte
!

atX:x y:y put:aColor
    "set the pixel at x/y to aColor.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel.
     This method checks, if it is possible to store the color
     in the image; i.e. for b/w images, the color MUST be black
     or white; for palette images it must be present in the palette."

    |clr0 clr1|

    photometric == #whiteIs0 ifTrue:[
	clr0 := Color white.
	clr1 := Color black.
    ] ifFalse:[
	photometric == #blackIs0 ifTrue:[
	    clr0 := Color black.
	    clr1 := Color white.
	] ifFalse:[
	    photometric ~~ #palette ifTrue:[
		self error:'format not supported'.
		^ nil
	    ].
	    clr0 := colorMap at:1.
	    clr1 := colorMap at:2.
	]
    ].
    aColor = clr0 ifTrue:[
	self atX:x y:y putValue:0.
	^ self
    ].
    aColor = clr1 ifTrue:[
	self atX:x y:y putValue:1.
	^ self
    ].
    "
     the color to be stored is not in the images colormap
    "
    self error:'invalid color'
! !

!Depth1Image 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 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 }"
     mask     "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     pixelValue|

    "this method needs more tuning, if used heavily 
     (fetch 8 bits at once, unroll the loop over these 8 pixels)"

    x1 := xLow.
    x2 := xHigh.
    srcIndex := (self bytesPerRow * y) + 1.

    "left pixel is in high bit"

    srcIndex := srcIndex + (x1 // 8).
    mask := #[2r10000000 
	      2r01000000
	      2r00100000
	      2r00010000
	      2r00001000
	      2r00000100
	      2r00000010
	      2r00000001] at:((x1 \\ 8) + 1).

    x1 to:x2 do:[:x |
	byte := bytes at:srcIndex.
	(byte bitAnd:mask) == 0 ifTrue:[
	    pixelValue := 0
	] ifFalse:[
	    pixelValue := 1
	].
	aBlock value:x value:pixelValue.

	mask := mask bitShift:-1.
	mask == 0 ifTrue:[
	    mask := 2r10000000.
	    srcIndex := srcIndex + 1
	]
    ]
!

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 }"
     mask     "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     color0 color1 color|

    x1 := xLow.
    x2 := xHigh.
    srcIndex := (self bytesPerRow * y) + 1.

    "left pixel is in high bit"

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

    srcIndex := srcIndex + (x1 // 8).
    mask := #[2r10000000 
	      2r01000000
	      2r00100000
	      2r00010000
	      2r00001000
	      2r00000100
	      2r00000010
	      2r00000001] at:((x1 \\ 8) + 1).

    x1 to:x2 do:[:x |
	byte := bytes at:srcIndex.
	(byte bitAnd:mask) == 0 ifTrue:[
	    color := color0
	] ifFalse:[
	    color := color1
	].
	aBlock value:x value:color.

	mask := mask bitShift:-1.
	mask == 0 ifTrue:[
	    mask := 2r10000000.
	    srcIndex := srcIndex + 1
	]
    ]
! !

!Depth1Image methodsFor:'converting greyscale images'!

greyImageAsFormOn:aDevice
    "convert a greyscale image to a device form"

    |f|

    f := Form width:width height:height fromArray:bytes on:aDevice.
    photometric == #blackIs0 ifTrue:[
	f function:#xor.
	f paint:(Color colorId:1).
	f fillRectangleX:0 y:0 width:width height:height
    ].
    ^ f
!

greyImageAsMonoFormOn:aDevice
    "convert to a monochrome form - thats easy"

    ^ self greyImageAsFormOn:aDevice
! !

!Depth1Image methodsFor:'converting palette images'!

paletteImageAsPseudoFormOn:aDevice
    "return a pseudo-deviceForm from the palette image."

    |f|

    "
     this is easy, since Form already supports colorMaps
    "
    f := Form width:width height:height fromArray:bytes.
    f colorMap:colorMap.
    ^ f
!

paletteImageAsTrueColorFormOn:aDevice
    "since all devices must support monochrome images, and
     a 2-entry colormap is implemented by ST/X's drawForm methods,
     we can do this on all color devices as a palette image."

    ^ self paletteImageAsPseudoFormOn:aDevice
! !

!Depth1Image methodsFor:'magnification'!

magnifyRowFrom:srcBytes offset:srcStart  
	  into:dstBytes offset:dstStart factor:mX

    "magnify a single pixel row - can only magnify by integer factors.
     This method has been specially tuned for magnification by 2 and 4."

%{
    unsigned char *srcP, *dstP;
    int _mag;
    REGISTER int i;
    REGISTER unsigned char _byte;
    int _pixels, bpr;
    REGISTER int outcnt, bits, bit, mask, incnt;
    int shift;
    unsigned char byte1, byte2, byte3, byte4;
    OBJ w = _INST(width);

    /* helper for monochrome magnification by 2 */
    static unsigned char mag1[16] = {0x00, 0x03, 0x0c, 0x0f, 0x30, 0x33, 0x3c, 0x3f, 
				     0xc0, 0xc3, 0xcc, 0xcf, 0xf0, 0xf3, 0xfc, 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++ = mag1[ _byte >> 4 ];
		    if (_pixels > 4) {
			*dstP++ = mag1[ _byte & 0x0F ];
		    }
		    _pixels -= 8;
		}
		break;

	    case 4:
		/* tuned for this common case */
		while (_pixels > 0) {
		    _byte = *srcP++;
		    byte1 = mag1[_byte >> 4];
		    byte2 = mag1[byte1 & 0xF];
		    byte1 = mag1[byte1 >> 4];
		    byte3 = mag1[ _byte & 0x0F ];
		    byte4 = mag1[byte3 & 0xF];
		    byte3 = mag1[byte3 >> 4];

		    *dstP++ = byte1;
		    if (_pixels > 2) {
			*dstP++ = byte2;
			if (_pixels > 4) {
			    *dstP++ = byte3;
			    if (_pixels > 6) {
				*dstP++ = byte4;
			    }
			}
		    }
		    _pixels -= 8;
		}
		break;

	    default:
		bits = 0, incnt = 0, outcnt = 0;
		mask = 0x80;
		_byte = *srcP++;
		while (_pixels--) {
		    if (_byte & mask)
			bit = 1;
		    else
			bit = 0;
		    incnt++;
		    if (incnt == 8) {
			incnt = 0;
			mask = 0x80;
			_byte = *srcP++;
		    } else {
			mask >>= 1;
		    }

		    for (i=_mag; i>0; i--) {
			bits = (bits << 1) | bit;
			outcnt++;
			if (outcnt == 8) {
			    *dstP++ = bits;
			    bits = 0;
			    outcnt = 0;
			}
		    }
		}
		break;
	}
	RETURN (self);
    }
%}.
    self primitiveFailed
! !