Depth4Image.st
author claus
Sat, 18 Mar 1995 06:13:39 +0100
changeset 118 25e775072a89
parent 97 dd6116883ac0
child 194 7ba58753a6b7
permissions -rw-r--r--
*** empty log message ***

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

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

$Header: /cvs/stx/stx/libview/Depth4Image.st,v 1.11 1995-03-18 05:10:32 claus Exp $
'!

!Depth4Image 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/Depth4Image.st,v 1.11 1995-03-18 05:10:32 claus Exp $
"
!

documentation
"
    this class represents 16-color (4 bit / pixel) images.
    Most images coming from the windows world are represented as Depth4Images.
    It mainly consists of methods already implemented in Image,
    reimplemented here for more performance.
"
! !

!Depth4Image class methodsFor:'queries'!

imageDepth
    ^ 4
! !

!Depth4Image methodsFor:'queries'!

bitsPerPixel
    "return the number of bits per pixel"

    ^ 4
!

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

    ^  width * 4
!

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

    ^ #(4)
!

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

    |nbytes|

    nbytes := width // 2.
    width odd ifTrue:[
	^ nbytes + 1
    ].
    ^ nbytes
!

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

    ^ 1
!

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

    |useFlags usedValues|

    useFlags := Array new:16 withAll:false.
    width even ifFalse:[
	0 to:self height - 1 do:[:y |
	    self valueAtY:y from:0 to:self width - 1 do:[:x :pixel |
		useFlags at:(pixel + 1) put:true
	    ]
	].
    ] ifTrue:[
	bytes usedValues do:[:byte |
	    useFlags at:(byte bitShift:-4)+1 put:true.
	    useFlags at:(byte bitAnd:2r1111)+1 put:true.
	].
    ].
    usedValues := OrderedCollection new.
    1 to:16 do:[:i | (useFlags at:i) ifTrue:[usedValues add:(i-1)]].
    ^ usedValues
! !

!Depth4Image methodsFor:'accessing'!

valueAtX:x y:y
    "retrieve a pixel at x/y; return a pixelValue.
     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 }" |

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

    "left pixel in high bits"
    byte := bytes at:(lineIndex + (x // 2)).
    x even ifTrue:[
	^ (byte bitShift:-4) bitAnd:16rF.
    ].
    ^ byte bitAnd:16rF.
!

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 }"
     value     "{ Class: SmallInteger }" |

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

    "left pixel in high bits"
    byte := bytes at:(lineIndex + (x // 2)).
    x even ifTrue:[
	value := (byte bitShift:-4) bitAnd:16rF.
    ] ifFalse:[
	value := byte bitAnd:16rF.
    ].
    photometric == #whiteIs0 ifTrue:[
	^ Color grey:100 - (100 / 15 * value)
    ].
    photometric == #blackIs0 ifTrue:[
	^ Color grey:(100 / 15 * value)
    ].
    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 }" |

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

    "left pixel is in high bits"
    index := lineIndex + (x // 2).
    byte := bytes at:index.
    x even ifTrue:[
	byte := (byte bitAnd:16rF) bitOr:(aPixelValue bitShift:4)
    ] ifFalse:[
	byte := (byte bitAnd:16rF0) bitOr:aPixelValue
    ].
    bytes at:index put:byte
! !

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

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

    x1 := xLow.
    x2 := xHigh.
    srcIndex := (self bytesPerRow * y) + 1.
    srcIndex := srcIndex + (x1 // 2).
    x1 even ifTrue:[
	shift := -4
    ] ifFalse:[
	shift := 0
    ].

    x1 to:x2 do:[:x |
	shift == 0 ifTrue:[
	    byte := bytes at:srcIndex.
	    pixelValue := byte bitAnd:16rF.
	    shift := -4.
	    srcIndex := srcIndex + 1.
	] ifFalse:[
	    byte := bytes at:srcIndex.
	    pixelValue := (byte bitShift:-4) bitAnd:16rF.
	    shift := 0
	].
	aBlock value:x value:pixelValue.
    ]
!

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 }"
     colors p |

    (p := photometric) == #whiteIs0 ifTrue:[
	colors := Array new:16.
	0 to:15 do:[:i |
	    colors at:(i+1) put:(Color grey:100 - (100 / 15 * i))
	]
    ] ifFalse:[
	p == #blackIs0 ifTrue:[
	    colors := Array new:16.
	    0 to:15 do:[:i |
		colors at:(i+1) put:(Color grey:(100 / 15 * i))
	    ]
	] ifFalse:[
	    p == #palette ifTrue:[
		colors := colorMap.
	    ] ifFalse:[
		self error:'format not supported'.
		^ nil
	    ]
	]
    ].

    x1 := xLow.
    x2 := xHigh.
    srcIndex := (self bytesPerRow * y) + 1.
    srcIndex := srcIndex + (x1 // 2).
    x1 even ifTrue:[
	shift := -4
    ] ifFalse:[
	shift := 0
    ].

    x1 to:x2 do:[:x |
	shift == 0 ifTrue:[
	    byte := bytes at:srcIndex.
	    value := byte bitAnd:16rF.
	    shift := -4.
	    srcIndex := srcIndex + 1.
	] ifFalse:[
	    byte := bytes at:srcIndex.
	    value := (byte bitShift:-4) bitAnd:16rF.
	    shift := 0
	].
	aBlock value:x value:(colors at:(value + 1)).
    ]
! !

!Depth4Image methodsFor:'magnification'!

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

    "magnify a single pixel row - can only magnify by integer factors.
     Specially tuned for factor 2."

%{
    unsigned char *srcP, *dstP;
    int _mag;
    REGISTER int i;
    REGISTER unsigned char _byte;
    int _pixels;
    REGISTER int outcnt, bits, bit;
    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);

	switch (_mag) {
	    case 1:
		break;

	    case 2:
		_byte = *srcP++;
		while (_pixels) {
		    bit = (_byte >> 4) & 0xF;
		    bits = (bit << 4) | bit;
		    *dstP++ = bits;

		    if (--_pixels) {
			bit = _byte & 0xF;
			bits = (bit << 4) | bit;
			*dstP++ = bits;
			_byte = *srcP++;
			_pixels--;
		    }
		}
		break;

	    default:
		bits = 0, outcnt = 0;
		_byte = *srcP++;
		while (_pixels) {
		    bit = (_byte >> 4) & 0xF;

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

		    if (--_pixels) {
			bit = _byte & 0xF;
			for (i=_mag; i>0; i--) {
			    bits = (bits << 4) | bit;
			    outcnt++;
			    if (outcnt == 2) {
				*dstP++ = bits;
				bits = 0;
				outcnt = 0;
			    }
			}
			_byte = *srcP++;
			_pixels--;
		    }
		}

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