Depth8Image.st
author Claus Gittinger <cg@exept.de>
Thu, 05 Feb 1998 15:20:43 +0100
changeset 2042 58c0228331bb
parent 2006 a80384aa337f
child 2044 9ea84b4ba249
permissions -rw-r--r--
single underscore-macros -> double underscores

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

    |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"
    "Created: 24.4.1997 / 17:33:58 / cg"
!

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

%{  /* NOCONTEXT */

    OBJ b = _INST(bytes);
    OBJ w = _INST(width);

    if (__isByteArray(b) 
     && __bothSmallInteger(x, y) 
     && __isSmallInteger(w) ) {
        int _idx, _pix;

        _idx = (__intVal(w) * __intVal(y)) + __intVal(x);
        if ((unsigned)_idx < __byteArraySize(b)) {
            _pix = __ByteArrayInstPtr(b)->ba_element[_idx];
            RETURN( __MKSMALLINT(_pix) );
        }
    }
%}.
    "/ should not be reached ...

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

pixelAtX:x y:y put: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 }"|

%{  /* NOCONTEXT */

    OBJ b = _INST(bytes);
    OBJ w = _INST(width);

    if (__isByteArray(b) 
     && __bothSmallInteger(x, y) 
     && __bothSmallInteger(w, aPixelValue) ) {
        int _idx;

        _idx = (__intVal(w) * __intVal(y)) + __intVal(x);
        if ((unsigned)_idx < __byteArraySize(b)) {
            __ByteArrayInstPtr(b)->ba_element[_idx] = __intVal(aPixelValue);
            RETURN( self );
        }
    }
%}.
    "/ should not be reached ...

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

rowAt:rowIndex into:aPixelBuffer startingAt:startIndex
    "fill aPixelBuffer with pixel values from a single row.
     Notice: row indexing starts at 0."

    |srcIdx|

    srcIdx := (rowIndex * width) + 1.
    aPixelBuffer replaceFrom:startIndex to:startIndex+width-1 with:bytes startingAt:srcIdx

    "Modified: 24.4.1997 / 15:47:22 / cg"
!

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

    |dstIdx|

    dstIdx := (rowIndex*width) + 1.
    bytes replaceFrom:dstIdx to:dstIdx+width-1 with:pixelArray startingAt:1.
    ^ pixelArray

    "Modified: 24.4.1997 / 14:34:23 / 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|

    dstIdx := (rowIndex * width) + 1.
    bytes replaceFrom:dstIdx to:dstIdx+width-1 with:pixelArray startingAt:startIndex.
    ^ pixelArray

    "Created: 24.4.1997 / 15:49:42 / cg"
! !

!Depth8Image methodsFor:'converting'!

anyImageAsPseudoFormOn:aDevice
    "return a pseudoForm from the palette picture. 
     The main work is in color reduction, when not all colors can be aquired.
     This method works for any photometric."

    |pseudoBits f gcRound has8BitImage deviceDepth
     imgMap newImage pixelRow dColors
     usedColors usageCounts maxIndex map
     fit scale lastOK error 
     div 
     bitsPerRGB "{Class: SmallInteger }"
     shift      "{Class: SmallInteger }"
     m          "{Class: SmallInteger }" 
     cube nR nG nB ditherColors|

    (cube := aDevice fixColors) notNil ifTrue:[
        nR := aDevice numFixRed.
        nG := aDevice numFixGreen.
        nB := aDevice numFixBlue.

        DitherAlgorithm == #floydSteinberg ifTrue:[
            f := self
                   asFloydSteinbergDitheredDepth8FormOn:aDevice 
                   colors:cube 
                   nRed:nR
                   nGreen:nG
                   nBlue:nB.
        ] ifFalse:[
            f := self
                   asNearestPaintDepth8FormOn:aDevice 
                   colors:cube 
                   nRed:nR
                   nGreen:nG
                   nBlue:nB.
        ].
        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:[
        ('Depth8Image [info]: allocating ' , usedColors size printString , ' colors ...') infoPrintCR.
    ].

    "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 := self colorFromValue:aColorIndex. 
            (color colorId notNil 
            and:[color graphicsDevice == 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:[
                                'Depth8Image [info]: force GC for possible color reclamation.' infoPrintCR.
                                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:[
        ('Depth8Image [info]: got %1 exact colors (out of %2)' bindWith:lastOK with:usedColors size) infoPrintCR.

        DitherAlgorithm == #floydSteinberg ifTrue:[
            dColors := imgMap collect:[:clr | clr isNil ifTrue:[clr]
                                                        ifFalse:[clr nearestOn:aDevice]].
            dColors := dColors select:[:clr | clr notNil].
            dColors := dColors collect:[:clr | clr exactOn:aDevice].
            dColors := dColors select:[:clr | clr notNil].
            dColors := dColors asSet.
            dColors addAll:((aDevice colorMap collect:[:c|c onDevice:aDevice])
                            select:[:c | c colorId notNil]).
            ditherColors := aDevice availableDitherColors.
            ditherColors notNil ifTrue:[
                dColors addAll:ditherColors.
            ].
            dColors := dColors asArray.
            dColors size > 256 ifTrue:[
                dColors := dColors copyTo:256
            ].
            ^ 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.
                    color := self colorFromValue:aColorIndex. 
                    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 graphicsDevice == 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:[
                                        'Depth8Image [info]: force GC for possible color reclamation.' infoPrintCR.
                                        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:[
                ('Depth8Image [info]: remaining colors with error <= %1' bindWith:error) infoPrintCR.
            ].

            error := error * 2.
            error > 100 ifTrue:[
                "
                 break out, if the error becomes too big.
                "
                'Depth8Image [info]: hard color allocation problem - revert to b&w for remaining colors' infoPrintCR.
                "
                 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 := self colorFromValue:aColorIndex. 
                    color brightness > 0.4 ifTrue:[
                        color := Color white.
                    ] ifFalse:[
                        color := Color black.
                    ].
                    imgMap at:mapIndex put:(color on:aDevice).
                ].
                fit := true.
            ]
        ].

        error > 10 ifTrue:[
            'Depth8Image [info]: not enough colors for a reasonable image' infoPrintCR
        ] ifFalse:[
            'Depth8Image [info]: not enough colors for exact picture' infoPrintCR.
        ]
    ].

    "
     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  
	    padding:8
            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 |
        pixelRow := self rowAt:row.
        pixelRow
            expandPixels:8         "xlate only"
            width:width 
            height:1
            into:pixelRow
            mapping:map.
        newImage rowAt:row putAll:pixelRow
    ].

    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
	padding:8
	width:width height:height
        x:0 y:0
        into:(f id) x:0 y:0 
        width:width height:height 
	with:(f gcId).

    ^ f

    "Modified: 15.10.1997 / 01:48:20 / cg"
    "Created: 19.10.1997 / 04:57:05 / cg"
!

fromImage:anImage
    "setup the receiver from another image.
     The code here is tuned for depth 1, 2 and 4 source images;
     other conversions are done in the superclasses fallBack method."

    |srcBytesPerRow srcBuffer dstBuffer srcBytes srcIdx dstIdx 
     srcDepth map|

    srcDepth := anImage depth.
    (#(1 2 4) includes:srcDepth) ifFalse:[
        ^ super fromImage:anImage
    ].

    width := anImage width.
    height := anImage height.
    bytes := ByteArray uninitializedNew:(width * height).
    bitsPerSample := self bitsPerSample.
    samplesPerPixel := self samplesPerPixel.
    self colormapFromImage:anImage.

    colorMap isNil ifTrue:[
        "/ if source has no colorMap, more work is needed ...
        map := #(
                #[0 16rFF]
                #[0 16r55 16rAA 16rFF]
                nil
                #[16r00 16r11 16r22 16r33 16r44 16r55 16r66 16r77
                  16r88 16r99 16rAA 16rBB 16rCC 16rDD 16rEE 16rFF]
               ) at:srcDepth.
    ].

    self mask:anImage mask.

    "/ only expand & translate pixels

    srcBytes := anImage bits.
    srcBytesPerRow := anImage bytesPerRow.
    srcBuffer := ByteArray new:srcBytesPerRow.

    dstBuffer := ByteArray new:width.
    srcIdx := 1.
    dstIdx := 1.
    1 to:height do:[:hi |
        srcBuffer replaceFrom:1 to:srcBytesPerRow with:srcBytes startingAt:srcIdx.
        srcBuffer expandPixels:srcDepth width:width height:1 into:dstBuffer
                       mapping:map. 
        bytes replaceFrom:dstIdx to:dstIdx+width-1 with:dstBuffer startingAt:1.
        dstIdx := dstIdx + width.
        srcIdx := srcIdx + srcBytesPerRow.
    ]

    "
     |i1 i2 i4 i8 i16 i24|

     i1 := Image fromFile:'bitmaps/SBrowser.xbm'.
     i2 := Depth2Image fromImage:i1.
     i4 := Depth4Image fromImage:i1.

     i8 := Depth8Image fromImage:i1.
     i8 inspect.
     i8 := Depth8Image fromImage:i2.
     i8 inspect.
     i8 := Depth8Image fromImage:i4.
     i8 inspect.
    "

    "Modified: 24.4.1997 / 14:01:14 / cg"
! !

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

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

    ^ self anyImageAsPseudoFormOn:aDevice

    "Modified: 19.10.1997 / 04:57:39 / cg"
    "Created: 19.10.1997 / 04:58:41 / cg"
!

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

    ^ self anyImageAsPseudoFormOn:aDevice

    "Modified: 19.10.1997 / 04:57:39 / cg"
!

paletteImageAsTrueColorFormOn:aDevice
    "return a true-color device-form for the palette-image receiver.
     Supports true color devices with depths: 8, 16, 24 and 32"

    |depth 
     nColors "{ Class: SmallInteger }"
     colorValues 
     scaleRed scaleGreen scaleBlue redShift greenShift blueShift
     form imageBits bestFormat usedDeviceDepth usedDeviceBitsPerPixel 
     usedDevicePadding usedDeviceBytesPerRow padd n|

    depth := aDevice depth.

    "/ gather r/g/b values for all colors in the map ...

    nColors := colorMap size.

    "/ precompute scales to map from 0..100 into devices range
    "/ (this may be different for the individual components)

    scaleRed := ((1 bitShift:aDevice bitsRed) - 1) / 100.
    scaleGreen := ((1 bitShift:aDevice bitsGreen) - 1) / 100.
    scaleBlue := ((1 bitShift:aDevice bitsBlue) - 1) / 100.
    redShift := aDevice shiftRed.
    greenShift := aDevice shiftGreen.
    blueShift := aDevice shiftBlue.

    colorValues := Array uninitializedNew:nColors.

    1 to:nColors do:[:index |
        |clr rv gv bv v "{ Class: SmallInteger }" |

        clr := colorMap at:index.
        clr notNil ifTrue:[
            rv := (clr red * scaleRed) rounded.
            gv := (clr green * scaleGreen) rounded.
            bv := (clr blue * scaleBlue) rounded.

            v := rv bitShift:redShift.
            v := v bitOr:(gv bitShift:greenShift).
            v := v bitOr:(bv bitShift:blueShift).
            colorValues at:index put:v.
"/ clr print. ' ' print.
"/ rv print. ' ' print. gv print. ' ' print. bv print. ' ' print.
"/ ' -> ' print. v printNL.

        ]
    ].

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

    usedDeviceBytesPerRow := self class bytesPerRowForWidth:width depth:usedDeviceBitsPerPixel padding:usedDevicePadding.
    padd := usedDeviceBytesPerRow -( self class bytesPerRowForWidth:width depth:usedDeviceBitsPerPixel padding:8).
    imageBits := ByteArray uninitializedNew:(usedDeviceBytesPerRow * height).

    "/ for now, only support some depths

    usedDeviceBitsPerPixel == 16 ifTrue:[
        "/ 16 bits/pixel

        "/ now, walk over the image and replace
        "/ colorMap indices by color values in the bits array

%{  
        if (__bothSmallInteger(_INST(height), _INST(width))
         && __isArray(colorValues)
         && __isByteArray(_INST(bytes))
         && __isByteArray(imageBits)) {
            int r,p;
            int x, y, w, h, nPix;

            unsigned char *srcPtr = __ByteArrayInstPtr(_INST(bytes))->ba_element;
            unsigned char *dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
            OBJ *ap = __ArrayInstPtr(colorValues)->a_element;

            w = __intVal(_INST(width));
            h = __intVal(_INST(height));
            r = w;
            p = __intVal(padd);
            nPix = w * h;
            while (nPix-- > 0) {
                unsigned idx, v;
                OBJ clr;

                idx = *srcPtr++;
                clr = ap[idx];
                v = __intVal(clr);
#ifdef MSBFIRST
                ((short *)dstPtr)[0] = v;
#else
                dstPtr[0] = (v>>8) & 0xFF;
                dstPtr[1] = (v) & 0xFF;
#endif
                dstPtr += 2;

                if (--r == 0) {
                  dstPtr += p;
                  r = w;
                }
            }
        }
%}.
    ] ifFalse:[
        usedDeviceBitsPerPixel == 32 ifTrue:[
            "/ 32 bits/pixel

            "/ now, walk over the image and replace
            "/ colorMap indices by color values in the bits array

%{       
            if (__bothSmallInteger(_INST(height), _INST(width))
             && __isArray(colorValues)
             && __isByteArray(_INST(bytes))
             && __isByteArray(imageBits)) {
                int x, y, w, h, nPix;

                unsigned char *srcPtr = __ByteArrayInstPtr(_INST(bytes))->ba_element;
                unsigned char *dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
                OBJ *ap = __ArrayInstPtr(colorValues)->a_element;

                w = __intVal(_INST(width));
                h = __intVal(_INST(height));
                nPix = w * h;
                while (nPix > 0) {
                    unsigned idx, v;
                    OBJ clr;

                    idx = *srcPtr;
                    clr = ap[idx];
                    v = __intVal(clr);
#ifdef MSBFIRST
                    ((long *)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 += 1;
                    nPix--;
                }
            }
%}.
        ] ifFalse:[
            usedDeviceBitsPerPixel == 8 ifTrue:[
                "/ 8 bits/pixel

                "/ now, walk over the image and replace
                "/ colorMap indices by color values in the bits array

%{       
                if (__bothSmallInteger(_INST(height), _INST(width))
                 && __isArray(colorValues)
                 && __isByteArray(_INST(bytes))
                 && __isByteArray(imageBits)) {
                    int x, y, w, h, nPix;
                    int r,p;

                    unsigned char *srcPtr = __ByteArrayInstPtr(_INST(bytes))->ba_element;
                    unsigned char *dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
                    OBJ *ap = __ArrayInstPtr(colorValues)->a_element;

                    w = __intVal(_INST(width));
                    h = __intVal(_INST(height));
                    r = w;
                    p = __intVal(padd);

                    nPix = w * h;
                    while (nPix > 0) {
                        unsigned idx, v;
                        OBJ clr;

                        idx = *srcPtr;
                        clr = ap[idx];
                        v = __intVal(clr);

                        dstPtr[0] = v;

                        dstPtr += 1;
                        srcPtr += 1;
                        nPix--;

                        if (--r == 0) {
                          dstPtr += p;
                          r = w;
                        }

                    }
                }
%}.
            ] ifFalse:[
                usedDeviceBitsPerPixel == 24 ifTrue:[
                    "/ 24 bits/pixel

                    "/ now, walk over the image and replace
                    "/ colorMap indices by color values in the bits array

%{       
                    if (__bothSmallInteger(_INST(height), _INST(width))
                     && __isArray(colorValues)
                     && __isByteArray(_INST(bytes))
                     && __isByteArray(imageBits)) {
                        int x, y, w, h, nPix;
                        int r,p;

                        unsigned char *srcPtr = __ByteArrayInstPtr(_INST(bytes))->ba_element;
                        unsigned char *dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
                        OBJ *ap = __ArrayInstPtr(colorValues)->a_element;

                        w = __intVal(_INST(width));
                        h = __intVal(_INST(height));
                        r = w;
                        p = __intVal(padd);

                        nPix = w * h;
                        while (nPix > 0) {
                            unsigned idx, v;
                            OBJ clr;

                            idx = *srcPtr;
                            clr = ap[idx];
                            v = __intVal(clr);

                            dstPtr[0] = (v>>16) & 0xFF;
                            dstPtr[1] = (v>>8) & 0xFF;
                            dstPtr[2] = (v) & 0xFF;

                            dstPtr += 3;
                            srcPtr += 1;
                            nPix--;
                            if (--r == 0) {
                              dstPtr += p;
                              r = w;
                            }
                        }
                    }
%}.
                ]
            ]
        ]
    ].

    imageBits isNil ifTrue:[            
        'Image [warning]: unimplemented trueColor depth in paletteImageAsTrueColorFormOn: ' errorPrint. usedDeviceBitsPerPixel errorPrintCR.
        ^ self asMonochromeFormOn:aDevice
    ].

    form := Form width:width height:height depth:usedDeviceDepth on:aDevice.
    form isNil ifTrue:[^ nil].
    form initGC.

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

    ^ form

    "Created: 20.10.1995 / 22:05:10 / cg"
    "Modified: 21.10.1995 / 19:30:26 / cg"
! !

!Depth8Image methodsFor:'dither helpers'!

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 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);

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

    unsigned 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/gifImages/claus.gif'.
     f := i asOrderedDitheredMonochromeFormOn:Display.


     |i f|

     i := Image fromFile:'bitmaps/gifImages/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|

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

    colorArray := Array new:256.

    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
    ]

    "Created: 7.6.1996 / 19:12:35 / cg"
    "Modified: 11.7.1996 / 20:22:32 / cg"
!

colorsFromX:xStart y:yStart toX:xEnd y:yEnd do:aBlock
    "perform aBlock for each pixel in the rectangle
     yStart..yEnd / xStart..xEnd.
     The block is passed the color at each pixel.
     This method allows slighly faster processing of an
     image than using individual atX:y: accesses, 
     both since some processing can be avoided when going from pixel to pixel,
     and since the color composition is done outside of the pixel loop. 
     However, for real high performance image processing, specialized methods 
     should be written which know how to deal with specific photometric interpretations."

    |srcIndex    "{ Class: SmallInteger }"
     srcNext     "{ Class: SmallInteger }"
     bytesPerRow "{ Class: SmallInteger }"
     value    "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     y1       "{ Class: SmallInteger }"
     y2       "{ Class: SmallInteger }"
     colorArray|

    x1 := xStart.
    x2 := xEnd.
    y1 := yStart.
    y2 := yEnd.

    srcIndex := (width * y1) + x1 + 1 .
    bytesPerRow := self bytesPerRow.

    colorArray := self realColorMap.

    y1 to:y2 do:[:y |
        srcNext := srcIndex + bytesPerRow.
        x1 to:x2 do:[:x |
            value := bytes at:srcIndex.
            srcIndex := srcIndex + 1.

            aBlock value:x value:y value:(colorArray at:value+1)
        ].
        srcIndex := srcNext.
    ].
    ^ self

    "Created: 7.6.1996 / 19:12:35 / cg"
    "Modified: 11.7.1996 / 20:20:55 / 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"
!

valuesFromX:xStart y:yStart toX:xEnd y:yEnd do:aBlock
    "perform aBlock for each pixel in the rectangle
     yStart..yEnd / xStart..xEnd.
     The block is passed the pixelValue at each pixel.
     This method allows slighly faster processing of an
     image than using individual valueAtX:y: accesses, 
     since some processing can be avoided when going from pixel to pixel.. 
     However, for real high performance image processing, specialized methods 
     should be written which know how to deal with specific photometric interpretations."

    |srcIndex    "{ Class: SmallInteger }"
     srcNext     "{ Class: SmallInteger }"
     bytesPerRow "{ Class: SmallInteger }"
     value    "{ Class: SmallInteger }"
     x1       "{ Class: SmallInteger }"
     x2       "{ Class: SmallInteger }"
     y1       "{ Class: SmallInteger }"
     y2       "{ Class: SmallInteger }"|

    x1 := xStart.
    x2 := xEnd.
    y1 := yStart.
    y2 := yEnd.

    srcIndex := (width * y1) + x1 + 1 .
    bytesPerRow := self bytesPerRow.

    y1 to:y2 do:[:y |
        srcNext := srcIndex + bytesPerRow.
        x1 to:x2 do:[:x |
            value := bytes at:srcIndex.
            srcIndex := srcIndex + 1.

            aBlock value:x value:y value:value
        ].
        srcIndex := srcNext.
    ].
    ^ self

    "Modified: 11.7.1996 / 20:06:47 / cg"
    "Created: 11.7.1996 / 20:08:11 / cg"
! !

!Depth8Image methodsFor:'image manipulations'!

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 * newHeight).

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

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

    "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 graphicsDevice 
        drawBits:formBytes
	depth:2 
	padding:8
	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.81 1998-02-05 14:20:43 cg Exp $'
! !