Depth32Image.st
author Claus Gittinger <cg@exept.de>
Tue, 23 Apr 2019 16:30:55 +0200
changeset 8674 e29a561c0fbe
parent 8339 b2b10047577b
child 8728 289cdc983b33
permissions -rw-r--r--
#FEATURE by cg class: SimpleView added: #isDialogBox

"{ Encoding: utf8 }"

"
 COPYRIGHT (c) 1995 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.
"
"{ Package: 'stx:libview' }"

"{ NameSpace: Smalltalk }"

Image subclass:#Depth32Image
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Images'
!

!Depth32Image class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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 32 bit (eg. rgb+alpha) images.

    Only the minimum protocol is implemented here; much more is
    needed for higher performance operations on depth32 images.

    with #rgb, #rgba, #rgbx, photometrics 
    pixels are internally stored byte-wise in rgba order.
    (i.e. r at low-address byte, a at high-address byte). 
    For rgb, a zero is always retrieved as alpha; 255 for rgbx.

    When reading pixel values, photometric argb is returned as aarrggbb,
    photometric rgb is returned as 00rrggbb,
    photometric rgba is returned as rrggbb00,
    both on LSB and on MSB machines.
    (i.e. blue in lower bits of the returned 32bit integer, alpha in the high bits for argb,
     and in the low bits for rgba)
    Thus, pixelValues and rgbValues are identical, simulating MSB on all
    architectures.
    (this should be transparent, if you use the rgbValueAt
     accessors; however, some old code uses pixelValueAt:, assuming that the
    returned pixel value is rrggbb - which it would not be without this hack).

    This also makes depth24Image's rgbValues compatible with depth32Image's rgbValues.

    For argb and xrgb formats, alpha (or dummy alpha) is in the first byte 
    (which are the high bits, as we present pixel values always MSB).

    [author:]
        Claus Gittinger

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

!Depth32Image class methodsFor:'queries'!

defaultPhotometric
    "return the default photometric pixel interpretation"

    "/ here we return #rgb - thus ignoring any alpha channel.
    "/ the reason is that many displays and graphics formats do use
    "/ 32bit per pixel, but provide an alpha value of 0, instead of 255.
    "/ Thus returning rgba here would make many images invisible (totally transparent)
    
    ^ #rgb

    "Created: / 27-05-2007 / 14:03:59 / cg"
    "Modified: / 16-02-2017 / 17:41:09 / cg"
    "Modified (comment): / 16-02-2017 / 19:00:25 / cg"
!

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

    ^ 32

    "Modified: 20.4.1996 / 23:40:01 / cg"
    "Created: 24.4.1997 / 19:00:28 / cg"
! !

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

    index := 1 + (((width * y) + x) * 4).
    ((photometric == #rgb) or:[photometric == #xrgb]) ifTrue:[
        "/ byteorder is: <ignoredAlpha>,r,g,b
        rVal := bytes at:(index + 1).
        gVal := bytes at:(index + 2).
        bVal := bytes at:(index + 3).
        ^ Color redByte:rVal greenByte:gVal blueByte:bVal
    ].
    (photometric == #rgba) ifTrue:[
        "/ byteorder is: r,g,b,<ignoredAlpha>
        rVal := bytes at:(index).
        gVal := bytes at:(index + 1).
        bVal := bytes at:(index + 2).
        aVal := bytes at:(index + 3).
        ^ Color redByte:rVal greenByte:gVal blueByte:bVal alphaByte:aVal
    ].
    photometric == #argb ifTrue:[
        "/ byteorder is: a,r,g,b
        aVal := bytes at:(index).
        rVal := bytes at:(index + 1).
        gVal := bytes at:(index + 2).
        bVal := bytes at:(index + 3).
        ^ Color redByte:rVal greenByte:gVal blueByte:bVal alphaByte:aVal
    ].
    photometric == #xrgb ifTrue:[
        "/ byteorder is: ignored-alpha,r,g,b
        rVal := bytes at:(index + 1).
        gVal := bytes at:(index + 2).
        bVal := bytes at:(index + 3).
        ^ Color redByte:rVal greenByte:gVal blueByte:bVal
    ].
    "/ the inherited method should handle all cases.
    ^ super colorAtX:x y:y.

    "Modified: / 22-08-2017 / 18:17:38 / 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 }"
     r g b|

    index := 1 + (((width * y) + x) * 4).
    r := aColor redByte.
    g := aColor greenByte.
    b := aColor blueByte.
    
    ((photometric == #rgb) or:[(photometric == #xrgb)]) ifTrue:[
        "/ byteorder is: ignored-alpha,r,g,b
        bytes at:(index + 1) put:r.
        bytes at:(index + 2) put:g.
        bytes at:(index + 3) put:b.
        ^ self
    ].
    (photometric == #rgba) ifTrue:[
        "/ byteorder is: r,g,b,a
        bytes at:(index + 0) put:r.
        bytes at:(index + 1) put:g.
        bytes at:(index + 2) put:b.
        bytes at:(index + 3) put:(aColor alphaByte). "alpha channel in last byte"
        ^ self
    ].
    (photometric == #argb) ifTrue:[
        "/ byteorder is: a,r,g,b
        bytes at:(index + 0) put:(aColor alphaByte).     "alpha channel in first byte"
        bytes at:(index + 1) put:r.
        bytes at:(index + 2) put:g.
        bytes at:(index + 3) put:b.             
        ^ self
    ].
    (photometric == #rgbx) ifTrue:[
        "/ byteorder is: <ignoredAlpha>,r,g,b
        bytes at:(index + 0) put:r.
        bytes at:(index + 1) put:g.
        bytes at:(index + 2) put:b.
        ^ self
    ].

    super colorAtX:x y:y put:aColor.

    "Modified: / 22-08-2017 / 18:17:14 / cg"
!

pixelAtX:x y:y
    "retrieve a pixel at x/y; return a pixelValue.
     The interpretation of the returned value depends on the photometric
     and the colormap. See also Image>>atX:y:)
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel.
     With rgba photometric, the pixel value contains r/g/b/a in lsb order 
     (i.e. r at low, a at high bits);
     with argb, alpha is in the low byte"

    |pixelIndex "{ Class: SmallInteger }"|

%{  /* NOCONTEXT */
    OBJ b = __INST(bytes);
    OBJ w = __INST(width);

    if (__isByteArrayLike(b)
     && __bothSmallInteger(x, y)
     && __isSmallInteger(w)
     && (__INST(pixelFunction)==nil) ) {
        int _idx;

        _idx = ((__intVal(w) * __intVal(y)) + __intVal(x))*4;
        if (((unsigned)(_idx+3)) < __byteArraySize(b)) {
            unsigned char *pPix = &(__ByteArrayInstPtr(b)->ba_element[_idx]);
            unsigned int _pix;

#ifdef __MSBFIRST__
            _pix = ((int *)pPix)[0];
#else
            _pix = pPix[0] << 24;
            _pix |= pPix[1] << 16;
            _pix |= pPix[2] << 8;
            _pix |= pPix[3];
#endif

#if __POINTER_SIZE__ == 8
            RETURN( __MKSMALLINT(_pix) );
#else
            RETURN( __MKUINT(_pix) );
#endif
        }
    }
%}.
    pixelFunction notNil ifTrue:[^ pixelFunction value:x value:y].

    pixelIndex := 1 + (((width * y) + x) * 4).
    ^ bytes unsignedInt32At:pixelIndex MSB:true.

    "Created: / 24-04-1997 / 19:00:28 / cg"
    "Modified: / 21-02-2017 / 17:21:44 / cg"
    "Modified (comment): / 22-08-2017 / 18:24:22 / cg"
!

pixelAtX:x y:y put:aPixelValue
    "set the pixel at x/y to aPixelValue.
     The interpretation of the pixelValue depends on the photometric.
     Pixels start at x=0 , y=0 for upper left pixel, end at
     x = width-1, y=height-1 for lower right pixel.
     With rgba photometric, the pixel value contains r/g/b/a in lsb order 
     (i.e. r at low, a at high bits);
     with argb, alpha is in the low byte"

    |pixelIndex "{ Class: SmallInteger }"|

%{  /* NOCONTEXT */
    OBJ b = __INST(bytes);
    OBJ w = __INST(width);

    if ((b != nil)
     && __isByteArrayLike(b)
     && __bothSmallInteger(x, y)
     && __isSmallInteger(aPixelValue)
     && (__INST(pixelFunction)==nil) ) {
        int _idx;

        _idx = ((__intVal(w) * __intVal(y)) + __intVal(x))*4;
        if (((unsigned)(_idx+3)) < __byteArraySize(b)) {
            unsigned char *pPix = &(__ByteArrayInstPtr(b)->ba_element[_idx]);
            unsigned int _pix = __intVal(aPixelValue);

#ifdef __MSBFIRST__
            ((int *)pPix)[0] = _pix;
#else
            pPix[0] = (_pix >> 24) & 0xFF;
            pPix[1] = (_pix >> 16) & 0xFF;
            pPix[2] = (_pix >> 8) & 0xFF;
            pPix[3] = _pix & 0xFF;
#endif
            RETURN(self);
        }
    }
%}.
    bytes isNil ifTrue:[ self createPixelStore ].

    pixelIndex := 1 + (((width * y) + x) * 4).
    bytes unsignedInt32At:pixelIndex put:aPixelValue MSB:true.

    "Created: / 24-04-1997 / 19:00:28 / cg"
    "Modified: / 22-08-2017 / 18:21:47 / cg"
!

rowAt:y putAll:pixelArray startingAt:startIndex
    "store a single rows bits from bits in the pixelArray argument;
     The interpretation of the pixel values depends on the photometric.
     Notice: row coordinate starts at 0."

    |bytes pixel
     dstIdx "{ Class: SmallInteger }" 
     w "{ Class: SmallInteger }"|

    bytes := self bits.
    dstIdx := (y * self bytesPerRow) + 1.
    w := width - 1.

    0 to:w do:[:col |
        pixel := pixelArray at:(startIndex + col).
        "/ msbFirst
        bytes unsignedInt32At:dstIdx put:pixel MSB:true.
        dstIdx := dstIdx + 4.
    ].

    "Modified (comment): / 21-02-2017 / 15:03:24 / cg"
! !

!Depth32Image methodsFor:'converting rgb images'!

computeAlphaValuesFromMask:aMaskImage
    "convert a mask into alpha values;
     masked pixels get an alpha value of 0, unmasked of 255"

    |alphaMask|

    alphaMask := (self alphaMaskForPixelValue bitShift:self alphaShiftForPixelValue).
    self 
        valuesFromX:0 y:0 toX:(width-1) y:(height-1)
        do:[:x :y :pixelValue |
            (aMaskImage pixelAtX:x y:y) ~~ 0 ifTrue:[
                self pixelAtX:x y:y put:(pixelValue bitOr:alphaMask).
            ] ifFalse:[
                self pixelAtX:x y:y put:(pixelValue bitClear:alphaMask).
            ].
        ].
    photometric := #rgba

    "Modified: / 21-02-2017 / 16:41:02 / cg"
!

rgbImageAsTrueColorFormOn:aDevice
    "return a truecolor form from the rgba or argb-picture."

    |bytes bestFormat usedDeviceDepth usedDeviceBitsPerPixel usedDevicePadding
     myDepth form imageBits padd
     rightShiftR rightShiftG rightShiftB
     shiftRed shiftGreen shiftBlue
     redOffs greenOffs blueOffs alphaOffs|

    bytes := self bits.

    bestFormat := self bestSupportedImageFormatFor:aDevice.

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

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

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

    redOffs := 0.
    greenOffs := 1.  
    blueOffs := 2.
    alphaOffs := 3.

    ((photometric == #argb) or:[ photometric == #rgb ]) ifTrue:[
        redOffs := 1. greenOffs := 2. blueOffs := 3. alphaOffs := 0.
    ] ifFalse:[
        (photometric == #rgba) ifFalse:[
            ^ self anyImageAsTrueColorFormOn:aDevice
        ].    
    ].    

    "/
    "/ for now, only a few formats are supported
    "/
    myDepth := self bitsPerPixel.
    usedDeviceBitsPerPixel == 24 ifTrue:[
        "/
        "/ 24 bit/pixel
        "/
        imageBits := ByteArray uninitializedNew:(width * height * 3).
        usedDevicePadding := 8.

        "/ now, walk over the image and compose 24bit values from the r/g/b/a triples
%{
        unsigned char *srcPtr = 0;
        unsigned char *dstPtr = 0;
        int _redOffs = __intVal(redOffs);
        int _greenOffs = __intVal(greenOffs);  
        int _blueOffs = __intVal(blueOffs);
        // int _alphaOffs = __intVal(alphaOffs);

        if (__isByteArrayLike(bytes)) {
            srcPtr = __ByteArrayInstPtr(bytes)->ba_element;
        } else {
            if (__isExternalBytesLike(bytes)) {
                srcPtr = __externalBytesAddress(bytes);
            }
        }
        if (__isByteArray(imageBits)) {
            dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
        } else {
            if (__isExternalBytesLike(imageBits)) {
                dstPtr = __externalBytesAddress(imageBits);
            }
        }

        if (__bothSmallInteger(__INST(height), __INST(width))
         && __bothSmallInteger(rightShiftR, shiftRed)
         && __bothSmallInteger(rightShiftG, shiftGreen)
         && __bothSmallInteger(rightShiftB, shiftBlue)
         && srcPtr
         && dstPtr) {
            int rShRed = __intVal(rightShiftR),
                rShGreen = __intVal(rightShiftG),
                rShBlue = __intVal(rightShiftB),
                lShRed = __intVal(shiftRed),
                lShGreen = __intVal(shiftGreen),
                lShBlue = __intVal(shiftBlue);
            int x, y, w;

            w = __intVal(__INST(width));
            if ((rShRed == 0) && (rShGreen == 0) && (rShBlue == 0)) {
                if ((lShRed == 0) && (lShGreen == 8) && (lShBlue == 16)) {
                    for (y=__intVal(__INST(height)); y > 0; y--) {
                        for (x=w; x > 0; x--) {                        
# ifdef __MSBFIRST
                            dstPtr[0] = srcPtr[_redOffs];
                            dstPtr[1] = srcPtr[_greenOffs];
                            dstPtr[2] = srcPtr[_blueOffs];
# else /* not MSB */
                            dstPtr[0] = srcPtr[_blueOffs];
                            dstPtr[1] = srcPtr[_greenOffs];
                            dstPtr[2] = srcPtr[_redOffs];
# endif /* not MSB */
                            dstPtr += 3;
                            srcPtr += 4;
                        }
                    }
                } else {
                    for (y=__intVal(__INST(height)); y > 0; y--) {
                        for (x=w; x > 0; x--) {
                            unsigned v;

                            v = srcPtr[_redOffs] << lShRed;
                            v |= (srcPtr[_greenOffs] << lShGreen);
                            v |= (srcPtr[_blueOffs] << lShBlue);
# ifdef __MSBFIRST
                            dstPtr[0] = (v) & 0xFF;
                            dstPtr[1] = (v>>8) & 0xFF;
                            dstPtr[2] = (v>>16) & 0xFF;
# else /* not MSB */
                            dstPtr[0] = (v>>16) & 0xFF;
                            dstPtr[1] = (v>>8) & 0xFF;
                            dstPtr[2] = (v) & 0xFF;
# endif /* not MSB */
                            dstPtr += 3;
                            srcPtr += 4;
                        }
                    }
                }
            } else {
                for (y=__intVal(__INST(height)); y > 0; y--) {
                    for (x=w; x > 0; x--) {
                        unsigned r, g, b, v;

                        r = srcPtr[_redOffs] >> rShRed;
                        g = srcPtr[_greenOffs] >> rShGreen;
                        b = srcPtr[_blueOffs] >> rShBlue;
                        v = r << lShRed;
                        v |= (g << lShGreen);
                        v |= (b << lShBlue);
# ifdef __MSBFIRST
                        dstPtr[0] = (v) & 0xFF;
                        dstPtr[1] = (v>>8) & 0xFF;
                        dstPtr[2] = (v>>16) & 0xFF;
# else /* not MSB */
                        dstPtr[0] = (v>>16) & 0xFF;
                        dstPtr[1] = (v>>8) & 0xFF;
                        dstPtr[2] = (v) & 0xFF;
# endif /* not MSB */
                        dstPtr += 3;
                        srcPtr += 4;
                    }
                }
            }
        }
%}.
    ] ifFalse:[
        "/
        "/ 8, 16 or 32 bit/pixel ...
        "/
        (usedDeviceBitsPerPixel == 16) ifTrue:[
            padd := width \\ (usedDevicePadding // 16).
            imageBits := ByteArray uninitializedNew:((width + padd) * height * 2).

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

%{
            unsigned char *srcPtr = 0;
            unsigned char *dstPtr = 0;
            int _redOffs = __intVal(redOffs);
            int _greenOffs = __intVal(greenOffs);  
            int _blueOffs = __intVal(blueOffs);
            // int _alphaOffs = __intVal(alphaOffs);

            if (__isByteArrayLike(bytes)) {
                srcPtr = __ByteArrayInstPtr(bytes)->ba_element;
            } else {
                if (__isExternalBytesLike(bytes)) {
                    srcPtr = __externalBytesAddress(bytes);
                }
            }
            if (__isByteArray(imageBits)) {
                dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
            } else {
                if (__isExternalBytesLike(imageBits)) {
                    dstPtr = __externalBytesAddress(imageBits);
                }
            }

            if (__bothSmallInteger(__INST(height),__INST(width))
             && __bothSmallInteger(rightShiftR, shiftRed)
             && __bothSmallInteger(rightShiftG, shiftGreen)
             && __bothSmallInteger(rightShiftB, shiftBlue)
             && srcPtr
             && dstPtr) {
                int rShRed = __intVal(rightShiftR),
                    rShGreen = __intVal(rightShiftG),
                    rShBlue = __intVal(rightShiftB),
                    lShRed = __intVal(shiftRed),
                    lShGreen = __intVal(shiftGreen),
                    lShBlue = __intVal(shiftBlue);
                int x, y, w;
                int p;

                w = __intVal(__INST(width));
                p = __intVal(padd) * 2;

                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[_redOffs] << lShRed;
                            v |= (srcPtr[_greenOffs] << lShGreen);
                            v |= (srcPtr[_blueOffs] << lShBlue);
# ifdef __MSBFIRST
                            ((short *)dstPtr)[0] = v;
# else /* not MSB */
                            dstPtr[0] = (v>>8) & 0xFF;
                            dstPtr[1] = (v) & 0xFF;
# endif /* not MSB */
                            dstPtr += 2;
                            srcPtr += 4;
                        }
                        dstPtr += p;
                    }
                } else {
                    if (p == 0) {
                        int n = __intVal(__INST(height)) * w;

                        while (n >= 2) {
                            unsigned w, r, g, b, v;

                            n -= 2;

                            r = srcPtr[_redOffs];
                            g = srcPtr[_greenOffs];
                            b = srcPtr[_blueOffs];
                            v = (r >> rShRed) << lShRed;
                            v |= ((g >> rShGreen) << lShGreen);
                            v |= ((b >> rShBlue) << lShBlue);
# ifdef __MSBFIRST
                            ((short *)dstPtr)[0] = v;
# else
                            dstPtr[0] = (v>>8) & 0xFF;
                            dstPtr[1] = (v) & 0xFF;
# endif /* not MSB */

                            r = srcPtr[3+_redOffs];
                            g = srcPtr[3+_greenOffs];
                            b = srcPtr[3+_blueOffs];
                            v = (r >> rShRed) << lShRed;
                            v |= ((g >> rShGreen) << lShGreen);
                            v |= ((b >> rShBlue) << lShBlue);
# ifdef __MSBFIRST
                            ((short *)dstPtr)[1] = v;
# else
                            dstPtr[2] = (v>>8) & 0xFF;
                            dstPtr[3] = (v) & 0xFF;
# endif /* not MSB */
                            dstPtr += 4;
                            srcPtr += 8;
                        }

                        while (n--) {
                            unsigned r, g, b, v;

                            r = srcPtr[_redOffs] >> rShRed;
                            g = srcPtr[_greenOffs] >> rShGreen;
                            b = srcPtr[_blueOffs] >> rShBlue;
                            v = r << lShRed;
                            v |= (g << lShGreen);
                            v |= (b << lShBlue);
# ifdef __MSBFIRST
                            ((short *)dstPtr)[0] = v;
# else /* not MSB */
                            dstPtr[0] = (v>>8) & 0xFF;
                            dstPtr[1] = (v) & 0xFF;
# endif /* not MSB */
                            dstPtr += 2;
                            srcPtr += 4;
                        }
                    } else {
                        for (y=__intVal(__INST(height)); y > 0; y--) {
                            for (x=w; x > 0; x--) {
                                unsigned r, g, b, v;

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

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

%{
                unsigned char *srcPtr = 0;
                unsigned char *dstPtr = 0;
                int _redOffs = __intVal(redOffs);
                int _greenOffs = __intVal(greenOffs);  
                int _blueOffs = __intVal(blueOffs);
                // int _alphaOffs = __intVal(alphaOffs);

                if (__isByteArrayLike(bytes)) {
                    srcPtr = __ByteArrayInstPtr(bytes)->ba_element;
                } else {
                    if (__isExternalBytesLike(bytes)) {
                        srcPtr = __externalBytesAddress(bytes);
                    }
                }
                if (__isByteArray(imageBits)) {
                    dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
                } else {
                    if (__isExternalBytesLike(imageBits)) {
                        dstPtr = __externalBytesAddress(imageBits);
                    }
                }

                if (__bothSmallInteger(__INST(height), __INST(width))
                 && __bothSmallInteger(rightShiftR, shiftRed)
                 && __bothSmallInteger(rightShiftG, shiftGreen)
                 && __bothSmallInteger(rightShiftB, shiftBlue)
                 && srcPtr
                 && dstPtr) {
                    int rShRed = __intVal(rightShiftR),
                        rShGreen = __intVal(rightShiftG),
                        rShBlue = __intVal(rightShiftB),
                        lShRed = __intVal(shiftRed),
                        lShGreen = __intVal(shiftGreen),
                        lShBlue = __intVal(shiftBlue);
                    int x, y, w;
                    
                    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[_redOffs] << lShRed;
                                v |= (srcPtr[_greenOffs] << lShGreen);
                                v |= (srcPtr[_blueOffs] << lShBlue);
# ifdef __MSBFIRST
                                ((int *)dstPtr)[0] = v;
# else /* not MSB */
                                dstPtr[0] = (v>>24) & 0xFF;
                                dstPtr[1] = (v>>16) & 0xFF;
                                dstPtr[2] = (v>>8) & 0xFF;
                                dstPtr[3] = (v) & 0xFF;
# endif /* not MSB */
                                dstPtr += 4;
                                srcPtr += 4;
                            }
                        }
                    } else {
                        for (y=__intVal(__INST(height)); y > 0; y--) {
                            for (x=w; x > 0; x--) {
                                unsigned r, g, b, v;

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

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

%{
                    unsigned char *srcPtr = 0;
                    unsigned char *dstPtr = 0;
                    int _redOffs = __intVal(redOffs);
                    int _greenOffs = __intVal(greenOffs);  
                    int _blueOffs = __intVal(blueOffs);
                    // int _alphaOffs = __intVal(alphaOffs);

                    if (__isByteArrayLike(bytes)) {
                        srcPtr = __ByteArrayInstPtr(bytes)->ba_element;
                    } else {
                        if (__isExternalBytesLike(bytes)) {
                            srcPtr = __externalBytesAddress(bytes);
                        }
                    }
                    if (__isByteArray(imageBits)) {
                        dstPtr = __ByteArrayInstPtr(imageBits)->ba_element;
                    } else {
                        if (__isExternalBytesLike(imageBits)) {
                            dstPtr = __externalBytesAddress(imageBits);
                        }
                    }

                    if (__bothSmallInteger(__INST(height), __INST(width))
                     && __bothSmallInteger(rightShiftR, shiftRed)
                     && __bothSmallInteger(rightShiftG, shiftGreen)
                     && __bothSmallInteger(rightShiftB, shiftBlue)
                     && srcPtr
                     && dstPtr) {
                        int rShRed = __intVal(rightShiftR),
                            rShGreen = __intVal(rightShiftG),
                            rShBlue = __intVal(rightShiftB),
                            lShRed = __intVal(shiftRed),
                            lShGreen = __intVal(shiftGreen),
                            lShBlue = __intVal(shiftBlue);
                        int x, y, w;

                        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[_redOffs] << lShRed;
                                    v |= (srcPtr[_greenOffs] << lShGreen);
                                    v |= (srcPtr[_blueOffs] << lShBlue);
                                    dstPtr[0] = v;

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

                                    r = srcPtr[_redOffs] >> rShRed;
                                    g = srcPtr[_greenOffs] >> rShGreen;
                                    b = srcPtr[_blueOffs] >> rShBlue;
                                    v = r << lShRed;
                                    v |= (g << lShGreen);
                                    v |= (b << lShBlue);

                                    dstPtr[0] = v;

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

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

    form := Form imageForm width:width height:height depth:usedDeviceDepth onDevice:aDevice.
    form isNil ifTrue:[
        'Depth32Image [warning]: display bitmap creation failed' errorPrintCR.
        ^ 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: / 27-05-2007 / 16:54:19 / cg"
    "Modified: / 27-08-2017 / 21:06:49 / cg"
! !

!Depth32Image methodsFor:'image manipulations'!

negative
    |bytes 
     index "{ Class: SmallInteger }"
     newImage newBytes nBytes r g b a
     alphaFirst|

    ((photometric ~~ #argb)
    and:[(photometric ~~ #rgba)
    and:[(photometric ~~ #xrgb)
    and:[(photometric ~~ #rgbx)
    and:[(photometric ~~ #rgb0)
    and:[(photometric ~~ #'0rgb')]]]]]) ifTrue:[
        ^ super negative.
    ].

    alphaFirst := (photometric == #argb)
                  or:[ (photometric == #xrgb) 
                  or:[ (photometric == #'0rgb') ]].

    bytes := self bits.

    newImage := self copy.
    nBytes := bytes size.
    newImage bits:(newBytes := ByteArray new:nBytes).
    index := 1.
    [index < nBytes] whileTrue:[
        alphaFirst ifTrue:[
            a := bytes at:index.
            newBytes at:index put:a.
            index := index + 1.
        ].

        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.

        alphaFirst ifFalse:[
            a := bytes at:index.
            newBytes at:index put:a.
            index := index + 1.
        ]
    ].
    ^ newImage

    "Modified (format): / 22-08-2017 / 17:13:38 / cg"
! !

!Depth32Image methodsFor:'initialization'!

initialize
    super initialize.
    samplesPerPixel := 4.
    bitsPerSample := #[8 8 8 8].

    "Created: / 27-05-2007 / 14:09:16 / cg"
    "Modified: / 30-01-2017 / 19:32:13 / stefan"
! !

!Depth32Image methodsFor:'magnification'!

hardAntiAliasedMagnifiedBy:scaleArg
    "return a new image magnified by scalePoint, aPoint.
     This interpolates pixels and is therefore much slower,
     but generates nicer looking magnifications."

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

    scalePoint := scaleArg asPoint. 
    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:[
        'Depth32Image [warning]: failed to allocate byteArray for image bits' errorPrintCR.
        ^ nil
    ].

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

    newImage := self species new.
    newImage
        width:newWidth
        height:newHeight
        photometric:photometric
        samplesPerPixel:samplesPerPixel
        bitsPerSample:bitsPerSample
        colorMap:nil
        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 _width4 = __intVal(__INST(width)) * 4;
    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 + (_width4 * _sR);

        for (_col = 0; _col <= _w; _col++) {
            unsigned int rHere, gHere, bHere, aHere;
            unsigned int rRight, gRight, bRight, aRight;
            unsigned int rRightBelow, gRightBelow, bRightBelow, aRightBelow;
            unsigned int rBelow, gBelow, bBelow, aBelow;
            unsigned int _r, _g, _b, _a;
            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 * 4);

            rHere = sP[0];
            gHere = sP[1];
            bHere = sP[2];
            aHere = sP[3];

            if (_sC < _oldW) {
                rRight = sP[0+4];
                gRight = sP[0+5];
                bRight = sP[0+6];
                aRight = sP[0+7];

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

            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;
            _a = ((aHere * wHere) + (aRight * wRight) + (aBelow * wBelow) + (aRightBelow * wRightBelow)) / sumW;

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

            _dstP += 4;
        }
    }
%}.

    ^ newImage

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

    "Created: / 02-06-1997 / 13:18:53 / cg"
    "Modified: / 30-08-2017 / 13:35:20 / cg"
!

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, byte4;
    int _pixels;
    OBJ w = __INST(width);

    if (__bothSmallInteger(srcStart, dstStart)
     && __bothSmallInteger(w, mX)
     && __isByteArrayLike(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);
	    byte4 = *(srcP+3);
	    srcP += 4;
	    for (i=_mag; i>0; i--) {
		*dstP = byte1;
		*(dstP+1) = byte2;
		*(dstP+2) = byte3;
		*(dstP+3) = byte4;
		dstP += 4;
	    }
	}
	RETURN (self);
    }
%}.
    super
	magnifyRowFrom:srcBytes offset:srcStart
	into:dstBytes offset:dstStart factor:mX

    "Created: / 28-05-2007 / 15:20:52 / cg"
! !

!Depth32Image methodsFor:'queries'!

alphaBitsOf:pixel
    "given a pixel-value, return the alpha component as byteValue (0..255)"

    photometric == #argb ifTrue:[
        "/ value is: aarrggbb
        ^ (pixel bitShift:-24) bitAnd:16rFF.   
    ].
    (photometric == #rgb) ifTrue:[
        "/ value is: 00rrggbb
        ^ 0
    ].
    (photometric == #xrgb) ifTrue:[
        "/ value is: FFrrggbb
        ^ 255       
    ].
    photometric == #rgba ifTrue:[
        "/ value is: rrggbbaa
        ^ pixel bitAnd:16rFF           
    ].
    photometric == #rgb0 ifTrue:[
        "/ value is: rrggbb00
        ^ 0           
    ].
    photometric == #rgbx ifTrue:[
        "/ value is: rrggbbFF
        ^ 255           
    ].

    ^ super alphaBitsOf:pixel.

    "Modified: / 22-08-2017 / 17:18:44 / cg"
!

alphaComponentOf:pixel
    "given a pixel-value, return the alpha component in percent (0..100)"

    ^ (self alphaBitsOf:pixel) * (100.0 / 255.0)
!

alphaMaskForPixelValue
    "return the mask used with translation from pixelValues to alphaBits.
     Determines the number of bits of alpha"

    ^ 16rFF

    "Modified (comment): / 21-02-2017 / 16:37:31 / cg"
!

alphaShiftForPixelValue
    "return the shift amount used with translation from pixelValues to alphaBits.
     That is the number of bits to shift the alpha value into the pixel value."

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ -24.    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ 0.    
    ].
    ^ super alphaShiftForPixelValue.

    "Modified: / 22-08-2017 / 17:19:36 / cg"
!

bitsPerPixel
    "return the number of bits per pixel"

    ^ 32

    "Created: 24.4.1997 / 19:00:28 / cg"
!

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

    ^ width * 32

    "Created: 24.4.1997 / 19:00:28 / cg"
!

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

    "Modified: / 30-01-2017 / 19:23:31 / stefan"
!

blueBitsOf:pixel
    "given a pixel-value, return the blue component as byteValue (0..255)"

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ pixel bitAnd:16rFF.    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ (pixel bitShift:-8) bitAnd:16rFF.    
    ].
    ^ super blueBitsOf:pixel.

    "Modified: / 22-08-2017 / 18:23:41 / cg"
!

blueComponentOf:pixel
    "given a pixel-value, return the blue component in percent (0..100)"

    ^ (self blueBitsOf:pixel) * (100.0 / 255.0)
!

blueMaskForPixelValue
    "return the mask used with translation from pixelValues to blueBits"

    ^ 16rFF
!

blueShiftForPixelValue
    "return the shift amount used with translation from pixelValues to blueBits"

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ 0.    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ -8
    ].
    ^ super blueShiftForPixelValue

    "Modified: / 22-08-2017 / 17:19:55 / cg"
!

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

    ^ width * 4.

    "Created: 24.4.1997 / 19:00:28 / cg"
!

greenBitsOf:pixel
    "given a pixel-value, return the green component as byteValue (0..255)"

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ (pixel bitShift:-8) bitAnd:16rFF.    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ (pixel bitShift:-16) bitAnd:16rFF.    
    ].
    ^ super greenBitsOf:pixel.

    "Modified: / 22-08-2017 / 18:23:41 / cg"
!

greenComponentOf:pixel
    "given a pixel-value, return the green component in percent (0..100)"

    ^ (self greenBitsOf:pixel) * (100.0 / 255.0)
!

greenMaskForPixelValue
    "return the mask used with translation from pixelValues to redBits"

    ^ 16rFF
!

greenShiftForPixelValue
    "return the shift amount used with translation from pixelValues to greenBits"

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ -8    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ -16.    
    ].
    ^ super greenShiftForPixelValue.
!

hasAlphaChannel
    "could be #rgb in 32 bits..."

    ^ (photometric == #argb) or:[photometric == #rgba]

    "Modified: / 21-02-2017 / 15:00:17 / cg"
!

numAlphaBits
    photometric == #argb ifTrue:[
        ^ 8.
    ].
    photometric == #rgba ifTrue:[
        ^ 8.
    ].
    ^ 0

    "Created: / 22-08-2017 / 17:38:59 / cg"
!

numBlueBits
    ^ 8

    "Created: / 22-08-2017 / 17:38:31 / cg"
!

numGreenBits
    ^ 8

    "Created: / 22-08-2017 / 17:38:28 / cg"
!

numRedBits
    ^ 8

    "Created: / 22-08-2017 / 17:38:25 / cg"
!

redBitsOf:pixel
    "given a pixel-value, return the red component as byteValue (0..255)"

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ (pixel bitShift:-16) bitAnd:16rFF.    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ (pixel bitShift:-24) bitAnd:16rFF.    
    ].
    ^ super redBitsOf:pixel.

    "Modified: / 22-08-2017 / 18:23:41 / cg"
!

redComponentOf:pixel
    "given a pixel-value, return the red component in percent (0..100)"

    ^ (self redBitsOf:pixel) * (100.0 / 255.0)
!

redMaskForPixelValue
    "return the mask used with translation from pixelValues to redBits"

    ^ 16rFF
!

redShiftForPixelValue
    "return the shift amount used with translation from pixelValues to redBits"

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ -16    
    ].
    ((photometric == #rgba) 
    or:[ (photometric == #rgbx) 
    or:[ (photometric == #rgb0)]]) ifTrue:[
        "/ rrggbbaa
        ^ -24.    
    ].
    ^ super redShiftForPixelValue.

    "Modified: / 22-08-2017 / 18:23:41 / cg"
!

rgbFromValue:pixelValue
    "given a pixel value, return the corresponding 24bit rgbValue (rrggbb, red is MSB)."

    ((photometric == #argb)
    or:[ (photometric == #rgb) 
    or:[ (photometric == #xrgb) ]])
     ifTrue:[
        "/ aarrggbb
        ^ pixelValue bitAnd:16rFFFFFF   
    ].

    ((photometric == #rgba) 
    or:[ photometric == #rgbx
    or:[ photometric == #rgb0]]) ifTrue:[
        "/ rrggbbaa
        ^ (pixelValue rightShift:8) bitAnd:16rFFFFFF       
    ].
    ^ super rgbFromValue:pixelValue.

    "Modified: / 22-08-2017 / 18:32:22 / cg"
!

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

    samplesPerPixel notNil ifTrue:[^ samplesPerPixel].
    ^ 4
!

valueFromRedBits:redBits greenBits:greenBits blueBits:blueBits
    (photometric == #rgba) ifTrue:[
        "/ alpha in low byte
        ^ (((((redBits bitShift:8) bitOr:greenBits) bitShift:8) bitOr:blueBits) bitShift:8) bitOr:16rFF
    ].
    (photometric == #argb) ifTrue:[
        "/ alpha in high byte
        ^ (((((redBits bitShift:8) bitOr:greenBits) bitShift:8) bitOr:blueBits)) bitOr:16rFF000000
    ].
    (photometric == #rgb) ifTrue:[
        "/ no alpha
        ^ (((redBits bitShift:8) bitOr:greenBits) bitShift:8) bitOr:blueBits
    ].
    ^ super valueFromRedBits:redBits greenBits:greenBits blueBits:blueBits.

    "Modified: / 22-08-2017 / 18:34:30 / cg"
!

valueFromRedBits:redBits greenBits:greenBits blueBits:blueBits alphaBits:alphaBits
    (photometric == #rgba) ifTrue:[
        "/ alpha in low byte
        ^ (((((redBits bitShift:8) bitOr:greenBits) bitShift:8) bitOr:blueBits) bitShift:8) bitOr:alphaBits
    ].
    (photometric == #argb) ifTrue:[
        "/ alpha in high byte
        ^ (((((redBits bitShift:8) bitOr:greenBits) bitShift:8) bitOr:blueBits)) bitOr:(alphaBits bitShift:24)
    ].
    (photometric == #rgb) ifTrue:[
        "/ no alpha
        ^ (((redBits bitShift:8) bitOr:greenBits) bitShift:8) bitOr:blueBits
    ].
    ^ super valueFromRedBits:redBits greenBits:greenBits blueBits:blueBits.

    "Created: / 05-09-2017 / 14:31:38 / cg"
! !

!Depth32Image class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !