Depth8Image.st
author Claus Gittinger <cg@exept.de>
Mon, 17 Jun 1996 14:48:33 +0200
changeset 875 b23541f72152
parent 859 34268959162d
child 880 8b2c06ed438d
permissions -rw-r--r--
added floydSteinberg dithering for pseudo-8 images

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

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

    [author:]
        Claus Gittinger

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

!Depth8Image class methodsFor:'queries'!

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

    ^ 8

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

!Depth8Image methodsFor:'accessing'!

atX:x y:y
    "retrieve a pixel at x/y; return a color.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel"

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

    index := (width * y) + 1 + x.
    value := bytes at:index.

    photometric == #whiteIs0 ifTrue:[
        ^ Color gray:100 - (100 / 255 * value)
    ].
    photometric == #blackIs0 ifTrue:[
        ^ Color gray:(100 / 255 * value)
    ].
    photometric ~~ #palette ifTrue:[
        ^ self colorFromValue:value
    ].
    index := value + 1.
    ^ colorMap at:index

    "Modified: 8.6.1996 / 10:52:48 / cg"
!

atX:x y:y putValue:aPixelValue
    "set the pixel at x/y to aPixelValue.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel"

    |index "{ Class: SmallInteger }"|

    index := (width * y) + 1 + x.
    bytes at:index put:aPixelValue.
!

valueAtX:x y:y
    "retrieve a pixel at x/y; return a pixelValue.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel"

    |index "{ Class: SmallInteger }"|

    index := (width * y) + 1 + x.
    ^ bytes at:index.
! !

!Depth8Image methodsFor:'converting palette images'!

asGray8FormOn:aDevice
    "return an 8-bit greyForm from the 8-bit receiver image.
     Redefined, since only a translation has to be done here."

    |greyBits map
     mapSize "{ Class: SmallInteger }"|

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

    map := ByteArray uninitializedNew:256.

    1 to:256 do:[:i |
        map at:i put:((self colorFromValue:(i-1)) brightness * 255) rounded
    ].

"/    mapSize := colorMap size.
"/
"/    1 to:mapSize do:[:i |
"/        map at:i put:((colorMap at:i) brightness * 255) rounded
"/    ].

    bytes expandPixels:8         "xlate only"
                width:width 
               height:height
                 into:greyBits
              mapping:map.

    ^ self makeDeviceGrayPixmapOn:aDevice depth:8 fromArray:greyBits

    "Modified: 10.6.1996 / 20:10:14 / cg"
    "Created: 14.6.1996 / 15:23:09 / cg"
!

asGrayFormOn:aDevice
    "get a gray device form.
     Redefined, since we can do it with simple translate, 
     if the depth matches my depth."

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

    "Created: 10.6.1996 / 18:51:19 / cg"
    "Modified: 10.6.1996 / 18:54:36 / cg"
!

paletteImageAsPseudoFormOn:aDevice
    "return a pseudoForm from the palette picture. The main work is
     in color reduction, when not all colors can be aquired."

    |pseudoBits f gcRound has8BitImage deviceDepth
     imgMap newImage pxl dColors
     usedColors usageCounts maxIndex map
     fit scale lastOK error 
     div 
     bitsPerRGB "{Class: SmallInteger }"
     shift      "{Class: SmallInteger }"
     m          "{Class: SmallInteger }" |

    Color fixColors notNil ifTrue:[
        f := self
               asFloydSteinbergDitheredDepth8FormOn:aDevice 
               colors:Color fixColors 
               nRed:Color numFixRed
               nGreen:Color numFixGreen
               nBlue:Color numFixBlue.
        f notNil ifTrue:[^ f].
    ].

    "find used colors"

    usedColors := bytes usedValues.    "gets us an array filled with used values"
                                       "(could use bytes asBag)"
    maxIndex := usedColors max + 1.

    usedColors size > 20 ifTrue:[
        ('D8IMAGE: allocating ' , usedColors size printString , ' colors ...') infoPrintNL.
    ].

    "sort by usage"
    usageCounts := bytes usageCounts.
    usageCounts := usedColors asArray collect:[:clr | usageCounts at:(clr + 1)].
    usageCounts sort:[:a :b | a > b] with:usedColors.

    "allocate the colors (in order of usage count)"

    imgMap := Array new:maxIndex.

    "
     first, try to get the exact colors ...
    "
    bitsPerRGB := aDevice bitsPerRGB.
    shift := (8 - bitsPerRGB) negated.
    m := (1 bitShift:bitsPerRGB) - 1.
    div := m asFloat.

    fit := true.
    scale := 100.0 / div.       "to scale 0..255 into 0.0 .. 100.0"
    lastOK := 0.
    gcRound := 0.

    usedColors do:[:aColorIndex |
        |devColor color
         r        "{Class: SmallInteger }"
         g        "{Class: SmallInteger }"
         b        "{Class: SmallInteger }"
         mapIndex "{Class: SmallInteger }"|

        fit ifTrue:[
            mapIndex := aColorIndex + 1.
            color := colorMap at:mapIndex.
            (color colorId notNil 
            and:[color device == aDevice]) ifTrue:[
                "wow - an immediate hit"
                devColor := color
            ] ifFalse:[
                devColor := color exactOn:aDevice.
                devColor isNil ifTrue:[
                    "
                     could not allocate color - on the first round, do a GC to flush 
                     unused colors - this may help if some colors where locked by 
                     already free images.
                    "
                    gcRound == 0 ifTrue:[
                        ObjectMemory scavenge; finalize.
                        devColor := color exactOn:aDevice.
                        gcRound := 1
                    ].
                    devColor isNil ifTrue:[
                        gcRound == 1 ifTrue:[
                            CollectGarbageWhenRunningOutOfColors ifTrue:[
                                'D8IMAGE: force GC for possible color reclamation.' infoPrintNL.
                                ObjectMemory incrementalGC; finalize.
                                devColor := color exactOn:aDevice.
                            ].    
                            gcRound := 2
                        ]
                    ]
                ].
            ].
            (devColor notNil and:[devColor colorId notNil]) ifTrue:[
                imgMap at:mapIndex put:devColor.
                lastOK := lastOK + 1.
            ] ifFalse:[
                fit := false
            ]
        ]
    ].

    fit ifFalse:[
"/        |tree|
"/
"/        "/ first, create an octTree containing colors which we got ...
"/        tree := ColorOctree new.
"/
"/        usedColors from:1 to:lastOK do:[:aColorIndex |
"/            tree insert:(colorMap at:aColorIndex + 1).
"/        ].
"/
"/        "/ then, remap remaining, using nearest from those already allocated
"/
"/        usedColors from:(lastOK+1) to:(usedColors size) do:[:aColorIndex |      
"/            |mapIndex|
"/
"/            mapIndex := aColorIndex + 1.
"/            imgMap at:mapIndex put:(tree findBest:(colorMap at:mapIndex))
"/        ].

        fit ifFalse:[
            ('D8IMAGE: got %1 exact colors (out of %2)' bindWith:lastOK with:usedColors size) infoPrintCR.
            DitherAlgorithm == #floydSteinberg ifTrue:[
                dColors := colorMap asArray collect:[:clr | clr isNil ifTrue:[clr]
                                                              ifFalse:[clr nearestOn:aDevice]].
                dColors := dColors select:[:clr | clr notNil].
                dColors := dColors asSet.
                dColors addAll:Color ditherColors.
                dColors := dColors asArray.

"/                ^ self asFloydSteinbergDitheredPseudoFormUsing:(Color allocatedColorsOn:aDevice) on:aDevice
"/                ^ self asFloydSteinbergDitheredPseudoFormUsing:(imgMap , Color ditherColors) on:aDevice
                ^ self asFloydSteinbergDitheredPseudoFormUsing:dColors on:aDevice
            ]
        ].

        "
         again, this time allow wrong colors (loop while increasing allowed error)
        "
        error := 1.
        [fit] whileFalse:[
            fit := true.
            usedColors from:(lastOK+1) to:(usedColors size) do:[:aColorIndex |
                |devColor color
                 r        "{Class: SmallInteger }"
                 g        "{Class: SmallInteger }"
                 b        "{Class: SmallInteger }"
                 mapIndex "{Class: SmallInteger }"
                 rMask    "{Class: SmallInteger }"
                 gMask    "{Class: SmallInteger }"
                 bMask    "{Class: SmallInteger }"|

                fit ifTrue:[
                    gMask := bMask := rMask := m.

                    mapIndex := aColorIndex + 1.
                    color := colorMap at:mapIndex.
                    r := (color red * 255 / 100.0) rounded.
                    g := (color green * 255 / 100.0) rounded.
                    b := (color blue * 255 / 100.0) rounded.

                    color := Color red:((r bitShift:shift) bitAnd:rMask) * scale
                                 green:((g bitShift:shift) bitAnd:gMask) * scale
                                  blue:((b bitShift:shift) bitAnd:bMask) * scale.

                    (color colorId notNil 
                    and:[color device == aDevice]) ifTrue:[
                        "wow - an immediate hit"
                        devColor := color.
                    ] ifFalse:[
                        devColor := color nearestOn:aDevice.
                        (devColor notNil and:[(devColor deltaFrom:color) > error]) ifTrue:[
                            devColor := nil
                        ].
                        devColor isNil ifTrue:[
                            "
                             no free color - on the first round, do a GC to flush unused
                             colors - this may help if some colors where locked by already
                             free images.
                            "
                            gcRound == 0 ifTrue:[
                                ObjectMemory scavenge; finalize.
                                devColor := color nearestOn:aDevice.
                                (devColor notNil and:[(devColor deltaFrom:color) > error]) ifTrue:[
                                    devColor := nil
                                ].
                                gcRound := 1
                            ].
                            devColor isNil ifTrue:[
                                gcRound == 1 ifTrue:[
                                    CollectGarbageWhenRunningOutOfColors ifTrue:[
                                        'D8IMAGE: force GC for possible color reclamation.' infoPrintNL.
                                        ObjectMemory incrementalGC; finalize.
                                        devColor := color nearestOn:aDevice.
                                        (devColor notNil and:[(devColor deltaFrom:color) > error]) ifTrue:[
                                            devColor := nil
                                        ].
                                    ].
                                    gcRound := 2
                                ]
                            ]
                        ].
                    ].
                    (devColor notNil and:[devColor colorId notNil]) ifTrue:[
                        imgMap at:mapIndex put:devColor.
                        lastOK := lastOK + 1.
                    ] ifFalse:[
                        fit := false
                    ]
                ].
            ].

            fit ifTrue:[
                ('D8IMAGE: remaining colors with error <= %1' bindWith:error) infoPrintCR.
            ].

            error := error * 2.
            error > 100 ifTrue:[
                "
                 break out, if the error becomes too big.
                "
                'D8IMAGE: hard color allocation problem - revert to b&w for remaining colors' infoPrintNL.
                "
                 map to b&w as a last fallback.
                 (should really do a dither here)
                "
                usedColors from:(lastOK+1) to:(usedColors size) do:[:aColorIndex |
                    |color
                     mapIndex "{ Class: SmallInteger }"|

                    mapIndex := aColorIndex + 1.
                    color := colorMap at:mapIndex.
                    color brightness > 0.4 ifTrue:[
                        color := Color white.
                    ] ifFalse:[
                        color := Color black.
                    ].
                    imgMap at:mapIndex put:(color on:aDevice).
                ].
                fit := true.
            ]
        ].

        error > 10 ifTrue:[
            'D8IMAGE: not enough colors for a reasonable image' infoPrintNL
        ] ifFalse:[
            'D8IMAGE: not enough colors for exact picture' infoPrintNL.
        ]
    ].

    "
     create translation map (from image colors to allocated colorIds)
    "
    map := ByteArray new:256.
    1 to:imgMap size do:[:i |
        |clr|

        (clr := imgMap at:i) notNil ifTrue:[
            map at:i put:clr colorId
        ]
    ].

    "
     does the device support 8-bit images ?
    "
    deviceDepth := aDevice depth.
    deviceDepth == 8 ifTrue:[
        has8BitImage := true.
    ] ifFalse:[
        has8BitImage := false.
        aDevice supportedImageFormats do:[:fmt |
            (fmt at:#bitsPerPixel) == 8 ifTrue:[
                has8BitImage := true.
            ]
        ]
    ].

    "
     finally, create a form on the device and copy (& translate)
     the pixel values
    "
    has8BitImage ifTrue:[
        pseudoBits := ByteArray uninitializedNew:(width * height).

        bytes expandPixels:8         "xlate only"
                    width:width 
                   height:height
                     into:pseudoBits
                  mapping:map.

        map := nil.

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

    "
     slow fall back: convert into appropriate depth image,
     by looping over each pixel individually
    "
    newImage := (Image implementorForDepth:deviceDepth) new.
    newImage width:width.
    newImage height:height.
    newImage bits:(ByteArray uninitializedNew:(height * newImage bytesPerRow)).

    0 to:height-1 do:[:row |
        0 to:width-1 do:[:col |
            pxl := self valueAtX:col y:row.
            newImage atX:col y:row putValue:(map at:pxl)
        ]
    ].

    f := Form width:width height:height depth:deviceDepth on:aDevice.
    f isNil ifTrue:[^ nil].
    f colorMap:imgMap. 
    f initGC.

    aDevice drawBits:(newImage bits) depth:deviceDepth width:width height:height
                   x:0 y:0
                into:(f id) x:0 y:0 
               width:width height:height with:(f gcId).

    ^ f

    "Modified: 17.6.1996 / 13:25:50 / cg"
! !

!Depth8Image methodsFor:'dither helpers'!

orderedDitheredBitsWithDitherMatrix: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 8-bit values."

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

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

    w := width.
    h := height.

    greyLevels := 1 bitShift:depth.
    pixelsPerByte := 8 / depth.

    bytesPerRow := self bytesPerRow.

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

    greyMap1 := self greyMapForRange:(greyLevels-1).                    "/ the pixels
    greyMap1 := (greyMap1 collect:[:b | b isNil ifTrue:[
                                            0
                                        ] ifFalse:[
                                            b truncated
                                        ]
                                  ]) asByteArray.      

    greyMap2 := self greyMapForRange:(greyLevels-1).
    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 __dT, __dO;
    int __depth = __intVal(depth);
    int __dstIdx = 0;
    int __srcIdx = 0;
    int __bitCnt;
    int __grey, __pixel;
    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);

    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++];            /* 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++;

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

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 8-bit values."

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

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

    greyMap := self greyByteMapForRange:nDither.

%{
    int __dW = __intVal(dW);
    int __dH = __intVal(dH);
    int __byte;
    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);

    char *__monoBits = __ByteArrayInstPtr(monoBits)->ba_element;
    unsigned char *__ditherMatrix = __ByteArrayInstPtr(ditherMatrix)->ba_element;
    unsigned char *__bytes = __ByteArrayInstPtr(__INST(bytes))->ba_element;
    unsigned char *__greyMap = __ByteArrayInstPtr(greyMap)->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=__w; __x>0; __x--) {
            __grey = __bytes[__srcIdx];   /* 0..255 */
            __srcIdx++;

            __grey = __greyMap[__grey];
            __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/claus.gif'.
     f := i asOrderedDitheredMonochromeFormOn:Display.


     |i f|

     i := Image fromFile:'bitmaps/garfield.gif'.
     f := i asOrderedDitheredMonochromeFormOn:Display.


     |i f|

     i := (Image fromFile:'bitmaps/PasteButton.tiff') magnifiedBy:10.
     f := i asOrderedDitheredMonochromeFormOn:Display.


     |i f|

     i := (Image fromFile:'bitmaps/blue-ball.gif') magnifiedBy:1.
     f := i asOrderedDitheredMonochromeFormOn:Display.
    "

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

!Depth8Image 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 }"
     value    "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     color colorArray scale gr|

    x1 := xLow.
    x2 := xHigh.
    srcIndex := (width * y) + 1 + x1.

    colorArray := Array new:256.

    photometric == #blackIs0 ifTrue:[
        scale := 100.0 / 255.0.

        x1 to:x2 do:[:x |
            value := bytes at:srcIndex.
            srcIndex := srcIndex + 1.

            color := colorArray at:value+1.
            color isNil ifTrue:[
                color := Color gray:(value * scale).
                colorArray at:value+1 put:color
            ].
            aBlock value:x value:color
        ].
        ^ self
    ].

    photometric == #whiteIs0 ifTrue:[
        scale := 100.0 / 255.0.

        x1 to:x2 do:[:x |
            value := bytes at:srcIndex.
            srcIndex := srcIndex + 1.

            color := colorArray at:value+1.
            color isNil ifTrue:[
                gr := 255 - value.
                color := Color gray:(gr * scale).
                colorArray at:value+1 put:color
            ].
            aBlock value:x value:color
        ].
        ^ self
    ].

    photometric ~~ #palette ifTrue:[
        x1 to:x2 do:[:x |
            value := bytes at:srcIndex.
            srcIndex := srcIndex + 1.

            color := colorArray at:value+1.
            color isNil ifTrue:[
                color := self colorFromValue:value.
                colorArray at:value+1 put:color
            ].
            aBlock value:x value:color
        ].
        ^ self
    ].

    colorArray := colorMap.

    x1 to:x2 do:[:x |
        value := bytes at:srcIndex.
        srcIndex := srcIndex + 1.

        color := colorArray at:(value+1).
        aBlock value:x value:color
    ]

    "Created: 7.6.1996 / 19:12:35 / cg"
    "Modified: 10.6.1996 / 10:32:07 / 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."

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

    x1 := xLow.
    x2 := xHigh.
    srcIndex := (width * y) + 1 + x1.

    x1 to:x2 do:[:x |
        pixelValue := bytes at:srcIndex.
        srcIndex := srcIndex + 1.
        aBlock value:x value:pixelValue 
    ]

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

!Depth8Image methodsFor:'image manipulations'!

flipHorizontal
    "inplace horizontal flip"

    |index  "{Class: SmallInteger }"
     h      "{Class: SmallInteger }"
     w      "{Class: SmallInteger }"
     buffer |

    w := width - 1.
    h := height - 1.

    buffer := ByteArray new:width.

    index := 1.
    0 to:h do:[:row |
	buffer replaceFrom:1 to:width with:bytes startingAt:index.
	buffer reverse.
	bytes replaceFrom:index to:index+w with:buffer startingAt:1.
	index := index + w + 1.
    ].
    "flush device info"
    self restored
!

hardMagnifiedBy:extent
    "return a new image magnified by extent, 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 }"|

    mX := extent x.
    mY := extent 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 * newHeight).

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

    "walk over destination image fetching pixels from source image"

    mY := mY asFloat.
    mX := mX asFloat.
%{
    unsigned char *_dstP = _ByteArrayInstPtr(newBytes)->ba_element;
    unsigned char *_srcP = _ByteArrayInstPtr(_INST(bytes))->ba_element;
    unsigned char *_srcRowP;
    int _width = _intVal(_INST(width));
    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 + (_width * (int)((double)_row / _mY));
	for (_col = 0; _col <= _w; _col++) {
	    *_dstP++ = _srcRowP[(int)((double)_col / _mX)];
	}
    }
%}
.
"/   the above C-code is equivalent to:
"/
"/    dstIndex := 1.
"/    w := newWidth - 1.
"/    h := newHeight - 1.
"/    0 to:h do:[:row |
"/        srcRowIdx := (width * (row // mY)) + 1.
"/        0 to:w do:[:col |
"/            srcIndex := srcRowIdx + (col // mX).
"/            value := bytes at:srcIndex.
"/            newBytes at:dstIndex put:value.
"/            dstIndex := dstIndex + 1
"/        ]
"/    ].
"/

    ^ newImage
!

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

    "magnify a single pixel row - can only magnify by integer factors.
     Specially tuned for factors 2,3 and 4."

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

	switch (_mag) {
	    case 1:
		break;

	    case 2:
		/* special code for common case */
		while (_pixels--) {
		    _byte = *srcP++;
		    *dstP++ = _byte;
		    *dstP++ = _byte;
		}
		break;

	    case 3:
		/* special code for common case */
		while (_pixels--) {
		    _byte = *srcP++;
		    *dstP++ = _byte;
		    *dstP++ = _byte;
		    *dstP++ = _byte;
		}
		break;

	    case 4:
		/* special code for common case */
		while (_pixels--) {
		    _byte = *srcP++;
		    *dstP++ = _byte;
		    *dstP++ = _byte;
		    *dstP++ = _byte;
		    *dstP++ = _byte;
		}
		break;

	    default:
		while (_pixels--) {
		    _byte = *srcP++;
		    for (i=_mag; i>0; i--)
			*dstP++ = _byte;
		}
		break;
	}
	RETURN (self);
    }
%}
.
    self primitiveFailed
! !

!Depth8Image methodsFor:'private'!

dither1PlaneUsingMap:map on:aDevice
    "a helper for dithering palette and greyscale images"

    |f
     patterns formBytes
     pixel0bytes pixel1bytes
     clr ditherPattern
     nColors       "{Class: SmallInteger }"
     w             "{Class: SmallInteger }"
     h             "{Class: SmallInteger }"|

    nColors := map size.
    w := width.
    h := height.

    formBytes := ByteArray uninitializedNew:(w + 7 // 8) * h.
    patterns := Array new:nColors.
    pixel0bytes := ByteArray uninitializedNew:nColors.
    pixel1bytes := ByteArray uninitializedNew:nColors.

    "
     extract dither patterns and values to use for 1/0 bits
     in those from the dithercolors
    "
    1 to:nColors do:[:i |
	clr := (map at:i) on:aDevice.
	ditherPattern := clr ditherForm.

	ditherPattern isNil ifTrue:[
	    patterns at:i put:#[2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111].
	    pixel0bytes at:i put:clr colorId.
	    pixel1bytes at:i put:clr colorId
	] ifFalse:[
	    patterns at:i put:(ditherPattern bits).
	    pixel0bytes at:i put:(ditherPattern colorMap at:1) colorId.
	    pixel1bytes at:i put:(ditherPattern colorMap at:2) colorId.
	].
    ].

%{
    unsigned char *_srcP, *_dstP;
    OBJ _patternBytes;
    unsigned char _mask = 0x80;
    unsigned char _outBits = 0;
    unsigned char _last, _v, _patternBits, _p0, _p1;
    int _h, _w;
    int _patternOffset = 0;

    _srcP = _ByteArrayInstPtr(_INST(bytes))->ba_element;
    _dstP = _ByteArrayInstPtr(formBytes)->ba_element;
    for (_h = _intVal(h); _h; _h--) {
	_last = -1;
	for (_w = _intVal(w); _w; _w--) {
	    _v = *_srcP++;
	    if (_v != _last) {
		_patternBytes = _ArrayInstPtr(patterns)->a_element[_v];
		if (__isByteArray(_patternBytes)) {
		    _patternBits = _ByteArrayInstPtr(_patternBytes)->ba_element[_patternOffset];
		} else if (__isArray(_patternBytes)) {
		    _patternBits = _intVal(_ArrayInstPtr(_patternBytes)->a_element[_patternOffset]);
		}
		_p0 = _ByteArrayInstPtr(pixel0bytes)->ba_element[_v];
		_p1 = _ByteArrayInstPtr(pixel1bytes)->ba_element[_v];
		_last = _v;
	    }
	    _outBits <<= 1;
	    if (_patternBits & _mask)
		_outBits |= _p1;
	    else
		_outBits |= _p0;
	    _mask >>= 1;
	    if (_mask == 0) {
		_mask = 0x80;
		*_dstP++ = _outBits;
		_outBits = 0;
	    }
	}
	if (_mask != 0x80) {
	    while (_mask != 0) {
		_outBits <<= 1;
		_mask >>= 1;
	    }
	    *_dstP++ = _outBits;
	    _mask = 0x80;
	    _outBits = 0;
	}
	_patternOffset++;
	if (_patternOffset == 8)
	    _patternOffset = 0;
    }
%}
.
    f := Form width:w height:h fromArray:formBytes.
    ^ f
!

dither2PlaneUsingMap:map on:aDevice
    "a helper for dithering palette and greyscale images"

    |f
     patterns formBytes
     pixel0bytes pixel1bytes
     clr ditherPattern
     nColors       "{Class: SmallInteger }"
     w             "{Class: SmallInteger }"
     h             "{Class: SmallInteger }"|

    nColors := map size.
    w := width.
    h := height.

    formBytes := ByteArray uninitializedNew:(w * 2 + 7 // 8) * h.
    patterns := Array new:nColors.
    pixel0bytes := ByteArray uninitializedNew:nColors.
    pixel1bytes := ByteArray uninitializedNew:nColors.

    "extract dither patterns and values to use for 1/0 bits
     in those from the dithercolors"

    1 to:nColors do:[:i |
	clr := (map at:i) on:aDevice.
	ditherPattern := clr ditherForm.

	ditherPattern isNil ifTrue:[
	    patterns at:i put:#[2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111
				2r11111111].
	    pixel0bytes at:i put:clr colorId.
	    pixel1bytes at:i put:clr colorId
	] ifFalse:[
	    patterns at:i put:(ditherPattern bits).
	    pixel0bytes at:i put:(ditherPattern colorMap at:1) colorId.
	    pixel1bytes at:i put:(ditherPattern colorMap at:2) colorId.
	].
    ].

%{
    unsigned char *_srcP, *_dstP;
    OBJ _patternBytes;
    unsigned char _mask = 0x80;
    unsigned char _outBits = 0;
    unsigned char _last, _v, _patternBits, _p0, _p1;
    int _h, _w;
    int _patternOffset = 0;
    int _outCount;

    _srcP = _ByteArrayInstPtr(_INST(bytes))->ba_element;
    _dstP = _ByteArrayInstPtr(formBytes)->ba_element;
    for (_h = _intVal(h); _h; _h--) {
	_last = -1;
	_outCount = 0;
	for (_w = _intVal(w); _w; _w--) {
	    _v = *_srcP++;
	    if (_v != _last) {
		_patternBytes = _ArrayInstPtr(patterns)->a_element[_v];
		if (__isByteArray(_patternBytes)) {
		    _patternBits = _ByteArrayInstPtr(_patternBytes)->ba_element[_patternOffset];
		} else if (__isArray(_patternBytes)) {
		    _patternBits = _intVal(_ArrayInstPtr(_patternBytes)->a_element[_patternOffset]);
		}
		_p0 = _ByteArrayInstPtr(pixel0bytes)->ba_element[_v];
		_p1 = _ByteArrayInstPtr(pixel1bytes)->ba_element[_v];
		_last = _v;
	    }
	    _outBits <<= 2;
	    if (_patternBits & _mask)
		_outBits |= _p1;
	    else
		_outBits |= _p0;
	    _mask >>= 1;
	    _outCount++;
	    if (_outCount == 4) {
		*_dstP++ = _outBits;
		_outCount = 0;
		if (_mask == 0) {
		    _mask = 0x80;
		}
	    }
	}
	if (_outCount) {
	    do {
		_outBits <<= 2;
	    } while (++_outCount != 4);
	    *_dstP++ = _outBits;
	}
	_mask = 0x80;
	_outBits = 0;
	_patternOffset++;
	if (_patternOffset == 8)
	    _patternOffset = 0;
    }
%}
.
    f := Form width:w height:h depth:2.
    f initGC.
    f device drawBits:formBytes depth:2 width:w height:h x:0 y:0
		 into:f id x:0 y:0 width:w height:h with:f gcId.
    ^ f
! !

!Depth8Image methodsFor:'queries'!

bitsPerPixel
    "return the number of bits per pixel"

    ^ 8
!

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

    ^  width * 8
!

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

    ^ width
!

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

    ^ bytes usedValues
! !

!Depth8Image class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Depth8Image.st,v 1.52 1996-06-17 12:48:33 cg Exp $'
! !