Depth24Image.st
author Claus Gittinger <cg@exept.de>
Tue, 22 Jul 1997 12:09:50 +0200
changeset 1818 fd245b7ae2f9
parent 1817 2f71142cb24d
child 1923 cdd2c4e199df
permissions -rw-r--r--
checkin from browser

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

!Depth24Image 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 true-color (24 bit / pixel) images.
    It mainly consists of methods already implemented in Image,
    reimplemented here for more performance.

    Only the #rgb format is supported here.

    [author:]
        Claus Gittinger

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

!Depth24Image class methodsFor:'queries'!

defaultPhotometric
    "return the default photometric pixel interpretation"

    ^ #rgb

    "Created: 10.6.1996 / 18:08:25 / cg"
!

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

    ^ 24

    "Modified: 20.4.1996 / 23:39:50 / cg"
! !

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

    |index "{ Class: SmallInteger }"
     rVal gVal bVal|

    index := 1 + (((width * y) + x) * 3).
    rVal := bytes at:(index).
    gVal := bytes at:(index + 1).
    bVal := bytes at:(index + 2).

    photometric ~~ #rgb ifTrue:[
        ^ super colorAtX:x y:y
    ].
    ^ Color redByte:rVal greenByte:gVal blueByte:bVal

    "Created: 24.4.1997 / 17:32:47 / cg"
    "Modified: 24.4.1997 / 21:32:37 / 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."

    |index "{ Class: SmallInteger }"|

    index := 1 + (((width * y) + x) * 3).
    bytes at:(index) put:(aColor redByte).
    bytes at:(index + 1) put:(aColor greenByte).
    bytes at:(index + 2) put:(aColor blueByte).

    "Created: 24.4.1997 / 17:32:59 / cg"
!

pixelAtX: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"

    |index "{ Class: SmallInteger }"
     rVal  "{ Class: SmallInteger }"
     gVal  "{ Class: SmallInteger }"
     bVal  "{ Class: SmallInteger }"|

    index := 1 + (((width * y) + x) * 3).
    rVal := bytes at:(index).
    gVal := bytes at:(index + 1).
    bVal := bytes at:(index + 2).
    ^ (((rVal bitShift:8) bitOr:gVal) bitShift:8) bitOr:bVal

    "Created: 24.4.1997 / 16:06:34 / cg"
!

pixelAtX:x y:y put:aPixelValue
    "set a pixel at x/y to aPixelValue, which is 24 bits RGB.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel"

    |index "{ Class: SmallInteger }"
     val   "{ Class: SmallInteger }" |

    index := 1 + (((width * y) + x) * 3).
    val := aPixelValue.
    bytes at:(index + 2) put:(val bitAnd:16rFF).
    val := val bitShift:-8.
    bytes at:(index + 1) put:(val bitAnd:16rFF).
    val := val bitShift:-8.
    bytes at:(index) put:val.

    "Created: 24.4.1997 / 17:06:33 / cg"
!

rowAt:rowIndex putAll:pixelArray
    "replace a single rows bits from bits in the pixelArray argument;
     Notice: row indexing starts at 0."

    |dstIdx pixel|

    dstIdx := (rowIndex * self bytesPerRow) + 1.
    1 to:width do:[:col |
        pixel := pixelArray at:col.
        bytes at:dstIdx put:((pixel bitShift:-16) bitAnd:16rFF).
        bytes at:dstIdx+1 put:((pixel bitShift:-8) bitAnd:16rFF).
        bytes at:dstIdx+2 put:(pixel bitAnd:16rFF).
        dstIdx := dstIdx + 3.
    ].
    ^ pixelArray

    "Created: 24.4.1997 / 15:43:08 / cg"
!

rowAt:rowIndex putAll:pixelArray startingAt:startIndex
    "store a single rows bits from bits in the pixelArray argument;
     Return the pixelArray.
     Notice: row indexing starts at 0."

    |dstIdx pixel|

    dstIdx := (rowIndex * self bytesPerRow) + 1.
    1 to:width do:[:col |
        pixel := pixelArray at:(startIndex + col).
        bytes at:dstIdx put:((pixel bitShift:-16) bitAnd:16rFF).
        bytes at:dstIdx+1 put:((pixel bitShift:-8) bitAnd:16rFF).
        bytes at:dstIdx+2 put:(pixel bitAnd:16rFF).
        dstIdx := dstIdx + 3.
    ].
    ^ pixelArray

    "Created: 24.4.1997 / 15:50:27 / cg"
! !

!Depth24Image methodsFor:'converting rgb images'!

asGrayFormOn:aDevice
    "return a grey form from the receiver.
     Redefined to use special code when converting to 8-bit
     greyScale displays."

    (aDevice visualType == #StaticGray) ifTrue:[
        aDevice depth == 8 ifTrue:[
            ^ self makeDeviceGrayPixmapOn:aDevice depth:aDevice depth fromArray:(self threshold8BitGrayBits)
        ].
    ].
    ^ super asGrayFormOn:aDevice

    "Created: 10.6.1996 / 19:00:45 / cg"
    "Modified: 10.6.1996 / 20:10:19 / cg"
!

asThresholdGrayImageDepth:depth
    "return an 8-bit grey image from the rgb picture.
     Pixel values are reduced to a 0..255 grey level."

    depth == 8 ifTrue:[
        photometric == #rgb ifTrue:[
            ^ Depth8Image
                width:width
                height:height
                fromArray:(self threshold8BitGrayBits)
        ]
    ].
    ^ super asThresholdGrayImageDepth:depth

    "
     |i|

     i := Image fromFile:'bitmaps/granite.tiff'.
     (i asThresholdGrayImageDepth:8) inspect.
     (i asThresholdGrayImageDepth:4) inspect.
     (i asThresholdGrayImageDepth:2) inspect.
     (i asThresholdGrayImageDepth:1) inspect.
    "

    "
     |i|

     i := Image fromFile:'bitmaps/granite.tiff'.
     ((i asThresholdGrayImageDepth:8) asOrderedDitheredGrayImageDepth:2) inspect
    "

    "
     |i|

     i := Image fromFile:'bitmaps/granite.tiff'.
     ((i asThresholdGrayImageDepth:8) asOrderedDitheredGrayImageDepth:4) inspect
    "

    "
     |i|

     i := Image fromFile:'bitmaps/granite.tiff'.
     (i asThresholdGrayImageDepth:8) asOrderedDitheredMonochromeImage inspect
    "

    "Created: 8.6.1996 / 13:58:46 / cg"
    "Modified: 10.6.1996 / 19:11:18 / cg"
!

rgbImageAsDitheredPseudoFormOn:aDevice
    "return a dithered pseudocolor form from the rgb-picture.
     This method depends on fixColors being allocated (see Color>>getColors*)"

    |ditherColors|

    (ditherColors := aDevice fixColors) notNil ifTrue:[
        ^ self 
                rgbImageAsDitheredPseudoFormOn:aDevice
                colors:ditherColors
                nRed:aDevice numFixRed
                nGreen:aDevice numFixGreen
                nBlue:aDevice numFixBlue
    ].

    ditherColors := Set new.
    ditherColors addAll:(aDevice ditherColors).
    ditherColors addAll:(aDevice deviceColors).
    ditherColors := ditherColors asArray.
    ^ self 
        rgbImageAsDitheredPseudoFormOn:aDevice 
        colors:ditherColors.

    "Modified: 22.4.1997 / 11:59:44 / cg"
!

rgbImageAsDitheredPseudoFormOn:aDevice colors:fixColors
    "return a dithered 8-bit pseudocolor form from the rgb-picture, using
     arbitrary fix colors in fixColors."

    |pseudoBits f
     h        "{ Class: SmallInteger }"
     w        "{ Class: SmallInteger }"
     numFix   "{Class: SmallInteger }"
     srcIndex "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     deviceDepth has8BitImage 
     fixIds fixRed fixGreen fixBlue failed cache idsUsed usedColors|

    numFix := fixColors size.
    numFix == 256 ifTrue:[
        "/ algorithm below only handles 255 colors.
        numFix := 255.
    ].
    fixIds := (fixColors asArray collect:[:clr | clr colorId]) asByteArray.

    fixRed := (fixColors asArray collect:[:clr | clr redByte]) asByteArray.
    fixGreen := (fixColors asArray collect:[:clr | clr greenByte]) asByteArray.
    fixBlue := (fixColors asArray collect:[:clr | clr blueByte]) asByteArray.
    cache := ByteArray new:(1 bitShift:14).
    cache atAllPut:16rFF.

    deviceDepth := aDevice depth.
    deviceDepth == 8 ifTrue:[
        has8BitImage := true.
    ] ifFalse:[
        has8BitImage := false.
        aDevice supportedImageFormats do:[:fmt |
            (fmt at:#bitsPerPixel) == 8 ifTrue:[
                has8BitImage := true.
            ]
        ]
    ].
    has8BitImage ifFalse:[^ nil].

    idsUsed := ByteArray new:(fixIds size).

    'Depth24Image [info]: dithering ...' infoPrintCR.

    pseudoBits := ByteArray uninitializedNew:(width * height).

    h := height.
    w := width.

%{
    int __x, __y, __numFix;
    int __eR, __eG, __eB;
    unsigned char *srcP, *dstP;
    int pix;
    unsigned char *idP, *usedIdP, *redP, *greenP, *blueP, *cacheP;
    int __w = __intVal(w);

    if (__isByteArray(__INST(bytes))
     && __isSmallInteger(numFix)
     && __isByteArray(pseudoBits)
     && __isByteArray(cache)
     && __isByteArray(fixIds)
     && __isByteArray(idsUsed)
     && __isByteArray(fixRed)
     && __isByteArray(fixGreen)
     && __isByteArray(fixBlue) ) {
        failed = false;

        srcP = __ByteArrayInstPtr(__INST(bytes))->ba_element;
        dstP = __ByteArrayInstPtr(pseudoBits)->ba_element;
        idP = __ByteArrayInstPtr(fixIds)->ba_element;
        usedIdP = __ByteArrayInstPtr(idsUsed)->ba_element;
        redP = __ByteArrayInstPtr(fixRed)->ba_element;
        greenP = __ByteArrayInstPtr(fixGreen)->ba_element;
        blueP = __ByteArrayInstPtr(fixBlue)->ba_element;
        cacheP = __ByteArrayInstPtr(cache)->ba_element;
        __numFix = __intVal(numFix);

        for (__y=__intVal(h); __y>0; __y--) {
            __eR = __eG = __eB = 0;
            for (__x=__w; __x>0; __x--) {
                int cacheIdx, clrIdx;
                int __wantR, __wantG, __wantB;

                __wantR = srcP[0] + __eR;
                if (__wantR > 255) __wantR = 255;
                else if (__wantR < 0) __wantR = 0;

                __wantG = srcP[1] + __eG;
                if (__wantG > 255) __wantG = 255;
                else if (__wantG < 0) __wantG = 0;

                __wantB = srcP[2] + __eB;
                if (__wantB > 255) __wantB = 255;
                else if (__wantB < 0) __wantB = 0;

                /*
                 * compute cache index
                 */
                cacheIdx = ((__wantR & 0xF8) >> 3);
                cacheIdx = (cacheIdx << 5) | ((__wantG & 0xF8) >> 3);
                cacheIdx = (cacheIdx << 4) | ((__wantB & 0xF0) >> 4);

                clrIdx = cacheP[cacheIdx];
                if (clrIdx == 0xFF) {   /* invalid slot */
                    unsigned minErr, minIdx;
                    int i;

                    /*
                     * must search ...
                     */
                    minErr = 0x7FFFFFF; minIdx = 0;
                    for (i=0; i<__numFix; i++) {
                        unsigned cR, cG, cB, e;
                        int eR, eG, eB;

                        cR = redP[i]; cG = greenP[i]; cB = blueP[i];
                        eR = cR - __wantR;
                        if (eR < 0) eR = -eR;

                        eG = cG - __wantG;
                        if (eG < 0) eG = -eG;

                        eB = cB - __wantB;
                        if (eB < 0) eB = -eB;

                        e = eR + eG + eB;
                        if (e < minErr) {
                            minErr = e;
                            minIdx = i;
                            if (e < 7) {
                                break;
                            }
                        }
                    }

                    /*
                     * minIdx is now index into fixColors
                     */
                    cacheP[cacheIdx] = clrIdx = minIdx;
/*
printf("want %d/%d/%d best: %d [%d/%d/%d]\n", __wantR, __wantG, __wantB, clrIdx, redP[clrIdx], greenP[clrIdx], blueP[clrIdx]);
*/
                }

                /*
                 * store the corresponding dither colorId
                 */
                *dstP++ = idP[clrIdx];
                usedIdP[clrIdx] = 1;

                srcP += 3;

                /*
                 * the new error:
                 */
                __eR = __wantR - redP[clrIdx]; 
                __eG = __wantG - greenP[clrIdx]; 
                __eB = __wantB - blueP[clrIdx]; 
            }
        }
    }
%}.
    failed ifTrue:[
        self primitiveFailed.
        ^ nil
    ].

    "/ not all colors may be really in use ...
    usedColors := fixColors copy.
    idsUsed keysAndValuesDo:[:idx :flag |
        flag == 0 ifTrue:[
            usedColors at:idx put:nil
        ]
    ].

    f := Form width:width height:height depth:aDevice depth on:aDevice.
    f isNil ifTrue:[^ nil].
    f colorMap:usedColors.
    f initGC.
    aDevice drawBits:pseudoBits bitsPerPixel:8 depth:aDevice depth
               width:width height:height
                   x:0 y:0
                into:(f id) x:0 y:0 width:width height:height with:(f gcId).
    ^ f
!

rgbImageAsDitheredPseudoFormOn:aDevice colors:fixColors nRed:nRed nGreen:nGreen nBlue:nBlue
    "return a dithered pseudocolor form from the rgb-picture,
     using colors from a colorCube for dithering."

    |pseudoBits f
     h        "{ Class: SmallInteger }"
     w        "{ Class: SmallInteger }"
"/     eR    "{Class: SmallInteger }"
"/     eG    "{Class: SmallInteger }"
"/     eB    "{Class: SmallInteger }"
"/     wantR "{Class: SmallInteger }"
"/     wantG "{Class: SmallInteger }"
"/     wantB "{Class: SmallInteger }"
     fixR  "{Class: SmallInteger }"
     fixG  "{Class: SmallInteger }"
     fixB  "{Class: SmallInteger }"
     srcIndex "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     deviceDepth has8BitImage 
     fixIds idsUsed failed usedColors|

    fixR := nRed.
    fixR == 0 ifTrue:[ ^ nil].
    fixG := nGreen.
    fixG == 0 ifTrue:[ ^ nil].
    fixB := nBlue.
    fixB == 0 ifTrue:[ ^ nil].
    "/ simple check
    (fixR * fixG * fixB) ~~ fixColors size ifTrue:[
        self error:'invalid color array passed'.
        ^ nil
    ].
    fixIds := (fixColors asArray collect:[:clr | clr colorId]) asByteArray.
    idsUsed := ByteArray new:(fixIds size).

    deviceDepth := aDevice depth.
    deviceDepth == 8 ifTrue:[
        has8BitImage := true.
    ] ifFalse:[
        has8BitImage := false.
        aDevice supportedImageFormats do:[:fmt |
            (fmt at:#bitsPerPixel) == 8 ifTrue:[
                has8BitImage := true.
            ]
        ]
    ].
    has8BitImage ifFalse:[^ nil].

    'Depth24Image [info]: dithering ...' infoPrintCR.

    pseudoBits := ByteArray uninitializedNew:(width * height).

    h := height.
    w := width.

%{
    int __x, __y;
    int __eR, __eG, __eB;
    int __wantR, __wantG, __wantB;
    unsigned char *srcP, *dstP;
    unsigned char *redP, *greenP, *blueP;
    int pix;
    unsigned char *idP;
    unsigned char *usedIdP;
    int __fR, __fG, __fB;
    int iR, iG, iB;
    int idx;
    int __w = __intVal(w);
    int leftToRight;

    if (__isByteArray(__INST(bytes))
     && __isByteArray(pseudoBits)
     && __isByteArray(fixIds)
     && __isByteArray(idsUsed)
     && __bothSmallInteger(fixR, fixG)
     && __isSmallInteger(fixB)) {
        failed = false;

        srcP = __ByteArrayInstPtr(__INST(bytes))->ba_element;
        dstP = __ByteArrayInstPtr(pseudoBits)->ba_element;
        idP = __ByteArrayInstPtr(fixIds)->ba_element;
        usedIdP = __ByteArrayInstPtr(idsUsed)->ba_element;
        __fR = __intVal(fixR)-1;
        __fG = __intVal(fixG)-1;
        __fB = __intVal(fixB)-1;

        __eR = __eG = __eB = 0;

        leftToRight = 1;
        for (__y=__intVal(h); __y>0; __y--) {
            if (leftToRight) {
                for (__x=__w; __x>0; __x--) {
                    int __want;

                    /*
                     * wR, wG and wB is the wanted r/g/b value;
                     * compute the index into the dId table ..
                     * values: 0..255; scale to 0..fR-1, 0..fG-1, 0..fB-1
                     *
                     * bad kludge: knows how to index into FixColor table
                     */
                    __wantR = __want = srcP[0] + __eR;

                    if (__want > 255) __want = 255;
                    else if (__want < 0) __want = 0;

                    iR = __want * __fR / 128;
                    iR = (iR / 2) + (iR & 1);

                    __wantG = __want = srcP[1] + __eG;
                    if (__want > 255) __want = 255;
                    else if (__want < 0) __want = 0;

                    iG = __want * __fG / 128;
                    iG = (iG / 2) + (iG & 1);

                    __wantB = __want = srcP[2] + __eB;
                    if (__want > 255) __want = 255;
                    else if (__want < 0) __want = 0;

                    iB = __want * __fB / 128;
                    iB = (iB / 2) + (iB & 1);

                    idx = iR * (__fG+1);
                    idx = (idx + iG) * (__fB+1);
                    idx = idx + iB;

                    /*
                     * store the corresponding dither colorId
                     */
                    *dstP++ = idP[idx];
                    usedIdP[idx] = 1;

                    srcP += 3;

                    /*
                     * the new error:
                     */
                    __eR = __wantR - (iR * 256 / __fR); 
                    __eG = __wantG - (iG * 256 / __fG); 
                    __eB = __wantB - (iB * 256 / __fB);
                }
                leftToRight = 0;
            } else {
                srcP += (__w*3);
                dstP += __w;
                for (__x=__w; __x>0; __x--) {
                    int __want;

                    /*
                     * wR, wG and wB is the wanted r/g/b value;
                     * compute the index into the dId table ..
                     * values: 0..255; scale to 0..fR-1, 0..fG-1, 0..fB-1
                     *
                     * bad kludge: knows how to index into FixColor table
                     */
                    srcP -= 3;
                    __wantR = __want = srcP[0] + __eR;

                    if (__want > 255) __want = 255;
                    else if (__want < 0) __want = 0;

                    iR = __want * __fR / 128;
                    iR = (iR / 2) + (iR & 1);

                    __wantG = __want = srcP[1] + __eG;
                    if (__want > 255) __want = 255;
                    else if (__want < 0) __want = 0;

                    iG = __want * __fG / 128;
                    iG = (iG / 2) + (iG & 1);

                    __wantB = __want = srcP[2] + __eB;
                    if (__want > 255) __want = 255;
                    else if (__want < 0) __want = 0;

                    iB = __want * __fB / 128;
                    iB = (iB / 2) + (iB & 1);

                    idx = iR * (__fG+1);
                    idx = (idx + iG) * (__fB+1);
                    idx = idx + iB;

                    /*
                     * store the corresponding dither colorId
                     */
                    *--dstP = idP[idx];
                    usedIdP[idx] = 1;

                    /*
                     * the new error:
                     */
                    __eR = __wantR - (iR * 256 / __fR); 
                    __eG = __wantG - (iG * 256 / __fG); 
                    __eB = __wantB - (iB * 256 / __fB); 
                }
                srcP += (__w*3);
                dstP += __w;
                leftToRight = 1;
            }
        }
    }
%}.
    failed ifTrue:[
        self primitiveFailed.
        ^ nil

"/ for non-C programmers:
"/     the above code is (roughly) equivalent to:
"/     (but it is just as ugly looking as the above ;-)
"/
"/    srcIndex := 1.
"/    dstIndex := 1.
"/    1 to:h do:[:y |
"/        eR := eG := eB := 0.
"/        1 to:w do:[:x |
"/            |pixel "{ Class: SmallInteger }"
"/             clr 
"/             idx   "{ Class: SmallInteger }"
"/             iR    "{ Class: SmallInteger }"
"/             iG    "{ Class: SmallInteger }"
"/             iB    "{ Class: SmallInteger }"
"/             wR    "{ Class: SmallInteger }"
"/             wG    "{ Class: SmallInteger }"
"/             wB    "{ Class: SmallInteger }" |
"/
"/            wantR := ((bytes at:srcIndex) + eR). srcIndex := srcIndex + 1.
"/            wantG := ((bytes at:srcIndex) + eG). srcIndex := srcIndex + 1.
"/            wantB := ((bytes at:srcIndex) + eB). srcIndex := srcIndex + 1.
"/            wR := wantR.
"/            wR > 255 ifTrue:[wR := 255] ifFalse:[wR < 0 ifTrue:[wR := 0]].
"/            wG := wantG.
"/            wG > 255 ifTrue:[wG := 255] ifFalse:[wG < 0 ifTrue:[wG := 0]].
"/            wB := wantB.
"/            wB > 255 ifTrue:[wB := 255] ifFalse:[wB < 0 ifTrue:[wB := 0]].
"/
"/            iR := wR * (fixR-1) // 128.
"/            iR := (iR // 2) + (iR bitAnd:1).
"/            iG := wG * (fixG-1) // 128.
"/            iG := (iG // 2) + (iG bitAnd:1).
"/            iB := wB * (fixB-1) // 128.
"/            iB := (iB // 2) + (iB bitAnd:1).
"/            idx := (iR * fixR + iG) * fixB + iB + 1.
"/
"/            clr := fixColors at:idx.
"/
"/            eR := wantR - (clr red * 2) asInteger.
"/            eG := wantG - (clr green * 2) asInteger.
"/            eB := wantB - (clr blue * 2) asInteger.
"/
"/            pixel := clr colorId.
"/            pseudoBits at:dstIndex put:pixel.
"/
"/            dstIndex := dstIndex + 1
"/        ].
    ].

    "/ not all colors may be really in use ...
    usedColors := fixColors copy.
    idsUsed keysAndValuesDo:[:idx :flag |
        flag == 0 ifTrue:[
            usedColors at:idx put:nil
        ]
    ].

    f := Form width:width height:height depth:aDevice depth on:aDevice.
    f isNil ifTrue:[^ nil].
    f colorMap:usedColors.
    f initGC.
    aDevice drawBits:pseudoBits bitsPerPixel:8 depth:aDevice depth
               width:width height:height
                   x:0 y:0
                into:(f id) x:0 y:0 width:width height:height with:(f gcId).
    ^ f
!

rgbImageAsPseudoFormOn:aDevice
    "return a pseudocolor form from the rgb-picture.
     If a colorCube is used, pass the work on to the cube-dither
     code. Otherwise, allocate as many colors as possible, then
     use those for dithering. 
     Could be improved, by searching for (& allocating)
     heavily used colors and/or min-max colors first."

    |pseudoBits f
     r        "{ Class: SmallInteger }"
     g        "{ Class: SmallInteger }"
     b        "{ Class: SmallInteger }"
     srcIndex "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"
     rMask    "{ Class: SmallInteger }"
     gMask    "{ Class: SmallInteger }"
     bMask    "{ Class: SmallInteger }"
     redArray greenArray blueArray
     dataSize "{ Class: SmallInteger }"
     nColors  "{ Class: SmallInteger }"
     fit fitMap colors color ditherColors
     fast
     colorIndex "{ Class: SmallInteger }"
     depth nColorCells deep nColorsNeeded|

    aDevice fixColors notNil ifTrue:[
        "/ no need to look for used colors - dithering anyway ...

        f := self rgbImageAsDitheredPseudoFormOn:aDevice.
        f notNil ifTrue:[^ f].
    ].

    "find used colors; build color-tree"

    fit := false.                       
    fitMap := false.
    depth := aDevice depth.
    nColorCells := aDevice ncells.

    deep := (depth > 8).

    rMask := 2r11111111.
    gMask := 2r11111111.
    bMask := 2r11111111.

    'Depth24Image [info]: allocating colors ...' infoPrintCR.

    [fit] whileFalse:[
        [fitMap] whileFalse:[
            srcIndex := 1.
            redArray := Array new:256.

            "
             find used colors, build [r][g][b] 3-dimensional array
             containing true for used colors
            "
            nColors := 0.
            srcIndex := 1.
            dataSize := bytes size.
            [(srcIndex < dataSize)
             and:[nColors <= nColorCells]] whileTrue:[
%{
                if (__isByteArray(_INST(bytes))) {
                    int sI = _intVal(srcIndex);
                    unsigned char *cp = _ByteArrayInstPtr(_INST(bytes))->ba_element;

                    r = __MKSMALLINT((cp[sI - 1] & _intVal(rMask)) + 1);
                    g = __MKSMALLINT((cp[sI]     & _intVal(gMask)) + 1);
                    b = __MKSMALLINT((cp[sI + 1] & _intVal(bMask)) + 1);
                    srcIndex = __MKSMALLINT(sI + 3);
                    fast = true;
                } else {
                    fast = false;
                }
%}
.
                fast ifFalse:[
                    r := bytes at:srcIndex.
                    r := (r bitAnd:rMask) + 1.
                    srcIndex := srcIndex + 1.
                    g := bytes at:srcIndex.
                    g := (g bitAnd:gMask) + 1.
                    srcIndex := srcIndex + 1.
                    b := bytes at:srcIndex.
                    b := (b bitAnd:bMask) + 1.
                    srcIndex := srcIndex + 1
                ].

                greenArray := redArray at:r.
                greenArray isNil ifTrue:[
                    greenArray := Array new:256.
                    redArray at:r put:greenArray
                ].
                blueArray := greenArray at:g.
                blueArray isNil ifTrue:[
                    deep ifTrue:[blueArray := Array new:256]
                    ifFalse:[blueArray := ByteArray new:256].
                    greenArray at:g put:blueArray
                ].
                (blueArray at:b) == 0 ifTrue:[
                    blueArray at:b put:1.
                    nColors := nColors + 1.
                    (nColors > nColorCells) ifTrue:[
                        'Depth24Image [info]: more than ' infoPrint. nColorCells infoPrint. ' colors' infoPrintCR.
                        srcIndex := dataSize + 1
                    ]
                ]
            ].
            nColorsNeeded isNil ifTrue:[
                nColorsNeeded := nColors
            ].

            "again with less color bits if it does not fit colormap"

            (nColors <= nColorCells) ifTrue:[
                fitMap := true
            ] ifFalse:[
                "/ must try again - cutting off some bits
                "/ blue bits are snipped off faster.
                (bMask == 2r11111111) ifTrue:[
                    bMask := 2r11111100
                ] ifFalse:[
                    (bMask == 2r11111100) ifTrue:[
                        bMask := 2r11110000
                    ] ifFalse:[
                        (rMask == 2r11111111) ifTrue:[
                            rMask := 2r11111100.
                            gMask := 2r11111100.
                        ] ifFalse:[
                            rMask := (rMask bitShift:1) bitAnd:2r11111111.
                            gMask := (gMask bitShift:1) bitAnd:2r11111111.
                            bMask := (bMask bitShift:1) bitAnd:2r11111111
                        ]
                    ]
                ].
                'Depth24Image [info]: too many colors; retry with less color resolution' infoPrintCR.
"
    'masks:' print. rMask print. ' ' print. gMask print. ' ' print.
    bMask printNewline
"
            ]
        ].

        'Depth24Image [info]: ' infoPrint. nColors infoPrint. ' colors used' infoPrintCR.

        colors := Array new:nColors.
        colorIndex := 1.

        "
         now, we have reduced things to the number of colors
         which are theoretically supported by the devices colormap.
         allocate all used colors in walking over true entries in
         the [r][g][b] table - this may still fail,
         if we run out of device colors.
        "
        fit := true.

        r := 0.
        redArray do:[:greenArray |
            (fit and:[greenArray notNil]) ifTrue:[
                g := 0.
                greenArray do:[:blueArray |
                    (fit and:[blueArray notNil]) ifTrue:[
                        b := 0.
                        blueArray do:[:present |
                            |id|

                            (fit and:[present ~~ 0]) ifTrue:[
                                color := Color redByte:r
                                             greenByte:g
                                              blueByte:b.
                                color := color on:aDevice.
                                (id := color colorId) isNil ifTrue:[
                                    fit := false
                                ] ifFalse:[
                                    colors at:colorIndex put:color.
                                    colorIndex := colorIndex + 1.
                                    blueArray at:(b + 1) put:id
                                ]
                            ].
                            b := b + 1
                        ]
                    ].
                    g := g + 1
                ]
            ].
            r := r + 1
        ].

        "again with less color bits if we did not get all colors"

        fit ifFalse:[
            'Depth24Image [info]: could not allocate color(s)' infoPrintCR.

            "free the allocated colors"
            colors atAllPut:nil.
            "a kludge - force immediate freeing of colors"
            ObjectMemory scavenge; finalize.

            "cut off one more color-bit - cut off blue first"
            (bMask == 2r11111111) ifTrue:[
                bMask := 2r11111100
            ] ifFalse:[
                (bMask == 2r11111100) ifTrue:[
                    bMask := 2r11110000
                ] ifFalse:[
                    (rMask == 2r11111111) ifTrue:[
                        rMask := 2r11111100.
                        gMask := 2r11111100.
                    ] ifFalse:[
                        rMask := (rMask bitShift:1) bitAnd:2r11111111.
                        gMask := (gMask bitShift:1) bitAnd:2r11111111.
                        bMask := (bMask bitShift:1) bitAnd:2r11111111
                    ]
                ]
            ].
            fitMap := false.
            redArray := nil
        ]
    ].

    (nColors ~~ nColorsNeeded) ifTrue:[
        "/ mhmh - did not get all colors ...
        "/ add existing colors and dither.

        'Depth24Image [info]: only got ' infoPrint. nColors infoPrint. ' out of ' infoPrint.
        nColorsNeeded infoPrint. ' image colors.' infoPrintCR.

        "/
        "/ dither using those we got ...
        "/
        DitherAlgorithm == #floydSteinberg ifTrue:[
            colors := colors asSet.
"/            ditherColors := aDevice availableDitherColors.
"/            ditherColors notNil ifTrue:[
"/                colors addAll:ditherColors.
"/            ].
            colors addAll:aDevice deviceColors.
            colors := colors asArray.
            f := self rgbImageAsDitheredPseudoFormOn:aDevice colors:colors.
            f notNil ifTrue:[^ f].
        ].
    ].

    "create pseudocolor bits and translate"

    pseudoBits := ByteArray uninitializedNew:(width * height).

    srcIndex := 1.
    dstIndex := 1.

    (rMask == 2r11111111
     and:[gMask == 2r11111111
     and:[bMask == 2r11111111]]) ifTrue:[
        [srcIndex < dataSize] whileTrue:[
            r := bytes at:srcIndex.
            srcIndex := srcIndex + 1.
            g := bytes at:srcIndex.
            srcIndex := srcIndex + 1.
            b := bytes at:srcIndex.
            srcIndex := srcIndex + 1.
            greenArray := redArray at:(r + 1).
            blueArray := greenArray at:(g + 1).
            pseudoBits at:dstIndex put:(blueArray at:(b + 1)).
            dstIndex := dstIndex + 1
        ]
    ] ifFalse:[
        [srcIndex < dataSize] whileTrue:[
            r := bytes at:srcIndex.
            r := r bitAnd:rMask.
            srcIndex := srcIndex + 1.
            g := bytes at:srcIndex.
            g := g bitAnd:gMask.
            srcIndex := srcIndex + 1.
            b := bytes at:srcIndex.
            b := b bitAnd:bMask.
            srcIndex := srcIndex + 1.
            greenArray := redArray at:(r + 1).
            blueArray := greenArray at:(g + 1).
            pseudoBits at:dstIndex put:(blueArray at:(b + 1)).
            dstIndex := dstIndex + 1
        ]
    ].

    f := Form width:width height:height depth:depth on:aDevice.
    f isNil ifTrue:[^ nil].
    f colorMap:colors.
    f initGC.
    aDevice drawBits:pseudoBits bitsPerPixel:8 depth:depth
               width:width height:height
                   x:0 y:0
                into:(f id) x:0 y:0 width:width height:height with:(f gcId).
    ^ f
!

rgbImageAsTrueColorFormOn:aDevice
    "return a truecolor form from the rgb-picture."

    |bestFormat usedDeviceDepth usedDeviceBitsPerPixel depth
     myDepth form imageBits destIndex srcIndex 
     rightShiftR rightShiftG rightShiftB shiftRed shiftGreen shiftBlue|

    bestFormat := self bestSupportedImageFormatFor:aDevice.
    usedDeviceDepth := bestFormat at:#depth.
    usedDeviceBitsPerPixel := bestFormat at:#bitsPerPixel.

    rightShiftR := (8 - aDevice bitsRed).
    rightShiftG := (8 - aDevice bitsGreen).
    rightShiftB := (8 - aDevice bitsBlue).

    shiftRed := aDevice shiftRed.
    shiftGreen := aDevice shiftGreen.
    shiftBlue := aDevice shiftBlue.

    "/
    "/ for now, only a few formats are supported
    "/
    myDepth := self bitsPerPixel.
    myDepth == usedDeviceBitsPerPixel ifTrue:[
        "/
        "/ first, the trivial case, where the depths match
        "/ 24 bit/pixel
        "/
        imageBits := bytes.
    ] ifFalse:[
        "/
        "/ 16 bit/pixel ...
        "/
        (usedDeviceBitsPerPixel == 16) ifTrue:[
            imageBits := ByteArray uninitializedNew:(width * height * 2).

            "/ now, walk over the image and compose 16bit values from the r/g/b triples

%{
            if (__bothSmallInteger(_INST(height),_INST(width))
             && __bothSmallInteger(rightShiftR, shiftRed)
             && __bothSmallInteger(rightShiftG, shiftGreen)
             && __bothSmallInteger(rightShiftB, shiftBlue)
             && __isByteArray(_INST(bytes))
             && __isByteArray(imageBits)) {
                int rShRed = __intVal(rightShiftR),
                    rShGreen = __intVal(rightShiftG),
                    rShBlue = __intVal(rightShiftB),
                    lShRed = __intVal(shiftRed),
                    lShGreen = __intVal(shiftGreen),
                    lShBlue = __intVal(shiftBlue);
                int x, y, w;

                unsigned char *srcPtr = _ByteArrayInstPtr(_INST(bytes))->ba_element;
                unsigned char *dstPtr = _ByteArrayInstPtr(imageBits)->ba_element;

                w = __intVal(_INST(width));
                if ((rShRed == 0) && (rShGreen == 0) && (rShBlue == 0)) {
                    for (y=__intVal(_INST(height)); y > 0; y--) {
                        for (x=w; x > 0; x--) {
                            unsigned v;

                            v = srcPtr[0] << lShRed;
                            v |= (srcPtr[1] << lShGreen);
                            v |= (srcPtr[2] << lShBlue);
# ifdef MSBFIRST
                            ((short *)dstPtr)[0] = v;
# else
                            dstPtr[0] = (v>>8) & 0xFF;
                            dstPtr[1] = (v) & 0xFF;
# endif
                            dstPtr += 2;
                            srcPtr += 3;
                        }
                    }
                } else {
                    for (y=__intVal(_INST(height)); y > 0; y--) {
                        for (x=w; x > 0; x--) {
                            unsigned r, g, b, v;

                            r = srcPtr[0] >> rShRed;
                            g = srcPtr[1] >> rShGreen;
                            b = srcPtr[2] >> rShBlue;
                            v = r << lShRed;
                            v |= (g << lShGreen);
                            v |= (b << lShBlue);
# ifdef MSBFIRST
                            ((short *)dstPtr)[0] = v;
# else
                            dstPtr[0] = (v>>8) & 0xFF;
                            dstPtr[1] = (v) & 0xFF;
# endif
                            dstPtr += 2;
                            srcPtr += 3;
                        }
                    }
                }
            }
%}.
        ] ifFalse:[
            "/
            "/ 32 bits/pixel ...
            "/
            (usedDeviceBitsPerPixel == 32) ifTrue:[
                imageBits := ByteArray uninitializedNew:(width * height * 4).

                "/ now, walk over the image and compose 32bit values from the r/g/b triples

%{       
                if (__bothSmallInteger(_INST(height), _INST(width))
                 && __bothSmallInteger(rightShiftR, shiftRed)
                 && __bothSmallInteger(rightShiftG, shiftGreen)
                 && __bothSmallInteger(rightShiftB, shiftBlue)
                 && __isByteArray(_INST(bytes))
                 && __isByteArray(imageBits)) {
                    int rShRed = __intVal(rightShiftR),
                        rShGreen = __intVal(rightShiftG),
                        rShBlue = __intVal(rightShiftB),
                        lShRed = __intVal(shiftRed),
                        lShGreen = __intVal(shiftGreen),
                        lShBlue = __intVal(shiftBlue);
                    int x, y, w;

                    unsigned char *srcPtr = _ByteArrayInstPtr(_INST(bytes))->ba_element;
                    unsigned char *dstPtr = _ByteArrayInstPtr(imageBits)->ba_element;

                    w = __intVal(_INST(width));
                    if ((rShRed == 0) && (rShGreen == 0) && (rShBlue == 0)) {
                        for (y=__intVal(_INST(height)); y > 0; y--) {
                            for (x=w; x > 0; x--) {
                                unsigned v;

                                v = srcPtr[0] << lShRed;
                                v |= (srcPtr[1] << lShGreen);
                                v |= (srcPtr[2] << lShBlue);
# ifdef MSBFIRST
                                ((int *)dstPtr)[0] = v;
# else
                                dstPtr[0] = (v>>24) & 0xFF;
                                dstPtr[1] = (v>>16) & 0xFF;
                                dstPtr[2] = (v>>8) & 0xFF;
                                dstPtr[3] = (v) & 0xFF;
# endif
                                dstPtr += 4;
                                srcPtr += 3;
                            }
                        }
                    } else {
                        for (y=__intVal(_INST(height)); y > 0; y--) {
                            for (x=w; x > 0; x--) {
                                unsigned r, g, b, v;

                                r = srcPtr[0] >> rShRed;
                                g = srcPtr[1] >> rShGreen;
                                b = srcPtr[2] >> rShBlue;
                                v = r << lShRed;
                                v |= (g << lShGreen);
                                v |= (b << lShBlue);
# ifdef MSBFIRST
                                ((int *)dstPtr)[0] = v;
# else
                                dstPtr[0] = (v>>24) & 0xFF;
                                dstPtr[1] = (v>>16) & 0xFF;
                                dstPtr[2] = (v>>8) & 0xFF;
                                dstPtr[3] = (v) & 0xFF;
# endif
                                dstPtr += 4;
                                srcPtr += 3;
                            }
                        }
                    }
                }
%}.
            ] ifFalse:[
                "/
                "/ 8 bits/pixel ...
                "/
                (usedDeviceBitsPerPixel == 8) ifTrue:[
                    imageBits := ByteArray uninitializedNew:(width * height).

                    "/ now, walk over the image and compose 8bit values from the r/g/b triples

%{              
                    if (__bothSmallInteger(_INST(height), _INST(width))
                     && __bothSmallInteger(rightShiftR, shiftRed)
                     && __bothSmallInteger(rightShiftG, shiftGreen)
                     && __bothSmallInteger(rightShiftB, shiftBlue)
                     && __isByteArray(_INST(bytes))
                     && __isByteArray(imageBits)) {
                        int rShRed = __intVal(rightShiftR),
                            rShGreen = __intVal(rightShiftG),
                            rShBlue = __intVal(rightShiftB),
                            lShRed = __intVal(shiftRed),
                            lShGreen = __intVal(shiftGreen),
                            lShBlue = __intVal(shiftBlue);
                        int x, y, w;

                        unsigned char *srcPtr = _ByteArrayInstPtr(_INST(bytes))->ba_element;
                        unsigned char *dstPtr = _ByteArrayInstPtr(imageBits)->ba_element;

                        w = __intVal(_INST(width));
                        if ((rShRed == 0) && (rShGreen == 0) && (rShBlue == 0)) {
                            for (y=__intVal(_INST(height)); y > 0; y--) {
                                for (x=w; x > 0; x--) {
                                    unsigned v;

                                    v = srcPtr[0] << lShRed;
                                    v |= (srcPtr[1] << lShGreen);
                                    v |= (srcPtr[2] << lShBlue);
                                    dstPtr[0] = v;

                                    dstPtr += 1;
                                    srcPtr += 3;
                                }
                            }
                        } else {
                            for (y=__intVal(_INST(height)); y > 0; y--) {
                                for (x=w; x > 0; x--) {
                                    unsigned r, g, b, v;

                                    r = srcPtr[0] >> rShRed;
                                    g = srcPtr[1] >> rShGreen;
                                    b = srcPtr[2] >> rShBlue;
                                    v = r << lShRed;
                                    v |= (g << lShGreen);
                                    v |= (b << lShBlue);

                                    dstPtr[0] = v;

                                    dstPtr += 1;
                                    srcPtr += 3;
                                }
                            }
                        }
                    }
%}.
                ]
            ].
        ]
    ].

    imageBits isNil ifTrue:[            
        'IMAGE: unimplemented trueColor depth in #rgbImageAsTrueColorFormOn: ' errorPrint.
        usedDeviceBitsPerPixel errorPrintCR.
        ^ self asMonochromeFormOn:aDevice
    ].

    form := Form width:width height:height depth:usedDeviceDepth on:aDevice.
    form isNil ifTrue:[
        'Depth24Image [warning]: display bitmap creation failed' errorPrintCR.
        ^ nil
    ].
    form initGC.

    form 
        copyBitsFrom:imageBits bitsPerPixel:usedDeviceBitsPerPixel depth:usedDeviceDepth 
               width:width height:height 
                   x:0 y:0 toX:0 y:0. 

    ^ form

    "Modified: 21.10.1995 / 19:30:11 / cg"
! !

!Depth24Image methodsFor:'dither helpers'!

floydSteinbergDitheredGrayBitsDepth:depth
    "return the bits for dithering a depth gray bitmap from the image.
     Redefined to make use of knowing that pixels are 24 bit r/g/b"

    |dstIndex        "{Class: SmallInteger }"
     nextDst         "{Class: SmallInteger }"
     bytesPerRow     "{Class: SmallInteger }"
     bytesPerOutRow  "{Class: SmallInteger }"
     outBits greyMap1 greyMap2 greyLevels 
     errorArray
     errorArray1
     e t v
     w               "{Class: SmallInteger }"
     h               "{Class: SmallInteger }"
     bitCnt          "{Class: SmallInteger }"
     byte            "{Class: SmallInteger }" 
     grey dT 
     eR eRB eB eLB |

    (samplesPerPixel ~~ 3
    or:[bitsPerSample ~= #(8 8 8)]) ifTrue:[
        ^ super floydSteinbergDitheredGrayBitsDepth:depth
    ].

    w := width.
    h := height.

    bytesPerRow := self bytesPerRow.
    bytesPerOutRow := ((w * depth) + 7) // 8.
    outBits := ByteArray uninitializedNew:(bytesPerOutRow * h).
    (outBits isNil or:[bytes isNil]) ifTrue:[
        ^ nil
    ].

    greyLevels := (1 bitShift:depth) - 1.

    greyMap1 := Array new:256.
    greyMap2 := Array new:256.
    1 to:256 do:[:i |
        v := (greyLevels / 255 * (i-1)).
        greyMap1 at:i put:v.
        greyMap2 at:i put:v.
    ].

    greyMap1 := (greyMap1 collect:[:b | b isNil ifTrue:[
                                            0
                                        ] ifFalse:[
                                            b truncated
                                        ]
                                  ]) asByteArray.      

    greyMap2 := (greyMap2 collect:[:el | 
                                        el isNil ifTrue:[
                                            0
                                        ] ifFalse:[
                                            ((el - el truncated)  "/ the error (0..1)
                                            * 255) rounded
                                        ]]) asByteArray.

    errorArray := ByteArray new:(w + 2) * 2.
    errorArray1 := ByteArray new:(w + 2) * 2.

%{
    int __byte;
    int __dT, __err, __e16, __eR, __eB, __eRB, __eLB;
    int __depth = __intVal(depth);
    int __dstIdx = 0;
    int __srcIdx = 0;
    int __bitCnt;
    int __grey;
    int __w = __intVal(w);
    int __h = __intVal(h);
    int __x;
    int __y;
    int __nextDst;
    int __nextSrc;
    int __bytesPerRow = __intVal(bytesPerRow);
    int __bytesPerOutRow = __intVal(bytesPerOutRow);
    int __pixel;
    int __greyLevels = __intVal(greyLevels);

    unsigned char *__outBits = __ByteArrayInstPtr(outBits)->ba_element;
    unsigned char *__bytes = __ByteArrayInstPtr(__INST(bytes))->ba_element;
    unsigned char *__greyMap1 = __ByteArrayInstPtr(greyMap1)->ba_element;
    unsigned char *__greyMap2 = __ByteArrayInstPtr(greyMap2)->ba_element;
    short *__errorArray = (short *)(__ByteArrayInstPtr(errorArray)->ba_element);
    short *__errorArray1 = (short *)(__ByteArrayInstPtr(errorArray1)->ba_element);
    short *__t;

    bzero(errorArray1, (__w+2) * 2);

    __bitCnt = 8;
    for (__y=0; __y<__h; __y++) {
        __nextDst = __dstIdx + __bytesPerOutRow;
        __nextSrc = __srcIdx + __bytesPerRow;

        __byte = 0;

        __t = __errorArray;
        __errorArray = __errorArray1;
        __errorArray1 = __t;
        bzero(errorArray1, (__w+2) * 2);

        for (__x=0; __x<__w; __x++) {
            __grey = (__bytes[__srcIdx] * 3)           /* 0.3*r + 0.6*g + b -> 0..2550 */
                     + (__bytes[__srcIdx+1] * 6)
                     + __bytes[__srcIdx+2];   
            __grey = __grey / 10;                      /* 0 .. 255 */

            __pixel = __greyMap1[__grey];            /* 0..(greyLevels-1) */
            __err = __greyMap2[__grey];              /* 0.. 255 - error) */
            __err += __errorArray[__x+1];

            if (__err > 127) {                        /* dither says: next pixel */
               if ( __pixel != __greyLevels)
                    __pixel++;
                __err = __err - 255;
            } else {
            }
            if (__err) {
                __e16 = __err >> 4;
                __eR = __e16 * 7;
                __eRB = __e16 * 1;
                __eB = __e16 * 5;
                __eLB = __err - __eR - __eRB - __eB;
                
                __errorArray [__x+1+1] += __eR;
                __errorArray1[__x+1+1] += __eRB;
                __errorArray1[__x+1  ] += __eB;
                __errorArray1[__x+1-1] += __eLB;
            }

            __srcIdx += 3;

            __byte = (__byte << __depth) | __pixel;

            __bitCnt = __bitCnt - __depth;
            if (__bitCnt == 0) {
                __outBits[__dstIdx] = __byte;
                __dstIdx++;
                __byte = 0;
                __bitCnt = 8;
            }
        }

        if (__bitCnt != 8) {
            __byte = __byte << __bitCnt;
            __outBits[__dstIdx] = __byte;
            __bitCnt = 8;
        }

        __srcIdx = __nextSrc;
        __dstIdx = __nextDst;
    }
%}.

    ^ outBits

    "Created: 10.6.1996 / 13:28:22 / cg"
    "Modified: 10.6.1996 / 15:09:07 / cg"

!

floydSteinbergDitheredMonochromeBits
    "return the bitmap for a dithered monochrome bitmap from the image.
     Redefined to make use of knowing that pixels are 24 bit r/g/b"


    ^ self floydSteinbergDitheredGrayBitsDepth:1

    "Created: 10.6.1996 / 22:55:59 / cg"
!

orderedDitheredGrayBitsWithDitherMatrix:ditherMatrix ditherWidth:dW depth:depth
    "return the bitmap for a dithered depth-bitmap from the image;
     with a constant ditherMatrix, this can be used for thresholding.
     Redefined to make use of knowing that pixels are 24-bit values."

    |f dH nDither v range  
     greyMap1 greyMap2 greyLevels outBits
     bytesPerOutRow  "{Class: SmallInteger }"
     bytesPerRow     "{Class: SmallInteger }"
     w               "{Class: SmallInteger }"
     h               "{Class: SmallInteger }"|

    photometric ~~ #rgb ifTrue:[
        self error:'invalid format'.
        ^ nil
    ].

    nDither := ditherMatrix size.
    dH := nDither / dW.

    w := width.
    h := height.

    greyLevels := 1 bitShift:depth.
    bytesPerRow := self bytesPerRow.

    bytesPerOutRow := (w * depth + 7) // 8.
    outBits := ByteArray uninitializedNew:(bytesPerOutRow * h).
    (outBits isNil or:[bytes isNil]) ifTrue:[
        ^ nil
    ].

    greyMap1 := Array new:256.
    greyMap2 := Array new:256.
    range := greyLevels-1.
    1 to:256 do:[:i |
        v := (range / 255 * (i-1)).
        greyMap1 at:i put:v.
        greyMap2 at:i put:v.
    ].

    greyMap1 := (greyMap1 collect:[:b | b isNil ifTrue:[
                                            0
                                        ] ifFalse:[
                                            b truncated
                                        ]
                                  ]) asByteArray.      

    greyMap2 := (greyMap2 collect:[:el | 
                                        el isNil ifTrue:[
                                            0
                                        ] ifFalse:[
                                            ((el - el truncated)  "/ the error (0..1)
                                            * nDither) rounded
                                        ]]) asByteArray.
%{
    int __dW = __intVal(dW);
    int __dH = __intVal(dH);
    int __byte;
    int __nDither = __intVal(nDither);
    int __dT, __dO;
    int __depth = __intVal(depth);
    int __dstIdx = 0;
    int __srcIdx = 0;
    int __bitCnt;
    int __grey;
    int __w = __intVal(w);
    int __h = __intVal(h);
    int __x;
    int __y;
    int __oX, __oY, __dY;
    int __nextDst;
    int __nextSrc;
    int __bytesPerRow = __intVal(bytesPerRow);
    int __bytesPerOutRow = __intVal(bytesPerOutRow);
    int __pixel;

    unsigned char *__outBits = __ByteArrayInstPtr(outBits)->ba_element;
    unsigned char *__ditherMatrix = __ByteArrayInstPtr(ditherMatrix)->ba_element;
    unsigned char *__bytes = __ByteArrayInstPtr(__INST(bytes))->ba_element;
    unsigned char *__greyMap1 = __ByteArrayInstPtr(greyMap1)->ba_element;
    unsigned char *__greyMap2 = __ByteArrayInstPtr(greyMap2)->ba_element;

    __oY = __dY = 0;
    for (__y=0; __y<__h; __y++) {
        __nextDst = __dstIdx + __bytesPerOutRow;
        __nextSrc = __srcIdx + __bytesPerRow;

        __byte = 0;
        __bitCnt = 8;

        __oX = 0;

        for (__x=0; __x<__w; __x++) {
            __grey = (__bytes[__srcIdx] * 3)           /* 0.3*r + 0.6*g + b -> 0..2550 */
                     + (__bytes[__srcIdx+1] * 6)
                     + __bytes[__srcIdx+2];   
            __grey = __grey / 10;                      /* 0 .. 255 */

            __pixel = __greyMap1[__grey];            /* 0..(greyLevels-1) */
            __dO    = __greyMap2[__grey];            /* 0.. nDither-1) */
            __dT = __ditherMatrix[__dY + __oX];

            if (__dO > __dT)                         /* dither says: next pixel */
                __pixel++;

            __srcIdx += 3;

            __oX++;
            if (__oX == __dW) __oX = 0;

            __byte = (__byte << __depth) | __pixel;

            __bitCnt = __bitCnt - __depth;
            if (__bitCnt == 0) {
                __outBits[__dstIdx] = __byte;
                __dstIdx++;
                __byte = 0;
                __bitCnt = 8;
            }
        }

        if (__bitCnt != 8) {
            __byte = __byte << __bitCnt;
            __outBits[__dstIdx] = __byte;
        }

        __oY++; __dY += __dW;
        if (__oY == __dH) {
            __oY = 0;
            __dY = 0;
        }

        __srcIdx = __nextSrc;
        __dstIdx = __nextDst;
    }
%}.

    ^ outBits

    "
     |i|

     i := Image fromFile:'bitmaps/granite.tiff'.
     i asOrderedDitheredMonochromeImage inspect.
     i asOrderedDitheredDepth2GrayImage inspect.
     i asOrderedDitheredDepth4GrayImage inspect.
     i asOrderedDitheredDepth8GrayImage inspect.
    "

    "Created: 7.6.1996 / 10:48:06 / cg"
    "Modified: 7.6.1996 / 11:08:50 / cg"
!

orderedDitheredMonochromeBitsWithDitherMatrix:ditherMatrix ditherWidth:dW
    "return the dithered monochrome bits for the receiver image;
     with a constant ditherMatrix, this can be used for thresholding.
     Redefined to make use of knowing that pixels are 24-bit values."

    |f dH nDither   
     greyMap monoBits
     bytesPerMonoRow "{Class: SmallInteger }"
     bytesPerRow     "{Class: SmallInteger }"
     w               "{Class: SmallInteger }"
     h               "{Class: SmallInteger }"|

    photometric ~~ #rgb ifTrue:[
        self error:'invalid format'.
        ^ nil
    ].

    nDither := ditherMatrix size.
    dH := nDither / dW.

    w := width.
    h := height.

    bytesPerRow := self bytesPerRow.

    bytesPerMonoRow := w + 7 // 8.
    monoBits := ByteArray uninitializedNew:(bytesPerMonoRow * h).
    (monoBits isNil or:[bytes isNil]) ifTrue:[
        ^ nil
    ].

%{
    int __dW = __intVal(dW);
    int __dH = __intVal(dH);
    int __byte;
    int __nDither = __intVal(nDither);
    int __dT;
    int __dstIdx = 0;
    int __srcIdx = 0;
    int __bitCnt;
    int __grey;
    int __w = __intVal(w);
    int __h = __intVal(h);
    int __x;
    int __y;
    int __oX, __oY, __dY;
    int __nextDst;
    int __nextSrc;
    int __bytesPerRow = __intVal(bytesPerRow);
    int __bytesPerMonoRow = __intVal(bytesPerMonoRow);

    unsigned char *__monoBits = __ByteArrayInstPtr(monoBits)->ba_element;
    unsigned char *__ditherMatrix = __ByteArrayInstPtr(ditherMatrix)->ba_element;
    unsigned char *__bytes = __ByteArrayInstPtr(__INST(bytes))->ba_element;

    __oY = __dY = 0;
    for (__y=0; __y<__h; __y++) {
        __nextDst = __dstIdx + __bytesPerMonoRow;
        __nextSrc = __srcIdx + __bytesPerRow;

        __byte = 0;
        __bitCnt = 8;

        __oX = 0;

        for (__x=0; __x<__w; __x++) {
            __grey = (__bytes[__srcIdx] * 3)           /* 0.3*r + 0.6*g + b -> 0..2550 */
                     + (__bytes[__srcIdx+1] * 6)
                     + __bytes[__srcIdx+2];   
            __grey = __grey * (__nDither+1) / 2550;    /* 0 .. nDither+1 */
            __srcIdx += 3;

            __dT = __ditherMatrix[__dY + __oX];

            __oX++;
            if (__oX == __dW) __oX = 0;

            __byte = __byte << 1;
            if (__grey > __dT) {
                __byte = __byte | 1;                   /* white */
            }

            __bitCnt--;
            if (__bitCnt == 0) {
                __monoBits[__dstIdx] = __byte;
                __dstIdx++;
                __byte = 0;
                __bitCnt = 8;
            }
        }

        if (__bitCnt != 8) {
            __byte = __byte << __bitCnt;
            __monoBits[__dstIdx] = __byte;
        }

        __oY++; __dY += __dW;
        if (__oY == __dH) {
            __oY = 0;
            __dY = 0;
        }

        __srcIdx = __nextSrc;
        __dstIdx = __nextDst;
    }
%}.

    ^ monoBits

    "
     |i f|

     i := Image fromFile:'bitmaps/granite.tiff'.
     f := i asOrderedDitheredMonochromeFormOn:Display.
    "

    "Created: 7.6.1996 / 10:48:06 / cg"
    "Modified: 7.6.1996 / 11:08:50 / cg"
!

threshold8BitGrayBits
    "return the bits for an 8-bit grey image from the receiver.
     Special code, since this is a common case."

    |greyBits
     srcIndex "{ Class: SmallInteger }"
     dstIndex "{ Class: SmallInteger }"|

    greyBits := ByteArray uninitializedNew:(width * height).
%{
    register unsigned char *srcPtr, *dstPtr;
    register __v;
    register i;

    if ((__Class(__INST(bytes)) == ByteArray)
     && (__Class(greyBits) == ByteArray)) {
        srcPtr = __ByteArrayInstPtr(__INST(bytes))->ba_element;
        dstPtr = __ByteArrayInstPtr(greyBits)->ba_element;

        i = __intVal(__INST(height)) * __intVal(__INST(width));

        for (; i > 0; i--) {
            __v = (srcPtr[0] * 3);     /* 3*r + 6*g + b ; 0 .. 2550 */
            __v += (srcPtr[1] * 6);
            __v += srcPtr[2];
            srcPtr += 3;
            __v /= 10;                 /* 0..255 */
            *dstPtr++ = __v ;
        }
    }
%}.
    ^ greyBits

! !

!Depth24Image 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 }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     rVal     "{ Class: SmallInteger }"
     gVal     "{ Class: SmallInteger }"
     bVal     "{ Class: SmallInteger }"
     lastR lastG lastB lastColor|

    photometric ~~ #rgb ifTrue:[
        ^ super colorsAtY:y from:xLow to:xHigh do:aBlock.
    ].

    x1 := xLow.
    x2 := xHigh.

    srcIndex := 1 + (((width * y) + x1) * 3).

    x1 to:x2 do:[:x |
        rVal := bytes at:(srcIndex).
        gVal := bytes at:(srcIndex + 1).
        bVal := bytes at:(srcIndex + 2).
        srcIndex := srcIndex + 3.

        (rVal == lastR and:[gVal == lastG and:[bVal == lastB]]) ifFalse:[
            lastColor := Color redByte:rVal greenByte:gVal blueByte:bVal * 100 / 255.
            lastR := rVal.
            lastG := gVal.
            lastB := bVal.
        ].
        aBlock value:x value:lastColor
    ]

    "Created: 7.6.1996 / 19:12:28 / cg"
    "Modified: 8.6.1996 / 10:16:51 / 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 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.
     Notice that the pixelValue is the r/g/b value packed into an integer
     (r bitShift:16) bitOr:(g bitSHift:8) bitOr:b"

    |srcIndex "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     r        "{ Class: SmallInteger }"
     g        "{ Class: SmallInteger }"
     b        "{ Class: SmallInteger }"|

    x1 := xLow.
    x2 := xHigh.

    srcIndex := 1 + (((width * y) + x1) * 3).

    x1 to:x2 do:[:x |
        r := bytes at:(srcIndex).
        g := bytes at:(srcIndex + 1).
        b := bytes at:(srcIndex + 2).
        srcIndex := srcIndex + 3.
        aBlock value:x value:(((r bitShift:16) bitOr:(g bitShift:8)) bitOr:b)
    ]

    "Created: 7.6.1996 / 19:09:40 / cg"
! !

!Depth24Image methodsFor:'image manipulations'!

negative
    |index newImage newBytes nBytes r g b|

    photometric ~~ #rgb ifTrue:[
        ^ super negative.
    ].
    newImage := self copy.
    nBytes := bytes size.
    newImage bits:(newBytes := ByteArray new:nBytes).
    index := 1.
    [index < nBytes] whileTrue:[
        r := bytes at:index.
        newBytes at:index put:(255-r).
        index := index + 1.
        g := bytes at:index.
        newBytes at:index put:(255-g).
        index := index + 1.
        b := bytes at:index.
        newBytes at:index put:(255-b).
        index := index + 1.
    ].
    ^ newImage

    "Modified: 23.6.1997 / 09:57:19 / cg"
! !

!Depth24Image methodsFor:'magnification'!

hardAntiAliasedMagnifiedBy:scalePoint
    "return a new image magnified by scalePoint, aPoint.
     This interpolates pixels and is therefore slower."

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

    mX := scalePoint x.
    mY := scalePoint y.
    ((mX < 0) or:[mY < 0]) ifTrue:[^ nil].
    ((mX = 1) and:[mY = 1]) ifTrue:[^ self].

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

    bitsPerPixel := self depth.
    newBytesPerRow := ((newWidth * bitsPerPixel) + 7) // 8.
    newBits := ByteArray new: "uninitializedNew:" (newBytesPerRow * newHeight).
    newBits isNil ifTrue:[self halt].

    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.

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

%{
    REGISTER unsigned char *_dstP = __ByteArrayInstPtr(newBits)->ba_element;
    unsigned char *_srcP = __ByteArrayInstPtr(_INST(bytes))->ba_element;
    unsigned char *_srcRowP, *sP;
    int _width3 = __intVal(_INST(width)) * 3;
    int _oldW = __intVal(_INST(width)) - 1;
    int _oldH = __intVal(_INST(height)) - 1;
    int _w = __intVal(newWidth) - 1;
    int _h = __intVal(newHeight) - 1;
    int _row, _col;
    double _mX = __floatVal(mX);
    double _mY = __floatVal(mY);

    for (_row = 0; _row <= _h; _row++) {
        double _srcY;
        double _dY;
        int _sR;

        _srcY = ((double)_row / _mY);
        _sR = (int)_srcY;
        _dY = _srcY - ((double)_sR);
        _srcRowP = _srcP + (_width3 * _sR);

        for (_col = 0; _col <= _w; _col++) {
            unsigned int rHere, gHere, bHere;
            unsigned int rRight, gRight, bRight;
            unsigned int rRightBelow, gRightBelow, bRightBelow;
            unsigned int rBelow, gBelow, bBelow;
            unsigned int _r, _g, _b;
            double wHere, wRight, wRightBelow, wBelow, sumW;
            double _srcX;
            double _dX;
            int _sC;

            _srcX = ((double)_col / _mX);
            _sC = (int)_srcX;
            _dX = _srcX - ((double)_sC);
            sP = _srcRowP + (_sC * 3);
        
            rHere = sP[0];
            gHere = sP[1];
            bHere = sP[2];

            if (_sC < _oldW) {
                rRight = sP[3];
                gRight = sP[4];
                bRight = sP[5];

                if (_sR < _oldH) {
                    rBelow = sP[0+_width3];
                    gBelow = sP[1+_width3];
                    bBelow = sP[2+_width3];
                    rRightBelow = sP[3+_width3];
                    gRightBelow = sP[4+_width3];
                    bRightBelow = sP[5+_width3];
                } else {
                    rRightBelow = rHere;
                    gRightBelow = gHere;
                    bRightBelow = bHere;
                    rBelow = rHere;
                    gBelow = gHere;
                    bBelow = bHere;
                }
            } else {
                rRight = rRightBelow = rHere;
                gRight = gRightBelow = gHere;
                bRight = bRightBelow = bHere;
                if (_sR < _oldH) {
                    rBelow = sP[0+_width3];
                    gBelow = sP[1+_width3];
                    bBelow = sP[2+_width3];
                } else {
                    rBelow = rHere;
                    gBelow = gHere;
                    bBelow = bHere;
                }
            }

            wHere = (1.0 - _dX) * (1.0 - _dY);
            wRight = _dX * (1.0 - _dY);
            wBelow = _dY * (1.0 - _dX);
            wRightBelow = _dX * _dY;
            sumW = wHere + wRight + wBelow + wRightBelow;

            _r = ((rHere * wHere) + (rRight * wRight) + (rBelow * wBelow) + (rRightBelow * wRightBelow)) / sumW;
            _g = ((gHere * wHere) + (gRight * wRight) + (gBelow * wBelow) + (gRightBelow * wRightBelow)) / sumW;
            _b = ((bHere * wHere) + (bRight * wRight) + (bBelow * wBelow) + (bRightBelow * wRightBelow)) / sumW;

            _dstP[0] = _r;
            _dstP[1] = _g;
            _dstP[2] = _b;

            _dstP += 3;
        }
    }
%}.

    ^ newImage

    "
     |i|
     i := Image fromFile:'bitmaps/gifImages/garfield.gif'.
     i hardAntiAliasedMagnifiedBy:2@2
    "
    "
     |i|
     i := Depth24Image width:3 height:3 fromArray:#[ 0 0 0  0 0 0  0 0 0
                                                     0 0 0  255 255 255  0 0 0
                                                     0 0 0  0 0 0  0 0 0].
     i hardAntiAliasedMagnifiedBy:8@8
    "

    "Modified: 2.6.1997 / 12:28:18 / cg"
    "Created: 2.6.1997 / 13:18:53 / cg"
!

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

    |mX mY
     newWidth  "{ Class: SmallInteger }"
     newHeight "{ Class: SmallInteger }"
     w         "{ Class: SmallInteger }"
     h         "{ Class: SmallInteger }"
     newImage newBytes
     value     "{ Class: SmallInteger }"
     srcRowIdx "{ Class: SmallInteger }"
     srcIndex  "{ Class: SmallInteger }"
     dstIndex  "{ Class: SmallInteger }"
     newMask|

    mX := scalePoint x.
    mY := scalePoint y.
    ((mX < 0) or:[mY < 0]) ifTrue:[^ nil].
    ((mX = 1) and:[mY = 1]) ifTrue:[^ self].

    newWidth := (width * mX) truncated.
    newHeight := (height * mY) truncated.
    newBytes := ByteArray uninitializedNew:(newWidth * 3 * newHeight).

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

    newImage := self species new.
    newImage 
        width:newWidth 
        height:newHeight 
        photometric:photometric 
        samplesPerPixel:samplesPerPixel 
        bitsPerSample:#(8 8 8) 
        colorMap:nil
        bits:newBytes
        mask:newMask.

    "walk over destination image fetching pixels from source image"

    mY := mY asFloat.
    mX := mX asFloat.
%{
    REGISTER unsigned char *_dstP = _ByteArrayInstPtr(newBytes)->ba_element;
    unsigned char *_srcP = _ByteArrayInstPtr(_INST(bytes))->ba_element;
    unsigned char *_srcRowP, *sP;
    int _width3 = _intVal(_INST(width)) * 3;
    int _w = _intVal(newWidth) - 1;
    int _h = _intVal(newHeight) - 1;
    int _row, _col;
    double _mX = _floatVal(mX);
    double _mY = _floatVal(mY);

    for (_row = 0; _row <= _h; _row++) {
        _srcRowP = _srcP + (_width3 * (int)((double)_row / _mY));
        for (_col = 0; _col <= _w; _col++) {
            sP = _srcRowP + (((int)((double)_col / _mX)) * 3);
            _dstP[0] = sP[0];
            _dstP[1] = sP[1];
            _dstP[2] = sP[2];
            _dstP += 3;
        }
    }
%}
.
"   the above C-code is equivalent to:

    dstIndex := 1.
    w := newWidth - 1.
    h := newHeight - 1.
    0 to:h do:[:row |
        srcRowIdx := (width * 3 * (row // mY)) + 1.
        0 to:w do:[:col |
            srcIndex := srcRowIdx + ((col // mX) * 3).
            value := bytes at:srcIndex.
            newBytes at:dstIndex put:value.
            value := bytes at:(srcIndex + 1).
            newBytes at:(dstIndex + 1) put:value.
            value := bytes at:(srcIndex + 2).
            newBytes at:(dstIndex + 2) put:value.
            dstIndex := dstIndex + 3
        ]
    ].
"
    ^ newImage
!

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 byte1, byte2, byte3;
    int _pixels;
    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);

	while (_pixels--) {
	    byte1 = *srcP;
	    byte2 = *(srcP+1);
	    byte3 = *(srcP+2);
	    srcP += 3;
	    for (i=_mag; i>0; i--) {
		*dstP = byte1;
		*(dstP+1) = byte2;
		*(dstP+2) = byte3;
		dstP += 3;
	    }
	}
	RETURN (self);
    }
%}
.
    self primitiveFailed
! !

!Depth24Image methodsFor:'queries'!

bitsPerPixel
    "return the number of bits per pixel"

    ^ 24
!

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

    ^  width * 24
!

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

    bitsPerSample notNil ifTrue:[^ bitsPerSample].
    ^ #(8 8 8)

    "Modified: 10.6.1996 / 18:02:33 / cg"
!

blueBitsOf:pixel
    ^ pixel bitAnd:16rFF.

    "Created: 8.6.1996 / 09:56:20 / cg"
!

blueComponentOf:pixel
    ^ (100.0 / 255.0) * (pixel bitAnd:16rFF)

    "Created: 8.6.1996 / 08:42:44 / cg"
    "Modified: 8.6.1996 / 09:57:41 / cg"
!

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

    ^ width * 3
!

greenBitsOf:pixel
    ^ (pixel bitShift:-8) bitAnd:16rFF.

    "Modified: 8.6.1996 / 08:56:28 / cg"
    "Created: 8.6.1996 / 09:56:30 / cg"
!

greenComponentOf:pixel
    ^ (100.0 / 255.0) * (pixel bitShift:-8) bitAnd:16rFF.

    "Created: 8.6.1996 / 08:42:37 / cg"
    "Modified: 8.6.1996 / 09:57:32 / cg"
!

redBitsOf:pixel
    ^ (pixel bitShift:-16) bitAnd:16rFF.

    "Modified: 8.6.1996 / 08:56:31 / cg"
    "Created: 8.6.1996 / 09:56:39 / cg"
!

redComponentOf:pixel
    ^ (100.0 / 255.0) * (pixel bitShift:-16) bitAnd:16rFF.

    "Created: 8.6.1996 / 08:42:25 / cg"
    "Modified: 8.6.1996 / 09:57:23 / cg"
!

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

    samplesPerPixel notNil ifTrue:[^ samplesPerPixel].
    ^ 3

    "Modified: 10.6.1996 / 18:03:09 / cg"
! !

!Depth24Image class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Depth24Image.st,v 1.56 1997-07-22 10:09:50 cg Exp $'
! !