Depth32Image.st
author Claus Gittinger <cg@exept.de>
Fri, 21 Jan 2011 16:09:31 +0100
changeset 5679 455385b07655
parent 5474 037b18c68ac9
child 6066 62426e8110ae
permissions -rw-r--r--
added: #isReallyShown

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

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 images.
    Only the minimum protocol is implemented here; much more is
    needed for higher performance operations on depth32 images.
    (however, 32bit images are very seldom used, so falling back into the
    slow general methods from Image should not hurt too much ..)

    [author:]
        Claus Gittinger

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

!Depth32Image class methodsFor:'queries'!

defaultPhotometric
    "return the default photometric pixel interpretation"

    ^ #rgb

    "Created: / 27-05-2007 / 14:03:59 / cg"
    "Modified: / 06-06-2007 / 11:12:13 / 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'!

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"

    |pixelIndex "{ Class: SmallInteger }"|

    pixelIndex := (width * 4 * y) + 1 + (x * 4).

    "left pixel in high bits"
    ^ bytes doubleWordAt:pixelIndex MSB:true.

    "Created: 24.4.1997 / 19:00:28 / cg"
    "Modified: 24.4.1997 / 23:11:05 / cg"
!

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"

    |pixelIndex "{ Class: SmallInteger }"|

    pixelIndex := (width * 4 * y) + 1 + (x * 4).
    bytes isNil ifTrue:[
        self createPixelStore
    ].
    bytes doubleWordAt:pixelIndex put:aPixelValue MSB:true

    "Created: / 24-04-1997 / 19:00:28 / cg"
    "Modified: / 06-06-2007 / 12:20:57 / cg"
! !

!Depth32Image methodsFor:'converting rgb images'!

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

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

    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.

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

        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--) {
                            unsigned v;

                            v = srcPtr[0] << 0;
                            v |= (srcPtr[1] << 8);
                            v |= (srcPtr[2] << 16);
# ifdef __MSBFIRST
                            dstPtr[0] = srcPtr[0];
                            dstPtr[1] = srcPtr[1];
                            dstPtr[2] = srcPtr[2];
# else /* not MSB */
                            dstPtr[0] = srcPtr[2];
                            dstPtr[1] = srcPtr[1];
                            dstPtr[2] = srcPtr[0];
# 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[0] << lShRed;
                            v |= (srcPtr[1] << lShGreen);
                            v |= (srcPtr[2] << 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[0] >> rShRed;
                        g = srcPtr[1] >> rShGreen;
                        b = srcPtr[2] >> 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:[
        "/
        "/ 16 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;

            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[0] << lShRed;
                            v |= (srcPtr[1] << lShGreen);
                            v |= (srcPtr[2] << 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[0];
                            g = srcPtr[1];
                            b = srcPtr[2];
                            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];
                            g = srcPtr[4];
                            b = srcPtr[5];
                            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[0] >> rShRed;
                            g = srcPtr[1] >> rShGreen;
                            b = srcPtr[2] >> rShBlue;
                            v = r << lShRed;
                            v |= (g << lShGreen);
                            v |= (b << lShBlue);
# ifdef __MSBFIRST
                            ((short *)dstPtr)[0] = v;
# else /* 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[0] >> rShRed;
                                g = srcPtr[1] >> rShGreen;
                                b = srcPtr[2] >> rShBlue;
                                v = r << lShRed;
                                v |= (g << lShGreen);
                                v |= (b << lShBlue);
# ifdef __MSBFIRST
                                ((short *)dstPtr)[0] = v;
# else /* not MSB */
                                dstPtr[0] = (v>>8) & 0xFF;
                                dstPtr[1] = (v) & 0xFF;
# endif /* not MSB */
                                dstPtr += 2;
                                srcPtr += 4;
                            }
                            dstPtr += p;
                        }
                    }
                }
            }
%}.
        ] ifFalse:[
            "/
            "/ 32 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;

                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[0] << lShRed;
                                v |= (srcPtr[1] << lShGreen);
                                v |= (srcPtr[2] << 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[0] >> rShRed;
                                g = srcPtr[1] >> rShGreen;
                                b = srcPtr[2] >> rShBlue;
                                v = r << lShRed;
                                v |= (g << lShGreen);
                                v |= (b << lShBlue);
# ifdef __MSBFIRST
                                ((int *)dstPtr)[0] = v;
# else /* 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;

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

                                    dstPtr[0] = v;

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

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

    form := Form 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: / 29-05-2007 / 12:19:04 / cg"
! !

!Depth32Image methodsFor:'initialization'!

initialize
    super initialize.
    samplesPerPixel := 4. 
    bitsPerSample := #(8 8 8 8).

    "Created: / 27-05-2007 / 14:09:16 / cg"
! !

!Depth32Image methodsFor:'magnification'!

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

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

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

    ^ width * 4.

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

hasAlphaChannel
    ^ true
! !

!Depth32Image class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Depth32Image.st,v 1.11 2009-11-05 14:37:08 stefan Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libview/Depth32Image.st,v 1.11 2009-11-05 14:37:08 stefan Exp $'
! !