UnboxedIntegerArray.st
author Claus Gittinger <cg@exept.de>
Thu, 09 Jun 2016 12:42:15 +0200
changeset 3903 5730e66fd49c
parent 3863 1ad2dc0cb100
child 4045 df87f891d9bc
permissions -rw-r--r--
class: HTMLPrinterStream changed: #initialize lazy package dependency

"
 COPYRIGHT (c) 2003 by eXept Software AG
              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:libbasic2' }"

"{ NameSpace: Smalltalk }"

AbstractNumberVector subclass:#UnboxedIntegerArray
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Arrayed'
!

!UnboxedIntegerArray class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2003 by eXept Software AG
              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
"
    An abstract superclass for all unboxed integer classes.
    In contrast to normal arrays (which store pointers to their elements),
    unboxedIntegerArrays store the values in a dense & compact way. 
    Since the representation fits corresponding underlying C-language representations,
    these are also useful to pass bulk data to c primitive code.

    [see also:]
        ByteArray WordArray BooleanArray FloatArray DoubleArray Array
        IntegerArray LongIntegerArray SignedLongIntegerArray

    [author:]
        Claus Gittinger
"
! !

!UnboxedIntegerArray class methodsFor:'queries'!

isAbstract
    "Return if this class is an abstract class.
     True is returned for UnboxedIntegerArray here; false for subclasses.
     Abstract subclasses must redefine this again."

    ^ self == UnboxedIntegerArray
!

maxVal
    "the maximum value which can be stored in instances of me"
    
    ^ self subclassResponsibility.
!

minVal
    "the minimum value which can be stored in instances of me"
    
    ^ self subclassResponsibility.
! !

!UnboxedIntegerArray methodsFor:'accessing'!

at:index
    "return the indexed instance variable with index, anInteger.
     Trigger an error if the receiver has no indexed instance variables.
     This method should NOT be redefined in any subclass (except with great care, for tuning)"

%{  /* NOCONTEXT */

    REGISTER int nbytes, indx;
    OBJ myClass;
    REGISTER char *pFirst;
    REGISTER int n;

    /*
     * notice the missing test for self being a nonNilObject -
     * this can be done since basicAt: is defined both in UndefinedObject
     * and SmallInteger
     */
    if (__isSmallInteger(index)) {
        myClass = __qClass(self);
        indx = __intVal(index) - 1;
        n /* nInstVars */ = __intVal(__ClassInstPtr(myClass)->c_ninstvars);
        n /* nInstBytes */ = OHDR_SIZE + __OBJS2BYTES__(n /* nInstVars */);
        nbytes = __qSize(self) - n /* nInstBytes */;
        pFirst = (char *)(__InstPtr(self)) + n /* nInstBytes */;

        switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
            case __MASKSMALLINT(WORDARRAY):
                /*
                 * unsigned 16bit ints
                 */
                /* Notice: the hard coded shifts are by purpose;
                 * it makes us independent of the short-size of the machine
                 */
                if ((unsigned)indx < (nbytes>>1)) {
                    unsigned short *sp;

                    sp = (unsigned short *)(pFirst + (indx<<1));
                    RETURN ( __MKSMALLINT( (INT)(*sp & 0xFFFF)) );
                }
                break;

            case __MASKSMALLINT(SWORDARRAY):
                /*
                 * signed 16bit ints
                 */
                /* Notice: the hard coded shifts are by purpose;
                 * it makes us independent of the short-size of the machine
                 */
                if ((unsigned)indx < (nbytes>>1)) {
                    short *ssp;

                    ssp = (short *)(pFirst + (indx<<1));
                    RETURN ( __MKSMALLINT( (INT)(*ssp) ));
                }
                break;

            case __MASKSMALLINT(LONGARRAY):
                /*
                 * unsigned 32bit ints
                 */
                /* Notice: the hard coded shifts are by purpose;
                 * it makes us independent of the int-size of the machine
                 */
                if ((unsigned)indx < (nbytes>>2)) {
                    unsigned int32 ul;
                    unsigned int32 *lp;

                    lp = (unsigned int32 *)(pFirst + (indx<<2));
                    ul = *lp;
#if __POINTER_SIZE__ == 8
                    {
                        unsigned  INT ull = (unsigned INT)ul;
                        RETURN ( __MKSMALLINT(ull) );
                    }
#else
                    if (ul <= _MAX_INT) {
                        RETURN ( __MKSMALLINT(ul) );
                    }
                    RETURN ( __MKULARGEINT(ul) );
#endif
                }
                break;

            case __MASKSMALLINT(SLONGARRAY):
                /*
                 * signed 32bit ints
                 */
                /* Notice: the hard coded shifts are by purpose;
                 * it makes us independent of the int-size of the machine
                 */
                if ((unsigned)indx < (nbytes>>2)) {
                    int32 *slp;
                    int32 l;

                    slp = (int32 *)(pFirst + (indx<<2));
                    l = *slp;
#if __POINTER_SIZE__ == 8
                    {
                        INT ll = (INT)l;
                        RETURN ( __MKSMALLINT(ll) );
                    }
#else
                    if (__ISVALIDINTEGER(l)) {
                        RETURN ( __MKSMALLINT(l) );
                    }
                    RETURN ( __MKLARGEINT(l) );
#endif
                }
                break;

            case __MASKSMALLINT(SLONGLONGARRAY):
                /*
                 * signed 64bit longlongs
                 */
#ifdef __NEED_LONGLONG_ALIGN
                if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
                    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));

                    pFirst += delta;
                    nbytes -= delta;
                }
#endif
                /* Notice: the hard coded shifts are by purpose;
                 * it makes us independent of the long/longlong-size of the machine
                 */
                if ((unsigned)indx < (nbytes>>3)) {
#if __POINTER_SIZE__ == 8
                    INT *slp, ll;

                    slp = (INT *)(pFirst + (indx<<3));
                    ll = *slp;
                    if (__ISVALIDINTEGER(ll)) {
                        RETURN ( __MKSMALLINT(ll) );
                    }
                    RETURN ( __MKLARGEINT(ll) );
#else
                    __int64__ *llp;

                    llp = (__int64__ *)(pFirst + (indx<<3));
                    RETURN (__MKINT64(llp));
#endif
                }
                break;

            case __MASKSMALLINT(LONGLONGARRAY):
                /*
                 * unsigned 64bit longlongs
                 */
#ifdef __NEED_LONGLONG_ALIGN
                if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
                    int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));

                    pFirst += delta;
                    nbytes -= delta;
                }
#endif
                /* Notice: the hard coded shifts are by purpose;
                 * it makes us independent of the long/longlong-size of the machine
                 */
                if ((unsigned)indx < (nbytes>>3)) {
#if __POINTER_SIZE__ == 8
                    unsigned INT *ulp, ul;

                    ulp = (unsigned INT *)(pFirst + (indx<<3));
                    ul = *ulp;
                    if (ul <= _MAX_INT) {
                        RETURN ( __MKSMALLINT(ul) );
                    }
                    RETURN ( __MKULARGEINT(ul) );
#else
                    __uint64__ *llp;

                    llp = (__uint64__ *)(pFirst + (indx<<3));
                    RETURN (__MKUINT64(llp));
#endif
                }
                break;
        }
    }
%}.
    ^ self indexNotIntegerOrOutOfBounds:index
!

byteAt:index
    "treating the receiver as a stream of bytes in native byteorder,
     return an individual byte"

    |lVal elementByteSize|

    elementByteSize := self class elementByteSize.

    lVal := self at:((index - 1) // elementByteSize) + 1.
    IsBigEndian ifTrue:[
        ^ lVal digitAt:(4 - ((index - 1) \\ elementByteSize)). 
    ].
    ^ lVal digitAt:((index - 1) \\ elementByteSize) + 1. 

    "
     (IntegerArray new:2)
        at:1 put:16r12345678;
        at:2 put:16r9abcdef0;
        byteAt:5      
    "

    "Created: / 27-02-2012 / 20:58:47 / cg"
! !

!UnboxedIntegerArray methodsFor:'printing'!

printOn:aStream base:radix showRadix:showRadix
    "append a printed representation to aStream in the given number base."

    (self class == WordArray or:[self class == LongIntegerArray]) 
    ifTrue:[    "/ care for subclasses
        aStream nextPutAll:'#('.
        self 
            do:[:word | word printOn:aStream base:radix showRadix:showRadix]
            separatedBy:[aStream space].
        aStream nextPut:$).
        ^ self
    ].
    ^ self printOn:aStream
! !

!UnboxedIntegerArray methodsFor:'queries'!

defaultElement
    ^ 0
! !

!UnboxedIntegerArray class methodsFor:'documentation'!

version
    ^ '$Header$'
! !