Array.st
author Claus Gittinger <cg@exept.de>
Sun, 30 Jun 1996 13:02:29 +0200
changeset 1498 5083a52b1718
parent 1422 9a0b792f2953
child 1688 8a42db1eea60
permissions -rw-r--r--
limit displayString to 5000 characters

"
 COPYRIGHT (c) 1989 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.
"

ArrayedCollection variableSubclass:#Array
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Arrayed'
!

!Array  class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 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
"
    Instances of Array store general objects; the arrays size is fixed, 
    therefore add:/remove: are not allowed. 
    (actually, #add: is implemented for compatibility with smalltalks which 
     provide it, but it is very slow and outputs an annoying warning message ...)

    Access to the individual elements is via an integer index,
    using the well-known access messages #at: and #at:put:.

    Since Arrays are used very often in the system, some methods have been 
    tuned by reimplementing them as primitives. Also, the compiler inline-codes
    some operations (especially: the above accessing messages).

    Notice that Array is a built-in class 
    (i.e. the VM knows about its representation). 
    Therefore it is NOT possible to add named instance variables or change 
    Arrays inheritance. 
    However, subclassing is allowed of course 
    - even with added named instance variables.

    Literal arrays (i.e. array-constants) are entered in source as:

        #( element1 element2 ... element-n)

    where each element must be itself a literal constant.
    Array, symbol and byteArray constants within an array can be written
    without the initial #-character.
    In addition, true, false and nil are also allowed as array-literal.

    Examples:
      #(1 2 3)                -> 3 elements: 1, 2 and 3
      #('foo' 2 (1 2))        -> 3 elements: a String, 2 and anotherArray
      #('foo' #(1 2) #foo)    -> 3 elements: a String, another array and a symbol
      #('foo' (1 2) foo)      -> same as above
      #(nil true #true)       -> 3 elements: nil, true and a symbol (watch out)
      #(two [3 3 3] (4 4 4))  -> 3 elements: a symbol, a byteArray and another array


    [author:]
        Claus Gittinger

    [see also:]
        OrderedCollection
        ByteArray FloatArray DoubleArray
        String
"
! !

!Array  class methodsFor:'instance creation'!

basicNew:anInteger
    "return an instance of myself with anInteger indexed variables.
     Since Array-creation is so common (all other collections use them),
     it seems worth to have a specially tuned version here."

%{  /* NOCONTEXT */

    OBJ newobj;
    unsigned INT instsize, nInstVars;
    INT nindexedinstvars;
    REGISTER OBJ *op;

    if (__isSmallInteger(anInteger)) {
	nindexedinstvars = __intVal(anInteger);
	if (nindexedinstvars >= 0) {
	    nInstVars = __intVal(__ClassInstPtr(self)->c_ninstvars);

	    nInstVars += nindexedinstvars;
	    instsize = OHDR_SIZE + __OBJS2BYTES__(nInstVars);
	    if (__CanDoQuickAlignedNew(instsize)) {
		/*
		 * the most common case
		 */
		__qCheckedAlignedNew(newobj, instsize);
	ok: ;
		__InstPtr(newobj)->o_class = self;
		__qSTORE(newobj, self);

#if defined(memset4) && defined(FAST_ARRAY_MEMSET4)
		memset4(__InstPtr(newobj)->i_instvars, nil, nInstVars);
#else
# if !defined(NEGATIVE_ADDRESSES)
		/*
		 * knowing that nil is 0
		 */
#ifdef XXmips
# undef FAST_ARRAY_MEMSET_DOUBLES_UNROLLED
# undef FAST_ARRAY_MEMSET_LONGLONG_UNROLLED
/* seems to be slightly faster */
# define FAST_ARRAY_MEMSET
#endif
#ifdef sparc
# define FAST_ARRAY_MEMSET_DOUBLES_UNROLLED
#endif

#  if defined(FAST_ARRAY_MEMSET_DOUBLES_UNROLLED)
		op = __InstPtr(newobj)->i_instvars;
		if (nInstVars > 8) {
		    *op++ = nil;    /* for alignment */
		    nInstVars--;
		    while (nInstVars >= 8) {
			*(double *)op = 0.0;
			((double *)op)[1] = 0.0;
			((double *)op)[2] = 0.0;
			((double *)op)[3] = 0.0;
			op += 8;
			nInstVars -= 8;
		    }
		}
		while (nInstVars) {
		    *op++ = 0;
		    nInstVars--;
		}
#  else
#   if defined(FAST_ARRAY_MEMSET_LONGLONG_UNROLLED)
		op = __InstPtr(newobj)->i_instvars;
		if (nInstVars > 8) {
		    *op++ = nil;    /* for alignment */
		    nInstVars--;
		    while (nInstVars >= 8) {
			*(long long *)op = 0;
			((long long *)op)[1] = 0;
			((long long *)op)[2] = 0;
			((long long *)op)[3] = 0;
			op += 8;
			nInstVars -= 8;
		    }
		}
		while (nInstVars) {
		    *op++ = 0;
		    nInstVars--;
		}
#   else
#    if defined(FAST_ARRAY_MEMSET)
		memset(__InstPtr(newobj)->i_instvars, 0, instsize - OHDR_SIZE);
#    else
		op = __InstPtr(newobj)->i_instvars;
		while (nInstVars--)
		    *op++ = nil;
#    endif
#   endif
#  endif
# else
		op = __InstPtr(newobj)->i_instvars;
		while (nInstVars--)
		    *op++ = nil;
# endif
#endif
		RETURN ( newobj );
	    } else {
		/*
		 * a GC will happen ...
		 * have to protect all context stuff
		 * (especially for self, but also for backtrace in case of
		 *  allocation failure)
		 */
		__PROTECT_CONTEXT__
		newobj = __new(instsize);
		__UNPROTECT_CONTEXT__
		if (newobj != nil) {
		    goto ok;
		}
	    }
	}
    }
%}.
    "
     arrive here if something went wrong ...
     figure out what it was
    "
    (anInteger isMemberOf:SmallInteger) ifFalse:[
	"
	 the argument is either not an integer,
	 or a LargeInteger (which means that its definitely too big)
	"
	self error:'argument to new: must be Integer'.
	^ nil
    ].
    (anInteger < 0) ifTrue:[
	"
	 the argument is negative,
	"
	self error:'bad (negative) argument to new:'.
	^ nil
    ].
    "
     memory allocation failed.
     When we arrive here, there was no memory, even after
     a garbage collect. 
     This means, that the VM wanted to get some more memory from the 
     Operatingsystem, which was not kind enough to give it.
     Bad luck - you should increase the swap space on your machine.
    "
    ^ ObjectMemory allocationFailureSignal raise.
!

new:anInteger
    "return an instance of myself with anInteger indexed variables.
     Redefined here to save a few cycles when executed.
     (Since this is often called, its worth giving it an extra ilc-slot.
      Future versions of stc will do this automatically.)"

    ^ self basicNew:anInteger

    "Modified: 23.4.1996 / 15:52:15 / cg"
! !

!Array  class methodsFor:'queries'!

isBuiltInClass
    "return true if this class is known by the run-time-system.
     Here, true is returned for myself, false for subclasses."

    ^ self == Array

    "Modified: 23.4.1996 / 15:55:06 / cg"
! !

!Array methodsFor:'accessing'!

at:index
    "return the indexed instance variable with index, anInteger.
     Reimplemented here to avoid the additional at:->basicAt: send
     (which we can do here, since at: is obviously not redefined in a subclass).
     This method is the same as basicAt:."

%{  /* NOCONTEXT */

    REGISTER int indx;
    REGISTER OBJ slf;
    REGISTER unsigned int nIndex;
    REGISTER OBJ cls;

    if (__isSmallInteger(index)) {
	indx = __intVal(index) - 1;
	slf = self;

	/* 
	 * thanks to Patterson/Hennesey - this can be done with a single
	 * compare ...
	 */
	nIndex = __BYTES2OBJS__(__qSize(slf) - OHDR_SIZE);
	if ((cls = __qClass(slf)) != Array)
	    indx += __intVal(__ClassInstPtr(cls)->c_ninstvars);
	if ((unsigned)indx < (unsigned)nIndex) {
	    RETURN ( __InstPtr(slf)->i_instvars[indx] );
	}
    }
%}.
    ^ super at:index
!

at:index put:anObject
    "store the 2nd arg, anObject as indexed instvar with index, anInteger.
     Returns anObject (sigh).
     Reimplemented here to avoid the additional at:put:->basicAt:put: send
     (which we can do here, since at: is obviously not redefined in a subclass).
     This method is the same as basicAt:put:."

%{  /* NOCONTEXT */

    REGISTER int indx;
    REGISTER OBJ slf;
    REGISTER unsigned int nIndex;
    REGISTER OBJ cls;

    if (__isSmallInteger(index)) {
        indx = __intVal(index) - 1;
        slf = self;

        /* thanks to Patterson/Hennesey - this can be done with a single
         * compare ...
         */
        nIndex = __BYTES2OBJS__(__qSize(slf) - OHDR_SIZE);
        if ((cls = __qClass(slf)) != Array)
            indx += __intVal(__ClassInstPtr(cls)->c_ninstvars);
        if ((unsigned)indx < (unsigned)nIndex) {
            __InstPtr(slf)->i_instvars[indx] = anObject;
            __STORE(slf, anObject);
            RETURN ( anObject );
        }
    }
%}.
    ^ super at:index put:anObject

    "Modified: 19.4.1996 / 11:16:42 / cg"
!

basicAt:index
    "return the indexed instance variable with index, anInteger
     - added here for speed"

%{  /* NOCONTEXT */

    REGISTER int indx;
    REGISTER OBJ slf;
    REGISTER unsigned int nIndex;
    REGISTER OBJ cls;

    if (__isSmallInteger(index)) {
	indx = __intVal(index) - 1;
	slf = self;

	/* 
	 * thanks to Patterson/Hennesey - this can be done with a single
	 * compare ...
	 */
	nIndex = __BYTES2OBJS__(__qSize(slf) - OHDR_SIZE);
	if ((cls = __qClass(slf)) != Array)
	    indx += __intVal(__ClassInstPtr(cls)->c_ninstvars);
	if ((unsigned)indx < (unsigned)nIndex) {
	    RETURN ( __InstPtr(slf)->i_instvars[indx] );
	}
    }
%}
.
    ^ super basicAt:index
!

basicAt:index put:anObject
    "store the 2nd arg, anObject as indexed instvar with index, anInteger.
     Returns anObject (sigh).
     - added here for speed"

%{  /* NOCONTEXT */

    REGISTER int indx;
    REGISTER OBJ slf;
    REGISTER unsigned int nIndex;
    REGISTER OBJ cls;

    if (__isSmallInteger(index)) {
        indx = __intVal(index) - 1;
        slf = self;

        /* 
         * thanks to Patterson/Hennesey - this can be done with a single
         * compare ...
         */
        nIndex = __BYTES2OBJS__(__qSize(slf) - OHDR_SIZE);
        if ((cls = __qClass(slf)) != Array)
            indx += __intVal(__ClassInstPtr(cls)->c_ninstvars);
        if ((unsigned)indx < (unsigned)nIndex) {
            __InstPtr(slf)->i_instvars[indx] = anObject;
            __STORE(slf, anObject);
            RETURN ( anObject );
        }
    }
%}
.
    ^ super basicAt:index put:anObject

    "Modified: 19.4.1996 / 11:14:26 / cg"
!

basicSize
    "return the number of indexed elements in the receiver"

%{  /* NOCONTEXT */
    REGISTER OBJ slf = self;

    RETURN ( __MKSMALLINT(__arraySize(slf) - __intVal(__ClassInstPtr(__qClass(slf))->c_ninstvars) ));
%}
!

size
    "return the number of indexed elements in the receiver.
     Reimplemented here to avoid the additional size->basicSize send
     (which we can do here, since size is obviously not redefined in a subclass).
     This method is the same as basicSize."

%{  /* NOCONTEXT */
    REGISTER OBJ slf = self;

    RETURN ( __MKSMALLINT(__arraySize(slf) - __intVal(__ClassInstPtr(__qClass(slf))->c_ninstvars) ));
%}
! !

!Array methodsFor:'converting'!

asArray
    "return the receiver as an array - thats the receiver itself"

    "could be an instance of a subclass..."
    self class == Array ifTrue:[
        ^ self
    ].
    ^ super asArray

    "Modified: 22.4.1996 / 12:42:09 / cg"
! !

!Array methodsFor:'copying'!

copyWith:something
    "return a new collection containing the receivers elements
     and the single new element, newElement. 
     This is different from concatentation, which expects another collection
     as argument, but equivalent to copy-and-addLast.
     Reimplemented for speed if receiver is an Array.
     (since the inherited copyWith uses replaceFromTo:, which is also
      tuned, it is questionable, if we need this)"

%{  /* NOCONTEXT */
    OBJ nObj, element;
    unsigned int sz;
    unsigned int nIndex;
    REGISTER OBJ *srcP, *dstP;
    REGISTER int spc;

    if (__qClass(self) == Array) {
	sz = __qSize(self) + sizeof(OBJ);
	__PROTECT2__(something, self);
	__qAlignedNew(nObj, sz, __context);
	__UNPROTECT2__(self, something);

	if (nObj) {
	    __InstPtr(nObj)->o_class = Array;

	    nIndex = __BYTES2OBJS__(sz - OHDR_SIZE - sizeof(OBJ));
	    /* 
	     * sorry: 
	     * cannot use bcopy, since we must take care of stores ... 
	     * could check for: notRemembered + inOld + notLifoRem
	     *                  + not incrGCRunning
	     * but copyWith: is not heavily used by real programmers ...
	     */
	    spc = __qSpace(nObj);
	    srcP = __ArrayInstPtr(self)->a_element;
	    dstP = __ArrayInstPtr(nObj)->a_element;
#ifdef UNROLL_LOOPS
	    while (nIndex >= 4) {
		element = srcP[0];
		dstP[0] = element;
		__STORE_SPC(nObj, element, spc);
		element = srcP[1];
		dstP[1] = element;
		__STORE_SPC(nObj, element, spc);
		element = srcP[2];
		dstP[2] = element;
		__STORE_SPC(nObj, element, spc);
		element = srcP[3];
		dstP[3] = element;
		__STORE_SPC(nObj, element, spc);
		srcP += 4;
		dstP += 4;
		nIndex -= 4;
	    }
#endif
	    while (nIndex--) {
		element = *srcP++;
		*dstP++ = element;
		__STORE_SPC(nObj, element, spc);
	    }
	    *dstP = something;
	    __STORE_SPC(nObj, something, spc);
	    RETURN ( nObj );
	}
    }
%}
.
    ^ super copyWith:something
! !

!Array methodsFor:'enumerating'!

addAllTo:aCollection
    "add all elements of the receiver to aCollection.
     return aCollection."

    |stop "{ Class: SmallInteger }"|

    stop := self size.
    1 to:stop do:[:idx |
	aCollection add:(self at:idx)
    ].
    ^ aCollection
!

do:aBlock
    "evaluate the argument, aBlock for each element in the collection.
     - reimplemented for speed"

    |home sz "{ Class: SmallInteger }"|

    sz := self size.
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    unsigned int nIndex;
    static struct inlineCache val = _ILC1;
    REGISTER OBJ rHome;
    int actualSize;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    actualSize = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    nIndex = index + __intVal(sz);
    if (nIndex <= actualSize) {

        if (__isBlockLike(aBlock)
         && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
         && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
	    for (; index < nIndex; index++) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);

	        (*codeVal)(aBlock, CON_COMMA  __InstPtr(self)->i_instvars[index]);
	    } 
#else
	    home = __BlockInstPtr(aBlock)->b_home;
	    rHome = home;
	    if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
	        /*
	         * home will not move - keep in a fast register
	         */
# if defined(UNROLL_LOOPS)
	        {
		    int i4;

		    while ((i4 = index+4) < nIndex) {
		        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
		        (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index]);
		        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
		        (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index+1]);
		        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
		        (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index+2]);
		        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
		        (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index+3]);
		        index = i4;
		    }
	        }
# endif
	        for (; index < nIndex; index++) {
		    if (InterruptPending != nil) __interruptL(@line COMMA_CON);

		    (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index]);
	        } 
	    } else {
	        for (; index < nIndex; index++) {
		    if (InterruptPending != nil) __interruptL(@line COMMA_CON);

		    (*codeVal)(home, CON_COMMA  __InstPtr(self)->i_instvars[index]);
	        } 
	    } 
#endif
        } else {
	    for (; index < nIndex; index++) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);

	        (*val.ilc_func)(aBlock, 
			        @symbol(value:), 
			        CON_COMMA  nil, &val, 
			        __InstPtr(self)->i_instvars[index]);
	    } 
        }
	RETURN (self );
    }
%}.
    ^ super do:aBlock
!

from:start to:stop do:aBlock
    "evaluate the argument, aBlock for the elements starting at index start
     up to (and including) stop in the collection.
     - reimplemented for speed"

    |home|
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    REGISTER OBJ rHome;
    int nIndex, nInsts;
    static struct inlineCache val = _ILC1;
    int indexLow, indexHigh;

    if (__bothSmallInteger(start, stop)) {
	indexLow = __intVal(start);
	if (indexLow > 0) {
	    indexHigh = __intVal(stop);
	    if (__qClass(self) != @global(Array)) {
		nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
		indexLow += nInsts;
		indexHigh += nInsts;
	    }
	    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
	    if (indexHigh <= nIndex) {
		indexLow--;
		indexHigh--;
		if (__isBlockLike(aBlock)
		 && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
		 && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
		    for (index=indexLow; index <= indexHigh; index++) {
			if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			(*codeVal)(aBlock, CON_COMMA  __InstPtr(self)->i_instvars[index]);
		    } 
#else
		    home = __BlockInstPtr(aBlock)->b_home;
		    rHome = home;
		    if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
			index = indexLow;
# if defined(UNROLL_LOOPS)
			{
			    int i4;

			    while ((i4 = index+4) <= indexHigh) {
				if (InterruptPending != nil) __interruptL(@line COMMA_CON);
				(*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index]);
				if (InterruptPending != nil) __interruptL(@line COMMA_CON);
				(*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index+1]);
				if (InterruptPending != nil) __interruptL(@line COMMA_CON);
				(*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index+2]);
				if (InterruptPending != nil) __interruptL(@line COMMA_CON);
				(*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index+3]);
				index = i4;
			    }
			}
# endif
			for (; index <= indexHigh; index++) {
			    if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			    (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index]);
			} 
		    } else {
			for (index=indexLow; index <= indexHigh; index++) {
			    if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			    (*codeVal)(home, CON_COMMA  __InstPtr(self)->i_instvars[index]);
			} 
		    }
#endif
		} else {
		    for (index=indexLow; index <= indexHigh; index++) {
			if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			(*val.ilc_func) (aBlock, 
					 @symbol(value:), 
					 CON_COMMA  nil, &val, 
					 __InstPtr(self)->i_instvars[index]);
		    } 
		}
	    }
	    RETURN ( self );
	}
    }
%}.
    ^ super from:start to:stop do:aBlock
!

from:start to:stop reverseDo:aBlock
    "evaluate the argument, aBlock for the elements starting at index start
     up to (and including) stop in the collection. Step in reverse order.
     - reimplemented for speed"

    |home|
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    REGISTER OBJ rHome;
    int nIndex;
    static struct inlineCache val = _ILC1;
    int indexLow, indexHigh;

    if (__bothSmallInteger(start, stop)
     && (__qClass(self) == @global(Array))) {
	indexLow = __intVal(start);
	if (indexLow > 0) {
	    indexHigh = __intVal(stop);
	    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
	    if (indexHigh <= nIndex) {
		indexLow--;
		indexHigh--;
		if (__isBlockLike(aBlock)
		 && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
		 && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
		    for (index=indexHigh; index >= indexLow; index--) {
			if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			(*codeVal)(aBlock, CON_COMMA  __InstPtr(self)->i_instvars[index]);
		    } 
#else
		    home = __BlockInstPtr(aBlock)->b_home;
		    rHome = home;
		    if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
			for (index=indexHigh; index >= indexLow; index--) {
			    if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			    (*codeVal)(rHome, CON_COMMA  __InstPtr(self)->i_instvars[index]);
			} 
		    } else {
			for (index=indexHigh; index >= indexLow; index--) {
			    if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			    (*codeVal)(home, CON_COMMA  __InstPtr(self)->i_instvars[index]);
			} 
		    }
#endif
		} else {
		    for (index=indexHigh; index >= indexLow; index--) {
			if (InterruptPending != nil) __interruptL(@line COMMA_CON);
			(*val.ilc_func) (aBlock, 
					 @symbol(value:), 
					 CON_COMMA nil, &val, 
					 __InstPtr(self)->i_instvars[index]);
		    } 
		}
	    }
	    RETURN ( self );
	}
    }
%}.
    ^ super from:start to:stop reverseDo:aBlock
!

keysAndValuesDo:aBlock
    "evaluate the argument, aBlock for each element in the collection.
     Pass both index and element to the block.
     - reimplemented for speed"

    |home sz "{ Class: SmallInteger }" |

    sz := self size.
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    unsigned int nIndex;
    static struct inlineCache val2 = _ILC2;
    REGISTER OBJ rHome;
    int actualSize;

    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);

    actualSize = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    nIndex = index + __intVal(sz);

    if (nIndex <= actualSize) {
        if (__isBlockLike(aBlock)
         && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
         && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(2))) {
#ifdef NEW_BLOCK_CALL
	    for (; index < nIndex; index++) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);

	        (*codeVal)(aBlock, CON_COMMA  __MKSMALLINT(index+1),
					      __InstPtr(self)->i_instvars[index]);
	    } 
#else
	    home = __BlockInstPtr(aBlock)->b_home;
	    rHome = home;
	    if ((rHome == nil) || (__qSpace(rHome) >= STACKSPACE)) {
	        /*
	         * home will not move - keep in a fast register
	         */
	        while (index < nIndex) {
		    if (InterruptPending != nil) __interruptL(@line COMMA_CON);

		    index++;
		    (*codeVal)(rHome, CON_COMMA  __MKSMALLINT(index),
					         __InstPtr(self)->i_instvars[index-1]);
	        } 
	    } else {
	        while (index < nIndex) {
		    if (InterruptPending != nil) __interruptL(@line COMMA_CON);

		    index++;
		    (*codeVal)(home, CON_COMMA  __MKSMALLINT(index),
					        __InstPtr(self)->i_instvars[index-1]);
	        } 
	    } 
#endif
        } else {
	    while (index < nIndex) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);

	        index++;
	        (*val2.ilc_func)(aBlock, 
			        @symbol(value:value:), 
			        CON_COMMA  nil, &val2,
			        __MKSMALLINT(index),
			        __InstPtr(self)->i_instvars[index-1]);
	    } 
        }
	RETURN (self);
    }
%}.
    ^ super keysAndValuesDo:aBlock
!

reverseDo:aBlock
    "evaluate the argument, aBlock for each element in the collection in reverse order.
     - reimplemented for speed"

    |home sz "{ Class: SmallInteger }" |

    sz := self size.
%{
    REGISTER OBJFUNC codeVal;
    REGISTER int index;
    unsigned int nIndex;
    int endIndex;
    static struct inlineCache val = _ILC1;
    int actualSize;

    endIndex = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    actualSize = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    nIndex = endIndex + __intVal(sz);

    if (nIndex <= actualSize) {
        if (__isBlockLike(aBlock)
         && ((codeVal = __BlockInstPtr(aBlock)->b_code) != (OBJFUNC)nil)
         && (__BlockInstPtr(aBlock)->b_nargs == __MKSMALLINT(1))) {
#ifdef NEW_BLOCK_CALL
	    for (index=nIndex-1; index >= endIndex; index--) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
	        (*codeVal)(aBlock, CON_COMMA  __InstPtr(self)->i_instvars[index]);
	    } 
#else
	    home = __BlockInstPtr(aBlock)->b_home;
	    for (index=nIndex-1; index >= endIndex; index--) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
	        (*codeVal)(home, CON_COMMA  __InstPtr(self)->i_instvars[index]);
	    } 
#endif
        } else {
	    for (index=nIndex-1; index >= endIndex; index--) {
	        if (InterruptPending != nil) __interruptL(@line COMMA_CON);
	        (*val.ilc_func)(aBlock, 
			        @symbol(value:), 
			        CON_COMMA  nil, &val, 
			        __InstPtr(self)->i_instvars[index]);
	    } 
	}
	RETURN (self);
    }
%}.
    ^ super reverseDo:aBlock
!

traverse:aBlock
    "Evaluate aBlock for every element that is not an Array, 
     and recursively traverse Arrays.
     Implemented here to support better search for selectors in
     literal arrays - might be a good idea to move it up in the collection
     hierarchy, since this may be a useful method for other collections
     as well."

    self do: [:el |
        el isArray
            ifTrue: [el traverse: aBlock]
            ifFalse: [aBlock value: el]]

    "
     example: flattening an Array:

     |s|

     s := WriteStream on:Array new.
     #(1 2 (3 (4 5 (6 7) 8) 9 10) 11 (12 (13)) 14) traverse:[:el | s nextPut:el].
     s contents 
    "
    "
     example: deep search

     #(1 2 (3 (4 5 (6 7) 8) 9 10) 11 (12 (13)) 14) traverse:[:el | 
        el == 10 ifTrue:[Transcript showCR:'found']
     ]
    "

    "Modified: 26.3.1996 / 17:08:10 / cg"
! !

!Array methodsFor:'filling & replacing'!

from:index1 to:index2 put:anObject
    "reimplemented for speed if receiver is an Array"

%{  /* NOCONTEXT */

    REGISTER int index;
    unsigned int nIndex;
    unsigned int endIndex;
    REGISTER OBJ *dst;

    if ((__qClass(self) == Array)
     && __bothSmallInteger(index1, index2)) {
	index = __intVal(index1) - 1;
	if (index >= 0) {
	    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
	    endIndex = __intVal(index2) - 1;
	    if ((endIndex >= index) && (endIndex < nIndex)) {
		dst = &(__InstPtr(self)->i_instvars[index]);
#ifdef memset4
		memset4(dst, anObject, (endIndex-index+1));
		__STORE(self, anObject);
#else
		if ((INT)anObject == 0) {
		    memset(dst, 0, __OBJS2BYTES__(endIndex-index+1));
		} else {
# if defined(UNROLL_LOOPS)
		    {
			int i8;

			while ((i8 = index + 8) <= endIndex) {
			    dst[0] = anObject;
			    dst[1] = anObject;
			    dst[2] = anObject;
			    dst[3] = anObject;
			    dst[4] = anObject;
			    dst[5] = anObject;
			    dst[6] = anObject;
			    dst[7] = anObject;
			    dst += 8;
			    index = i8;
			}
		    }
# endif
		    for (; index <= endIndex; index++) {
			*dst++ = anObject;
		    }
		    __STORE(self, anObject);
		}
#endif
		RETURN ( self );
	    }
	}
    }
%}.
    ^ super from:index1 to:index2 put:anObject
!

replaceFrom:start to:stop with:aCollection startingAt:repStart
    "replace elements in the receiver between index start and stop,
     with elements  taken from replacementCollection starting at repStart.
     Reimplemented for speed if both receiver and aCollection are Arrays"

%{  /* NOCONTEXT */

    unsigned int nIndex;
    unsigned int repNIndex;
    int startIndex, stopIndex;
    REGISTER OBJ *src;
    REGISTER OBJ *dst;
    int repStopIndex;
    REGISTER int repStartIndex;
    REGISTER OBJ t;
    REGISTER int count;

    
    if ((__ClassInstPtr(__qClass(self))->c_ninstvars == __MKSMALLINT(0))
     && (((t = __Class(aCollection)) == Array) || (t == __qClass(self)))
     && __bothSmallInteger(start, stop)
     && __isSmallInteger(repStart)) {
        startIndex = __intVal(start) - 1;
        if (startIndex >= 0) {
            nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
            stopIndex = __intVal(stop) - 1;
            count = stopIndex - startIndex + 1;
            if (count == 0) {
                RETURN ( self );
            }
            if ((count > 0) && (stopIndex < nIndex)) {
                repStartIndex = __intVal(repStart) - 1;
                if (repStartIndex >= 0) {
                    repNIndex = __BYTES2OBJS__(__qSize(aCollection)-OHDR_SIZE);
                    repStopIndex = repStartIndex + (stopIndex - startIndex);
                    if (repStopIndex < repNIndex) {
                        src = &(__InstPtr(aCollection)->i_instvars[repStartIndex]);
                        dst = &(__InstPtr(self)->i_instvars[startIndex]);
                        if (aCollection == self) {
                            /* 
                             * no need to check stores if copying
                             * from myself
                             */
                            /* 
                             * take care of overlapping copy
                             * do not depend on memset being smart enough
                             * (some are not ;-)
                             */
                            if (src < dst) {
                                /* must do a reverse copy */
                                src += count;
                                dst += count;
#if defined(UNROLL_LOOPS)
                                while (count > 8) {
                                    dst[-1] = src[-1];
                                    dst[-2] = src[-2];
                                    dst[-3] = src[-3];
                                    dst[-4] = src[-4];
                                    dst[-5] = src[-5];
                                    dst[-6] = src[-6];
                                    dst[-7] = src[-7];
                                    dst[-8] = src[-8];
                                    dst -= 8; src -= 8;
                                    count -= 8;
                                }
#endif
                                while (count-- > 0) {
                                    *--dst = *--src;
                                }
                                RETURN ( self );
                            }
#ifdef bcopy4
                            bcopy4(src, dst, count);
#else
# ifdef FAST_MEMCPY
                            bcopy(src, dst, __OBJS2BYTES__(count));
# else
                            while (count--) {
                                *dst++ = *src++;
                            }
# endif
#endif
                        } else {
                            REGISTER int spc;

                            spc = __qSpace(self);
#if defined(UNROLL_LOOPS)
                            while (count >= 4) {
                                t = src[0]; dst[0] = t; __STORE_SPC(self, t, spc);
                                t = src[1]; dst[1] = t; __STORE_SPC(self, t, spc);
                                t = src[2]; dst[2] = t; __STORE_SPC(self, t, spc);
                                t = src[3]; dst[3] = t; __STORE_SPC(self, t, spc);
                                count -= 4; src += 4; dst += 4;
                            }
#endif
                            while (count-- > 0) {
                                t = *src++;
                                *dst++ = t;
                                __STORE_SPC(self, t, spc);
                            }
                        }
                        RETURN ( self );
                    }
                }
            }
        }
    }
%}.
    ^ super replaceFrom:start to:stop with:aCollection startingAt:repStart

    "Modified: 13.4.1996 / 12:17:13 / cg"
! !

!Array methodsFor:'printing & storing'!

displayString
    "return a printed representation of the receiver for displaying"

    |s sz|

    (self isLiteral) ifTrue:[
        s := WriteStream on:String new.
        s writeLimit:5000.

        WriteStream writeErrorSignal handle:[:ex |
            s writeLimit:nil.
            s nextPutAll:' ...'
        ] do:[
            s nextPutAll:'#('.
            sz := self size.
            self keysAndValuesDo:[:idx :element | 
                                    s nextPutAll:element displayString. 
                                    idx ~~ sz ifTrue:[s space]
                                 ].
        ].
        s writeLimit:nil.
        s nextPutAll:')'.
        ^ s contents
    ].
    ^ super displayString

    "
     #(1 2 3 4) displayString
     #(1 2 3 4) printString    
     (Array new:10000) displayString    
    "

    "Modified: 30.6.1996 / 13:00:08 / cg"
!

storeOn:aStream
    "append a printed representation of the receiver to aStream,
     which allows reconstructing it via readFrom:.
     Redefined to output a somewhat more user friendly string."

    self isLiteral ifTrue:[
        aStream nextPutAll:'#('.
        self do:[:element | element storeOn:aStream. aStream space].
        aStream nextPutAll:')'
    ] ifFalse:[
        super storeOn:aStream
    ]

    "
     #(1 2 $a 'hello') storeString 
     #(1 2 $a [1 2 3]) storeString 
    "

    "Created: 20.11.1995 / 11:16:58 / cg"
! !

!Array methodsFor:'queries'!

isArray
    "return true, if the receiver is some kind of array (or weakArray etc).
     true is returned here"

    ^ true
!

isLiteral
    "return true, if the receiver can be used as a literal
     (i.e. can be used in constant arrays)"

    "/ no, simply returning true here is a mistake:
    "/ it could be a subclass of Array 
    "/ (of which the compiler does not know at all ...)

    self class == Array ifFalse:[^ false].

    "/
    "/ care for recursive arrays ...
    "/
    thisContext isRecursive ifTrue:[^ false].
    self do:[:element |
        element isLiteral ifFalse:[^ false]
    ].
    ^ true

    "Modified: 22.4.1996 / 12:55:19 / cg"
!

refersToLiteral:aLiteral
    "return true if the receiver or recursively any array element in the
     receiver referes to aLiteral"

    self do: [ :el | 
        el == aLiteral ifTrue:[^true].
        el class == Array ifTrue:[
            (el refersToLiteral: aLiteral) ifTrue: [^true]
        ]
    ].
    ^ false

    "
     #(1 2 3) refersToLiteral:#foo  
     #(1 2 3 foo bar baz) refersToLiteral:#foo 
     #(1 2 3 (((bar foo))) bar baz) refersToLiteral:#foo  
    "

    "Modified: 22.4.1996 / 12:41:46 / cg"
! !

!Array methodsFor:'testing'!

identityIndexOf:anElement or:alternative 
    "search the array for anElement or alternative; 
     return the index of anElement if found, or the index of anAlternative,
     if not found. If anAlternative is also not found, return 0.
     This is a special interface for high-speed searching in an array
     and at the same time searching for an empty slot.
     Do not use this method for your application classes, since it is
     not portable (i.e. other smalltalks do not offer this)"

%{  /* NOCONTEXT */

    REGISTER int index;
    REGISTER OBJ o, el1, el2;
    REGISTER OBJ *op;
    REGISTER unsigned int nIndex;
    int altIndex = 0;
    int nInsts;

    index = 0;
    nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
    index += nInsts;
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    el1 = anElement; el2 = alternative; 
    op = & (__InstPtr(self)->i_instvars[index]);
    while (index++ < nIndex) {
	if ((o = *op++) == el1) {
	    RETURN ( __MKSMALLINT(index - nInsts) );
	}
	if (o == el2) {
	    if (altIndex == 0) {
		altIndex = index;
	    }
	}
    }
    RETURN ( __MKSMALLINT(altIndex) );
%}

    "
     #(1 2 3 4 5 6 7 8 9) identityIndexOf:3 or:5
     #(1 2 0 4 5 6 7 8 9) identityIndexOf:3 or:5
     #(1 2 0 4 5 6 7 3 9) identityIndexOf:3 or:5
     #(1 2 3 4 5 nil 7 3 9) identityIndexOf:3 or:nil 
     #(1 2 nil 4 5 6 7 3 9) identityIndexOf:3 or:nil  
     #(1 2 nil 4 5 6 7 8 9) identityIndexOf:3 or:nil 
     #() identityIndexOf:3 or:nil        
     #(1 2) identityIndexOf:3 or:nil 
    "
!

identityIndexOf:anElement startingAt:start
    "search the array for anElement; return index if found, 0 otherwise
     - reimplemented for speed"

%{  /* NOCONTEXT */

    REGISTER int index;
    REGISTER OBJ el;
    REGISTER OBJ *op;
    REGISTER unsigned int nIndex;
    int nInsts;

    if (__isSmallInteger(start)) {
        index = __intVal(start) - 1;
        if (index >= 0) {
            nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
            index += nInsts;
            nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
            el = anElement;
            op = & (__InstPtr(self)->i_instvars[index]);
#if defined(UNROLL_LOOPS)
            {
                unsigned int i8;

                while ((i8 = index + 8) < nIndex) {
                    if (op[0] == el) { RETURN ( __MKSMALLINT(index + 1 - nInsts) ); }
                    if (op[1] == el) { RETURN ( __MKSMALLINT(index + 2 - nInsts) ); }
                    if (op[2] == el) { RETURN ( __MKSMALLINT(index + 3 - nInsts) ); }
                    if (op[3] == el) { RETURN ( __MKSMALLINT(index + 4 - nInsts) ); }
                    if (op[4] == el) { RETURN ( __MKSMALLINT(index + 5 - nInsts) ); }
                    if (op[5] == el) { RETURN ( __MKSMALLINT(index + 6 - nInsts) ); }
                    if (op[6] == el) { RETURN ( __MKSMALLINT(index + 7 - nInsts) ); }
                    if (op[7] == el) { RETURN ( __MKSMALLINT(index + 8 - nInsts) ); }
                    index = i8;
                    op += 8;
                }
            }
#endif
            while (index++ < nIndex) {
                if (*op++ == el) {
                    RETURN ( __MKSMALLINT(index - nInsts) );
                }
            }
        }
        RETURN ( __MKSMALLINT(0) );
    }
%}.
    ^ self indexNotInteger


!

identityIndexOf:anElement startingAt:start endingAt:stop
    "search the array for anElement in the range start..stop; 
     return the index if found, 0 otherwise.
     - reimplemented for speed when searching in OrderedCollections"

%{  /* NOCONTEXT */

    REGISTER int index;
    REGISTER OBJ el;
    REGISTER OBJ *op;
    REGISTER unsigned int lastIndex;
    unsigned int nIndex;
    int nInsts;

    if (__bothSmallInteger(start, stop)) {
        index = __intVal(start) - 1;
        if (index >= 0) {
            nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
            index += nInsts;
            lastIndex = nInsts + __intVal(stop);
            nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
            if (nIndex < lastIndex) {
                lastIndex = nIndex;
            }
            el = anElement;
            op = & (__InstPtr(self)->i_instvars[index]);
#if defined(UNROLL_LOOPS)
            {
                unsigned int i8;

                while ((i8 = index + 8) < lastIndex) {
                    if (op[0] == el) { RETURN ( __MKSMALLINT(index + 1 - nInsts) ); }
                    if (op[1] == el) { RETURN ( __MKSMALLINT(index + 2 - nInsts) ); }
                    if (op[2] == el) { RETURN ( __MKSMALLINT(index + 3 - nInsts) ); }
                    if (op[3] == el) { RETURN ( __MKSMALLINT(index + 4 - nInsts) ); }
                    if (op[4] == el) { RETURN ( __MKSMALLINT(index + 5 - nInsts) ); }
                    if (op[5] == el) { RETURN ( __MKSMALLINT(index + 6 - nInsts) ); }
                    if (op[6] == el) { RETURN ( __MKSMALLINT(index + 7 - nInsts) ); }
                    if (op[7] == el) { RETURN ( __MKSMALLINT(index + 8 - nInsts) ); }
                    index = i8;
                    op += 8;
                }
            }
#endif
            while (index++ < lastIndex) {
                if (*op++ == el) {
                    RETURN ( __MKSMALLINT(index - nInsts) );
                }
            }
        }
        RETURN ( __MKSMALLINT(0) );
    }
%}.
    ^ self indexNotInteger

!

includes:anObject
    "return true, if the argument, anObject is contained in the array
     - reimplemented for speed"

    |element|

%{  /* NOCONTEXT */

    /* 
     * first, do a quick check using ==
     * this does not need a context or message send.
     * In many cases this will already find a match.
     */
    REGISTER int index;
    REGISTER OBJ o;
    unsigned int nIndex;

    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);

    /*
     * however, the search is limited to the first 1000
     * elements, since otherwise, we may spend too much time
     * searching for identity if an equal value is found early
     * (except if searching for nil - there is no need for equal compare ...)
     */
    if (nIndex > 1000) {
	if (o != nil)
	    nIndex = 1000;
    }

    o = anObject;
#if defined(UNROLL_LOOPS)
    {
	unsigned int i8;

	while ((i8 = index + 8) < nIndex) {
	    if (__InstPtr(self)->i_instvars[index] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+1] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+2] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+3] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+4] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+5] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+6] == o) { RETURN ( true ); }
	    if (__InstPtr(self)->i_instvars[index+7] == o) { RETURN ( true ); }
	    index = i8;
	}
    }
#endif
    while (index < nIndex) {
	if (__InstPtr(self)->i_instvars[index++] == o) {
	    RETURN ( true );
	}
    }
    if (o == nil) {
	RETURN ( false );
    }
%}
.
%{
    /* 
     * then do a slow(er) check using =
     */
    REGISTER int index;
    unsigned int nIndex;
    static struct inlineCache eq = _ILC1;

    /* 
     * sorry: cannot access the stuff from above ...
     */
    nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
    index = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);

    while (index < nIndex) {
	element = __InstPtr(self)->i_instvars[index++];
	if (element != nil) {
	    if ((*eq.ilc_func)(anObject,
			       @symbol(=),
			       CON_COMMA nil,&eq,
			       element)==true) {
		RETURN ( true );
	    }
	}
    }
%}.
    ^ false
!

indexOf:anElement startingAt:start
    "search the array for anElement; return index if found, 0 otherwise
     - reimplemented for speed"

    |element|
%{
    REGISTER int index;
    unsigned int nIndex, nInsts;
    static struct inlineCache eq = _ILC1;

    if (__isSmallInteger(start)) {
        index = __intVal(start) - 1;
        if (index >= 0) {
            nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
            index += nInsts;
            nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
            if (anElement != nil) {
#define SPECIAL_STRING_OPT
#ifdef SPECIAL_STRING_OPT
                if (__isString(anElement)) {
                    while (index < nIndex) {
                        element = __InstPtr(self)->i_instvars[index++];
                        if (__isNonNilObject(element)) {
                            if (element == anElement) {
                                RETURN ( __MKSMALLINT(index - nInsts) );
                            }
                            if (__qClass(element) == @global(String)) {
                                if (strcmp(__stringVal(anElement), __stringVal(element)) == 0) {
                                    RETURN ( __MKSMALLINT(index - nInsts) );
                                }
                            } else {
                                if ((*eq.ilc_func)(anElement, @symbol(=), CON_COMMA nil,&eq, element) == true) {
                                    RETURN ( __MKSMALLINT(index - nInsts) );
                                }
                            }
                        }
                    }
                    RETURN (__MKSMALLINT(0));
                }
#endif
                while (index < nIndex) {
                    element = __InstPtr(self)->i_instvars[index++];
                    if (element != nil) {
                        if ((element == anElement) 
                         || ((*eq.ilc_func)(anElement,
                                            @symbol(=), 
                                            CON_COMMA nil,&eq,
                                            element) == true)) {
                            RETURN ( __MKSMALLINT(index - nInsts) );
                        }
                    }
                }
            } else {
                /* search for nil */
#if defined(UNROLL_LOOPS)
                {
                    unsigned int i8;

                    while ((i8 = index + 8) < nIndex) {
                        if (__InstPtr(self)->i_instvars[index] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 1) ); }
                        if (__InstPtr(self)->i_instvars[index+1] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 2) ); }
                        if (__InstPtr(self)->i_instvars[index+2] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 3) ); }
                        if (__InstPtr(self)->i_instvars[index+3] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 4) ); }
                        if (__InstPtr(self)->i_instvars[index+4] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 5) ); }
                        if (__InstPtr(self)->i_instvars[index+5] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 6) ); }
                        if (__InstPtr(self)->i_instvars[index+6] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 7) ); }
                        if (__InstPtr(self)->i_instvars[index+7] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 8) ); }
                        index = i8;
                    }
                }
#endif

                while (index < nIndex) {
                    if (__InstPtr(self)->i_instvars[index++] == nil) {
                        RETURN ( __MKSMALLINT(index - nInsts) );
                    }
                }
            }
        }
        RETURN (__MKSMALLINT(0));
    }
%}.
    ^ self indexNotInteger


!

indexOf:anElement startingAt:start endingAt:stop
    "search the array for anElement in the range start..stop; 
     Return the index if found, 0 otherwise.
     - reimplemented for speed when searching in OrderedCollections"

    |element|
%{
    REGISTER int index;
    unsigned int lastIndex, nIndex, nInsts;
    static struct inlineCache eq = _ILC1;

    if (__bothSmallInteger(start, stop)) {
        index = __intVal(start) - 1;
        if (index >= 0) {
            nInsts = __intVal(__ClassInstPtr(__qClass(self))->c_ninstvars);
            index += nInsts;
            lastIndex = nInsts + __intVal(stop);
            nIndex = __BYTES2OBJS__(__qSize(self) - OHDR_SIZE);
            if (nIndex < lastIndex) {
                lastIndex = nIndex;
            }

            if (anElement != nil) {
#ifdef SPECIAL_STRING_OPT
                if (__isString(anElement)) {
                    while (index < lastIndex) {
                        element = __InstPtr(self)->i_instvars[index++];
                        if (__isNonNilObject(element)) {
                            if (element == anElement) {
                                RETURN ( __MKSMALLINT(index - nInsts) );
                            }
                            if (__qClass(element) == @global(String)) {
                                if (strcmp(__stringVal(anElement), __stringVal(element)) == 0) {
                                    RETURN ( __MKSMALLINT(index - nInsts) );
                                }
                            } else {
                                if ((*eq.ilc_func)(anElement, @symbol(=), CON_COMMA nil,&eq, element) == true) {
                                    RETURN ( __MKSMALLINT(index - nInsts) );
                                }
                            }
                        }
                    }
                    RETURN (__MKSMALLINT(0));
                }
#endif
                while (index < lastIndex) {
                    element = __InstPtr(self)->i_instvars[index++];
                    if (element != nil) {
                        if ((element == anElement) 
                         || ((*eq.ilc_func)(anElement,
                                            @symbol(=), 
                                            CON_COMMA nil,&eq,
                                            element) == true)) {
                            RETURN ( __MKSMALLINT(index - nInsts) );
                        }
                    }
                }
            } else {
                if (__isSmallInteger(anElement)) {
                    /* search for a small number */
                    while (index < lastIndex) {
                        element = __InstPtr(self)->i_instvars[index++];
                        if (element == anElement) {
                            RETURN ( __MKSMALLINT(index - nInsts) );
                        }
                        if (!__isSmallInteger(element)) {
                            if ((*eq.ilc_func)(anElement,
                                                @symbol(=), 
                                                CON_COMMA nil,&eq,
                                                element) == true) {
                                RETURN ( __MKSMALLINT(index - nInsts) );
                            }
                        }
                    }
                } else {
                    /* search for nil */
#if defined(UNROLL_LOOPS)
                    {
                        unsigned int i8;

                        while ((i8 = index + 8) < lastIndex) {
                            if (__InstPtr(self)->i_instvars[index] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 1) ); }
                            if (__InstPtr(self)->i_instvars[index+1] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 2) ); }
                            if (__InstPtr(self)->i_instvars[index+2] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 3) ); }
                            if (__InstPtr(self)->i_instvars[index+3] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 4) ); }
                            if (__InstPtr(self)->i_instvars[index+4] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 5) ); }
                            if (__InstPtr(self)->i_instvars[index+5] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 6) ); }
                            if (__InstPtr(self)->i_instvars[index+6] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 7) ); }
                            if (__InstPtr(self)->i_instvars[index+7] == nil) { RETURN ( __MKSMALLINT(index - nInsts + 8) ); }
                            index = i8;
                        }
                    }
#endif

                    while (index < lastIndex) {
                        if (__InstPtr(self)->i_instvars[index++] == nil) {
                            RETURN ( __MKSMALLINT(index - nInsts) );
                        }
                    }
                }
            }
        }
        RETURN (__MKSMALLINT(0));
    }
%}.
    ^ self indexNotInteger
! !

!Array  class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Array.st,v 1.71 1996-06-30 11:02:29 cg Exp $'
! !