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

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

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

!Depth4Image methodsFor:'accessing'!

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
!

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

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

    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
    ].
    ^ 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"

    |lineIndex index byte|

    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
!

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|

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

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

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

        aBlock value:x value:(colors at:(value + 1)).
        shift == 0 ifTrue:[
            shift := -4.
            srcIndex := srcIndex + 1.
        ] ifFalse:[
            shift := 0
        ]
    ]
! !

!Depth4Image 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;

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