Depth1Image.st
author claus
Wed, 13 Oct 1993 01:30:35 +0100
changeset 1 304f026e10cd
child 3 c0aaded4ef28
permissions -rw-r--r--
Initial revision

'From Smalltalk/X, Version:2.7.1 on 9-Aug-1993 at 20:32:31'!

Image subclass:#Depth1Image
         instanceVariableNames:''
         classVariableNames:''
         poolDictionaries:''
         category:'Graphics-Display Objects'
!

!Depth1Image methodsFor:'accessing'!

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
!

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"

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

%{  /* NOCONTEXT */
    if (_isByteArray(_INST(bytes))
     && _isSmallInteger(x)
     && _isSmallInteger(y)
     && _isSmallInteger(_INST(width)) ) {
	int _w = _intVal(_INST(width));
	int _y = _intVal(y);
	int _x = _intVal(x);
	unsigned _byte;
	_byte = _ByteArrayInstPtr(_INST(bytes))->ba_element[(_w + 7) / 8 * _y + (_x / 8)];
	RETURN( (_byte & (0x80 >> (_x % 8))) ? _MKSMALLINT(1) : _MKSMALLINT(0) );
    }
%}
.
    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
!

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 byte shift value|

    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.
    photometric == #whiteIs0 ifTrue:[
        (value == 0) ifTrue:[
            ^ Color white
        ].
        ^ Color black
    ].
    photometric == #blackIs0 ifTrue:[
        (value == 0) ifTrue:[
            ^ Color black
        ].
        ^ Color white
    ].
    photometric ~~ #palette ifTrue:[
        self error:'format not supported'.
        ^ nil
    ].
    ^ Color red:(((colorMap at:1) at:(value + 1)) * 100 / 255)
          green:(((colorMap at:2) at:(value + 1)) * 100 / 255)
           blue:(((colorMap at:3) at:(value + 1)) * 100 / 255)
!

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"

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

%{  /* NOCONTEXT */
    if (_isByteArray(_INST(bytes))
     && _isSmallInteger(x)
     && _isSmallInteger(y)
     && _isSmallInteger(_INST(width)) ) {
        int _w = _intVal(_INST(width));
        int _y = _intVal(y);
        int _x = _intVal(x);
	int _idx;

	_idx = (_w + 7) / 8 * _y + (_x / 8);
	if (aPixelValue == _MKSMALLINT(0)) {
            _ByteArrayInstPtr(_INST(bytes))->ba_element[_idx] &= ~(0x80 >> (_x % 8));
	} else {
            _ByteArrayInstPtr(_INST(bytes))->ba_element[_idx] |= (0x80 >> (_x % 8));
	}
        RETURN( self );
    }
%}
.
    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."

    |value|

    photometric == #whiteIs0 ifTrue:[
        aColor = Color white ifTrue:[
            value := 0
        ] ifFalse:[
            aColor = Color black ifTrue:[
                value := 1
            ] ifFalse:[
                self error:'invalid color'
            ]
        ]
    ] ifFalse:[
        photometric == #blackIs0 ifTrue:[
            aColor = Color black ifTrue:[
                value := 0
            ] ifFalse:[
                aColor = Color white ifTrue:[
                    value := 1
                ] ifFalse:[
                    self error:'invalid color'
                ]
            ]
        ] ifFalse:[
            photometric ~~ #palette ifTrue:[
                self error:'format not supported'.
                ^ nil
            ].
            (aColor = colorMap at:1) ifTrue:[
                value := 0
            ] ifFalse:[
                (aColor = colorMap at:2) ifTrue:[
                    value := 0
                ] ifFalse:[
                    self error:'invalid color'
                ]
            ]
        ]
    ].
    self atX:x y:y putValue:value
!

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 := Color red:(((colorMap at:1) at:1) * 100 / 255)
                              green:(((colorMap at:2) at:1) * 100 / 255)
                               blue:(((colorMap at:3) at:1) * 100 / 255).
                color1 := Color red:(((colorMap at:1) at:2) * 100 / 255)
                              green:(((colorMap at:2) at:2) * 100 / 255)
                               blue:(((colorMap at:3) at:2) * 100 / 255).
            ] 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
! !

!Depth1Image 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, bpr;
    REGISTER int outcnt, bits, bit, mask, incnt;
    int shift;
    unsigned char byte1, byte2, byte3, byte4;

    /* 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 (_isSmallInteger(srcStart) && _isSmallInteger(dstStart)
     && _isSmallInteger(_INST(width)) && _isSmallInteger(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(_INST(width));

        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:
                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
! !