Depth1Image.st
author Claus Gittinger <cg@exept.de>
Tue, 28 Jul 1998 22:25:16 +0200
changeset 2201 7272763312a0
parent 2179 30461fd19cd5
child 2208 eb1122c8d556
permissions -rw-r--r--
comments

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

    #blackIs0 / #whiteIs0 and #palette formats are supported here.

    [author:]
        Claus Gittinger

    [see also:]
        Depth2Image Depth4Image Depth8Image Depth16Image Depth24Image
        ImageReader
"
! !

!Depth1Image class methodsFor:'queries'!

imageDepth
    "return the depth of images represented by instances of
     this class - here we return 1"

    ^ 1

    "Modified: 20.4.1996 / 23:40:06 / cg"
! !

!Depth1Image methodsFor:'accessing - pixels'!

colorAtX: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 colorFromValue:value
    ].
    value := value + 1.
    ^ colorMap at:value

    "Modified: 8.6.1996 / 10:52:15 / cg"
    "Created: 24.4.1997 / 17:33:17 / cg"
!

colorAtX: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 pixelAtX:x y:y put:0.
        ^ self
    ].
    aColor = clr1 ifTrue:[
        self pixelAtX:x y:y put:1.
        ^ self
    ].

    "
     the color to be stored is not in the images colormap
    "
    self error:'invalid color - not in colorMap'

    "Modified: 24.4.1997 / 17:16:38 / cg"
    "Created: 24.4.1997 / 17:33:23 / cg"
!

pixelAtX: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;
        int _idx;

        _idx = ((_w + 7) >> 3) * _y + (_x >> 3);
        if ((unsigned)_idx < __byteArraySize(b)) {
            _byte = __ByteArrayInstPtr(b)->ba_element[_idx];
            RETURN( (_byte & (0x80 >> (_x & 7))) ? __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
!

pixelAtX:x y:y put: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) >> 3) * _y + (_x >> 3);
        if ((unsigned)_idx < __byteArraySize(b)) {
            if (aPixelValue == __MKSMALLINT(0)) {
                __ByteArrayInstPtr(b)->ba_element[_idx] &= ~(0x80 >> (_x & 7));
            } else {
                __ByteArrayInstPtr(b)->ba_element[_idx] |= (0x80 >> (_x & 7));
            }
            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
! !

!Depth1Image methodsFor:'converting greyscale images'!

asFormOn:aDevice
    "convert a monochrome image to a device form"

    |f|

    ((aDevice == device) and:[deviceForm notNil]) ifTrue:[^ deviceForm].

    f := Form width:width height:height fromArray:bytes on:aDevice.
    f notNil ifTrue:[
        f colorMap:(Array with:(self colorFromValue:0)
                          with:(self colorFromValue:1)).
    ].
    ^ f

    "Created: 14.6.1996 / 15:20:00 / cg"
    "Modified: 24.4.1997 / 17:50:43 / cg"
!

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

    ^ self asFormOn:aDevice

    "Modified: 14.6.1996 / 15:21:04 / cg"
!

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

    ^ self asFormOn:aDevice

    "Modified: 14.6.1996 / 15:21:09 / cg"
! !

!Depth1Image methodsFor:'converting palette images'!

paletteImageAsMonoFormOn:aDevice
    "convert a palette image to a b&w monochrome device form"

    |f c0 c1|

    f := Form width:width height:height fromArray:bytes on:aDevice.
    c0 := self colorFromValue:0.
    c1 := self colorFromValue:1.
    c0 brightness > 0.5 ifTrue:[
        c0 := Color white
    ] ifFalse:[
        c0 := Color black.
    ].
    c1 brightness > 0.5 ifTrue:[
        c1 := Color white
    ] ifFalse:[
        c1 := Color black.
    ].
    f colorMap:(Array with:c0 with:c1).
    ^ f

    "Modified: 24.4.1997 / 17:51:54 / cg"
!

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

    ^ self asFormOn:aDevice

    "Modified: 14.6.1996 / 15:21:33 / cg"
!

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 asFormOn:aDevice

    "
     |i|

     i := Depth1Image
                width:4
                height:4
                fromArray:#[ 2r00000000
                             2r11110000
                             2r01010000
                             2r10100000 ].
     i photometric:#rgb.
     i samplesPerPixel:3.
     i bitsPerSample:#(1 0 0).

     i := i magnifiedBy:30.
     i inspect.
    "

    "Modified: 14.6.1996 / 15:21:37 / cg"
! !

!Depth1Image methodsFor:'enumerating'!

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

    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:[
                color0 := self colorFromValue:0.
                color1 := self colorFromValue:1.
            ]
        ]
    ].

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

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

        mask := mask bitShift:-1.
        mask == 0 ifTrue:[
            mask := 2r10000000.
            srcIndex := srcIndex + 1.
            x < x2 ifTrue:[
                byte := bytes at:srcIndex.
            ]
        ]
    ]

    "Created: 7.6.1996 / 19:12:26 / cg"
    "Modified: 10.6.1996 / 10:33:06 / cg"
!

valuesAtY: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).

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

        mask := mask bitShift:-1.
        mask == 0 ifTrue:[
            mask := 2r10000000.
            srcIndex := srcIndex + 1.
            x < x2 ifTrue:[
                byte := bytes at:srcIndex.
            ]
        ]
    ]

    "Created: 7.6.1996 / 19:09:38 / cg"
    "Modified: 8.6.1996 / 13:36:37 / cg"
! !

!Depth1Image methodsFor:'magnification'!

hardMagnifiedBy:scalePoint
    "return a new image magnified by scalePoint, aPoint.
     This is the general magnification method, handling non-integral values.
     It is slower than the integral magnification method."

    |mX        
     mY        
     newWidth  "{ Class: SmallInteger }"
     newHeight "{ Class: SmallInteger }"
     w         "{ Class: SmallInteger }"
     h         "{ Class: SmallInteger }"
     newImage newBits bitsPerPixel newBytesPerRow
     value srcRow srcCol
     dstBytes dstRow dstCol newMask|

    mX := scalePoint x.
    mY := scalePoint y.

    newWidth := (width * mX) truncated.
    newHeight := (height * mY) truncated.

    bitsPerPixel := self depth.
    newBytesPerRow := ((newWidth * bitsPerPixel) + 7) // 8.
    newBits := ByteArray new:(newBytesPerRow * newHeight).

    mask notNil ifTrue:[
        newMask := (mask magnifiedBy:scalePoint)
    ].

    newImage := self species new.

    newImage 
        width:newWidth 
        height:newHeight 
        photometric:photometric 
        samplesPerPixel:samplesPerPixel 
        bitsPerSample:bitsPerSample 
        colorMap:colorMap copy
        bits:newBits
        mask:newMask.

    "walk over destination image fetching pixels from source image"

    mX := mX asFloat.
    mY := mY asFloat.

%{
{
    OBJ b1 = __INST(bytes);
    int _w1 = __intVal(__INST(width));
    int _y1, _y2;
    OBJ b2 = newBits;
    int _w2 = __intVal(newWidth);
    int _h2 = __intVal(newHeight);
    int _x2, _x1;
    int _idx2;
    unsigned _byte;
    double _mY = __floatVal(mY);
    double _mX = __floatVal(mX);

    for (_y2 = 0; _y2 < _h2; _y2++) {
        _y1 = (int)( (double)_y2 / _mY);

        for (_x2 = 0; _x2 < _w2; _x2++) {
            _x1 = (int)( (double)_x2 / _mX);
            
            _byte = __ByteArrayInstPtr(b1)->ba_element[(_w1 + 7) / 8 * _y1 + (_x1 / 8)];

            if ((_byte & (0x80 >> (_x1 % 8)))) {
                _idx2 = (_w2 + 7) / 8 * _y2 + (_x2 / 8);
                __ByteArrayInstPtr(b2)->ba_element[_idx2] |= (0x80 >> (_x2 % 8));
            }
        }
    }
}
%}.

"/    w := newWidth - 1.
"/    h := newHeight - 1.
"/
"/    0 to:h do:[:row |
"/        dstRow := row.
"/        srcRow := (row // mY).
"/        0 to:w do:[:col |
"/
"/            dstCol := col.
"/            srcCol := col // mX.
"/            value := self valueAtX:(col // mX) y:srcRow.
"/            newImage atX:col y:row putValue:value.
"/        ]
"/    ].

    ^ newImage

    "((Image fromFile:'bitmaps/claus.gif') magnifiedBy:0.5@0.5)"

    "Created: 18.6.1996 / 16:04:26 / cg"
!

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;
                        }
                    }
                }
                if (outcnt) {
                    *dstP = bits << (8-outcnt);
                }
                break;
        }
        RETURN (self);
    }
%}.
    self primitiveFailed
! !

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

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

    |nbytes|

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

usedColors
    "return a collection of colors used in the receiver.
     For depth1 images, we return the colorMap here, assuming all
     pixels are used ...
     ... which is not really true - it could be all-white or all-black"

    photometric ~~ #palette ifTrue:[
        ^ Array with:Color white with:Color black.
    ].
    ^ colorMap

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

    "Modified: / 28.7.1998 / 22:21:29 / cg"
!

usedValues
    "return a collection of color values used in the receiver.
     For depth1 images, we assuming both 1- and 0-pixels are present ...
     ... which is not really true - it could be all-white or all-black"

    ^ #(0 1)

    "Modified: / 28.7.1998 / 22:22:43 / cg"
! !

!Depth1Image class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Depth1Image.st,v 1.35 1998-07-28 20:24:40 cg Exp $'
! !